'From Pharo1.0beta of 16 May 2008 [Latest update: #10487] on 19 October 2009 at 4:57:33 pm'! BracketSliderMorph subclass: #AColorSelectorMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !AColorSelectorMorph commentStamp: 'gvc 5/18/2007 13:52' prior: 0! ColorComponentSelector showing an alpha gradient over a hatched background.! !AColorSelectorMorph methodsFor: 'accessing' stamp: 'gvc 9/3/2009 13:43'! color: aColor "Set the gradient colors." super color: aColor asNontranslucentColor. self fillStyle: self defaultFillStyle! ! !AColorSelectorMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/3/2009 13:43'! defaultFillStyle "Answer the hue gradient." ^(GradientFillStyle colors: {self color alpha: 0. self color}) origin: self topLeft; direction: (self bounds isWide ifTrue: [self width@0] ifFalse: [0@self height])! ! !AColorSelectorMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 09:17'! hatchForm "Answer a form showing a grid hatch pattern." ^ColorPresenterMorph hatchForm! ! !AColorSelectorMorph methodsFor: 'drawing' stamp: 'gvc 9/19/2006 14:28'! drawOn: aCanvas "Draw a hatch pattern first." aCanvas fillRectangle: self innerBounds fillStyle: (InfiniteForm with: self hatchForm). super drawOn: aCanvas ! ! !AColorSelectorMorph methodsFor: 'initialization' stamp: 'gvc 9/26/2006 11:54'! initialize "Initialize the receiver." super initialize. self value: 1.0; color: Color black! ! !AColorSelectorMorph methodsFor: 'visual properties' stamp: 'gvc 9/19/2006 15:46'! fillStyle: fillStyle "If it is a color then override with gradient." fillStyle isColor ifTrue: [self color: fillStyle] ifFalse: [super fillStyle: fillStyle]! ! TestCase subclass: #ATestCase instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Traits'! !ATestCase methodsFor: 'as yet unclassified' stamp: 'oscar.nierstrasz 10/18/2009 14:59'! testRequirement " self debug: #testRequirement " | class | class := Object subclass: #AClassForTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: self class category. [ class compile: 'call ^ self isCalled'. self assert: (class requiredSelectors includes: #isCalled). class compile: 'isCalled ^ 1'. "Fail here:" self deny: (class requiredSelectors includes: #isCalled)] ensure: [class removeFromSystem. RequiredSelectors current clearOut: class ] ! ! Exception subclass: #Abort instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !Abort methodsFor: 'as yet unclassified' stamp: 'ajh 3/24/2003 00:55'! defaultAction "No one has handled this error, but now give them a chance to decide how to debug it. If none handle this either then open debugger (see UnhandedError-defaultAction)" UnhandledError signalForException: self! ! DialogWindow subclass: #AboutDialogWindow instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !AboutDialogWindow commentStamp: 'gvc 5/18/2007 13:53' prior: 0! Default superclass for application about dialogs.! !AboutDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/12/2007 16:32'! newButtons "Answer new buttons as appropriate." ^{self newCloseButton isDefault: true}! ! Object subclass: #AbstractEvent instanceVariableNames: 'item itemKind environment' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'! !AbstractEvent methodsFor: 'accessing' stamp: 'rw 6/30/2003 08:22'! item "Return the item that triggered the event (typically the name of a class, a category, a protocol, a method)." ^item! ! !AbstractEvent methodsFor: 'accessing' stamp: 'rw 7/10/2003 12:43'! itemCategory ^self environmentAt: self class categoryKind! ! !AbstractEvent methodsFor: 'accessing' stamp: 'rw 7/10/2003 12:43'! itemClass ^self environmentAt: self class classKind! ! !AbstractEvent methodsFor: 'accessing' stamp: 'rw 7/14/2003 12:10'! itemExpression ^self environmentAt: self class expressionKind! ! !AbstractEvent methodsFor: 'accessing' stamp: 'rw 6/30/2003 08:22'! itemKind "Return the kind of the item of the event (#category, #class, #protocol, #method, ...)" ^itemKind! ! !AbstractEvent methodsFor: 'accessing' stamp: 'rw 7/10/2003 12:44'! itemMethod ^self environmentAt: self class methodKind! ! !AbstractEvent methodsFor: 'accessing' stamp: 'rw 7/10/2003 12:44'! itemProtocol ^self environmentAt: self class protocolKind! ! !AbstractEvent methodsFor: 'accessing' stamp: 'NS 1/27/2004 10:38'! itemRequestor ^self environmentAt: #requestor! ! !AbstractEvent methodsFor: 'accessing' stamp: 'NS 1/27/2004 10:38'! itemSelector ^self environmentAt: #selector! ! !AbstractEvent methodsFor: 'printing' stamp: 'NS 1/19/2004 17:52'! printOn: aStream self printEventKindOn: aStream. aStream nextPutAll: ' Event for item: '; print: self item; nextPutAll: ' of kind: '; print: self itemKind! ! !AbstractEvent methodsFor: 'testing' stamp: 'rw 6/30/2003 08:34'! isAdded ^false! ! !AbstractEvent methodsFor: 'testing' stamp: 'NS 1/19/2004 18:41'! isCategoryKnown ^self itemCategory notNil! ! !AbstractEvent methodsFor: 'testing' stamp: 'rw 7/10/2003 15:01'! isCommented ^false! ! !AbstractEvent methodsFor: 'testing' stamp: 'rw 7/14/2003 10:15'! isDoIt ^false! ! !AbstractEvent methodsFor: 'testing' stamp: 'NS 1/19/2004 15:09'! isModified ^false! ! !AbstractEvent methodsFor: 'testing' stamp: 'NS 1/21/2004 09:40'! isProtocolKnown ^self itemCategory notNil! ! !AbstractEvent methodsFor: 'testing' stamp: 'rw 7/1/2003 19:53'! isRecategorized ^false! ! !AbstractEvent methodsFor: 'testing' stamp: 'rw 6/30/2003 08:34'! isRemoved ^false! ! !AbstractEvent methodsFor: 'testing' stamp: 'rw 7/1/2003 11:35'! isRenamed ^false! ! !AbstractEvent methodsFor: 'testing' stamp: 'NS 1/27/2004 12:44'! isReorganized ^ false! ! !AbstractEvent methodsFor: 'triggering' stamp: 'rw 7/14/2003 17:06'! trigger: anEventManager "Trigger the event manager." anEventManager triggerEvent: self eventSelector with: self.! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'rw 7/10/2003 12:10'! changeKind ^self class changeKind! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'rw 7/10/2003 12:43'! environmentAt: anItemKind (self itemKind = anItemKind) ifTrue: [^self item]. ^environment at: anItemKind ifAbsent: [nil]! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'rw 7/10/2003 12:20'! eventSelector ^self class eventSelectorBlock value: itemKind value: self changeKind! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'rw 7/10/2003 12:36'! item: anItem kind: anItemKind item := anItem. itemKind := anItemKind. environment := Dictionary new! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'rw 7/10/2003 12:37'! itemCategory: aCategory environment at: self class categoryKind put: aCategory! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'rw 7/10/2003 12:36'! itemClass: aClass environment at: self class classKind put: aClass! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'rw 7/14/2003 12:11'! itemExpression: anExpression environment at: self class expressionKind put: anExpression! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'rw 7/10/2003 12:38'! itemMethod: aMethod environment at: self class methodKind put: aMethod! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'rw 7/10/2003 12:38'! itemProtocol: aProtocol environment at: self class protocolKind put: aProtocol! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'NS 1/27/2004 10:38'! itemRequestor: requestor environment at: #requestor put: requestor! ! !AbstractEvent methodsFor: 'private-accessing' stamp: 'NS 1/27/2004 10:39'! itemSelector: aSymbol environment at: #selector put: aSymbol! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AbstractEvent class instanceVariableNames: ''! !AbstractEvent class methodsFor: 'accessing' stamp: 'NS 1/16/2004 14:08'! allChangeKinds "AbstractEvent allChangeKinds" ^AbstractEvent allSubclasses collect: [:cl | cl changeKind]! ! !AbstractEvent class methodsFor: 'accessing' stamp: 'bvs 7/20/2004 12:12'! allItemKinds "self allItemKinds" ^(AbstractEvent class organization listAtCategoryNamed: #'item kinds') collect: [:sel | self perform: sel]! ! !AbstractEvent class methodsFor: 'accessing' stamp: 'rw 7/10/2003 12:08'! changeKind "Return a symbol, with a : as last character, identifying the change kind." self subclassResponsibility! ! !AbstractEvent class methodsFor: 'accessing' stamp: 'rw 7/10/2003 12:18'! eventSelectorBlock ^[:itemKind :changeKind | itemKind, changeKind, 'Event:']! ! !AbstractEvent class methodsFor: 'accessing' stamp: 'rw 7/10/2003 12:19'! itemChangeCombinations ^self supportedKinds collect: [:itemKind | self eventSelectorBlock value: itemKind value: self changeKind]! ! !AbstractEvent class methodsFor: 'accessing' stamp: 'rw 7/10/2003 12:04'! supportedKinds "All the kinds of items that this event can take. By default this is all the kinds in the system. But subclasses can override this to limit the choices. For example, the SuperChangedEvent only works with classes, and not with methods, instance variables, ..." ^self allItemKinds! ! !AbstractEvent class methodsFor: 'accessing' stamp: 'rw 7/10/2003 11:39'! systemEvents "Return all the possible events in the system. Make a cross product of the items and the change types." "self systemEvents" ^self allSubclasses inject: OrderedCollection new into: [:allEvents :eventClass | allEvents addAll: eventClass itemChangeCombinations; yourself]! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'ab 2/10/2005 16:32'! classCategory: aName ^ self item: aName kind: AbstractEvent categoryKind.! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'NS 1/19/2004 18:42'! class: aClass ^ self item: aClass kind: AbstractEvent classKind.! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'NS 1/19/2004 18:42'! class: aClass category: cat | instance | instance := self class: aClass. instance itemCategory: cat. ^instance! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'rw 7/9/2003 11:19'! item: anItem kind: anItemKind ^self basicNew item: anItem kind: anItemKind! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'NS 1/16/2004 14:19'! method: aMethod class: aClass | instance | instance := self item: aMethod kind: self methodKind. instance itemClass: aClass. ^instance! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'NS 1/16/2004 14:20'! method: aMethod protocol: prot class: aClass | instance | instance := self method: aMethod class: aClass. instance itemProtocol: prot. ^instance! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'NS 1/27/2004 10:48'! method: aMethod selector: aSymbol class: aClass | instance | instance := self item: aMethod kind: self methodKind. instance itemSelector: aSymbol. instance itemClass: aClass. ^instance! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'NS 1/27/2004 10:49'! method: aMethod selector: aSymbol class: aClass requestor: requestor | instance | instance := self method: aMethod selector: aSymbol class: aClass. instance itemRequestor: requestor. ^instance! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'NS 1/27/2004 10:49'! method: aMethod selector: aSymbol protocol: prot class: aClass | instance | instance := self method: aMethod selector: aSymbol class: aClass. instance itemProtocol: prot. ^instance! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'NS 1/27/2004 10:50'! method: aMethod selector: aSymbol protocol: prot class: aClass requestor: requestor | instance | instance := self method: aMethod selector: aSymbol protocol: prot class: aClass. instance itemRequestor: requestor. ^instance! ! !AbstractEvent class methodsFor: 'instance creation' stamp: 'rw 6/30/2003 09:20'! new "Override new to trigger an error, since we want to use specialized methods to create basic and higher-level events." ^self error: 'Instances can only be created using specialized instance creation methods.'! ! !AbstractEvent class methodsFor: 'item kinds' stamp: 'rw 7/9/2003 11:12'! categoryKind ^#category! ! !AbstractEvent class methodsFor: 'item kinds' stamp: 'rw 7/9/2003 11:12'! classKind ^#class! ! !AbstractEvent class methodsFor: 'item kinds' stamp: 'rw 7/14/2003 11:41'! expressionKind ^#expression! ! !AbstractEvent class methodsFor: 'item kinds' stamp: 'rw 7/9/2003 11:12'! methodKind ^#method! ! !AbstractEvent class methodsFor: 'item kinds' stamp: 'rw 7/10/2003 12:36'! protocolKind ^#protocol! ! !AbstractEvent class methodsFor: 'temporary' stamp: 'rw 7/11/2003 10:23'! comment1 "Smalltalk organization removeElement: #ClassForTestingSystemChanges3 Smalltalk garbageCollect Smalltalk organizati classify:under: SystemChangeNotifier uniqueInstance releaseAll SystemChangeNotifier uniqueInstance noMoreNotificationsFor: aDependent. aDependent := SystemChangeNotifierTest new. SystemChangeNotifier uniqueInstance notifyOfAllSystemChanges: aDependent using: #event: SystemChangeNotifier uniqueInstance classAdded: #Foo inCategory: #FooCat | eventSource dependentObject | eventSource := EventManager new. dependentObject := Object new. register - dependentObject becomes dependent: eventSource when: #anEvent send: #error to: dependentObject. unregister dependentObject: eventSource removeDependent: dependentObject. [eventSource triggerEvent: #anEvent] on: Error do: [:exc | self halt: 'Should not be!!']."! ! !AbstractEvent class methodsFor: 'temporary' stamp: 'rw 7/11/2003 10:24'! comment2 "HTTPSocket useProxyServerNamed: 'proxy.telenet.be' port: 8080 TestRunner open -------------------- We propose two orthogonal groups to categorize each event: (1) the 'change type': added, removed, modified, renamed + the composite 'changed' (see below for an explanation) (2) the 'item type': class, method, instance variable, pool variable, protocol, category + the composite 'any' (see below for an explanation). The list of supported events is the cross product of these two lists (see below for an explicit enumeration of the events). Depending on the change type, certain information related to the change is always present (for adding, the new things that was added, for removals, what was removed, for renaming, the old and the new name, etc.). Depending on the item type, information regarding the item is present (for a method, which class it belongs to). Certain events 'overlap', for example, a method rename triggers a class change. To capture this I impose a hierarchy on the 'item types' (just put some numbers to clearly show the idea. They don't need numbers, really. Items at a certain categories are included by items one category number higher): level 1 category level 2 class level 3 instance variable, pool variable, protocol, method. Changes propagate according to this tree: any 'added', 'removed' or 'renamed' change type in level X triggers a 'changed' change type in level X - 1. A 'modified' change type does not trigger anything special. For example, a method additions triggers a class modification. This does not trigger a category modification. Note that we added 'composite events': wildcards for the 'change type' ('any' - any system additions) and for the 'item type' ('Changed' - all changes related to classes), and one for 'any change systemwide' (systemChanged). This result is this list of Events: classAdded classRemoved classModified classRenamed (?) classChanged (composite) methodAdded methodRemoved methodModified methodRenamed (?) methodChanged (composite) instanceVariableAdded instanceVariableRemoved instanceVariableModified instanceVariableRenamed (?) instanceVariableChanged (composite) protocolAdded protocolRemoved protocolModified protocolRenamed (?) protocolChanged (composite) poolVariableAdded poolVariableRemoved poolVariableModified poolVariableRenamed (?) poolChanged (composite) categoryAdded categoryRemoved categoryModified categeryRenamed (?) categoryChanged (composite) anyAdded (composite) anyRemoved (composite) anyModified (composite) anyRenamed (composite) anyChanged (composite) To check: can we pass somehow the 'source' of the change (a browser, a file-in, something else) ? Maybe by checking the context, but should not be too expensive either... I found this useful in some of my tools, but it might be too advanced to have in general. Tools that need this can always write code to check it for them. But is not always simple... Utilities (for the recent methods) and ChangeSet are the two main clients at this moment. Important: make it very explicit that the event is send synchronously (or asynchronously, would we take that route). category class comment protocol method OR category Smalltalk class comment protocol method ?? Smalltalk category \ / class / | \ comment | protocol | / method "! ! !AbstractEvent class methodsFor: 'temporary' stamp: 'rw 7/11/2003 15:43'! comment3 "Things to consider for trapping: ClassOrganizer>>#changeFromCategorySpecs: Problem: I want to trap this to send the appropriate bunch of ReCategorization events, but ClassOrganizer instances do not know where they belong to (what class, or what system); it just uses symbols. So I cannot trigger the change, because not enough information is available. This is a conceptual problem: the organization is stand-alone implementation-wise, while conceptually it belongs to a class. The clean solution could be to reroute this message to a class, but this does not work for all of the senders (that would work from the browserm but not for the file-in). Browser>>#categorizeAllUncategorizedMethods Problem: should be trapped to send a ReCategorization event. However, this is model code that should not be in the Browser. Clean solution is to move it out of there to the model, and then trap it there (or reroute it to one of the trapped places). Note: Debugger>>#contents:notifying: recompiles methods when needed, so I trapped it to get updates. However, I need to find a way to write a unit test for this. Haven't gotten around yet for doing this though... "! ! Object subclass: #AbstractFont instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Fonts'! !AbstractFont commentStamp: '' prior: 0! AbstractFont defines the generic interface that all fonts need to implement.! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 7/29/2006 14:36'! displayStrikeoutOn: aDisplayContext from: baselineStartPoint to: baselineEndPoint "display the strikeout if appropriate for the receiver"! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 7/29/2006 13:51'! displayUnderlineOn: aDisplayContext from: baselineStartPoint to: baselineEndPoint "display the underline if appropriate for the receiver"! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 8/10/2006 07:16'! emphasisString "Answer a translated string that represents the receiver's emphasis." ^self emphasisStringFor: self emphasis! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 8/10/2006 07:13'! emphasisStringFor: emphasisCode "Answer a translated string that represents the attributes given in emphasisCode." ^self class emphasisStringFor: emphasisCode! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 3/29/2007 13:43'! hasDistinctGlyphsForAll: asciiString "Answer true if the receiver has glyphs for all the characters in asciiString and no single glyph is shared by more than one character, false otherwise. The default behaviour is to answer true, but subclasses may reimplement" ^true! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 3/29/2007 13:25'! hasGlyphsForAll: asciiString "Answer true if the receiver has glyphs for all the characters in asciiString, false otherwise. The default behaviour is to answer true, but subclasses may reimplement" ^true! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 4/6/2007 12:58'! isSubPixelPositioned "Answer true if the receiver is currently using subpixel positioned glyphs, false otherwise. This affects how padded space sizes are calculated when composing text. Currently, only FreeTypeFonts are subPixelPositioned, and only when not Hinted" ^false ! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 3/29/2007 13:32'! isSymbolFont "Answer true if the receiver is a Symbol font, false otherwise. The default is to answer false, subclasses can reimplement" ^false! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 3/10/2007 13:08'! kerningLeft: leftChar right: rightChar ^0! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 3/31/2007 20:17'! linearWidthOf: aCharacter "This is the scaled, unrounded advance width." ^self widthOf: aCharacter! ! !AbstractFont methodsFor: '*FreeType-addition' stamp: 'tween 4/3/2007 16:47'! widthAndKernedWidthOfLeft: leftCharacter right: rightCharacterOrNil into: aTwoElementArray "Set the first element of aTwoElementArray to the width of leftCharacter and the second element to the width of left character when kerned with rightCharacterOrNil. Answer aTwoElementArray" | w k | w := self widthOf: leftCharacter. rightCharacterOrNil isNil ifTrue:[ aTwoElementArray at: 1 put: w; at: 2 put: w] ifFalse:[ k := self kerningLeft: leftCharacter right: rightCharacterOrNil. aTwoElementArray at: 1 put: w; at: 2 put: w+k]. ^aTwoElementArray ! ! !AbstractFont methodsFor: 'accessing' stamp: 'yo 1/7/2005 11:19'! ascent self subclassResponsibility. ! ! !AbstractFont methodsFor: 'accessing' stamp: 'yo 1/7/2005 11:18'! ascentOf: aCharacter ^ self ascent. ! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 4/2/2004 11:06'! baseKern ^0! ! !AbstractFont methodsFor: 'accessing' stamp: 'yo 1/7/2005 11:18'! basicAscentOf: aCharacter ^ self ascent. ! ! !AbstractFont methodsFor: 'accessing' stamp: 'yo 1/7/2005 11:19'! basicDescentOf: aCharacter ^ self descent. ! ! !AbstractFont methodsFor: 'accessing' stamp: 'ar 5/19/2000 14:56'! characterToGlyphMap "Return the character to glyph mapping table. If the table is not provided the character scanner will query the font directly for the width of each individual character." ^nil! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 3/15/2004 18:57'! derivativeFonts ^#()! ! !AbstractFont methodsFor: 'accessing' stamp: 'yo 1/7/2005 11:20'! descent self subclassResponsibility. ! ! !AbstractFont methodsFor: 'accessing' stamp: 'yo 1/7/2005 11:20'! descentOf: aCharacter ^ self descent. ! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 8/31/2004 09:15'! familyName "Answer the name to be used as a key in the TextConstants dictionary." ^self subclassResponsibility! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 8/31/2004 09:14'! height "Answer the height of the receiver, total of maximum extents of characters above and below the baseline." ^self subclassResponsibility! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 5/26/2003 09:45'! isRegular ^false! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 8/31/2004 09:14'! lineGrid "Answer the relative space between lines" ^self subclassResponsibility! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 4/2/2004 11:33'! pixelSize "Make sure that we don't return a Fraction" ^ TextStyle pointsToPixels: self pointSize! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 4/1/2004 10:48'! pointSize self subclassResponsibility.! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 7/11/2004 21:15'! textStyle ^ TextStyle actualTextStyles detect: [:aStyle | aStyle fontArray includes: self] ifNone: [ TextStyle fontArray: { self } ]! ! !AbstractFont methodsFor: 'accessing' stamp: 'nk 3/22/2004 15:15'! textStyleName "Answer the name to be used as a key in the TextConstants dictionary." ^self familyName! ! !AbstractFont methodsFor: 'accessing' stamp: 'ar 5/19/2000 14:57'! xTable "Return the xTable for the font. The xTable defines the left x-value for each individual glyph in the receiver. If such a table is not provided, the character scanner will ask the font directly for the appropriate width of each individual character." ^nil! ! !AbstractFont methodsFor: 'caching' stamp: 'nk 3/15/2004 18:47'! releaseCachedState ! ! !AbstractFont methodsFor: 'displaying' stamp: 'ar 5/19/2000 14:59'! displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta "Draw the given string from startIndex to stopIndex at aPoint on the (already prepared) display context." ^self subclassResponsibility! ! !AbstractFont methodsFor: 'displaying' stamp: 'yo 1/7/2005 11:36'! displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY "Draw the given string from startIndex to stopIndex at aPoint on the (already prepared) display context." ^self subclassResponsibility! ! !AbstractFont methodsFor: 'displaying' stamp: 'ar 5/19/2000 14:59'! installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor "Install the receiver on the given DisplayContext (either BitBlt or Canvas) for further drawing operations." ^self subclassResponsibility! ! !AbstractFont methodsFor: 'measuring' stamp: 'lr 7/4/2009 10:42'! approxWidthOfText: aText "Return the width of aText -- quickly, and a little bit dirty. Used by lists morphs containing Text objects to get a quick, fairly accurate measure of the width of a list item." | w | (aText isNil or: [ aText size == 0 ]) ifTrue: [ ^ 0 ]. w := self widthOfString: aText asString. "If the text has no emphasis, just return the string size. If it is empasized, just approximate the width by adding about 20% to the width" ((aText runLengthFor: 1) == aText size and: [ (aText emphasisAt: 1) == 0 ]) ifTrue: [ ^ w ] ifFalse: [ ^ w * 6 // 5 ]! ! !AbstractFont methodsFor: 'measuring' stamp: 'ar 5/19/2000 14:58'! widthOf: aCharacter "Return the width of the given character" ^self subclassResponsibility! ! !AbstractFont methodsFor: 'measuring' stamp: 'ar 12/31/2001 14:25'! widthOfString: aString aString ifNil:[^0]. ^self widthOfString: aString from: 1 to: aString size. " TextStyle default defaultFont widthOfString: 'zort' 21 "! ! !AbstractFont methodsFor: 'measuring' stamp: 'lr 7/4/2009 10:42'! widthOfString: aString from: startIndex to: stopIndex "Measure the length of the given string between start and stop index" | character resultX | resultX := 0. startIndex to: stopIndex do: [ :i | character := aString at: i. resultX := resultX + (self widthOf: character) ]. ^ resultX! ! !AbstractFont methodsFor: 'measuring' stamp: 'sps 3/23/2004 15:50'! widthOfStringOrText: aStringOrText aStringOrText ifNil:[^0]. ^aStringOrText isText ifTrue:[self approxWidthOfText: aStringOrText ] ifFalse:[self widthOfString: aStringOrText ] ! ! !AbstractFont methodsFor: 'notifications' stamp: 'nk 4/2/2004 11:25'! pixelsPerInchChanged "The definition of TextStyle class>>pixelsPerInch has changed. Do whatever is necessary."! ! !AbstractFont methodsFor: 'testing' stamp: 'yo 2/12/2007 19:34'! isFontSet ^ false. ! ! !AbstractFont methodsFor: 'testing' stamp: 'nk 6/25/2003 12:54'! isTTCFont ^false! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AbstractFont class instanceVariableNames: ''! !AbstractFont class methodsFor: 'as yet unclassified' stamp: 'eem 6/11/2008 12:35'! emphasisStringFor: emphasisCode "Answer a translated string that represents the attributes given in emphasisCode." | emphases | emphasisCode = 0 ifTrue: [ ^'Normal' translated ]. emphases := (IdentityDictionary new) at: 1 put: 'Bold' translated; at: 2 put: 'Italic' translated; at: 4 put: 'Underlined' translated; at: 8 put: 'Narrow' translated; at: 16 put: 'StruckOut' translated; yourself. ^String streamContents: [ :s | | bit | bit := 1. [ bit < 32 ] whileTrue: [ | code | code := emphasisCode bitAnd: bit. code isZero ifFalse: [ s nextPutAll: (emphases at: code); space ]. bit := bit bitShift: 1 ]. s position isZero ifFalse: [ s skip: -1 ]. ]! ! DialogWindow subclass: #AbstractFontSelectorDialogWindow instanceVariableNames: 'fontFamilies selectedFont textPreviewMorph fontFamilyIndex fontSizeIndex isBold isItalic isUnderlined isStruckOut previewText' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !AbstractFontSelectorDialogWindow commentStamp: 'gvc 5/18/2007 13:04' prior: 0! Dialog based font chooser with preview.! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 15:40'! fontFamilies "Answer the set of available fonts families that are supported as Text objects in the font that they represent." ^fontFamilies ifNil: [ self fontFamilies: self defaultFontFamilies. fontFamilies]! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 15:02'! fontFamilies: anObject "Set the value of fontFamilies" fontFamilies := anObject! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 14:30'! fontFamilyIndex "Answer the value of fontFamilyIndex" ^ fontFamilyIndex! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 15:19'! fontFamilyIndex: anObject "Set the value of fontFamilyIndex" fontFamilyIndex := anObject. self updateSelectedFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 14:30'! fontSizeIndex "Answer the value of fontSizeIndex" ^ fontSizeIndex! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 15:19'! fontSizeIndex: anObject "Set the value of fontSizeIndex" fontSizeIndex := anObject. self updateSelectedFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 15:12'! isBold "Answer the value of isBold" ^ isBold! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 4/21/2009 17:07'! isBold: anObject "Set the value of isBold" isBold := anObject. self changed: #isBold! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 15:12'! isItalic "Answer the value of isItalic" ^ isItalic! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 4/21/2009 17:07'! isItalic: anObject "Set the value of isItalic" isItalic := anObject. self changed: #isItalic! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 15:12'! isStruckOut "Answer the value of isStruckOut" ^ isStruckOut! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 4/21/2009 17:07'! isStruckOut: anObject "Set the value of isStruckOut" isStruckOut := anObject. self changed: #isStruckOut! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 15:12'! isUnderlined "Answer the value of isUnderlined" ^ isUnderlined! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 4/21/2009 17:07'! isUnderlined: anObject "Set the value of isUnderlined" isUnderlined := anObject. self changed: #isUnderlined! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 4/21/2009 17:30'! previewText "Answer the value of previewText" ^previewText asText addAttribute: (TextEmphasis new emphasisCode: self textEmphasisCode)! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/18/2007 13:07'! previewText: anObject "Set the value of previewText" previewText := anObject. self changed: #previewText! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 13:41'! selectedFont "Answer the value of selectedFont" ^ selectedFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 10/9/2007 14:19'! selectedFont: anObject "Set the value of selectedFont" selectedFont := anObject ifNil: [TextStyle defaultFont]. self updateFromSelectedFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 13:41'! textPreviewMorph "Answer the value of textPreviewMorph" ^ textPreviewMorph! ! !AbstractFontSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/3/2007 13:41'! textPreviewMorph: anObject "Set the value of textPreviewMorph" textPreviewMorph := anObject! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/26/2008 15:49'! defaultFontFamilies "Answer the set of available fonts families that are supported in the font that they represent." self subclassResponsibility! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/26/2008 15:31'! defaultPreviewText "Answer the default text to use for the preview of the font." ^(33 to: 127) asByteArray asString! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/3/2007 15:47'! familyName "Answer the selected family name or nil if none." (self fontFamilyIndex between: 1 and: self fontFamilies size) ifFalse: [^nil]. ^(self fontFamilies at: self fontFamilyIndex) asString! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/3/2007 16:03'! fontSize "Answer the selected font size or nil if none." (self fontSizeIndex between: 1 and: self fontSizes size) ifFalse: [^nil]. ^self fontSizes at: self fontSizeIndex! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/3/2007 14:31'! fontSizes "Answer the set of available fonts sizes that are supported." ^#(6 7 8 9 10 11 12 13 14 15 16 18 20 21 22 24 26 28 32 36 48)! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:22'! initialize "Initialize the receiver." self isBold: false; isItalic: false; isUnderlined: false; isStruckOut: false; previewText: self defaultPreviewText; fontFamilyIndex: 0; fontSizeIndex: 0. super initialize! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 7/16/2007 13:43'! isFreeTypeInstalled "Answer whether FreeType appears to be installed." ^Smalltalk includesKey: #FreeTypeFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/26/2008 15:35'! matchingFont "Answer the font that matches the selections." self subclassResponsibility! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:02'! newBoldButtonMorph "Answer a button for the boldness of the font." ^self newButtonFor: self getState: #isBold action: #toggleBold arguments: nil getEnabled: nil labelForm: self theme smallBoldIcon help: 'Toggle bold font' translated! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:48'! newContentMorph "Answer a new content morph." self textPreviewMorph: self newTextPreviewMorph. ^(self newColumn: { (self newRow: { self newGroupbox: 'Family' translated for: self newFontFamilyMorph. (self newColumn: { (self newGroupbox: 'Style' translated for: self newFontStyleButtonRowMorph) vResizing: #shrinkWrap. self newGroupbox: 'Point size' translated for: self newFontSizeMorph}) hResizing: #shrinkWrap}) vResizing: #spaceFill. (self newGroupbox: 'Preview' translated for: self textPreviewMorph) vResizing: #shrinkWrap}) minWidth: 350; minHeight: 400! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 11:49'! newFontFamilyMorph "Answer a list for the font family of the font." |highestFont| highestFont := self fontFamilies first fontAt: 1 withStyle: TextStyle default. self fontFamilies do: [:ff | |f| f := ff fontAt: 1 withStyle: TextStyle default. f height > highestFont height ifTrue: [highestFont := f]]. ^(self newListFor: self list: #fontFamilies selected: #fontFamilyIndex changeSelected: #fontFamilyIndex: help: nil) font: highestFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 11:49'! newFontSizeMorph "Answer a list for the font size of the font." ^self newListFor: self list: #fontSizes selected: #fontSizeIndex changeSelected: #fontSizeIndex: help: nil! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:48'! newFontStyleButtonRowMorph "Answer a new font style button row morph." ^self newRow: { self newBoldButtonMorph. self newItalicButtonMorph. self newUnderlinedButtonMorph. self newStruckOutButtonMorph}! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:02'! newItalicButtonMorph "Answer a button for the italic emphasis of the font." ^self newButtonFor: self getState: #isItalic action: #toggleItalic arguments: nil getEnabled: nil labelForm: self theme smallItalicIcon help: 'Toggle italic font' translated! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:02'! newStruckOutButtonMorph "Answer a button for the struck out emphasis of the font." ^self newButtonFor: self getState: #isStruckOut action: #toggleStruckOut arguments: nil getEnabled: nil labelForm: self theme smallStrikeOutIcon help: 'Toggle struck-out font' translated! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/3/2007 16:31'! newTextPreviewMorph "Answer a text entry morph for the preview of the font." ^(self newTextEditorFor: self getText: #previewText setText: nil getEnabled: nil) vResizing: #rigid; enabled: false; extent: 20@90! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:02'! newUnderlinedButtonMorph "Answer a button for the italic emphasis of the font." ^self newButtonFor: self getState: #isUnderlined action: #toggleUnderlined arguments: nil getEnabled: nil labelForm: self theme smallUnderlineIcon help: 'Toggle underlined font' translated! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:33'! textEmphasisCode "Answer the current bitmask for the text emphasis." ^(((self isBold ifTrue: [1] ifFalse: [0]) bitOr: (self isItalic ifTrue: [2] ifFalse: [0])) bitOr: (self isUnderlined ifTrue: [4] ifFalse: [0])) bitOr: (self isStruckOut ifTrue: [16] ifFalse: [0])! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/3/2007 15:31'! toggleBold "Toggle the font bold emphasis." self isBold: self isBold not. self updateSelectedFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/3/2007 15:31'! toggleItalic "Toggle the font italic emphasis." self isItalic: self isItalic not. self updateSelectedFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/3/2007 15:31'! toggleStruckOut "Toggle the font struck out emphasis." self isStruckOut: self isStruckOut not. self updateSelectedFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/3/2007 15:31'! toggleUnderlined "Toggle the font underlined emphasis." self isUnderlined: self isUnderlined not. self updateSelectedFont! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:21'! updateFromSelectedFont "Update our state based on the selected font." self subclassResponsibility! ! !AbstractFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/4/2007 10:25'! updateSelectedFont "Update the selected font to reflect the choices." self selectedFont: self matchingFont! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AbstractFontSelectorDialogWindow class instanceVariableNames: ''! !AbstractFontSelectorDialogWindow class methodsFor: 'as yet unclassified' stamp: 'gvc 5/21/2007 12:42'! taskbarIcon "Answer the icon for the receiver in a task bar." ^MenuIcons smallFontsIcon! ! Model subclass: #AbstractHierarchicalList instanceVariableNames: 'currentSelection' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Explorer'! !AbstractHierarchicalList commentStamp: '' prior: 0! Contributed by Bob Arning as part of the ObjectExplorer package. ! !AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 6/21/1999 15:22'! genericMenu: aMenu aMenu add: 'no menu yet' target: self selector: #yourself. ^aMenu! ! !AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 4/7/1999 16:44'! getCurrentSelection ^currentSelection! ! !AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 4/7/1999 16:46'! noteNewSelection: x currentSelection := x. self changed: #getCurrentSelection. currentSelection ifNil: [^self]. currentSelection sendSettingMessageTo: self. ! ! !AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 4/7/1999 16:53'! perform: selector orSendTo: otherTarget "Selector was just chosen from a menu by a user. If can respond, then perform it on myself. If not, send it to otherTarget, presumably the editPane from which the menu was invoked." (self respondsTo: selector) ifTrue: [^ self perform: selector] ifFalse: [^ otherTarget perform: selector]! ! !AbstractHierarchicalList methodsFor: 'as yet unclassified' stamp: 'RAA 4/7/1999 16:47'! update: aSymbol aSymbol == #hierarchicalList ifTrue: [ ^self changed: #getList ]. super update: aSymbol! ! Object subclass: #AbstractLauncher instanceVariableNames: 'parameters' classVariableNames: '' poolDictionaries: '' category: 'System-Support'! !AbstractLauncher commentStamp: '' prior: 0! The class AutoStart in combination with the Launcher classes provides a mechanism for starting Squeak from the command line or a web page. Parameters on the command line or in the embed tag in the web page a parsed and stored in the lauchner's parameter dictionary. Subclasses can access these parameters to determine what to do. CommandLineLauncherExample provides an example for a command line application. if you start squeak with a command line 'class Integer' it will launch a class browser on class Integer. To enable this execute CommandLineLauncherExample activate before you save the image. To disable execute CommandLineLauncherExample deactivate The PluginLauchner is an example how to use this framework to start Squeak as a browser plugin. It looks for a parameter 'src' which should point to a file containing a squeak script.! !AbstractLauncher methodsFor: 'running' stamp: 'tk 10/24/2001 06:40'! startUp "A backstop for subclasses. Note that this is not a class message (most startUps are class messages)." ! ! !AbstractLauncher methodsFor: 'private' stamp: 'dc 5/30/2008 10:17'! commandLine: aString "Start up this launcher from within Squeak as if it Squeak been launched the given command line." | dict tokens cmd arg | dict := Dictionary new. tokens := (aString findTokens: ' ') readStream. [ cmd := tokens next. arg := tokens next. cmd ~~ nil and: [ arg ~~ nil ] ] whileTrue: [ dict at: cmd put: arg ]. self parameters: dict. self startUp! ! !AbstractLauncher methodsFor: 'private' stamp: 'mir 9/23/1999 13:18'! determineParameterNameFrom: alternateParameterNames "Determine which of the given alternate parameter names is actually used." ^alternateParameterNames detect: [:each | self includesParameter: each asUppercase] ifNone: [nil] ! ! !AbstractLauncher methodsFor: 'private' stamp: 'mir 1/11/2000 16:35'! includesParameter: parName "Return if the parameter named parName exists." ^self parameters includesKey: parName asUppercase! ! !AbstractLauncher methodsFor: 'private' stamp: 'mdr 4/10/2001 10:50'! numericParameterAtOneOf: alternateParameterNames ifAbsent: aBlock "Return the parameter named using one of the alternate names or an empty string" | parameterValue | parameterValue := self parameterAtOneOf: alternateParameterNames. parameterValue isEmpty ifTrue: [^aBlock value]. ^[Number readFrom: parameterValue] ifError: aBlock ! ! !AbstractLauncher methodsFor: 'private' stamp: 'mir 8/4/1999 14:19'! parameterAt: parName "Return the parameter named parName or an empty string" ^self parameterAt: parName ifAbsent: ['']! ! !AbstractLauncher methodsFor: 'private' stamp: 'mir 1/11/2000 16:36'! parameterAt: parName ifAbsent: aBlock "Return the parameter named parName. Evaluate the block if parameter does not exist." ^self parameters at: parName asUppercase ifAbsent: [aBlock value]! ! !AbstractLauncher methodsFor: 'private' stamp: 'mir 9/23/1999 12:09'! parameterAtOneOf: alternateParameterNames | parameterName | "Return the parameter named using one of the alternate names or an empty string" parameterName := self determineParameterNameFrom: alternateParameterNames. ^parameterName isNil ifTrue: [''] ifFalse: [self parameterAt: parameterName ifAbsent: ['']]! ! !AbstractLauncher methodsFor: 'private' stamp: 'marcus.denker 9/14/2008 18:54'! parameters parameters ifNil: [parameters := self class extractParameters]. ^parameters! ! !AbstractLauncher methodsFor: 'private' stamp: 'mir 7/29/1999 10:21'! parameters: startupParameters parameters := startupParameters! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AbstractLauncher class instanceVariableNames: ''! !AbstractLauncher class methodsFor: 'activation' stamp: 'mir 8/6/1999 18:14'! activate "Register this launcher with the auto start class" self autoStarter addLauncher: self! ! !AbstractLauncher class methodsFor: 'activation'! deactivate "Unregister this launcher with the auto start class" self autoStarter removeLauncher: self! ! !AbstractLauncher class methodsFor: 'private' stamp: 'mir 8/4/1999 13:57'! autoStarter ^AutoStart! ! !AbstractLauncher class methodsFor: 'private' stamp: 'sd 9/30/2003 13:55'! extractParameters ^ SmalltalkImage current extractParameters! ! Object subclass: #AbstractObjectsAsMethod instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-ObjectsAsMethods'! !AbstractObjectsAsMethod methodsFor: 'as yet unclassified' stamp: 'md 3/1/2006 14:25'! flushCache! ! !AbstractObjectsAsMethod methodsFor: 'as yet unclassified' stamp: 'md 3/1/2006 14:23'! methodClass: aMethodClass! ! !AbstractObjectsAsMethod methodsFor: 'as yet unclassified' stamp: 'md 3/1/2006 14:23'! selector: aSymbol! ! Morph subclass: #AbstractResizerMorph instanceVariableNames: 'dotColor handleColor lastMouse' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Windows'! !AbstractResizerMorph commentStamp: 'jmv 1/29/2006 17:15' prior: 0! I am the superclass of a hierarchy of morph specialized in allowing the user to resize or rearrange windows and panes.! !AbstractResizerMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/27/2008 21:34'! adoptPaneColor: paneColor "Just get the resizer fill style for the theme." paneColor ifNil: [^super adoptPaneColor: paneColor]. self fillStyle: (self theme resizerGripNormalFillStyleFor: self)! ! !AbstractResizerMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/12/2007 10:59'! mouseUp: anEvent "Change the cursor back to normal if necessary." (self bounds containsPoint: anEvent cursorPoint) ifFalse: [ anEvent hand showTemporaryCursor: nil. self setDefaultColors; changed]! ! !AbstractResizerMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 5/13/2008 10:20'! shouldDraw "Answer whether the resizer should be drawn." ^self fillStyle isTransparent not! ! !AbstractResizerMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 5/13/2008 10:35'! shouldInvalidateOnMouseTransition "Answer whether the resizer should be invalidated when the mouse enters or leaves." ^false! ! !AbstractResizerMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 5/13/2008 10:36'! mouseEnter: anEvent self isCursorOverHandle ifTrue: [self setInverseColors. self shouldInvalidateOnMouseTransition ifTrue: [self changed]. "avoid unnecessary invalidation" anEvent hand showTemporaryCursor: self resizeCursor]! ! !AbstractResizerMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 5/13/2008 10:36'! mouseLeave: anEvent anEvent hand showTemporaryCursor: nil. self setDefaultColors. self shouldInvalidateOnMouseTransition ifTrue: [self changed]. "avoid unnecessary invalidation"! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'jrp 7/5/2005 21:36'! dotColor ^ dotColor ifNil: [self setDefaultColors. dotColor]! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'jrp 7/5/2005 21:35'! handleColor ^ handleColor ifNil: [self setDefaultColors. handleColor]! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'jrp 7/5/2005 21:37'! handlesMouseDown: anEvent ^ true! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'jrp 7/5/2005 21:37'! handlesMouseOver: anEvent ^ true ! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'md 2/24/2006 23:01'! initialize super initialize. self color: Color transparent! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'jrp 7/5/2005 21:40'! isCursorOverHandle ^ true! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'jrp 7/5/2005 21:42'! mouseDown: anEvent lastMouse := anEvent cursorPoint! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'jrp 7/5/2005 21:37'! resizeCursor self subclassResponsibility! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'jrp 7/29/2005 13:25'! setDefaultColors handleColor := Color lightGray lighter lighter. dotColor := Color gray lighter! ! !AbstractResizerMorph methodsFor: 'as yet unclassified' stamp: 'jrp 7/30/2005 21:30'! setInverseColors handleColor := Color lightGray. dotColor := Color white! ! Object subclass: #AbstractSoundSystem instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Support'! !AbstractSoundSystem commentStamp: 'gk 2/24/2004 08:34' prior: 0! This is the abstract base class for a sound system. A sound system offers a small protocol for playing sounds and making beeps and works like a facade towards the rest of Squeak. A sound system is registered in the application registry SoundService and can be accessed by "SoundService default" like for example: SoundService default playSoundNamed: 'croak' The idea is that as much sound playing as possible should go through this facade. This way we decouple the sound system from the rest of Squeak and make it pluggable. It also is a perfect spot to check for the Preference class>>soundsEnabled. Two basic subclasses exist at the time of this writing, the BaseSoundSystem which represents the standard Squeak sound system, and the DummySoundSystem which is a dummy implementation that can be used when there is no sound card available, or when the base sound system isn't in the image, or when you simply don't want to use the available sound card.! !AbstractSoundSystem methodsFor: 'misc' stamp: 'gk 2/23/2004 19:52'! randomBitsFromSoundInput: bitCount self subclassResponsibility! ! !AbstractSoundSystem methodsFor: 'misc' stamp: 'gk 2/23/2004 19:52'! sampledSoundChoices self subclassResponsibility! ! !AbstractSoundSystem methodsFor: 'misc' stamp: 'gk 2/23/2004 19:53'! shutDown "Default is to do nothing."! ! !AbstractSoundSystem methodsFor: 'misc' stamp: 'gk 2/23/2004 19:56'! soundNamed: soundName self subclassResponsibility! ! !AbstractSoundSystem methodsFor: 'playing' stamp: 'gk 2/24/2004 23:27'! beep "Make a primitive beep." self subclassResponsibility! ! !AbstractSoundSystem methodsFor: 'playing' stamp: 'gk 2/23/2004 19:47'! playSampledSound: samples rate: rate self subclassResponsibility! ! !AbstractSoundSystem methodsFor: 'playing' stamp: 'gk 2/23/2004 19:50'! playSoundNamed: soundName self subclassResponsibility! ! !AbstractSoundSystem methodsFor: 'playing' stamp: 'gk 2/23/2004 19:51'! playSoundNamed: soundName ifAbsentReadFrom: aifFileName self subclassResponsibility! ! !AbstractSoundSystem methodsFor: 'playing' stamp: 'gk 2/23/2004 19:51'! playSoundNamedOrBeep: soundName self subclassResponsibility! ! PluggableTextMorph subclass: #AcceptableCleanTextMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Pluggable Widgets'! !AcceptableCleanTextMorph methodsFor: 'menu commands' stamp: 'dgd 2/21/2003 22:50'! accept "Overridden to allow accept of clean text" | textToAccept ok | textToAccept := textMorph asText. ok := setTextSelector isNil or: [setTextSelector numArgs = 2 ifTrue: [model perform: setTextSelector with: textToAccept with: self] ifFalse: [model perform: setTextSelector with: textToAccept]]. ok ifTrue: [self setText: self getText. self hasUnacceptedEdits: false]! ! FileDirectory subclass: #AcornFileDirectory instanceVariableNames: '' classVariableNames: 'LegalCharMap' poolDictionaries: '' category: 'Files-Directories'! !AcornFileDirectory methodsFor: 'file name utilities' stamp: 'stephaneducasse 2/4/2006 20:31'! checkName: aFileName fixErrors: fixing "Check if the file name contains any invalid characters" | fName hasBadChars correctedName newChar| fName := super checkName: aFileName fixErrors: fixing. correctedName := String streamContents:[:s| fName do:[:c| (newChar := LegalCharMap at: c asciiValue +1) ifNotNil:[s nextPut: newChar]]]. hasBadChars := fName ~= correctedName. (hasBadChars and:[fixing not]) ifTrue:[^self error:'Invalid file name']. hasBadChars ifFalse:[^ fName]. ^ correctedName! ! !AcornFileDirectory methodsFor: 'file name utilities' stamp: 'tpr 11/5/2004 13:08'! fullPathFor: path "if the arg is an empty string, just return my path name converted via the language stuff. If the arg seems to be a rooted path, return it raw, assuming it is already ok. Otherwise cons up a path" path isEmpty ifTrue:[^pathName asSqueakPathName]. ((path includes: $$ ) or:[path includes: $:]) ifTrue:[^path]. ^pathName asSqueakPathName, self slash, path! ! !AcornFileDirectory methodsFor: 'path access' stamp: 'tpr 11/30/2003 21:42'! pathParts "Return the path from the root of the file system to this directory as an array of directory names. This version tries to cope with the RISC OS' strange filename formatting; filesystem::discname/$/path/to/file where the $ needs to be considered part of the filingsystem-discname atom." | pathList | pathList := super pathParts. (pathList indexOf: '$') = 2 ifTrue: ["if the second atom is root ($) then stick $ on the first atom and drop the second. Yuck" ^ Array streamContents: [:a | a nextPut: (pathList at: 1), '/$'. 3 to: pathList size do: [:i | a nextPut: (pathList at: i)]]]. ^ pathList! ! !AcornFileDirectory methodsFor: 'testing' stamp: 'tpr 4/28/2004 21:54'! directoryExists: filenameOrPath "if the path is a root,we have to treat it carefully" (filenameOrPath endsWith: '$') ifTrue:[^(FileDirectory on: filenameOrPath) exists]. ^(self directoryNamed: filenameOrPath ) exists! ! !AcornFileDirectory methodsFor: 'private' stamp: 'stephaneducasse 2/4/2006 20:31'! directoryContentsFor: fullPath "Return a collection of directory entries for the files and directories in the directory with the given path. See primLookupEntryIn:index: for further details." "FileDirectory default directoryContentsFor: ''" | entries extraPath | entries := super directoryContentsFor: fullPath. fullPath isNullPath ifTrue: [ "For Acorn we also make sure that at least the parent of the current dir is added - sometimes this is in a filing system that has not been (or cannot be) polled for disc root names" extraPath := self class default containingDirectory. "Only add the extra path if we haven't already got the root of the current dir in the list" entries detect: [:ent | extraPath fullName beginsWith: ent name] ifNone: [entries := entries copyWith: (DirectoryEntry name: extraPath fullName creationTime: 0 modificationTime: 0 isDirectory: true fileSize: 0)]]. ^ entries ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AcornFileDirectory class instanceVariableNames: ''! !AcornFileDirectory class methodsFor: '*network-uri' stamp: 'tpr 5/4/2005 17:22'! privateFullPathForURI: aURI "derive the full filepath from aURI" | first path | path := String streamContents: [ :s | first := false. aURI pathComponents do: [ :p | first ifTrue: [ s nextPut: self pathNameDelimiter ]. first := true. s nextPutAll: p ] ]. ^path unescapePercents ! ! !AcornFileDirectory class methodsFor: 'initialization' stamp: 'stephaneducasse 2/4/2006 20:32'! initialize "Set up the legal chars map for filenames. May need extending for unicode etc. Basic rule is that any char legal for use in filenames will have a non-nil entry in this array; except for space, this is the same character. Space is transcoded to a char 160 to be a 'hard space' " "AcornFileDirectory initialize" | aVal | LegalCharMap := Array new: 256. Character alphabet do:[:c| LegalCharMap at: c asciiValue +1 put: c. LegalCharMap at: (aVal := c asUppercase) asciiValue +1 put: aVal]. '`!!()-_=+[{]};~,./1234567890' do:[:c| LegalCharMap at: c asciiValue + 1 put: c]. LegalCharMap at: Character space asciiValue +1 put: (Character value:160 "hardspace"). LegalCharMap at: 161 put: (Character value:160 "hardspace")."secondary mapping to keep it in strings"! ! !AcornFileDirectory class methodsFor: 'platform specific' stamp: 'md 10/26/2003 13:16'! isActiveDirectoryClass "Does this class claim to be that properly active subclass of FileDirectory for the current platform? On Acorn, the test is whether platformName is 'RiscOS' (on newer VMs) or if the primPathNameDelimiter is $. (on older ones), which is what we would like to use for a dirsep if only it would work out. See pathNameDelimiter for more woeful details - then just get on and enjoy Squeak" ^ SmalltalkImage current platformName = 'RiscOS' or: [self primPathNameDelimiter = $.]! ! !AcornFileDirectory class methodsFor: 'platform specific' stamp: 'tpr 8/1/2003 16:38'! isCaseSensitive "Risc OS ignores the case of file names" ^ false! ! !AcornFileDirectory class methodsFor: 'platform specific' stamp: 'TPR 7/20/1999 17:52'! maxFileNameLength ^ 255 ! ! !AcornFileDirectory class methodsFor: 'platform specific' stamp: 'TPR 5/10/1998 21:45'! pathNameDelimiter "Acorn RiscOS uses a dot as the directory separator and has no real concept of filename extensions. We tried to make code handle this, but there are just too many uses of dot as a filename extension - so fake it out by pretending to use a slash. The file prims do conversions instead. Sad, but pragmatic" ^ $/ ! ! HostWindowProxy subclass: #AcornWindowProxy instanceVariableNames: 'flags' classVariableNames: 'BackButton CloseButton HasTitleBar IconiseButton ToggleSizeButton' poolDictionaries: '' category: 'Graphics-External-Ffenestri'! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'tpr 10/6/2004 16:32'! addButton: buttonFlag "we need a button on the window. If there is already one, ignore this. If the host window does not yet exist we need only set the flag. If there is already a window, we will need to destroy the old window, add the flag and recreate" "do we already have a button? - if so just return" (self hasButton: buttonFlag) ifTrue:[^self]. "add the close button flag" self addFlag: buttonFlag. "note that we have a titlebar in order for the button to exist" self addFlag: HasTitleBar. "if we have a window recreate it" self isOpen ifTrue:[self recreate]! ! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'tpr 10/6/2004 15:01'! addCloseButton "we need a close button on the window. If there is already one, ignore this. If the host window does not yet exist we need only set the flag. If there is already a window, we will need to destroy the old window, add the flag and recreate" ^self addButton: CloseButton! ! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'lr 7/4/2009 10:42'! addFlag: flagVal "add flagVal to the flags" flags ifNil: [ flags := 0 ]. flags := flags bitOr: flagVal! ! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'tpr 10/6/2004 15:01'! addIconiseButton "we need a iconise button on the window. If there is already one, ignore this. If the host window does not yet exist we need only set the flag. If there is already a window, we will need to destroy the old window, add the flag and recreate" ^self addButton: IconiseButton! ! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'tpr 10/6/2004 15:25'! addToggleSizeButton "we need a toggle size button on the window. If there is already one, ignore this. If the host window does not yet exist we need only set the flag. If there is already a window, we will need to destroy the old window, add the flag and recreate" ^self addButton: ToggleSizeButton! ! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'lr 7/4/2009 10:42'! attributes | val | ^ flags ifNil: [ super attributes ] ifNotNil: [ (val := ByteArray new: 4) longAt: 1 put: flags bigEndian: false. val ]! ! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'tpr 10/7/2004 11:37'! defaultWindowType "set myself up for use as a normal window titlebar, close, iconise & size buttons" self addCloseButton; addIconiseButton; addToggleSizeButton! ! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'tpr 10/6/2004 15:20'! hasButton: buttonFlag "do I have the button?" flags ifNil:[^false]. ^flags anyMask: buttonFlag! ! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'tpr 10/11/2004 18:31'! hasTitleBar "do I have a title bar set?" ^self hasButton: HasTitleBar! ! !AcornWindowProxy methodsFor: 'window decorations' stamp: 'tpr 10/6/2004 16:33'! windowTitle: titleString "set the window title. If the window is open and doesn't already have a titlebar, add the title bar, recreate and set the title" (self isOpen and: [self hasTitleBar not]) ifTrue:[ "note that we have a titlebar in order for the title to exist" self addFlag: HasTitleBar. self recreate]. super windowTitle: titleString! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AcornWindowProxy class instanceVariableNames: ''! !AcornWindowProxy class methodsFor: 'class initialization' stamp: 'lr 7/4/2009 10:42'! initialize "AcornWindowProxy initialize" "Encode attributes in a 4byte ByteArary to be treated as an int in the vm" BackButton := 16777216. CloseButton := 33554432. IconiseButton := 0. "handled by OS completely independently" ToggleSizeButton := 134217728. HasTitleBar := 67108864! ! !AcornWindowProxy class methodsFor: 'system startup' stamp: 'tpr 10/1/2004 16:28'! isActiveHostWindowProxyClass "Am I active?" ^SmalltalkImage current platformName = 'RiscOS'! ! Array variableSubclass: #ActionSequence instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Object Events'! !ActionSequence commentStamp: 'tlk 5/7/2006 20:02' prior: 0! An ActionSequence is an array that lists the object's dependant objects.! !ActionSequence methodsFor: 'converting' stamp: 'reThink 2/18/2001 15:12'! asActionSequence ^self! ! !ActionSequence methodsFor: 'converting' stamp: 'rw 7/20/2003 16:03'! asActionSequenceTrappingErrors ^WeakActionSequenceTrappingErrors withAll: self! ! !ActionSequence methodsFor: 'converting' stamp: 'reThink 2/18/2001 15:28'! asMinimalRepresentation self size = 0 ifTrue: [^nil]. self size = 1 ifTrue: [^self first]. ^self! ! !ActionSequence methodsFor: 'evaluating' stamp: 'reThink 2/18/2001 17:51'! value "Answer the result of evaluating the elements of the receiver." | answer | self do: [:each | answer := each value]. ^answer! ! !ActionSequence methodsFor: 'evaluating' stamp: 'reThink 2/18/2001 17:52'! valueWithArguments: anArray | answer | self do: [:each | answer := each valueWithArguments: anArray]. ^answer! ! !ActionSequence methodsFor: 'printing' stamp: 'SqR 07/28/2001 18:25'! printOn: aStream self size < 2 ifTrue: [^super printOn: aStream]. aStream nextPutAll: '#('. self do: [:each | each printOn: aStream] separatedBy: [aStream cr]. aStream nextPut: $)! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ActionSequence class instanceVariableNames: ''! AbstractEvent subclass: #AddedEvent instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'! !AddedEvent methodsFor: 'printing' stamp: 'rw 6/30/2003 09:31'! printEventKindOn: aStream aStream nextPutAll: 'Added'! ! !AddedEvent methodsFor: 'testing' stamp: 'rw 6/30/2003 08:35'! isAdded ^true! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AddedEvent class instanceVariableNames: ''! !AddedEvent class methodsFor: 'accessing' stamp: 'rw 7/19/2003 09:52'! changeKind ^#Added! ! !AddedEvent class methodsFor: 'accessing' stamp: 'NS 1/20/2004 12:22'! supportedKinds "All the kinds of items that this event can take." ^ Array with: self classKind with: self methodKind with: self categoryKind with: self protocolKind! ! Object variableSubclass: #AdditionalMethodState instanceVariableNames: 'method selector' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Methods'! !AdditionalMethodState commentStamp: '' prior: 0! I am class holding state for compiled methods. All my instance variables should be actually part of the CompiledMethod itself, but the current implementation of the VM doesn't allow this. Currently I hold the selector and any pragmas or properties the compiled method has. Pragmas and properties are stored in indexable fields; pragmas as instances of Pragma, properties as instances of Association. I am a reimplementation of much of MethodProperties, but eliminating the explicit properties and pragmas dictionaries. Hence I answer true to isMethodProperties.! !AdditionalMethodState methodsFor: 'testing' stamp: 'eem 11/27/2008 13:12'! analogousCodeTo: aMethodProperties | bs | (bs := self basicSize) ~= aMethodProperties basicSize ifTrue: [^false]. 1 to: bs do: [:i| ((self basicAt: i) analogousCodeTo: (aMethodProperties basicAt: i)) ifFalse: [^false]]. ^true! ! !AdditionalMethodState methodsFor: 'testing' stamp: 'bgf 12/6/2008 12:15'! hasLiteralSuchThat: aBlock "Answer true if litBlock returns true for any literal in this array, even if embedded in further array structure. This method is only intended for private use by CompiledMethod hasLiteralSuchThat:" 1 to: self basicSize do: [:i | | propertyOrPragma "" | propertyOrPragma := self basicAt: i. (propertyOrPragma isVariableBinding ifTrue: [(aBlock value: propertyOrPragma key) or: [(aBlock value: propertyOrPragma value) or: [propertyOrPragma value isArray and: [propertyOrPragma value hasLiteralSuchThat: aBlock]]]] ifFalse: [propertyOrPragma hasLiteralSuchThat: aBlock]) ifTrue: [^true]]. ^false! ! !AdditionalMethodState methodsFor: 'testing' stamp: 'eem 11/29/2008 16:40'! hasLiteralThorough: literal "Answer true if any literal in these properties is literal, even if embedded in array structure." 1 to: self basicSize do: [:i | | propertyOrPragma "" | propertyOrPragma := self basicAt: i. (propertyOrPragma isVariableBinding ifTrue: [propertyOrPragma key == literal or: [propertyOrPragma value == literal or: [propertyOrPragma value isArray and: [propertyOrPragma value hasLiteral: literal]]]] ifFalse: [propertyOrPragma hasLiteral: literal]) ifTrue: [^true]]. ^false! ! !AdditionalMethodState methodsFor: 'testing' stamp: 'eem 12/1/2008 10:53'! includes: aPropertyOrPragma "" "Test if the property or pragma is present." 1 to: self basicSize do: [:i | (self basicAt: i) = aPropertyOrPragma ifTrue: [^true]]. ^false! ! !AdditionalMethodState methodsFor: 'testing' stamp: 'eem 12/1/2008 10:53'! includesKey: aKey "Test if the property aKey or pragma with selector aKey is present." 1 to: self basicSize do: [:i | (self basicAt: i) key == aKey ifTrue: [^true]]. ^false! ! !AdditionalMethodState methodsFor: 'testing' stamp: 'eem 11/29/2008 13:47'! isEmpty ^self basicSize = 0! ! !AdditionalMethodState methodsFor: 'testing' stamp: 'md 2/19/2006 11:24'! isMethodProperties ^true! ! !AdditionalMethodState methodsFor: 'testing' stamp: 'eem 12/1/2008 16:49'! notEmpty ^self basicSize > 0! ! !AdditionalMethodState methodsFor: 'testing' stamp: 'JohanBrichau 10/7/2009 20:07'! refersToLiteral: aLiteral ^ self pragmas anySatisfy: [ :pragma | pragma hasLiteral: aLiteral ]! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'eem 11/29/2008 10:19'! at: aKey "Answer the property value or pragma associated with aKey." ^self at: aKey ifAbsent: [self error: 'not found']! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'eem 12/1/2008 10:55'! at: aKey ifAbsent: aBlock "Answer the property value or pragma associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock." 1 to: self basicSize do: [:i | | propertyOrPragma "" | (propertyOrPragma := self basicAt: i) key == aKey ifTrue: [^propertyOrPragma isVariableBinding ifTrue: [propertyOrPragma value] ifFalse: [propertyOrPragma]]]. ^aBlock value! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'eem 12/1/2008 10:54'! at: aKey ifAbsentPut: aBlock "Answer the property value or pragma associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock." 1 to: self basicSize do: [:i | | propertyOrPragma "" | (propertyOrPragma := self basicAt: i) key == aKey ifTrue: [^propertyOrPragma isVariableBinding ifTrue: [propertyOrPragma value] ifFalse: [propertyOrPragma]]]. ^method propertyValueAt: aKey put: aBlock value! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'eem 12/1/2008 10:56'! at: aKey put: aValue "Replace the property value or pragma associated with aKey." 1 to: self basicSize do: [:i | | propertyOrPragma "" | (propertyOrPragma := self basicAt: i) key == aKey ifTrue: [propertyOrPragma isVariableBinding ifTrue: [propertyOrPragma value: aValue] ifFalse: [self basicAt: i put: aValue]]]. ^method propertyValueAt: aKey put: aValue! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'eem 11/29/2008 18:36'! keysAndValuesDo: aBlock "Enumerate the receiver with all the keys and values." 1 to: self basicSize do: [:i | | propertyOrPragma "" | (propertyOrPragma := self basicAt: i) isVariableBinding ifTrue: [aBlock value: propertyOrPragma key value: propertyOrPragma value] ifFalse: [aBlock value: propertyOrPragma keyword value: propertyOrPragma]]! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'eem 11/29/2008 14:11'! pragmas "Answer the raw messages comprising my pragmas." | pragmaStream | pragmaStream := WriteStream on: (Array new: self basicSize). 1 to: self basicSize do: [:i | | propertyOrPragma "" | (propertyOrPragma := self basicAt: i) isVariableBinding ifFalse: [pragmaStream nextPut: propertyOrPragma]]. ^pragmaStream contents! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'eem 11/29/2008 10:25'! properties | propertyStream | propertyStream := WriteStream on: (Array new: self basicSize * 2). 1 to: self basicSize do: [:i | | propertyOrPragma "" | (propertyOrPragma := self basicAt: i) isVariableBinding ifTrue: [propertyStream nextPut: propertyOrPragma key; nextPut: propertyOrPragma value]]. ^IdentityDictionary newFromPairs: propertyStream contents! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'eem 11/29/2008 19:32'! removeKey: aKey ifAbsent: aBlock "Remove the property with aKey. Answer the value or, if aKey isn't found, answer the result of evaluating aBlock." 1 to: self basicSize do: [:i | | propertyOrPragma "" | propertyOrPragma := self basicAt: i. (propertyOrPragma isVariableBinding ifTrue: [propertyOrPragma key] ifFalse: [propertyOrPragma keyword]) == aKey ifTrue: [^method removeProperty: aKey]]. ^aBlock value! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'md 2/16/2006 17:50'! selector ^selector! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'md 2/16/2006 17:50'! selector: aSymbol selector := aSymbol! ! !AdditionalMethodState methodsFor: 'accessing' stamp: 'eem 11/29/2008 18:28'! setMethod: aMethod method := aMethod. 1 to: self basicSize do: [:i| | propertyOrPragma "" | (propertyOrPragma := self basicAt: i) isVariableBinding ifFalse: [propertyOrPragma setMethod: aMethod]]! ! !AdditionalMethodState methodsFor: 'copying' stamp: 'eem 11/29/2008 18:35'! copyWith: aPropertyOrPragma "" "Answer a copy of the receiver which includes aPropertyOrPragma" | bs copy | (Association == aPropertyOrPragma class or: [Pragma == aPropertyOrPragma class]) ifFalse: [self error: self class name, ' instances should hold only Associations or Pragmas.']. copy := self class new: (bs := self basicSize) + 1. 1 to: bs do: [:i| copy basicAt: i put: (self basicAt: i)]. copy basicAt: bs + 1 put: aPropertyOrPragma. ^copy selector: selector; setMethod: method; yourself ! ! !AdditionalMethodState methodsFor: 'copying' stamp: 'eem 11/29/2008 18:35'! copyWithout: aPropertyOrPragma "" "Answer a copy of the receiver which no longer includes aPropertyOrPragma" | bs copy offset | copy := self class new: (bs := self basicSize) - ((self includes: aPropertyOrPragma) ifTrue: [1] ifFalse: [0]). offset := 0. 1 to: bs do: [:i| (self basicAt: i) = aPropertyOrPragma ifTrue: [offset := 1] ifFalse: [copy basicAt: i - offset put: (self basicAt: i)]]. ^copy selector: selector; setMethod: method; yourself ! ! !AdditionalMethodState methodsFor: 'properties' stamp: 'eem 11/29/2008 10:28'! includesProperty: aKey "Test if the property aKey is present." 1 to: self basicSize do: [:i | | propertyOrPragma "" | propertyOrPragma := self basicAt: i. (propertyOrPragma isVariableBinding and: [propertyOrPragma key == aKey]) ifTrue: [^true]]. ^false! ! !AdditionalMethodState methodsFor: 'properties' stamp: 'eem 11/29/2008 10:18'! propertyKeysAndValuesDo: aBlock "Enumerate the receiver with all the keys and values." 1 to: self basicSize do: [:i | | propertyOrPragma "" | (propertyOrPragma := self basicAt: i) isVariableBinding ifTrue: [aBlock value: propertyOrPragma key value: propertyOrPragma value]]! ! !AdditionalMethodState methodsFor: 'properties' stamp: 'eem 11/29/2008 11:46'! propertyValueAt: aKey "Answer the property value associated with aKey." ^ self propertyValueAt: aKey ifAbsent: [ self error: 'Property not found' ].! ! !AdditionalMethodState methodsFor: 'properties' stamp: 'eem 11/29/2008 11:45'! propertyValueAt: aKey ifAbsent: aBlock "Answer the property value associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock." 1 to: self basicSize do: [:i | | propertyOrPragma "" | propertyOrPragma := self basicAt: i. (propertyOrPragma isVariableBinding and: [propertyOrPragma key == aKey]) ifTrue: [^propertyOrPragma value]]. ^aBlock value! ! !AdditionalMethodState methodsFor: 'properties' stamp: 'lr 2/6/2006 20:48'! removeKey: aKey "Remove the property with aKey. Answer the property or raise an error if aKey isn't found." ^ self removeKey: aKey ifAbsent: [ self error: 'Property not found' ].! ! !AdditionalMethodState methodsFor: 'decompiling' stamp: 'eem 6/11/2009 17:06'! method: aMethodNodeOrNil "For decompilation" method := aMethodNodeOrNil! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AdditionalMethodState class instanceVariableNames: ''! !AdditionalMethodState class methodsFor: 'instance creation' stamp: 'eem 11/29/2008 18:48'! forMethod: aMethod selector: aSelector ^(self basicNew: 0) selector: aSelector; setMethod: aMethod; yourself! ! !AdditionalMethodState class methodsFor: 'instance creation' stamp: 'eem 11/28/2008 12:26'! selector: aSelector with: aPropertyOrPragma ^(self basicNew: 1) selector: aSelector; basicAt: 1 put: aPropertyOrPragma; yourself! ! MessageDialogWindow subclass: #AlertDialogWindow instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !AlertDialogWindow commentStamp: 'gvc 5/18/2007 13:52' prior: 0! Message dialog with a warning icon.! !AlertDialogWindow methodsFor: 'visual properties' stamp: 'gvc 5/18/2007 10:27'! icon "Answer an icon for the receiver." ^self theme warningIcon! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AlertDialogWindow class instanceVariableNames: ''! !AlertDialogWindow class methodsFor: 'as yet unclassified' stamp: 'gvc 5/22/2007 11:50'! taskbarIcon "Answer the icon for the receiver in a task bar." ^self theme smallWarningIcon! ! RectangleMorph subclass: #AlignmentMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Basic'! !AlignmentMorph commentStamp: 'kfr 10/27/2003 10:25' prior: 0! Used for layout. Since all morphs now support layoutPolicy the main use of this class is no longer needed. Kept around for compability. Supports a few methods not found elsewhere that can be convenient, eg. newRow ! !AlignmentMorph methodsFor: 'adding' stamp: 'stephane.ducasse 1/15/2009 15:52'! addAColumn: aCollectionOfMorphs | col | col := self inAColumn: aCollectionOfMorphs. self addMorphBack: col. ^col! ! !AlignmentMorph methodsFor: 'adding' stamp: 'stephane.ducasse 1/15/2009 15:52'! addARow: aCollectionOfMorphs | row | row := self inARow: aCollectionOfMorphs. self addMorphBack: row. ^row! ! !AlignmentMorph methodsFor: 'adding' stamp: 'stephane.ducasse 1/15/2009 15:52'! addARowCentered: aCollectionOfMorphs ^(self addARow: aCollectionOfMorphs) hResizing: #shrinkWrap; wrapCentering: #center; cellPositioning: #leftCenter! ! !AlignmentMorph methodsFor: 'adding' stamp: 'stephane.ducasse 1/15/2009 15:52'! addARowCentered: aCollectionOfMorphs cellInset: cellInsetInteger ^(self addARow: aCollectionOfMorphs) hResizing: #shrinkWrap; wrapCentering: #center; cellPositioning: #leftCenter; cellInset: cellInsetInteger! ! !AlignmentMorph methodsFor: 'classification' stamp: 'di 5/7/1998 01:20'! isAlignmentMorph ^ true ! ! !AlignmentMorph methodsFor: 'event handling' stamp: 'sw 5/6/1998 15:58'! wantsKeyboardFocusFor: aSubmorph aSubmorph wouldAcceptKeyboardFocus ifTrue: [^ true]. ^ super wantsKeyboardFocusFor: aSubmorph! ! !AlignmentMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:36'! defaultBorderWidth "answer the default border width for the receiver" ^ 0! ! !AlignmentMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:24'! defaultColor "answer the default color/fill style for the receiver" ^ Color r: 0.8 g: 1.0 b: 0.8! ! !AlignmentMorph methodsFor: 'initialization' stamp: 'stephane.ducasse 1/15/2009 15:58'! initialize super initialize. self layoutPolicy: TableLayout new; listDirection: #leftToRight; wrapCentering: #topLeft; hResizing: #spaceFill; vResizing: #spaceFill; layoutInset: 2; rubberBandCells: true "from AlignmentMorphBob1which was merged in this class, in an effort to remove alignementBob1 and still preserving the addInRow behavior" " self listDirection: #topToBottom. self layoutInset: 0. self hResizing: #rigid. self vResizing: #rigid"! ! !AlignmentMorph methodsFor: 'initialization' stamp: 'ar 11/9/2000 20:34'! openInWindowLabeled: aString inWorld: aWorld self layoutInset: 0. ^super openInWindowLabeled: aString inWorld: aWorld.! ! !AlignmentMorph methodsFor: 'object filein' stamp: 'gm 2/22/2003 13:12'! convertOldAlignmentsNov2000: varDict using: smartRefStrm "major change - much of AlignmentMorph is now implemented more generally in Morph" "These are going away #('orientation' 'centering' 'hResizing' 'vResizing' 'inset' 'minCellSize' 'layoutNeeded' 'priorFullBounds')" | orientation centering hResizing vResizing inset minCellSize inAlignment | orientation := varDict at: 'orientation'. centering := varDict at: 'centering'. hResizing := varDict at: 'hResizing'. vResizing := varDict at: 'vResizing'. inset := varDict at: 'inset'. minCellSize := varDict at: 'minCellSize'. (orientation == #horizontal or: [orientation == #vertical]) ifTrue: [self layoutPolicy: TableLayout new]. self cellPositioning: #topLeft. self rubberBandCells: true. orientation == #horizontal ifTrue: [self listDirection: #leftToRight]. orientation == #vertical ifTrue: [self listDirection: #topToBottom]. centering == #topLeft ifTrue: [self wrapCentering: #topLeft]. centering == #bottomRight ifTrue: [self wrapCentering: #bottomRight]. centering == #center ifTrue: [self wrapCentering: #center. orientation == #horizontal ifTrue: [self cellPositioning: #leftCenter] ifFalse: [self cellPositioning: #topCenter]]. (inset isNumber or: [inset isPoint]) ifTrue: [self layoutInset: inset]. (minCellSize isNumber or: [minCellSize isPoint]) ifTrue: [self minCellSize: minCellSize]. (self hasProperty: #clipToOwnerWidth) ifTrue: [self clipSubmorphs: true]. "now figure out if our owner was an AlignmentMorph, even if it is reshaped..." inAlignment := false. owner isMorph ifTrue: [(owner isAlignmentMorph) ifTrue: [inAlignment := true]] ifFalse: ["e.g., owner may be reshaped" (owner class instanceVariablesString findString: 'orientation centering hResizing vResizing') > 0 ifTrue: ["this was an alignment morph being reshaped" inAlignment := true]]. "And check for containment in system windows" owner isSystemWindow ifTrue: [inAlignment := true]. (hResizing == #spaceFill and: [inAlignment not]) ifTrue: [self hResizing: #shrinkWrap] ifFalse: [self hResizing: hResizing]. (vResizing == #spaceFill and: [inAlignment not]) ifTrue: [self vResizing: #shrinkWrap] ifFalse: [self vResizing: vResizing]! ! !AlignmentMorph methodsFor: 'visual properties' stamp: 'sw 11/5/2001 15:11'! canHaveFillStyles "Return true if the receiver can have general fill styles; not just colors. This method is for gradually converting old morphs." ^ self class == AlignmentMorph "no subclasses"! ! !AlignmentMorph methodsFor: 'visual properties' stamp: 'stephane.ducasse 1/15/2009 15:52'! fancyText: aString font: aFont color: aColor | answer tm col | col := ColorTheme current dialog3DTitles ifTrue: [aColor] ifFalse: [aColor negated]. tm := TextMorph new. tm beAllFont: aFont; color: col; contents: aString. answer := self inAColumn: {tm}. ColorTheme current dialog3DTitles ifTrue: ["" tm addDropShadow. tm shadowPoint: 5 @ 5 + tm bounds center]. tm lock. ^ answer! ! !AlignmentMorph methodsFor: 'visual properties' stamp: 'stephane.ducasse 1/15/2009 15:53'! inAColumn: aCollectionOfMorphs | col | col := self class newColumn color: Color transparent; vResizing: #shrinkWrap; layoutInset: 1; wrapCentering: #center; cellPositioning: #topCenter. aCollectionOfMorphs do: [ :each | col addMorphBack: each]. ^col! ! !AlignmentMorph methodsFor: 'visual properties' stamp: 'stephane.ducasse 1/15/2009 15:54'! inARightColumn: aCollectionOfMorphs | col | col := self class newColumn color: Color transparent; vResizing: #shrinkWrap; layoutInset: 1; wrapCentering: #bottomRight; cellPositioning: #topCenter. aCollectionOfMorphs do: [:each | col addMorphBack: each]. ^ col! ! !AlignmentMorph methodsFor: 'visual properties' stamp: 'stephane.ducasse 1/15/2009 15:55'! inARow: aCollectionOfMorphs | row | row := self class newRow color: Color transparent; vResizing: #shrinkWrap; layoutInset: 2; wrapCentering: #center; cellPositioning: #leftCenter. aCollectionOfMorphs do: [:each | row addMorphBack: each]. ^ row! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AlignmentMorph class instanceVariableNames: ''! !AlignmentMorph class methodsFor: 'instance creation' stamp: 'dgd 9/20/2003 19:05'! columnPrototype "Answer a prototypical column" | sampleMorphs aColumn | sampleMorphs := #(red yellow green) collect: [:aColor | Morph new extent: 130 @ 38; color: (Color perform: aColor); setNameTo: aColor asString; yourself]. aColumn := self inAColumn: sampleMorphs. aColumn setNameTo: 'Column'. aColumn color: Color veryVeryLightGray. aColumn cellInset: 4; layoutInset: 6. aColumn enableDragNDrop. aColumn setBalloonText: 'Things dropped into here will automatically be organized into a column. Once you have added your own items here, you will want to remove the sample colored rectangles that this started with, and you will want to change this balloon help message to one of your own!!' translated. ^ aColumn! ! !AlignmentMorph class methodsFor: 'instance creation' stamp: 'sw 11/2/2001 04:45'! inAColumn: aCollectionOfMorphs "Answer a columnar AlignmentMorph holding the given collection" | col | col := self newColumn color: Color transparent; vResizing: #shrinkWrap; hResizing: #shrinkWrap; layoutInset: 1; borderColor: Color black; borderWidth: 1; wrapCentering: #center; cellPositioning: #topCenter. aCollectionOfMorphs do: [:each | col addMorphBack: each]. ^ col! ! !AlignmentMorph class methodsFor: 'instance creation' stamp: 'sw 11/5/2001 15:11'! inARow: aCollectionOfMorphs "Answer a row-oriented AlignmentMorph holding the given collection" | aRow | aRow := self newRow color: Color transparent; vResizing: #shrinkWrap; hResizing: #shrinkWrap; layoutInset: 1; borderColor: Color black; borderWidth: 1; wrapCentering: #center; cellPositioning: #topCenter. aCollectionOfMorphs do: [ :each | aRow addMorphBack: each]. ^ aRow! ! !AlignmentMorph class methodsFor: 'instance creation' stamp: 'ar 11/9/2000 20:51'! newColumn ^ self new listDirection: #topToBottom; hResizing: #spaceFill; extent: 1@1; vResizing: #spaceFill ! ! !AlignmentMorph class methodsFor: 'instance creation' stamp: 'ar 11/9/2000 20:50'! newRow ^ self new listDirection: #leftToRight; hResizing: #spaceFill; vResizing: #spaceFill; extent: 1@1; borderWidth: 0 ! ! !AlignmentMorph class methodsFor: 'instance creation' stamp: 'ar 11/9/2000 20:37'! newSpacer: aColor "Answer a space-filling instance of me of the given color." ^ self new hResizing: #spaceFill; vResizing: #spaceFill; layoutInset: 0; borderWidth: 0; extent: 1@1; color: aColor. ! ! !AlignmentMorph class methodsFor: 'instance creation' stamp: 'ar 11/9/2000 20:37'! newVariableTransparentSpacer "Answer a space-filling instance of me of the given color." ^ self new hResizing: #spaceFill; vResizing: #spaceFill; layoutInset: 0; borderWidth: 0; extent: 1@1; color: Color transparent ! ! !AlignmentMorph class methodsFor: 'instance creation' stamp: 'dgd 9/20/2003 19:05'! rowPrototype "Answer a prototypical row" | sampleMorphs aRow | sampleMorphs := (1 to: (2 + 3 atRandom)) collect: [:integer | EllipseMorph new extent: ((60 + (20 atRandom)) @ (80 + ((20 atRandom)))); color: Color random; setNameTo: ('egg', integer asString); yourself]. aRow := self inARow: sampleMorphs. aRow setNameTo: 'Row'. aRow enableDragNDrop. aRow cellInset: 6. aRow layoutInset: 8. aRow setBalloonText: 'Things dropped into here will automatically be organized into a row. Once you have added your own items here, you will want to remove the sample colored eggs that this started with, and you will want to change this balloon help message to one of your own!!' translated. aRow color: Color veryVeryLightGray. ^ aRow "AlignmentMorph rowPrototype openInHand"! ! !AlignmentMorph class methodsFor: 'scripting' stamp: 'sw 11/16/2004 00:44'! defaultNameStemForInstances "The code just below, now commented out, resulted in every instance of every sublcass of AlignmentMorph being given a default name of the form 'Alignment1', rather than the desired 'MoviePlayer1', 'ScriptEditor2', etc." "^ 'Alignment'" ^ super defaultNameStemForInstances! ! ColorMappingCanvas subclass: #AlphaBlendingCanvas instanceVariableNames: 'alpha' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'! !AlphaBlendingCanvas methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 9/1/2008 16:31'! image: aForm at: aPoint sourceRect: sourceRect rule: rule "Draw the given form. For the 'paint' combination rule use stenciling otherwise simply fill the source rectangle. Do a blendAlpha if the rule is blend to cope with translucent images being drawn (via translucentImage:...)." rule = Form paint ifTrue:[ ^myCanvas image: aForm at: aPoint sourceRect: sourceRect rule: Form paintAlpha alpha: alpha. ]. rule = Form over ifTrue:[ ^myCanvas image: aForm at: aPoint sourceRect: sourceRect rule: Form blendAlpha alpha: alpha. ]. rule = Form blend ifTrue:[ ^myCanvas image: aForm at: aPoint sourceRect: sourceRect rule: Form blendAlpha alpha: alpha. ].! ! !AlphaBlendingCanvas methodsFor: 'accessing' stamp: 'ar 8/8/2001 14:24'! alpha ^alpha! ! !AlphaBlendingCanvas methodsFor: 'accessing' stamp: 'ar 8/8/2001 14:24'! alpha: newAlpha alpha := newAlpha.! ! !AlphaBlendingCanvas methodsFor: 'initialization' stamp: 'ar 8/8/2001 14:18'! on: aCanvas myCanvas := aCanvas. alpha := 1.0.! ! !AlphaBlendingCanvas methodsFor: 'private' stamp: 'ar 8/8/2001 14:23'! mapColor: aColor aColor isColor ifFalse:[^aColor]. "Should not happen but who knows..." aColor isTransparent ifTrue:[^aColor]. aColor isOpaque ifTrue:[^aColor alpha: alpha]. ^aColor alpha: (aColor alpha * alpha)! ! ImageMorph subclass: #AlphaImageMorph instanceVariableNames: 'alpha cachedForm layout scale enabled' classVariableNames: 'DefaultImage' poolDictionaries: '' category: 'Polymorph-Widgets'! !AlphaImageMorph commentStamp: 'gvc 5/18/2007 13:52' prior: 0! Displays an image with the specified alpha value (translucency) and optional scale and layout (scaled, top-right etc.).! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 9/26/2006 09:40'! alpha "Answer the value of alpha" ^ alpha! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 8/8/2007 15:34'! alpha: anObject "Set the value of alpha" alpha := anObject. self cachedForm: nil; changed; changed: #alpha! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 1/13/2009 17:58'! cachedForm "Answer the value of cachedForm" |form i effectiveAlpha| cachedForm ifNil: [ i := self image. self layout == #scaled ifTrue: [self extent = i extent ifFalse: [i := i magnify: i boundingBox by: (self extent / i extent) smoothing: 2]] ifFalse: [self scale ~= 1 ifTrue: [i := i magnify: i boundingBox by: self scale smoothing: 2]]. effectiveAlpha := self enabled ifTrue: [self alpha] ifFalse: [self alpha / 2]. effectiveAlpha = 1.0 ifTrue: [self cachedForm: i] ifFalse: [form := Form extent: i extent depth: 32. form fillColor: (Color white alpha: 0.003922). (form getCanvas asAlphaBlendingCanvas: effectiveAlpha) drawImage: i at: 0@0. self cachedForm: form]]. ^cachedForm! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 9/27/2006 15:02'! cachedForm: anObject "Set the value of cachedForm" cachedForm := anObject! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 1/13/2009 17:56'! enabled "Answer the value of enabled" ^enabled! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 1/13/2009 17:57'! enabled: anObject "Set the value of enabled" enabled := anObject. self cachedForm: nil; changed! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 9/28/2006 14:15'! image: anImage "Clear the cached form." ^self image: anImage size: anImage extent! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 8/27/2009 16:14'! image: aForm size: aPoint "Set the image to be the form scaled to the given size and padded if neccesary." |f f2| f := aForm scaledToSize: aPoint. (f depth < 32 and: [f depth > 4]) ifTrue: [f2 := Form extent: aPoint depth: 32. f2 fillColor: (Color white alpha: 0.003922). f2 getCanvas translucentImage: f at: 0@0. f2 fixAlpha] ifFalse: [f2 := f]. self cachedForm: nil. super image: f2. self extent: aPoint + (self borderWidth * 2). self changed: #imageExtent! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 6/30/2009 16:02'! imageExtent "Answer the extent of the original form." ^self image extent! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 10/11/2006 12:00'! layout "Answer the value of layout" ^ layout! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 8/8/2007 15:28'! layout: aSymbol "Set the value of layout" |old| (old := layout) = aSymbol ifTrue: [^self]. layout := aSymbol. (old = #scaled or: [aSymbol = #scaled]) ifTrue: [self cachedForm: nil]. self changed! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 8/8/2007 16:10'! layoutSymbols "Answer the available layout options." ^#(#center #tiled #scaled #topLeft #topCenter #topRight #rightCenter #bottomRight #bottomCenter #bottomLeft #leftCenter)! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 10/11/2006 12:43'! scale "Answer the value of scale" ^ scale! ! !AlphaImageMorph methodsFor: 'accessing' stamp: 'gvc 8/8/2007 15:34'! scale: aNumber "Set the value of scale" scale = aNumber ifTrue: [^self]. scale := aNumber. self cachedForm: nil; changed; changed: #scale! ! !AlphaImageMorph methodsFor: 'drawing' stamp: 'gvc 8/8/2007 16:25'! drawOn: aCanvas "Draw with the current alpha Can't do simple way since BitBlt rules are dodgy!!." aCanvas fillRectangle: self bounds fillStyle: self fillStyle borderStyle: self borderStyle. (self cachedForm width = 0 or: [self cachedForm height = 0]) ifTrue: [^self]. self layout == #tiled ifTrue: [aCanvas fillRectangle: self innerBounds fillStyle: (AlphaInfiniteForm with: self cachedForm)] ifFalse: [aCanvas clipBy: self innerBounds during: [:c | c translucentImage: self cachedForm at: self layoutPosition]]! ! !AlphaImageMorph methodsFor: 'geometry' stamp: 'gvc 10/11/2006 12:02'! extent: aPoint "Allow as normal." self perform: #extent: withArguments: {aPoint} inSuperclass: Morph ! ! !AlphaImageMorph methodsFor: 'geometry' stamp: 'gvc 8/8/2007 16:09'! layoutPosition "Answer the position that the cached form should be drawn based on the layout" self layout == #topCenter ifTrue: [^self innerBounds topCenter - (self cachedForm width // 2 @ 0)]. self layout == #topRight ifTrue: [^self innerBounds topRight - (self cachedForm width @ 0)]. self layout == #rightCenter ifTrue: [^self innerBounds rightCenter - (self cachedForm width @ (self cachedForm height // 2))]. self layout == #bottomRight ifTrue: [^self innerBounds bottomRight - self cachedForm extent]. self layout == #bottomCenter ifTrue: [^self innerBounds bottomCenter - (self cachedForm width // 2 @ self cachedForm height)]. self layout == #bottomLeft ifTrue: [^self innerBounds bottomLeft - (0 @ self cachedForm height)]. self layout == #leftCenter ifTrue: [^self innerBounds leftCenter - (0 @ (self cachedForm height // 2))]. self layout == #center ifTrue: [^self innerBounds center - (self cachedForm extent // 2)]. ^self innerBounds topLeft! ! !AlphaImageMorph methodsFor: 'geometry' stamp: 'gvc 10/22/2007 11:51'! optimalExtent "Answer the optimal extent for the receiver." ^self image extent * self scale + (self borderWidth * 2)! ! !AlphaImageMorph methodsFor: 'initialization' stamp: 'gvc 9/26/2006 12:40'! defaultColor "Answer the default color for the receiver." ^Color transparent! ! !AlphaImageMorph methodsFor: 'initialization' stamp: 'gvc 12/3/2007 11:37'! defaultImage "Answer the default image for the receiver." ^DefaultImage ifNil: [DefaultImage := DefaultForm asFormOfDepth: 32]! ! !AlphaImageMorph methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:37'! initialize "Initialize the receiver. Use the 32 bit depth default image to avoid unnecessary conversions." super initialize. enabled := true. self scale: 1.0; layout: #topLeft; alpha: 1.0! ! InfiniteForm subclass: #AlphaInfiniteForm instanceVariableNames: 'origin extent' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-FillStyles'! !AlphaInfiniteForm commentStamp: 'gvc 5/18/2007 13:49' prior: 0! Alpha aware InfiniteForm.! !AlphaInfiniteForm methodsFor: 'accessing' stamp: 'gvc 10/7/2008 14:00'! extent "Answer the extent of the repeating area." ^extent ifNil: [SmallInteger maxVal @ SmallInteger maxVal]! ! !AlphaInfiniteForm methodsFor: 'accessing' stamp: 'gvc 10/3/2008 12:48'! extent: anObject "Set the value of extent" extent := anObject! ! !AlphaInfiniteForm methodsFor: 'accessing' stamp: 'gvc 10/3/2008 12:42'! origin "Answer the origin." ^origin ifNil: [0@0]! ! !AlphaInfiniteForm methodsFor: 'accessing' stamp: 'gvc 10/3/2008 12:42'! origin: aPoint "Set the origin." origin := aPoint! ! !AlphaInfiniteForm methodsFor: 'as yet unclassified' stamp: 'gvc 12/3/2008 17:09'! direction: aPoint "Ignore" ! ! !AlphaInfiniteForm methodsFor: 'displaying' stamp: 'gvc 10/7/2008 13:59'! computeBoundingBox "Refer to the comment in DisplayObject|computeBoundingBox." ^self origin extent: self extent! ! !AlphaInfiniteForm methodsFor: 'displaying' stamp: 'gvc 8/10/2009 11:42'! displayOnPort: aPort offsetBy: offset | targetBox patternBox savedMap top left | aPort destForm depth < 32 ifTrue: [^super displayOnPort: aPort offsetBy: offset]. "this version tries to get the form aligned where the user wants it and not just aligned with the cliprect" (patternForm isForm) ifFalse: [ "patternForm is a Pattern or Color; just use it as a mask for BitBlt" ^ aPort fill: aPort clipRect fillColor: patternForm rule: Form over]. "do it iteratively" targetBox := aPort clipRect. patternBox := patternForm boundingBox. savedMap := aPort colorMap. aPort sourceForm: patternForm; fillColor: nil; combinationRule: Form blend; sourceRect: (0@0 extent: patternBox extent); colorMap: (patternForm colormapIfNeededFor: aPort destForm). top := (targetBox top truncateTo: patternBox height) + offset y. left := (targetBox left truncateTo: patternBox width) + offset x. left to: (targetBox right - 1) by: patternBox width do: [:x | top to: (targetBox bottom - 1) by: patternBox height do: [:y | aPort destOrigin: x@y; copyBits]]. aPort colorMap: savedMap. ! ! GIFReadWriter subclass: #AnimatedGIFReadWriter instanceVariableNames: 'forms delays comments' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Files'! !AnimatedGIFReadWriter methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! allImages | body colorTable | stream class == ReadWriteStream ifFalse: [ stream binary. self on: (ReadWriteStream with: stream contentsOfEntireFile) ]. localColorTable := nil. forms := OrderedCollection new. delays := OrderedCollection new. comments := OrderedCollection new. self readHeader. [ (body := self readBody) isNil ] whileFalse: [ colorTable := localColorTable ifNil: [ colorPalette ]. transparentIndex ifNotNil: [ transparentIndex + 1 > colorTable size ifTrue: [ colorTable := colorTable forceTo: transparentIndex + 1 paddingWith: Color white ]. colorTable at: transparentIndex + 1 put: Color transparent ]. body colors: colorTable. forms add: body. delays add: delay ]. ^ forms! ! !AnimatedGIFReadWriter methodsFor: 'accessing' stamp: 'mir 11/19/2003 14:16'! delays ^ delays! ! !AnimatedGIFReadWriter methodsFor: 'accessing' stamp: 'mir 11/19/2003 14:16'! forms ^ forms! ! !AnimatedGIFReadWriter methodsFor: 'private' stamp: 'mir 11/19/2003 12:25'! comment: aString comments add: aString! ! !AnimatedGIFReadWriter methodsFor: 'private-decoding' stamp: 'mir 11/19/2003 12:21'! readBitData | form | form := super readBitData. form offset: offset. ^form! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AnimatedGIFReadWriter class instanceVariableNames: ''! !AnimatedGIFReadWriter class methodsFor: 'image reading/writing' stamp: 'lr 7/4/2009 10:42'! formsFromFileNamed: fileName | stream | stream := FileStream readOnlyFileNamed: fileName. ^ self formsFromStream: stream! ! !AnimatedGIFReadWriter class methodsFor: 'image reading/writing' stamp: 'lr 7/4/2009 10:42'! formsFromStream: stream | reader | reader := self new on: stream reset. Cursor read showWhile: [ reader allImages. reader close ]. ^ reader! ! !AnimatedGIFReadWriter class methodsFor: 'image reading/writing' stamp: 'nk 6/12/2004 13:12'! typicalFileExtensions "Answer a collection of file extensions (lowercase) which files that I can read might commonly have" ^#('gif')! ! !AnimatedGIFReadWriter class methodsFor: 'image reading/writing' stamp: 'asm 12/11/2003 21:29'! wantsToHandleGIFs ^true! ! Object subclass: #Announcement instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Announcements-Core'! !Announcement methodsFor: '*announcements-view' stamp: 'lr 9/3/2006 16:17'! open self inspect! ! !Announcement methodsFor: 'converting' stamp: 'lr 10/3/2006 14:32'! asAnnouncement ^ self! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Announcement class instanceVariableNames: ''! !Announcement class methodsFor: 'converting' stamp: 'lr 10/3/2006 14:31'! asAnnouncement ^ self new! ! !Announcement class methodsFor: 'public' stamp: 'lr 9/20/2006 08:18'! , anAnnouncementClass ^ AnnouncementSet with: self with: anAnnouncementClass! ! !Announcement class methodsFor: 'testing' stamp: 'lr 10/3/2006 14:31'! handles: anAnnouncementClass ^ anAnnouncementClass isKindOf: self! ! Announcement subclass: #AnnouncementMockA instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Announcements'! Announcement subclass: #AnnouncementMockB instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Announcements'! AnnouncementMockB subclass: #AnnouncementMockC instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Announcements'! Set subclass: #AnnouncementSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Announcements-Core'! !AnnouncementSet methodsFor: 'adding' stamp: 'lr 6/13/2006 08:13'! , anAnnouncementClass self add: anAnnouncementClass! ! !AnnouncementSet methodsFor: 'testing' stamp: 'lr 10/3/2006 14:31'! handles: anAnnouncementClass ^ self anySatisfy: [ :each | each handles: anAnnouncementClass ]! ! Object subclass: #AnnouncementSpy instanceVariableNames: 'announcer announcements index' classVariableNames: '' poolDictionaries: '' category: 'Announcements-View'! !AnnouncementSpy methodsFor: 'accessing' stamp: 'lr 6/14/2006 17:02'! announcements ^ announcements! ! !AnnouncementSpy methodsFor: 'accessing' stamp: 'lr 9/3/2006 14:08'! announcements: aCollection announcements := aCollection. self changed: #announcements! ! !AnnouncementSpy methodsFor: 'accessing' stamp: 'lr 6/14/2006 17:04'! announcer ^ announcer! ! !AnnouncementSpy methodsFor: 'accessing' stamp: 'lr 9/25/2006 09:26'! announcer: anAnnouncer announcer ifNotNil: [ announcer unsubscribe: self ]. announcer := anAnnouncer. announcer ifNotNil: [ announcer subscribe: Announcement send: #announce: to: self ]! ! !AnnouncementSpy methodsFor: 'accessing' stamp: 'lr 6/14/2006 17:02'! index ^ index ! ! !AnnouncementSpy methodsFor: 'accessing' stamp: 'lr 6/14/2006 17:20'! index: anInteger index := anInteger. self changed: #index! ! !AnnouncementSpy methodsFor: 'accessing-dynamic' stamp: 'lr 9/3/2006 14:08'! extent ^ 250 @ 400! ! !AnnouncementSpy methodsFor: 'accessing-dynamic' stamp: 'lr 6/14/2006 17:03'! label ^ self announcer printString! ! !AnnouncementSpy methodsFor: 'actions' stamp: 'lr 9/3/2006 16:21'! clear self announcements: OrderedCollection new! ! !AnnouncementSpy methodsFor: 'actions' stamp: 'lr 9/25/2006 09:19'! close self announcer: nil! ! !AnnouncementSpy methodsFor: 'actions' stamp: 'lr 9/25/2006 09:25'! open (self announcements at: self index ifAbsent: [ ^ self ]) open! ! !AnnouncementSpy methodsFor: 'building' stamp: 'lr 9/3/2006 16:21'! buildMenu: aMenuMorph ^ aMenuMorph defaultTarget: self; add: 'open' action: #open; add: 'clear' action: #clear; yourself! ! !AnnouncementSpy methodsFor: 'building' stamp: 'lr 9/25/2006 09:20'! buildWith: aBuilder ^ aBuilder build: (aBuilder pluggableWindowSpec new model: self; label: self label; extent: self extent; closeAction: #close; children: (OrderedCollection new add: (aBuilder pluggableListSpec new model: self; list: #announcements; menu: #buildMenu:; getIndex: #index; setIndex: #index:; frame: (0 @ 0 corner: 1 @ 1); yourself); yourself); yourself)! ! !AnnouncementSpy methodsFor: 'initialization' stamp: 'lr 6/14/2006 17:03'! initialize super initialize. self announcements: OrderedCollection new. self index: 0! ! !AnnouncementSpy methodsFor: 'private' stamp: 'lr 9/3/2006 14:09'! announce: anAnnouncement self announcements add: anAnnouncement. self index: self announcements size. self changed: #announcements! ! !AnnouncementSpy methodsFor: 'private' stamp: 'lr 6/14/2006 17:19'! changed: aSymbol WorldState addDeferredUIMessage: [ super changed: aSymbol ]! ! !AnnouncementSpy methodsFor: 'private' stamp: 'lr 6/14/2006 17:29'! perform: selector orSendTo: otherTarget ^ (self respondsTo: selector) ifTrue: [ self perform: selector ] ifFalse: [ super perform: selector orSendTo: otherTarget ]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AnnouncementSpy class instanceVariableNames: ''! !AnnouncementSpy class methodsFor: 'instance-creation' stamp: 'lr 6/14/2006 17:05'! on: anAnnouncer ^ self new announcer: anAnnouncer; yourself! ! !AnnouncementSpy class methodsFor: 'instance-creation' stamp: 'lr 6/14/2006 17:05'! openOn: anAnnouncer ToolBuilder open: (self on: anAnnouncer)! ! Object subclass: #Announcer instanceVariableNames: 'subscriptions' classVariableNames: '' poolDictionaries: '' category: 'Announcements-Core'! !Announcer commentStamp: 'lr 3/2/2009 10:27' prior: 0! The code is based on the announcements as described by Vassili Bykov in . The implementation is a slightly extended and generalized version of the code found in OmniBrowser by Colin Putney.! !Announcer methodsFor: '*announcements-view' stamp: 'lr 9/20/2006 08:18'! open AnnouncementSpy openOn: self! ! !Announcer methodsFor: 'announce' stamp: 'lr 8/5/2008 12:06'! announce: anAnnouncement | announcement | announcement := anAnnouncement asAnnouncement. subscriptions ifNil: [ ^ announcement ]. subscriptions keysAndValuesDo: [ :class :actions | (class handles: announcement) ifTrue: [ actions valueWithArguments: (Array with: announcement) ] ]. ^ announcement! ! !Announcer methodsFor: 'convenience' stamp: 'lr 10/27/2006 14:26'! on: anAnnouncementClass do: aValuable ^ self subscribe: anAnnouncementClass do: aValuable! ! !Announcer methodsFor: 'convenience' stamp: 'lr 10/27/2006 14:27'! on: anAnnouncementClass send: aSelector to: anObject ^ self subscribe: anAnnouncementClass send: aSelector to: anObject! ! !Announcer methodsFor: 'convenience' stamp: 'tg 2/25/2009 12:05'! when: anAnnouncementClass do: aValuable ^ self subscribe: anAnnouncementClass do: aValuable! ! !Announcer methodsFor: 'subscription' stamp: 'lr 8/5/2008 12:05'! subscribe: anAnnouncementClass do: aValuable | actions | subscriptions ifNil: [ subscriptions := IdentityDictionary new ]. actions := subscriptions at: anAnnouncementClass ifAbsent: [ ActionSequence new ]. subscriptions at: anAnnouncementClass put: (actions copyWith: aValuable). ^ aValuable! ! !Announcer methodsFor: 'subscription' stamp: 'lr 10/27/2006 14:27'! subscribe: anAnnouncementClass send: aSelector to: anObject ^ self subscribe: anAnnouncementClass do: (MessageSend receiver: anObject selector: aSelector)! ! !Announcer methodsFor: 'subscription' stamp: 'lr 8/5/2008 12:05'! unsubscribe: anObject subscriptions ifNil: [ ^ self ]. subscriptions keysAndValuesDo: [ :class :actions | subscriptions at: class put: (actions reject: [ :each | each receiver == anObject ]) ]. subscriptions keysAndValuesRemove: [ :class :actions | actions isEmpty ]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Announcer class instanceVariableNames: ''! TestCase subclass: #AnnouncerTest instanceVariableNames: 'announcer' classVariableNames: '' poolDictionaries: '' category: 'Tests-Announcements'! !AnnouncerTest methodsFor: 'running' stamp: 'lr 9/25/2006 08:42'! setUp announcer := Announcer new! ! !AnnouncerTest methodsFor: 'testing' stamp: 'lr 3/2/2009 10:11'! testAnnounceClass self assert: (announcer announce: AnnouncementMockA) class = AnnouncementMockA! ! !AnnouncerTest methodsFor: 'testing' stamp: 'lr 3/2/2009 10:10'! testAnnounceInstance | instance | instance := AnnouncementMockA new. self assert: (announcer announce: instance) = instance! ! !AnnouncerTest methodsFor: 'testing' stamp: 'lr 3/2/2009 10:08'! testSubscribeBlock | announcement instance | announcer subscribe: AnnouncementMockA do: [ :ann | announcement := ann ]. announcement := nil. instance := announcer announce: AnnouncementMockA. self assert: announcement = instance. announcement := nil. instance := announcer announce: AnnouncementMockB. self assert: announcement isNil! ! !AnnouncerTest methodsFor: 'testing' stamp: 'lr 3/2/2009 10:07'! testSubscribeSend | announcement instance | announcer subscribe: AnnouncementMockA send: #value: to: [ :ann | announcement := ann ]. announcement := nil. instance := announcer announce: AnnouncementMockA. self assert: announcement = instance. announcement := nil. instance := announcer announce: AnnouncementMockB new. self assert: announcement isNil! ! !AnnouncerTest methodsFor: 'testing' stamp: 'lr 3/2/2009 10:07'! testSubscribeSet | announcement instance | announcer subscribe: AnnouncementMockA , AnnouncementMockC do: [ :ann | announcement := ann ]. announcement := nil. instance := announcer announce: AnnouncementMockA. self assert: announcement = instance. announcement := nil. instance := announcer announce: AnnouncementMockB. self assert: announcement isNil. announcement := nil. instance := announcer announce: AnnouncementMockC. self assert: announcement = instance! ! !AnnouncerTest methodsFor: 'testing' stamp: 'lr 3/2/2009 10:06'! testSubscribeSubclass | announcement instance | announcer subscribe: AnnouncementMockB do: [ :ann | announcement := ann ]. announcement := nil. instance := announcer announce: AnnouncementMockA. self assert: announcement isNil. announcement := nil. instance := announcer announce: AnnouncementMockB. self assert: announcement = instance. announcement := nil. instance := announcer announce: AnnouncementMockC. self assert: announcement = instance.! ! !AnnouncerTest methodsFor: 'testing' stamp: 'lr 9/25/2006 09:10'! testUnsubscribeBlock | announcement | announcer subscribe: AnnouncementMockA do: [ :ann | announcement := ann ]. announcer unsubscribe: self. announcement := nil. announcer announce: AnnouncementMockA new. self assert: announcement isNil! ! !AnnouncerTest methodsFor: 'testing' stamp: 'lr 9/25/2006 09:13'! testUnsubscribeSend | announcement receiver | announcer subscribe: AnnouncementMockA send: #value: to: (receiver := [ :ann | announcement := ann ]). announcer unsubscribe: receiver. announcement := nil. announcer announce: AnnouncementMockA new. self assert: announcement isNil! ! !AnnouncerTest methodsFor: 'testing' stamp: 'lr 9/25/2006 09:13'! testUnsubscribeSet | announcement | announcer subscribe: AnnouncementMockA , AnnouncementMockB do: [ :ann | announcement := ann ]. announcer unsubscribe: self. announcement := nil. announcer announce: AnnouncementMockA new. self assert: announcement isNil. announcement := nil. announcer announce: AnnouncementMockB new. self assert: announcement isNil.! ! Object subclass: #AppRegistry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Applications'! !AppRegistry commentStamp: 'ads 4/2/2003 15:30' prior: 0! AppRegistry is a simple little class, not much more than a wrapper around a collection. It's intended to help break dependencies between packages. For example, if you'd like to be able to send e-mail, you could use the bare-bones MailComposition class, or you could use the full-blown Celeste e-mail client. Instead of choosing one or the other, you can call "MailSender default" (where MailSender is a subclass of AppRegistry), and thus avoid creating a hard-coded dependency on either of the two mail senders. This will only really be useful, of course, for applications that have a very simple, general, well-defined interface. Most of the time, you're probably better off just marking your package as being dependent on a specific other package, and avoiding the hassle of this whole AppRegistry thing. But for simple things like e-mail senders or web browsers, it might be useful. ! !AppRegistry methodsFor: 'notes' stamp: 'ads 4/2/2003 15:04'! seeClassSide "All the code for AppRegistry is on the class side."! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AppRegistry class instanceVariableNames: 'registeredClasses default'! !AppRegistry class methodsFor: 'as yet unclassified' stamp: 'ads 3/29/2003 13:36'! appName "Defaults to the class name, which is probably good enough, but you could override this in subclasses if you want to." ^ self name! ! !AppRegistry class methodsFor: 'as yet unclassified' stamp: 'alain.plantec 2/8/2009 21:37'! askForDefault "self askForDefault" self registeredClasses isEmpty ifTrue: [self inform: 'There are no ', self appName, ' applications registered.'. ^ default := nil]. self registeredClasses size = 1 ifTrue: [^ default := self registeredClasses anyOne]. default := UIManager default chooseFrom: (self registeredClasses collect: [:c | c name]) values: self registeredClasses title: ('Which ' , self appName, ' would you prefer?') translated. default ifNil: [default := self registeredClasses first]. ^default.! ! !AppRegistry class methodsFor: 'as yet unclassified' stamp: 'ads 3/29/2003 13:11'! default ^ default ifNil: [self askForDefault]! ! !AppRegistry class methodsFor: 'as yet unclassified' stamp: 'nk 3/9/2004 12:33'! default: aClassOrNil "Sets my default to aClassOrNil. Answers the old default." | oldDefault | oldDefault := default. aClassOrNil ifNotNil: [ self register: aClassOrNil ]. default := aClassOrNil. ^ oldDefault! ! !AppRegistry class methodsFor: 'as yet unclassified' stamp: 'nk 3/9/2004 12:35'! defaultOrNil ^ default! ! !AppRegistry class methodsFor: 'as yet unclassified' stamp: 'ads 4/2/2003 15:25'! register: aProviderClass (self registeredClasses includes: aProviderClass) ifFalse: [default := nil. "so it'll ask for a new default, since if you're registering a new app you probably want to use it" self registeredClasses add: aProviderClass].! ! !AppRegistry class methodsFor: 'as yet unclassified' stamp: 'ads 3/29/2003 13:01'! registeredClasses ^ registeredClasses ifNil: [registeredClasses := OrderedCollection new]! ! !AppRegistry class methodsFor: 'as yet unclassified' stamp: 'ar 9/27/2005 21:48'! removeObsolete "AppRegistry removeObsoleteClasses" self registeredClasses copy do:[:cls| (cls class isObsolete or:[cls isBehavior and:[cls isObsolete]]) ifTrue:[self unregister: cls]]. self subclasses do:[:cls| cls removeObsolete].! ! !AppRegistry class methodsFor: 'as yet unclassified' stamp: 'ads 3/29/2003 13:03'! unregister: aProviderClass (default = aProviderClass) ifTrue: [default := nil]. self registeredClasses remove: aProviderClass ifAbsent: [].! ! Path subclass: #Arc instanceVariableNames: 'quadrant radius center' classVariableNames: '' poolDictionaries: '' category: 'ST80-Paths'! !Arc commentStamp: '' prior: 0! Arcs are an unusual implementation of splines due to Ted Kaehler. Imagine two lines that meet at a corner. Now imagine two moving points; one moves from the corner to the end on one line, the other moves from the end of the other line in to the corner. Now imagine a series of lines drawn between those moving points at each step along the way (they form a sort of spider web pattern). By connecting segments of the intersecting lines, a smooth curve is achieved that is tangent to both of the original lines. Voila.! !Arc methodsFor: 'accessing'! center "Answer the point at the center of the receiver." ^center! ! !Arc methodsFor: 'accessing'! center: aPoint "Set aPoint to be the receiver's center." center := aPoint! ! !Arc methodsFor: 'accessing'! center: aPoint radius: anInteger "The receiver is defined by a point at the center and a radius. The quadrant is not reset." center := aPoint. radius := anInteger! ! !Arc methodsFor: 'accessing'! center: aPoint radius: anInteger quadrant: section "Set the receiver's quadrant to be the argument, section. The size of the receiver is defined by the center and its radius." center := aPoint. radius := anInteger. quadrant := section! ! !Arc methodsFor: 'accessing'! quadrant "Answer the part of the circle represented by the receiver." ^quadrant! ! !Arc methodsFor: 'accessing'! quadrant: section "Set the part of the circle represented by the receiver to be the argument, section." quadrant := section! ! !Arc methodsFor: 'accessing'! radius "Answer the receiver's radius." ^radius! ! !Arc methodsFor: 'accessing'! radius: anInteger "Set the receiver's radius to be the argument, anInteger." radius := anInteger! ! !Arc methodsFor: 'display box access'! computeBoundingBox | aRectangle aPoint | aRectangle := center - radius + form offset extent: form extent + (radius * 2) asPoint. aPoint := center + form extent. quadrant = 1 ifTrue: [^ aRectangle encompass: center x @ aPoint y]. quadrant = 2 ifTrue: [^ aRectangle encompass: aPoint x @ aPoint y]. quadrant = 3 ifTrue: [^ aRectangle encompass: aPoint x @ center y]. quadrant = 4 ifTrue: [^ aRectangle encompass: center x @ center y]! ! !Arc methodsFor: 'displaying'! displayOn: aDisplayMedium at: aPoint clippingBox: clipRect rule: anInteger fillColor: aForm | nSegments line angle sin cos xn yn xn1 yn1 | nSegments := 12.0. line := Line new. line form: self form. angle := 90.0 / nSegments. sin := (angle * (2 * Float pi / 360.0)) sin. cos := (angle * (2 * Float pi / 360.0)) cos. quadrant = 1 ifTrue: [xn := radius asFloat. yn := 0.0]. quadrant = 2 ifTrue: [xn := 0.0. yn := 0.0 - radius asFloat]. quadrant = 3 ifTrue: [xn := 0.0 - radius asFloat. yn := 0.0]. quadrant = 4 ifTrue: [xn := 0.0. yn := radius asFloat]. nSegments asInteger timesRepeat: [xn1 := xn * cos + (yn * sin). yn1 := yn * cos - (xn * sin). line beginPoint: center + (xn asInteger @ yn asInteger). line endPoint: center + (xn1 asInteger @ yn1 asInteger). line displayOn: aDisplayMedium at: aPoint clippingBox: clipRect rule: anInteger fillColor: aForm. xn := xn1. yn := yn1]! ! !Arc methodsFor: 'displaying'! displayOn: aDisplayMedium transformation: aTransformation clippingBox: clipRect rule: anInteger fillColor: aForm | newArc tempCenter | newArc := Arc new. tempCenter := aTransformation applyTo: self center. newArc center: tempCenter x asInteger @ tempCenter y asInteger. newArc quadrant: self quadrant. newArc radius: (self radius * aTransformation scale x) asInteger. newArc form: self form. newArc displayOn: aDisplayMedium at: 0 @ 0 clippingBox: clipRect rule: anInteger fillColor: aForm! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Arc class instanceVariableNames: ''! !Arc class methodsFor: 'examples'! example "Click the button somewhere on the screen. The designated point will be the center of an Arc with radius 50 in the 4th quadrant." | anArc aForm | aForm := Form extent: 1 @ 30. "make a long thin Form for display" aForm fillBlack. "turn it black" anArc := Arc new. anArc form: aForm. "set the form for display" anArc radius: 50.0. anArc center: Sensor waitButton. anArc quadrant: 4. anArc displayOn: Display. Sensor waitButton "Arc example"! ! Object subclass: #Archive instanceVariableNames: 'members' classVariableNames: '' poolDictionaries: '' category: 'Compression-Archives'! !Archive commentStamp: '' prior: 0! This is the abstract superclass for file archives. Archives can be read from or written to files, and contain members that represent files and directories.! !Archive methodsFor: 'archive operations' stamp: 'nk 2/22/2001 19:09'! addDirectory: aFileName ^self addDirectory: aFileName as: aFileName ! ! !Archive methodsFor: 'archive operations' stamp: 'nk 12/20/2002 14:57'! addDirectory: aFileName as: anotherFileName | newMember | newMember := self memberClass newFromDirectory: aFileName. self addMember: newMember. newMember localFileName: anotherFileName. ^newMember! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/21/2001 18:29'! addFile: aFileName ^self addFile: aFileName as: aFileName! ! !Archive methodsFor: 'archive operations' stamp: 'nk 12/20/2002 15:03'! addFile: aFileName as: anotherFileName | newMember | newMember := self memberClass newFromFile: aFileName. self addMember: newMember. newMember localFileName: anotherFileName. ^newMember! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/22/2001 19:09'! addMember: aMember ^members addLast: aMember! ! !Archive methodsFor: 'archive operations' stamp: 'nk 12/20/2002 15:03'! addString: aString as: aFileName | newMember | newMember := self memberClass newFromString: aString named: aFileName. self addMember: newMember. newMember localFileName: aFileName. ^newMember! ! !Archive methodsFor: 'archive operations' stamp: 'tak 2/2/2005 13:22'! addTree: aFileNameOrDirectory match: aBlock | nameSize | nameSize := aFileNameOrDirectory isString ifTrue: [aFileNameOrDirectory size] ifFalse: [aFileNameOrDirectory pathName size]. ^ self addTree: aFileNameOrDirectory removingFirstCharacters: nameSize + 1 match: aBlock! ! !Archive methodsFor: 'archive operations' stamp: 'tak 2/2/2005 13:00'! addTree: aFileNameOrDirectory removingFirstCharacters: n ^ self addTree: aFileNameOrDirectory removingFirstCharacters: n match: [:e | true]! ! !Archive methodsFor: 'archive operations' stamp: 'eem 6/11/2008 12:47'! addTree: aFileNameOrDirectory removingFirstCharacters: n match: aBlock | dir fullPath relativePath | dir := (aFileNameOrDirectory isString) ifTrue: [ FileDirectory on: aFileNameOrDirectory ] ifFalse: [ aFileNameOrDirectory ]. fullPath := dir pathName, dir slash. relativePath := fullPath copyFrom: n + 1 to: fullPath size. (dir entries select: [ :entry | aBlock value: entry]) do: [ :ea | | fullName newMember | fullName := fullPath, ea name. newMember := ea isDirectory ifTrue: [ self memberClass newFromDirectory: fullName ] ifFalse: [ self memberClass newFromFile: fullName ]. newMember localFileName: relativePath, ea name. self addMember: newMember. ea isDirectory ifTrue: [ self addTree: fullName removingFirstCharacters: n match: aBlock]. ]. ! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/24/2001 14:12'! canWriteToFileNamed: aFileName "Catch attempts to overwrite existing zip file" ^(members anySatisfy: [ :ea | ea usesFileNamed: aFileName ]) not. ! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/22/2001 07:57'! contentsOf: aMemberOrName | member | member := self member: aMemberOrName. member ifNil: [ ^nil ]. ^member contents! ! !Archive methodsFor: 'archive operations' stamp: 'nk 12/20/2002 14:48'! extractMember: aMemberOrName | member | member := self member: aMemberOrName. member ifNil: [ ^nil ]. member extractToFileNamed: member localFileName inDirectory: FileDirectory default.! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/22/2001 07:57'! extractMember: aMemberOrName toFileNamed: aFileName | member | member := self member: aMemberOrName. member ifNil: [ ^nil ]. member extractToFileNamed: aFileName! ! !Archive methodsFor: 'archive operations' stamp: 'nk 11/11/2002 14:09'! extractMemberWithoutPath: aMemberOrName self extractMemberWithoutPath: aMemberOrName inDirectory: FileDirectory default.! ! !Archive methodsFor: 'archive operations' stamp: 'nk 12/20/2002 14:48'! extractMemberWithoutPath: aMemberOrName inDirectory: dir | member | member := self member: aMemberOrName. member ifNil: [ ^nil ]. member extractToFileNamed: (FileDirectory localNameFor: member localFileName) inDirectory: dir! ! !Archive methodsFor: 'archive operations' stamp: 'nk 12/20/2002 14:50'! memberNamed: aString "Return the first member whose zip name or local file name matches aString, or nil" ^members detect: [ :ea | ea fileName = aString or: [ ea localFileName = aString ]] ifNone: [ ]! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/21/2001 18:00'! memberNames ^members collect: [ :ea | ea fileName ]! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/21/2001 17:58'! members ^members! ! !Archive methodsFor: 'archive operations' stamp: 'nk 12/20/2002 14:50'! membersMatching: aString ^members select: [ :ea | (aString match: ea fileName) or: [ aString match: ea localFileName ] ]! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/21/2001 17:59'! numberOfMembers ^members size! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/22/2001 07:57'! removeMember: aMemberOrName | member | member := self member: aMemberOrName. member ifNotNil: [ members remove: member ]. ^member! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/22/2001 07:57'! replaceMember: aMemberOrName with: newMember | member | member := self member: aMemberOrName. member ifNotNil: [ members replaceAll: member with: newMember ]. ^member! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/22/2001 17:24'! setContentsOf: aMemberOrName to: aString | newMember oldMember | oldMember := self member: aMemberOrName. newMember := (self memberClass newFromString: aString named: oldMember fileName) copyFrom: oldMember. self replaceMember: oldMember with: newMember.! ! !Archive methodsFor: 'archive operations' stamp: 'nk 2/21/2001 20:58'! writeTo: aStream self subclassResponsibility! ! !Archive methodsFor: 'archive operations' stamp: 'stephane.ducasse 8/8/2009 12:32'! writeToFileNamed: aFileName | stream | "Catch attempts to overwrite existing zip file" (self canWriteToFileNamed: aFileName) ifFalse: [ ^self error: (aFileName, ' is needed by one or more members in this archive') ]. stream := StandardFileStream forceNewFileNamed: aFileName. [ self writeTo: stream ] ensure: [ stream close ]! ! !Archive methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:39'! initialize super initialize. members := OrderedCollection new.! ! !Archive methodsFor: 'private' stamp: 'nk 2/22/2001 07:56'! member: aMemberOrName ^(members includes: aMemberOrName) ifTrue: [ aMemberOrName ] ifFalse: [ self memberNamed: aMemberOrName ].! ! !Archive methodsFor: 'private' stamp: 'nk 2/21/2001 18:14'! memberClass self subclassResponsibility! ! Object subclass: #ArchiveMember instanceVariableNames: 'fileName isCorrupt' classVariableNames: '' poolDictionaries: '' category: 'Compression-Archives'! !ArchiveMember commentStamp: '' prior: 0! This is the abstract superclass for archive members, which are files or directories stored in archives.! !ArchiveMember methodsFor: 'accessing' stamp: 'nk 2/22/2001 16:00'! fileName ^fileName! ! !ArchiveMember methodsFor: 'accessing' stamp: 'nk 2/22/2001 16:00'! fileName: aName fileName := aName! ! !ArchiveMember methodsFor: 'accessing' stamp: 'nk 3/7/2004 16:16'! isCorrupt ^isCorrupt ifNil: [ isCorrupt := false ]! ! !ArchiveMember methodsFor: 'accessing' stamp: 'nk 3/7/2004 16:06'! isCorrupt: aBoolean "Mark this member as being corrupt." isCorrupt := aBoolean! ! !ArchiveMember methodsFor: 'accessing' stamp: 'nk 12/20/2002 15:02'! localFileName: aString "Set my internal filename. Returns the (possibly new) filename. aString will be translated from local FS format into Unix format." ^fileName := aString copyReplaceAll: FileDirectory slash with: '/'.! ! !ArchiveMember methodsFor: 'initialization' stamp: 'ar 3/2/2001 18:46'! close ! ! !ArchiveMember methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:39'! initialize super initialize. fileName := ''. isCorrupt := false.! ! !ArchiveMember methodsFor: 'printing' stamp: 'nk 12/20/2002 15:11'! printOn: aStream super printOn: aStream. aStream nextPut: $(; nextPutAll: self fileName; nextPut: $)! ! !ArchiveMember methodsFor: 'testing' stamp: 'nk 2/21/2001 19:43'! usesFileNamed: aFileName "Do I require aFileName? That is, do I care if it's clobbered?" ^false! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ArchiveMember class instanceVariableNames: ''! !ArchiveMember class methodsFor: 'as yet unclassified' stamp: 'nk 2/21/2001 18:33'! newDirectoryNamed: aString self subclassResponsibility! ! !ArchiveMember class methodsFor: 'as yet unclassified' stamp: 'nk 2/21/2001 18:32'! newFromFile: aFileName self subclassResponsibility! ! !ArchiveMember class methodsFor: 'as yet unclassified' stamp: 'nk 2/21/2001 18:32'! newFromString: aString self subclassResponsibility! ! Error subclass: #ArithmeticError instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! ArrayedCollection variableSubclass: #Array instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Collections-Arrayed'! !Array commentStamp: '' prior: 0! I present an ArrayedCollection whose elements are objects.! !Array methodsFor: 'accessing' stamp: 'ar 8/26/2001 22:02'! atWrap: index "Optimized to go through the primitive if possible" ^ self at: index - 1 \\ self size + 1! ! !Array methodsFor: 'accessing' stamp: 'ar 8/26/2001 22:03'! atWrap: index put: anObject "Optimized to go through the primitive if possible" ^ self at: index - 1 \\ self size + 1 put: anObject! ! !Array methodsFor: 'arithmetic' stamp: 'raok 10/22/2002 20:09'! +* aCollection "Premultiply aCollection by self. aCollection should be an Array or Matrix. The name of this method is APL's +.x squished into Smalltalk syntax." ^aCollection preMultiplyByArray: self ! ! !Array methodsFor: 'arithmetic' stamp: 'raok 10/22/2002 20:10'! preMultiplyByArray: a "Answer a+*self where a is an Array. Arrays are always understood as column vectors, so an n element Array is an n*1 Array. This multiplication is legal iff self size = 1." self size = 1 ifFalse: [self error: 'dimensions do not conform']. ^a * self first! ! !Array methodsFor: 'arithmetic' stamp: 'eem 6/11/2008 12:49'! preMultiplyByMatrix: m "Answer m+*self where m is a Matrix." m columnCount = self size ifFalse: [self error: 'dimensions do not conform']. ^(1 to: m rowCount) collect: [:row | | s | s := 0. 1 to: self size do: [:k | s := (m at: row at: k) * (self at: k) + s]. s]! ! !Array methodsFor: 'comparing' stamp: 'ajh 2/2/2002 15:03'! literalEqual: other self class == other class ifFalse: [^ false]. self size = other size ifFalse: [^ false]. self with: other do: [:e1 :e2 | (e1 literalEqual: e2) ifFalse: [^ false]]. ^ true! ! !Array methodsFor: 'converting' stamp: 'sma 5/12/2000 17:32'! asArray "Answer with the receiver itself." ^ self! ! !Array methodsFor: 'converting' stamp: 'tpr 11/2/2004 11:31'! elementsExchangeIdentityWith: otherArray "This primitive performs a bulk mutation, causing all pointers to the elements of this array to be replaced by pointers to the corresponding elements of otherArray. At the same time, all pointers to the elements of otherArray are replaced by pointers to the corresponding elements of this array. The identityHashes remain with the pointers rather than with the objects so that objects in hashed structures should still be properly indexed after the mutation." otherArray class == Array ifFalse: [^ self error: 'arg must be array']. self size = otherArray size ifFalse: [^ self error: 'arrays must be same size']. (self anySatisfy: [:obj | obj class == SmallInteger]) ifTrue: [^ self error: 'can''t become SmallIntegers']. (otherArray anySatisfy: [:obj | obj class == SmallInteger]) ifTrue: [^ self error: 'can''t become SmallIntegers']. self with: otherArray do:[:a :b| a == b ifTrue:[^self error:'can''t become yourself']]. "Must have failed because not enough space in forwarding table (see ObjectMemory-prepareForwardingTableForBecoming:with:twoWay:). Do GC and try again only once" (Smalltalk bytesLeft: true) = Smalltalk primitiveGarbageCollect ifTrue: [^ self primitiveFailed]. ^ self elementsExchangeIdentityWith: otherArray! ! !Array methodsFor: 'converting' stamp: 'di 3/28/1999 10:23'! elementsForwardIdentityTo: otherArray "This primitive performs a bulk mutation, causing all pointers to the elements of this array to be replaced by pointers to the corresponding elements of otherArray. The identityHashes remain with the pointers rather than with the objects so that the objects in this array should still be properly indexed in any existing hashed structures after the mutation." self primitiveFailed! ! !Array methodsFor: 'converting' stamp: 'brp 9/26/2003 08:09'! elementsForwardIdentityTo: otherArray copyHash: copyHash "This primitive performs a bulk mutation, causing all pointers to the elements of this array to be replaced by pointers to the corresponding elements of otherArray. The identityHashes remain with the pointers rather than with the objects so that the objects in this array should still be properly indexed in any existing hashed structures after the mutation." self primitiveFailed! ! !Array methodsFor: 'converting' stamp: 'nice 4/16/2009 09:35'! evalStrings "Allows you to construct literal arrays. #(true false nil '5@6' 'Set new' '''text string''') evalStrings gives an array with true, false, nil, a Point, a Set, and a String instead of just a bunch of Symbols" ^ self collect: [:each | | item | item := each. (each isString and: [each isSymbol not]) ifTrue: [ item := Compiler evaluate: each]. each class == Array ifTrue: [item := item evalStrings]. item]! ! !Array methodsFor: 'copying' stamp: 'ar 2/11/2001 01:55'! copyWithDependent: newElement self size = 0 ifTrue:[^DependentsArray with: newElement]. ^self copyWith: newElement! ! !Array methodsFor: 'file in/out' stamp: 'tk 9/28/2000 15:35'! objectForDataStream: refStrm | dp | "I am about to be written on an object file. If I am one of two shared global arrays, write a proxy instead." self == (TextConstants at: #DefaultTabsArray) ifTrue: [ dp := DiskProxy global: #TextConstants selector: #at: args: #(DefaultTabsArray). refStrm replace: self with: dp. ^ dp]. self == (TextConstants at: #DefaultMarginTabsArray) ifTrue: [ dp := DiskProxy global: #TextConstants selector: #at: args: #(DefaultMarginTabsArray). refStrm replace: self with: dp. ^ dp]. ^ super objectForDataStream: refStrm! ! !Array methodsFor: 'filter streaming' stamp: 'MPW 1/1/1901 01:42'! byteEncode:aStream aStream writeArray:self. ! ! !Array methodsFor: 'filter streaming' stamp: 'MPW 1/1/1901 01:55'! storeOnStream:aStream self isLiteral ifTrue: [super storeOnStream:aStream] ifFalse:[aStream writeCollection:self]. ! ! !Array methodsFor: 'printing' stamp: 'sd 7/31/2005 21:44'! printOn: aStream self isLiteral ifTrue: [self printAsLiteralFormOn: aStream. ^ self]. self isSelfEvaluating ifTrue: [self printAsSelfEvaluatingFormOn: aStream. ^ self]. super printOn: aStream! ! !Array methodsFor: 'printing'! storeOn: aStream "Use the literal form if possible." self isLiteral ifTrue: [aStream nextPut: $#; nextPut: $(. self do: [:element | element printOn: aStream. aStream space]. aStream nextPut: $)] ifFalse: [super storeOn: aStream]! ! !Array methodsFor: 'self evaluating' stamp: 'sd 7/31/2005 21:44'! isSelfEvaluating ^ (self allSatisfy: [:each | each isSelfEvaluating]) and: [self class == Array]! ! !Array methodsFor: 'self evaluating' stamp: 'sd 7/31/2005 21:44'! printAsLiteralFormOn: aStream aStream nextPut: $#. self printElementsOn: aStream ! ! !Array methodsFor: 'self evaluating' stamp: 'MarcusDenker 10/5/2009 11:44'! printAsSelfEvaluatingFormOn: aStream aStream nextPut: ${. self do: [:el | aStream print: el] separatedBy: [ aStream nextPutAll: '. ']. aStream nextPut: $}! ! !Array methodsFor: 'testing' stamp: 'eem 5/8/2008 11:13'! isArray ^true! ! !Array methodsFor: 'testing' stamp: 'sma 5/12/2000 14:11'! isLiteral ^ self allSatisfy: [:each | each isLiteral]! ! !Array methodsFor: 'private' stamp: 'marcus.denker 9/28/2008 09:57'! hasLiteral: literal "Answer true if literal is identical to any literal in this array, even if imbedded in further array structure. This method is only intended for private use by CompiledMethod hasLiteralSymbol:" 1 to: self size do: [:index | | lit | (lit := self at: index) == literal ifTrue: [^ true]. (lit class == Array and: [lit hasLiteral: literal]) ifTrue: [^ true]]. ^ false! ! !Array methodsFor: 'private' stamp: 'md 3/1/2006 21:09'! hasLiteralSuchThat: testBlock "Answer true if testBlock returns true for any literal in this array, even if imbedded in further Arrays or CompiledMethods. This method is only intended for private use by CompiledMethod hasLiteralSuchThat:" | lit | 1 to: self size do: [:index | (testBlock value: (lit := self at: index)) ifTrue: [^ true]. (lit hasLiteralSuchThat: testBlock) ifTrue: [^ true]]. ^ false! ! !Array methodsFor: 'private' stamp: 'G.C 10/22/2008 09:59'! refersToLiteral: literal "Answer true if literal is identical to any literal in this array, even if imbedded in further array structures or closure methods" 1 to: self size do: [ :index | | lit | (lit := self at: index) == literal ifTrue: [ ^ true ]. (lit refersToLiteral: literal) ifTrue: [ ^ true ] ]. ^ false! ! !Array methodsFor: 'private'! replaceFrom: start to: stop with: replacement startingAt: repStart "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive." super replaceFrom: start to: stop with: replacement startingAt: repStart! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Array class instanceVariableNames: ''! !Array class methodsFor: 'brace support' stamp: 'di 11/18/1999 22:53'! braceStream: nElements "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." ^ WriteStream basicNew braceArray: (self new: nElements) ! ! !Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:16'! braceWith: a "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." | array | array := self new: 1. array at: 1 put: a. ^ array! ! !Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:15'! braceWith: a with: b "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." | array | array := self new: 2. array at: 1 put: a. array at: 2 put: b. ^ array! ! !Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:17'! braceWith: a with: b with: c "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." | array | array := self new: 3. array at: 1 put: a. array at: 2 put: b. array at: 3 put: c. ^ array! ! !Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:17'! braceWith: a with: b with: c with: d "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." | array | array := self new: 4. array at: 1 put: a. array at: 2 put: b. array at: 3 put: c. array at: 4 put: d. ^ array! ! !Array class methodsFor: 'brace support' stamp: 'di 11/19/1999 08:16'! braceWithNone "This method is used in compilation of brace constructs. It MUST NOT be deleted or altered." ^ self new: 0! ! !Array class methodsFor: 'instance creation' stamp: 'md 7/19/2004 12:34'! new: sizeRequested "Answer an instance of this class with the number of indexable variables specified by the argument, sizeRequested. This is a shortcut (direct call of primitive, no #initialize, for performance" "This method runs primitively if successful" ^ self basicNew: sizeRequested "Exceptional conditions will be handled in basicNew:" ! ! TestCase subclass: #ArrayLiteralTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Compiler'! !ArrayLiteralTest methodsFor: 'initialization' stamp: 'avi 2/16/2004 21:09'! tearDown self class removeSelector: #array! ! !ArrayLiteralTest methodsFor: 'tests' stamp: 'lr 1/29/2009 20:34'! testByteArrayBase self class compile: 'array ^ #[2r1010 8r333 16rFF]'. self assert: (self array isKindOf: ByteArray). self assert: (self array size = 3). self assert: (self array first = 10). self assert: (self array second = 219). self assert: (self array last = 255) ! ! !ArrayLiteralTest methodsFor: 'tests' stamp: 'lr 1/29/2009 20:35'! testByteArrayEmpty self class compile: 'array ^ #[]'. self assert: (self array isKindOf: ByteArray). self assert: (self array isEmpty)! ! !ArrayLiteralTest methodsFor: 'tests' stamp: 'lr 1/29/2009 20:36'! testByteArrayLiteral self class compile: 'array ^ #[ 1 2 3 4 ]'. self assert: (self array = self array). self assert: (self array == self array)! ! !ArrayLiteralTest methodsFor: 'tests' stamp: 'lr 1/29/2009 20:45'! testByteArrayLong self class compile: 'array ^ #[ ' , ((0 to: 255) inject: ' ' into: [ :r :e | r , ' ' , e asString ]) , ' ]'. self assert: (self array isKindOf: ByteArray). self assert: (self array size = 256). 0 to: 255 do: [ :index | self assert: (self array at: index + 1) = index ]! ! !ArrayLiteralTest methodsFor: 'tests' stamp: 'lr 1/29/2009 20:32'! testByteArrayRange self class compile: 'array ^ #[ 0 255 ]'. self assert: (self array isKindOf: ByteArray). self assert: (self array size = 2). self assert: (self array first = 0). self assert: (self array last = 255)! ! !ArrayLiteralTest methodsFor: 'tests' stamp: 'Henrik Sperre Johansen 3/23/2009 13:55'! testByteArrayWithinArray self class compile: 'array ^ #( #[1] #[2] )'. self assert: (self array isKindOf: Array). self assert: (self array size = 2). self assert: (self array first isKindOf: ByteArray). self assert: (self array first first = 1). self assert: (self array last isKindOf: ByteArray). self assert: (self array last first = 2) ! ! !ArrayLiteralTest methodsFor: 'tests' stamp: 'avi 2/16/2004 21:08'! testReservedIdentifiers self class compile: 'array ^ #(nil true false)'. self assert: self array = {nil. true. false}.! ! !ArrayLiteralTest methodsFor: 'tests' stamp: 'avi 2/16/2004 21:09'! testSymbols self class compile: 'array ^ #(#nil #true #false #''nil'' #''true'' #''false'')'. self assert: self array = {#nil. #true. #false. #nil. #true. #false}.! ! CollectionRootTest subclass: #ArrayTest uses: TEmptySequenceableTest + TSequencedElementAccessTest + TCloneTest + TIncludesWithIdentityCheckTest + TCopyTest + TSetArithmetic + TCreationWithTest + TPutBasicTest + TConvertTest - {} + TSortTest + TOccurrencesForMultiplinessTest + TIterateSequencedReadableTest + TSequencedConcatenationTest + TReplacementSequencedTest + TAsStringCommaAndDelimiterSequenceableTest + TBeginsEndsWith + TPrintOnSequencedTest + TIndexAccess + TSubCollectionAccess + TConvertAsSetForMultiplinessIdentityTest + TCopyPartOfSequenceable + TCopySequenceableSameContents + TCopySequenceableWithOrWithoutSpecificElements + TCopySequenceableWithReplacement + TIndexAccessForMultipliness + TCopyPartOfSequenceableForMultipliness + TConvertAsSortedTest + TPutTest + TSequencedStructuralEqualityTest instanceVariableNames: 'example1 literalArray selfEvaluatingArray otherArray nonSEArray1 nonSEarray2 example2 empty collection result withoutEqualElements withEqualElements withCharacters unsortedCollection sortedInAscendingOrderCollection sizeCollection collectionNotIncluded removedCollection elementInForCopy elementNotInForCopy firstIndex secondIndex replacementCollection indexArray valueArray nonEmptyMoreThan1Element subCollectionNotIn replacementCollectionSameSize oldSubCollection nonEmpty1Element collectionOfCollection collectionOfFloatWithEqualElements floatCollectionWithSameBeginingAnEnd collectionWithoutNil duplicateElement collection5Elements' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Arrayed'! !ArrayTest commentStamp: '' prior: 0! This is the unit test for the class Array. Unit tests are a good way to exercise the functionality of your system in a repeatable and automatic manner. They are therefore recommended if you plan to release anything. For more information, see: - http://www.c2.com/cgi/wiki?UnitTest - http://minnow.cc.gatech.edu/squeak/1547 - the sunit class category! !ArrayTest methodsFor: 'helpers' stamp: 'stephane.ducasse 1/12/2009 17:12'! aValue ^ 33! ! !ArrayTest methodsFor: 'helpers' stamp: 'stephane.ducasse 1/12/2009 17:13'! anIndex ^ 2! ! !ArrayTest methodsFor: 'helpers' stamp: 'stephane.ducasse 1/12/2009 17:19'! anotherValue ^ 66! ! !ArrayTest methodsFor: 'initialization' stamp: 'stephane.ducasse 10/6/2008 16:53'! collection ^ collection ! ! !ArrayTest methodsFor: 'initialization' stamp: 'stephane.ducasse 10/5/2008 15:06'! empty ^ empty! ! !ArrayTest methodsFor: 'initialization' stamp: 'stephane.ducasse 10/5/2008 15:06'! nonEmpty ^ example1! ! !ArrayTest methodsFor: 'initialization' stamp: 'stephane.ducasse 10/6/2008 16:54'! result ^ result! ! !ArrayTest methodsFor: 'initialization' stamp: 'delaunay 5/14/2009 14:00'! setUp literalArray := #(1 true 3 #four). selfEvaluatingArray := { 1. true. (3/4). Color black. (2 to: 4) . 5 }. nonSEArray1 := { 1 . Set with: 1 }. nonSEarray2 := { Smalltalk associationAt: #Array }. example1 := #(1 2 3 4 5) copy. indexArray:= {2. 3. 4.}. valueArray:={0. 0. 0.}. oldSubCollection:= {2. 3. 4.}. nonEmptyMoreThan1Element:= example1. subCollectionNotIn:= {1. 8. 3.}. collectionNotIncluded:= {7. 8. 9.}. removedCollection:= { 2. 4. }. example2 := {1. 2. 3/4. 4. 5}. collection := #(1 -2 3 1). collectionWithoutNil := #( 1 2 3 4). result := {SmallInteger. SmallInteger. SmallInteger. SmallInteger.}. empty := #(). duplicateElement := 5.2. withEqualElements := {1.5. duplicateElement . 6.1. 2.0. duplicateElement .} . withoutEqualElements := {1.1. 4.4. 6.5. 2.4. 3.1.}. withCharacters := {$a. $x. $d. $c. $m.}. unsortedCollection := {1. 2. 8. 5. 6. 7.}. sortedInAscendingOrderCollection := {1. 2. 3. 4. 5. 6.}. elementInForCopy:= 2. elementNotInForCopy:= 9. firstIndex:= 2. secondIndex:= 4. replacementCollection:= {4. 3. 2. 1.}. replacementCollectionSameSize := {5. 4. 3.}. nonEmpty1Element:={ 5.}. collectionOfCollection:={1.5. 5.5. 6.5.}. collectionOfFloatWithEqualElements:={1.5. 5.5. 6.5. 1.5}. floatCollectionWithSameBeginingAnEnd := {1.5. 5.5. 1.5 copy}. collection5Elements := { 1. 2. 5. 3. 4.}.! ! !ArrayTest methodsFor: 'parameters'! accessValuePutIn "return access the element put in the non-empty collection" ^ self perform: self selectorToAccessValuePutIn! ! !ArrayTest methodsFor: 'parameters'! accessValuePutInOn: s "return access the element put in the non-empty collection" ^ s perform: self selectorToAccessValuePutIn! ! !ArrayTest methodsFor: 'parameters' stamp: 'stephane.ducasse 10/5/2008 15:12'! selectorToAccessValuePutIn "return the selector of the method that should be invoked to access an element" ^ #second! ! !ArrayTest methodsFor: 'parameters' stamp: 'stephane.ducasse 10/9/2008 18:49'! valuePutIn "the value that we will put in the non empty collection" ^ 2! ! !ArrayTest methodsFor: 'requirements' stamp: 'stephane.ducasse 10/30/2008 19:02'! accessCollection ^ example1! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/24/2009 14:45'! anotherElementNotIn ^ elementNotInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 12:05'! anotherElementOrAssociationIn " return an element (or an association for Dictionary ) present in 'collection' " ^ self collection anyOne.! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 12:05'! anotherElementOrAssociationNotIn " return an element (or an association for Dictionary )not present in 'collection' " ^ elementNotInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/9/2009 11:11'! collectionInForIncluding ^ self nonEmpty copyWithoutFirst.! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/23/2009 15:16'! collectionMoreThan1NoDuplicates " return a collection of size 5 without equal elements" ^ withoutEqualElements ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 14:01'! collectionMoreThan5Elements " return a collection including at least 5 elements" ^ collection5Elements ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/30/2009 10:51'! collectionNotIncluded ^ collectionNotIncluded.! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/15/2009 14:07'! collectionOfFloat ^ collectionOfCollection! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/17/2009 10:28'! collectionWith1TimeSubcollection ^ (self oldSubCollection copyWithoutFirst),self oldSubCollection,(self oldSubCollection copyWithoutFirst). ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/17/2009 10:29'! collectionWith2TimeSubcollection ^ (self oldSubCollection copyWithoutFirst),self oldSubCollection,(self oldSubCollection copyWithoutFirst),self oldSubCollection .! ! !ArrayTest methodsFor: 'requirements' stamp: 'cyrille.delaunay 3/26/2009 09:58'! collectionWithCharacters ^ withCharacters.! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 13:49'! collectionWithCopy "return a collection of type 'self collectionWIithoutEqualsElements clas' containing no elements equals ( with identity equality) but 2 elements only equals with classic equality" | result collection | collection := OrderedCollection withAll: self elementsCopyNonIdenticalWithoutEqualElements. collection add: collection first copy. result := self elementsCopyNonIdenticalWithoutEqualElements class withAll: collection. ^ result! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 10:22'! collectionWithCopyNonIdentical " return a collection that include elements for which 'copy' return a different object (this is not the case of SmallInteger)" ^ collectionOfCollection! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/17/2009 15:24'! collectionWithElementsToRemove ^ removedCollection! ! !ArrayTest methodsFor: 'requirements' stamp: 'cyrille.delaunay 3/26/2009 09:57'! collectionWithEqualElements ^ withEqualElements.! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 13:50'! collectionWithIdentical "return a collection of type : 'self collectionWIithoutEqualsElements class containing two elements equals ( with identity equality)" | result collection element | collection := OrderedCollection withAll: self elementsCopyNonIdenticalWithoutEqualElements. element := collection first. collection add: element. result := self elementsCopyNonIdenticalWithoutEqualElements class withAll: collection. ^ result! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/27/2009 14:17'! collectionWithNonIdentitySameAtEndAndBegining " return a collection with elements at end and begining equals only with classic equality (they are not the same object). (others elements of the collection are not equal to those elements)" ^ floatCollectionWithSameBeginingAnEnd ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/22/2009 11:15'! collectionWithSameAtEndAndBegining " return a collection with elements at end and begining equals . (others elements of the collection are not equal to those elements)" ^ floatCollectionWithSameBeginingAnEnd ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/24/2009 10:27'! collectionWithSortableElements " return a collection elements that can be sorte ( understanding message ' < ' or ' > ')" ^ withoutEqualElements ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/20/2009 10:25'! collectionWithoutEqualElements ^ withoutEqualElements .! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/16/2009 15:49'! collectionWithoutEqualsElements ^ withoutEqualElements ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/23/2009 11:39'! collectionWithoutNilElements " return a collection that doesn't includes a nil element and that doesn't includes equal elements'" ^ collectionWithoutNil ! ! !ArrayTest methodsFor: 'requirements' stamp: 'damienpollet 1/30/2009 17:27'! element ^ 3! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/15/2009 14:22'! elementInCollectionOfFloat ^ collectionOfCollection atRandom! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/31/2009 10:28'! elementInForCopy ^ elementInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/20/2009 14:39'! elementInForElementAccessing " return an element inculded in 'accessCollection '" ^ self accessCollection anyOne! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/14/2009 13:55'! elementInForIncludesTest ^ elementInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/10/2009 14:49'! elementInForIndexAccess ^ elementInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/23/2009 15:18'! elementInForIndexAccessing ^ withoutEqualElements anyOne! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/2/2009 11:54'! elementInForOccurrences ^ elementInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/6/2009 10:16'! elementInForReplacement ^ elementInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/24/2009 14:45'! elementNotIn "return an element not included in 'nonEmpty' " ^ elementNotInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/31/2009 10:29'! elementNotInForCopy ^ elementNotInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/20/2009 14:39'! elementNotInForElementAccessing " return an element not included in 'accessCollection' " ^ elementNotInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/7/2009 11:18'! elementNotInForIndexAccessing ^elementNotInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/24/2009 14:45'! elementNotInForOccurrences ^ elementNotInForCopy ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/13/2009 16:13'! elementTwiceInForOccurrences " return an element included exactly two time in # collectionWithEqualElements" ^ duplicateElement ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 13:46'! elementsCopyNonIdenticalWithoutEqualElements " return a collection that does niot include equal elements ( classic equality )" ^ collectionOfCollection! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/2/2009 16:41'! firstCollection ^example1 ! ! !ArrayTest methodsFor: 'requirements' stamp: 'damiencassou 1/27/2009 10:35'! firstEven "Returns the first even number of #collection" ^ -2! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/31/2009 10:29'! firstIndex ^ firstIndex ! ! !ArrayTest methodsFor: 'requirements' stamp: 'damiencassou 1/27/2009 10:35'! firstOdd "Returns the first odd number of #collection" ^ 1! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/21/2009 14:00'! floatCollectionWithSameAtEndAndBegining " return a collection with elements at end and begining equals only with classic equality (they are not the same object). (others elements of the collection are not equal to those elements)" ^ floatCollectionWithSameBeginingAnEnd ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/31/2009 16:00'! indexArray ^ indexArray .! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/16/2009 15:59'! indexInForCollectionWithoutDuplicates ^ 2.! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/16/2009 16:56'! indexInNonEmpty ^ 2 ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/9/2009 15:53'! integerCollection ^example1 .! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/20/2009 10:28'! integerCollectionWithoutEqualElements ^{1. 2. 6. 5.}! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/27/2009 10:53'! moreThan3Elements " return a collection including atLeast 3 elements" ^ example1 ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/27/2009 10:53'! moreThan4Elements " return a collection including at leat 4 elements" ^ example1 ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/6/2009 10:16'! newElement ^999! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/8/2009 11:40'! nonEmpty1Element ^ nonEmpty1Element ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/2/2009 15:20'! nonEmptyMoreThan1Element ^nonEmptyMoreThan1Element .! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/6/2009 11:41'! oldSubCollection ^oldSubCollection ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/31/2009 10:29'! replacementCollection ^replacementCollection .! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/6/2009 10:32'! replacementCollectionSameSize ^replacementCollectionSameSize ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/23/2009 11:29'! resultForCollectElementsClass " return the retsult expected by collecting the class of each element of collectionWithoutNilElements" ^ result ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/2/2009 16:41'! secondCollection ^example2 ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/31/2009 10:29'! secondIndex ^ secondIndex ! ! !ArrayTest methodsFor: 'requirements' stamp: 'damienpollet 1/13/2009 16:59'! sizeCollection ^ self collection! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/31/2009 14:08'! smallerIndex ^ firstIndex -1! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/27/2009 15:20'! sortedInAscendingOrderCollection ^sortedInAscendingOrderCollection . ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/3/2009 11:35'! subCollectionNotIn ^subCollectionNotIn ! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 3/27/2009 15:20'! unsortedCollection ^unsortedCollection .! ! !ArrayTest methodsFor: 'requirements'! valueArray " return a collection (with the same size than 'indexArray' )of values to be put in 'nonEmpty' at indexes in 'indexArray' " | result | result := Array new: self indexArray size. 1 to: result size do: [:i | result at:i put: (self aValue ). ]. ^ result.! ! !ArrayTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 14:11'! withEqualElements " return a collection of float including equal elements (classic equality)" ^ collectionOfFloatWithEqualElements! ! !ArrayTest methodsFor: 'test - copy' stamp: 'delaunay 4/17/2009 15:26'! elementToAdd ^ 55! ! !ArrayTest methodsFor: 'test - creation' stamp: 'stephane.ducasse 12/9/2008 22:00'! collectionClass ^ Array! ! !ArrayTest methodsFor: 'test - creation'! testOfSize "self debug: #testOfSize" | aCol | aCol := self collectionClass ofSize: 3. self assert: (aCol size = 3). ! ! !ArrayTest methodsFor: 'test - creation'! testWith "self debug: #testWith" | aCol element | element := self collectionMoreThan5Elements anyOne. aCol := self collectionClass with: element. self assert: (aCol includes: element).! ! !ArrayTest methodsFor: 'test - creation'! testWithAll "self debug: #testWithAll" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection . aCol := self collectionClass withAll: collection . collection do: [ :each | self assert: (aCol occurrencesOf: each ) = ( collection occurrencesOf: each ) ]. self assert: (aCol size = collection size ).! ! !ArrayTest methodsFor: 'test - creation'! testWithWith "self debug: #testWithWith" | aCol collection element1 element2 | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 2 . element1 := collection at: 1. element2 := collection at:2. aCol := self collectionClass with: element1 with: element2 . self assert: (aCol occurrencesOf: element1 ) == ( collection occurrencesOf: element1). self assert: (aCol occurrencesOf: element2 ) == ( collection occurrencesOf: element2). ! ! !ArrayTest methodsFor: 'test - creation'! testWithWithWith "self debug: #testWithWithWith" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom:1 to: 3 . aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3). 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ].! ! !ArrayTest methodsFor: 'test - creation'! testWithWithWithWith "self debug: #testWithWithWithWith" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 4. aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3) with: ( collection at: 4). 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ].! ! !ArrayTest methodsFor: 'test - creation'! testWithWithWithWithWith "self debug: #testWithWithWithWithWith" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 5 . aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3) with: (collection at: 4 ) with: ( collection at: 5 ). 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ].! ! !ArrayTest methodsFor: 'test - equality'! testEqualSign "self debug: #testEqualSign" self deny: (self empty = self nonEmpty).! ! !ArrayTest methodsFor: 'test - equality'! testEqualSignIsTrueForNonIdenticalButEqualCollections "self debug: #testEqualSignIsTrueForNonIdenticalButEqualCollections" self assert: (self empty = self empty copy). self assert: (self empty copy = self empty). self assert: (self empty copy = self empty copy). self assert: (self nonEmpty = self nonEmpty copy). self assert: (self nonEmpty copy = self nonEmpty). self assert: (self nonEmpty copy = self nonEmpty copy).! ! !ArrayTest methodsFor: 'test - equality'! testEqualSignOfIdenticalCollectionObjects "self debug: #testEqualSignOfIdenticalCollectionObjects" self assert: (self empty = self empty). self assert: (self nonEmpty = self nonEmpty). ! ! !ArrayTest methodsFor: 'test - iterate' stamp: 'luc.fabresse 11/29/2008 23:10'! expectedSizeAfterReject ^1! ! !ArrayTest methodsFor: 'test - iterate' stamp: 'stephane.ducasse 10/6/2008 17:39'! speciesClass ^ Array! ! !ArrayTest methodsFor: 'test - iterate' stamp: 'damienpollet 1/13/2009 16:28'! testAnySatisfy self assert: ( self collection anySatisfy: [:each | each = -2]). self deny: (self collection anySatisfy: [:each | each isString]).! ! !ArrayTest methodsFor: 'test - iterate' stamp: 'delaunay 4/14/2009 14:12'! testDo | res | res := OrderedCollection new. self collection do: [:each | res add: each class]. self assert: res asArray = self result.! ! !ArrayTest methodsFor: 'test - iterate' stamp: 'delaunay 4/14/2009 14:13'! testDo2 | res | res := OrderedCollection new. self collection do: [:each | res add: each class]. self assert: res asArray = self result. ! ! !ArrayTest methodsFor: 'testing' stamp: 'zz 12/5/2005 17:12'! testIsArray self assert: example1 isArray! ! !ArrayTest methodsFor: 'testing' stamp: 'apb 4/21/2006 08:59'! testIsLiteral "We work with a copy of literalArray, to avoid corrupting the code." | l | l := literalArray copy. self assert: l isLiteral. l at: 1 put: self class. self deny: l isLiteral! ! !ArrayTest methodsFor: 'testing' stamp: 'zz 12/5/2005 17:18'! testIsSelfEvaluating self assert: example1 isSelfEvaluating. example1 at: 1 put: Bag new. self deny: example1 isSelfEvaluating. example1 at: 1 put: 1.! ! !ArrayTest methodsFor: 'testing' stamp: 'zz 12/5/2005 17:50'! testLiteralEqual self deny: (example1 literalEqual: example1 asIntegerArray)! ! !ArrayTest methodsFor: 'testing' stamp: 'dc 5/24/2007 10:56'! testNewWithSize |array| array := Array new: 5. self assert: array size = 5. 1 to: 5 do: [:index | self assert: (array at: index) isNil]! ! !ArrayTest methodsFor: 'testing' stamp: 'stephane.ducasse 10/6/2008 16:53'! testPremultiply self assert: example1 +* #(2 ) = #(2 4 6 8 10 ) ! ! !ArrayTest methodsFor: 'testing' stamp: 'delaunay 5/4/2009 15:15'! testPrinting self assert: literalArray printString = '#(1 true 3 #four)'. self assert: (literalArray = (Compiler evaluate: literalArray printString)). "self assert: selfEvaluatingArray printString = '{1. true. (3/4). Color black. (2 to: 4). 5}'." self assert: (selfEvaluatingArray = (Compiler evaluate: selfEvaluatingArray printString)). self assert: nonSEArray1 printString = 'an Array(1 a Set(1))'. self assert: nonSEarray2 printString = '{#Array->Array}' ! ! !ArrayTest methodsFor: 'tests - accessing' stamp: 'delaunay 4/10/2009 16:19'! testAtWrap2 | tabTest | tabTest := #(5 6 8 ). self assert: (tabTest atWrap: 2) = 6. self assert: (tabTest atWrap: 7) = 5. self assert: (tabTest atWrap: 5) = 6. self assert: (tabTest atWrap: 0) = 8. self assert: (tabTest atWrap: 1) = 5. self assert: (tabTest atWrap: -2) = 5! ! !ArrayTest methodsFor: 'tests - as identity set'! testAsIdentitySetWithIdentityEqualsElements | result | result := self collectionWithIdentical asIdentitySet. " Only one element should have been removed as two elements are equals with Identity equality" self assert: result size = (self collectionWithIdentical size - 1). self collectionWithIdentical do: [ :each | (self collectionWithIdentical occurrencesOf: each) > 1 ifTrue: [ "the two elements equals only with classic equality shouldn't 'have been removed" self assert: (result asOrderedCollection occurrencesOf: each) = 1 " the other elements are still here" ] ifFalse: [ self assert: (result asOrderedCollection occurrencesOf: each) = 1 ] ]. self assert: result class = IdentitySet! ! !ArrayTest methodsFor: 'tests - as identity set'! testAsIdentitySetWithoutIdentityEqualsElements | result collection | collection := self collectionWithCopy. result := collection asIdentitySet. " no elements should have been removed as no elements are equels with Identity equality" self assert: result size = collection size. collection do: [ :each | (collection occurrencesOf: each) = (result asOrderedCollection occurrencesOf: each) ]. self assert: result class = IdentitySet! ! !ArrayTest methodsFor: 'tests - as set tests'! testAsIdentitySetWithEqualsElements | result collection | collection := self withEqualElements . result := collection asIdentitySet. collection do: [ :each | self assert: (result occurrencesOf: each) = 1 ]. self assert: result class = IdentitySet.! ! !ArrayTest methodsFor: 'tests - as set tests'! testAsSetWithEqualsElements | result | result := self withEqualElements asSet. self withEqualElements do: [ :each | self assert: (result occurrencesOf: each) = 1 ]. self assert: result class = Set! ! !ArrayTest methodsFor: 'tests - as sorted collection'! testAsSortedArray | result collection | collection := self collectionWithSortableElements . result := collection asSortedArray. self assert: (result class includesBehavior: Array). self assert: result isSorted. self assert: result size = collection size! ! !ArrayTest methodsFor: 'tests - as sorted collection'! testAsSortedCollection | aCollection result | aCollection := self collectionWithSortableElements . result := aCollection asSortedCollection. self assert: (result class includesBehavior: SortedCollection). result do: [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. self assert: result size = aCollection size.! ! !ArrayTest methodsFor: 'tests - as sorted collection'! testAsSortedCollectionWithSortBlock | result tmp | result := self collectionWithSortableElements asSortedCollection: [:a :b | a > b]. self assert: (result class includesBehavior: SortedCollection). result do: [ :each | self assert: (self collectionWithSortableElements occurrencesOf: each) = (result occurrencesOf: each) ]. self assert: result size = self collectionWithSortableElements size. tmp:=result at: 1. result do: [:each| self assert: tmp>=each. tmp:=each]. ! ! !ArrayTest methodsFor: 'tests - at put'! testAtPut "self debug: #testAtPut" self nonEmpty at: self anIndex put: self aValue. self assert: (self nonEmpty at: self anIndex) = self aValue. ! ! !ArrayTest methodsFor: 'tests - at put'! testAtPutOutOfBounds "self debug: #testAtPutOutOfBounds" self should: [self empty at: self anIndex put: self aValue] raise: Error ! ! !ArrayTest methodsFor: 'tests - at put'! testAtPutTwoValues "self debug: #testAtPutTwoValues" self nonEmpty at: self anIndex put: self aValue. self nonEmpty at: self anIndex put: self anotherValue. self assert: (self nonEmpty at: self anIndex) = self anotherValue.! ! !ArrayTest methodsFor: 'tests - begins ends with'! testsBeginsWith self assert: (self nonEmpty beginsWith:(self nonEmpty copyUpTo: self nonEmpty size)). self assert: (self nonEmpty beginsWith:(self nonEmpty )). self deny: (self nonEmpty beginsWith:(self nonEmpty copyWith:self nonEmpty first)).! ! !ArrayTest methodsFor: 'tests - begins ends with'! testsBeginsWithEmpty self deny: (self nonEmpty beginsWith:(self empty)). self deny: (self empty beginsWith:(self nonEmpty )). ! ! !ArrayTest methodsFor: 'tests - begins ends with'! testsEndsWith self assert: (self nonEmpty endsWith:(self nonEmpty copyWithoutFirst)). self assert: (self nonEmpty endsWith:(self nonEmpty )). self deny: (self nonEmpty endsWith:(self nonEmpty copyWith:self nonEmpty first)).! ! !ArrayTest methodsFor: 'tests - begins ends with'! testsEndsWithEmpty self deny: (self nonEmpty endsWith:(self empty )). self deny: (self empty endsWith:(self nonEmpty )). ! ! !ArrayTest methodsFor: 'tests - comma and delimiter'! testAsCommaStringEmpty self assert: self empty asCommaString = ''. self assert: self empty asCommaStringAnd = ''. ! ! !ArrayTest methodsFor: 'tests - comma and delimiter'! testAsCommaStringMore "self assert: self oneTwoThreeItemCol asCommaString = '1, 2, 3'. self assert: self oneTwoThreeItemCol asCommaStringAnd = '1, 2 and 3' " | result resultAnd index allElementsAsString | result:= self nonEmpty asCommaString . resultAnd:= self nonEmpty asCommaStringAnd . index := 1. (result findBetweenSubStrs: ',' )do: [:each | index = 1 ifTrue: [self assert: each= ((self nonEmpty at:index)asString)] ifFalse: [self assert: each= (' ',(self nonEmpty at:index) asString)]. index:=index+1 ]. "verifying esultAnd :" allElementsAsString:=(resultAnd findBetweenSubStrs: ',' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size ) ifTrue: [ i = 1 ifTrue:[self assert: (allElementsAsString at:i)=((self nonEmpty at:i) asString)] ifFalse:[self assert: (allElementsAsString at:i)=(' ',(self nonEmpty at:i) asString)] ]. i=(allElementsAsString size) ifTrue:[ i = 1 ifTrue:[self assert: (allElementsAsString at:i)=( (self nonEmpty at:i ) asString ,' and ', (self nonEmpty at: ( i + 1) ) asString )] ifFalse:[self assert: (allElementsAsString at:i)=( ' ' , (self nonEmpty at:i ) asString ,' and ', (self nonEmpty at: ( i + 1) ) asString )] ]. ].! ! !ArrayTest methodsFor: 'tests - comma and delimiter'! testAsCommaStringOne "self assert: self oneItemCol asCommaString = '1'. self assert: self oneItemCol asCommaStringAnd = '1'." self assert: self nonEmpty1Element asCommaString = (self nonEmpty1Element first asString). self assert: self nonEmpty1Element asCommaStringAnd = (self nonEmpty1Element first asString). ! ! !ArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterEmpty | delim emptyStream | delim := ', '. emptyStream := ReadWriteStream on: ''. self empty asStringOn: emptyStream delimiter: delim. self assert: emptyStream contents = ''. ! ! !ArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterLastEmpty | delim emptyStream | delim := ', '. emptyStream := ReadWriteStream on: ''. self empty asStringOn: emptyStream delimiter: delim last:'and'. self assert: emptyStream contents = ''. ! ! !ArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterLastMore | delim multiItemStream result last allElementsAsString | delim := ', '. last := 'and'. result:=''. multiItemStream := ReadWriteStream on:result. self nonEmpty asStringOn: multiItemStream delimiter: ', ' last: last. allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString)]. i=(allElementsAsString size-1) ifTrue:[ self deny: (allElementsAsString at:i)=(last)asString]. i=(allElementsAsString size) ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:(i-1))asString)]. ]. ! ! !ArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterLastOne | delim oneItemStream result | delim := ', '. result:=''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim last: 'and'. oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)]. ! ! !ArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterMore | delim multiItemStream result index | "delim := ', '. multiItemStream := '' readWrite. self oneTwoThreeItemCol asStringOn: multiItemStream delimiter: ', '. self assert: multiItemStream contents = '1, 2, 3'." delim := ', '. result:=''. multiItemStream := ReadWriteStream on:result. self nonEmpty asStringOn: multiItemStream delimiter: ', '. index:=1. (result findBetweenSubStrs: ', ' )do: [:each | self assert: each= ((self nonEmpty at:index)asString). index:=index+1 ].! ! !ArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterOne | delim oneItemStream result | "delim := ', '. oneItemStream := '' readWrite. self oneItemCol asStringOn: oneItemStream delimiter: delim. self assert: oneItemStream contents = '1'." delim := ', '. result:=''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim. oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)]. ! ! !ArrayTest methodsFor: 'tests - concatenation'! testConcatenation | result index | result:= self firstCollection,self secondCollection . "first part : " index := 1. self firstCollection do: [:each | self assert: (self firstCollection at: index)=each. index := index+1.]. "second part : " 1 to: self secondCollection size do: [:i | self assert: (self secondCollection at:i)= (result at:index). index:=index+1]. "size : " self assert: result size = (self firstCollection size + self secondCollection size).! ! !ArrayTest methodsFor: 'tests - concatenation'! testConcatenationWithEmpty | result | result:= self empty,self secondCollection . 1 to: self secondCollection size do: [:i | self assert: (self secondCollection at:i)= (result at:i). ]. "size : " self assert: result size = ( self secondCollection size).! ! !ArrayTest methodsFor: 'tests - converting'! assertNoDuplicates: aCollection whenConvertedTo: aClass | result | result := self collectionWithEqualElements asIdentitySet. self assert: (result class includesBehavior: IdentitySet). self collectionWithEqualElements do: [ :initial | self assert: (result occurrencesOf: initial) = 1 ]! ! !ArrayTest methodsFor: 'tests - converting'! assertNonDuplicatedContents: aCollection whenConvertedTo: aClass | result | result := aCollection perform: ('as' , aClass name) asSymbol. self assert: (result class includesBehavior: aClass). result do: [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. ^ result! ! !ArrayTest methodsFor: 'tests - converting' stamp: 'cyrille.delaunay 3/26/2009 12:35'! assertSameContents: aCollection whenConvertedTo: aClass | result | result := aCollection perform: ('as' , aClass name) asSymbol. self assert: (result class includesBehavior: aClass). result do: [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. self assert: result size = aCollection size! ! !ArrayTest methodsFor: 'tests - converting' stamp: 'cyrille.delaunay 3/26/2009 14:55'! testAsArray "self debug: #testAsArray3" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Array! ! !ArrayTest methodsFor: 'tests - converting'! testAsBag self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Bag! ! !ArrayTest methodsFor: 'tests - converting'! testAsByteArray | res | self shouldnt: [self integerCollectionWithoutEqualElements ] raise: Error. self integerCollectionWithoutEqualElements do: [ :each | self assert: each class = SmallInteger] . res := true. self integerCollectionWithoutEqualElements detect: [ :each | (self integerCollectionWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false. self assertSameContents: self integerCollectionWithoutEqualElements whenConvertedTo: ByteArray! ! !ArrayTest methodsFor: 'tests - converting'! testAsIdentitySet "test with a collection without equal elements :" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: IdentitySet. ! ! !ArrayTest methodsFor: 'tests - converting'! testAsOrderedCollection self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: OrderedCollection! ! !ArrayTest methodsFor: 'tests - converting'! testAsSet | | "test with a collection without equal elements :" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Set. ! ! !ArrayTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:26'! testCopyEmptyWith "self debug: #testCopyWith" | res | res := self empty copyWith: self elementToAdd. self assert: res size = (self empty size + 1). self assert: (res includes: self elementToAdd)! ! !ArrayTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:26'! testCopyEmptyWithout "self debug: #testCopyEmptyWithout" | res | res := self empty copyWithout: self elementToAdd. self assert: res size = self empty size. self deny: (res includes: self elementToAdd)! ! !ArrayTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:24'! testCopyEmptyWithoutAll "self debug: #testCopyEmptyWithoutAll" | res | res := self empty copyWithoutAll: self collectionWithElementsToRemove. self assert: res size = self empty size. self collectionWithElementsToRemove do: [ :each | self deny: (res includes: each) ]! ! !ArrayTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:26'! testCopyNonEmptyWith "self debug: #testCopyNonEmptyWith" | res | res := self nonEmpty copyWith: self elementToAdd. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self assert: (res includes: self elementToAdd). self nonEmpty do: [ :each | res includes: each ]! ! !ArrayTest methodsFor: 'tests - copy'! testCopyNonEmptyWithout "self debug: #testCopyNonEmptyWithout" | res anElementOfTheCollection | anElementOfTheCollection := self nonEmpty anyOne. res := (self nonEmpty copyWithout: anElementOfTheCollection). "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self deny: (res includes: anElementOfTheCollection). self nonEmpty do: [:each | (each = anElementOfTheCollection) ifFalse: [self assert: (res includes: each)]]. ! ! !ArrayTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:24'! testCopyNonEmptyWithoutAll "self debug: #testCopyNonEmptyWithoutAll" | res | res := self nonEmpty copyWithoutAll: self collectionWithElementsToRemove. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self collectionWithElementsToRemove do: [ :each | self deny: (res includes: each) ]. self nonEmpty do: [ :each | (self collectionWithElementsToRemove includes: each) ifFalse: [ self assert: (res includes: each) ] ]! ! !ArrayTest methodsFor: 'tests - copy' stamp: 'delaunay 3/30/2009 10:33'! testCopyNonEmptyWithoutAllNotIncluded ! ! !ArrayTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:26'! testCopyNonEmptyWithoutNotIncluded "self debug: #testCopyNonEmptyWithoutNotIncluded" | res | res := self nonEmpty copyWithout: self elementToAdd. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self nonEmpty do: [ :each | self assert: (res includes: each) ]! ! !ArrayTest methodsFor: 'tests - copy - clone'! testCopyCreatesNewObject "self debug: #testCopyCreatesNewObject" | copy | copy := self nonEmpty copy. self deny: self nonEmpty == copy. ! ! !ArrayTest methodsFor: 'tests - copy - clone'! testCopyEmpty "self debug: #testCopyEmpty" | copy | copy := self empty copy. self assert: copy isEmpty.! ! !ArrayTest methodsFor: 'tests - copy - clone'! testCopyNonEmpty "self debug: #testCopyNonEmpty" | copy | copy := self nonEmpty copy. self deny: copy isEmpty. self assert: copy size = self nonEmpty size. self nonEmpty do: [:each | copy includes: each]! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyAfter | result index collection | collection := self collectionWithoutEqualsElements . index:= self indexInForCollectionWithoutDuplicates . result := collection copyAfter: (collection at:index ). "verifying content: " (1) to: result size do: [:i | self assert: (collection at:(i + index ))=(result at: (i))]. "verify size: " self assert: result size = (collection size - index).! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyAfterEmpty | result | result := self empty copyAfter: self collectionWithoutEqualsElements first. self assert: result isEmpty. ! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyAfterLast | result index collection | collection := self collectionWithoutEqualsElements . index:= self indexInForCollectionWithoutDuplicates . result := collection copyAfterLast: (collection at:index ). "verifying content: " (1) to: result size do: [:i | self assert: (collection at:(i + index ))=(result at: (i))]. "verify size: " self assert: result size = (collection size - index).! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyAfterLastEmpty | result | result := self empty copyAfterLast: self collectionWithoutEqualsElements first. self assert: result isEmpty.! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyEmptyMethod | result | result := self collectionWithoutEqualsElements copyEmpty . self assert: result isEmpty . self assert: result class= self nonEmpty class.! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyFromTo | result index collection | collection := self collectionWithoutEqualsElements . index :=self indexInForCollectionWithoutDuplicates . result := collection copyFrom: index to: collection size . "verify content of 'result' : " 1 to: result size do: [:i | self assert: (result at:i)=(collection at: (i + index - 1))]. "verify size of 'result' : " self assert: result size = (collection size - index + 1).! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyUpTo | result index collection | collection := self collectionWithoutEqualsElements . index:= self indexInForCollectionWithoutDuplicates . result := collection copyUpTo: (collection at:index). "verify content of 'result' :" 1 to: result size do: [:i| self assert: (collection at:i)=(result at:i)]. "verify size of 'result' :" self assert: result size = (index-1). ! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyUpToEmpty | result | result := self empty copyUpTo: self collectionWithoutEqualsElements first. self assert: result isEmpty. ! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyUpToLast | result index collection | collection := self collectionWithoutEqualsElements . index:= self indexInForCollectionWithoutDuplicates . result := collection copyUpToLast: (collection at:index). "verify content of 'result' :" 1 to: result size do: [:i| self assert: (collection at:i)=(result at:i)]. "verify size of 'result' :" self assert: result size = (index-1).! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyUpToLastEmpty | result | result := self empty copyUpToLast: self collectionWithoutEqualsElements first. self assert: result isEmpty.! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable for multipliness'! testCopyAfterLastWithDuplicate | result element collection | collection := self collectionWithSameAtEndAndBegining . element := collection first. " collectionWithSameAtEndAndBegining first and last elements are equals. 'copyAfter:' should copy after the last occurence of element :" result := collection copyAfterLast: (element ). "verifying content: " self assert: result isEmpty. ! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable for multipliness'! testCopyAfterWithDuplicate | result element collection | collection := self collectionWithSameAtEndAndBegining . element := collection last. " collectionWithSameAtEndAndBegining first and last elements are equals. 'copyAfter:' should copy after the first occurence :" result := collection copyAfter: (element ). "verifying content: " 1 to: result size do: [:i | self assert: (collection at:(i + 1 )) = (result at: (i)) ]. "verify size: " self assert: result size = (collection size - 1).! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable for multipliness'! testCopyUpToLastWithDuplicate | result element collection | collection := self collectionWithSameAtEndAndBegining . element := collection first. " collectionWithSameAtEndAndBegining first and last elements are equals. 'copyUpToLast:' should copy until the last occurence :" result := collection copyUpToLast: (element ). "verifying content: " 1 to: result size do: [:i | self assert: (result at: i ) = ( collection at: i ) ]. self assert: result size = (collection size - 1). ! ! !ArrayTest methodsFor: 'tests - copying part of sequenceable for multipliness'! testCopyUpToWithDuplicate | result element collection | collection := self collectionWithSameAtEndAndBegining . element := collection last. " collectionWithSameAtEndAndBegining first and last elements are equals. 'copyUpTo:' should copy until the first occurence :" result := collection copyUpTo: (element ). "verifying content: " self assert: result isEmpty. ! ! !ArrayTest methodsFor: 'tests - copying same contents'! testReverse | result | result := self nonEmpty reverse . "verify content of 'result: '" 1 to: result size do: [:i | self assert: ((result at:i)=(self nonEmpty at:(self nonEmpty size-i+1)))]. "verify size of 'result' :" self assert: result size=self nonEmpty size.! ! !ArrayTest methodsFor: 'tests - copying same contents'! testReversed | result | result := self nonEmpty reversed . "verify content of 'result: '" 1 to: result size do: [:i | self assert: ((result at:i)=(self nonEmpty at:(self nonEmpty size-i+1)))]. "verify size of 'result' :" self assert: result size=self nonEmpty size.! ! !ArrayTest methodsFor: 'tests - copying same contents'! testShallowCopy | result | result := self nonEmpty shallowCopy . "verify content of 'result: '" 1 to: self nonEmpty size do: [:i | self assert: ((result at:i)=(self nonEmpty at:i))]. "verify size of 'result' :" self assert: result size=self nonEmpty size.! ! !ArrayTest methodsFor: 'tests - copying same contents'! testShallowCopyEmpty | result | result := self empty shallowCopy . self assert: result isEmpty .! ! !ArrayTest methodsFor: 'tests - copying same contents'! testShuffled | result | result := self nonEmpty shuffled . "verify content of 'result: '" result do: [:each | self assert: (self nonEmpty occurrencesOf: each)=(result occurrencesOf: each)]. "verify size of 'result' :" self assert: result size=self nonEmpty size.! ! !ArrayTest methodsFor: 'tests - copying same contents'! testSortBy " can only be used if the collection tested can include sortable elements :" | result tmp | self shouldnt: [ self collectionWithSortableElements ] raise: Error. self shouldnt: [self collectionWithSortableElements anyOne < self collectionWithSortableElements anyOne] raise: Error. result := self collectionWithSortableElements sortBy: [ :a :b | a < b ]. "verify content of 'result' : " result do: [ :each | (self collectionWithSortableElements occurrencesOf: each) = (result occurrencesOf: each) ]. tmp := result first. result do: [ :each | self assert: each >= tmp. tmp := each ]. "verify size of 'result' :" self assert: result size = self collectionWithSortableElements size! ! !ArrayTest methodsFor: 'tests - copying with or without'! testCopyWithFirst | index element result | index:= self indexInNonEmpty . element:= self nonEmpty at: index. result := self nonEmpty copyWithFirst: element. self assert: result size = (self nonEmpty size + 1). self assert: result first = element . 2 to: result size do: [ :i | self assert: (result at: i) = ( self nonEmpty at: ( i - 1 ))].! ! !ArrayTest methodsFor: 'tests - copying with or without'! testCopyWithSequenceable | result index element | index := self indexInNonEmpty . element := self nonEmpty at: index. result := self nonEmpty copyWith: (element ). self assert: result size = (self nonEmpty size + 1). self assert: result last = element . 1 to: (result size - 1) do: [ :i | self assert: (result at: i) = ( self nonEmpty at: ( i ))].! ! !ArrayTest methodsFor: 'tests - copying with or without'! testCopyWithoutFirst | result | result := self nonEmpty copyWithoutFirst. self assert: result size = (self nonEmpty size - 1). 1 to: result size do: [:i | self assert: (result at: i)= (self nonEmpty at: (i + 1))].! ! !ArrayTest methodsFor: 'tests - copying with or without'! testCopyWithoutIndex | result index | index := self indexInNonEmpty . result := self nonEmpty copyWithoutIndex: index . "verify content of 'result:'" 1 to: result size do: [:i | i<( index ) ifTrue: [self assert: ((result at:i )= (self nonEmpty at:i))]. i>=( index ) ifTrue: [self assert: (result at:i )= (self nonEmpty at:(i+1))]]. "verify size of result : " self assert: result size=(self nonEmpty size -1).! ! !ArrayTest methodsFor: 'tests - copying with or without'! testForceToPaddingStartWith | result element | element := self nonEmpty at: self indexInNonEmpty . result := self nonEmpty forceTo: (self nonEmpty size+2) paddingStartWith: ( element ). "verify content of 'result' : " 1 to: 2 do: [:i | self assert: ( element ) = ( result at:(i) ) ]. 3 to: result size do: [:i | self assert: ( result at:i ) = ( self nonEmpty at:(i-2) ) ]. "verify size of 'result' :" self assert: result size = (self nonEmpty size + 2).! ! !ArrayTest methodsFor: 'tests - copying with or without'! testForceToPaddingWith | result element | element := self nonEmpty at: self indexInNonEmpty . result := self nonEmpty forceTo: (self nonEmpty size+2) paddingWith: ( element ). "verify content of 'result' : " 1 to: self nonEmpty size do: [:i | self assert: ( self nonEmpty at: i ) = ( result at:(i) ). ]. (result size - 1) to: result size do: [:i | self assert: ( result at:i ) = ( element ) ]. "verify size of 'result' :" self assert: result size = (self nonEmpty size + 2).! ! !ArrayTest methodsFor: 'tests - copying with replacement'! firstIndexesOf: subCollection in: collection " return an OrderedCollection with the first indexes of the occurrences of subCollection in collection " | tmp result currentIndex | tmp:= collection. result:= OrderedCollection new. currentIndex := 1. [tmp isEmpty ]whileFalse: [ (tmp beginsWith: subCollection) ifTrue: [ result add: currentIndex. 1 to: subCollection size do: [:i | tmp := tmp copyWithoutFirst. currentIndex := currentIndex + 1] ] ifFalse: [ tmp := tmp copyWithoutFirst. currentIndex := currentIndex +1. ] ]. ^ result. ! ! !ArrayTest methodsFor: 'tests - copying with replacement'! testCopyReplaceAllWith1Occurence | result firstIndexesOfOccurrence index endPartIndexResult endPartIndexCollection | result := self collectionWith1TimeSubcollection copyReplaceAll: self oldSubCollection with: self replacementCollection . "detecting indexes of olSubCollection" firstIndexesOfOccurrence := self firstIndexesOf: self oldSubCollection in: self collectionWith1TimeSubcollection . index:= firstIndexesOfOccurrence at: 1. "verify content of 'result' : " "first part of 'result'' : '" 1 to: (index -1) do: [ :i | self assert: (self collectionWith1TimeSubcollection at:i)=(result at: i) ]. " middle part containing replacementCollection : " index to: (index + self replacementCollection size-1) do: [ :i | self assert: ( result at: i )=(self replacementCollection at: ( i - index + 1 )) ]. " end part :" endPartIndexResult := index + self replacementCollection size . endPartIndexCollection := index + self oldSubCollection size . 1 to: (result size - endPartIndexResult - 1 ) do: [ :i | self assert: (result at: ( endPartIndexResult + i - 1 ) ) = (self collectionWith1TimeSubcollection at: ( endPartIndexCollection + i - 1 ) ). ]. ! ! !ArrayTest methodsFor: 'tests - copying with replacement'! testCopyReplaceAllWithManyOccurence | result firstIndexesOfOccurrence resultBetweenPartIndex collectionBetweenPartIndex diff | " testing fixture here as this method may be not used for collection that can't contain equals element :" self shouldnt: [self collectionWith2TimeSubcollection ]raise: Error. self assert: (self howMany: self oldSubCollection in: self collectionWith2TimeSubcollection ) = 2. " test :" diff := self replacementCollection size - self oldSubCollection size. result := self collectionWith2TimeSubcollection copyReplaceAll: self oldSubCollection with: self replacementCollection . "detecting indexes of olSubCollection" firstIndexesOfOccurrence := self firstIndexesOf: self oldSubCollection in: self collectionWith2TimeSubcollection . " verifying that replacementCollection has been put in places of oldSubCollections " firstIndexesOfOccurrence do: [ :each | (firstIndexesOfOccurrence indexOf: each) = 1 ifTrue: [ each to: self replacementCollection size do: [ :i | self assert: (result at: i) = ( self replacementCollection at: ( i - each + 1 ) ) ]. ] ifFalse:[ (each + diff) to: self replacementCollection size do: [ :i | self assert: (result at: i) = ( self replacementCollection at: ( i - each + 1 ) ) ]. ]. ]. " verifying that the 'between' parts correspond to the initial collection : " 1 to: firstIndexesOfOccurrence size do: [ :i | i = 1 " specific comportement for the begining of the collection :" ifTrue: [ 1 to: ((firstIndexesOfOccurrence at: i) - 1 ) do: [ :j | self assert: (result at: i) = (self collectionWith2TimeSubcollection at: i) ] ] " between parts till the end : " ifFalse: [ resultBetweenPartIndex := (firstIndexesOfOccurrence at: (i -1)) + self replacementCollection size. collectionBetweenPartIndex := (firstIndexesOfOccurrence at: (i -1)) + self oldSubCollection size. 1 to: ( firstIndexesOfOccurrence at: i) - collectionBetweenPartIndex - 1 do: [ :j | self assert: (result at: (resultBetweenPartIndex + i - 1)) = (self collectionWith2TimeSubcollection at: (collectionBetweenPartIndex +i - 1)) ] ] ]. "final part :" 1 to: (self collectionWith2TimeSubcollection size - (firstIndexesOfOccurrence last + self oldSubCollection size ) ) do: [ :i | self assert: ( result at:(firstIndexesOfOccurrence last + self replacementCollection size -1) + i ) = ( self collectionWith2TimeSubcollection at:(firstIndexesOfOccurrence last + self oldSubCollection size -1) + i ) . ]! ! !ArrayTest methodsFor: 'tests - copying with replacement'! testCopyReplaceFromToWith | result indexOfSubcollection lastIndexOfOldSubcollection lastIndexOfReplacementCollection | indexOfSubcollection := (self firstIndexesOf: self oldSubCollection in: self collectionWith1TimeSubcollection) at: 1. lastIndexOfOldSubcollection := indexOfSubcollection + self oldSubCollection size -1. lastIndexOfReplacementCollection := indexOfSubcollection + self replacementCollection size -1. result := self collectionWith1TimeSubcollection copyReplaceFrom: indexOfSubcollection to: lastIndexOfOldSubcollection with: self replacementCollection . "verify content of 'result' : " "first part of 'result' " 1 to: (indexOfSubcollection - 1) do: [ :i | self assert: (self collectionWith1TimeSubcollection at:i) = (result at: i) ]. " middle part containing replacementCollection : " (indexOfSubcollection ) to: ( lastIndexOfReplacementCollection ) do: [ :i | self assert: (result at: i)=(self replacementCollection at: (i - indexOfSubcollection +1)) ]. " end part :" 1 to: (result size - lastIndexOfReplacementCollection ) do: [ :i | self assert: (result at: ( lastIndexOfReplacementCollection + i ) ) = (self collectionWith1TimeSubcollection at: ( lastIndexOfOldSubcollection + i ) ). ]. ! ! !ArrayTest methodsFor: 'tests - copying with replacement'! testCopyReplaceFromToWithInsertion | result indexOfSubcollection | indexOfSubcollection := (self firstIndexesOf: self oldSubCollection in: self collectionWith1TimeSubcollection) at: 1. result := self collectionWith1TimeSubcollection copyReplaceFrom: indexOfSubcollection to: ( indexOfSubcollection - 1 ) with: self replacementCollection . "verify content of 'result' : " "first part of 'result'' : '" 1 to: (indexOfSubcollection -1) do: [ :i | self assert: (self collectionWith1TimeSubcollection at:i)=(result at: i) ]. " middle part containing replacementCollection : " indexOfSubcollection to: (indexOfSubcollection + self replacementCollection size-1) do: [ :i | self assert: ( result at: i )=(self replacementCollection at: ( i - indexOfSubcollection +1 )) ]. " end part :" (indexOfSubcollection + self replacementCollection size) to: (result size) do: [:i| self assert: (result at: i)=(self collectionWith1TimeSubcollection at: (i-self replacementCollection size))]. " verify size: " self assert: result size=(self collectionWith1TimeSubcollection size + self replacementCollection size). ! ! !ArrayTest methodsFor: 'tests - element accessing'! testAfter "self debug: #testAfter" self assert: (self moreThan4Elements after: (self moreThan4Elements at: 1)) = (self moreThan4Elements at: 2). self should: [ self moreThan4Elements after: (self moreThan4Elements at: self moreThan4Elements size) ] raise: Error. self should: [ self moreThan4Elements after: self elementNotInForElementAccessing ] raise: Error! ! !ArrayTest methodsFor: 'tests - element accessing'! testAfterIfAbsent "self debug: #testAfterIfAbsent" self assert: (self moreThan4Elements after: (self moreThan4Elements at: 1) ifAbsent: [ 33 ]) = (self moreThan4Elements at: 2). self assert: (self moreThan4Elements after: (self moreThan4Elements at: self moreThan4Elements size) ifAbsent: [ 33 ]) == 33. self assert: (self moreThan4Elements after: self elementNotInForElementAccessing ifAbsent: [ 33 ]) = 33! ! !ArrayTest methodsFor: 'tests - element accessing'! testAt "self debug: #testAt" " self assert: (self accessCollection at: 1) = 1. self assert: (self accessCollection at: 2) = 2. " | index | index := self moreThan4Elements indexOf: self elementInForElementAccessing. self assert: (self moreThan4Elements at: index) = self elementInForElementAccessing! ! !ArrayTest methodsFor: 'tests - element accessing'! testAtAll "self debug: #testAtAll" " self flag: #theCollectionshouldbe102030intheFixture. self assert: (self accessCollection atAll: #(2 1)) first = self accessCollection second. self assert: (self accessCollection atAll: #(2)) first = self accessCollection second." | result | result := self moreThan4Elements atAll: #(2 1 2 ). self assert: (result at: 1) = (self moreThan4Elements at: 2). self assert: (result at: 2) = (self moreThan4Elements at: 1). self assert: (result at: 3) = (self moreThan4Elements at: 2). self assert: (self moreThan4Elements atAll: #()) = self moreThan4Elements species new! ! !ArrayTest methodsFor: 'tests - element accessing'! testAtIfAbsent "self debug: #testAt" | absent | absent := false. self moreThan4Elements at: self moreThan4Elements size + 1 ifAbsent: [ absent := true ]. self assert: absent = true. absent := false. self moreThan4Elements at: self moreThan4Elements size ifAbsent: [ absent := true ]. self assert: absent = false! ! !ArrayTest methodsFor: 'tests - element accessing'! testAtLast "self debug: #testAtLast" | index | self assert: (self moreThan4Elements atLast: 1) = self moreThan4Elements last. "tmp:=1. self do: [:each | each =self elementInForIndexAccessing ifTrue:[index:=tmp]. tmp:=tmp+1]." index := self moreThan4Elements indexOf: self elementInForElementAccessing. self assert: (self moreThan4Elements atLast: index) = (self moreThan4Elements at: self moreThan4Elements size - index + 1)! ! !ArrayTest methodsFor: 'tests - element accessing'! testAtLastError "self debug: #testAtLast" self should: [ self moreThan4Elements atLast: self moreThan4Elements size + 1 ] raise: Error! ! !ArrayTest methodsFor: 'tests - element accessing'! testAtLastIfAbsent "self debug: #testAtLastIfAbsent" self assert: (self moreThan4Elements atLast: 1 ifAbsent: [ nil ]) = self moreThan4Elements last. self assert: (self moreThan4Elements atLast: self moreThan4Elements size + 1 ifAbsent: [ 222 ]) = 222! ! !ArrayTest methodsFor: 'tests - element accessing'! testAtOutOfBounds "self debug: #testAtOutOfBounds" self should: [ self moreThan4Elements at: self moreThan4Elements size + 1 ] raise: Error. self should: [ self moreThan4Elements at: -1 ] raise: Error! ! !ArrayTest methodsFor: 'tests - element accessing'! testAtPin "self debug: #testAtPin" self assert: (self moreThan4Elements atPin: 2) = self moreThan4Elements second. self assert: (self moreThan4Elements atPin: 99) = self moreThan4Elements last. self assert: (self moreThan4Elements atPin: -99) = self moreThan4Elements first! ! !ArrayTest methodsFor: 'tests - element accessing'! testAtRandom | result | result := self nonEmpty atRandom . self assert: (self nonEmpty includes: result).! ! !ArrayTest methodsFor: 'tests - element accessing'! testAtWrap "self debug: #testAt" " self assert: (self accessCollection at: 1) = 1. self assert: (self accessCollection at: 2) = 2. " | index | index := self moreThan4Elements indexOf: self elementInForElementAccessing. self assert: (self moreThan4Elements atWrap: index) = self elementInForElementAccessing. self assert: (self moreThan4Elements atWrap: index + self moreThan4Elements size) = self elementInForElementAccessing. self assert: (self moreThan4Elements atWrap: index - self moreThan4Elements size) = self elementInForElementAccessing. self assert: (self moreThan4Elements atWrap: 1 + self moreThan4Elements size) = (self moreThan4Elements at: 1)! ! !ArrayTest methodsFor: 'tests - element accessing'! testBefore "self debug: #testBefore" self assert: (self moreThan4Elements before: (self moreThan4Elements at: 2)) = (self moreThan4Elements at: 1). self should: [ self moreThan4Elements before: (self moreThan4Elements at: 1) ] raise: Error. self should: [ self moreThan4Elements before: 66 ] raise: Error! ! !ArrayTest methodsFor: 'tests - element accessing'! testBeforeIfAbsent "self debug: #testBefore" self assert: (self moreThan4Elements before: (self moreThan4Elements at: 1) ifAbsent: [ 99 ]) = 99. self assert: (self moreThan4Elements before: (self moreThan4Elements at: 2) ifAbsent: [ 99 ]) = (self moreThan4Elements at: 1)! ! !ArrayTest methodsFor: 'tests - element accessing'! testFirstSecondThird "self debug: #testFirstSecondThird" self assert: self moreThan4Elements first = (self moreThan4Elements at: 1). self assert: self moreThan4Elements second = (self moreThan4Elements at: 2). self assert: self moreThan4Elements third = (self moreThan4Elements at: 3). self assert: self moreThan4Elements fourth = (self moreThan4Elements at: 4)! ! !ArrayTest methodsFor: 'tests - element accessing'! testLast "self debug: #testLast" self assert: self moreThan4Elements last = (self moreThan4Elements at: self moreThan4Elements size)! ! !ArrayTest methodsFor: 'tests - element accessing'! testMiddle "self debug: #testMiddle" self assert: self moreThan4Elements middle = (self moreThan4Elements at: self moreThan4Elements size // 2 + 1)! ! !ArrayTest methodsFor: 'tests - equality'! testEqualSignForSequenceableCollections "self debug: #testEqualSign" self deny: (self nonEmpty = self nonEmpty asSet). self deny: (self nonEmpty reversed = self nonEmpty). self deny: (self nonEmpty = self nonEmpty reversed).! ! !ArrayTest methodsFor: 'tests - equality'! testHasEqualElements "self debug: #testHasEqualElements" self deny: (self empty hasEqualElements: self nonEmpty). self deny: (self nonEmpty hasEqualElements: self nonEmpty asSet). self deny: (self nonEmpty reversed hasEqualElements: self nonEmpty). self deny: (self nonEmpty hasEqualElements: self nonEmpty reversed).! ! !ArrayTest methodsFor: 'tests - equality'! testHasEqualElementsIsTrueForNonIdenticalButEqualCollections "self debug: #testHasEqualElementsIsTrueForNonIdenticalButEqualCollections" self assert: (self empty hasEqualElements: self empty copy). self assert: (self empty copy hasEqualElements: self empty). self assert: (self empty copy hasEqualElements: self empty copy). self assert: (self nonEmpty hasEqualElements: self nonEmpty copy). self assert: (self nonEmpty copy hasEqualElements: self nonEmpty). self assert: (self nonEmpty copy hasEqualElements: self nonEmpty copy).! ! !ArrayTest methodsFor: 'tests - equality'! testHasEqualElementsOfIdenticalCollectionObjects "self debug: #testHasEqualElementsOfIdenticalCollectionObjects" self assert: (self empty hasEqualElements: self empty). self assert: (self nonEmpty hasEqualElements: self nonEmpty). ! ! !ArrayTest methodsFor: 'tests - fixture'! howMany: subCollection in: collection " return an integer representing how many time 'subCollection' appears in 'collection' " | tmp nTime | tmp:= collection. nTime:= 0. [tmp isEmpty ]whileFalse: [ (tmp beginsWith: subCollection) ifTrue: [ nTime := nTime + 1. 1 to: subCollection size do: [:i | tmp := tmp copyWithoutFirst.] ] ifFalse: [tmp := tmp copyWithoutFirst.] ]. ^ nTime. ! ! !ArrayTest methodsFor: 'tests - fixture' stamp: 'delaunay 4/17/2009 15:26'! test0CopyTest self shouldnt: self empty raise: Error. self assert: self empty size = 0. self shouldnt: self nonEmpty raise: Error. self assert: (self nonEmpty size = 0) not. self shouldnt: self collectionWithElementsToRemove raise: Error. self assert: (self collectionWithElementsToRemove size = 0) not. self shouldnt: self elementToAdd raise: Error! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureAsSetForIdentityMultiplinessTest "a collection (of elements for which copy is not identical ) without equal elements:" | element res | self shouldnt: [ self elementsCopyNonIdenticalWithoutEqualElements ]raise: Error. element := self elementsCopyNonIdenticalWithoutEqualElements anyOne. self deny: element copy == element . res := true. self elementsCopyNonIdenticalWithoutEqualElements detect: [ :each | (self elementsCopyNonIdenticalWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false ! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureAsStringCommaAndDelimiterTest self shouldnt: [self nonEmpty] raise:Error . self deny: self nonEmpty isEmpty. self shouldnt: [self empty] raise:Error . self assert: self empty isEmpty. self shouldnt: [self nonEmpty1Element ] raise:Error . self assert: self nonEmpty1Element size=1.! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureBeginsEndsWithTest self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self assert: self nonEmpty size>1. self shouldnt: [self empty ] raise: Error. self assert: self empty isEmpty.! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureCloneTest self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty. ! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureConverAsSortedTest self shouldnt: [self collectionWithSortableElements ] raise: Error. self deny: self collectionWithSortableElements isEmpty .! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureCopyPartOfForMultipliness self shouldnt: [self collectionWithSameAtEndAndBegining ] raise: Error. self assert: self collectionWithSameAtEndAndBegining first = self collectionWithSameAtEndAndBegining last. self assert: self collectionWithSameAtEndAndBegining size > 1. 1 to: self collectionWithSameAtEndAndBegining size do: [:i | (i > 1 ) & (i < self collectionWithSameAtEndAndBegining size) ifTrue: [ self deny: (self collectionWithSameAtEndAndBegining at:i) = (self collectionWithSameAtEndAndBegining first)]. ]! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureCopyPartOfSequenceableTest self shouldnt: [self collectionWithoutEqualsElements ] raise: Error. self collectionWithoutEqualsElements do: [:each | self assert: (self collectionWithoutEqualsElements occurrencesOf: each)=1]. self shouldnt: [self indexInForCollectionWithoutDuplicates ] raise: Error. self assert: self indexInForCollectionWithoutDuplicates >0 & self indexInForCollectionWithoutDuplicates < self collectionWithoutEqualsElements size. self shouldnt: [self empty] raise: Error. self assert: self empty isEmpty .! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureCopySameContentsTest self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [self empty ] raise: Error. self assert: self empty isEmpty. ! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureCopyWithOrWithoutSpecificElementsTest self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty . self shouldnt: [self indexInNonEmpty ] raise: Error. self assert: self indexInNonEmpty > 0. self assert: self indexInNonEmpty <= self nonEmpty size.! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureCopyWithReplacementTest self shouldnt: [self replacementCollection ]raise: Error. self shouldnt: [self oldSubCollection] raise: Error. self shouldnt: [self collectionWith1TimeSubcollection ]raise: Error. self assert: (self howMany: self oldSubCollection in: self collectionWith1TimeSubcollection ) = 1. ! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureCreationWithTest self shouldnt: [ self collectionMoreThan5Elements ] raise: Error. self assert: self collectionMoreThan5Elements size >= 5.! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureEmptySequenceableTest self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty . self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty.! ! !ArrayTest methodsFor: 'tests - fixture' stamp: 'delaunay 4/15/2009 14:37'! test0FixtureIncludeTest | elementIn | self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self elementNotIn ] raise: Error. elementIn := true. self nonEmpty detect: [ :each | each = self elementNotIn ] ifNone: [ elementIn := false ]. self assert: elementIn = false. self shouldnt: [ self anotherElementNotIn ] raise: Error. elementIn := true. self nonEmpty detect: [ :each | each = self anotherElementNotIn ] ifNone: [ elementIn := false ]. self assert: elementIn = false. self shouldnt: [ self collection ] raise: Error. "self shouldnt: [self collectionInForIncluding ] raise: Error." "collectionIn:=false. index:=1. 1 to: self nonEmpty size do: [:i| collectionIn = false ifTrue:[(self nonEmpty at:i)=(self collectionInForIncluding at:index) ifTrue:[ index=self collectionInForIncluding ifTrue:[collectionIn := true]. index:=index+1.] ifFalse:[index:=1]. ] ]. self assert: collectionIn=true." self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty. self shouldnt: [ self collectionOfFloat ] raise: Error. self collectionOfFloat do: [ :each | self assert: each class = Float ]. self shouldnt: [ self elementInForIncludesTest ] raise: Error. elementIn := true. self nonEmpty detect: [ :each | each = self elementInForIncludesTest ] ifNone: [ elementIn := false ]. self assert: elementIn = true! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureIncludeWithIdentityTest | element | self shouldnt: [ self collectionWithCopyNonIdentical ]raise: Error. element := self collectionWithCopyNonIdentical anyOne. self deny: element == element copy. ! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureIndexAccessFotMultipliness self shouldnt: [ self collectionWithSameAtEndAndBegining ] raise: Error. self assert: self collectionWithSameAtEndAndBegining first = self collectionWithSameAtEndAndBegining last. self assert: self collectionWithSameAtEndAndBegining size > 1. 1 to: self collectionWithSameAtEndAndBegining size do: [ :i | i > 1 & (i < self collectionWithSameAtEndAndBegining size) ifTrue: [ self deny: (self collectionWithSameAtEndAndBegining at: i) = self collectionWithSameAtEndAndBegining first ] ]! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureIndexAccessTest | res collection element | self shouldnt: [ self collectionMoreThan1NoDuplicates ] raise: Error. self assert: self collectionMoreThan1NoDuplicates size >1. res := true. self collectionMoreThan1NoDuplicates detect: [ :each | (self collectionMoreThan1NoDuplicates occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false. self shouldnt: [ self elementInForIndexAccessing ] raise: Error. self assert: ( (collection := self collectionMoreThan1NoDuplicates )includes: (element:= self elementInForIndexAccessing)). self shouldnt: [ self elementNotInForIndexAccessing ] raise: Error. self deny: (self collectionMoreThan1NoDuplicates includes: self elementNotInForIndexAccessing)! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureIterateSequencedReadableTest | res | self shouldnt: self nonEmptyMoreThan1Element raise: Error. self assert: self nonEmptyMoreThan1Element size > 1. self shouldnt: self empty raise: Error. self assert: self empty isEmpty . res := true. self nonEmptyMoreThan1Element detect: [ :each | (self nonEmptyMoreThan1Element occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false.! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureOccurrencesForMultiplinessTest | cpt element collection | self shouldnt: [self collectionWithEqualElements ]raise: Error. self shouldnt: [self collectionWithEqualElements ]raise: Error. self shouldnt: [ self elementTwiceInForOccurrences ] raise: Error. element := self elementTwiceInForOccurrences . collection := self collectionWithEqualElements . cpt := 0 . " testing with identity check ( == ) so that identy collections can use this trait : " self collectionWithEqualElements do: [ :each | each == self elementTwiceInForOccurrences ifTrue: [ cpt := cpt + 1 ] ]. self assert: cpt = 2.! ! !ArrayTest methodsFor: 'tests - fixture' stamp: 'delaunay 4/2/2009 11:53'! test0FixtureOccurrencesTest self shouldnt: self empty raise: Error. self assert: self empty isEmpty. self shouldnt: self nonEmpty raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: self elementInForOccurrences raise: Error. self assert: (self nonEmpty includes: self elementInForOccurrences). self shouldnt: self elementNotInForOccurrences raise: Error. self deny: (self nonEmpty includes: self elementNotInForOccurrences)! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixturePrintTest self shouldnt: [self nonEmpty ] raise: Error.! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixturePutOneOrMoreElementsTest self shouldnt: self aValue raise: Error. self shouldnt: self indexArray raise: Error. self indexArray do: [ :each| self assert: each class = SmallInteger. self assert: (each>=1 & each<= self nonEmpty size). ]. self assert: self indexArray size = self valueArray size. self shouldnt: self empty raise: Error. self assert: self empty isEmpty . self shouldnt: self nonEmpty raise: Error. self deny: self nonEmpty isEmpty.! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixturePutTest self shouldnt: self aValue raise: Error. self shouldnt: self anotherValue raise: Error. self shouldnt: self anIndex raise: Error. self nonEmpty isDictionary ifFalse:[self assert: (self anIndex >=1 & self anIndex <= self nonEmpty size).]. self shouldnt: self empty raise: Error. self assert: self empty isEmpty . self shouldnt: self nonEmpty raise: Error. self deny: self nonEmpty isEmpty.! ! !ArrayTest methodsFor: 'tests - fixture' stamp: 'delaunay 4/14/2009 11:50'! test0FixtureSequencedConcatenationTest self shouldnt: self empty raise: Exception. self assert: self empty isEmpty. self shouldnt: self firstCollection raise: Exception. self shouldnt: self secondCollection raise: Exception! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureSequencedElementAccessTest self shouldnt: [ self moreThan4Elements ] raise: Error. self assert: self moreThan4Elements size >= 4. self shouldnt: [ self subCollectionNotIn ] raise: Error. self subCollectionNotIn detect: [ :each | (self moreThan4Elements includes: each) not ] ifNone: [ self assert: false ]. self shouldnt: [ self elementNotInForElementAccessing ] raise: Error. self deny: (self moreThan4Elements includes: self elementNotInForElementAccessing). self shouldnt: [ self elementInForElementAccessing ] raise: Error. self assert: (self moreThan4Elements includes: self elementInForElementAccessing)! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureSetAritmeticTest self shouldnt: [ self collection ] raise: Error. self deny: self collection isEmpty. self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self anotherElementOrAssociationNotIn ] raise: Error. self collection isDictionary ifTrue: [ self deny: (self collection associations includes: self anotherElementOrAssociationNotIn key) ] ifFalse: [ self deny: (self collection includes: self anotherElementOrAssociationNotIn) ]. self shouldnt: [ self collectionClass ] raise: Error! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureSubcollectionAccessTest self shouldnt: [ self moreThan3Elements ] raise: Error. self assert: self moreThan3Elements size > 2! ! !ArrayTest methodsFor: 'tests - fixture' stamp: 'delaunay 4/28/2009 14:11'! test0FixtureTConvertAsSetForMultiplinessTest "a collection ofFloat with equal elements:" | res | self shouldnt: [ self withEqualElements ] raise: Error. self shouldnt: [ self withEqualElements do: [ :each | self assert: each class = Float ] ] raise: Error. res := true. self withEqualElements detect: [ :each | (self withEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = true. "a collection of Float without equal elements:" self shouldnt: [ self elementsCopyNonIdenticalWithoutEqualElements ] raise: Error. self shouldnt: [ self elementsCopyNonIdenticalWithoutEqualElements do: [ :each | self assert: each class = Float ] ] raise: Error. res := true. self elementsCopyNonIdenticalWithoutEqualElements detect: [ :each | (self elementsCopyNonIdenticalWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false! ! !ArrayTest methodsFor: 'tests - fixture'! test0FixtureTConvertTest "a collection of number without equal elements:" | res | self shouldnt: [ self collectionWithoutEqualElements ]raise: Error. res := true. self collectionWithoutEqualElements detect: [ :each | (self collectionWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false. ! ! !ArrayTest methodsFor: 'tests - fixture'! test0SortingArrayedTest | tmp sorted | " an unsorted collection of number " self shouldnt: [ self unsortedCollection ]raise: Error. self unsortedCollection do:[:each | each isNumber]. sorted := true. self unsortedCollection pairsDo: [ :each1 :each2 | each2 < each1 ifTrue: [ sorted := false]. ]. self assert: sorted = false. " a collection of number sorted in an ascending order" self shouldnt: [ self sortedInAscendingOrderCollection ]raise: Error. self sortedInAscendingOrderCollection do:[:each | each isNumber]. tmp:= self sortedInAscendingOrderCollection at:1. self sortedInAscendingOrderCollection do: [: each | self assert: (each>= tmp). tmp:=each] ! ! !ArrayTest methodsFor: 'tests - fixture'! test0TSequencedStructuralEqualityTest self shouldnt: [self nonEmpty at: 1] raise: Error. "Ensures #nonEmpty is sequenceable"! ! !ArrayTest methodsFor: 'tests - fixture'! test0TStructuralEqualityTest self shouldnt: [self empty] raise: Error. self shouldnt: [self nonEmpty] raise: Error. self assert: self empty isEmpty. self deny: self nonEmpty isEmpty.! ! !ArrayTest methodsFor: 'tests - fixture'! testOFixtureReplacementSequencedTest self shouldnt: self nonEmpty raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: self elementInForReplacement raise: Error. self assert: (self nonEmpty includes: self elementInForReplacement ) . self shouldnt: self newElement raise: Error. self shouldnt: self firstIndex raise: Error. self assert: (self firstIndex >= 1 & self firstIndex <= self nonEmpty size). self shouldnt: self secondIndex raise: Error. self assert: (self secondIndex >= 1 & self secondIndex <= self nonEmpty size). self assert: self firstIndex <=self secondIndex . self shouldnt: self replacementCollection raise: Error. self shouldnt: self replacementCollectionSameSize raise: Error. self assert: (self secondIndex - self firstIndex +1)= self replacementCollectionSameSize size ! ! !ArrayTest methodsFor: 'tests - includes' stamp: 'delaunay 4/28/2009 10:22'! testIdentityIncludes " test the comportement in presence of elements 'includes' but not 'identityIncludes' " " can not be used by collections that can't include elements for wich copy doesn't return another instance " | collection element | self shouldnt: [ self collectionWithCopyNonIdentical ] raise: Error. collection := self collectionWithCopyNonIdentical. element := collection anyOne copy. "self assert: (collection includes: element)." self deny: (collection identityIncludes: element)! ! !ArrayTest methodsFor: 'tests - includes'! testIdentityIncludesNonSpecificComportement " test the same comportement than 'includes: ' " | collection | collection := self nonEmpty . self deny: (collection identityIncludes: self elementNotIn ). self assert:(collection identityIncludes: collection anyOne) ! ! !ArrayTest methodsFor: 'tests - includes'! testIncludesAllOfAllThere "self debug: #testIncludesAllOfAllThere'" self assert: (self empty includesAllOf: self empty). self assert: (self nonEmpty includesAllOf: { self nonEmpty anyOne }). self assert: (self nonEmpty includesAllOf: self nonEmpty).! ! !ArrayTest methodsFor: 'tests - includes'! testIncludesAllOfNoneThere "self debug: #testIncludesAllOfNoneThere'" self deny: (self empty includesAllOf: self nonEmpty ). self deny: (self nonEmpty includesAllOf: { self elementNotIn. self anotherElementNotIn })! ! !ArrayTest methodsFor: 'tests - includes'! testIncludesAnyOfAllThere "self debug: #testIncludesAnyOfAllThere'" self deny: (self nonEmpty includesAnyOf: self empty). self assert: (self nonEmpty includesAnyOf: { self nonEmpty anyOne }). self assert: (self nonEmpty includesAnyOf: self nonEmpty).! ! !ArrayTest methodsFor: 'tests - includes'! testIncludesAnyOfNoneThere "self debug: #testIncludesAnyOfNoneThere'" self deny: (self nonEmpty includesAnyOf: self empty). self deny: (self nonEmpty includesAnyOf: { self elementNotIn. self anotherElementNotIn })! ! !ArrayTest methodsFor: 'tests - includes'! testIncludesElementIsNotThere "self debug: #testIncludesElementIsNotThere" self deny: (self nonEmpty includes: self elementNotIn). self assert: (self nonEmpty includes: self nonEmpty anyOne). self deny: (self empty includes: self elementNotIn)! ! !ArrayTest methodsFor: 'tests - includes'! testIncludesElementIsThere "self debug: #testIncludesElementIsThere" self assert: (self nonEmpty includes: self nonEmpty anyOne).! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/15/2009 14:22'! testIdentityIndexOf "self debug: #testIdentityIndexOf" | collection element | element := self elementInCollectionOfFloat copy. self deny: self elementInCollectionOfFloat == element. collection := self collectionOfFloat copyWith: element. self assert: (collection identityIndexOf: element) = collection size! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/15/2009 14:22'! testIdentityIndexOfIAbsent "self debug: #testIdentityIndexOfIfAbsent" | collection element | element := self elementInCollectionOfFloat copy. self deny: self elementInCollectionOfFloat == element. collection := self collectionOfFloat copyWith: element. self assert: (collection identityIndexOf: element ifAbsent: [ 0 ]) = collection size. self assert: (self collectionOfFloat identityIndexOf: element ifAbsent: [ 55 ]) = 55! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/23/2009 15:14'! testIndexOf "self debug: #testIndexOf" | tmp index collection | collection := self collectionMoreThan1NoDuplicates. tmp := collection size. collection reverseDo: [ :each | each = self elementInForIndexAccessing ifTrue: [ index := tmp ]. tmp := tmp - 1 ]. self assert: (collection indexOf: self elementInForIndexAccessing) = index! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/23/2009 15:14'! testIndexOfIfAbsent "self debug: #testIndexOfIfAbsent" | collection | collection := self collectionMoreThan1NoDuplicates. self assert: (collection indexOf: collection first ifAbsent: [ 33 ]) = 1. self assert: (collection indexOf: self elementNotInForIndexAccessing ifAbsent: [ 33 ]) = 33! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/23/2009 15:14'! testIndexOfStartingAt "self debug: #testLastIndexOf" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection first. self assert: (collection indexOf: element startingAt: 2 ifAbsent: [ 99 ]) = 99. self assert: (collection indexOf: element startingAt: 1 ifAbsent: [ 99 ]) = 1. self assert: (collection indexOf: self elementNotInForIndexAccessing startingAt: 1 ifAbsent: [ 99 ]) = 99! ! !ArrayTest methodsFor: 'tests - index access'! testIndexOfStartingAtIfAbsent "self debug: #testLastIndexOf" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection first. self assert: (collection indexOf: element startingAt: 2 ifAbsent: [ 99 ]) = 99. self assert: (collection indexOf: element startingAt: 1 ifAbsent: [ 99 ]) = 1. self assert: (collection indexOf: self elementNotInForIndexAccessing startingAt: 1 ifAbsent: [ 99 ]) = 99! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/23/2009 15:14'! testIndexOfSubCollectionStartingAt "self debug: #testIndexOfIfAbsent" | subcollection index collection | collection := self collectionMoreThan1NoDuplicates. subcollection := self collectionMoreThan1NoDuplicates. index := collection indexOfSubCollection: subcollection startingAt: 1. self assert: index = 1. index := collection indexOfSubCollection: subcollection startingAt: 2. self assert: index = 0! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/23/2009 15:14'! testIndexOfSubCollectionStartingAtIfAbsent "self debug: #testIndexOfIfAbsent" | index absent subcollection collection | collection := self collectionMoreThan1NoDuplicates. subcollection := self collectionMoreThan1NoDuplicates. absent := false. index := collection indexOfSubCollection: subcollection startingAt: 1 ifAbsent: [ absent := true ]. self assert: absent = false. absent := false. index := collection indexOfSubCollection: subcollection startingAt: 2 ifAbsent: [ absent := true ]. self assert: absent = true! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/23/2009 15:14'! testLastIndexOf "self debug: #testLastIndexOf" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection first. self assert: (collection lastIndexOf: element) = 1. self assert: (collection lastIndexOf: self elementNotInForIndexAccessing) = 0! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/23/2009 15:14'! testLastIndexOfIfAbsent "self debug: #testIndexOfIfAbsent" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection first. self assert: (collection lastIndexOf: element ifAbsent: [ 99 ]) = 1. self assert: (collection lastIndexOf: self elementNotInForIndexAccessing ifAbsent: [ 99 ]) = 99! ! !ArrayTest methodsFor: 'tests - index access' stamp: 'delaunay 4/23/2009 15:14'! testLastIndexOfStartingAt "self debug: #testLastIndexOf" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection last. self assert: (collection lastIndexOf: element startingAt: collection size ifAbsent: [ 99 ]) = collection size. self assert: (collection lastIndexOf: element startingAt: collection size - 1 ifAbsent: [ 99 ]) = 99. self assert: (collection lastIndexOf: self elementNotInForIndexAccessing startingAt: collection size ifAbsent: [ 99 ]) = 99! ! !ArrayTest methodsFor: 'tests - index accessing for multipliness'! testIdentityIndexOfDuplicate "self debug: #testIdentityIndexOf" | collection element | "testing fixture here as this method may not be used by some collections testClass" self shouldnt: [self collectionWithNonIdentitySameAtEndAndBegining ] raise: Error. collection := self collectionWithNonIdentitySameAtEndAndBegining . self assert: collection first = collection last. self deny: collection first == collection last. 1 to: collection size do: [ :i | i > 1 & (i < collection size) ifTrue: [ self deny: (collection at: i) = collection first ] ]. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals but are not the same object" self assert: (collection identityIndexOf: element) = collection size! ! !ArrayTest methodsFor: 'tests - index accessing for multipliness'! testIdentityIndexOfIAbsentDuplicate "self debug: #testIdentityIndexOfIfAbsent" | collection element elementCopy | collection := self collectionWithNonIdentitySameAtEndAndBegining . element := collection last. elementCopy := element copy. self deny: element == elementCopy . self assert: (collection identityIndexOf: element ifAbsent: [ 0 ]) = collection size. self assert: (collection identityIndexOf: elementCopy ifAbsent: [ 55 ]) = 55! ! !ArrayTest methodsFor: 'tests - index accessing for multipliness'! testIndexOfDuplicate "self debug: #testIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'indexOf: should return the position of the first occurrence :'" self assert: (collection indexOf: element) = 1! ! !ArrayTest methodsFor: 'tests - index accessing for multipliness'! testIndexOfIfAbsentDuplicate "self debug: #testIndexOfIfAbsent" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'indexOf:ifAbsent: should return the position of the first occurrence :'" self assert: (collection indexOf: element ifAbsent: [ 55 ]) = 1! ! !ArrayTest methodsFor: 'tests - index accessing for multipliness'! testIndexOfStartingAtDuplicate "self debug: #testLastIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'indexOf:ifAbsent:startingAt: should return the position of the first occurrence :'" self assert: (collection indexOf: element startingAt: 1 ifAbsent: [ 55 ]) = 1. self assert: (collection indexOf: element startingAt: 2 ifAbsent: [ 55 ]) = collection size! ! !ArrayTest methodsFor: 'tests - index accessing for multipliness'! testLastIndexOfDuplicate "self debug: #testLastIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection first. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'lastIndexOf: should return the position of the last occurrence :'" self assert: (collection lastIndexOf: element) = collection size! ! !ArrayTest methodsFor: 'tests - index accessing for multipliness'! testLastIndexOfIfAbsentDuplicate "self debug: #testIndexOfIfAbsent" "self debug: #testLastIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection first. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'lastIndexOf: should return the position of the last occurrence :'" self assert: (collection lastIndexOf: element ifAbsent: [ 55 ]) = collection size! ! !ArrayTest methodsFor: 'tests - index accessing for multipliness'! testLastIndexOfStartingAtDuplicate "self debug: #testLastIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'lastIndexOf:ifAbsent:startingAt: should return the position of the last occurrence :'" self assert: (collection lastIndexOf: element startingAt: collection size ifAbsent: [ 55 ]) = collection size. self assert: (collection lastIndexOf: element startingAt: collection size - 1 ifAbsent: [ 55 ]) = 1! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testAllButFirstDo | result | result:= OrderedCollection new. self nonEmptyMoreThan1Element allButFirstDo: [:each | result add: each]. 1 to: (result size) do: [:i| self assert: (self nonEmptyMoreThan1Element at:(i +1))=(result at:i)]. self assert: result size=(self nonEmptyMoreThan1Element size-1).! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testAllButLastDo | result | result:= OrderedCollection new. self nonEmptyMoreThan1Element allButLastDo: [:each | result add: each]. 1 to: (result size) do: [:i| self assert: (self nonEmptyMoreThan1Element at:(i ))=(result at:i)]. self assert: result size=(self nonEmptyMoreThan1Element size-1).! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testCollectFromTo | result | result:=self nonEmptyMoreThan1Element collect: [ :each | each ] from: 1 to: (self nonEmptyMoreThan1Element size - 1). 1 to: result size do: [ :i | self assert: (self nonEmptyMoreThan1Element at: i) = (result at: i) ]. self assert: result size = (self nonEmptyMoreThan1Element size - 1)! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testDetectSequenced " testing that detect keep the first element returning true for sequenceable collections " | element result | element := self nonEmptyMoreThan1Element at:1. result:=self nonEmptyMoreThan1Element detect: [:each | each notNil ]. self assert: result = element. ! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFindFirst | element result | element := self nonEmptyMoreThan1Element at:1. result:=self nonEmptyMoreThan1Element findFirst: [:each | each =element]. self assert: result=1. ! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFindFirstNotIn | result | result:=self empty findFirst: [:each | true]. self assert: result=0. ! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFindLast | element result | element := self nonEmptyMoreThan1Element at:self nonEmptyMoreThan1Element size. result:=self nonEmptyMoreThan1Element findLast: [:each | each =element]. self assert: result=self nonEmptyMoreThan1Element size. ! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFindLastNotIn | result | result:=self empty findFirst: [:each | true]. self assert: result=0. ! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFromToDo | result | result:= OrderedCollection new. self nonEmptyMoreThan1Element from: 1 to: (self nonEmptyMoreThan1Element size -1) do: [:each | result add: each]. 1 to: (self nonEmptyMoreThan1Element size -1) do: [:i| self assert: (self nonEmptyMoreThan1Element at:i )=(result at:i)]. self assert: result size=(self nonEmptyMoreThan1Element size-1).! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testKeysAndValuesDo "| result | result:= OrderedCollection new. self nonEmptyMoreThan1Element keysAndValuesDo: [:i :value| result add: (value+i)]. 1 to: result size do: [:i| self assert: (result at:i)=((self nonEmptyMoreThan1Element at:i)+i)]" | indexes elements | indexes:= OrderedCollection new. elements := OrderedCollection new. self nonEmptyMoreThan1Element keysAndValuesDo: [:i :value| indexes add: (i). elements add: value]. (1 to: self nonEmptyMoreThan1Element size )do: [ :i | self assert: (indexes at: i) = i. self assert: (elements at: i) = (self nonEmptyMoreThan1Element at: i). ]. self assert: indexes size = elements size. self assert: indexes size = self nonEmptyMoreThan1Element size . ! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testKeysAndValuesDoEmpty | result | result:= OrderedCollection new. self empty keysAndValuesDo: [:i :value| result add: (value+i)]. self assert: result isEmpty .! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testPairsCollect | index result | index:=0. result:=self nonEmptyMoreThan1Element pairsCollect: [:each1 :each2 | self assert: ( self nonEmptyMoreThan1Element indexOf: each2 ) = (index := index + 2). (self nonEmptyMoreThan1Element indexOf: each2) = ((self nonEmptyMoreThan1Element indexOf: each1) + 1). ]. result do: [:each | self assert: each = true]. ! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testPairsDo | index | index:=1. self nonEmptyMoreThan1Element pairsDo: [:each1 :each2 | self assert:(self nonEmptyMoreThan1Element at:index)=each1. self assert:(self nonEmptyMoreThan1Element at:(index+1))=each2. index:=index+2]. self nonEmptyMoreThan1Element size odd ifTrue:[self assert: index=self nonEmptyMoreThan1Element size] ifFalse:[self assert: index=(self nonEmptyMoreThan1Element size+1)].! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testReverseDo | result | result:= OrderedCollection new. self nonEmpty reverseDo: [: each | result add: each]. 1 to: result size do: [:i| self assert: (result at: i)=(self nonEmpty at:(self nonEmpty size-i+1))].! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testReverseDoEmpty | result | result:= OrderedCollection new. self empty reverseDo: [: each | result add: each]. self assert: result isEmpty .! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testReverseWithDo | secondCollection result index | result:= OrderedCollection new. index := self nonEmptyMoreThan1Element size + 1. secondCollection:= self nonEmptyMoreThan1Element copy. self nonEmptyMoreThan1Element reverseWith: secondCollection do: [:a :b | self assert: (self nonEmptyMoreThan1Element indexOf: a ) = (index := index - 1 ). result add: (a = b)]. 1 to: result size do: [:i| self assert: (result at:i)=(true)]. self assert: result size = self nonEmptyMoreThan1Element size.! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithCollect | result newCollection index collection | index := 0. collection := self nonEmptyMoreThan1Element . newCollection := collection copy. result:=collection with: newCollection collect: [:a :b | self assert: (collection indexOf: a ) = ( index := index + 1). self assert: (a = b). b]. 1 to: result size do:[: i | self assert: (result at:i)= (collection at: i)]. self assert: result size = collection size.! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithCollectError self should: [self nonEmptyMoreThan1Element with: self empty collect:[:a :b | ]] raise: Error.! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithDo | secondCollection result index | result:= OrderedCollection new. secondCollection:= self nonEmptyMoreThan1Element copy. index := 0. self nonEmptyMoreThan1Element with: secondCollection do: [:a :b | self assert: (self nonEmptyMoreThan1Element indexOf: a) = ( index := index + 1). result add: (a =b)]. 1 to: result size do: [:i| self assert: (result at:i)=(true)]. self assert: result size = self nonEmptyMoreThan1Element size.! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithDoError self should: [self nonEmptyMoreThan1Element with: self empty do:[:a :b | ]] raise: Error.! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithIndexCollect | result index collection | index := 0. collection := self nonEmptyMoreThan1Element . result := collection withIndexCollect: [:each :i | self assert: i = (index := index + 1). self assert: i = (collection indexOf: each) . each] . 1 to: result size do:[: i | self assert: (result at:i)= (collection at: i)]. self assert: result size = collection size.! ! !ArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithIndexDo "| result | result:=Array new: self nonEmptyMoreThan1Element size. self nonEmptyMoreThan1Element withIndexDo: [:each :i | result at:i put:(each+i)]. 1 to: result size do:[: i | self assert: (result at:i)= ((self nonEmptyMoreThan1Element at: i) + i)]" | indexes elements | indexes:= OrderedCollection new. elements := OrderedCollection new. self nonEmptyMoreThan1Element withIndexDo: [:value :i | indexes add: (i). elements add: value]. (1 to: self nonEmptyMoreThan1Element size )do: [ :i | self assert: (indexes at: i) = i. self assert: (elements at: i) = (self nonEmptyMoreThan1Element at: i). ]. self assert: indexes size = elements size. self assert: indexes size = self nonEmptyMoreThan1Element size . ! ! !ArrayTest methodsFor: 'tests - occurrencesOf' stamp: 'delaunay 4/2/2009 11:52'! testOccurrencesOf | result expected | result := self nonEmpty occurrencesOf: self elementInForOccurrences. expected := 0. self nonEmpty do: [ :each | self elementInForOccurrences = each ifTrue: [ expected := expected + 1 ] ]. self assert: result = expected! ! !ArrayTest methodsFor: 'tests - occurrencesOf' stamp: 'delaunay 4/2/2009 11:52'! testOccurrencesOfEmpty | result | result := self empty occurrencesOf: self elementInForOccurrences. self assert: result = 0! ! !ArrayTest methodsFor: 'tests - occurrencesOf' stamp: 'delaunay 4/2/2009 11:53'! testOccurrencesOfNotIn | result | result := self empty occurrencesOf: self elementNotInForOccurrences. self assert: result = 0! ! !ArrayTest methodsFor: 'tests - occurrencesOf for multipliness'! testOccurrencesOfForMultipliness | collection element | collection := self collectionWithEqualElements . element := self elementTwiceInForOccurrences . self assert: (collection occurrencesOf: element ) = 2. ! ! !ArrayTest methodsFor: 'tests - printing'! testPrintElementsOn | aStream result allElementsAsString | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printElementsOn: aStream . allElementsAsString:=(result findBetweenSubStrs: ' ' ). 1 to: allElementsAsString size do: [:i | self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString). ].! ! !ArrayTest methodsFor: 'tests - printing'! testPrintNameOn | aStream result | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printNameOn: aStream . Transcript show: result asString. self nonEmpty class name first isVowel ifTrue:[ self assert: aStream contents =('an ',self nonEmpty class name ) ] ifFalse:[self assert: aStream contents =('a ',self nonEmpty class name)].! ! !ArrayTest methodsFor: 'tests - printing'! testPrintOn | aStream result allElementsAsString | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printOn: aStream . allElementsAsString:=(result findBetweenSubStrs: ' ' ). 1 to: allElementsAsString size do: [:i | i=1 ifTrue:[ self accessCollection class name first isVowel ifTrue:[self assert: (allElementsAsString at:i)='an' ] ifFalse:[self assert: (allElementsAsString at:i)='a'].]. i=2 ifTrue:[self assert: (allElementsAsString at:i)=self accessCollection class name]. i>2 ifTrue:[self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString).]. ].! ! !ArrayTest methodsFor: 'tests - printing'! testPrintOnDelimiter | aStream result allElementsAsString | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printOn: aStream delimiter: ', ' . allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString). ].! ! !ArrayTest methodsFor: 'tests - printing'! testPrintOnDelimiterLast | aStream result allElementsAsString | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printOn: aStream delimiter: ', ' last: 'and'. allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString)]. i=(allElementsAsString size-1) ifTrue:[ self deny: (allElementsAsString at:i)=('and')asString]. i=(allElementsAsString size) ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:(i-1))asString)]. ].! ! !ArrayTest methodsFor: 'tests - printing'! testStoreOn " for the moment work only for collection that include simple elements such that Integer" "| string str result cuttedResult index elementsAsStringExpected elementsAsStringObtained tmp | string := ''. str := ReadWriteStream on: string. elementsAsStringExpected := OrderedCollection new. elementsAsStringObtained := OrderedCollection new. self nonEmpty do: [ :each | elementsAsStringExpected add: each asString]. self nonEmpty storeOn: str. result := str contents . cuttedResult := ( result findBetweenSubStrs: ';' ). index := 1. cuttedResult do: [ :each | index = 1 ifTrue: [ self assert: (each beginsWith: ( tmp := '((' , self nonEmpty class asString , ' new) add: ' )). tmp := each copyFrom: ( tmp size + 1) to: ( each size ). elementsAsStringObtained add: tmp. index := index + 1. ] ifFalse: [ index < cuttedResult size ifTrue:[self assert: (each beginsWith: ( tmp:= ' add: ' )). tmp := each copyFrom: ( tmp size + 1) to: ( each size ). elementsAsStringObtained add: tmp. index := index + 1.] ifFalse: [self assert: ( each = ' yourself)' ) ]. ] ]. elementsAsStringExpected do: [ :each | self assert: (elementsAsStringExpected occurrencesOf: each ) = ( elementsAsStringObtained occurrencesOf: each) ]" ! ! !ArrayTest methodsFor: 'tests - puting with indexes'! testAtAllIndexesPut self nonEmpty atAllPut: self aValue. self nonEmpty do:[ :each| self assert: each = self aValue]. ! ! !ArrayTest methodsFor: 'tests - puting with indexes'! testAtAllPut | | self nonEmpty atAll: self indexArray put: self aValue.. self indexArray do: [:i | self assert: (self nonEmpty at: i)=self aValue ]. ! ! !ArrayTest methodsFor: 'tests - puting with indexes'! testAtAllPutAll | valueArray | valueArray := self valueArray . self nonEmpty atAll: self indexArray putAll: valueArray . 1 to: self indexArray size do: [:i | self assert: (self nonEmpty at:(self indexArray at: i))= (valueArray at:i) ]! ! !ArrayTest methodsFor: 'tests - puting with indexes'! testAtLastPut | result index | index := self indexArray anyOne. result := self nonEmpty atLast: index put: self aValue. self assert: (self nonEmpty at: (self nonEmpty size +1 - index)) = self aValue .! ! !ArrayTest methodsFor: 'tests - puting with indexes'! testAtWrapPut "self debug: #testAtWrapPut" | index | index := self indexArray anyOne. self nonEmpty atWrap: 0 put: self aValue. self assert: (self nonEmpty at:(self nonEmpty size))=self aValue. self nonEmpty atWrap: (self nonEmpty size+1) put: self aValue. self assert: (self nonEmpty at:(1))=self aValue. self nonEmpty atWrap: (index ) put: self aValue. self assert: (self nonEmpty at: index ) = self aValue. self nonEmpty atWrap: (self nonEmpty size+index ) put: self aValue . self assert: (self nonEmpty at:(index ))=self aValue .! ! !ArrayTest methodsFor: 'tests - puting with indexes'! testFromToPut | collection index | index := self indexArray anyOne. collection := self nonEmpty copy. collection from: 1 to: index put: self aValue.. 1 to: index do: [:i | self assert: (collection at: i)= self aValue]. (index +1) to: collection size do: [:i | self assert: (collection at:i)= (self nonEmpty at:i)].! ! !ArrayTest methodsFor: 'tests - puting with indexes'! testSwapWith "self debug: #testSwapWith" | result index | index := self indexArray anyOne. result:= self nonEmpty copy . result swap: index with: 1. self assert: (result at: index) = (self nonEmpty at:1). self assert: (result at: 1) = (self nonEmpty at: index). ! ! !ArrayTest methodsFor: 'tests - replacing'! testReplaceAllWith | result collection oldElement newElement | collection := self nonEmpty . result := collection copy. oldElement := self elementInForReplacement . newElement := self newElement . result replaceAll: oldElement with: newElement . 1 to: collection size do: [: each | ( collection at: each ) = oldElement ifTrue: [ self assert: ( result at: each ) = newElement ]. ].! ! !ArrayTest methodsFor: 'tests - replacing'! testReplaceFromToWith | result collection replacementCollection firstIndex secondIndex | collection := self nonEmpty . replacementCollection := self replacementCollectionSameSize . firstIndex := self firstIndex . secondIndex := self secondIndex . result := collection copy. result replaceFrom: firstIndex to: secondIndex with: replacementCollection . "verify content of 'result' : " "first part of 'result'' : '" 1 to: ( firstIndex - 1 ) do: [ :i | self assert: (collection at:i ) = ( result at: i ) ]. " middle part containing replacementCollection : " ( firstIndex ) to: ( firstIndex + replacementCollection size - 1 ) do: [ :i | self assert: ( result at: i ) = ( replacementCollection at: ( i - firstIndex +1 ) ) ]. " end part :" ( firstIndex + replacementCollection size) to: (result size) do: [:i| self assert: ( result at: i ) = ( collection at: ( secondIndex + 1 - ( firstIndex + replacementCollection size ) + i ) ) ]. ! ! !ArrayTest methodsFor: 'tests - replacing'! testReplaceFromToWithStartingAt | result repStart collection replacementCollection firstIndex secondIndex | collection := self nonEmpty . result := collection copy. replacementCollection := self replacementCollectionSameSize . firstIndex := self firstIndex . secondIndex := self secondIndex . repStart := replacementCollection size - ( secondIndex - firstIndex + 1 ) + 1. result replaceFrom: firstIndex to: secondIndex with: replacementCollection startingAt: repStart . "verify content of 'result' : " "first part of 'result'' : '" 1 to: ( firstIndex - 1 ) do: [ :i | self assert: ( collection at:i ) = ( result at: i ) ]. " middle part containing replacementCollection : " ( firstIndex ) to: ( replacementCollection size - repStart +1 ) do: [:i| self assert: (result at: i)=( replacementCollection at: ( repStart + ( i -firstIndex ) ) ) ]. " end part :" ( firstIndex + replacementCollection size ) to: ( result size ) do: [ :i | self assert: ( result at: i ) = ( collection at: ( secondIndex + 1 - ( firstIndex + replacementCollection size ) + i ) ) ].! ! !ArrayTest methodsFor: 'tests - sequence isempty'! testSequenceAbleIfEmptyifNotEmptyDo "self debug: #testSequenceAbleIfEmptyifNotEmptyDo" self assert: (self nonEmpty ifEmpty: [false] ifNotEmptyDo: [:s | (self accessValuePutInOn: s) = self valuePutIn]).! ! !ArrayTest methodsFor: 'tests - sequence isempty'! testSequenceIfEmptyifNotEmptyDo "self debug #testSequenceIfEmptyifNotEmptyDo" self assert: (self nonEmpty ifEmpty: [false] ifNotEmptyDo: [:s | (self accessValuePutInOn: s) = self valuePutIn]).! ! !ArrayTest methodsFor: 'tests - sequence isempty'! testSequenceIfNotEmpty self assert: (self nonEmpty ifNotEmpty: [:s | self accessValuePutInOn: s]) = self valuePutIn! ! !ArrayTest methodsFor: 'tests - sequence isempty'! testSequenceIfNotEmptyDo self empty ifNotEmptyDo: [:s | self assert: false]. self assert: (self nonEmpty ifNotEmptyDo: [:s | self accessValuePutInOn: s]) = self valuePutIn ! ! !ArrayTest methodsFor: 'tests - sequence isempty'! testSequenceIfNotEmptyDoifNotEmpty self assert: (self nonEmpty ifNotEmptyDo: [:s | (self accessValuePutInOn: s) = self valuePutIn] ifEmpty: [false])! ! !ArrayTest methodsFor: 'tests - sequence isempty'! testSequenceIfNotEmptyifEmpty self assert: (self nonEmpty ifEmpty: [false] ifNotEmpty: [:s | (self accessValuePutInOn: s) = self valuePutIn])! ! !ArrayTest methodsFor: 'tests - set arithmetic'! containsAll: union of: one andOf: another self assert: (one allSatisfy: [:each | union includes: each]). self assert: (another allSatisfy: [:each | union includes: each])! ! !ArrayTest methodsFor: 'tests - set arithmetic'! numberOfSimilarElementsInIntersection ^ self collection occurrencesOf: self anotherElementOrAssociationIn! ! !ArrayTest methodsFor: 'tests - set arithmetic'! testDifference "Answer the set theoretic difference of two collections." "self debug: #testDifference" self assert: (self collection difference: self collection) isEmpty. self assert: (self empty difference: self collection) isEmpty. self assert: (self collection difference: self empty) = self collection ! ! !ArrayTest methodsFor: 'tests - set arithmetic'! testDifferenceWithNonNullIntersection "Answer the set theoretic difference of two collections." "self debug: #testDifferenceWithNonNullIntersection" " #(1 2 3) difference: #(2 4) -> #(1 3)" | res overlapping | overlapping := self collectionClass with: self anotherElementOrAssociationNotIn with: self anotherElementOrAssociationIn. res := self collection difference: overlapping. self deny: (res includes: self anotherElementOrAssociationIn). overlapping do: [ :each | self deny: (res includes: each) ]! ! !ArrayTest methodsFor: 'tests - set arithmetic'! testDifferenceWithSeparateCollection "Answer the set theoretic difference of two collections." "self debug: #testDifferenceWithSeparateCollection" | res separateCol | separateCol := self collectionClass with: self anotherElementOrAssociationNotIn. res := self collection difference: separateCol. self deny: (res includes: self anotherElementOrAssociationNotIn). self assert: res = self collection. res := separateCol difference: self collection. self deny: (res includes: self collection anyOne). self assert: res = separateCol! ! !ArrayTest methodsFor: 'tests - set arithmetic'! testIntersectionBasic "self debug: #testIntersectionBasic" | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). self deny: inter isEmpty. self assert: (inter includes: self anotherElementOrAssociationIn value)! ! !ArrayTest methodsFor: 'tests - set arithmetic'! testIntersectionEmpty "self debug: #testIntersectionEmpty" | inter | inter := self empty intersection: self empty. self assert: inter isEmpty. inter := self empty intersection: self collection . self assert: inter = self empty. ! ! !ArrayTest methodsFor: 'tests - set arithmetic'! testIntersectionItself "self debug: #testIntersectionItself" self assert: (self collection intersection: self collection) = self collection. ! ! !ArrayTest methodsFor: 'tests - set arithmetic'! testIntersectionTwoSimilarElementsInIntersection "self debug: #testIntersectionBasic" | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). self assert: (self collection occurrencesOf: self anotherElementOrAssociationIn) = self numberOfSimilarElementsInIntersection. self assert: (inter includes: self anotherElementOrAssociationIn value)! ! !ArrayTest methodsFor: 'tests - set arithmetic'! testUnion "self debug: #testUnionOfEmpties" | union | union := self empty union: self nonEmpty. self containsAll: union of: self empty andOf: self nonEmpty. union := self nonEmpty union: self empty. self containsAll: union of: self empty andOf: self nonEmpty. union := self collection union: self nonEmpty. self containsAll: union of: self collection andOf: self nonEmpty.! ! !ArrayTest methodsFor: 'tests - set arithmetic'! testUnionOfEmpties "self debug: #testUnionOfEmpties" self assert: (self empty union: self empty) isEmpty. ! ! !ArrayTest methodsFor: 'tests - sorting'! testIsSorted self assert: [ self sortedInAscendingOrderCollection isSorted ]. self deny: [ self unsortedCollection isSorted ]! ! !ArrayTest methodsFor: 'tests - sorting'! testIsSortedBy self assert: (self sortedInAscendingOrderCollection isSortedBy: [:a :b | ab]). ! ! !ArrayTest methodsFor: 'tests - sorting'! testSort | result tmp | result := self unsortedCollection sort. tmp := result at: 1. result do: [:each | self assert: each>=tmp. tmp:= each. ].! ! !ArrayTest methodsFor: 'tests - sorting'! testSortUsingSortBlock | result tmp | result := self unsortedCollection sort: [:a :b | a>b]. tmp := result at: 1. result do: [:each | self assert: each<=tmp. tmp:= each. ].! ! !ArrayTest methodsFor: 'tests - subcollections access'! testAllButFirst "self debug: #testAllButFirst" | abf col | col := self moreThan3Elements. abf := col allButFirst. self deny: abf first = col first. self assert: abf size + 1 = col size! ! !ArrayTest methodsFor: 'tests - subcollections access'! testAllButFirstNElements "self debug: #testAllButFirst" | abf col | col := self moreThan3Elements. abf := col allButFirst: 2. 1 to: abf size do: [ :i | self assert: (abf at: i) = (col at: i + 2) ]. self assert: abf size + 2 = col size! ! !ArrayTest methodsFor: 'tests - subcollections access'! testAllButLast "self debug: #testAllButLast" | abf col | col := self moreThan3Elements. abf := col allButLast. self deny: abf last = col last. self assert: abf size + 1 = col size! ! !ArrayTest methodsFor: 'tests - subcollections access'! testAllButLastNElements "self debug: #testAllButFirst" | abf col | col := self moreThan3Elements. abf := col allButLast: 2. 1 to: abf size do: [ :i | self assert: (abf at: i) = (col at: i) ]. self assert: abf size + 2 = col size! ! !ArrayTest methodsFor: 'tests - subcollections access'! testFirstNElements "self debug: #testFirstNElements" | result | result := self moreThan3Elements first: self moreThan3Elements size - 1. 1 to: result size do: [ :i | self assert: (result at: i) = (self moreThan3Elements at: i) ]. self assert: result size = (self moreThan3Elements size - 1). self should: [ self moreThan3Elements first: self moreThan3Elements size + 1 ] raise: Error! ! !ArrayTest methodsFor: 'tests - subcollections access'! testLastNElements "self debug: #testLastNElements" | result | result := self moreThan3Elements last: self moreThan3Elements size - 1. 1 to: result size do: [ :i | self assert: (result at: i) = (self moreThan3Elements at: i + 1) ]. self assert: result size = (self moreThan3Elements size - 1). self should: [ self moreThan3Elements last: self moreThan3Elements size + 1 ] raise: Error! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ArrayTest class uses: TEmptySequenceableTest classTrait + TSequencedElementAccessTest classTrait + TCloneTest classTrait + TCopyTest classTrait + TSetArithmetic classTrait + TCreationWithTest classTrait + TPutBasicTest classTrait + TConvertTest classTrait + TSortTest classTrait + TIterateSequencedReadableTest classTrait + TSequencedConcatenationTest classTrait + TReplacementSequencedTest classTrait + TAsStringCommaAndDelimiterSequenceableTest classTrait + TBeginsEndsWith classTrait + TPrintOnSequencedTest classTrait + TIndexAccess classTrait + TSubCollectionAccess classTrait + TCopyPartOfSequenceable classTrait + TCopySequenceableSameContents classTrait + TCopySequenceableWithOrWithoutSpecificElements classTrait + TCopySequenceableWithReplacement classTrait + TIndexAccessForMultipliness classTrait + TCopyPartOfSequenceableForMultipliness classTrait + TConvertAsSortedTest classTrait + TPutTest classTrait + TIncludesWithIdentityCheckTest classTrait + TConvertAsSetForMultiplinessIdentityTest classTrait + TSequencedStructuralEqualityTest classTrait + TOccurrencesForMultiplinessTest classTrait instanceVariableNames: ''! SequenceableCollection subclass: #ArrayedCollection instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Collections-Abstract'! !ArrayedCollection commentStamp: '' prior: 0! I am an abstract collection of elements with a fixed range of integers (from 1 to n>=0) as external keys.! !ArrayedCollection methodsFor: 'accessing' stamp: 'sma 5/12/2000 11:36'! size "Answer how many elements the receiver contains." ^ self basicSize! ! !ArrayedCollection methodsFor: 'adding' stamp: 'sma 5/12/2000 14:09'! add: newObject self shouldNotImplement! ! !ArrayedCollection methodsFor: 'filter streaming' stamp: 'sma 5/12/2000 14:20'! flattenOnStream: aStream aStream writeArrayedCollection: self! ! !ArrayedCollection methodsFor: 'objects from disk' stamp: 'nk 3/17/2004 15:22'! byteSize ^self basicSize * self bytesPerBasicElement ! ! !ArrayedCollection methodsFor: 'objects from disk' stamp: 'nk 3/17/2004 16:28'! bytesPerBasicElement "Answer the number of bytes that each of my basic elements requires. In other words: self basicSize * self bytesPerBasicElement should equal the space required on disk by my variable sized representation." ^self class isBytes ifTrue: [ 1 ] ifFalse: [ 4 ]! ! !ArrayedCollection methodsFor: 'objects from disk' stamp: 'nk 3/17/2004 18:51'! bytesPerElement ^self class isBytes ifTrue: [ 1 ] ifFalse: [ 4 ]. ! ! !ArrayedCollection methodsFor: 'objects from disk' stamp: 'nk 7/30/2004 17:50'! restoreEndianness "This word object was just read in from a stream. It was stored in Big Endian (Mac) format. Reverse the byte order if the current machine is Little Endian. We only intend this for non-pointer arrays. Do nothing if I contain pointers." self class isPointers | self class isWords not ifTrue: [^self]. SmalltalkImage current isLittleEndian ifTrue: [Bitmap swapBytesIn: self from: 1 to: self basicSize]! ! !ArrayedCollection methodsFor: 'objects from disk' stamp: 'tk 3/7/2001 17:36'! swapHalves "A normal switch in endianness (byte order in words) reverses the order of 4 bytes. That is not correct for SoundBuffers, which use 2-bytes units. If a normal switch has be done, this method corrects it further by swapping the two halves of the long word. This method is only used for 16-bit quanities in SoundBuffer, ShortIntegerArray, etc." | hack blt | "The implementation is a hack, but fast for large ranges" hack := Form new hackBits: self. blt := (BitBlt toForm: hack) sourceForm: hack. blt combinationRule: Form reverse. "XOR" blt sourceY: 0; destY: 0; height: self size; width: 2. blt sourceX: 0; destX: 2; copyBits. "Exchange bytes 0&1 with 2&3" blt sourceX: 2; destX: 0; copyBits. blt sourceX: 0; destX: 2; copyBits.! ! !ArrayedCollection methodsFor: 'objects from disk' stamp: 'ar 5/17/2001 19:50'! writeOn: aStream "Store the array of bits onto the argument, aStream. (leading byte ~= 16r80) identifies this as raw bits (uncompressed). Always store in Big Endian (Mac) byte order. Do the writing at BitBlt speeds. We only intend this for non-pointer arrays. Do nothing if I contain pointers." self class isPointers | self class isWords not ifTrue: [^ super writeOn: aStream]. "super may cause an error, but will not be called." aStream nextInt32Put: self basicSize. aStream nextWordsPutAll: self.! ! !ArrayedCollection methodsFor: 'objects from disk' stamp: 'tk 3/7/2001 18:07'! writeOnGZIPByteStream: aStream "We only intend this for non-pointer arrays. Do nothing if I contain pointers." self class isPointers | self class isWords not ifTrue: [^ super writeOnGZIPByteStream: aStream]. "super may cause an error, but will not be called." aStream nextPutAllWordArray: self! ! !ArrayedCollection methodsFor: 'printing'! storeOn: aStream aStream nextPutAll: '(('. aStream nextPutAll: self class name. aStream nextPutAll: ' new: '. aStream store: self size. aStream nextPut: $). (self storeElementsFrom: 1 to: self size on: aStream) ifFalse: [aStream nextPutAll: '; yourself']. aStream nextPut: $)! ! !ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 18:18'! asSortedArray self isSorted ifTrue: [^ self asArray]. ^ super asSortedArray! ! !ArrayedCollection methodsFor: 'sorting' stamp: 'sma 6/1/2000 11:57'! isSorted "Return true if the receiver is sorted by the given criterion. Optimization for isSortedBy: [:a :b | a <= b]." | lastElm elm | self isEmpty ifTrue: [^ true]. lastElm := self first. 2 to: self size do: [:index | elm := self at: index. lastElm <= elm ifFalse: [^ false]. lastElm := elm]. ^ true! ! !ArrayedCollection methodsFor: 'sorting' stamp: 'sma 6/1/2000 11:58'! isSortedBy: aBlock "Return true if the receiver is sorted by the given criterion." | lastElm elm | self isEmpty ifTrue: [^ true]. lastElm := self first. 2 to: self size do: [:index | elm := self at: index. (aBlock value: lastElm value: elm) ifFalse: [^ false]. lastElm := elm]. ^ true! ! !ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:28'! mergeFirst: first middle: middle last: last into: dst by: aBlock "Private. Merge the sorted ranges [first..middle] and [middle+1..last] of the receiver into the range [first..last] of dst." | i1 i2 val1 val2 out | i1 := first. i2 := middle + 1. val1 := self at: i1. val2 := self at: i2. out := first - 1. "will be pre-incremented" "select 'lower' half of the elements based on comparator" [(i1 <= middle) and: [i2 <= last]] whileTrue: [(aBlock value: val1 value: val2) ifTrue: [dst at: (out := out + 1) put: val1. val1 := self at: (i1 := i1 + 1)] ifFalse: [dst at: (out := out + 1) put: val2. i2 := i2 + 1. i2 <= last ifTrue: [val2 := self at: i2]]]. "copy the remaining elements" i1 <= middle ifTrue: [dst replaceFrom: out + 1 to: last with: self startingAt: i1] ifFalse: [dst replaceFrom: out + 1 to: last with: self startingAt: i2]! ! !ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:25'! mergeSortFrom: startIndex to: stopIndex by: aBlock "Sort the given range of indices using the mergesort algorithm. Mergesort is a worst-case O(N log N) sorting algorithm that usually does only half as many comparisons as heapsort or quicksort." "Details: recursively split the range to be sorted into two halves, mergesort each half, then merge the two halves together. An extra copy of the data is used as temporary storage and successive merge phases copy data back and forth between the receiver and this copy. The recursion is set up so that the final merge is performed into the receiver, resulting in the receiver being completely sorted." self size <= 1 ifTrue: [^ self]. "nothing to do" startIndex = stopIndex ifTrue: [^ self]. self assert: [startIndex >= 1 and: [startIndex < stopIndex]]. "bad start index" self assert: [stopIndex <= self size]. "bad stop index" self mergeSortFrom: startIndex to: stopIndex src: self clone dst: self by: aBlock! ! !ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:26'! mergeSortFrom: first to: last src: src dst: dst by: aBlock "Private. Split the range to be sorted in half, sort each half, and merge the two half-ranges into dst." | middle | first = last ifTrue: [^ self]. middle := (first + last) // 2. self mergeSortFrom: first to: middle src: dst dst: src by: aBlock. self mergeSortFrom: middle + 1 to: last src: dst dst: src by: aBlock. src mergeFirst: first middle: middle last: last into: dst by: aBlock! ! !ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:22'! sort "Sort this array into ascending order using the '<=' operator." self sort: [:a :b | a <= b]! ! !ArrayedCollection methodsFor: 'sorting' stamp: 'sma 5/12/2000 14:21'! sort: aSortBlock "Sort this array using aSortBlock. The block should take two arguments and return true if the first element should preceed the second one." self mergeSortFrom: 1 to: self size by: aSortBlock! ! !ArrayedCollection methodsFor: 'private'! defaultElement ^nil! ! !ArrayedCollection methodsFor: 'private'! storeElementsFrom: firstIndex to: lastIndex on: aStream | noneYet defaultElement arrayElement | noneYet := true. defaultElement := self defaultElement. firstIndex to: lastIndex do: [:index | arrayElement := self at: index. arrayElement = defaultElement ifFalse: [noneYet ifTrue: [noneYet := false] ifFalse: [aStream nextPut: $;]. aStream nextPutAll: ' at: '. aStream store: index. aStream nextPutAll: ' put: '. aStream store: arrayElement]]. ^noneYet! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ArrayedCollection class instanceVariableNames: ''! !ArrayedCollection class methodsFor: 'instance creation'! new "Answer a new instance of me, with size = 0." ^self new: 0! ! !ArrayedCollection class methodsFor: 'instance creation'! new: size withAll: value "Answer an instance of me, with number of elements equal to size, each of which refers to the argument, value." ^(self new: size) atAllPut: value! ! !ArrayedCollection class methodsFor: 'instance creation'! newFrom: aCollection "Answer an instance of me containing the same elements as aCollection." | newArray | newArray := self new: aCollection size. 1 to: aCollection size do: [:i | newArray at: i put: (aCollection at: i)]. ^ newArray " Array newFrom: {1. 2. 3} {1. 2. 3} as: Array {1. 2. 3} as: ByteArray {$c. $h. $r} as: String {$c. $h. $r} as: Text "! ! !ArrayedCollection class methodsFor: 'instance creation' stamp: 'ar 5/17/2001 19:50'! newFromStream: s "Only meant for my subclasses that are raw bits and word-like. For quick unpack form the disk." | len | self isPointers | self isWords not ifTrue: [^ super newFromStream: s]. "super may cause an error, but will not be called." s next = 16r80 ifTrue: ["A compressed format. Could copy what BitMap does, or use a special sound compression format. Callers normally compress their own way." ^ self error: 'not implemented']. s skip: -1. len := s nextInt32. ^ s nextWordsInto: (self basicNew: len)! ! !ArrayedCollection class methodsFor: 'instance creation'! with: anObject "Answer a new instance of me, containing only anObject." | newCollection | newCollection := self new: 1. newCollection at: 1 put: anObject. ^newCollection! ! !ArrayedCollection class methodsFor: 'instance creation'! with: firstObject with: secondObject "Answer a new instance of me, containing firstObject and secondObject." | newCollection | newCollection := self new: 2. newCollection at: 1 put: firstObject. newCollection at: 2 put: secondObject. ^newCollection! ! !ArrayedCollection class methodsFor: 'instance creation'! with: firstObject with: secondObject with: thirdObject "Answer a new instance of me, containing only the three arguments as elements." | newCollection | newCollection := self new: 3. newCollection at: 1 put: firstObject. newCollection at: 2 put: secondObject. newCollection at: 3 put: thirdObject. ^newCollection! ! !ArrayedCollection class methodsFor: 'instance creation'! with: firstObject with: secondObject with: thirdObject with: fourthObject "Answer a new instance of me, containing only the three arguments as elements." | newCollection | newCollection := self new: 4. newCollection at: 1 put: firstObject. newCollection at: 2 put: secondObject. newCollection at: 3 put: thirdObject. newCollection at: 4 put: fourthObject. ^newCollection! ! !ArrayedCollection class methodsFor: 'instance creation'! with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject "Answer a new instance of me, containing only the five arguments as elements." | newCollection | newCollection := self new: 5. newCollection at: 1 put: firstObject. newCollection at: 2 put: secondObject. newCollection at: 3 put: thirdObject. newCollection at: 4 put: fourthObject. newCollection at: 5 put: fifthObject. ^newCollection! ! !ArrayedCollection class methodsFor: 'instance creation' stamp: 'sw 10/24/1998 22:22'! with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject with: sixthObject "Answer a new instance of me, containing only the 6 arguments as elements." | newCollection | newCollection := self new: 6. newCollection at: 1 put: firstObject. newCollection at: 2 put: secondObject. newCollection at: 3 put: thirdObject. newCollection at: 4 put: fourthObject. newCollection at: 5 put: fifthObject. newCollection at: 6 put: sixthObject. ^ newCollection! ! !ArrayedCollection class methodsFor: 'instance creation' stamp: 'sma 5/12/2000 17:37'! withAll: aCollection "Create a new collection containing all the elements from aCollection." ^ (self new: aCollection size) replaceFrom: 1 to: aCollection size with: aCollection! ! Halt subclass: #AssertionFailure instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Extensions'! !AssertionFailure commentStamp: 'gh 5/2/2002 20:29' prior: 0! AsssertionFailure is the exception signaled from Object>>assert: when the assertion block evaluates to false.! ParseNode subclass: #AssignmentNode instanceVariableNames: 'variable value' classVariableNames: '' poolDictionaries: '' category: 'Compiler-ParseNodes'! !AssignmentNode commentStamp: '' prior: 0! AssignmentNode comment: 'I represent a (var_expr) construct.'! !AssignmentNode methodsFor: 'code generation' stamp: 'eem 6/4/2008 11:26'! emitForEffect: stack on: aStream variable emitLoad: stack on: aStream. value emitForValue: stack on: aStream. pc := aStream position + 1. "debug pc is first byte of the store". variable emitStorePop: stack on: aStream! ! !AssignmentNode methodsFor: 'code generation' stamp: 'eem 6/4/2008 11:26'! emitForValue: stack on: aStream variable emitLoad: stack on: aStream. value emitForValue: stack on: aStream. pc := aStream position + 1. "debug pc is first byte of the store" variable emitStore: stack on: aStream! ! !AssignmentNode methodsFor: 'code generation'! sizeForEffect: encoder ^(value sizeForValue: encoder) + (variable sizeForStorePop: encoder)! ! !AssignmentNode methodsFor: 'code generation'! sizeForValue: encoder ^(value sizeForValue: encoder) + (variable sizeForStore: encoder)! ! !AssignmentNode methodsFor: 'code generation (closures)' stamp: 'eem 5/30/2008 09:37'! analyseTempsWithin: scopeBlock "" rootNode: rootNode "" assignmentPools: assignmentPools "" "N.B. since assigment happens _after_ the value is evaluated the value is sent the message _first_." value analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools. variable beingAssignedToAnalyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools! ! !AssignmentNode methodsFor: 'code generation (new scheme)' stamp: 'eem 6/4/2008 11:27'! emitCodeForEffect: stack encoder: encoder variable emitCodeForLoad: stack encoder: encoder. value emitCodeForValue: stack encoder: encoder. pc := encoder methodStreamPosition + 1. "debug pc is first byte of the store, i.e. the next byte". variable emitCodeForStorePop: stack encoder: encoder! ! !AssignmentNode methodsFor: 'code generation (new scheme)' stamp: 'eem 6/4/2008 11:27'! emitCodeForValue: stack encoder: encoder variable emitCodeForLoad: stack encoder: encoder. value emitCodeForValue: stack encoder: encoder. pc := encoder methodStreamPosition + 1. "debug pc is first byte of the store, i.e. the next byte". variable emitCodeForStore: stack encoder: encoder! ! !AssignmentNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/20/2008 15:16'! sizeCodeForEffect: encoder ^(variable sizeCodeForLoad: encoder) + (value sizeCodeForValue: encoder) + (variable sizeCodeForStorePop: encoder)! ! !AssignmentNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/20/2008 15:16'! sizeCodeForValue: encoder ^(variable sizeCodeForLoad: encoder) + (value sizeCodeForValue: encoder) + (variable sizeCodeForStore: encoder)! ! !AssignmentNode methodsFor: 'equation translation'! variable ^variable! ! !AssignmentNode methodsFor: 'initialize-release'! toDoIncrement: var var = variable ifFalse: [^ nil]. (value isMemberOf: MessageNode) ifTrue: [^ value toDoIncrement: var] ifFalse: [^ nil]! ! !AssignmentNode methodsFor: 'initialize-release'! value ^ value! ! !AssignmentNode methodsFor: 'initialize-release'! variable: aVariable value: expression variable := aVariable. value := expression! ! !AssignmentNode methodsFor: 'initialize-release' stamp: 'di 3/22/1999 12:00'! variable: aVariable value: expression from: encoder (aVariable isMemberOf: MessageAsTempNode) ifTrue: ["Case of remote temp vars" ^ aVariable store: expression from: encoder]. variable := aVariable. value := expression! ! !AssignmentNode methodsFor: 'initialize-release' stamp: 'hmm 7/15/2001 21:17'! variable: aVariable value: expression from: encoder sourceRange: range encoder noteSourceRange: range forNode: self. ^self variable: aVariable value: expression from: encoder! ! !AssignmentNode methodsFor: 'printing' stamp: 'eem 5/6/2008 13:48'! printOn: aStream indent: level variable printOn: aStream indent: level. aStream nextPutAll: ' := '. value printOn: aStream indent: level + 2! ! !AssignmentNode methodsFor: 'printing' stamp: 'eem 5/9/2008 18:44'! printOn: aStream indent: level precedence: p aStream nextPut: $(. self printOn: aStream indent: level. aStream nextPut: $)! ! !AssignmentNode methodsFor: 'printing' stamp: 'eem 6/2/2008 11:47'! printWithClosureAnalysisOn: aStream indent: level variable printWithClosureAnalysisOn: aStream indent: level. aStream nextPutAll: ' := '. value printWithClosureAnalysisOn: aStream indent: level + 2! ! !AssignmentNode methodsFor: 'printing' stamp: 'eem 6/2/2008 11:47'! printWithClosureAnalysisOn: aStream indent: level precedence: p aStream nextPut: $(. self printWithClosureAnalysisOn: aStream indent: level. aStream nextPut: $)! ! !AssignmentNode methodsFor: 'testing' stamp: 'eem 6/16/2008 09:37'! isAssignmentNode ^true! ! !AssignmentNode methodsFor: 'visiting' stamp: 'eem 9/10/2008 15:12'! accept: aVisitor aVisitor visitAssignmentNode: self! ! LookupKey subclass: #Association instanceVariableNames: 'value' classVariableNames: '' poolDictionaries: '' category: 'Collections-Support'! !Association commentStamp: '' prior: 0! I represent a pair of associated objects--a key and a value. My instances can serve as entries in a dictionary.! !Association methodsFor: '*services-base-preferences' stamp: 'rr 3/21/2006 11:58'! serviceUpdate self key service perform: self value! ! !Association methodsFor: 'accessing' stamp: 'John M McIntosh 3/2/2009 21:15'! isSpecialWriteBinding "Return true if this variable binding is write protected, e.g., should not be accessed primitively but rather by sending #value: messages" ^false! ! !Association methodsFor: 'accessing'! key: aKey value: anObject "Store the arguments as the variables of the receiver." key := aKey. value := anObject! ! !Association methodsFor: 'accessing'! value "Answer the value of the receiver." ^value! ! !Association methodsFor: 'accessing'! value: anObject "Store the argument, anObject, as the value of the receiver." value := anObject! ! !Association methodsFor: 'comparing' stamp: 'md 1/27/2004 17:27'! = anAssociation ^ super = anAssociation and: [value = anAssociation value]! ! !Association methodsFor: 'filter streaming' stamp: 'MPW 1/1/1901 20:53'! byteEncode: aStream aStream writeAssocation:self.! ! !Association methodsFor: 'objects from disk' stamp: 'tk 10/3/2000 13:03'! objectForDataStream: refStrm | dp | "I am about to be written on an object file. If I am a known global, write a proxy that will hook up with the same resource in the destination system." ^ (Smalltalk associationAt: key ifAbsent: [nil]) == self ifTrue: [dp := DiskProxy global: #Smalltalk selector: #associationOrUndeclaredAt: args: (Array with: key). refStrm replace: self with: dp. dp] ifFalse: [self]! ! !Association methodsFor: 'printing'! printOn: aStream super printOn: aStream. aStream nextPutAll: '->'. value printOn: aStream! ! !Association methodsFor: 'printing' stamp: 'MPW 1/4/1901 08:31'! propertyListOn: aStream aStream write:key; print:'='; write:value. ! ! !Association methodsFor: 'printing'! storeOn: aStream "Store in the format (key->value)" aStream nextPut: $(. key storeOn: aStream. aStream nextPutAll: '->'. value storeOn: aStream. aStream nextPut: $)! ! !Association methodsFor: 'self evaluating' stamp: 'sd 7/31/2005 21:44'! isSelfEvaluating ^ self class == Association! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Association class instanceVariableNames: ''! !Association class methodsFor: 'instance creation'! key: newKey value: newValue "Answer an instance of me with the arguments as the key and value of the association." ^(super key: newKey) value: newValue! ! ClassTestCase subclass: #AssociationTest instanceVariableNames: 'a b' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Support'! !AssociationTest methodsFor: 'setup' stamp: 'zz 12/5/2005 18:33'! setUp a := 1 -> 'one'. b := 1 -> 'een'.! ! !AssociationTest methodsFor: 'tests' stamp: 'ab 12/29/2008 07:59'! testComparison self assert: ((#a -> 'foo') < (#b -> 'zork'))! ! !AssociationTest methodsFor: 'tests' stamp: 'md 3/8/2004 16:37'! testEquality self assert: (a key = b key); deny: (a value = b value); deny: (a = b) ! ! !AssociationTest methodsFor: 'tests' stamp: 'al 10/13/2008 20:32'! testHash self assert: (a hash = a copy hash); assert: (a hash = b hash)! ! !AssociationTest methodsFor: 'tests' stamp: 'ab 12/29/2008 08:01'! testIsSelfEvaluating self assert: (a isSelfEvaluating). self assert: (a printString = '1->''one''') ! ! Object subclass: #AsyncFile instanceVariableNames: 'name writeable semaphore fileHandle' classVariableNames: 'Busy ErrorCode' poolDictionaries: '' category: 'Files-Kernel'! !AsyncFile commentStamp: '' prior: 0! An asynchronous file allows simple file read and write operations to be performed in parallel with other processing. This is useful in multimedia applications that need to stream large amounts of sound or image data from or to a file while doing other work. ! !AsyncFile methodsFor: 'as yet unclassified' stamp: 'stephaneducasse 2/4/2006 20:31'! close fileHandle ifNil: [^ self]. "already closed" self primClose: fileHandle. Smalltalk unregisterExternalObject: semaphore. semaphore := nil. fileHandle := nil. ! ! !AsyncFile methodsFor: 'as yet unclassified' stamp: 'di 7/6/1998 10:58'! fileHandle ^ fileHandle! ! !AsyncFile methodsFor: 'as yet unclassified' stamp: 'ar 6/3/2007 22:13'! open: fullFileName forWrite: aBoolean "Open a file of the given name, and return a handle for that file. Answer the receiver if the primitive succeeds, nil otherwise. If openForWrite is true, then: if there is no existing file with this name, then create one else open the existing file in read-write mode otherwise: if there is an existing file with this name, then open it read-only else answer nil." "Note: if an exisiting file is opened for writing, it is NOT truncated. If truncation is desired, the file should be deleted before being opened as an asynchronous file." "Note: On some platforms (e.g., Mac), a file can only have one writer at a time." | semaIndex | name := fullFileName. writeable := aBoolean. semaphore := Semaphore new. semaIndex := Smalltalk registerExternalObject: semaphore. fileHandle := self primOpen: name asVmPathName forWrite: writeable semaIndex: semaIndex. fileHandle ifNil: [ Smalltalk unregisterExternalObject: semaphore. semaphore := nil. ^ nil]. ! ! !AsyncFile methodsFor: 'as yet unclassified' stamp: 'nice 4/16/2009 10:02'! readByteCount: byteCount fromFilePosition: fPosition onCompletionDo: aBlock "Start a read operation to read byteCount's from the given position in this file. and fork a process to await its completion. When the operation completes, evaluate the given block. Note that, since the completion block may run asynchronous, the client may need to use a SharedQueue or a semaphore for synchronization." | buffer | buffer := String new: byteCount. self primReadStart: fileHandle fPosition: fPosition count: byteCount. "here's the process that awaits the results:" [| n | [ semaphore wait. n := self primReadResult: fileHandle intoBuffer: buffer at: 1 count: byteCount. n = Busy. ] whileTrue. "loop while busy in case the semaphore had excess signals" n = ErrorCode ifTrue: [^ self error: 'asynchronous read operation failed']. aBlock value: buffer. ] forkAt: Processor userInterruptPriority. ! ! !AsyncFile methodsFor: 'as yet unclassified' stamp: 'stephaneducasse 2/4/2006 20:31'! test: byteCount fileName: fileName "AsyncFile new test: 10000 fileName: 'testData'" | buf1 buf2 bytesWritten bytesRead | buf1 := String new: byteCount withAll: $x. buf2 := String new: byteCount. self open: ( FileDirectory default fullNameFor: fileName) forWrite: true. self primWriteStart: fileHandle fPosition: 0 fromBuffer: buf1 at: 1 count: byteCount. semaphore wait. bytesWritten := self primWriteResult: fileHandle. self close. self open: ( FileDirectory default fullNameFor: fileName) forWrite: false. self primReadStart: fileHandle fPosition: 0 count: byteCount. semaphore wait. bytesRead := self primReadResult: fileHandle intoBuffer: buf2 at: 1 count: byteCount. self close. buf1 = buf2 ifFalse: [self error: 'buffers do not match']. ^ 'wrote ', bytesWritten printString, ' bytes; ', 'read ', bytesRead printString, ' bytes' ! ! !AsyncFile methodsFor: 'as yet unclassified' stamp: 'di 7/6/1998 10:58'! waitForCompletion semaphore wait! ! !AsyncFile methodsFor: 'as yet unclassified' stamp: 'nice 4/16/2009 10:02'! writeBuffer: buffer atFilePosition: fPosition onCompletionDo: aBlock "Start an operation to write the contents of the buffer at given position in this file, and fork a process to await its completion. When the write completes, evaluate the given block. Note that, since the completion block runs asynchronously, the client may need to use a SharedQueue or a semaphore for synchronization." self primWriteStart: fileHandle fPosition: fPosition fromBuffer: buffer at: 1 count: buffer size. "here's the process that awaits the results:" [| n | [ semaphore wait. n := self primWriteResult: fileHandle. n = Busy. ] whileTrue. "loop while busy in case the semaphore had excess signals" n = ErrorCode ifTrue: [^ self error: 'asynchronous write operation failed']. n = buffer size ifFalse: [^ self error: 'did not write the entire buffer']. aBlock value. ] forkAt: Processor userInterruptPriority. ! ! !AsyncFile methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'! primClose: fHandle "Close this file. Do nothing if primitive fails." ! ! !AsyncFile methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'! primOpen: fileName forWrite: openForWrite semaIndex: semaIndex "Open a file of the given name, and return a handle for that file. Answer the receiver if the primitive succeeds, nil otherwise." ^ nil ! ! !AsyncFile methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'! primReadResult: fHandle intoBuffer: buffer at: startIndex count: count "Copy the result of the last read operation into the given buffer starting at the given index. The buffer may be any sort of bytes or words object, excluding CompiledMethods. Answer the number of bytes read. A negative result means: -1 the last operation is still in progress -2 the last operation encountered an error" self primitiveFailed ! ! !AsyncFile methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'! primReadStart: fHandle fPosition: fPosition count: count "Start a read operation of count bytes starting at the given offset in the given file." self error: 'READ THE COMMENT FOR THIS METHOD.' "NOTE: This method will fail if there is insufficient C heap to allocate an internal buffer of the required size (the value of count). If you are trying to read a movie file, then the buffer size will be height*width*2 bytes. Each Squeak image retains a value to be used for this allocation, and it it initially set to 0. If you are wish to play a 640x480 movie, you need room for a buffer of 640*480*2 = 614400 bytes. You should execute the following... Smalltalk extraVMMemory 2555000. Then save-and-quit, restart, and try to open the movie file again. If you are using Async files in another way, find out the value of count when this failure occurs (call it NNNN), and instead of the above, execute... Smalltalk extraVMMemory: Smalltalk extraVMMemory + NNNN then save-and-quit, restart, and try again. " ! ! !AsyncFile methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'! primWriteResult: fHandle "Answer the number of bytes written. A negative result means: -1 the last operation is still in progress -2 the last operation encountered an error" self primitiveFailed ! ! !AsyncFile methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'! primWriteStart: fHandle fPosition: fPosition fromBuffer: buffer at: startIndex count: count "Start a write operation of count bytes starting at the given index in the given buffer. The buffer may be any sort of bytes or words object, excluding CompiledMethods. The contents of the buffer are copied into an internal buffer immediately, so the buffer can be reused after the write operation has been started. Fail if there is insufficient C heap to allocate an internal buffer of the requested size." writeable ifFalse: [^ self error: 'attempt to write a file opened read-only']. self primitiveFailed ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AsyncFile class instanceVariableNames: ''! !AsyncFile class methodsFor: 'initialization' stamp: 'bootstrap 5/31/2006 20:45'! initialize "AsyncFile initialize" "Possible abnormal I/O completion results." Busy := -1. ErrorCode := -2. ! ! Object subclass: #Author instanceVariableNames: 'fullName' classVariableNames: '' poolDictionaries: '' category: 'System-Support'! !Author commentStamp: 'MiguelCoba 7/25/2009 01:09' prior: 0! I am responsible for the full name used to identify the current code author.! !Author methodsFor: 'accessing' stamp: 'MiguelCoba 7/25/2009 02:41'! fullName "Answer the full name to be used to identify the current code author." [fullName isEmptyOrNil ] whileTrue: [self requestFullName]. ^ fullName! ! !Author methodsFor: 'accessing' stamp: 'MiguelCoba 7/25/2009 00:55'! fullName: aString fullName := aString.! ! !Author methodsFor: 'accessing' stamp: 'MiguelCoba 7/25/2009 00:58'! fullNamePerSe "Answer the currently-prevailing author full name, such as it is, empty or not" ^ fullName! ! !Author methodsFor: 'initialization' stamp: 'MiguelCoba 7/25/2009 03:07'! initialize super initialize. fullName := ''.! ! !Author methodsFor: 'ui-requests' stamp: 'MiguelCoba 9/16/2009 12:10'! messagePrompt ^ 'Please type your full name. It will be used to sign the changes you make to the image. Avoid spaces, accents, dashes, underscore and similar characters. Vincent van Gogh -> VincentVanGogh Miguel Cobá -> MiguelCoba Göran Krampe -> GoranKrampe Göran Krampe -> GoeranKrampe Stéphane DUCASSE -> StephaneDucasse Yoshiki Oshima -> YoshikiOshima '! ! !Author methodsFor: 'ui-requests' stamp: 'MiguelCoba 7/25/2009 01:54'! requestFullName | initialAnswer | initialAnswer := fullName isEmptyOrNil ifTrue: ['FirstnameLastname' translated] ifFalse: [fullName]. fullName := UIManager default request: self messagePrompt initialAnswer: initialAnswer! ! !Author methodsFor: 'testing-support' stamp: 'oscar.nierstrasz 10/18/2009 18:27'! useAuthor: aString during: aBlock | previous | previous := fullName. fullName := aString. ^ aBlock ensure: [ fullName := previous ]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Author class instanceVariableNames: 'uniqueInstance'! !Author class methodsFor: 'convenience' stamp: 'MiguelCoba 7/25/2009 01:58'! fullName ^ Author uniqueInstance fullName! ! !Author class methodsFor: 'convenience' stamp: 'MiguelCoba 7/25/2009 01:58'! fullName: aString ^ Author uniqueInstance fullName: aString! ! !Author class methodsFor: 'convenience' stamp: 'MiguelCoba 7/25/2009 01:58'! fullNamePerSe ^ Author uniqueInstance fullNamePerSe! ! !Author class methodsFor: 'convenience' stamp: 'MiguelCoba 7/25/2009 01:10'! requestFullName ^ Author uniqueInstance requestFullName! ! !Author class methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 06:24'! initials self deprecated: 'Use ''Author fullName'' instead.'. ^ Author uniqueInstance fullName! ! !Author class methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 06:25'! initials: aString self deprecated: 'Use ''Author fullName:'' instead.'. ^ Author uniqueInstance fullName: aString! ! !Author class methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 06:25'! initialsPerSe self deprecated: 'Use ''Author fullNamePerSe'' instead.'. ^ Author uniqueInstance fullNamePerSe! ! !Author class methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 06:26'! requestInitials self deprecated: 'Use ''Author requestFullName'' instead.'. ^ Author uniqueInstance requestFullName! ! !Author class methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 06:27'! requestName self deprecated: 'Use ''Author requestFullName'' instead.'. ^ Author uniqueInstance requestFullName! ! !Author class methodsFor: 'instance creation' stamp: 'on 5/10/2008 13:05'! new self error: 'Author is a singleton -- send uniqueInstance instead'! ! !Author class methodsFor: 'instance creation' stamp: 'on 5/10/2008 13:10'! reset ^ uniqueInstance := nil! ! !Author class methodsFor: 'instance creation' stamp: 'on 5/10/2008 13:09'! uniqueInstance ^ uniqueInstance ifNil: [ uniqueInstance := super new ]! ! !Author class methodsFor: 'instance creation' stamp: 'on 5/10/2008 13:27'! uniqueInstance: anInstance "Needed by AuthorTest to restore saved instance" ^ uniqueInstance := anInstance! ! !Author class methodsFor: 'testing-support' stamp: 'oscar.nierstrasz 10/18/2009 18:31'! useAuthor: aString during: aBlock ^ self uniqueInstance useAuthor: aString during: aBlock! ! TestCase subclass: #AuthorTest instanceVariableNames: 'author' classVariableNames: '' poolDictionaries: '' category: 'Tests-System'! !AuthorTest methodsFor: 'running' stamp: 'on 5/10/2008 13:31'! setUp author := Author uniqueInstance. Author reset.! ! !AuthorTest methodsFor: 'running' stamp: 'on 5/10/2008 13:21'! tearDown Author uniqueInstance: author! ! !AuthorTest methodsFor: 'running' stamp: 'on 5/10/2008 14:48'! testDeprecation | savedPref | savedPref := Preferences showDeprecationWarnings. Preferences setPreference: #showDeprecationWarnings toValue: true. self should: [ Utilities authorInitials ] raise: Warning. self should: [ Utilities authorInitialsPerSe ] raise: Warning. self should: [ Utilities setAuthorInitials ] raise: Warning. self should: [ Utilities setAuthorInitials: 'ak' ] raise: Warning. self should: [ Utilities authorName ] raise: Warning. self should: [ Utilities authorName: 'alan' ] raise: Warning. self should: [ Utilities authorNamePerSe ] raise: Warning. self should: [ Utilities setAuthorName ] raise: Warning. Preferences setPreference: #showDeprecationWarnings toValue: savedPref. ! ! !AuthorTest methodsFor: 'running' stamp: 'MiguelCoba 7/25/2009 02:45'! testInitiallyEmpty self assert: (Author uniqueInstance fullNamePerSe isEmpty). ! ! !AuthorTest methodsFor: 'running' stamp: 'on 5/10/2008 13:35'! testUniqueness self should: [ Author new ] raise: Error.! ! Object subclass: #Authorizer instanceVariableNames: 'users realm' classVariableNames: '' poolDictionaries: '' category: 'Network-Url'! !Authorizer commentStamp: '' prior: 0! The Authorizer does user authorization checking. Each instance of authorizer keeps track of the realm that it is authorizing for, and the table of authorized users. An authorizer can be asked to return the user name/symbol associated with a userID (which concatenates the username and password from the HTTP request) with the user: method. ! !Authorizer methodsFor: 'authentication' stamp: 'PeterHugossonMiller 9/3/2009 00:12'! encode: nameString password: pwdString "Encode per RFC1421 of the username:password combination." | clear code clearSize idx map | clear := (nameString, ':', pwdString) asByteArray. clearSize := clear size. [ clear size \\ 3 ~= 0 ] whileTrue: [ clear := clear, #(0) ]. idx := 1. map := 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/'. code := String new writeStream. [ idx < clear size ] whileTrue: [ code nextPut: (map at: (clear at: idx) // 4 + 1); nextPut: (map at: (clear at: idx) \\ 4 * 16 + ((clear at: idx + 1) // 16) + 1); nextPut: (map at: (clear at: idx + 1) \\ 16 * 4 + ((clear at: idx + 2) // 64) + 1); nextPut: (map at: (clear at: idx + 2) \\ 64 + 1). idx := idx + 3 ]. code := code contents. idx := code size. clear size - clearSize timesRepeat: [ code at: idx put: $=. idx := idx - 1]. ^code! ! !Authorizer methodsFor: 'authentication' stamp: 'mjg 11/3/97 12:31'! mapFrom: aKey to: aPerson "Establish a mapping from a RFC 1421 key to a user." users isNil ifTrue: [ users := Dictionary new ]. aPerson isNil ifTrue: [ users removeKey: aKey ] ifFalse: [ users removeKey: (users keyAtValue: aPerson ifAbsent: []) ifAbsent: []. users at: aKey put: aPerson ] ! ! !Authorizer methodsFor: 'authentication' stamp: 'tk 5/21/1998 16:32'! mapName: nameString password: pwdString to: aPerson "Insert/remove the encoding per RFC1421 of the username:password combination into/from the UserMap. DO NOT call this directly, use mapName:password:to: in your ServerAction class. Only it knows how to record the change on the disk!!" self mapFrom: (self encode: nameString password: pwdString) to: aPerson ! ! !Authorizer methodsFor: 'authentication' stamp: 'ar 8/17/2001 18:19'! user: userId "Return the requesting user." ^users at: userId ifAbsent: [ self error: (self class unauthorizedFor: realm) ]! ! !Authorizer methodsFor: 'realms' stamp: 'mjg 11/3/97 12:33'! realm ^realm! ! !Authorizer methodsFor: 'realms' stamp: 'mjg 11/3/97 12:33'! realm: aString realm := aString ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Authorizer class instanceVariableNames: ''! !Authorizer class methodsFor: 'as yet unclassified' stamp: 'adrian_lienhard 7/18/2009 15:52'! unauthorizedFor: realm ^'HTTP/1.0 401 Unauthorized', self crlf, 'WWW-Authenticate: Basic realm="Pharo/',realm,'"', String crlfcrlf, 'Unauthorized

Unauthorized for ',realm, '

' ! ! Object subclass: #AutoStart instanceVariableNames: 'parameters' classVariableNames: 'Active InstalledLaunchers' poolDictionaries: '' category: 'System-Support'! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AutoStart class instanceVariableNames: ''! !AutoStart class methodsFor: 'accessing' stamp: 'mir 7/28/1999 17:47'! addLauncher: launcher self installedLaunchers add: launcher! ! !AutoStart class methodsFor: 'accessing'! addLauncherFirst: launcher self installedLaunchers addFirst: launcher! ! !AutoStart class methodsFor: 'accessing' stamp: 'mir 7/28/1999 17:47'! removeLauncher: launcher self installedLaunchers remove: launcher ifAbsent: []! ! !AutoStart class methodsFor: 'initialization' stamp: 'mir 7/28/1999 17:44'! deinstall "AutoStart deinstall" Smalltalk removeFromStartUpList: AutoStart. InstalledLaunchers := nil! ! !AutoStart class methodsFor: 'initialization' stamp: 'mir 9/30/2004 15:05'! initialize "AutoStart initialize" "Order: ExternalSettings, SecurityManager, AutoStart" Smalltalk addToStartUpList: AutoStart after: SecurityManager. Smalltalk addToShutDownList: AutoStart after: SecurityManager.! ! !AutoStart class methodsFor: 'initialization' stamp: 'mir 9/30/2004 15:06'! shutDown: quitting self active: false! ! !AutoStart class methodsFor: 'initialization' stamp: 'stephane.ducasse 4/13/2009 21:14'! startUp: resuming "The image is either being newly started (resuming is true), or it's just been snapshotted. If this has just been a snapshot, skip all the startup stuff." | startupParameters launchers | self active ifTrue: [^self]. self active: true. resuming ifFalse: [^self]. HTTPClient determineIfRunningInBrowser. startupParameters := AbstractLauncher extractParameters. (startupParameters includesKey: 'apiSupported' asUppercase ) ifTrue: [ HTTPClient browserSupportsAPI: ((startupParameters at: 'apiSupported' asUppercase) asUppercase = 'TRUE'). HTTPClient isRunningInBrowser ifFalse: [HTTPClient isRunningInBrowser: true]]. self checkForUpdates ifTrue: [^self]. self checkForPluginUpdate. launchers := self installedLaunchers collect: [:launcher | launcher new]. launchers do: [:launcher | launcher parameters: startupParameters]. launchers do: [:launcher | Smalltalk at: #WorldState ifPresent: [ :ws | ws addDeferredUIMessage: [launcher startUp]]]! ! !AutoStart class methodsFor: 'updating' stamp: 'sd 3/20/2008 22:26'! checkForPluginUpdate | pluginVersion updateURL | World ifNotNil: [ World install. ActiveHand position: 100@100]. HTTPClient isRunningInBrowser ifFalse: [^false]. pluginVersion := AbstractLauncher extractParameters at: (SmalltalkImage current platformName copyWithout: Character space) asUppercase ifAbsent: [^false]. updateURL := AbstractLauncher extractParameters at: 'UPDATE_URL' ifAbsent: [^false]. ^SystemVersion check: pluginVersion andRequestPluginUpdate: updateURL! ! !AutoStart class methodsFor: 'updating' stamp: 'sd 3/20/2008 22:26'! checkForUpdates | availableUpdate updateServer | World ifNotNil: [ World install. ActiveHand position: 100@100]. HTTPClient isRunningInBrowser ifFalse: [^self processUpdates]. availableUpdate := (AbstractLauncher extractParameters at: 'UPDATE' ifAbsent: [''] ) asInteger. availableUpdate ifNil: [^false]. updateServer := AbstractLauncher extractParameters at: 'UPDATESERVER' ifAbsent: [AbstractLauncher extractParameters at: 'UPDATE_SERVER' ifAbsent: ['Squeakland']]. Utilities setUpdateServer: updateServer. ^SystemVersion checkAndApplyUpdates: availableUpdate! ! !AutoStart class methodsFor: 'updating' stamp: 'CdG 10/17/2005 19:34'! processUpdates "Process update files from a well-known update server. This method is called at system startup time, Only if the preference #updateFromServerAtStartup is true is the actual update processing undertaken automatically" | choice | (Preferences valueOfFlag: #updateFromServerAtStartup) ifTrue: [choice := UIManager default chooseFrom: #('Yes, Update' 'No, Not now' 'Don''t ask again') title: 'Shall I look for new code\updates on the server?' withCRs. choice = 1 ifTrue: [ Utilities updateFromServer]. choice = 3 ifTrue: [ Preferences setPreference: #updateFromServerAtStartup toValue: false. self inform: 'Remember to save you image to make this setting permant.']]. ^false! ! !AutoStart class methodsFor: 'private' stamp: 'mir 9/7/2004 13:34'! active ^ Active == true! ! !AutoStart class methodsFor: 'private' stamp: 'mir 9/7/2004 13:36'! active: aBoolean Active := aBoolean! ! !AutoStart class methodsFor: 'private' stamp: 'mir 7/28/1999 17:43'! installedLaunchers InstalledLaunchers ifNil: [ InstalledLaunchers := OrderedCollection new]. ^InstalledLaunchers! ! Object subclass: #BDFFontReader instanceVariableNames: 'file properties' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Fonts'! !BDFFontReader commentStamp: '' prior: 0! I am a conversion utility for reading X11 Bitmap Distribution Format fonts. My code is derived from the multilingual Squeak changeset written by OHSHIMA Yoshiki (ohshima@is.titech.ac.jp), although all support for fonts with more than 256 glyphs has been ripped out. See http://www.is.titech.ac.jp/~ohshima/squeak/squeak-multilingual-e.html . My class methods contain tools for fetching BDF source files from a well-known archive site, batch conversion to Squeak's .sf2 format, and installation of these fonts as TextStyles. Also, the legal notices for the standard 75dpi fonts I process this way are included as "x11FontLegalNotices'.! !BDFFontReader methodsFor: 'initialize' stamp: 'alain.plantec 5/28/2009 09:41'! initialize super initialize. properties := Dictionary new.! ! !BDFFontReader methodsFor: 'initialize' stamp: 'pmm 7/4/2009 12:05'! openFileNamed: fileName file := (MultiByteFileStream readOnlyFileNamed: fileName) ascii; wantsLineEndConversion: true; yourself! ! !BDFFontReader methodsFor: 'reading' stamp: 'nop 1/18/2000 19:45'! errorFileFormat self error: 'malformed bdf format'! ! !BDFFontReader methodsFor: 'reading' stamp: 'nop 1/18/2000 19:46'! errorUnsupported self error: 'unsupported bdf'! ! !BDFFontReader methodsFor: 'reading' stamp: 'ar 10/25/2005 00:35'! getLine ^file upTo: Character cr.! ! !BDFFontReader methodsFor: 'reading' stamp: 'damiencassou 5/30/2008 14:51'! read | xTable strikeWidth glyphs ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx array width blt lastAscii pointSize ret stream | form := encoding := bbx := nil. self readAttributes. height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2). ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first. descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first. pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10. maxWidth := 0. minAscii := 9999. strikeWidth := 0. maxAscii := 0. charsNum := Integer readFromString: (properties at: #CHARS) first. chars := Set new: charsNum. 1 to: charsNum do: [ :i | array := self readOneCharacter. stream := array readStream. form := stream next. encoding := stream next. bbx := stream next. form ifNotNil: [ width := bbx at: 1. maxWidth := maxWidth max: width. minAscii := minAscii min: encoding. maxAscii := maxAscii max: encoding. strikeWidth := strikeWidth + width. chars add: array ] ]. chars := chars asSortedCollection: [ :x :y | (x at: 2) <= (y at: 2) ]. charsNum := chars size. "undefined encodings make this different" charsNum > 256 ifTrue: [ "it should be 94x94 charset, and should be fixed width font" strikeWidth := 94 * 94 * maxWidth. maxAscii := 94 * 94. minAscii := 0. xTable := XTableForFixedFont new. xTable maxAscii: 94 * 94. xTable width: maxWidth ] ifFalse: [ xTable := (Array new: 258) atAllPut: 0 ]. glyphs := Form extent: strikeWidth @ height. blt := BitBlt toForm: glyphs. lastAscii := 0. charsNum > 256 ifTrue: [ 1 to: charsNum do: [ :i | stream := (chars at: i) readStream. form := stream next. encoding := stream next. bbx := stream next. encoding := (encoding // 256 - 33) * 94 + (encoding \\ 256 - 33). blt copy: ((encoding * maxWidth) @ 0 extent: maxWidth @ height) from: 0 @ 0 in: form ] ] ifFalse: [ 1 to: charsNum do: [ :i | stream := (chars at: i) readStream. form := stream next. encoding := stream next. bbx := stream next. lastAscii + 1 to: encoding - 1 do: [ :a | xTable at: a + 2 put: (xTable at: a + 1) ]. blt copy: ((xTable at: encoding + 1) @ (ascent - (bbx at: 2) - (bbx at: 4)) extent: (bbx at: 1) @ (bbx at: 2)) from: 0 @ 0 in: form. xTable at: encoding + 2 put: (xTable at: encoding + 1) + (bbx at: 1). lastAscii := encoding ] ]. ret := Array new: 8. ret at: 1 put: xTable. ret at: 2 put: glyphs. ret at: 3 put: minAscii. ret at: 4 put: maxAscii. ret at: 5 put: maxWidth. ret at: 6 put: ascent. ret at: 7 put: descent. ret at: 8 put: pointSize. ^ ret " ^{xTable. glyphs. minAscii. maxAscii. maxWidth. ascent. descent. pointSize}"! ! !BDFFontReader methodsFor: 'reading' stamp: 'lr 7/4/2009 10:42'! readAttributes "I don't handle double-quotes correctly, but it works" | str a | file reset. [ file atEnd ] whileFalse: [ str := self getLine. (str beginsWith: 'STARTCHAR') ifTrue: [ file skip: 0 - str size - 1. ^ self ]. a := str substrings. properties at: a first asSymbol put: a allButFirst ]. self error: 'file seems corrupted'! ! !BDFFontReader methodsFor: 'reading' stamp: 'damiencassou 5/30/2008 14:51'! readChars | strikeWidth ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx array width pointSize stream | form := encoding := bbx := nil. self readAttributes. height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2). ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first. descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first. pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10. maxWidth := 0. minAscii := 9999. strikeWidth := 0. maxAscii := 0. charsNum := Integer readFromString: (properties at: #CHARS) first. chars := Set new: charsNum. 1 to: charsNum do: [ :i | array := self readOneCharacter. stream := array readStream. form := stream next. encoding := stream next. bbx := stream next. form ifNotNil: [ width := bbx at: 1. maxWidth := maxWidth max: width. minAscii := minAscii min: encoding. maxAscii := maxAscii max: encoding. strikeWidth := strikeWidth + width. chars add: array ] ]. chars := chars asSortedCollection: [ :x :y | (x at: 2) <= (y at: 2) ]. ^ chars! ! !BDFFontReader methodsFor: 'reading' stamp: 'lr 7/4/2009 10:42'! readOneCharacter | str a encoding bbx form bits hi low pos | ((str := self getLine) beginsWith: 'ENDFONT') ifTrue: [ ^ { nil. nil. nil } ]. (str beginsWith: 'STARTCHAR') ifFalse: [ self errorFileFormat ]. ((str := self getLine) beginsWith: 'ENCODING') ifFalse: [ self errorFileFormat ]. encoding := Integer readFromString: str substrings second. (self getLine beginsWith: 'SWIDTH') ifFalse: [ self errorFileFormat ]. (self getLine beginsWith: 'DWIDTH') ifFalse: [ self errorFileFormat ]. ((str := self getLine) beginsWith: 'BBX') ifFalse: [ self errorFileFormat ]. a := str substrings. bbx := (2 to: 5) collect: [ :i | Integer readFromString: (a at: i) ]. ((str := self getLine) beginsWith: 'ATTRIBUTES') ifTrue: [ str := self getLine ]. (str beginsWith: 'BITMAP') ifFalse: [ self errorFileFormat ]. form := Form extent: (bbx at: 1) @ (bbx at: 2). bits := form bits. pos := 0. 1 to: (bbx at: 2) do: [ :t | 1 to: ((bbx at: 1) - 1) // 8 + 1 do: [ :i | hi := ('0123456789ABCDEF' indexOf: file next asUppercase) - 1 bitShift: 4. low := ('0123456789ABCDEF' indexOf: file next asUppercase) - 1. bits byteAt: pos + i put: hi + low ]. file next ~= Character cr ifTrue: [ self errorFileFormat ]. pos := pos + (((bbx at: 1) // 32 + 1) * 4) ]. (self getLine beginsWith: 'ENDCHAR') ifFalse: [ self errorFileFormat ]. encoding < 0 ifTrue: [ ^ { nil. nil. nil } ]. ^ { form. encoding. bbx }! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BDFFontReader class instanceVariableNames: ''! !BDFFontReader class methodsFor: 'documentation' stamp: 'nop 2/11/2001 00:22'! gettingAndInstallingTheFonts "Download the 1.3M of BDF font source files from x.org: BDFFontReader downloadFonts. Convert them to .sf2 StrikeFont files: BDFFontReader convertX11FontsToStrike2. Install them into the system as TextStyles: BDFFontReader installX11Fonts. Read the legal notices in 'BDFFontReader x11FontLegalNotices' before redistributing images containing these fonts."! ! !BDFFontReader class methodsFor: 'documentation' stamp: 'nop 1/23/2000 18:30'! x11FontLegalNotices ^ 'The X11 BDF fonts contain copyright and license information as comments in the font source code. For the font family files "cour" (Courier), "helv" (Helvetica), "ncen" (New Century Schoolbook), and "tim" (Times Roman) the notice reads: COMMENT Copyright 1984-1989, 1994 Adobe Systems Incorporated. COMMENT Copyright 1988, 1994 Digital Equipment Corporation. COMMENT COMMENT Adobe is a trademark of Adobe Systems Incorporated which may be COMMENT registered in certain jurisdictions. COMMENT Permission to use these trademarks is hereby granted only in COMMENT association with the images described in this file. COMMENT COMMENT Permission to use, copy, modify, distribute and sell this software COMMENT and its documentation for any purpose and without fee is hereby COMMENT granted, provided that the above copyright notices appear in all COMMENT copies and that both those copyright notices and this permission COMMENT notice appear in supporting documentation, and that the names of COMMENT Adobe Systems and Digital Equipment Corporation not be used in COMMENT advertising or publicity pertaining to distribution of the software COMMENT without specific, written prior permission. Adobe Systems and COMMENT Digital Equipment Corporation make no representations about the COMMENT suitability of this software for any purpose. It is provided "as COMMENT is" without express or implied warranty. For the font family files "char" (Charter), the notice reads: COMMENT Copyright 1988 Bitstream, Inc., Cambridge, Massachusetts, USA COMMENT Bitstream and Charter are registered trademarks of Bitstream, Inc. COMMENT COMMENT The names "Bitstream" and "Charter" are registered trademarks of COMMENT Bitstream, Inc. Permission to use these trademarks is hereby COMMENT granted only in association with the images described in this file. COMMENT COMMENT Permission to use, copy, modify, and distribute this software and COMMENT its documentation for any purpose and without fee is hereby COMMENT granted, provided that the above copyright notice appear in all COMMENT copies and that both that copyright notice and this permission COMMENT notice appear in supporting documentation, and that the name of COMMENT Bitstream not be used in advertising or publicity pertaining to COMMENT distribution of the software without specific, written prior COMMENT permission. Bitstream makes no representations about the COMMENT suitability of this software for any purpose. It is provided "as COMMENT is" without express or implied warranty. COMMENT COMMENT BITSTREAM DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS SOFTWARE, COMMENT INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS, IN COMMENT NO EVENT SHALL BITSTREAM BE LIABLE FOR ANY SPECIAL, INDIRECT OR COMMENT CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS COMMENT OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, COMMENT NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN COMMENT CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. For the font family files "lu" (Lucida), "lub" (Lucida Bright), and "lut" (Lucida Typewriter), the notice reads: COMMENT (c) Copyright Bigelow & Holmes 1986, 1985. Lucida is a registered COMMENT trademark of Bigelow & Holmes. See LEGAL NOTICE file for terms COMMENT of the license. The LEGAL NOTICE contains: This is the LEGAL NOTICE pertaining to the Lucida fonts from Bigelow & Holmes: NOTICE TO USER: The source code, including the glyphs or icons forming a par of the OPEN LOOK TM Graphic User Interface, on this tape and in these files is copyrighted under U.S. and international laws. Sun Microsystems, Inc. of Mountain View, California owns the copyright and has design patents pending on many of the icons. AT&T is the owner of the OPEN LOOK trademark associated with the materials on this tape. Users and possessors of this source code are hereby granted a nonexclusive, royalty-free copyright and design patent license to use this code in individual and commercial software. A royalty-free, nonexclusive trademark license to refer to the code and output as "OPEN LOOK" compatible is available from AT&T if, and only if, the appearance of the icons or glyphs is not changed in any manner except as absolutely necessary to accommodate the standard resolution of the screen or other output device, the code and output is not changed except as authorized herein, and the code and output is validated by AT&T. Bigelow & Holmes is the owner of the Lucida (R) trademark for the fonts and bit-mapped images associated with the materials on this tape. Users are granted a royalty-free, nonexclusive license to use the trademark only to identify the fonts and bit-mapped images if, and only if, the fonts and bit-mapped images are not modified in any way by the user. Any use of this source code must include, in the user documentation and internal comments to the code, notices to the end user as follows: (c) Copyright 1989 Sun Microsystems, Inc. Sun design patents pending in the U.S. and foreign countries. OPEN LOOK is a trademark of AT&T. Used by written permission of the owners. (c) Copyright Bigelow & Holmes 1986, 1985. Lucida is a registered trademark of Bigelow & Holmes. Permission to use the Lucida trademark is hereby granted only in association with the images and fonts described in this file. SUN MICROSYSTEMS, INC., AT&T, AND BIGELOW & HOLMES MAKE NO REPRESENTATIONS ABOUT THE SUITABILITY OF THIS SOURCE CODE FOR ANY PURPOSE. IT IS PROVIDED "AS IS" WITHOUT EXPRESS OR IMPLIED WARRANTY OF ANY KIND. SUN MICROSYSTEMS, INC., AT&T AND BIGELOW & HOLMES, SEVERALLY AND INDIVIDUALLY, DISCLAIM ALL WARRANTIES WITH REGARD TO THIS SOURCE CODE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. IN NO EVENT SHALL SUN MICROSYSTEMS, INC., AT&T OR BIGELOW & HOLMES BE LIABLE FOR ANY SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL DAMAGES, OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOURCE CODE. '. ! ! !BDFFontReader class methodsFor: 'file creation' stamp: 'nice 4/16/2009 10:04'! convertFilesNamed: fileName toFamilyNamed: familyName inDirectoryNamed: dirName "BDFFontReader convertFilesNamed: 'helvR' toFamilyNamed: 'Helvetica' inDirectoryNamed: '' " "This utility converts X11 BDF font files to Squeak .sf2 StrikeFont files." "For this utility to work as is, the BDF files must be named 'familyNN.bdf', and must reside in the directory named by dirName (use '' for the current directory). The output StrikeFont files will be named familyNN.sf2, and will be placed in the current directory." "Check for matching file names." | allFontNames dir | dir := dirName isEmpty ifTrue: [ FileDirectory default ] ifFalse: [ FileDirectory default directoryNamed: dirName ]. allFontNames := dir fileNamesMatching: fileName , '##.bdf'. allFontNames isEmpty ifTrue: [ ^ self error: 'No files found like ' , fileName , 'NN.bdf' ]. UIManager default informUserDuring: [ :info | allFontNames do: [ :fname | | sizeChars f | info value: 'Converting ' , familyName , ' BDF file ' , fname , ' to SF2 format'. sizeChars := (fname copyFrom: fileName size + 1 to: fname size) copyUpTo: $.. f := StrikeFont new readBDFFromFile: (dir fullNameFor: fname) name: familyName , sizeChars. f writeAsStrike2named: familyName , sizeChars , '.sf2' ] ]! ! !BDFFontReader class methodsFor: 'file creation' stamp: 'yo 5/25/2004 10:52'! new ^ self basicNew. ! ! !BDFFontReader class methodsFor: 'file creation' stamp: 'ar 10/25/2005 00:21'! openFileNamed: fileName ^self new openFileNamed: fileName! ! !BDFFontReader class methodsFor: 'resource download' stamp: 'nop 1/23/2000 18:43'! convertX11FontsToStrike2 "BDFFontReader convertX11FontsToStrike2" "Given a set of standard X11 BDF font files (probably downloaded via BDFFontReader downloadFonts), produce .sf2 format fonts. The source and destination directory is the current directory." "Charter currently tickles a bug in the BDF parser. Skip it for now." "self convertFilesNamed: 'charR' toFamilyNamed: 'Charter' inDirectoryNamed: ''." self convertFilesNamed: 'courR' toFamilyNamed: 'Courier' inDirectoryNamed: ''. self convertFilesNamed: 'helvR' toFamilyNamed: 'Helvetica' inDirectoryNamed: ''. self convertFilesNamed: 'lubR' toFamilyNamed: 'LucidaBright' inDirectoryNamed: ''. self convertFilesNamed: 'luRS' toFamilyNamed: 'Lucida' inDirectoryNamed: ''. self convertFilesNamed: 'lutRS' toFamilyNamed: 'LucidaTypewriter' inDirectoryNamed: ''. self convertFilesNamed: 'ncenR' toFamilyNamed: 'NewCenturySchoolbook' inDirectoryNamed: ''. self convertFilesNamed: 'timR' toFamilyNamed: 'TimesRoman' inDirectoryNamed: ''.! ! !BDFFontReader class methodsFor: 'resource download' stamp: 'pmm 7/4/2009 12:07'! downloadFonts "BDFFontReader downloadFonts" "Download a standard set of BDF sources from x.org. The combined size of these source files is around 1.2M; after conversion to .sf2 format they may be deleted." | heads tails filenames baseUrl basePath | heads := #( 'charR' 'courR' 'helvR' 'lubR' 'luRS' 'lutRS' 'ncenR' 'timR' ). tails := #('08' '10' '12' '14' '18' '24' ). filenames := OrderedCollection new. heads do: [ :head | filenames addAll: (tails collect: [ :tail | head , tail , '.bdf' ]) ]. baseUrl := Url absoluteFromText: 'http://ftp.x.org/pub/R6.4/xc/fonts/bdf/75dpi/'. basePath := baseUrl path. filenames do: [ :filename | | newUrl newPath document f | newUrl := baseUrl clone. newPath := OrderedCollection newFrom: basePath. newPath addLast: filename. newUrl path: newPath. UIManager default informUser: 'Fetching ' translated, filename during: [ document := newUrl retrieveContents ]. f := (MultiByteFileStream newFileNamed: filename) ascii; wantsLineEndConversion: true; yourself. f nextPutAll: document content. f close ]! ! !BDFFontReader class methodsFor: 'resource download' stamp: 'eem 6/11/2008 13:33'! installX11Fonts "BDFFontReader installX11Fonts" "Installs previously-converted .sf2 fonts into the TextConstants dictionary. This makes them available as TextStyles everywhere in the image." | families | families := #( 'Courier' 'Helvetica' 'LucidaBright' 'Lucida' 'LucidaTypewriter' 'NewCenturySchoolbook' 'TimesRoman' ). families do: [:family | | fontArray textStyle | fontArray := StrikeFont readStrikeFont2Family: family. textStyle := TextStyle fontArray: fontArray. TextConstants at: family asSymbol put: textStyle. ]. ! ! ImageReadWriter subclass: #BMPReadWriter instanceVariableNames: 'bfType bfSize bfOffBits biSize biWidth biHeight biPlanes biBitCount biCompression biSizeImage biXPelsPerMeter biYPelsPerMeter biClrUsed biClrImportant' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Files'! !BMPReadWriter methodsFor: 'reading' stamp: 'ar 6/16/2002 15:36'! nextImage | colors | stream binary. self readHeader. biBitCount = 24 ifTrue:[^self read24BmpFile]. "read the color map" colors := self readColorMap. ^self readIndexedBmpFile: colors! ! !BMPReadWriter methodsFor: 'reading' stamp: 'lr 7/4/2009 10:42'! read24BmpFile "Read 24-bit pixel data from the given a BMP stream." | form formBits pixelLine bitsIndex bitBlt | form := Form extent: biWidth @ biHeight depth: 32. pixelLine := ByteArray new: (24 * biWidth + 31) // 32 * 4. bitsIndex := (form height - 1) * biWidth + 1. formBits := form bits. 1 to: biHeight do: [ :i | pixelLine := stream nextInto: pixelLine. self read24BmpLine: pixelLine into: formBits startingAt: bitsIndex width: biWidth. bitsIndex := bitsIndex - biWidth ]. bitBlt := BitBlt toForm: form. bitBlt combinationRule: 7. "bitOr:with:" bitBlt halftoneForm: (Bitmap with: 4278190080). bitBlt copyBits. ^ form! ! !BMPReadWriter methodsFor: 'reading' stamp: 'lr 7/4/2009 10:42'! read24BmpLine: pixelLine into: formBits startingAt: formBitsIndex width: width | pixIndex rgb bitsIndex | pixIndex := 0. "pre-increment" bitsIndex := formBitsIndex - 1. "pre-increment" 1 to: width do: [ :j | rgb := (pixelLine at: (pixIndex := pixIndex + 1)) + ((pixelLine at: (pixIndex := pixIndex + 1)) bitShift: 8) + ((pixelLine at: (pixIndex := pixIndex + 1)) bitShift: 16). formBits at: (bitsIndex := bitsIndex + 1) put: rgb ]! ! !BMPReadWriter methodsFor: 'reading' stamp: 'damiencassou 5/30/2008 14:51'! readColorMap "Read colorCount BMP color map entries from the given binary stream. Answer an array of Colors." | colorCount colors maxLevel b g r ccStream | colorCount := (bfOffBits - 54) // 4. "Note: some programs (e.g. Photoshop 4.0) apparently do not set colorCount; assume that any data between the end of the header and the start of the pixel data is the color map" biBitCount >= 16 ifTrue: [ ^ nil ]. colorCount = 0 ifTrue: [ "this BMP file does not have a color map" "default monochrome color map" biBitCount = 1 ifTrue: [ ^ Array with: Color white with: Color black ]. "default gray-scale color map" maxLevel := (2 raisedTo: biBitCount) - 1. ^ (0 to: maxLevel) collect: [ :level | Color gray: level asFloat / maxLevel ] ]. ccStream := (stream next: colorCount * 4) readStream. colors := Array new: colorCount. 1 to: colorCount do: [ :i | b := ccStream next. g := ccStream next. r := ccStream next. ccStream next. "skip reserved" colors at: i put: (Color r: r g: g b: b range: 255) ]. ^ colors! ! !BMPReadWriter methodsFor: 'reading' stamp: 'lr 7/4/2009 10:42'! readHeader | reserved | bfType := stream nextLittleEndianNumber: 2. bfSize := stream nextLittleEndianNumber: 4. reserved := stream nextLittleEndianNumber: 4. bfOffBits := stream nextLittleEndianNumber: 4. biSize := stream nextLittleEndianNumber: 4. biWidth := stream nextLittleEndianNumber: 4. biHeight := stream nextLittleEndianNumber: 4. biPlanes := stream nextLittleEndianNumber: 2. biBitCount := stream nextLittleEndianNumber: 2. biCompression := stream nextLittleEndianNumber: 4. biSizeImage := stream nextLittleEndianNumber: 4. biXPelsPerMeter := stream nextLittleEndianNumber: 4. biYPelsPerMeter := stream nextLittleEndianNumber: 4. biClrUsed := stream nextLittleEndianNumber: 4. biClrImportant := stream nextLittleEndianNumber: 4! ! !BMPReadWriter methodsFor: 'reading' stamp: 'lr 7/4/2009 10:42'! readIndexedBmpFile: colors "Read uncompressed pixel data of depth d from the given BMP stream, where d is 1, 4, 8, or 16" | form bytesPerRow pixelData pixelLine startIndex map bitBlt mask | colors ifNil: [ form := Form extent: biWidth @ biHeight depth: biBitCount ] ifNotNil: [ form := ColorForm extent: biWidth @ biHeight depth: biBitCount. form colors: colors ]. bytesPerRow := (biBitCount * biWidth + 31) // 32 * 4. pixelData := ByteArray new: bytesPerRow * biHeight. biHeight to: 1 by: -1 do: [ :y | pixelLine := stream next: bytesPerRow. startIndex := (y - 1) * bytesPerRow + 1. pixelData replaceFrom: startIndex to: startIndex + bytesPerRow - 1 with: pixelLine startingAt: 1 ]. form bits copyFromByteArray: pixelData. biBitCount = 16 ifTrue: [ map := ColorMap shifts: #(8 -8 0 0 ) masks: #(255 65280 0 0 ). mask := 2147516416 ]. biBitCount = 32 ifTrue: [ map := ColorMap shifts: #(24 8 -8 -24 ) masks: #(255 65280 16711680 4278190080 ). mask := 4278190080 ]. map ifNotNil: [ bitBlt := BitBlt toForm: form. bitBlt sourceForm: form. bitBlt colorMap: map. bitBlt combinationRule: Form over. bitBlt copyBits ]. mask ifNotNil: [ bitBlt := BitBlt toForm: form. bitBlt combinationRule: 7. "bitOr:with:" bitBlt halftoneForm: (Bitmap with: mask). bitBlt copyBits ]. ^ form! ! !BMPReadWriter methodsFor: 'testing' stamp: 'ar 6/16/2002 15:27'! understandsImageFormat stream size < 54 ifTrue:[^false]. "min size = BITMAPFILEHEADER+BITMAPINFOHEADER" self readHeader. bfType = 19778 "BM" ifFalse:[^false]. biSize = 40 ifFalse:[^false]. biPlanes = 1 ifFalse:[^false]. bfSize <= stream size ifFalse:[^false]. biCompression = 0 ifFalse:[^false]. ^true! ! !BMPReadWriter methodsFor: 'writing' stamp: 'lr 7/4/2009 10:42'! nextPutImage: aForm | bhSize rowBytes rgb data colorValues depth image ppw scanLineLen | depth := aForm depth. [ #(1 4 8 32 ) includes: depth ] whileFalse: [ depth := depth + 1 asLargerPowerOfTwo ]. image := aForm asFormOfDepth: depth. image unhibernate. bhSize := 14. "# bytes in file header" biSize := 40. "info header size in bytes" biWidth := image width. biHeight := image height. biClrUsed := depth = 32 ifTrue: [ 0 ] ifFalse: [ 1 << depth ]. "No. color table entries" bfOffBits := biSize + bhSize + (4 * biClrUsed). rowBytes := ((depth min: 24) * biWidth + 31) // 32 * 4. biSizeImage := biHeight * rowBytes. "Write the file header" stream position: 0. stream nextLittleEndianNumber: 2 put: 19778. "bfType = BM" stream nextLittleEndianNumber: 4 put: bfOffBits + biSizeImage. "Entire file size in bytes" stream nextLittleEndianNumber: 4 put: 0. "bfReserved" stream nextLittleEndianNumber: 4 put: bfOffBits. "Offset of bitmap data from start of hdr (and file)" "Write the bitmap info header" stream position: bhSize. stream nextLittleEndianNumber: 4 put: biSize. "info header size in bytes" stream nextLittleEndianNumber: 4 put: image width. "biWidth" stream nextLittleEndianNumber: 4 put: image height. "biHeight" stream nextLittleEndianNumber: 2 put: 1. "biPlanes" stream nextLittleEndianNumber: 2 put: (depth min: 24). "biBitCount" stream nextLittleEndianNumber: 4 put: 0. "biCompression" stream nextLittleEndianNumber: 4 put: biSizeImage. "size of image section in bytes" stream nextLittleEndianNumber: 4 put: 2800. "biXPelsPerMeter" stream nextLittleEndianNumber: 4 put: 2800. "biYPelsPerMeter" stream nextLittleEndianNumber: 4 put: biClrUsed. stream nextLittleEndianNumber: 4 put: 0. "biClrImportant" biClrUsed > 0 ifTrue: [ "write color map; this works for ColorForms, too" colorValues := image colormapIfNeededForDepth: 32. 1 to: biClrUsed do: [ :i | rgb := colorValues at: i. 0 to: 24 by: 8 do: [ :j | stream nextPut: (rgb >> j bitAnd: 255) ] ] ]. depth < 32 ifTrue: [ "depth = 1, 4 or 8." data := image bits asByteArray. ppw := 32 // depth. scanLineLen := (biWidth + ppw - 1) // ppw * 4. "# of bytes in line" 1 to: biHeight do: [ :i | stream next: scanLineLen putAll: data startingAt: (biHeight - i) * scanLineLen + 1 ] ] ifFalse: [ 1 to: biHeight do: [ :i | data := (image copy: (0 @ (biHeight - i) extent: biWidth @ 1)) bits. 1 to: data size do: [ :j | stream nextLittleEndianNumber: 3 put: (data at: j) ]. 1 to: (data size * 3 + 3) // 4 * 4 - (data size * 3) do: [ :j | stream nextPut: 0 "pad to 32-bits" ] ] ]. stream position = (bfOffBits + biSizeImage) ifFalse: [ self error: 'Write failure' ]. stream close! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BMPReadWriter class instanceVariableNames: ''! !BMPReadWriter class methodsFor: 'image reading/writing' stamp: 'nk 7/16/2003 17:56'! typicalFileExtensions "Answer a collection of file extensions (lowercase) which files that I can read might commonly have" ^#('bmp')! ! !BMPReadWriter class methodsFor: 'testing' stamp: 'ar 6/16/2002 18:55'! displayAllFrom: fd "BMPReadWriter displayAllFrom: FileDirectory default" fd fileNames do:[:fName| (fName endsWith: '.bmp') ifTrue:[ [(Form fromBinaryStream: (fd readOnlyFileNamed: fName)) display. Display forceDisplayUpdate] on: Error do:[:nix|]. ]. ]. fd directoryNames do:[:fdName| self displayAllFrom: (fd directoryNamed: fdName) ].! ! !BMPReadWriter class methodsFor: 'testing' stamp: 'ar 6/16/2002 18:56'! readAllFrom: fd "MessageTally spyOn:[BMPReadWriter readAllFrom: FileDirectory default]" fd fileNames do:[:fName| (fName endsWith: '.bmp') ifTrue:[ [Form fromBinaryStream: (fd readOnlyFileNamed: fName)] on: Error do:[:nix]. ]. ]. fd directoryNames do:[:fdName| self readAllFrom: (fd directoryNamed: fdName) ].! ! TestCase subclass: #BMPReadWriterTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'GraphicsTests-Files'! !BMPReadWriterTest methodsFor: 'data' stamp: 'ar 10/25/2005 02:22'! bmpData16bit "Created via: (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: 'bmptest16b.bmp') binary) contents " ^(Base64MimeConverter mimeDecodeToBytes: 'Qk24AAAAAAAAADYAAAAoAAAACAAAAAgAAAABABAAAAAAAIIAAADDDgAAww4AAAAAAAAAAAAA 4APgA+AD4AMfAB8AHwAfAOAD4APgA+ADHwAfAB8AHwDgA+AD/3//f/9//38fAB8A4APgA/9/ /3//f/9/HwAfAAAAAAD/f/9//3//fwB8AHwAAAAA/3//f/9//38AfAB8AAAAAAAAAAAAfAB8 AHwAfAAAAAAAAAAAAHwAfAB8AHwAAA==' readStream) contents! ! !BMPReadWriterTest methodsFor: 'data' stamp: 'ar 10/24/2005 21:27'! bmpData24bit "Created via: (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: 'bmptest24.bmp') binary) contents " ^(Base64MimeConverter mimeDecodeToBytes: 'Qk32AAAAAAAAADYAAAAoAAAACAAAAAgAAAABABgAAAAAAAAAAADEDgAAxA4AAAAAAAAAAAAA AP8AAP8AAP8AAP8A/wAA/wAA/wAA/wAAAP8AAP8AAP8AAP8A/wAA/wAA/wAA/wAAAP8AAP8A /////////////////wAA/wAAAP8AAP8A/////////////////wAA/wAAAAAAAAAA//////// ////////AAD/AAD/AAAAAAAA////////////////AAD/AAD/AAAAAAAAAAAAAAAAAAD/AAD/ AAD/AAD/AAAAAAAAAAAAAAAAAAD/AAD/AAD/AAD/' readStream) contents! ! !BMPReadWriterTest methodsFor: 'data' stamp: 'ar 10/25/2005 02:22'! bmpData32bit "Created via: (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: 'bmptest32b.bmp') binary) contents " ^(Base64MimeConverter mimeDecodeToBytes: 'Qk04AQAAAAAAADYAAAAoAAAACAAAAAgAAAABACAAAAAAAAIBAADDDgAAww4AAAAAAAAAAAAA AP8AAAD/AAAA/wAAAP8AAP8AAAD/AAAA/wAAAP8AAAAA/wAAAP8AAAD/AAAA/wAA/wAAAP8A AAD/AAAA/wAAAAD/AAAA/wAA////AP///wD///8A////AP8AAAD/AAAAAP8AAAD/AAD///8A ////AP///wD///8A/wAAAP8AAAAAAAAAAAAAAP///wD///8A////AP///wAAAP8AAAD/AAAA AAAAAAAA////AP///wD///8A////AAAA/wAAAP8AAAAAAAAAAAAAAAAAAAAAAAAA/wAAAP8A AAD/AAAA/wAAAAAAAAAAAAAAAAAAAAAAAAD/AAAA/wAAAP8AAAD/AAAA' readStream) contents! ! !BMPReadWriterTest methodsFor: 'data' stamp: 'ar 10/24/2005 21:41'! bmpData4bit "Created via: (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: 'bmptest4.bmp') binary) contents " ^(Base64MimeConverter mimeDecodeToBytes: 'Qk12BAAAAAAAADYEAAAoAAAACAAAAAgAAAABAAgAAAAAAEAAAADEDgAAxA4AAAAAAAAAAAAA AAAAAAAAgAAAgAAAAICAAIAAAACAAIAAgIAAAMDAwADA3MAA8MqmAAAgQAAAIGAAACCAAAAg oAAAIMAAACDgAABAAAAAQCAAAEBAAABAYAAAQIAAAECgAABAwAAAQOAAAGAAAABgIAAAYEAA AGBgAABggAAAYKAAAGDAAABg4AAAgAAAAIAgAACAQAAAgGAAAICAAACAoAAAgMAAAIDgAACg AAAAoCAAAKBAAACgYAAAoIAAAKCgAACgwAAAoOAAAMAAAADAIAAAwEAAAMBgAADAgAAAwKAA AMDAAADA4AAA4AAAAOAgAADgQAAA4GAAAOCAAADgoAAA4MAAAODgAEAAAABAACAAQABAAEAA YABAAIAAQACgAEAAwABAAOAAQCAAAEAgIABAIEAAQCBgAEAggABAIKAAQCDAAEAg4ABAQAAA QEAgAEBAQABAQGAAQECAAEBAoABAQMAAQEDgAEBgAABAYCAAQGBAAEBgYABAYIAAQGCgAEBg wABAYOAAQIAAAECAIABAgEAAQIBgAECAgABAgKAAQIDAAECA4ABAoAAAQKAgAECgQABAoGAA QKCAAECgoABAoMAAQKDgAEDAAABAwCAAQMBAAEDAYABAwIAAQMCgAEDAwABAwOAAQOAAAEDg IABA4EAAQOBgAEDggABA4KAAQODAAEDg4ACAAAAAgAAgAIAAQACAAGAAgACAAIAAoACAAMAA gADgAIAgAACAICAAgCBAAIAgYACAIIAAgCCgAIAgwACAIOAAgEAAAIBAIACAQEAAgEBgAIBA gACAQKAAgEDAAIBA4ACAYAAAgGAgAIBgQACAYGAAgGCAAIBgoACAYMAAgGDgAICAAACAgCAA gIBAAICAYACAgIAAgICgAICAwACAgOAAgKAAAICgIACAoEAAgKBgAICggACAoKAAgKDAAICg 4ACAwAAAgMAgAIDAQACAwGAAgMCAAIDAoACAwMAAgMDgAIDgAACA4CAAgOBAAIDgYACA4IAA gOCgAIDgwACA4OAAwAAAAMAAIADAAEAAwABgAMAAgADAAKAAwADAAMAA4ADAIAAAwCAgAMAg QADAIGAAwCCAAMAgoADAIMAAwCDgAMBAAADAQCAAwEBAAMBAYADAQIAAwECgAMBAwADAQOAA wGAAAMBgIADAYEAAwGBgAMBggADAYKAAwGDAAMBg4ADAgAAAwIAgAMCAQADAgGAAwICAAMCA oADAgMAAwIDgAMCgAADAoCAAwKBAAMCgYADAoIAAwKCgAMCgwADAoOAAwMAAAMDAIADAwEAA wMBgAMDAgADAwKAA8Pv/AKSgoACAgIAAAAD/AAD/AAAA//8A/wAAAP8A/wD//wAA////APr6 +vr8/Pz8+vr6+vz8/Pz6+v/////8/Pr6//////z8AAD/////+fkAAP/////5+QAAAAD5+fn5 AAAAAPn5+fk=' readStream) contents! ! !BMPReadWriterTest methodsFor: 'data' stamp: 'ar 10/24/2005 21:27'! bmpData8bit "Created via: (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: 'bmptest8.bmp') binary) contents " ^(Base64MimeConverter mimeDecodeToBytes: 'Qk12BAAAAAAAADYEAAAoAAAACAAAAAgAAAABAAgAAAAAAEAAAADEDgAAxA4AAAAAAAAAAAAA AAAAAAAAgAAAgAAAAICAAIAAAACAAIAAgIAAAMDAwADA3MAA8MqmAAAgQAAAIGAAACCAAAAg oAAAIMAAACDgAABAAAAAQCAAAEBAAABAYAAAQIAAAECgAABAwAAAQOAAAGAAAABgIAAAYEAA AGBgAABggAAAYKAAAGDAAABg4AAAgAAAAIAgAACAQAAAgGAAAICAAACAoAAAgMAAAIDgAACg AAAAoCAAAKBAAACgYAAAoIAAAKCgAACgwAAAoOAAAMAAAADAIAAAwEAAAMBgAADAgAAAwKAA AMDAAADA4AAA4AAAAOAgAADgQAAA4GAAAOCAAADgoAAA4MAAAODgAEAAAABAACAAQABAAEAA YABAAIAAQACgAEAAwABAAOAAQCAAAEAgIABAIEAAQCBgAEAggABAIKAAQCDAAEAg4ABAQAAA QEAgAEBAQABAQGAAQECAAEBAoABAQMAAQEDgAEBgAABAYCAAQGBAAEBgYABAYIAAQGCgAEBg wABAYOAAQIAAAECAIABAgEAAQIBgAECAgABAgKAAQIDAAECA4ABAoAAAQKAgAECgQABAoGAA QKCAAECgoABAoMAAQKDgAEDAAABAwCAAQMBAAEDAYABAwIAAQMCgAEDAwABAwOAAQOAAAEDg IABA4EAAQOBgAEDggABA4KAAQODAAEDg4ACAAAAAgAAgAIAAQACAAGAAgACAAIAAoACAAMAA gADgAIAgAACAICAAgCBAAIAgYACAIIAAgCCgAIAgwACAIOAAgEAAAIBAIACAQEAAgEBgAIBA gACAQKAAgEDAAIBA4ACAYAAAgGAgAIBgQACAYGAAgGCAAIBgoACAYMAAgGDgAICAAACAgCAA gIBAAICAYACAgIAAgICgAICAwACAgOAAgKAAAICgIACAoEAAgKBgAICggACAoKAAgKDAAICg 4ACAwAAAgMAgAIDAQACAwGAAgMCAAIDAoACAwMAAgMDgAIDgAACA4CAAgOBAAIDgYACA4IAA gOCgAIDgwACA4OAAwAAAAMAAIADAAEAAwABgAMAAgADAAKAAwADAAMAA4ADAIAAAwCAgAMAg QADAIGAAwCCAAMAgoADAIMAAwCDgAMBAAADAQCAAwEBAAMBAYADAQIAAwECgAMBAwADAQOAA wGAAAMBgIADAYEAAwGBgAMBggADAYKAAwGDAAMBg4ADAgAAAwIAgAMCAQADAgGAAwICAAMCA oADAgMAAwIDgAMCgAADAoCAAwKBAAMCgYADAoIAAwKCgAMCgwADAoOAAwMAAAMDAIADAwEAA wMBgAMDAgADAwKAA8Pv/AKSgoACAgIAAAAD/AAD/AAAA//8A/wAAAP8A/wD//wAA////APr6 +vr8/Pz8+vr6+vz8/Pz6+v/////8/Pr6//////z8AAD/////+fkAAP/////5+QAAAAD5+fn5 AAAAAPn5+fk=' readStream) contents! ! !BMPReadWriterTest methodsFor: 'data' stamp: 'ar 10/25/2005 14:04'! bmpDataR5G6B5 "This is a BMP file based on BitmapV4Header which is currently unsupported." "Created via: (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: 'bmptest16-R5G6B5.bmp') binary) contents " ^(Base64MimeConverter mimeDecodeToBytes: 'Qk3IAAAAAAAAAEYAAAA4AAAACAAAAAgAAAABABAAAwAAAIIAAADDDgAAww4AAAAAAAAAAAAA APgAAOAHAAAfAAAAAAAAAOAH4AfgB+AHHwAfAB8AHwDgB+AH4AfgBx8AHwAfAB8A4AfgB/// ////////HwAfAOAH4Af//////////x8AHwAAAAAA//////////8A+AD4AAAAAP////////// APgA+AAAAAAAAAAAAPgA+AD4APgAAAAAAAAAAAD4APgA+AD4AAA=' readStream) contents! ! !BMPReadWriterTest methodsFor: 'data' stamp: 'ar 10/25/2005 14:04'! bmpDataX4R4G4B4 "This is a BMP file based on BitmapV4Header which is currently unsupported." "Created via: (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: 'bmptest16-X4R4G4B4.bmp') binary) contents " ^(Base64MimeConverter mimeDecodeToBytes: 'Qk3IAAAAAAAAAEYAAAA4AAAACAAAAAgAAAABABAAAwAAAIIAAADDDgAAww4AAAAAAAAAAAAA AA8AAPAAAAAPAAAAAAAAAPAA8ADwAPAADwAPAA8ADwDwAPAA8ADwAA8ADwAPAA8A8ADwAP8P /w//D/8PDwAPAPAA8AD/D/8P/w//Dw8ADwAAAAAA/w//D/8P/w8ADwAPAAAAAP8P/w//D/8P AA8ADwAAAAAAAAAAAA8ADwAPAA8AAAAAAAAAAAAPAA8ADwAPAAA=' readStream) contents! ! !BMPReadWriterTest methodsFor: 'data' stamp: 'ar 10/25/2005 14:05'! bmpDataX8R8G8B8 "This is a BMP file based on BitmapV4Header which is currently unsupported." "Created via: (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: 'bmptest32-X8R8G8B8.bmp') binary) contents " ^(Base64MimeConverter mimeDecodeToBytes: 'Qk1IAQAAAAAAAEYAAAA4AAAACAAAAAgAAAABACAAAwAAAAIBAADDDgAAww4AAAAAAAAAAAAA AAAA/wAA/wAA/wAAAAAAAAAA/wAAAP8AAAD/AAAA/wAA/wAAAP8AAAD/AAAA/wAAAAD/AAAA /wAAAP8AAAD/AAD/AAAA/wAAAP8AAAD/AAAAAP8AAAD/AAD///8A////AP///wD///8A/wAA AP8AAAAA/wAAAP8AAP///wD///8A////AP///wD/AAAA/wAAAAAAAAAAAAAA////AP///wD/ //8A////AAAA/wAAAP8AAAAAAAAAAAD///8A////AP///wD///8AAAD/AAAA/wAAAAAAAAAA AAAAAAAAAAAAAAD/AAAA/wAAAP8AAAD/AAAAAAAAAAAAAAAAAAAAAAAAAP8AAAD/AAAA/wAA AP8AAA==' readStream) contents! ! !BMPReadWriterTest methodsFor: 'reading' stamp: 'damiencassou 5/30/2008 14:57'! testBmp16Bit | reader form | reader := BMPReadWriter new on: self bmpData16bit readStream. form := reader nextImage. "special black here to compensate for zero-is-transparent effect" self assert: (form colorAt: 7 @ 1) = Color red. self assert: (form colorAt: 1 @ 7) = Color green. self assert: (form colorAt: 7 @ 7) = Color blue. self assert: (form colorAt: 4 @ 4) = Color white. self assert: (form pixelValueAt: 1 @ 1) = 32768! ! !BMPReadWriterTest methodsFor: 'reading' stamp: 'damiencassou 5/30/2008 14:57'! testBmp24Bit | reader form | reader := BMPReadWriter new on: self bmpData24bit readStream. form := reader nextImage. self assert: (form colorAt: 7 @ 1) = Color red. self assert: (form colorAt: 1 @ 7) = Color green. self assert: (form colorAt: 7 @ 7) = Color blue. self assert: (form colorAt: 4 @ 4) = Color white. self assert: (form pixelValueAt: 1 @ 1) = 4278190080! ! !BMPReadWriterTest methodsFor: 'reading' stamp: 'damiencassou 5/30/2008 14:57'! testBmp32Bit | reader form | reader := BMPReadWriter new on: self bmpData32bit readStream. form := reader nextImage. self assert: (form colorAt: 7 @ 1) = Color red. self assert: (form colorAt: 1 @ 7) = Color green. self assert: (form colorAt: 7 @ 7) = Color blue. self assert: (form colorAt: 4 @ 4) = Color white. self assert: (form pixelValueAt: 1 @ 1) = 4278190080! ! !BMPReadWriterTest methodsFor: 'reading' stamp: 'damiencassou 5/30/2008 14:57'! testBmp4Bit | reader form | reader := BMPReadWriter new on: self bmpData4bit readStream. form := reader nextImage. self assert: (form colorAt: 1 @ 1) = Color black. self assert: (form colorAt: 7 @ 1) = Color red. self assert: (form colorAt: 1 @ 7) = Color green. self assert: (form colorAt: 7 @ 7) = Color blue. self assert: (form colorAt: 4 @ 4) = Color white! ! !BMPReadWriterTest methodsFor: 'reading' stamp: 'damiencassou 5/30/2008 14:57'! testBmp8Bit | reader form | reader := BMPReadWriter new on: self bmpData8bit readStream. form := reader nextImage. self assert: (form colorAt: 1 @ 1) = Color black. self assert: (form colorAt: 7 @ 1) = Color red. self assert: (form colorAt: 1 @ 7) = Color green. self assert: (form colorAt: 7 @ 7) = Color blue. self assert: (form colorAt: 4 @ 4) = Color white! ! Object subclass: #BadEqualer instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'SUnit-Utilities'! !BadEqualer commentStamp: 'mjr 8/20/2003 13:28' prior: 0! I am an object that doesn't always report #= correctly. Used for testing the EqualityTester.! !BadEqualer methodsFor: 'comparing' stamp: 'mjr 8/20/2003 18:56'! = other self class = other class ifFalse: [^ false]. ^ 100 atRandom < 30 ! ! Object subclass: #BadHasher instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'SUnit-Utilities'! !BadHasher commentStamp: 'mjr 8/20/2003 13:28' prior: 0! I am an object that doesn't always hash correctly. I am used for testing the HashTester.! !BadHasher methodsFor: 'comparing' stamp: 'mjr 8/20/2003 18:56'! hash "answer with a different hash some of the time" 100 atRandom < 30 ifTrue: [^ 1]. ^ 2! ! Collection subclass: #Bag instanceVariableNames: 'contents' classVariableNames: '' poolDictionaries: '' category: 'Collections-Unordered'! !Bag commentStamp: '' prior: 0! I represent an unordered collection of possibly duplicate elements. I store these elements in a dictionary, tallying up occurrences of equal objects. Because I store an occurrence only once, my clients should beware that objects they store will not necessarily be retrieved such that == is true. If the client cares, a subclass of me should be created.! !Bag methodsFor: 'accessing' stamp: 'sma 5/12/2000 17:23'! at: index self errorNotKeyed! ! !Bag methodsFor: 'accessing' stamp: 'sma 5/12/2000 17:23'! at: index put: anObject self errorNotKeyed! ! !Bag methodsFor: 'accessing' stamp: 'tao 1/5/2000 18:25'! cumulativeCounts "Answer with a collection of cumulative percents covered by elements so far." | s n | s := self size / 100.0. n := 0. ^ self sortedCounts asArray collect: [:a | n := n + a key. (n / s roundTo: 0.1) -> a value]! ! !Bag methodsFor: 'accessing' stamp: 'sma 5/12/2000 11:35'! size "Answer how many elements the receiver contains." | tally | tally := 0. contents do: [:each | tally := tally + each]. ^ tally! ! !Bag methodsFor: 'accessing' stamp: 'sma 6/15/2000 17:00'! sortedCounts "Answer with a collection of counts with elements, sorted by decreasing count." | counts | counts := SortedCollection sortBlock: [:x :y | x >= y]. contents associationsDo: [:assn | counts add: (Association key: assn value value: assn key)]. ^ counts! ! !Bag methodsFor: 'accessing'! sortedElements "Answer with a collection of elements with counts, sorted by element." | elements | elements := SortedCollection new. contents associationsDo: [:assn | elements add: assn]. ^elements! ! !Bag methodsFor: 'accessing' stamp: 'md 1/20/2006 15:58'! valuesAndCounts ^ contents! ! !Bag methodsFor: 'adding' stamp: 'sma 5/12/2000 17:18'! add: newObject "Include newObject as one of the receiver's elements. Answer newObject." ^ self add: newObject withOccurrences: 1! ! !Bag methodsFor: 'adding' stamp: 'sma 5/12/2000 17:20'! add: newObject withOccurrences: anInteger "Add newObject anInteger times to the receiver. Answer newObject." contents at: newObject put: (contents at: newObject ifAbsent: [0]) + anInteger. ^ newObject! ! !Bag methodsFor: 'comparing' stamp: 'md 10/17/2004 16:09'! = aBag "Two bags are equal if (a) they are the same 'kind' of thing. (b) they have the same size. (c) each element occurs the same number of times in both of them" (aBag isKindOf: Bag) ifFalse: [^false]. self size = aBag size ifFalse: [^false]. contents associationsDo: [:assoc| (aBag occurrencesOf: assoc key) = assoc value ifFalse: [^false]]. ^true ! ! !Bag methodsFor: 'converting' stamp: 'sma 5/12/2000 14:34'! asBag ^ self! ! !Bag methodsFor: 'converting' stamp: 'sma 5/12/2000 14:30'! asSet "Answer a set with the elements of the receiver." ^ contents keys! ! !Bag methodsFor: 'copying' stamp: 'sma 5/12/2000 14:53'! copy ^ self shallowCopy setContents: contents copy! ! !Bag methodsFor: 'enumerating'! do: aBlock "Refer to the comment in Collection|do:." contents associationsDo: [:assoc | assoc value timesRepeat: [aBlock value: assoc key]]! ! !Bag methodsFor: 'removing' stamp: 'sma 5/12/2000 14:32'! remove: oldObject ifAbsent: exceptionBlock "Refer to the comment in Collection|remove:ifAbsent:." | count | count := contents at: oldObject ifAbsent: [^ exceptionBlock value]. count = 1 ifTrue: [contents removeKey: oldObject] ifFalse: [contents at: oldObject put: count - 1]. ^ oldObject! ! !Bag methodsFor: 'removing' stamp: 'nice 9/14/2009 20:28'! removeAll "Implementation Note: as contents will be overwritten, a shallowCopy of self would be modified. An alternative implementation preserving capacity would be to create a new contents: self setContents: (self class contentsClass new: contents size)." contents removeAll! ! !Bag methodsFor: 'testing'! includes: anObject "Refer to the comment in Collection|includes:." ^contents includesKey: anObject! ! !Bag methodsFor: 'testing'! occurrencesOf: anObject "Refer to the comment in Collection|occurrencesOf:." (self includes: anObject) ifTrue: [^contents at: anObject] ifFalse: [^0]! ! !Bag methodsFor: 'private' stamp: 'sma 5/12/2000 14:49'! setContents: aDictionary contents := aDictionary! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Bag class instanceVariableNames: ''! !Bag class methodsFor: 'instance creation' stamp: 'nk 3/17/2001 09:52'! contentsClass ^Dictionary! ! !Bag class methodsFor: 'instance creation' stamp: 'sma 5/12/2000 13:31'! new ^ self new: 4! ! !Bag class methodsFor: 'instance creation' stamp: 'nk 3/17/2001 09:52'! new: nElements ^ super new setContents: (self contentsClass new: nElements)! ! !Bag class methodsFor: 'instance creation' stamp: 'sma 5/12/2000 17:17'! newFrom: aCollection "Answer an instance of me containing the same elements as aCollection." ^ self withAll: aCollection "Examples: Bag newFrom: {1. 2. 3. 3} {1. 2. 3. 3} as: Bag "! ! CollectionRootTest subclass: #BagTest uses: TAddTest + TIncludesWithIdentityCheckTest + TCloneTest + TCopyTest + TSetArithmetic + TConvertTest + TAsStringCommaAndDelimiterTest + TRemoveForMultiplenessTest + TPrintTest + TConvertAsSortedTest + TConvertAsSetForMultiplinessTest + TConcatenationTest + TStructuralEqualityTest + TCreationWithTest - {#testOfSize} + TOccurrencesForMultiplinessTest instanceVariableNames: 'empty nonEmpty result emptyButAllocatedWith20 elementExistsTwice element collectionWithElement collectionIn collectionNotIn collectionOfString elementNotIn collectionWithCharacters otherCollectionWithoutEqualElements collectionWithoutNilMoreThan5' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Unordered'! !BagTest methodsFor: 'as yet unclassified' stamp: 'damienpollet 1/13/2009 15:57'! testAnySastify self assert: ( self collection anySatisfy: [:each | each = self element]). self deny: (self collection anySatisfy: [:each | each isString]).! ! !BagTest methodsFor: 'basic tests' stamp: 'sd 3/21/2006 22:28'! testAdd "self run: #testAdd" "self debug: #testAdd" | aBag | aBag := Bag new. aBag add: 'a'. aBag add: 'b'. self assert: aBag size = 2. aBag add: 'a'. self assert: aBag size = 3. self assert: (aBag occurrencesOf: 'a') = 2 ! ! !BagTest methodsFor: 'basic tests' stamp: 'sd 3/21/2006 22:28'! testAddWithOccurrences "self debug:#testAddWithOccurrences" | aBag | aBag := Bag new. aBag add: 'a' withOccurrences: 3. self assert: (aBag size = 3). ! ! !BagTest methodsFor: 'basic tests' stamp: 'TJ 3/8/2006 08:42'! testAsBag | aBag | aBag := Bag new. self assert: aBag asBag = aBag.! ! !BagTest methodsFor: 'basic tests' stamp: 'sd 3/21/2006 22:29'! testAsSet | aBag aSet | aBag := Bag new. aBag add:'a' withOccurrences: 4. aBag add:'b' withOccurrences: 2. aSet := aBag asSet. self assert: aSet size = 2. self assert: (aSet occurrencesOf: 'a') = 1 ! ! !BagTest methodsFor: 'basic tests' stamp: 'sd 3/21/2006 22:30'! testCopy "self run: #testCopy" | aBag newBag | aBag := Bag new. aBag add:'a' withOccurrences: 4. aBag add:'b' withOccurrences: 2. newBag := aBag copy. self assert: newBag = newBag. self assert: newBag asSet size = 2.! ! !BagTest methodsFor: 'basic tests' stamp: 'sd 3/21/2006 22:32'! testOccurrencesOf "self debug: #testOccurrencesOf" | aBag | aBag := Bag new. aBag add: 'a' withOccurrences: 3. aBag add: 'b'. aBag add: 'b'. aBag add: 'b'. aBag add: 'b'. self assert: (aBag occurrencesOf:'a') = 3. self assert: (aBag occurrencesOf:'b') = 4. self assert: (aBag occurrencesOf:'c') = 0. self assert: (aBag occurrencesOf: nil) =0. aBag add: nil. self assert: (aBag occurrencesOf: nil) =1. ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 12:01'! anotherElementOrAssociationIn " return an element (or an association for Dictionary ) present in 'collection' " ^ self collection anyOne! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 12:01'! anotherElementOrAssociationNotIn " return an element (or an association for Dictionary )not present in 'collection' " ^ elementNotIn ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/14/2009 12:07'! collectionInForIncluding ^ collectionIn ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 12:16'! collectionMoreThan5Elements " return a collection including at least 5 elements" ^ collectionWithoutNilMoreThan5 ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/14/2009 12:08'! collectionNotIncluded ^ collectionNotIn ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/15/2009 14:07'! collectionOfFloat ^ collectionOfString! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/14/2009 14:22'! collectionWithCharacters ^ collectionWithCharacters .! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 10:22'! collectionWithCopyNonIdentical " return a collection that include elements for which 'copy' return a different object (this is not the case of SmallInteger)" ^ collectionOfString! ! !BagTest methodsFor: 'requirements' stamp: 'sd 1/28/2009 16:32'! collectionWithElement "Returns a collection that already includes what is returned by #element." ^ collectionWithElement! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/17/2009 15:24'! collectionWithElementsToRemove ^ collectionIn! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/14/2009 14:20'! collectionWithEqualElements ^ nonEmpty ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/24/2009 10:31'! collectionWithSortableElements " return a collection elements that can be sorte ( understanding message ' < ' or ' > ')" ^ nonEmpty ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/11/2009 11:27'! collectionWithoutEqualElements ^ otherCollectionWithoutEqualElements! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 12:15'! collectionWithoutNilElements " return a collection that doesn't includes a nil element and that doesn't includes equal elements'" ^ collectionWithoutNilMoreThan5! ! !BagTest methodsFor: 'requirements' stamp: 'damienpollet 1/30/2009 17:32'! element ^ super element! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/14/2009 14:19'! elementInForIncludesTest ^ self element ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/13/2009 14:32'! elementInForOccurrences " return an element included in nonEmpty" ^self nonEmpty anyOne.! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/14/2009 13:40'! elementNotIn ^elementNotIn ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/13/2009 15:33'! elementTwiceInForOccurrences " return an element included exactly two time in # collectionWithEqualElements" ^ self elementTwiceIn ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 14:19'! elementsCopyNonIdenticalWithoutEqualElements " return a collection that does niot incllude equal elements ( classic equality ) all elements included are elements for which copy is not identical to the element " ^ collectionOfString ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/11/2009 11:53'! firstCollection " return a collection that will be the first part of the concatenation" ^ nonEmpty ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/11/2009 11:27'! integerCollectionWithoutEqualElements ^ otherCollectionWithoutEqualElements! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/30/2009 10:54'! nonEmpty1Element ^ self speciesClass new add: self element ;yourself.! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/11/2009 11:28'! nonEmptyWithoutEqualElements " return a collection without equal elements " ^ otherCollectionWithoutEqualElements ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/11/2009 11:27'! otherCollection ^ otherCollectionWithoutEqualElements! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/23/2009 11:47'! resultForCollectElementsClass " return the retsult expected by collecting the class of each element of collectionWithoutNilElements" ^ result ! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 5/11/2009 11:53'! secondCollection " return a collection that will be the second part of the concatenation" ^ collectionWithCharacters ! ! !BagTest methodsFor: 'requirements' stamp: 'damienpollet 1/30/2009 17:40'! selectedNumber ^ 4! ! !BagTest methodsFor: 'requirements' stamp: 'stephane.ducasse 10/6/2008 17:39'! speciesClass ^ Bag! ! !BagTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 14:21'! withEqualElements " return a collection including equal elements (classic equality)" ^ nonEmpty .! ! !BagTest methodsFor: 'setup' stamp: 'stephane.ducasse 10/6/2008 17:22'! collection ^ nonEmpty. ! ! !BagTest methodsFor: 'setup' stamp: 'stephane.ducasse 10/5/2008 15:13'! empty ^ empty ! ! !BagTest methodsFor: 'setup' stamp: 'stephane.ducasse 10/6/2008 17:26'! emptyButAllocatedWith20 ^ emptyButAllocatedWith20! ! !BagTest methodsFor: 'setup' stamp: 'stephane.ducasse 10/5/2008 15:14'! nonEmpty ^ nonEmpty ! ! !BagTest methodsFor: 'setup' stamp: 'stephane.ducasse 10/6/2008 17:22'! result ^ result. ! ! !BagTest methodsFor: 'setup' stamp: 'delaunay 5/14/2009 12:15'! setUp empty := self speciesClass new. nonEmpty := self speciesClass new add: 13; add: -2; add: self elementTwiceIn; add: 10; add: self elementTwiceIn; add: self element; yourself. elementNotIn := 0. collectionIn := self speciesClass new add: -2; add: self elementTwiceIn; add: 10; yourself. collectionNotIn := self speciesClass new add: self elementNotIn; add: 5; yourself. collectionOfString := self speciesClass new add: 1.5; add: 5.5; add: 7.5; yourself. otherCollectionWithoutEqualElements := self speciesClass new add: 1; add: 20; add: 30; add: 40; yourself. collectionWithoutNilMoreThan5 := self speciesClass new add: 1; add: 2; add: 3; add: 4; add: 5; add: 6; yourself. result := self speciesClass new add: SmallInteger; add: SmallInteger; add: SmallInteger; add: SmallInteger; add: SmallInteger; add: SmallInteger; yourself. emptyButAllocatedWith20 := self speciesClass new: 20. collectionWithElement := self speciesClass new add: self element; yourself. collectionWithCharacters := self speciesClass new add: $p; add: $v; add: $i; add: $y; yourself! ! !BagTest methodsFor: 'setup' stamp: 'delaunay 5/11/2009 11:27'! sizeCollection ^ otherCollectionWithoutEqualElements! ! !BagTest methodsFor: 'test - copy' stamp: 'delaunay 4/17/2009 15:26'! elementToAdd ^ 42! ! !BagTest methodsFor: 'test - creation'! testWith "self debug: #testWith" | aCol element | element := self collectionMoreThan5Elements anyOne. aCol := self collectionClass with: element. self assert: (aCol includes: element).! ! !BagTest methodsFor: 'test - creation'! testWithAll "self debug: #testWithAll" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection . aCol := self collectionClass withAll: collection . collection do: [ :each | self assert: (aCol occurrencesOf: each ) = ( collection occurrencesOf: each ) ]. self assert: (aCol size = collection size ).! ! !BagTest methodsFor: 'test - creation'! testWithWith "self debug: #testWithWith" | aCol collection element1 element2 | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 2 . element1 := collection at: 1. element2 := collection at:2. aCol := self collectionClass with: element1 with: element2 . self assert: (aCol occurrencesOf: element1 ) == ( collection occurrencesOf: element1). self assert: (aCol occurrencesOf: element2 ) == ( collection occurrencesOf: element2). ! ! !BagTest methodsFor: 'test - creation'! testWithWithWith "self debug: #testWithWithWith" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom:1 to: 3 . aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3). 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ].! ! !BagTest methodsFor: 'test - creation'! testWithWithWithWith "self debug: #testWithWithWithWith" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 4. aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3) with: ( collection at: 4). 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ].! ! !BagTest methodsFor: 'test - creation'! testWithWithWithWithWith "self debug: #testWithWithWithWithWith" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 5 . aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3) with: (collection at: 4 ) with: ( collection at: 5 ). 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ].! ! !BagTest methodsFor: 'test - equality'! testEqualSign "self debug: #testEqualSign" self deny: (self empty = self nonEmpty).! ! !BagTest methodsFor: 'test - equality'! testEqualSignIsTrueForNonIdenticalButEqualCollections "self debug: #testEqualSignIsTrueForNonIdenticalButEqualCollections" self assert: (self empty = self empty copy). self assert: (self empty copy = self empty). self assert: (self empty copy = self empty copy). self assert: (self nonEmpty = self nonEmpty copy). self assert: (self nonEmpty copy = self nonEmpty). self assert: (self nonEmpty copy = self nonEmpty copy).! ! !BagTest methodsFor: 'test - equality'! testEqualSignOfIdenticalCollectionObjects "self debug: #testEqualSignOfIdenticalCollectionObjects" self assert: (self empty = self empty). self assert: (self nonEmpty = self nonEmpty). ! ! !BagTest methodsFor: 'test - iterate' stamp: 'damienpollet 1/30/2009 17:36'! doWithoutNumber ^ 4! ! !BagTest methodsFor: 'test - iterate' stamp: 'marcus.denker 2/20/2009 16:29'! expectedElementByDetect ^ -2 ! ! !BagTest methodsFor: 'test - iterate' stamp: 'damienpollet 1/30/2009 17:37'! expectedSizeAfterReject ^ 2! ! !BagTest methodsFor: 'test - remove' stamp: 'damienpollet 1/30/2009 17:15'! elementTwiceIn ^ super elementTwiceIn! ! !BagTest methodsFor: 'test - remove' stamp: 'damienpollet 1/30/2009 17:07'! testRemoveElementThatExistsTwice "self debug: #testRemoveElementThatDoesExistsTwice" | size | size := self nonEmpty size. self assert: (self nonEmpty includes: self elementTwiceIn). self nonEmpty remove: self elementTwiceIn. self assert: size - 1 = self nonEmpty size! ! !BagTest methodsFor: 'test - set arithmetic' stamp: 'stephane.ducasse 12/20/2008 22:46'! collectionClass ^ Bag! ! !BagTest methodsFor: 'tests' stamp: 'stephane.ducasse 5/20/2009 18:02'! testCreation "self run: #testCreation" "self debug: #testCreation" | bag | bag := Bag new. self assert: (bag size) = 0. self assert: (bag isEmpty). ! ! !BagTest methodsFor: 'tests' stamp: 'stephane.ducasse 5/20/2009 18:02'! testCumulativeCounts "self run: #testCumulativeCounts" "self debug: #testCumulativeCounts" | bag cumulativeCounts | bag := Bag new. bag add: '1' withOccurrences: 50. bag add: '2' withOccurrences: 40. bag add: '3' withOccurrences: 10. cumulativeCounts := bag cumulativeCounts. self assert: cumulativeCounts size = 3. self assert: cumulativeCounts first = (50 -> '1'). self assert: cumulativeCounts second = (90 -> '2'). self assert: cumulativeCounts third = (100 -> '3'). ! ! !BagTest methodsFor: 'tests' stamp: 'stephane.ducasse 5/20/2009 18:02'! testEqual "(self run: #testEqual)" "(self debug: #testEqual)" | bag1 bag2 | bag1 := Bag new. bag2 := Bag new. self assert: bag1 = bag2. bag1 add: #a; add: #b. bag2 add: #a; add: #a. self deny: bag1 = bag2. self assert: bag1 = bag1. bag1 add: #a. bag2 add: #b. self assert: bag1 = bag2. bag1 add: #c. self deny: bag1 = bag2. bag2 add: #c. self assert: bag1 = bag2! ! !BagTest methodsFor: 'tests' stamp: 'stephane.ducasse 5/20/2009 18:03'! testRemove "self run: #testRemove" "self debug: #testRemove" | bag item | item := 'test item'. bag := Bag new. bag add: item. self assert: (bag size) = 1. bag remove: item. self assert: bag isEmpty. bag add: item withOccurrences: 2. bag remove: item. bag remove: item. self assert: (bag size) = 0. self should: [bag remove: item.] raise: Error.! ! !BagTest methodsFor: 'tests' stamp: 'nice 9/14/2009 21:05'! testRemoveAll "Allows one to remove all elements of a collection" | c1 c2 s2 | c1 := #(10 9 8 7 5 4 4 2) asBag. c2 := c1 copy. s2 := c2 size. c1 removeAll. self assert: c1 size = 0. self assert: c2 size = s2 description: 'the copy has not been modified'.! ! !BagTest methodsFor: 'tests' stamp: 'stephane.ducasse 5/20/2009 18:03'! testSortedCounts "self run: #testSortedCounts" "self debug: #testSortedCounts" | bag sortedCounts| bag := Bag new. bag add: '1' withOccurrences: 10. bag add: '2' withOccurrences: 1. bag add: '3' withOccurrences: 5. sortedCounts := bag sortedCounts. self assert: sortedCounts size = 3. self assert: sortedCounts first = (10->'1'). self assert: sortedCounts second = (5->'3'). self assert: sortedCounts third = (1->'2'). ! ! !BagTest methodsFor: 'tests' stamp: 'stephane.ducasse 5/20/2009 18:03'! testSortedElements "self run: #testSortedElements" "self debug: #testSortedElements" | bag sortedElements| bag := Bag new. bag add: '2' withOccurrences: 1. bag add: '1' withOccurrences: 10. bag add: '3' withOccurrences: 5. sortedElements := bag sortedElements. self assert: sortedElements size = 3. self assert: sortedElements first = ('1'->10). self assert: sortedElements second = ('2'->1). self assert: sortedElements third = ('3'->5). ! ! !BagTest methodsFor: 'tests - adding'! testTAdd | added collection | collection :=self otherCollection . added := collection add: self element. self assert: added == self element. "test for identiy because #add: has not reason to copy its parameter." self assert: (collection includes: self element) . self assert: (self collectionWithElement includes: self element). ! ! !BagTest methodsFor: 'tests - adding'! testTAddAll | added collection toBeAdded | collection := self collectionWithElement . toBeAdded := self otherCollection . added := collection addAll: toBeAdded . self assert: added == toBeAdded . "test for identiy because #addAll: has not reason to copy its parameter." self assert: (collection includesAllOf: toBeAdded )! ! !BagTest methodsFor: 'tests - adding'! testTAddIfNotPresentWithElementAlreadyIn | added oldSize collection element | collection := self collectionWithElement . oldSize := collection size. element := self element . self assert: (collection includes: element ). added := collection addIfNotPresent: element . self assert: added == element . "test for identiy because #add: has not reason to copy its parameter." self assert: collection size = oldSize! ! !BagTest methodsFor: 'tests - adding'! testTAddIfNotPresentWithNewElement | added oldSize collection element | collection := self otherCollection . oldSize := collection size. element := self element . self deny: (collection includes: element ). added := collection addIfNotPresent: element . self assert: added == element . "test for identiy because #add: has not reason to copy its parameter." self assert: (collection size = (oldSize + 1)). ! ! !BagTest methodsFor: 'tests - adding'! testTAddTwice | added oldSize collection element | collection := self collectionWithElement . element := self element . oldSize := collection size. added := collection add: element ; add: element . self assert: added == element . "test for identiy because #add: has not reason to copy its parameter." self assert: (collection includes: element ). self assert: collection size = (oldSize + 2)! ! !BagTest methodsFor: 'tests - adding'! testTAddWithOccurences | added oldSize collection element | collection := self collectionWithElement . element := self element . oldSize := collection size. added := collection add: element withOccurrences: 5. self assert: added == element. "test for identiy because #add: has not reason to copy its parameter." self assert: (collection includes: element). self assert: collection size = (oldSize + 5)! ! !BagTest methodsFor: 'tests - adding'! testTWrite | added collection element | collection := self otherCollection . element := self element . added := collection write: element . self assert: added == element . "test for identiy because #add: has not reason to copy its parameter." self assert: (collection includes: element ) . self assert: (collection includes: element ). ! ! !BagTest methodsFor: 'tests - adding'! testTWriteTwice | added oldSize collection element | collection := self collectionWithElement . element := self element . oldSize := collection size. added := collection write: element ; write: element . self assert: added == element . "test for identiy because #add: has not reason to copy its parameter." self assert: (collection includes: element ). self assert: collection size = (oldSize + 2)! ! !BagTest methodsFor: 'tests - as set tests'! testAsIdentitySetWithEqualsElements | result collection | collection := self withEqualElements . result := collection asIdentitySet. collection do: [ :each | self assert: (result occurrencesOf: each) = 1 ]. self assert: result class = IdentitySet.! ! !BagTest methodsFor: 'tests - as set tests'! testAsSetWithEqualsElements | result | result := self withEqualElements asSet. self withEqualElements do: [ :each | self assert: (result occurrencesOf: each) = 1 ]. self assert: result class = Set! ! !BagTest methodsFor: 'tests - as sorted collection'! testAsSortedArray | result collection | collection := self collectionWithSortableElements . result := collection asSortedArray. self assert: (result class includesBehavior: Array). self assert: result isSorted. self assert: result size = collection size! ! !BagTest methodsFor: 'tests - as sorted collection'! testAsSortedCollection | aCollection result | aCollection := self collectionWithSortableElements . result := aCollection asSortedCollection. self assert: (result class includesBehavior: SortedCollection). result do: [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. self assert: result size = aCollection size.! ! !BagTest methodsFor: 'tests - as sorted collection'! testAsSortedCollectionWithSortBlock | result tmp | result := self collectionWithSortableElements asSortedCollection: [:a :b | a > b]. self assert: (result class includesBehavior: SortedCollection). result do: [ :each | self assert: (self collectionWithSortableElements occurrencesOf: each) = (result occurrencesOf: each) ]. self assert: result size = self collectionWithSortableElements size. tmp:=result at: 1. result do: [:each| self assert: tmp>=each. tmp:=each]. ! ! !BagTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsCommaStringEmpty self assert: self empty asCommaString = ''. self assert: self empty asCommaStringAnd = ''. ! ! !BagTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsCommaStringMore | result resultAnd index allElementsAsString tmp | result:= self nonEmpty asCommaString . resultAnd:= self nonEmpty asCommaStringAnd . tmp :=OrderedCollection new. self nonEmpty do: [ :each | tmp add: each asString]. "verifying result :" index := 1. allElementsAsString := (result findBetweenSubStrs: ', ' ). allElementsAsString do: [:each | self assert: (tmp occurrencesOf: each)=(allElementsAsString occurrencesOf: each). ]. "verifying esultAnd :" allElementsAsString:=(resultAnd findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) | i= allElementsAsString size ifTrue: [self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i))]. i=(allElementsAsString size-1) ifTrue:[ self assert: (allElementsAsString at:i)=('and')]. ].! ! !BagTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsCommaStringOne self nonEmpty1Element do: [:each | self assert: each asString =self nonEmpty1Element asCommaString. self assert: each asString=self nonEmpty1Element asCommaStringAnd.]. ! ! !BagTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterEmpty | delim emptyStream | delim := ', '. emptyStream := ReadWriteStream on: ''. self empty asStringOn: emptyStream delimiter: delim. self assert: emptyStream contents = ''. ! ! !BagTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterLastEmpty | delim emptyStream | delim := ', '. emptyStream := ReadWriteStream on: ''. self empty asStringOn: emptyStream delimiter: delim last:'and'. self assert: emptyStream contents = ''. ! ! !BagTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterLastMore | delim multiItemStream result last allElementsAsString tmp | delim := ', '. last := 'and'. result:=''. tmp := self nonEmpty collect: [:each | each asString]. multiItemStream := ReadWriteStream on:result. self nonEmpty asStringOn: multiItemStream delimiter: ', ' last: last. allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) | i= allElementsAsString size ifTrue: [self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i))]. i=(allElementsAsString size-1) ifTrue:[ self assert: (allElementsAsString at:i)=('and')]. ]. ! ! !BagTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterLastOne | delim oneItemStream result | delim := ', '. result:=''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim last: 'and'. oneItemStream do: [:each1 | self nonEmpty1Element do: [:each2 |self assert: each1 = (each2 asString) ] ]. ! ! !BagTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterMore | delim multiItemStream result allElementsAsString tmp | delim := ', '. result:=''. tmp:= self nonEmpty collect:[:each | each asString]. multiItemStream := ReadWriteStream on:result. self nonEmpty asStringOn: multiItemStream delimiter: ', '. allElementsAsString := (result findBetweenSubStrs: ', ' ). allElementsAsString do: [:each | self assert: (tmp occurrencesOf: each)=(allElementsAsString occurrencesOf: each). ].! ! !BagTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterOne | delim oneItemStream result | delim := ', '. result:=''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim. oneItemStream do: [:each1 | self nonEmpty1Element do: [:each2 |self assert: each1 = (each2 asString) ] ]. ! ! !BagTest methodsFor: 'tests - concatenation'! testConcatenation "| collection1 collection2 result | collection1 := self firstCollection . collection2 := self secondCollection . result := collection1 , collection2. collection1 do:[ :each | self assert: (result includes: each)]. collection2 do:[ :each | self assert: (result includes: each)]." | collection1 collection2 result | collection1 := self firstCollection . collection2 := self secondCollection . result := collection1 , collection2. result do: [ :each | self assert: (result occurrencesOf: each) = (( collection1 occurrencesOf: each ) + ( collection2 occurrencesOf: each ) ). ]. self assert: result size = (collection1 size + collection2 size)! ! !BagTest methodsFor: 'tests - concatenation'! testConcatenationWithDuplicate | collection1 collection2 result | collection1 := self firstCollection . collection2 := self firstCollection . result := collection1 , collection2. result do: [ :each | self assert: (result occurrencesOf: each) = (( collection1 occurrencesOf: each ) + ( collection2 occurrencesOf: each ) ). ]. self assert: result size = (collection1 size * 2)! ! !BagTest methodsFor: 'tests - concatenation'! testConcatenationWithEmpty | result | result := self firstCollection , self empty. self assert: result = self firstCollection! ! !BagTest methodsFor: 'tests - converting'! assertNoDuplicates: aCollection whenConvertedTo: aClass | result | result := self collectionWithEqualElements asIdentitySet. self assert: (result class includesBehavior: IdentitySet). self collectionWithEqualElements do: [ :initial | self assert: (result occurrencesOf: initial) = 1 ]! ! !BagTest methodsFor: 'tests - converting'! assertNonDuplicatedContents: aCollection whenConvertedTo: aClass | result | result := aCollection perform: ('as' , aClass name) asSymbol. self assert: (result class includesBehavior: aClass). result do: [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. ^ result! ! !BagTest methodsFor: 'tests - converting'! assertSameContents: aCollection whenConvertedTo: aClass | result | result := self assertNonDuplicatedContents: aCollection whenConvertedTo: aClass. self assert: result size = aCollection size! ! !BagTest methodsFor: 'tests - converting'! testAsArray "self debug: #testAsArray3" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Array! ! !BagTest methodsFor: 'tests - converting'! testAsByteArray | res | self shouldnt: [self integerCollectionWithoutEqualElements ] raise: Error. self integerCollectionWithoutEqualElements do: [ :each | self assert: each class = SmallInteger] . res := true. self integerCollectionWithoutEqualElements detect: [ :each | (self integerCollectionWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false. self assertSameContents: self integerCollectionWithoutEqualElements whenConvertedTo: ByteArray! ! !BagTest methodsFor: 'tests - converting'! testAsIdentitySet "test with a collection without equal elements :" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: IdentitySet. ! ! !BagTest methodsFor: 'tests - converting'! testAsOrderedCollection self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: OrderedCollection! ! !BagTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:26'! testCopyEmptyWith "self debug: #testCopyWith" | res | res := self empty copyWith: self elementToAdd. self assert: res size = (self empty size + 1). self assert: (res includes: self elementToAdd)! ! !BagTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:26'! testCopyEmptyWithout "self debug: #testCopyEmptyWithout" | res | res := self empty copyWithout: self elementToAdd. self assert: res size = self empty size. self deny: (res includes: self elementToAdd)! ! !BagTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:24'! testCopyEmptyWithoutAll "self debug: #testCopyEmptyWithoutAll" | res | res := self empty copyWithoutAll: self collectionWithElementsToRemove. self assert: res size = self empty size. self collectionWithElementsToRemove do: [ :each | self deny: (res includes: each) ]! ! !BagTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:26'! testCopyNonEmptyWith "self debug: #testCopyNonEmptyWith" | res | res := self nonEmpty copyWith: self elementToAdd. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self assert: (res includes: self elementToAdd). self nonEmpty do: [ :each | res includes: each ]! ! !BagTest methodsFor: 'tests - copy'! testCopyNonEmptyWithout "self debug: #testCopyNonEmptyWithout" | res anElementOfTheCollection | anElementOfTheCollection := self nonEmpty anyOne. res := (self nonEmpty copyWithout: anElementOfTheCollection). "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self deny: (res includes: anElementOfTheCollection). self nonEmpty do: [:each | (each = anElementOfTheCollection) ifFalse: [self assert: (res includes: each)]]. ! ! !BagTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:24'! testCopyNonEmptyWithoutAll "self debug: #testCopyNonEmptyWithoutAll" | res | res := self nonEmpty copyWithoutAll: self collectionWithElementsToRemove. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self collectionWithElementsToRemove do: [ :each | self deny: (res includes: each) ]. self nonEmpty do: [ :each | (self collectionWithElementsToRemove includes: each) ifFalse: [ self assert: (res includes: each) ] ]! ! !BagTest methodsFor: 'tests - copy' stamp: 'delaunay 3/30/2009 10:33'! testCopyNonEmptyWithoutAllNotIncluded ! ! !BagTest methodsFor: 'tests - copy' stamp: 'delaunay 4/17/2009 15:26'! testCopyNonEmptyWithoutNotIncluded "self debug: #testCopyNonEmptyWithoutNotIncluded" | res | res := self nonEmpty copyWithout: self elementToAdd. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self nonEmpty do: [ :each | self assert: (res includes: each) ]! ! !BagTest methodsFor: 'tests - copy - clone'! testCopyCreatesNewObject "self debug: #testCopyCreatesNewObject" | copy | copy := self nonEmpty copy. self deny: self nonEmpty == copy. ! ! !BagTest methodsFor: 'tests - copy - clone'! testCopyEmpty "self debug: #testCopyEmpty" | copy | copy := self empty copy. self assert: copy isEmpty.! ! !BagTest methodsFor: 'tests - copy - clone'! testCopyNonEmpty "self debug: #testCopyNonEmpty" | copy | copy := self nonEmpty copy. self deny: copy isEmpty. self assert: copy size = self nonEmpty size. self nonEmpty do: [:each | copy includes: each]! ! !BagTest methodsFor: 'tests - fixture' stamp: 'delaunay 4/17/2009 15:26'! test0CopyTest self shouldnt: self empty raise: Error. self assert: self empty size = 0. self shouldnt: self nonEmpty raise: Error. self assert: (self nonEmpty size = 0) not. self shouldnt: self collectionWithElementsToRemove raise: Error. self assert: (self collectionWithElementsToRemove size = 0) not. self shouldnt: self elementToAdd raise: Error! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureAsStringCommaAndDelimiterTest self shouldnt: [self nonEmpty] raise:Error . self deny: self nonEmpty isEmpty. self shouldnt: [self empty] raise:Error . self assert: self empty isEmpty. self shouldnt: [self nonEmpty1Element ] raise:Error . self assert: self nonEmpty1Element size=1.! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureCloneTest self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty. ! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureConcatenationTest self shouldnt: [ self firstCollection ]raise: Error. self deny: self firstCollection isEmpty. self shouldnt: [ self firstCollection ]raise: Error. self deny: self firstCollection isEmpty. self shouldnt: [ self empty ]raise: Error. self assert: self empty isEmpty! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureConverAsSortedTest self shouldnt: [self collectionWithSortableElements ] raise: Error. self deny: self collectionWithSortableElements isEmpty .! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureCreationWithTest self shouldnt: [ self collectionMoreThan5Elements ] raise: Error. self assert: self collectionMoreThan5Elements size >= 5.! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureIncludeTest | elementIn | self shouldnt: [ self nonEmpty ]raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self elementNotIn ]raise: Error. elementIn := true. self nonEmpty detect: [ :each | each = self elementNotIn ] ifNone: [ elementIn := false ]. self assert: elementIn = false. self shouldnt: [ self anotherElementNotIn ]raise: Error. elementIn := true. self nonEmpty detect: [ :each | each = self anotherElementNotIn ] ifNone: [ elementIn := false ]. self assert: elementIn = false. self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty. ! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureIncludeWithIdentityTest | element | self shouldnt: [ self collectionWithCopyNonIdentical ]raise: Error. element := self collectionWithCopyNonIdentical anyOne. self deny: element == element copy. ! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureOccurrencesForMultiplinessTest | cpt element collection | self shouldnt: [self collectionWithEqualElements ]raise: Error. self shouldnt: [self collectionWithEqualElements ]raise: Error. self shouldnt: [ self elementTwiceInForOccurrences ] raise: Error. element := self elementTwiceInForOccurrences . collection := self collectionWithEqualElements . cpt := 0 . " testing with identity check ( == ) so that identy collections can use this trait : " self collectionWithEqualElements do: [ :each | each == self elementTwiceInForOccurrences ifTrue: [ cpt := cpt + 1 ] ]. self assert: cpt = 2.! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureOccurrencesTest | tmp | self shouldnt: [self empty ]raise: Error. self assert: self empty isEmpty. self shouldnt: [ self collectionWithoutEqualElements ] raise: Error. self deny: self collectionWithoutEqualElements isEmpty. tmp := OrderedCollection new. self collectionWithoutEqualElements do: [ :each | self deny: (tmp includes: each). tmp add: each. ]. self shouldnt: [ self elementNotInForOccurrences ] raise: Error. self deny: (self collectionWithoutEqualElements includes: self elementNotInForOccurrences)! ! !BagTest methodsFor: 'tests - fixture'! test0FixturePrintTest self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty.! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureRequirementsOfTAddTest self shouldnt: [ self collectionWithElement ] raise: Exception. self shouldnt: [ self otherCollection ] raise: Exception. self shouldnt: [ self element ] raise: Exception. self assert: (self collectionWithElement includes: self element). self deny: (self otherCollection includes: self element)! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureSetAritmeticTest self shouldnt: [ self collection ] raise: Error. self deny: self collection isEmpty. self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self anotherElementOrAssociationNotIn ] raise: Error. self collection isDictionary ifTrue: [ self deny: (self collection associations includes: self anotherElementOrAssociationNotIn key) ] ifFalse: [ self deny: (self collection includes: self anotherElementOrAssociationNotIn) ]. self shouldnt: [ self collectionClass ] raise: Error! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureTConvertAsSetForMultiplinessTest "a collection with equal elements:" | res | self shouldnt: [ self withEqualElements] raise: Error. res := true. self withEqualElements detect: [ :each | (self withEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = true. ! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureTConvertTest "a collection of number without equal elements:" | res | self shouldnt: [ self collectionWithoutEqualElements ]raise: Error. res := true. self collectionWithoutEqualElements detect: [ :each | (self collectionWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false. ! ! !BagTest methodsFor: 'tests - fixture'! test0FixtureTRemoveTest | duplicate | self shouldnt: [ self empty ]raise: Error. self shouldnt: [ self nonEmptyWithoutEqualElements] raise:Error. self deny: self nonEmptyWithoutEqualElements isEmpty. duplicate := true. self nonEmptyWithoutEqualElements detect: [:each | (self nonEmptyWithoutEqualElements occurrencesOf: each) > 1] ifNone: [duplicate := false]. self assert: duplicate = false. self shouldnt: [ self elementNotIn ] raise: Error. self assert: self empty isEmpty. self deny: self nonEmptyWithoutEqualElements isEmpty. self deny: (self nonEmptyWithoutEqualElements includes: self elementNotIn)! ! !BagTest methodsFor: 'tests - fixture'! test0TStructuralEqualityTest self shouldnt: [self empty] raise: Error. self shouldnt: [self nonEmpty] raise: Error. self assert: self empty isEmpty. self deny: self nonEmpty isEmpty.! ! !BagTest methodsFor: 'tests - includes' stamp: 'stephane.ducasse 11/21/2008 14:58'! anotherElementNotIn ^ 42! ! !BagTest methodsFor: 'tests - includes' stamp: 'delaunay 4/2/2009 11:53'! elementNotInForOccurrences ^ 666! ! !BagTest methodsFor: 'tests - includes' stamp: 'delaunay 4/28/2009 10:22'! testIdentityIncludes " test the comportement in presence of elements 'includes' but not 'identityIncludes' " " can not be used by collections that can't include elements for wich copy doesn't return another instance " | collection element | self shouldnt: [ self collectionWithCopyNonIdentical ] raise: Error. collection := self collectionWithCopyNonIdentical. element := collection anyOne copy. "self assert: (collection includes: element)." self deny: (collection identityIncludes: element)! ! !BagTest methodsFor: 'tests - includes'! testIdentityIncludesNonSpecificComportement " test the same comportement than 'includes: ' " | collection | collection := self nonEmpty . self deny: (collection identityIncludes: self elementNotIn ). self assert:(collection identityIncludes: collection anyOne) ! ! !BagTest methodsFor: 'tests - includes'! testIncludesAllOfAllThere "self debug: #testIncludesAllOfAllThere'" self assert: (self empty includesAllOf: self empty). self assert: (self nonEmpty includesAllOf: { self nonEmpty anyOne }). self assert: (self nonEmpty includesAllOf: self nonEmpty).! ! !BagTest methodsFor: 'tests - includes' stamp: 'delaunay 4/2/2009 11:53'! testIncludesAllOfNoneThere "self debug: #testIncludesAllOfNoneThere'" self deny: (self empty includesAllOf: self collection). self deny: (self nonEmpty includesAllOf: { (self elementNotIn). (self anotherElementNotIn) })! ! !BagTest methodsFor: 'tests - includes'! testIncludesAnyOfAllThere "self debug: #testIncludesAnyOfAllThere'" self deny: (self nonEmpty includesAnyOf: self empty). self assert: (self nonEmpty includesAnyOf: { self nonEmpty anyOne }). self assert: (self nonEmpty includesAnyOf: self nonEmpty).! ! !BagTest methodsFor: 'tests - includes' stamp: 'delaunay 4/2/2009 11:53'! testIncludesAnyOfNoneThere "self debug: #testIncludesAnyOfNoneThere'" self deny: (self nonEmpty includesAnyOf: self empty). self deny: (self nonEmpty includesAnyOf: { (self elementNotIn). (self anotherElementNotIn) })! ! !BagTest methodsFor: 'tests - includes' stamp: 'delaunay 4/2/2009 11:53'! testIncludesElementIsNotThere "self debug: #testIncludesElementIsNotThere" self deny: (self nonEmpty includes: self elementNotInForOccurrences). self assert: (self nonEmpty includes: self nonEmpty anyOne). self deny: (self empty includes: self elementNotInForOccurrences)! ! !BagTest methodsFor: 'tests - includes'! testIncludesElementIsThere "self debug: #testIncludesElementIsThere" self assert: (self nonEmpty includes: self nonEmpty anyOne).! ! !BagTest methodsFor: 'tests - includes' stamp: 'delaunay 4/9/2009 10:44'! testIncludesSubstringAnywhere "self debug: #testIncludesSubstringAnywher'" self assert: (self empty includesAllOf: self empty). self assert: (self nonEmpty includesAllOf: { (self nonEmpty anyOne) }). self assert: (self nonEmpty includesAllOf: self nonEmpty)! ! !BagTest methodsFor: 'tests - occurrencesOf'! testOccurrencesOfEmpty | result | result := self empty occurrencesOf: (self collectionWithoutEqualElements anyOne). self assert: result = 0! ! !BagTest methodsFor: 'tests - occurrencesOf'! testOccurrencesOfNotIn | result | result := self collectionWithoutEqualElements occurrencesOf: self elementNotInForOccurrences. self assert: result = 0! ! !BagTest methodsFor: 'tests - occurrencesOf for multipliness'! testOccurrencesOfForMultipliness | collection element | collection := self collectionWithEqualElements . element := self elementTwiceInForOccurrences . self assert: (collection occurrencesOf: element ) = 2. ! ! !BagTest methodsFor: 'tests - printing'! testPrintElementsOn | aStream result allElementsAsString tmp | result:=''. aStream:= ReadWriteStream on: result. tmp:= OrderedCollection new. self nonEmpty do: [:each | tmp add: each asString]. self nonEmpty printElementsOn: aStream . allElementsAsString:=(result findBetweenSubStrs: ' ' ). 1 to: allElementsAsString size do: [:i | self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i)). ].! ! !BagTest methodsFor: 'tests - printing'! testPrintNameOn | aStream result | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printNameOn: aStream . Transcript show: result asString. self nonEmpty class name first isVowel ifTrue:[ self assert: aStream contents =('an ',self nonEmpty class name ) ] ifFalse:[self assert: aStream contents =('a ',self nonEmpty class name)].! ! !BagTest methodsFor: 'tests - printing'! testPrintOn | aStream result allElementsAsString tmp | result:=''. aStream:= ReadWriteStream on: result. tmp:= OrderedCollection new. self nonEmpty do: [:each | tmp add: each asString]. self nonEmpty printOn: aStream . allElementsAsString:=(result findBetweenSubStrs: ' ' ). 1 to: allElementsAsString size do: [:i | i=1 ifTrue:[ self accessCollection class name first isVowel ifTrue:[self assert: (allElementsAsString at:i)='an' ] ifFalse:[self assert: (allElementsAsString at:i)='a'].]. i=2 ifTrue:[self assert: (allElementsAsString at:i)=self accessCollection class name]. i>2 ifTrue:[self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i)).]. ].! ! !BagTest methodsFor: 'tests - printing'! testPrintOnDelimiter | aStream result allElementsAsString tmp | result:=''. aStream:= ReadWriteStream on: result. tmp:= OrderedCollection new. self nonEmpty do: [:each | tmp add: each asString]. self nonEmpty printOn: aStream delimiter: ', ' . allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i)) ].! ! !BagTest methodsFor: 'tests - printing'! testPrintOnDelimiterLast | aStream result allElementsAsString tmp | result:=''. aStream:= ReadWriteStream on: result. tmp:= OrderedCollection new. self nonEmpty do: [:each | tmp add: each asString]. self nonEmpty printOn: aStream delimiter: ', ' last: 'and'. allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) ifTrue: [self assert: (tmp occurrencesOf: (allElementsAsString at:i))=(allElementsAsString occurrencesOf: (allElementsAsString at:i))]. i=(allElementsAsString size-1) ifTrue:[ self deny: (allElementsAsString at:i)=('and')asString]. i=(allElementsAsString size) ifTrue: [self assert: (tmp occurrencesOf: (allElementsAsString at:i))=(allElementsAsString occurrencesOf: (allElementsAsString at:i))]. ].! ! !BagTest methodsFor: 'tests - printing'! testStoreOn " for the moment work only for collection that include simple elements such that Integer" "| string str result cuttedResult index elementsAsStringExpected elementsAsStringObtained tmp | string := ''. str := ReadWriteStream on: string. elementsAsStringExpected := OrderedCollection new. elementsAsStringObtained := OrderedCollection new. self nonEmpty do: [ :each | elementsAsStringExpected add: each asString]. self nonEmpty storeOn: str. result := str contents . cuttedResult := ( result findBetweenSubStrs: ';' ). index := 1. cuttedResult do: [ :each | index = 1 ifTrue: [ self assert: (each beginsWith: ( tmp := '((' , self nonEmpty class asString , ' new) add: ' )). tmp := each copyFrom: ( tmp size + 1) to: ( each size ). elementsAsStringObtained add: tmp. index := index + 1. ] ifFalse: [ index < cuttedResult size ifTrue:[self assert: (each beginsWith: ( tmp:= ' add: ' )). tmp := each copyFrom: ( tmp size + 1) to: ( each size ). elementsAsStringObtained add: tmp. index := index + 1.] ifFalse: [self assert: ( each = ' yourself)' ) ]. ] ]. elementsAsStringExpected do: [ :each | self assert: (elementsAsStringExpected occurrencesOf: each ) = ( elementsAsStringObtained occurrencesOf: each) ]" ! ! !BagTest methodsFor: 'tests - remove'! testRemoveAllError "self debug: #testRemoveElementThatExists" | el res subCollection | el := self elementNotIn. subCollection := self nonEmptyWithoutEqualElements copyWith: el. self should: [ res := self nonEmptyWithoutEqualElements removeAll: subCollection ] raise: Error! ! !BagTest methodsFor: 'tests - remove'! testRemoveAllFoundIn "self debug: #testRemoveElementThatExists" | el res subCollection | el := self nonEmptyWithoutEqualElements anyOne. subCollection := (self nonEmptyWithoutEqualElements copyWithout: el) copyWith: self elementNotIn. self shouldnt: [ res := self nonEmptyWithoutEqualElements removeAllFoundIn: subCollection ] raise: Error. self assert: self nonEmptyWithoutEqualElements size = 1. self nonEmptyWithoutEqualElements do: [ :each | self assert: each = el ]! ! !BagTest methodsFor: 'tests - remove'! testRemoveAllSuchThat "self debug: #testRemoveElementThatExists" | el subCollection | el := self nonEmptyWithoutEqualElements anyOne. subCollection := self nonEmptyWithoutEqualElements copyWithout: el. self nonEmptyWithoutEqualElements removeAllSuchThat: [ :each | subCollection includes: each ]. self assert: self nonEmptyWithoutEqualElements size = 1. self nonEmptyWithoutEqualElements do: [ :each | self assert: each = el ]! ! !BagTest methodsFor: 'tests - remove'! testRemoveElementFromEmpty "self debug: #testRemoveElementFromEmpty" self should: [ self empty remove: self nonEmptyWithoutEqualElements anyOne ] raise: Error! ! !BagTest methodsFor: 'tests - remove'! testRemoveElementReallyRemovesElement "self debug: #testRemoveElementReallyRemovesElement" | size | size := self nonEmptyWithoutEqualElements size. self nonEmptyWithoutEqualElements remove: self nonEmptyWithoutEqualElements anyOne. self assert: size - 1 = self nonEmptyWithoutEqualElements size! ! !BagTest methodsFor: 'tests - remove'! testRemoveElementThatExists "self debug: #testRemoveElementThatExists" | el res | el := self nonEmptyWithoutEqualElements anyOne. self shouldnt: [ res := self nonEmptyWithoutEqualElements remove: el ] raise: Error. self assert: res == el! ! !BagTest methodsFor: 'tests - remove'! testRemoveIfAbsent "self debug: #testRemoveElementThatExists" | el res | el := self elementNotIn. self shouldnt: [ res := self nonEmptyWithoutEqualElements remove: el ifAbsent: [ 33 ] ] raise: Error. self assert: res == 33! ! !BagTest methodsFor: 'tests - set arithmetic'! containsAll: union of: one andOf: another self assert: (one allSatisfy: [:each | union includes: each]). self assert: (another allSatisfy: [:each | union includes: each])! ! !BagTest methodsFor: 'tests - set arithmetic'! numberOfSimilarElementsInIntersection ^ self collection occurrencesOf: self anotherElementOrAssociationIn! ! !BagTest methodsFor: 'tests - set arithmetic'! testDifference "Answer the set theoretic difference of two collections." "self debug: #testDifference" self assert: (self collection difference: self collection) isEmpty. self assert: (self empty difference: self collection) isEmpty. self assert: (self collection difference: self empty) = self collection ! ! !BagTest methodsFor: 'tests - set arithmetic'! testDifferenceWithNonNullIntersection "Answer the set theoretic difference of two collections." "self debug: #testDifferenceWithNonNullIntersection" " #(1 2 3) difference: #(2 4) -> #(1 3)" | res overlapping | overlapping := self collectionClass with: self anotherElementOrAssociationNotIn with: self anotherElementOrAssociationIn. res := self collection difference: overlapping. self deny: (res includes: self anotherElementOrAssociationIn). overlapping do: [ :each | self deny: (res includes: each) ]! ! !BagTest methodsFor: 'tests - set arithmetic'! testDifferenceWithSeparateCollection "Answer the set theoretic difference of two collections." "self debug: #testDifferenceWithSeparateCollection" | res separateCol | separateCol := self collectionClass with: self anotherElementOrAssociationNotIn. res := self collection difference: separateCol. self deny: (res includes: self anotherElementOrAssociationNotIn). self assert: res = self collection. res := separateCol difference: self collection. self deny: (res includes: self collection anyOne). self assert: res = separateCol! ! !BagTest methodsFor: 'tests - set arithmetic'! testIntersectionBasic "self debug: #testIntersectionBasic" | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). self deny: inter isEmpty. self assert: (inter includes: self anotherElementOrAssociationIn value)! ! !BagTest methodsFor: 'tests - set arithmetic'! testIntersectionEmpty "self debug: #testIntersectionEmpty" | inter | inter := self empty intersection: self empty. self assert: inter isEmpty. inter := self empty intersection: self collection . self assert: inter = self empty. ! ! !BagTest methodsFor: 'tests - set arithmetic'! testIntersectionItself "self debug: #testIntersectionItself" self assert: (self collection intersection: self collection) = self collection. ! ! !BagTest methodsFor: 'tests - set arithmetic'! testIntersectionTwoSimilarElementsInIntersection "self debug: #testIntersectionBasic" | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). self assert: (self collection occurrencesOf: self anotherElementOrAssociationIn) = self numberOfSimilarElementsInIntersection. self assert: (inter includes: self anotherElementOrAssociationIn value)! ! !BagTest methodsFor: 'tests - set arithmetic'! testUnion "self debug: #testUnionOfEmpties" | union | union := self empty union: self nonEmpty. self containsAll: union of: self empty andOf: self nonEmpty. union := self nonEmpty union: self empty. self containsAll: union of: self empty andOf: self nonEmpty. union := self collection union: self nonEmpty. self containsAll: union of: self collection andOf: self nonEmpty.! ! !BagTest methodsFor: 'tests - set arithmetic'! testUnionOfEmpties "self debug: #testUnionOfEmpties" self assert: (self empty union: self empty) isEmpty. ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BagTest class uses: TAddTest classTrait + TCloneTest classTrait + TCopyTest classTrait + TSetArithmetic classTrait + TConvertTest classTrait + TAsStringCommaAndDelimiterTest classTrait + TRemoveForMultiplenessTest classTrait + TPrintTest classTrait + TConvertAsSortedTest classTrait + TIncludesWithIdentityCheckTest classTrait + TConvertAsSetForMultiplinessTest classTrait + TConcatenationTest classTrait + TStructuralEqualityTest classTrait + TCreationWithTest classTrait + TOccurrencesForMultiplinessTest classTrait instanceVariableNames: ''! Object subclass: #BalloonBezierSimulation instanceVariableNames: 'start end via lastX lastY fwDx fwDy fwDDx fwDDy maxSteps' classVariableNames: 'HeightSubdivisions LineConversions MonotonSubdivisions OverflowSubdivisions' poolDictionaries: '' category: 'Balloon-Simulation'! !BalloonBezierSimulation commentStamp: '' prior: 0! This class is a simulation of the code that's run by the Balloon engine. For debugging purposes only.! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'! end ^end! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'! end: aPoint end := aPoint! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/30/1998 01:57'! inTangent "Return the tangent at the start point" ^via - start! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'! initialX ^start y <= end y ifTrue:[start x] ifFalse:[end x]! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'! initialY ^start y <= end y ifTrue:[start y] ifFalse:[end y]! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'! initialZ ^0 "Assume no depth given"! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/30/1998 01:57'! outTangent "Return the tangent at the end point" ^end - via! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'! start ^start! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'! start: aPoint start := aPoint! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'! via ^via! ! !BalloonBezierSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:45'! via: aPoint via := aPoint! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/27/1998 20:46'! computeInitialStateFrom: source with: transformation "Compute the initial state in the receiver." start := (transformation localPointToGlobal: source start) asIntegerPoint. end := (transformation localPointToGlobal: source end) asIntegerPoint. via := (transformation localPointToGlobal: source via) asIntegerPoint.! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 02:39'! computeSplitAt: t "Split the receiver at the parametric value t" | left right newVia1 newVia2 newPoint | left := self clone. right := self clone. "Compute new intermediate points" newVia1 := (via - start) * t + start. newVia2 := (end - via) * t + via. "Compute new point on curve" newPoint := ((newVia1 - newVia2) * t + newVia2) asIntegerPoint. left via: newVia1 asIntegerPoint. left end: newPoint. right start: newPoint. right via: newVia2 asIntegerPoint. ^Array with: left with: right! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 01:34'! floatStepToFirstScanLineAt: yValue in: edgeTableEntry "Float version of forward differencing" | startX endX startY endY deltaY fwX1 fwX2 fwY1 fwY2 steps scaledStepSize squaredStepSize | (end y) >= (start y) ifTrue:[ startX := start x. endX := end x. startY := start y. endY := end y. ] ifFalse:[ startX := end x. endX := start x. startY := end y. endY := start y. ]. deltaY := endY - startY. "Quickly check if the line is visible at all" (yValue >= endY or:[deltaY = 0]) ifTrue:[ ^edgeTableEntry lines: 0]. fwX1 := (startX + endX - (2 * via x)) asFloat. fwX2 := (via x - startX * 2) asFloat. fwY1 := (startY + endY - (2 * via y)) asFloat. fwY2 := ((via y - startY) * 2) asFloat. steps := deltaY asInteger * 2. scaledStepSize := 1.0 / steps asFloat. squaredStepSize := scaledStepSize * scaledStepSize. fwDx := fwX2 * scaledStepSize. fwDDx := 2.0 * fwX1 * squaredStepSize. fwDy := fwY2 * scaledStepSize. fwDDy := 2.0 * fwY1 * squaredStepSize. fwDx := fwDx + (fwDDx * 0.5). fwDy := fwDy + (fwDDy * 0.5). lastX := startX asFloat. lastY := startY asFloat. "self xDirection: xDir. self yDirection: yDir." edgeTableEntry xValue: startX. edgeTableEntry yValue: startY. edgeTableEntry zValue: 0. edgeTableEntry lines: deltaY. "If not at first scan line then step down to yValue" yValue = startY ifFalse:[ self stepToNextScanLineAt: yValue in: edgeTableEntry. "And adjust remainingLines" edgeTableEntry lines: deltaY - (yValue - startY). ].! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 02:45'! floatStepToNextScanLineAt: yValue in: edgeTableEntry "Float version of forward differencing" [yValue asFloat > lastY] whileTrue:[ (fwDx < -50.0 or:[fwDx > 50.0]) ifTrue:[self halt]. (fwDy < -50.0 or:[fwDy > 50.0]) ifTrue:[self halt]. (fwDDx < -50.0 or:[fwDDx > 50.0]) ifTrue:[self halt]. (fwDDy < -50.0 or:[fwDDy > 50.0]) ifTrue:[self halt]. lastX := lastX + fwDx. lastY := lastY + fwDy. fwDx := fwDx + fwDDx. fwDy := fwDy + fwDDy. ]. edgeTableEntry xValue: lastX asInteger. edgeTableEntry zValue: 0.! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 16:23'! intStepToFirstScanLineAt: yValue in: edgeTableEntry "Scaled integer version of forward differencing" | startX endX startY endY deltaY fwX1 fwX2 fwY1 fwY2 scaledStepSize squaredStepSize | (end y) >= (start y) ifTrue:[ startX := start x. endX := end x. startY := start y. endY := end y. ] ifFalse:[ startX := end x. endX := start x. startY := end y. endY := start y. ]. deltaY := endY - startY. "Quickly check if the line is visible at all" (yValue >= endY or:[deltaY = 0]) ifTrue:[ ^edgeTableEntry lines: 0]. fwX1 := (startX + endX - (2 * via x)). fwX2 := (via x - startX * 2). fwY1 := (startY + endY - (2 * via y)). fwY2 := ((via y - startY) * 2). maxSteps := deltaY asInteger * 2. scaledStepSize := 16r1000000 // maxSteps. "@@: Okay, we need some fancy 64bit multiplication here" squaredStepSize := self absoluteSquared8Dot24: scaledStepSize. squaredStepSize = ((scaledStepSize * scaledStepSize) bitShift: -24) ifFalse:[self error:'Bad computation']. fwDx := fwX2 * scaledStepSize. fwDDx := 2 * fwX1 * squaredStepSize. fwDy := fwY2 * scaledStepSize. fwDDy := 2 * fwY1 * squaredStepSize. fwDx := fwDx + (fwDDx // 2). fwDy := fwDy + (fwDDy // 2). self validateIntegerRange. lastX := startX * 256. lastY := startY * 256. edgeTableEntry xValue: startX. edgeTableEntry yValue: startY. edgeTableEntry zValue: 0. edgeTableEntry lines: deltaY. "If not at first scan line then step down to yValue" yValue = startY ifFalse:[ self stepToNextScanLineAt: yValue in: edgeTableEntry. "And adjust remainingLines" edgeTableEntry lines: deltaY - (yValue - startY). ].! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 04:02'! intStepToNextScanLineAt: yValue in: edgeTableEntry "Scaled integer version of forward differencing" [maxSteps >= 0 and:[yValue * 256 > lastY]] whileTrue:[ self validateIntegerRange. lastX := lastX + ((fwDx + 16r8000) // 16r10000). lastY := lastY + ((fwDy + 16r8000) // 16r10000). fwDx := fwDx + fwDDx. fwDy := fwDy + fwDDy. maxSteps := maxSteps - 1. ]. edgeTableEntry xValue: lastX // 256. edgeTableEntry zValue: 0.! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/29/1998 22:14'! isMonoton "Return true if the receiver is monoton along the y-axis, e.g., check if the tangents have the same sign" ^(via y - start y) * (end y - via y) >= 0! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/31/1998 16:36'! stepToFirstScanLineAt: yValue in: edgeTableEntry "Compute the initial x value for the scan line at yValue" ^self intStepToFirstScanLineAt: yValue in: edgeTableEntry! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 03:40'! stepToNextScanLineAt: yValue in: edgeTableEntry "Compute the next x value for the scan line at yValue. This message is sent during incremental updates. The yValue parameter is passed in here for edges that have more complicated computations," ^self intStepToNextScanLineAt: yValue in: edgeTableEntry! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 11/1/1998 00:31'! subdivide "Subdivide the receiver" | dy dx | "Test 1: If the bezier curve is not monoton in Y, we need a subdivision" self isMonoton ifFalse:[ MonotonSubdivisions := MonotonSubdivisions + 1. ^self subdivideToBeMonoton]. "Test 2: If the receiver is horizontal, don't do anything" (end y = start y) ifTrue:[^nil]. "Test 3: If the receiver can be represented as a straight line, make a line from the receiver and declare it invalid" ((end - start) crossProduct: (via - start)) = 0 ifTrue:[ LineConversions := LineConversions + 1. ^self subdivideToBeLine]. "Test 4: If the height of the curve exceeds 256 pixels, subdivide (forward differencing is numerically not very stable)" dy := end y - start y. dy < 0 ifTrue:[dy := dy negated]. (dy > 255) ifTrue:[ HeightSubdivisions := HeightSubdivisions + 1. ^self subdivideAt: 0.5]. "Test 5: Check if the incremental values could possibly overflow the scaled integer range" dx := end x - start x. dx < 0 ifTrue:[dx := dx negated]. dy * 32 < dx ifTrue:[ OverflowSubdivisions := OverflowSubdivisions + 1. ^self subdivideAt: 0.5]. ^nil! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 22:13'! subdivideAt: parameter "Subdivide the receiver at the given parameter" | both | (parameter <= 0.0 or:[parameter >= 1.0]) ifTrue:[self halt]. both := self computeSplitAt: parameter. "Transcript cr. self quickPrint: self. Transcript space. self quickPrint: both first. Transcript space. self quickPrint: both last. Transcript endEntry." self via: both first via. self end: both first end. ^both last! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 11/11/1998 22:15'! subdivideToBeLine "Not a true subdivision. Just return a line representing the receiver and fake me to be of zero height" | line | line := BalloonLineSimulation new. line start: start. line end: end. "Make me invalid" end := start. via := start. ^line! ! !BalloonBezierSimulation methodsFor: 'computing' stamp: 'ar 10/30/1998 02:24'! subdivideToBeMonoton "Subdivide the receiver at it's extreme point" | v1 v2 t other | v1 := (via - start). v2 := (end - via). t := (v1 y / (v2 y - v1 y)) negated asFloat. other := self subdivideAt: t. self isMonoton ifFalse:[self halt]. other isMonoton ifFalse:[self halt]. ^other! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 16:37'! absoluteSquared8Dot24: value "Compute the squared value of a 8.24 number with 0.0 <= value < 1.0, e.g., compute (value * value) bitShift: -24" | halfWord1 halfWord2 result | (value >= 0 and:[value < 16r1000000]) ifFalse:[^self error:'Value out of range']. halfWord1 := value bitAnd: 16rFFFF. halfWord2 := (value bitShift: -16) bitAnd: 255. result := (halfWord1 * halfWord1) bitShift: -16. "We don't need the lower 16bits at all" result := result + ((halfWord1 * halfWord2) * 2). result := result + ((halfWord2 * halfWord2) bitShift: 16). "word1 := halfWord1 * halfWord1. word2 := (halfWord2 * halfWord1) + (word1 bitShift: -16). word1 := word1 bitAnd: 16rFFFF. word2 := word2 + (halfWord1 * halfWord2). word2 := word2 + ((halfWord2 * halfWord2) bitShift: 16)." ^result bitShift: -8! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 5/25/2000 17:57'! debugDraw | entry minY maxY lX lY canvas | entry := BalloonEdgeData new. canvas := Display getCanvas. minY := (start y min: end y) min: via y. maxY := (start y max: end y) max: via y. entry yValue: minY. self stepToFirstScanLineAt: minY in: entry. lX := entry xValue. lY := entry yValue. minY+1 to: maxY do:[:y| self stepToNextScanLineAt: y in: entry. canvas line: lX@lY to: entry xValue @ y width: 2 color: Color black. lX := entry xValue. lY := y. ]. ! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 5/25/2000 17:57'! debugDraw2 | canvas last max t next | canvas := Display getCanvas. max := 100. last := nil. 0 to: max do:[:i| t := i asFloat / max asFloat. next := self valueAt: t. last ifNotNil:[ canvas line: last to: next rounded width: 2 color: Color blue. ]. last := next rounded. ].! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 5/25/2000 17:57'! debugDrawWide: n | entry minY maxY canvas curve p1 p2 entry2 y | curve := self class new. curve start: start + (0@n). curve via: via + (0@n). curve end: end + (0@n). entry := BalloonEdgeData new. entry2 := BalloonEdgeData new. canvas := Display getCanvas. minY := (start y min: end y) min: via y. maxY := (start y max: end y) max: via y. entry yValue: minY. entry2 yValue: minY + n. self stepToFirstScanLineAt: minY in: entry. curve stepToFirstScanLineAt: minY+n in: entry2. y := minY. 1 to: n do:[:i| y := y + 1. self stepToNextScanLineAt: y in: entry. p1 := entry xValue @ y. canvas line: p1 to: p1 + (n@0) width: 1 color: Color black. ]. [y < maxY] whileTrue:[ y := y + 1. self stepToNextScanLineAt: y in: entry. p2 := (entry xValue + n) @ y. curve stepToNextScanLineAt: y in: entry2. p1 := entry2 xValue @ y. canvas line: p1 to: p2 width: 1 color: Color black. ]. ! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 00:35'! printOn: aStream aStream nextPutAll: self class name; nextPut:$(; print: start; nextPutAll:' - '; print: via; nextPutAll:' - '; print: end; nextPut:$)! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'MPW 1/1/1901 21:55'! printOnStream: aStream aStream print: self class name; print:'('; write: start; print:' - '; write: via; print:' - '; write: end; print:')'.! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 21:56'! quickPrint: curve Transcript nextPut:$(; print: curve start; space; print: curve via; space; print: curve end; nextPut:$).! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 22:13'! quickPrint: curve first: aBool aBool ifTrue:[Transcript cr]. Transcript nextPut:$(; print: curve start; space; print: curve via; space; print: curve end; nextPut:$). Transcript endEntry.! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 03:53'! stepToFirst | startX endX startY endY deltaY fwX1 fwX2 fwY1 fwY2 steps scaledStepSize squaredStepSize | (end y) >= (start y) ifTrue:[ startX := start x. endX := end x. startY := start y. endY := end y. ] ifFalse:[ startX := end x. endX := start x. startY := end y. endY := start y. ]. deltaY := endY - startY. "Quickly check if the line is visible at all" (deltaY = 0) ifTrue:[^self]. fwX1 := (startX + endX - (2 * via x)) asFloat. fwX2 := (via x - startX * 2) asFloat. fwY1 := (startY + endY - (2 * via y)) asFloat. fwY2 := ((via y - startY) * 2) asFloat. steps := deltaY asInteger * 2. scaledStepSize := 1.0 / steps asFloat. squaredStepSize := scaledStepSize * scaledStepSize. fwDx := fwX2 * scaledStepSize. fwDDx := 2.0 * fwX1 * squaredStepSize. fwDy := fwY2 * scaledStepSize. fwDDy := 2.0 * fwY1 * squaredStepSize. fwDx := fwDx + (fwDDx * 0.5). fwDy := fwDy + (fwDDy * 0.5). lastX := startX asFloat. lastY := startY asFloat. ! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 03:50'! stepToFirstInt "Scaled integer version of forward differencing" | startX endX startY endY deltaY fwX1 fwX2 fwY1 fwY2 scaledStepSize squaredStepSize | self halt. (end y) >= (start y) ifTrue:[ startX := start x. endX := end x. startY := start y. endY := end y. ] ifFalse:[ startX := end x. endX := start x. startY := end y. endY := start y. ]. deltaY := endY - startY. "Quickly check if the line is visible at all" (deltaY = 0) ifTrue:[^nil]. fwX1 := (startX + endX - (2 * via x)). fwX2 := (via x - startX * 2). fwY1 := (startY + endY - (2 * via y)). fwY2 := ((via y - startY) * 2). maxSteps := deltaY asInteger * 2. scaledStepSize := 16r1000000 // maxSteps. "@@: Okay, we need some fancy 64bit multiplication here" squaredStepSize := (scaledStepSize * scaledStepSize) bitShift: -24. fwDx := fwX2 * scaledStepSize. fwDDx := 2 * fwX1 * squaredStepSize. fwDy := fwY2 * scaledStepSize. fwDDy := 2 * fwY1 * squaredStepSize. fwDx := fwDx + (fwDDx // 2). fwDy := fwDy + (fwDDy // 2). self validateIntegerRange. lastX := startX * 256. lastY := startY * 256. ! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 00:26'! stepToNext lastX := lastX + fwDx. lastY := lastY + fwDy. fwDx := fwDx + fwDDx. fwDy := fwDy + fwDDy.! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 04:01'! stepToNextInt "Scaled integer version of forward differencing" self halt. (maxSteps >= 0) ifTrue:[ self validateIntegerRange. lastX := lastX + ((fwDx + 16r8000) // 16r10000). lastY := lastY + ((fwDy + 16r8000) // 16r10000). fwDx := fwDx + fwDDx. fwDy := fwDy + fwDDy. maxSteps := maxSteps - 1. ].! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/30/1998 03:27'! validateIntegerRange fwDx class == SmallInteger ifFalse:[self halt]. fwDy class == SmallInteger ifFalse:[self halt]. fwDDx class == SmallInteger ifFalse:[self halt]. fwDDy class == SmallInteger ifFalse:[self halt]. ! ! !BalloonBezierSimulation methodsFor: 'private' stamp: 'ar 10/29/1998 21:26'! valueAt: parameter "Return the point at the value parameter: p(t) = (1-t)^2 * p1 + 2*t*(1-t) * p2 + t^2 * p3. " | t1 t2 t3 | t1 := (1.0 - parameter) squared. t2 := 2 * parameter * (1.0 - parameter). t3 := parameter squared. ^(start * t1) + (via * t2) + (end * t3)! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BalloonBezierSimulation class instanceVariableNames: ''! !BalloonBezierSimulation class methodsFor: 'initialization' stamp: 'MarcusDenker 9/30/2009 11:56'! initialize HeightSubdivisions := 0. LineConversions := 0. MonotonSubdivisions := 0. OverflowSubdivisions := 0.! ! Object variableWordSubclass: #BalloonBuffer instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Engine'! !BalloonBuffer commentStamp: '' prior: 0! BalloonBuffer is a repository for primitive data used by the BalloonEngine.! !BalloonBuffer methodsFor: 'accessing' stamp: 'ar 10/26/1998 21:12'! at: index "For simulation only" | word | word := self basicAt: index. word < 16r3FFFFFFF ifTrue:[^word]. "Avoid LargeInteger computations" ^word >= 16r80000000 "Negative?!!" ifTrue:["word - 16r100000000" (word bitInvert32 + 1) negated] ifFalse:[word]! ! !BalloonBuffer methodsFor: 'accessing' stamp: 'ar 10/26/1998 21:12'! at: index put: anInteger "For simulation only" | word | anInteger < 0 ifTrue:["word := 16r100000000 + anInteger" word := (anInteger + 1) negated bitInvert32] ifFalse:[word := anInteger]. self basicAt: index put: word. ^anInteger! ! !BalloonBuffer methodsFor: 'accessing' stamp: 'ar 2/2/2001 15:47'! floatAt: index "For simulation only" ^Float fromIEEE32Bit: (self basicAt: index)! ! !BalloonBuffer methodsFor: 'accessing' stamp: 'ar 2/2/2001 15:47'! floatAt: index put: value "For simulation only" value isFloat ifTrue:[self basicAt: index put: value asIEEE32BitWord] ifFalse:[self at: index put: value asFloat]. ^value! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BalloonBuffer class instanceVariableNames: ''! !BalloonBuffer class methodsFor: 'instance creation' stamp: 'ar 10/26/1998 21:11'! new ^self new: 256.! ! FormCanvas subclass: #BalloonCanvas instanceVariableNames: 'transform colorTransform engine aaLevel deferred' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Balloon'! !BalloonCanvas commentStamp: '' prior: 0! BalloonCanvas is a canvas using the BalloonEngine for drawing wherever possible. It has various methods which other canvases do not support due to the extra features of the balloon engine.! !BalloonCanvas methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/21/2008 16:46'! fillRectangle: aRectangle basicFillStyle: aFillStyle "Fill the given rectangle with the given, non-composite, fill style." ^self drawRectangle: aRectangle color: aFillStyle "@@: Name confusion!!!!!!" borderWidth: 0 borderColor: nil ! ! !BalloonCanvas methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 3/21/2008 16:46'! fillRectangle: aRectangle fillStyle: aFillStyle "Fill the given rectangle. Double-dispatched via the fill style." aFillStyle fillRectangle: aRectangle on: self! ! !BalloonCanvas methodsFor: 'accessing' stamp: 'ar 11/13/1998 01:02'! aaLevel ^aaLevel! ! !BalloonCanvas methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:53'! aaLevel: newLevel "Only allow changes to aaLevel if we're working on >= 8 bit forms" form depth >= 8 ifFalse:[^self]. aaLevel = newLevel ifTrue:[^self]. self flush. "In case there are pending primitives in the engine" aaLevel := newLevel. engine ifNotNil:[engine aaLevel: aaLevel].! ! !BalloonCanvas methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:54'! deferred ^deferred! ! !BalloonCanvas methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:55'! deferred: aBoolean deferred == aBoolean ifTrue:[^self]. self flush. "Force pending prims on screen" deferred := aBoolean. engine ifNotNil:[engine deferred: aBoolean].! ! !BalloonCanvas methodsFor: 'accessing' stamp: 'ar 2/13/2001 21:07'! ensuredEngine engine ifNil:[ engine := BalloonEngine new. "engine := BalloonDebugEngine new" engine aaLevel: aaLevel. engine bitBlt: port. engine destOffset: origin. engine clipRect: clipRect. engine deferred: deferred. engine]. engine colorTransform: colorTransform. engine edgeTransform: transform. ^engine! ! !BalloonCanvas methodsFor: 'balloon drawing' stamp: 'DSM 10/15/1999 15:14'! drawBezier3Shape: vertices color: c borderWidth: borderWidth borderColor: borderColor self drawBezierShape: (Bezier3Segment convertBezier3ToBezier2: vertices) color: c borderWidth: borderWidth borderColor: borderColor! ! !BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:25'! drawBezierShape: vertices color: c borderWidth: borderWidth borderColor: borderColor "Draw a boundary shape that is defined by a list of vertices. Each three subsequent vertices define a quadratic bezier segment. For lines, the control point should be set to either the start or the end of the bezier curve." | fillC borderC | fillC := self shadowColor ifNil:[c]. borderC := self shadowColor ifNil:[borderColor]. self ensuredEngine drawBezierShape: vertices fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! ! !BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 11/24/1998 15:16'! drawCompressedShape: compressedShape "Draw a compressed shape" self ensuredEngine drawCompressedShape: compressedShape transform: transform.! ! !BalloonCanvas methodsFor: 'balloon drawing' stamp: 'DSM 10/15/1999 15:18'! drawGeneralBezier3Shape: contours color: c borderWidth: borderWidth borderColor: borderColor | b2 | b2 := contours collect: [:b3 | Bezier3Segment convertBezier3ToBezier2: b3 ]. self drawGeneralBezierShape: b2 color: c borderWidth: borderWidth borderColor: borderColor! ! !BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:24'! drawGeneralBezierShape: contours color: c borderWidth: borderWidth borderColor: borderColor "Draw a general boundary shape (e.g., possibly containing holes)" | fillC borderC | fillC := self shadowColor ifNil:[c]. borderC := self shadowColor ifNil:[borderColor]. self ensuredEngine drawGeneralBezierShape: contours fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! ! !BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:24'! drawGeneralPolygon: contours color: c borderWidth: borderWidth borderColor: borderColor "Draw a general polygon (e.g., a polygon that can contain holes)" | fillC borderC | fillC := self shadowColor ifNil:[c]. borderC := self shadowColor ifNil:[borderColor]. self ensuredEngine drawGeneralPolygon: contours fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! ! !BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:24'! drawOval: r color: c borderWidth: borderWidth borderColor: borderColor "Draw the oval defined by the given rectangle" | fillC borderC | fillC := self shadowColor ifNil:[c]. borderC := self shadowColor ifNil:[borderColor]. self ensuredEngine drawOval: r fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! ! !BalloonCanvas methodsFor: 'balloon drawing' stamp: 'ar 2/17/2000 00:24'! drawRectangle: r color: c borderWidth: borderWidth borderColor: borderColor "Draw a rectangle" | fillC borderC | fillC := self shadowColor ifNil:[c]. borderC := self shadowColor ifNil:[borderColor]. self ensuredEngine drawRectangle: r fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! ! !BalloonCanvas methodsFor: 'converting' stamp: 'ar 11/11/1998 22:57'! asBalloonCanvas ^self! ! !BalloonCanvas methodsFor: 'copying' stamp: 'ar 11/24/1998 22:33'! copy self flush. ^super copy resetEngine! ! !BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 05:40'! fillColor: c "Note: This always fills, even if the color is transparent." "Note2: To achieve the above we must make sure that c is NOT transparent" self frameAndFillRectangle: form boundingBox fillColor: (c alpha: 1.0) borderWidth: 0 borderColor: nil! ! !BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 05:51'! fillOval: r color: c borderWidth: borderWidth borderColor: borderColor "Draw a filled and outlined oval" "Note: The optimization test below should actually read: self ifNoTransformWithIn: (r insetBy: borderWidth // 2) but since borderWidth is assumed to be very small related to r we don't check it." (self ifNoTransformWithIn: r) ifTrue:[^super fillOval: r color: c borderWidth: borderWidth borderColor: borderColor]. ^self drawOval: (r insetBy: borderWidth // 2) color: c borderWidth: borderWidth borderColor: borderColor! ! !BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 05:40'! fillRectangle: r color: c "Fill the rectangle with the given color" ^self frameAndFillRectangle: r fillColor: c borderWidth: 0 borderColor: nil! ! !BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 06:26'! frameAndFillRectangle: r fillColor: c borderWidth: borderWidth borderColor: borderColor "Draw a filled and outlined rectangle" "Note: The optimization test below should actually read: self ifNoTransformWithIn: (r insetBy: borderWidth // 2) but since borderWidth is assumed to be very small related to r we don't check it." (self ifNoTransformWithIn: r) ifTrue:[^super frameAndFillRectangle: r fillColor: c borderWidth: borderWidth borderColor: borderColor]. ^self drawRectangle: (r insetBy: borderWidth // 2) color: c borderWidth: borderWidth borderColor: borderColor! ! !BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/9/1999 05:52'! frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth topLeftColor: topLeftColor bottomRightColor: bottomRightColor "Draw a beveled or raised rectangle" | bw | "Note: The optimization test below should actually read: self ifNoTransformWithIn: (r insetBy: borderWidth // 2) but since borderWidth is assumed to be very small related to r we don't check it." (self ifNoTransformWithIn: r) ifTrue:[^super frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth topLeftColor: topLeftColor bottomRightColor: bottomRightColor]. "Fill rectangle and draw top and left border" bw := borderWidth // 2. self drawRectangle: (r insetBy: bw) color: fillColor borderWidth: borderWidth borderColor: topLeftColor. "Now draw bottom right border." self drawPolygon: (Array with: r topRight + (bw negated@bw) with: r bottomRight - bw asPoint with: r bottomLeft + (bw@bw negated)) color: nil borderWidth: borderWidth borderColor: bottomRightColor.! ! !BalloonCanvas methodsFor: 'drawing' stamp: 'ar 2/12/1999 17:45'! line: pt1 to: pt2 width: w color: c "Draw a line from pt1 to: pt2" (self ifNoTransformWithIn:(pt1 rect: pt2)) ifTrue:[^super line: pt1 to: pt2 width: w color: c]. ^self drawPolygon: (Array with: pt1 with: pt2) color: c borderWidth: w borderColor: c! ! !BalloonCanvas methodsFor: 'drawing' stamp: 'ar 11/11/1998 19:39'! point: pt color: c "Is there any use for this?" | myPt | transform ifNil:[myPt := pt] ifNotNil:[myPt := transform localPointToGlobal: pt]. ^super point: myPt color: c! ! !BalloonCanvas methodsFor: 'drawing-ovals' stamp: 'ar 6/18/1999 08:50'! fillOval: aRectangle fillStyle: aFillStyle borderWidth: bw borderColor: bc "Fill the given rectangle." ^self drawOval: (aRectangle insetBy: bw // 2) color: aFillStyle "@@: Name confusion!!!!!!" borderWidth: bw borderColor: bc ! ! !BalloonCanvas methodsFor: 'drawing-polygons' stamp: 'ar 8/26/2001 22:14'! drawPolygon: vertices fillStyle: aFillStyle "Fill the given polygon." self drawPolygon: vertices fillStyle: aFillStyle borderWidth: 0 borderColor: nil! ! !BalloonCanvas methodsFor: 'drawing-polygons' stamp: 'ar 2/17/2000 00:25'! drawPolygon: vertices fillStyle: aFillStyle borderWidth: borderWidth borderColor: borderColor "Draw a simple polygon defined by the list of vertices." | fillC borderC | fillC := self shadowColor ifNil:[aFillStyle]. borderC := self shadowColor ifNil:[borderColor]. self ensuredEngine drawPolygon: (vertices copyWith: vertices first) fill: fillC borderWidth: borderWidth borderColor: borderC transform: transform.! ! !BalloonCanvas methodsFor: 'initialize' stamp: 'ar 11/24/1998 15:28'! flush "Force all pending primitives onscreen" engine ifNotNil:[engine flush].! ! !BalloonCanvas methodsFor: 'initialize' stamp: 'alain.plantec 5/28/2009 09:42'! initialize super initialize. aaLevel := 1. deferred := false.! ! !BalloonCanvas methodsFor: 'initialize' stamp: 'ar 11/11/1998 20:25'! resetEngine engine := nil.! ! !BalloonCanvas methodsFor: 'testing' stamp: 'ar 11/13/1998 13:19'! isBalloonCanvas ^true! ! !BalloonCanvas methodsFor: 'testing' stamp: 'ar 11/12/1998 01:07'! isVisible: aRectangle ^transform ifNil:[super isVisible: aRectangle] ifNotNil:[super isVisible: (transform localBoundsToGlobal: aRectangle)]! ! !BalloonCanvas methodsFor: 'todo' stamp: 'ar 12/31/2001 02:27'! drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: c (self ifNoTransformWithIn: boundsRect) ifTrue:[^super drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: c]! ! !BalloonCanvas methodsFor: 'todo' stamp: 'tween 3/10/2009 07:49'! drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: c underline: underline underlineColor: uc strikethrough: strikethrough strikethroughColor: sc (self ifNoTransformWithIn: boundsRect) ifTrue:[^super drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: c underline: underline underlineColor: uc strikethrough: strikethrough strikethroughColor: sc]! ! !BalloonCanvas methodsFor: 'todo' stamp: 'ar 2/9/1999 05:46'! line: point1 to: point2 brushForm: brush "Who's gonna use this?" | pt1 pt2 | self flush. "Sorry, but necessary..." transform ifNil:[pt1 := point1. pt2 := point2] ifNotNil:[pt1 := transform localPointToGlobal: point1. pt2 := transform localPointToGlobal: point2]. ^super line: pt1 to: pt2 brushForm: brush! ! !BalloonCanvas methodsFor: 'todo' stamp: 'ar 2/9/1999 05:46'! paragraph: para bounds: bounds color: c (self ifNoTransformWithIn: bounds) ifTrue:[^super paragraph: para bounds: bounds color: c].! ! !BalloonCanvas methodsFor: 'transforming' stamp: 'ar 11/24/1998 14:45'! colorTransformBy: aColorTransform aColorTransform ifNil:[^self]. colorTransform ifNil:[colorTransform := aColorTransform] ifNotNil:[colorTransform := colorTransform composedWithLocal: aColorTransform]! ! !BalloonCanvas methodsFor: 'transforming' stamp: 'ar 12/30/1998 10:47'! preserveStateDuring: aBlock | state result | state := BalloonState new. state transform: transform. state colorTransform: colorTransform. state aaLevel: self aaLevel. result := aBlock value: self. transform := state transform. colorTransform := state colorTransform. self aaLevel: state aaLevel. ^result! ! !BalloonCanvas methodsFor: 'transforming' stamp: 'ar 11/12/1998 00:32'! transformBy: aTransform aTransform ifNil:[^self]. transform ifNil:[transform := aTransform] ifNotNil:[transform := transform composedWithLocal: aTransform]! ! !BalloonCanvas methodsFor: 'transforming' stamp: 'ar 5/29/1999 08:59'! transformBy: aDisplayTransform during: aBlock | myTransform result | myTransform := transform. self transformBy: aDisplayTransform. result := aBlock value: self. transform := myTransform. ^result! ! !BalloonCanvas methodsFor: 'private' stamp: 'marcus.denker 9/14/2008 21:01'! ifNoTransformWithIn: box "Return true if the current transformation does not affect the given bounding box" | delta | transform ifNil: [^true]. delta := (transform localPointToGlobal: box origin) - box origin. ^(transform localPointToGlobal: box corner) - box corner = delta! ! !BalloonCanvas methodsFor: 'private' stamp: 'nk 5/1/2004 12:54'! image: aForm at: aPoint sourceRect: sourceRect rule: rule | warp dstRect srcQuad dstOffset center | (self ifNoTransformWithIn: sourceRect) & false ifTrue:[^super image: aForm at: aPoint sourceRect: sourceRect rule: rule]. dstRect := (transform localBoundsToGlobal: (aForm boundingBox translateBy: aPoint)). dstOffset := 0@0. "dstRect origin." "dstRect := 0@0 corner: dstRect extent." center := 0@0."transform globalPointToLocal: dstRect origin." srcQuad := transform globalPointsToLocal: (dstRect innerCorners). srcQuad := srcQuad collect:[:pt| pt - aPoint]. warp := (WarpBlt current toForm: form) sourceForm: aForm; cellSize: 2; "installs a new colormap if cellSize > 1" combinationRule: Form over. warp copyQuad: srcQuad toRect: (dstRect translateBy: dstOffset). self frameRectangle: (aForm boundingBox translateBy: aPoint) color: Color green. "... TODO ... create a bitmap fill style from the form and use it for a simple rectangle."! ! Object subclass: #BalloonEdgeData instanceVariableNames: 'index xValue yValue zValue lines source' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Simulation'! !BalloonEdgeData commentStamp: '' prior: 0! BalloonEdgeData defines an entry in the internal edge table of the Balloon engine. Instance Variables: index The index into the external objects array of the associated graphics engine xValue The computed x-value of the requested operation yValue The y-value for the requested operation height The (remaining) height of the edge source The object from the external objects array! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:34'! index ^index! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:35'! index: anInteger index := anInteger! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:13'! lines ^lines! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:13'! lines: anInteger ^lines := anInteger! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:34'! source ^source! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 21:39'! source: anObject source := anObject! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:34'! xValue ^xValue! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:35'! xValue: anInteger xValue := anInteger! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:34'! yValue ^yValue! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:35'! yValue: anInteger yValue := anInteger! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 19:56'! zValue ^zValue! ! !BalloonEdgeData methodsFor: 'accessing' stamp: 'ar 10/27/1998 19:56'! zValue: anInteger zValue := anInteger! ! !BalloonEdgeData methodsFor: 'computing' stamp: 'ar 10/27/1998 15:53'! stepToFirstScanLine source stepToFirstScanLineAt: yValue in: self! ! !BalloonEdgeData methodsFor: 'computing' stamp: 'ar 10/27/1998 15:53'! stepToNextScanLine source stepToNextScanLineAt: yValue in: self! ! Object subclass: #BalloonEngine instanceVariableNames: 'workBuffer span bitBlt forms clipRect destOffset externals aaLevel edgeTransform colorTransform deferred postFlushNeeded' classVariableNames: 'BezierStats BufferCache CacheProtect Counts Debug Times' poolDictionaries: 'BalloonEngineConstants' category: 'Balloon-Engine'! !BalloonEngine commentStamp: '' prior: 0! BalloonEngine is the representative for the Balloon engine inside Squeak. For most purposes it should not be used directly but via BalloonCanvas since this ensures proper initialization and is polymorphic with other canvas uses.! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/11/1998 23:04'! aaLevel ^aaLevel ifNil:[1]! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/11/1998 23:04'! aaLevel: anInteger aaLevel := (anInteger min: 4) max: 1.! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 10/29/1998 01:51'! aaTransform "Return a transformation for the current anti-aliasing level" | matrix | matrix := MatrixTransform2x3 withScale: (self aaLevel) asFloat asPoint. matrix offset: (self aaLevel // 2) asFloat asPoint. ^matrix composedWith:(MatrixTransform2x3 withOffset: destOffset asFloatPoint)! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 10/13/1998 03:04'! bitBlt ^bitBlt! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 5/28/2000 15:02'! bitBlt: aBitBlt bitBlt := aBitBlt. bitBlt isNil ifTrue:[^self]. self class primitiveSetBitBltPlugin: bitBlt getPluginName. self clipRect: bitBlt clipRect. bitBlt sourceForm: (Form extent: span size @ 1 depth: 32 bits: span); sourceRect: (0@0 extent: 1@span size); colorMap: (Color colorMapIfNeededFrom: 32 to: bitBlt destForm depth); combinationRule: (bitBlt destForm depth >= 8 ifTrue:[34] ifFalse:[Form paint]).! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/1/1998 02:57'! clipRect ^clipRect! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 10/13/1998 02:44'! clipRect: aRect clipRect := aRect truncated! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/24/1998 15:04'! colorTransform ^colorTransform! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/24/1998 15:04'! colorTransform: aColorTransform colorTransform := aColorTransform! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 12/30/1998 11:24'! deferred ^deferred! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 12/30/1998 11:24'! deferred: aBoolean deferred := aBoolean.! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/1/1998 02:56'! destOffset ^destOffset! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/12/1998 00:22'! destOffset: aPoint destOffset := aPoint asIntegerPoint. bitBlt destX: aPoint x; destY: aPoint y.! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/25/1998 22:34'! edgeTransform ^edgeTransform! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 11/25/1998 22:34'! edgeTransform: aTransform edgeTransform := aTransform.! ! !BalloonEngine methodsFor: 'accessing' stamp: 'ar 10/29/1998 01:51'! fullTransformFrom: aMatrix | m | m := self aaTransform composedWith: aMatrix. "m offset: m offset + destOffset." ^m! ! !BalloonEngine methodsFor: 'copying' stamp: 'ar 11/25/1998 00:45'! canProceedAfter: failureReason "Check if we can proceed after the failureReason indicated." | newBuffer | failureReason = GErrorNeedFlush ifTrue:[ "Need to flush engine before proceeding" self copyBits. self reset. ^true]. failureReason = GErrorNoMoreSpace ifTrue:[ "Work buffer is too small" newBuffer := workBuffer species new: workBuffer size * 2. self primCopyBufferFrom: workBuffer to: newBuffer. workBuffer := newBuffer. ^true]. "Not handled" ^false! ! !BalloonEngine methodsFor: 'copying' stamp: 'ar 3/6/2001 12:06'! copyBits (bitBlt notNil and:[bitBlt destForm notNil]) ifTrue:[bitBlt destForm unhibernate]. self copyLoopFaster.! ! !BalloonEngine methodsFor: 'copying' stamp: 'ar 11/14/1998 19:32'! copyLoop "This is the basic rendering loop using as little primitive support as possible." | finished edge fill | edge := BalloonEdgeData new. fill := BalloonFillData new. self primInitializeProcessing. "Initialize the GE for processing" [self primFinishedProcessing] whileFalse:[ "Step 1: Process the edges in the global edge table that will be added in this step" [finished := self primNextGlobalEdgeEntryInto: edge. finished] whileFalse:[ edge source: (externals at: edge index). edge stepToFirstScanLine. self primAddActiveEdgeTableEntryFrom: edge]. "Step 2: Scan the active edge table" [finished := self primNextFillEntryInto: fill. finished] whileFalse:[ fill source: (externals at: fill index). "Compute the new fill" fill computeFill. "And mix it in the out buffer" self primMergeFill: fill destForm bits from: fill]. "Step 3: Display the current span buffer if necessary" self primDisplaySpanBuffer. "Step 4: Advance and resort the active edge table" [finished := self primNextActiveEdgeEntryInto: edge. finished] whileFalse:[ "If the index is zero then the edge has been handled by the GE" edge source: (externals at: edge index). edge stepToNextScanLine. self primChangeActiveEdgeTableEntryFrom: edge]. ]. self primGetTimes: Times. self primGetCounts: Counts. self primGetBezierStats: BezierStats.! ! !BalloonEngine methodsFor: 'copying' stamp: 'ar 11/14/1998 19:32'! copyLoopFaster "This is a copy loop drawing one scan line at a time" | edge fill reason | edge := BalloonEdgeData new. fill := BalloonFillData new. [self primFinishedProcessing] whileFalse:[ reason := self primRenderScanline: edge with: fill. "reason ~= 0 means there has been a problem" reason = 0 ifFalse:[ self processStopReason: reason edge: edge fill: fill. ]. ]. self primGetTimes: Times. self primGetCounts: Counts. self primGetBezierStats: BezierStats.! ! !BalloonEngine methodsFor: 'copying' stamp: 'ar 11/14/1998 19:33'! copyLoopFastest "This is a copy loop drawing the entire image" | edge fill reason | edge := BalloonEdgeData new. fill := BalloonFillData new. [self primFinishedProcessing] whileFalse:[ reason := self primRenderImage: edge with: fill. "reason ~= 0 means there has been a problem" reason = 0 ifFalse:[ self processStopReason: reason edge: edge fill: fill. ]. ]. self primGetTimes: Times. self primGetCounts: Counts. self primGetBezierStats: BezierStats.! ! !BalloonEngine methodsFor: 'copying' stamp: 'ar 11/11/1998 21:19'! processStopReason: reason edge: edge fill: fill "The engine has stopped because of some reason. Try to figure out how to respond and do the necessary actions." "Note: The order of operations below can affect the speed" "Process unknown fills first" reason = GErrorFillEntry ifTrue:[ fill source: (externals at: fill index). "Compute the new fill" fill computeFill. "And mix it in the out buffer" ^self primMergeFill: fill destForm bits from: fill]. "Process unknown steppings in the AET second" reason = GErrorAETEntry ifTrue:[ edge source: (externals at: edge index). edge stepToNextScanLine. ^self primChangeActiveEdgeTableEntryFrom: edge]. "Process unknown entries in the GET third" reason = GErrorGETEntry ifTrue:[ edge source: (externals at: edge index). edge stepToFirstScanLine. ^self primAddActiveEdgeTableEntryFrom: edge]. "Process generic problems last" (self canProceedAfter: reason) ifTrue:[^self]. "Okay." ^self error:'Unkown stop reason in graphics engine' ! ! !BalloonEngine methodsFor: 'drawing' stamp: 'ar 10/11/1999 16:49'! drawBezierShape: points fill: fillStyle borderWidth: borderWidth borderColor: borderFill transform: aTransform | fills | self edgeTransform: aTransform. self resetIfNeeded. fills := self registerFill: fillStyle and: borderFill. self primAddBezierShape: points segments: (points size) // 3 fill: (fills at: 1) lineWidth: borderWidth lineFill: (fills at: 2). self postFlushIfNeeded.! ! !BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:44'! drawCompressedShape: shape transform: aTransform | fillIndexList | self edgeTransform: aTransform. self resetIfNeeded. fillIndexList := self registerFills: shape fillStyles. self primAddCompressedShape: shape points segments: shape numSegments leftFills: shape leftFills rightFills: shape rightFills lineWidths: shape lineWidths lineFills: shape lineFills fillIndexList: fillIndexList. self postFlushIfNeeded.! ! !BalloonEngine methodsFor: 'drawing' stamp: 'ar 1/15/1999 03:02'! drawGeneralBezierShape: contours fill: fillStyle borderWidth: borderWidth borderColor: borderFill transform: aTransform | fills | self edgeTransform: aTransform. self resetIfNeeded. fills := self registerFill: fillStyle and: borderFill. contours do:[:points| self primAddBezierShape: points segments: (points size // 3) fill: (fills at: 1) lineWidth: borderWidth lineFill: (fills at: 2). "Note: To avoid premature flushing of the pipeline we need to reset the flush bit within the engine." self primFlushNeeded: false. ]. "And set the flush bit afterwards" self primFlushNeeded: true. self postFlushIfNeeded.! ! !BalloonEngine methodsFor: 'drawing' stamp: 'ar 1/15/1999 03:02'! drawGeneralPolygon: contours fill: fillStyle borderWidth: borderWidth borderColor: borderFill transform: aTransform | fills | self edgeTransform: aTransform. self resetIfNeeded. fills := self registerFill: fillStyle and: borderFill. contours do:[:points| self primAddPolygon: points segments: points size fill: (fills at: 1) lineWidth: borderWidth lineFill: (fills at: 2). "Note: To avoid premature flushing of the pipeline we need to reset the flush bit within the engine." self primFlushNeeded: false. ]. "And set the flush bit afterwards" self primFlushNeeded: true. self postFlushIfNeeded.! ! !BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:45'! drawOval: rect fill: fillStyle borderWidth: borderWidth borderColor: borderColor transform: aMatrix | fills | self edgeTransform: aMatrix. self resetIfNeeded. fills := self registerFill: fillStyle and: borderColor. self primAddOvalFrom: rect origin to: rect corner fillIndex: (fills at: 1) borderWidth: borderWidth borderColor: (fills at: 2). self postFlushIfNeeded.! ! !BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:45'! drawPolygon: points fill: fillStyle borderWidth: borderWidth borderColor: borderFill transform: aTransform | fills | self edgeTransform: aTransform. self resetIfNeeded. fills := self registerFill: fillStyle and: borderFill. self primAddPolygon: points segments: points size fill: (fills at: 1) lineWidth: borderWidth lineFill: (fills at: 2). self postFlushIfNeeded.! ! !BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:45'! drawRectangle: rect fill: fillStyle borderWidth: borderWidth borderColor: borderColor transform: aMatrix | fills | self edgeTransform: aMatrix. self resetIfNeeded. fills := self registerFill: fillStyle and: borderColor. self primAddRectFrom: rect origin to: rect corner fillIndex: (fills at: 1) borderWidth: borderWidth borderColor: (fills at: 2). self postFlushIfNeeded.! ! !BalloonEngine methodsFor: 'drawing' stamp: 'bf 4/3/2004 01:36'! registerFill: aFillStyle "Register the given fill style." | theForm | aFillStyle ifNil:[^0]. aFillStyle isSolidFill ifTrue:[^aFillStyle scaledPixelValue32]. aFillStyle isGradientFill ifTrue:[ ^self primAddGradientFill: aFillStyle pixelRamp from: aFillStyle origin along: aFillStyle direction normal: aFillStyle normal radial: aFillStyle isRadialFill ]. aFillStyle isBitmapFill ifTrue:[ theForm := aFillStyle form asSourceForm. theForm unhibernate. forms := forms copyWith: theForm. ^self primAddBitmapFill: theForm colormap: (theForm colormapIfNeededForDepth: 32) tile: aFillStyle isTiled from: aFillStyle origin along: aFillStyle direction normal: aFillStyle normal xIndex: forms size]. ^0! ! !BalloonEngine methodsFor: 'drawing' stamp: 'ar 11/26/1998 19:45'! registerFill: fill1 and: fill2 ^self registerFills: (Array with: fill1 with: fill2)! ! !BalloonEngine methodsFor: 'drawing' stamp: 'di 11/21/1999 20:15'! registerFills: fills | fillIndexList index fillIndex | ((colorTransform notNil and:[colorTransform isAlphaTransform]) or:[ fills anySatisfy: [:any| any notNil and:[any isTranslucent]]]) ifTrue:[ self flush. self reset. postFlushNeeded := true]. fillIndexList := WordArray new: fills size. index := 1. [index <= fills size] whileTrue:[ fillIndex := self registerFill: (fills at: index). fillIndex == nil ifTrue:[index := 1] "Need to start over" ifFalse:[fillIndexList at: index put: fillIndex. index := index+1] ]. ^fillIndexList! ! !BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:29'! flush "Force all pending primitives onscreen" workBuffer ifNil:[^self]. self copyBits. self release.! ! !BalloonEngine methodsFor: 'initialize' stamp: 'stephane.ducasse 6/14/2009 22:37'! initialize | w | super initialize. w := Display width > 2048 ifTrue: [ 4096 ] ifFalse: [ 2048 ]. externals := OrderedCollection new: 100. span := Bitmap new: w. bitBlt := nil. self bitBlt: ((BitBlt toForm: Display) destRect: Display boundingBox; yourself). forms := #(). deferred := false.! ! !BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:42'! postFlushIfNeeded "Force all pending primitives onscreen" workBuffer ifNil:[^self]. (deferred not or:[postFlushNeeded]) ifTrue:[ self copyBits. self release].! ! !BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:43'! preFlushIfNeeded "Force all pending primitives onscreen" workBuffer ifNil:[^self]. self primFlushNeeded ifTrue:[ self copyBits. self reset].! ! !BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/11/1998 22:52'! release self class recycleBuffer: workBuffer. workBuffer := nil.! ! !BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:34'! reset workBuffer ifNil:[workBuffer := self class allocateOrRecycleBuffer: 10000]. self primInitializeBuffer: workBuffer. self primSetAALevel: self aaLevel. self primSetOffset: destOffset. self primSetClipRect: clipRect. self primSetEdgeTransform: edgeTransform. self primSetColorTransform: colorTransform. forms := #().! ! !BalloonEngine methodsFor: 'initialize' stamp: 'ar 11/25/1998 22:39'! resetIfNeeded workBuffer ifNil:[self reset]. self primSetEdgeTransform: edgeTransform. self primSetColorTransform: colorTransform. self primSetDepth: self primGetDepth + 1. postFlushNeeded := false.! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:48'! primClipRectInto: rect ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:47'! primFlushNeeded ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:47'! primFlushNeeded: aBoolean ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primGetAALevel "Set the AA level" ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primGetBezierStats: statsArray ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primGetClipRect: rect ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primGetCounts: statsArray ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:47'! primGetDepth ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primGetFailureReason ^0! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primGetOffset ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primGetTimes: statsArray ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primSetAALevel: level "Set the AA level" ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primSetClipRect: rect ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:47'! primSetColorTransform: transform ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:47'! primSetDepth: depth ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:47'! primSetEdgeTransform: transform ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-access' stamp: 'ar 2/2/2001 15:49'! primSetOffset: point ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddBezierFrom: start to: end via: via leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddBezierFrom: start to: end via: via leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddBezierShape: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddBezierShape: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddBitmapFill: form colormap: cmap tile: tileFlag from: origin along: direction normal: normal xIndex: xIndex (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddBitmapFill: form colormap: cmap tile: tileFlag from: origin along: direction normal: normal xIndex: xIndex ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddCompressedShape: points segments: nSegments leftFills: leftFills rightFills: rightFills lineWidths: lineWidths lineFills: lineFills fillIndexList: fillIndexList ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddExternalEdge: index initialX: initialX initialY: initialY initialZ: initialZ leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddExternalEdge: index initialX: initialX initialY: initialY initialZ: initialZ leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddExternalFill: index (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddExternalFill: index ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddGradientFill: colorRamp from: origin along: direction normal: normal radial: isRadial (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddGradientFill: colorRamp from: origin along: direction normal: normal radial: isRadial ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddLineFrom: start to: end leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddLineFrom: start to: end leftFillIndex: leftFillIndex rightFillIndex: rightFillIndex ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddOvalFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddOvalFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddPolygon: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddPolygon: points segments: nSegments fill: fillStyle lineWidth: lineWidth lineFill: lineFill ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-adding' stamp: 'ar 2/2/2001 15:47'! primAddRectFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddRectFrom: start to: end fillIndex: fillIndex borderWidth: width borderColor: pixelValue32 ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:48'! primAddActiveEdgeTableEntryFrom: edgeEntry "Add edge entry to the AET." (self canProceedAfter: self primGetFailureReason) ifTrue:[ ^self primAddActiveEdgeTableEntryFrom: edgeEntry ]. ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:48'! primChangeActiveEdgeTableEntryFrom: edgeEntry "Change the entry in the active edge table from edgeEntry" ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:48'! primDisplaySpanBuffer "Display the current scan line if necessary" ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:49'! primFinishedProcessing "Return true if there are no more entries in AET and GET and the last scan line has been displayed" ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:49'! primInitializeProcessing "Initialize processing in the GE. Create the active edge table and sort it." ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:49'! primMergeFill: fillBitmap from: fill "Merge the filled bitmap into the current output buffer." ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:49'! primNextActiveEdgeEntryInto: edgeEntry "Store the next entry of the AET at the current y-value in edgeEntry. Return false if there is no entry, true otherwise." ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:49'! primNextFillEntryInto: fillEntry "Store the next fill entry of the active edge table in fillEntry. Return false if there is no such entry, true otherwise" ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:49'! primNextGlobalEdgeEntryInto: edgeEntry "Store the next entry of the GET at the current y-value in edgeEntry. Return false if there is no entry, true otherwise." ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:49'! primRenderImage: edge with: fill "Start/Proceed rendering the current scan line" ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-incremental' stamp: 'ar 2/2/2001 15:49'! primRenderScanline: edge with: fill "Start/Proceed rendering the current scan line" ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-misc' stamp: 'ar 2/2/2001 15:48'! primCopyBufferFrom: oldBuffer to: newBuffer "Copy the contents of oldBuffer into the (larger) newBuffer" ^self primitiveFailed! ! !BalloonEngine methodsFor: 'primitives-misc' stamp: 'ar 2/2/2001 15:49'! primInitializeBuffer: buffer ^self primitiveFailed! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BalloonEngine class instanceVariableNames: ''! !BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/25/1998 17:37'! debug: aBoolean "BalloonEngine debug: true" "BalloonEngine debug: false" Debug := aBoolean! ! !BalloonEngine class methodsFor: 'accessing' stamp: 'ar 2/2/2001 15:47'! doProfileStats: aBool "Note: On Macintosh systems turning on profiling can significantly degrade the performance of Balloon since we're using the high accuracy timer for measuring." "BalloonEngine doProfileStats: true" "BalloonEngine doProfileStats: false" ^false! ! !BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/30/1998 23:57'! printBezierStats "BalloonEngine printBezierStats" "BalloonEngine resetBezierStats" Transcript cr; nextPutAll:'Bezier statistics:'; crtab; print: (BezierStats at: 1); tab; nextPutAll:' non-monoton curves splitted'; crtab; print: (BezierStats at: 2); tab; nextPutAll:' curves splitted for numerical accuracy'; crtab; print: (BezierStats at: 3); tab; nextPutAll:' curves splitted to avoid integer overflow'; crtab; print: (BezierStats at: 4); tab; nextPutAll:' curves internally converted to lines'; endEntry.! ! !BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/28/1998 23:59'! printStat: time count: n string: aString Transcript cr; print: time; tab; nextPutAll:' mSecs -- '; print: n; tab; nextPutAll:' ops -- '; print: ((time asFloat / (n max: 1) asFloat) roundTo: 0.01); tab; nextPutAll: ' avg. mSecs/op -- '; nextPutAll: aString.! ! !BalloonEngine class methodsFor: 'accessing' stamp: 'ar 1/12/1999 10:52'! printStats "BalloonEngine doProfileStats: true" "BalloonEngine printStats" "BalloonEngine resetStats" Transcript cr; nextPutAll:'/************** BalloonEngine statistics ****************/'. self printStat: (Times at: 1) count: (Counts at: 1) string: 'Initialization'. self printStat: (Times at: 2) count: (Counts at: 2) string: 'Finish test'. self printStat: (Times at: 3) count: (Counts at: 3) string: 'Fetching/Adding GET entries'. self printStat: (Times at: 4) count: (Counts at: 4) string: 'Adding AET entries'. self printStat: (Times at: 5) count: (Counts at: 5) string: 'Fetching/Computing fills'. self printStat: (Times at: 6) count: (Counts at: 6) string: 'Merging fills'. self printStat: (Times at: 7) count: (Counts at: 7) string: 'Displaying span buffer'. self printStat: (Times at: 8) count: (Counts at: 8) string: 'Fetching/Updating AET entries'. self printStat: (Times at: 9) count: (Counts at: 9) string: 'Changing AET entries'. Transcript cr; print: Times sum; nextPutAll:' mSecs for all operations'. Transcript cr; print: Counts sum; nextPutAll: ' overall operations'. Transcript endEntry.! ! !BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/30/1998 23:57'! resetBezierStats BezierStats := WordArray new: 4.! ! !BalloonEngine class methodsFor: 'accessing' stamp: 'ar 10/28/1998 23:38'! resetStats Times := WordArray new: 10. Counts := WordArray new: 10.! ! !BalloonEngine class methodsFor: 'initialization' stamp: 'ar 11/11/1998 22:49'! initialize "BalloonEngine initialize" BufferCache := WeakArray new: 1. Smalltalk garbageCollect. "Make the cache old" CacheProtect := Semaphore forMutualExclusion. Times := WordArray new: 10. Counts := WordArray new: 10. BezierStats := WordArray new: 4. Debug ifNil:[Debug := false].! ! !BalloonEngine class methodsFor: 'private' stamp: 'ar 11/11/1998 22:50'! allocateOrRecycleBuffer: initialSize "Try to recycly a buffer. If this is not possibly, create a new one." | buffer | CacheProtect critical:[ buffer := BufferCache at: 1. BufferCache at: 1 put: nil. ]. ^buffer ifNil:[BalloonBuffer new: initialSize]! ! !BalloonEngine class methodsFor: 'private' stamp: 'ar 5/28/2000 22:17'! primitiveSetBitBltPlugin: pluginName ^nil! ! !BalloonEngine class methodsFor: 'private' stamp: 'eem 6/11/2008 13:00'! recycleBuffer: balloonBuffer "Try to keep the buffer for later drawing operations." CacheProtect critical:[ | buffer | buffer := BufferCache at: 1. (buffer isNil or:[buffer size < balloonBuffer size] ) ifTrue:[BufferCache at: 1 put: balloonBuffer]. ].! ! SharedPool subclass: #BalloonEngineConstants instanceVariableNames: '' classVariableNames: 'BEAaLevelIndex BEBalloonEngineSize BEBitBltIndex BEClipRectIndex BEColorTransformIndex BEDeferredIndex BEDestOffsetIndex BEEdgeTransformIndex BEExternalsIndex BEFormsIndex BEPostFlushNeededIndex BESpanIndex BEWorkBufferIndex ETBalloonEdgeDataSize ETIndexIndex ETLinesIndex ETSourceIndex ETXValueIndex ETYValueIndex ETZValueIndex FTBalloonFillDataSize FTDestFormIndex FTIndexIndex FTMaxXIndex FTMinXIndex FTSourceIndex FTYValueIndex GBBaseSize GBBitmapDepth GBBitmapHeight GBBitmapRaster GBBitmapSize GBBitmapWidth GBColormapOffset GBColormapSize GBEndX GBEndY GBFinalX GBMBaseSize GBTileFlag GBUpdateDDX GBUpdateDDY GBUpdateDX GBUpdateDY GBUpdateData GBUpdateX GBUpdateY GBViaX GBViaY GBWideEntry GBWideExit GBWideExtent GBWideFill GBWideSize GBWideUpdateData GBWideWidth GEBaseEdgeSize GEBaseFillSize GEEdgeClipFlag GEEdgeFillsInvalid GEFillIndexLeft GEFillIndexRight GENumLines GEObjectIndex GEObjectLength GEObjectType GEObjectUnused GEPrimitiveBezier GEPrimitiveClippedBitmapFill GEPrimitiveEdge GEPrimitiveEdgeMask GEPrimitiveFill GEPrimitiveFillMask GEPrimitiveLine GEPrimitiveLinearGradientFill GEPrimitiveRadialGradientFill GEPrimitiveRepeatedBitmapFill GEPrimitiveTypeMask GEPrimitiveUnknown GEPrimitiveWide GEPrimitiveWideBezier GEPrimitiveWideEdge GEPrimitiveWideLine GEPrimitiveWideMask GEStateAddingFromGET GEStateBlitBuffer GEStateCompleted GEStateScanningAET GEStateUnlocked GEStateUpdateEdges GEStateWaitingChange GEStateWaitingForEdge GEStateWaitingForFill GEXValue GEYValue GEZValue GErrorAETEntry GErrorBadState GErrorFillEntry GErrorGETEntry GErrorNeedFlush GErrorNoMoreSpace GFDirectionX GFDirectionY GFNormalX GFNormalY GFOriginX GFOriginY GFRampLength GFRampOffset GGBaseSize GLBaseSize GLEndX GLEndY GLError GLErrorAdjDown GLErrorAdjUp GLWideEntry GLWideExit GLWideExtent GLWideFill GLWideSize GLWideWidth GLXDirection GLXIncrement GLYDirection GWAAColorMask GWAAColorShift GWAAHalfPixel GWAALevel GWAAScanMask GWAAShift GWAETStart GWAETUsed GWBezierHeightSubdivisions GWBezierLineConversions GWBezierMonotonSubdivisions GWBezierOverflowSubdivisions GWBufferTop GWClearSpanBuffer GWClipMaxX GWClipMaxY GWClipMinX GWClipMinY GWColorTransform GWCountAddAETEntry GWCountChangeAETEntry GWCountDisplaySpan GWCountFinishTest GWCountInitializing GWCountMergeFill GWCountNextAETEntry GWCountNextFillEntry GWCountNextGETEntry GWCurrentY GWCurrentZ GWDestOffsetX GWDestOffsetY GWEdgeTransform GWFillMaxX GWFillMaxY GWFillMinX GWFillMinY GWFillOffsetX GWFillOffsetY GWGETStart GWGETUsed GWHasClipShapes GWHasColorTransform GWHasEdgeTransform GWHeaderSize GWLastExportedEdge GWLastExportedFill GWLastExportedLeftX GWLastExportedRightX GWMagicIndex GWMagicNumber GWMinimalSize GWNeedsFlush GWObjStart GWObjUsed GWPoint1 GWPoint2 GWPoint3 GWPoint4 GWPointListFirst GWSize GWSpanEnd GWSpanEndAA GWSpanSize GWSpanStart GWState GWStopReason GWTimeAddAETEntry GWTimeChangeAETEntry GWTimeDisplaySpan GWTimeFinishTest GWTimeInitializing GWTimeMergeFill GWTimeNextAETEntry GWTimeNextFillEntry GWTimeNextGETEntry' poolDictionaries: '' category: 'Balloon-Engine'! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BalloonEngineConstants class instanceVariableNames: ''! !BalloonEngineConstants class methodsFor: 'pool definition' stamp: 'ar 5/18/2003 19:55'! initEdgeConstants "Initialize the edge constants" "Edge primitive types" GEPrimitiveEdge := 2. "External edge - not handled by the GE" GEPrimitiveWideEdge := 3. "Wide external edge" GEPrimitiveLine := 4. "Straight line" GEPrimitiveWideLine := 5. "Wide line" GEPrimitiveBezier := 6. "Quadratic bezier curve" GEPrimitiveWideBezier := 7. "Wide bezier curve" "Special flags" GEPrimitiveWide := 16r01. "Flag determining a wide primitive" GEPrimitiveWideMask := 16rFE. "Mask for clearing the wide flag" GEEdgeFillsInvalid := 16r10000. "Flag determining if left/right fills of an edge are invalid" GEEdgeClipFlag := 16r20000. "Flag determining if this is a clip edge" "General edge state constants" GEXValue := 4. "Current raster x" GEYValue := 5. "Current raster y" GEZValue := 6. "Current raster z" GENumLines := 7. "Number of scan lines remaining" GEFillIndexLeft := 8. "Left fill index" GEFillIndexRight := 9. "Right fill index" GEBaseEdgeSize := 10. "Basic size of each edge" "General fill state constants" GEBaseFillSize := 4. "Basic size of each fill" "General Line state constants" GLXDirection := 10. "Direction of edge (1: left-to-right; -1: right-to-left)" GLYDirection := 11. "Direction of edge (1: top-to-bottom; -1: bottom-to-top)" GLXIncrement := 12. "Increment at each scan line" GLError := 13. "Current error" GLErrorAdjUp := 14. "Error to add at each scan line" GLErrorAdjDown := 15. "Error to subtract on roll-over" "Note: The following entries are only needed before the incremental state is computed. They are therefore aliased to the error values above" GLEndX := 14. "End X of line" GLEndY := 15. "End Y of line" GLBaseSize := 16. "Basic size of each line" "Additional stuff for wide lines" GLWideFill := 16. "Current fill of line" GLWideWidth := 17. "Current width of line" GLWideEntry := 18. "Initial steps" GLWideExit := 19. "Final steps" GLWideExtent := 20. "Target width" GLWideSize := 21. "Size of wide lines" "General Bezier state constants" GBUpdateData := 10. "Incremental update data for beziers" GBUpdateX := 0. "Last computed X value (24.8)" GBUpdateY := 1. "Last computed Y value (24.8)" GBUpdateDX := 2. "Delta X forward difference step (8.24)" GBUpdateDY := 3. "Delta Y forward difference step (8.24)" GBUpdateDDX := 4. "Delta DX forward difference step (8.24)" GBUpdateDDY := 5. "Delta DY forward difference step (8.24)" "Note: The following four entries are only needed before the incremental state is computed. They are therefore aliased to the incremental values above" GBViaX := 12. "via x" GBViaY := 13. "via y" GBEndX := 14. "end x" GBEndY := 15. "end y" GBBaseSize := 16. "Basic size of each bezier. Note: MUST be greater or equal to the size of lines" "Additional stuff for wide beziers" GBWideFill := 16. "Current fill of line" GBWideWidth := 17. "Current width of line" GBWideEntry := 18. "Initial steps" GBWideExit := 19. "Final steps" GBWideExtent := 20. "Target extent" GBFinalX := 21. "Final X value" GBWideUpdateData := 22. "Update data for second curve" GBWideSize := 28. "Size of wide beziers" ! ! !BalloonEngineConstants class methodsFor: 'pool definition' stamp: 'ar 5/18/2003 20:08'! initFillConstants "Initialize the fill constants" "Fill primitive types" GEPrimitiveFill := 16r100. GEPrimitiveLinearGradientFill := 16r200. GEPrimitiveRadialGradientFill := 16r300. GEPrimitiveClippedBitmapFill := 16r400. GEPrimitiveRepeatedBitmapFill := 16r500. "General fill state constants" GEBaseFillSize := 4. "Basic size of each fill" "Oriented fill constants" GFOriginX := 4. "X origin of fill" GFOriginY := 5. "Y origin of fill" GFDirectionX := 6. "X direction of fill" GFDirectionY := 7. "Y direction of fill" GFNormalX := 8. "X normal of fill" GFNormalY := 9. "Y normal of fill" "Gradient fill constants" GFRampLength := 10. "Length of following color ramp" GFRampOffset := 12. "Offset of first ramp entry" GGBaseSize := 12. "Bitmap fill constants" GBBitmapWidth := 10. "Width of bitmap" GBBitmapHeight := 11. "Height of bitmap" GBBitmapDepth := 12. "Depth of bitmap" GBBitmapSize := 13. "Size of bitmap words" GBBitmapRaster := 14. "Size of raster line" GBColormapSize := 15. "Size of colormap, if any" GBTileFlag := 16. "True if the bitmap is tiled" GBColormapOffset := 18. "Offset of colormap, if any" GBMBaseSize := 18. "Basic size of bitmap fill" ! ! !BalloonEngineConstants class methodsFor: 'pool definition' stamp: 'ar 5/18/2003 19:59'! initPrimitiveConstants "Initialize the primitive constants" "Primitive type constants" GEPrimitiveUnknown := 0. GEPrimitiveEdgeMask := 16rFF. GEPrimitiveFillMask := 16rFF00. GEPrimitiveTypeMask := 16rFFFF. "General state constants (Note: could be compressed later)" GEObjectType := 0. "Type of object" GEObjectLength := 1. "Length of object" GEObjectIndex := 2. "Index into external objects" GEObjectUnused := 3. "Currently unused" ! ! !BalloonEngineConstants class methodsFor: 'pool definition' stamp: 'ar 5/18/2003 20:00'! initStateConstants "Initialize the state Constants" GEStateUnlocked := 0. "Buffer is unlocked and can be modified as wanted" GEStateAddingFromGET := 1. "Adding edges from the GET" GEStateWaitingForEdge := 2. "Waiting for edges added to GET" GEStateScanningAET := 3. "Scanning the active edge table" GEStateWaitingForFill := 4. "Waiting for a fill to mix in during AET scan" GEStateBlitBuffer := 5. "Blt the current scan line" GEStateUpdateEdges := 6. "Update edges to next scan line" GEStateWaitingChange := 7. "Waiting for a changed edge" GEStateCompleted := 8. "Rendering completed" "Error constants" GErrorNoMoreSpace := 1. "No more space in collection" GErrorBadState := 2. "Tried to call a primitive while engine in bad state" GErrorNeedFlush := 3. "Tried to call a primitive that requires flushing before" "Incremental error constants" GErrorGETEntry := 4. "Unknown entry in GET" GErrorFillEntry := 5. "Unknown FILL encountered" GErrorAETEntry := 6. "Unknown entry in AET" ! ! !BalloonEngineConstants class methodsFor: 'pool definition' stamp: 'ar 5/18/2003 20:04'! initWorkBufferConstants "Initialize the work buffer constants" "General work buffer constants" GWMagicNumber := 16r416E6469. "Magic number" GWHeaderSize := 128. "Size of header" GWMinimalSize := 256. "Minimal size of work buffer" "Header entries" GWMagicIndex := 0. "Index of magic number" GWSize := 1. "Size of full buffer" GWState := 2. "Current state (e.g., locked or not." "Buffer entries" GWObjStart := 8. "objStart" GWObjUsed := 9. "objUsed" GWBufferTop := 10. "wbTop" GWGETStart := 11. "getStart" GWGETUsed := 12. "getUsed" GWAETStart := 13. "aetStart" GWAETUsed := 14. "aetUsed" "Transform entries" GWHasEdgeTransform := 16. "True if we have an edge transformation" GWHasColorTransform := 17. "True if we have a color transformation" GWEdgeTransform := 18. "2x3 edge transformation" GWColorTransform := 24. "8 word RGBA color transformation" "Span entries" GWSpanStart := 32. "spStart" GWSpanSize := 33. "spSize" GWSpanEnd := 34. "spEnd" GWSpanEndAA := 35. "spEndAA" "Bounds entries" GWFillMinX := 36. "fillMinX" GWFillMaxX := 37. "fillMaxX" GWFillMinY := 38. "fillMinY" GWFillMaxY := 39. "fillMaxY" GWFillOffsetX := 40. "fillOffsetX" GWFillOffsetY := 41. "fillOffsetY" GWClipMinX := 42. GWClipMaxX := 43. GWClipMinY := 44. GWClipMaxY := 45. GWDestOffsetX := 46. GWDestOffsetY := 47. "AA entries" GWAALevel := 48. "aaLevel" GWAAShift := 49. "aaShift" GWAAColorShift := 50. "aaColorShift" GWAAColorMask := 51. "aaColorMask" GWAAScanMask := 52. "aaScanMask" GWAAHalfPixel := 53. "aaHalfPixel" "Misc entries" GWNeedsFlush := 63. "True if the engine may need a flush" GWStopReason := 64. "stopReason" GWLastExportedEdge := 65. "last exported edge" GWLastExportedFill := 66. "last exported fill" GWLastExportedLeftX := 67. "last exported leftX" GWLastExportedRightX := 68. "last exported rightX" GWClearSpanBuffer := 69. "Do we have to clear the span buffer?" GWPointListFirst := 70. "First point list in buffer" GWPoint1 := 80. GWPoint2 := 82. GWPoint3 := 84. GWPoint4 := 86. GWCurrentY := 88. "Profile stats" GWTimeInitializing := 90. GWCountInitializing := 91. GWTimeFinishTest := 92. GWCountFinishTest := 93. GWTimeNextGETEntry := 94. GWCountNextGETEntry := 95. GWTimeAddAETEntry := 96. GWCountAddAETEntry := 97. GWTimeNextFillEntry := 98. GWCountNextFillEntry := 99. GWTimeMergeFill := 100. GWCountMergeFill := 101. GWTimeDisplaySpan := 102. GWCountDisplaySpan := 103. GWTimeNextAETEntry := 104. GWCountNextAETEntry := 105. GWTimeChangeAETEntry := 106. GWCountChangeAETEntry := 107. "Bezier stats" GWBezierMonotonSubdivisions := 108. "# of subdivision due to non-monoton beziers" GWBezierHeightSubdivisions := 109. "# of subdivisions due to excessive height" GWBezierOverflowSubdivisions := 110. "# of subdivisions due to possible int overflow" GWBezierLineConversions := 111. "# of beziers converted to lines" GWHasClipShapes := 112. "True if the engine contains clip shapes" GWCurrentZ := 113. "Current z value of primitives" ! ! !BalloonEngineConstants class methodsFor: 'pool definition' stamp: 'ar 5/18/2003 20:08'! initialize "BalloonEngineConstants initialize" self initStateConstants. self initWorkBufferConstants. self initPrimitiveConstants. self initEdgeConstants. self initFillConstants. self initializeInstVarNames: BalloonEngine prefixedBy: 'BE'. self initializeInstVarNames: BalloonEdgeData prefixedBy: 'ET'. self initializeInstVarNames: BalloonFillData prefixedBy: 'FT'.! ! !BalloonEngineConstants class methodsFor: 'pool definition' stamp: 'ar 5/18/2003 20:07'! initializeInstVarNames: aClass prefixedBy: aString | token value | aClass instVarNames doWithIndex:[:instVarName :index| token := (aString, instVarName first asUppercase asString, (instVarName copyFrom: 2 to: instVarName size),'Index') asSymbol. value := index - 1. (self bindingOf: token) ifNil:[self addClassVarName: token]. (self bindingOf: token) value: value. ]. token := (aString, aClass name,'Size') asSymbol. (self bindingOf: token) ifNil:[self addClassVarName: token]. (self bindingOf: token) value: aClass instSize.! ! Object subclass: #BalloonFillData instanceVariableNames: 'index minX maxX yValue source destForm' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Simulation'! !BalloonFillData commentStamp: '' prior: 0! This class is a simulation of the code that's run by the Balloon engine. For debugging purposes only.! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:56'! destForm ^destForm! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:56'! destForm: aForm destForm := aForm! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:55'! index ^index! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:55'! index: anInteger index := anInteger! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:55'! maxX ^maxX! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:55'! maxX: anInteger maxX := anInteger! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:55'! minX ^minX! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:55'! minX: anInteger minX := anInteger! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:56'! source ^source! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:56'! source: anObject source := anObject! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/28/1998 16:35'! width ^maxX - minX! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:55'! yValue ^yValue! ! !BalloonFillData methodsFor: 'accessing' stamp: 'ar 10/27/1998 15:55'! yValue: anInteger yValue := anInteger! ! !BalloonFillData methodsFor: 'computing' stamp: 'ar 11/14/1998 19:32'! computeFill (destForm isNil or:[destForm width < self width]) ifTrue:[ destForm := Form extent: (self width + 10) @ 1 depth: 32. ]. source computeFillFrom: minX to: maxX at: yValue in: destForm! ! TestCase subclass: #BalloonFontTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'MorphicTests-Widgets'! !BalloonFontTest methodsFor: 'tests' stamp: 'sd 12/9/2001 21:44'! testDefaultFont "(self selector: #testDefaultFont) debug" self assert: RectangleMorph new balloonFont = BalloonMorph balloonFont. self assert: RectangleMorph new defaultBalloonFont = BalloonMorph balloonFont.! ! !BalloonFontTest methodsFor: 'tests' stamp: 'sd 12/9/2001 21:55'! testSpecificFont "(self selector: #testSpecificFont) debug" | aMorph | aMorph := RectangleMorph new. self assert: RectangleMorph new balloonFont = BalloonMorph balloonFont. self assert: RectangleMorph new defaultBalloonFont = BalloonMorph balloonFont. aMorph balloonFont: (StrikeFont familyName: #ComicPlain size: 19). self assert: aMorph balloonFont = (StrikeFont familyName: #ComicPlain size: 19). "The next test is horrible because I do no know how to access the font with the appropiate interface" self assert: (((BalloonMorph getTextMorph: 'lulu' for: aMorph) text runs at: 1) at: 1) font = (StrikeFont familyName: #ComicPlain size: 19)! ! Object subclass: #BalloonLineSimulation instanceVariableNames: 'start end xIncrement xDirection error errorAdjUp errorAdjDown' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Simulation'! !BalloonLineSimulation commentStamp: '' prior: 0! This class is a simulation of the code that's run by the Balloon engine. For debugging purposes only.! !BalloonLineSimulation methodsFor: 'accessing' stamp: 'ar 10/30/1998 03:02'! end ^end! ! !BalloonLineSimulation methodsFor: 'accessing' stamp: 'ar 10/30/1998 03:02'! end: aPoint end := aPoint! ! !BalloonLineSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:31'! initialX ^start y <= end y ifTrue:[start x] ifFalse:[end x]! ! !BalloonLineSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:31'! initialY ^start y <= end y ifTrue:[start y] ifFalse:[end y]! ! !BalloonLineSimulation methodsFor: 'accessing' stamp: 'ar 10/27/1998 20:31'! initialZ ^0 "Assume no depth given"! ! !BalloonLineSimulation methodsFor: 'accessing' stamp: 'ar 10/30/1998 03:02'! start ^start! ! !BalloonLineSimulation methodsFor: 'accessing' stamp: 'ar 10/30/1998 03:02'! start: aPoint start := aPoint! ! !BalloonLineSimulation methodsFor: 'computing' stamp: 'ar 10/27/1998 20:52'! computeInitialStateFrom: source with: aTransformation "Compute the initial state in the receiver." start := (aTransformation localPointToGlobal: source start) asIntegerPoint. end := (aTransformation localPointToGlobal: source end) asIntegerPoint.! ! !BalloonLineSimulation methodsFor: 'computing' stamp: 'ar 10/27/1998 23:22'! stepToFirstScanLineAt: yValue in: edgeTableEntry "Compute the initial x value for the scan line at yValue" | startX endX startY endY yDir deltaY deltaX widthX | (start y) <= (end y) ifTrue:[ startX := start x. endX := end x. startY := start y. endY := end y. yDir := 1. ] ifFalse:[ startX := end x. endX := start x. startY := end y. endY := start y. yDir := -1. ]. deltaY := endY - startY. deltaX := endX - startX. "Quickly check if the line is visible at all" (yValue >= endY or:[deltaY = 0]) ifTrue:[^edgeTableEntry lines: 0]. "Check if edge goes left to right" deltaX >= 0 ifTrue:[ xDirection := 1. widthX := deltaX. error := 0. ] ifFalse:[ xDirection := -1. widthX := 0 - deltaX. error := 1 - deltaY. ]. "Check if edge is horizontal" deltaY = 0 ifTrue:[ xIncrement := 0. errorAdjUp := 0] ifFalse:["Check if edge is y-major" deltaY > widthX ifTrue:[ xIncrement := 0. errorAdjUp := widthX] ifFalse:[ xIncrement := (widthX // deltaY) * xDirection. errorAdjUp := widthX \\ deltaY]]. errorAdjDown := deltaY. edgeTableEntry xValue: startX. edgeTableEntry lines: deltaY. "If not at first scan line then step down to yValue" yValue = startY ifFalse:[ startY to: yValue do:[:y| self stepToNextScanLineAt: y in: edgeTableEntry]. "And adjust remainingLines" edgeTableEntry lines: deltaY - (yValue - startY). ].! ! !BalloonLineSimulation methodsFor: 'computing' stamp: 'ar 10/27/1998 20:39'! stepToNextScanLineAt: yValue in: edgeTableEntry "Compute the next x value for the scan line at yValue. This message is sent during incremental updates. The yValue parameter is passed in here for edges that have more complicated computations," | x | x := edgeTableEntry xValue + xIncrement. error := error + errorAdjUp. error > 0 ifTrue:[ x := x + xDirection. error := error - errorAdjDown. ]. edgeTableEntry xValue: x.! ! !BalloonLineSimulation methodsFor: 'computing' stamp: 'ar 10/29/1998 23:42'! subdivide ^nil! ! !BalloonLineSimulation methodsFor: 'printing' stamp: 'ar 10/27/1998 23:20'! printOn: aStream aStream nextPutAll: self class name; nextPut:$(; print: start; nextPutAll:' - '; print: end; nextPut:$)! ! !BalloonLineSimulation methodsFor: 'printing' stamp: 'MPW 1/1/1901 21:57'! printOnStream: aStream aStream print: self class name; print:'('; write: start; print:' - '; write: end; print:')'.! ! PolygonMorph subclass: #BalloonMorph instanceVariableNames: 'target offsetFromTarget balloonOwner' classVariableNames: 'BalloonColor BalloonFont' poolDictionaries: '' category: 'Morphic-Widgets'! !BalloonMorph commentStamp: '' prior: 0! A balloon with text used for the display of explanatory information. Balloon help is integrated into Morphic as follows: If a Morph has the property #balloonText, then it will respond to #showBalloon by adding a text balloon to the world, and to #deleteBalloon by removing the balloon. Moreover, if mouseOverEnabled is true (see class msg), then the Hand will arrange to cause display of the balloon after the mouse has lingered over the morph for a while, and removal of the balloon when the mouse leaves the bounds of that morph. In any case, the Hand will attempt to remove any such balloons before handling mouseDown events, or displaying other balloons. Balloons should not be duplicated with veryDeepCopy unless their target is also duplicated at the same time.! !BalloonMorph methodsFor: 'accessing' stamp: 'ar 10/3/2000 17:19'! balloonOwner ^balloonOwner! ! !BalloonMorph methodsFor: 'initialization' stamp: 'dgd 3/12/2006 14:27'! defaultBorderColor "answer the default border color/fill style for the receiver" ^ self defaultColor muchDarker"Color black"! ! !BalloonMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:36'! defaultBorderWidth "answer the default border width for the receiver" ^ 1! ! !BalloonMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:24'! defaultColor "answer the default color/fill style for the receiver" ^ self class balloonColor! ! !BalloonMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 20:20'! initialize "initialize the state of the receiver" super initialize. "" self beSmoothCurve. offsetFromTarget := 0 @ 0! ! !BalloonMorph methodsFor: 'initialization' stamp: 'ar 10/4/2000 10:13'! popUpFor: aMorph hand: aHand "Pop up the receiver as balloon help for the given hand" balloonOwner := aMorph. self popUpForHand: aHand.! ! !BalloonMorph methodsFor: 'initialization' stamp: 'RAA 7/1/2001 18:48'! popUpForHand: aHand "Pop up the receiver as balloon help for the given hand" | worldBounds | self lock. self fullBounds. "force layout" self setProperty: #morphicLayerNumber toValue: self morphicLayerNumber. aHand world addMorphFront: self. "So that if the translation below makes it overlap the receiver, it won't interfere with the rootMorphsAt: logic and hence cause flashing. Without this, flashing happens, believe me!!" ((worldBounds := aHand world bounds) containsRect: self bounds) ifFalse: [self bounds: (self bounds translatedToBeWithin: worldBounds)]. aHand balloonHelp: self. ! ! !BalloonMorph methodsFor: 'menus' stamp: 'wiz 12/30/2004 17:14'! adjustedCenter "Return the center of the original textMorph box within the balloon." ^ (self vertices last: 4) average rounded ! ! !BalloonMorph methodsFor: 'stepping and presenter' stamp: 'sma 12/23/1999 14:05'! step "Move with target." target ifNotNil: [self position: target position + offsetFromTarget]. ! ! !BalloonMorph methodsFor: 'testing' stamp: 'di 9/18/97 10:10'! stepTime ^ 0 "every cycle"! ! !BalloonMorph methodsFor: 'wiw support' stamp: 'RAA 6/27/2000 18:07'! morphicLayerNumber "helpful for insuring some morphs always appear in front of or behind others. smaller numbers are in front" ^5 "Balloons are very front-like things"! ! !BalloonMorph methodsFor: 'private' stamp: 'sma 12/23/1999 14:06'! setTarget: aMorph (target := aMorph) ifNotNil: [offsetFromTarget := self position - target position]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BalloonMorph class instanceVariableNames: ''! !BalloonMorph class methodsFor: '*FreeType-override' stamp: 'tween 8/7/2007 01:59'! chooseBalloonFont "BalloonMorph chooseBalloonFont" Preferences chooseFontWithPrompt: 'Ballon Help font...' translated andSendTo: self withSelector: #setBalloonFontTo: highlightSelector: #balloonFont! ! !BalloonMorph class methodsFor: 'instance creation' stamp: 'sma 12/23/1999 20:05'! string: str for: morph ^ self string: str for: morph corner: #bottomLeft! ! !BalloonMorph class methodsFor: 'instance creation' stamp: 'sd 12/5/2001 20:27'! string: str for: morph corner: cornerName "Make up and return a balloon for morph. Find the quadrant that clips the text the least, using cornerName as a tie-breaker. tk 9/12/97" | tm vertices | tm := self getTextMorph: str for: morph. vertices := self getVertices: tm bounds. vertices := self getBestLocation: vertices for: morph corner: cornerName. ^ self new color: morph balloonColor; setVertices: vertices; addMorph: tm; setTarget: morph! ! !BalloonMorph class methodsFor: 'utility' stamp: 'sma 11/11/2000 14:59'! balloonColor ^ BalloonColor! ! !BalloonMorph class methodsFor: 'utility' stamp: 'sw 1/31/2000 15:43'! balloonFont ^ BalloonFont! ! !BalloonMorph class methodsFor: 'utility' stamp: 'sma 11/11/2000 14:59'! setBalloonColorTo: aColor aColor ifNotNil: [BalloonColor := aColor]! ! !BalloonMorph class methodsFor: 'utility' stamp: 'sw 1/31/2000 15:40'! setBalloonFontTo: aFont aFont ifNotNil: [BalloonFont := aFont]! ! !BalloonMorph class methodsFor: 'private' stamp: 'wiz 1/24/2005 00:32'! getBestLocation: vertices for: morph corner: cornerName "Try four rel locations of the balloon for greatest unclipped area. 12/99 sma" | rect maxArea verts rectCorner morphPoint mbc a mp dir bestVerts result usableArea | "wiz 1/8/2005 Choose rect independantly of vertice order or size. Would be nice it this took into account curveBounds but it does not." rect := Rectangle encompassing: vertices. maxArea := -1. verts := vertices. usableArea := (morph world ifNil: [self currentWorld]) viewBox. 1 to: 4 do: [:i | dir := #(vertical horizontal) atWrap: i. verts := verts collect: [:p | p flipBy: dir centerAt: rect center]. rectCorner := #(bottomLeft bottomRight topRight topLeft) at: i. morphPoint := #(topCenter topCenter bottomCenter bottomCenter) at: i. a := ((rect align: (rect perform: rectCorner) with: (mbc := morph boundsForBalloon perform: morphPoint)) intersect: usableArea) area. (a > maxArea or: [a = rect area and: [rectCorner = cornerName]]) ifTrue: [maxArea := a. bestVerts := verts. mp := mbc]]. result := bestVerts collect: [:p | p + (mp - bestVerts first)] "Inlined align:with:". ^ result! ! !BalloonMorph class methodsFor: 'private' stamp: 'sd 12/5/2001 20:28'! getTextMorph: aStringOrMorph for: balloonOwner "Construct text morph." | m text | aStringOrMorph isMorph ifTrue: [m := aStringOrMorph] ifFalse: [BalloonFont ifNil: [text := aStringOrMorph] ifNotNil: [text := Text string: aStringOrMorph attribute: (TextFontReference toFont: balloonOwner balloonFont)]. m := (TextMorph new contents: text) centered]. m setToAdhereToEdge: #adjustedCenter. ^ m! ! !BalloonMorph class methodsFor: 'private' stamp: 'wiz 1/8/2005 18:05'! getVertices: bounds "Construct vertices for a balloon up and to left of anchor" | corners | corners := bounds corners atAll: #(1 4 3 2). ^ (Array with: corners first + (0 - bounds width // 2 @ 0) with: corners first + (0 - bounds width // 4 @ (bounds height // 2))) , corners! ! RectangleMorph subclass: #BalloonRectangleMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Balloon'! !BalloonRectangleMorph commentStamp: '' prior: 0! BalloonRectangleMorph is an example for drawing using the BalloonEngine.! !BalloonRectangleMorph methodsFor: 'accessing' stamp: 'ar 11/15/1998 22:24'! doesBevels "To return true means that this object can show bevelled borders, and therefore can accept, eg, #raised or #inset as valid borderColors. Must be overridden by subclasses that do not support bevelled borders." ^ false! ! !BalloonRectangleMorph methodsFor: 'drawing' stamp: 'ar 11/15/1998 22:40'! drawOn: aCanvas (color isKindOf: OrientedFillStyle) ifTrue:[ color origin: bounds center. color direction: (bounds extent x * 0.7) @ 0. color normal: 0@(bounds extent y * 0.7). ]. (borderColor isKindOf: OrientedFillStyle) ifTrue:[ borderColor origin: bounds topLeft. borderColor direction: (bounds extent x) @ 0. borderColor normal: 0@(bounds extent y). ]. aCanvas asBalloonCanvas drawRectangle: (bounds insetBy: borderWidth // 2) color: color borderWidth: borderWidth borderColor: borderColor.! ! !BalloonRectangleMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:33'! defaultBorderColor "answer the default border color/fill style for the receiver" ^ GradientFillStyle ramp: {0.0 -> Color black. 1.0 -> Color white}! ! !BalloonRectangleMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:36'! defaultBorderWidth "answer the default border width for the receiver" ^ 10! ! !BalloonRectangleMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:24'! defaultColor "answer the default color/fill style for the receiver" | result | result := GradientFillStyle ramp: {0.0 -> Color green. 0.5 -> Color yellow. 1.0 -> Color red}. result radial: true. ^ result! ! !BalloonRectangleMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:41'! initialize "initialize the state of the receiver" super initialize. "" self extent: 100 @ 100! ! !BalloonRectangleMorph methodsFor: 'rotate scale and flex' stamp: 'ar 11/15/1998 22:20'! newTransformationMorph ^MatrixTransformMorph new! ! !BalloonRectangleMorph methodsFor: 'testing' stamp: 'ar 8/25/2001 19:08'! canDrawBorder: aBorderStyle ^aBorderStyle style == #simple! ! Object subclass: #BalloonSolidFillSimulation instanceVariableNames: 'color' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Simulation'! !BalloonSolidFillSimulation commentStamp: '' prior: 0! This class is a simulation of the code that's run by the Balloon engine. For debugging purposes only.! !BalloonSolidFillSimulation methodsFor: 'computing' stamp: 'ar 10/27/1998 23:07'! computeFillFrom: minX to: maxX at: yValue in: form | bb | color isTransparent ifFalse:[ bb := BitBlt toForm: form. bb fillColor: color. bb destX: 0 destY: 0 width: (maxX - minX) height: 1. bb combinationRule: Form over. bb copyBits].! ! !BalloonSolidFillSimulation methodsFor: 'computing' stamp: 'ar 10/27/1998 23:08'! computeInitialStateFrom: source with: aColorTransform color := source asColor.! ! Object subclass: #BalloonState instanceVariableNames: 'transform colorTransform aaLevel' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Engine'! !BalloonState commentStamp: '' prior: 0! This class is a repository for data which needs to be preserved during certain operations of BalloonCanvas.! !BalloonState methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:47'! aaLevel ^aaLevel! ! !BalloonState methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:47'! aaLevel: aNumber aaLevel := aNumber! ! !BalloonState methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:42'! colorTransform ^colorTransform! ! !BalloonState methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:42'! colorTransform: aColorTransform colorTransform := aColorTransform! ! !BalloonState methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:41'! transform ^transform! ! !BalloonState methodsFor: 'accessing' stamp: 'ar 12/30/1998 10:42'! transform: aMatrixTransform transform := aMatrixTransform! ! MimeConverter subclass: #Base64MimeConverter instanceVariableNames: 'data' classVariableNames: 'FromCharTable ToCharTable' poolDictionaries: '' category: 'Network-MIME'! !Base64MimeConverter commentStamp: '' prior: 0! This class encodes and decodes data in Base64 format. This is MIME encoding. We translate a whole stream at once, taking a Stream as input and giving one as output. Returns a whole stream for the caller to use. 0 A 17 R 34 i 51 z 1 B 18 S 35 j 52 0 2 C 19 T 36 k 53 1 3 D 20 U 37 l 54 2 4 E 21 V 38 m 55 3 5 F 22 W 39 n 56 4 6 G 23 X 40 o 57 5 7 H 24 Y 41 p 58 6 8 I 25 Z 42 q 59 7 9 J 26 a 43 r 60 8 10 K 27 b 44 s 61 9 11 L 28 c 45 t 62 + 12 M 29 d 46 u 63 / 13 N 30 e 47 v 14 O 31 f 48 w (pad) = 15 P 32 g 49 x 16 Q 33 h 50 y Outbound: bytes are broken into 6 bit chunks, and the 0-63 value is converted to a character. 3 data bytes go into 4 characters. Inbound: Characters are translated in to 0-63 values and shifted into 8 bit bytes. (See: N. Borenstein, Bellcore, N. Freed, Innosoft, Network Working Group, Request for Comments: RFC 1521, September 1993, MIME (Multipurpose Internet Mail Extensions) Part One: Mechanisms for Specifying and Describing the Format of Internet Message Bodies. Sec 6.2) By Ted Kaehler, based on Tim Olson's Base64Filter.! !Base64MimeConverter methodsFor: 'conversion' stamp: 'tk 12/9/97 13:34'! mimeDecode "Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full byte stream of characters. Reutrn a whole stream for the user to read." | nibA nibB nibC nibD | [mimeStream atEnd] whileFalse: [ (nibA := self nextValue) ifNil: [^ dataStream]. (nibB := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibA bitShift: 2) + (nibB bitShift: -4)) asCharacter. nibB := nibB bitAnd: 16rF. (nibC := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibB bitShift: 4) + (nibC bitShift: -2)) asCharacter. nibC := nibC bitAnd: 16r3. (nibD := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibC bitShift: 6) + nibD) asCharacter. ]. ^ dataStream! ! !Base64MimeConverter methodsFor: 'conversion' stamp: 'tk 12/9/97 13:39'! mimeDecodeToByteArray "Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full ByteArray of 0-255 values. Reutrn a whole stream for the user to read." | nibA nibB nibC nibD | [mimeStream atEnd] whileFalse: [ (nibA := self nextValue) ifNil: [^ dataStream]. (nibB := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibA bitShift: 2) + (nibB bitShift: -4)). nibB := nibB bitAnd: 16rF. (nibC := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibB bitShift: 4) + (nibC bitShift: -2)). nibC := nibC bitAnd: 16r3. (nibD := self nextValue) ifNil: [^ dataStream]. dataStream nextPut: ((nibC bitShift: 6) + nibD). ]. ^ dataStream! ! !Base64MimeConverter methodsFor: 'conversion' stamp: 'ls 2/10/2001 13:26'! mimeEncode "Convert from data to 6 bit characters." | phase1 phase2 raw nib lineLength | phase1 := phase2 := false. lineLength := 0. [dataStream atEnd] whileFalse: [ lineLength >= 70 ifTrue: [ mimeStream cr. lineLength := 0. ]. data := raw := dataStream next asInteger. nib := (data bitAnd: 16rFC) bitShift: -2. mimeStream nextPut: (ToCharTable at: nib+1). (raw := dataStream next) ifNil: [raw := 0. phase1 := true]. data := ((data bitAnd: 3) bitShift: 8) + raw asInteger. nib := (data bitAnd: 16r3F0) bitShift: -4. mimeStream nextPut: (ToCharTable at: nib+1). (raw := dataStream next) ifNil: [raw := 0. phase2 := true]. data := ((data bitAnd: 16rF) bitShift: 8) + (raw asInteger). nib := (data bitAnd: 16rFC0) bitShift: -6. mimeStream nextPut: (ToCharTable at: nib+1). nib := (data bitAnd: 16r3F). mimeStream nextPut: (ToCharTable at: nib+1). lineLength := lineLength + 4.]. phase1 ifTrue: [mimeStream skip: -2; nextPut: $=; nextPut: $=. ^ mimeStream]. phase2 ifTrue: [mimeStream skip: -1; nextPut: $=. ^ mimeStream]. ! ! !Base64MimeConverter methodsFor: 'conversion' stamp: 'tk 12/9/97 13:21'! nextValue "The next six bits of data char from the mimeStream, or nil. Skip all other chars" | raw num | [raw := mimeStream next. raw ifNil: [^ nil]. "end of stream" raw == $= ifTrue: [^ nil]. num := FromCharTable at: raw asciiValue + 1. num ifNotNil: [^ num]. "else ignore space, return, tab, ..." true] whileTrue.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Base64MimeConverter class instanceVariableNames: ''! !Base64MimeConverter class methodsFor: 'as yet unclassified' stamp: 'damiencassou 5/30/2008 11:45'! decodeInteger: mimeString "Decode the MIME string into an integer of any length" | bytes sum | bytes := (Base64MimeConverter mimeDecodeToBytes: mimeString readStream) contents. sum := 0. bytes reverseDo: [ :by | sum := sum * 256 + by ]. ^ sum! ! !Base64MimeConverter class methodsFor: 'as yet unclassified' stamp: 'tk 2/21/2000 17:22'! encodeInteger: int | strm | "Encode an integer of any length and return the MIME string" strm := ReadWriteStream on: (ByteArray new: int digitLength). 1 to: int digitLength do: [:ii | strm nextPut: (int digitAt: ii)]. strm reset. ^ ((self mimeEncode: strm) contents) copyUpTo: $= "remove padding"! ! !Base64MimeConverter class methodsFor: 'as yet unclassified' stamp: 'tk 12/9/97 13:53'! initialize FromCharTable := Array new: 256. "nils" ToCharTable := Array new: 64. ($A asciiValue to: $Z asciiValue) doWithIndex: [:val :ind | FromCharTable at: val+1 put: ind-1. ToCharTable at: ind put: val asCharacter]. ($a asciiValue to: $z asciiValue) doWithIndex: [:val :ind | FromCharTable at: val+1 put: ind+25. ToCharTable at: ind+26 put: val asCharacter]. ($0 asciiValue to: $9 asciiValue) doWithIndex: [:val :ind | FromCharTable at: val+1 put: ind+25+26. ToCharTable at: ind+26+26 put: val asCharacter]. FromCharTable at: $+ asciiValue + 1 put: 62. ToCharTable at: 63 put: $+. FromCharTable at: $/ asciiValue + 1 put: 63. ToCharTable at: 64 put: $/. ! ! !Base64MimeConverter class methodsFor: 'as yet unclassified' stamp: 'tk 12/12/97 11:41'! mimeDecodeToBytes: aStream "Return a RWBinaryOrTextStream of the original ByteArray. aStream has only 65 innocuous character values. aStream is not binary. (See class comment). 4 bytes in aStream goes to 3 bytes in output." | me | aStream position: 0. me := self new mimeStream: aStream. me dataStream: (RWBinaryOrTextStream on: (ByteArray new: aStream size * 3 // 4)). me mimeDecodeToByteArray. me dataStream position: 0. ^ me dataStream! ! !Base64MimeConverter class methodsFor: 'as yet unclassified' stamp: 'tk 12/9/97 13:01'! mimeDecodeToChars: aStream "Return a ReadWriteStream of the original String. aStream has only 65 innocuous character values. It is not binary. (See class comment). 4 bytes in aStream goes to 3 bytes in output." | me | aStream position: 0. me := self new mimeStream: aStream. me dataStream: (ReadWriteStream on: (String new: aStream size * 3 // 4)). me mimeDecode. me dataStream position: 0. ^ me dataStream! ! !Base64MimeConverter class methodsFor: 'as yet unclassified' stamp: 'tk 12/9/97 12:28'! mimeEncode: aStream "Return a ReadWriteStream of characters. The data of aStream is encoded as 65 innocuous characters. (See class comment). 3 bytes in aStream goes to 4 bytes in output." | me | aStream position: 0. me := self new dataStream: aStream. me mimeStream: (ReadWriteStream on: (String new: aStream size + 20 * 4 // 3)). me mimeEncode. me mimeStream position: 0. ^ me mimeStream! ! TestCase subclass: #Base64MimeConverterTest instanceVariableNames: 'message' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Streams'! !Base64MimeConverterTest commentStamp: '' prior: 0! This is the unit test for the class Base64MimeConverter. Unit tests are a good way to exercise the functionality of your system in a repeatable and automatic manner. They are therefore recommended if you plan to release anything. For more information, see: - http://www.c2.com/cgi/wiki?UnitTest - http://minnow.cc.gatech.edu/squeak/1547 - the sunit class category! !Base64MimeConverterTest methodsFor: 'initialization' stamp: 'stephaneducasse 2/4/2006 20:10'! setUp message := ReadWriteStream on: (String new: 10). message nextPutAll: 'Hi There!!'.! ! !Base64MimeConverterTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:23'! testMimeEncodeDecode | encoded | encoded := Base64MimeConverter mimeEncode: message. self assert: (encoded contents = 'SGkgVGhlcmUh'). self assert: ((Base64MimeConverter mimeDecodeToChars: encoded) contents = message contents).! ! TestCase subclass: #BasicBehaviorClassMetaclassTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Classes'! !BasicBehaviorClassMetaclassTest commentStamp: '' prior: 0! This class contains some tests regarding the classes Behavior ClassDescription Class Metaclass --- ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'sd 6/5/2005 08:19'! testBehaviorClassClassDescriptionMetaclassHierarchy "self run: #testBehaviorClassClassDescriptionMetaclassHierarchy" self assert: Class superclass == ClassDescription. self assert: Metaclass superclass == ClassDescription. self assert: ClassDescription superclass == Behavior. self assert: Behavior superclass = Object. self assert: Class class class == Metaclass. self assert: Metaclass class class == Metaclass. self assert: ClassDescription class class == Metaclass. self assert: Behavior class class == Metaclass. ! ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'md 7/24/2009 15:29'! testClassDescriptionAllSubInstances "self run: #testClassDescriptionAllSubInstances" | cdNo clsNo metaclsNo | Smalltalk garbageCollect. cdNo := ClassDescription allSubInstances size. clsNo := Class allSubInstances size . metaclsNo := Metaclass allSubInstances size. self assert: cdNo = (clsNo + metaclsNo). ! ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'sd 6/5/2005 08:17'! testMetaclass "self run: #testMetaclass" self assert: OrderedCollection class class == Metaclass. self assert: Dictionary class class == Metaclass. self assert: Object class class == Metaclass. ! ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'sd 6/5/2005 08:12'! testMetaclassName "self run: #testMetaclassName" self assert: Dictionary class name = 'Dictionary class'. self assert: OrderedCollection class name = 'OrderedCollection class'. ! ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'sd 6/5/2005 08:12'! testMetaclassNumberOfInstances "self run: #testMetaclassNumberOfInstances" self assert: Dictionary class allInstances size = 1. self assert: OrderedCollection class allInstances size = 1.! ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'sd 6/5/2005 08:18'! testMetaclassPointOfCircularity "self run: #testMetaclassPointOfCircularity" self assert: Metaclass class instanceCount = 1. self assert: Metaclass class someInstance == Metaclass. ! ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'sd 6/5/2005 08:13'! testMetaclassSuperclass "self run: #testMetaclassSuperclass" self assert: Dictionary class superclass == Set class. self assert: OrderedCollection class superclass == SequenceableCollection class. ! ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'sd 6/5/2005 08:14'! testMetaclassSuperclassHierarchy "self run: #testMetaclassSuperclassHierarchy" | s | self assert: SequenceableCollection class instanceCount = 1. self assert: Collection class instanceCount = 1. self assert: Object class instanceCount = 1. self assert: ProtoObject class instanceCount = 1. s := OrderedCollection new. s add: SequenceableCollection class. s add: Collection class. s add: Object class. s add: ProtoObject class. s add: Class. s add: ClassDescription. s add: Behavior. s add: Object. s add: ProtoObject. self assert: OrderedCollection class allSuperclasses = s. ! ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'sd 6/5/2005 08:21'! testObjectAllSubclasses "self run: #testObjectAllSubclasses" | n2 | n2 := Object allSubclasses size. self assert: n2 = (Object allSubclasses select: [:cls | cls class class == Metaclass or: [cls class == Metaclass]]) size! ! !BasicBehaviorClassMetaclassTest methodsFor: 'testing' stamp: 'sd 6/5/2005 08:13'! testSuperclass "self run: #testSuperclass" | s | self assert: Dictionary superclass == Set. self assert: OrderedCollection superclass == SequenceableCollection. s := OrderedCollection new. s add: SequenceableCollection. s add: Collection. s add: Object. s add: ProtoObject. self assert: OrderedCollection allSuperclasses = s. ! ! Categorizer subclass: #BasicClassOrganizer instanceVariableNames: 'subject classComment commentStamp' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Classes'! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 16:02'! classComment classComment ifNil: [^ '']. ^ classComment text ifNil: ['']! ! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'marcus.denker 8/17/2008 20:56'! classComment: aString "Store the comment, aString, associated with the object that refers to the receiver." (aString isKindOf: RemoteString) ifTrue: [classComment := aString] ifFalse: [aString isEmptyOrNil ifTrue: [classComment := nil] ifFalse: [ self error: 'use aClass classComment:'. classComment := RemoteString newString: aString onFileNumber: 2]] "Later add priorSource and date and initials?"! ! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'marcus.denker 8/17/2008 20:56'! classComment: aString stamp: aStamp "Store the comment, aString, associated with the object that refers to the receiver." self commentStamp: aStamp. (aString isKindOf: RemoteString) ifTrue: [classComment := aString] ifFalse: [aString isEmptyOrNil ifTrue: [classComment := nil] ifFalse: [self error: 'use aClass classComment:'. classComment := RemoteString newString: aString onFileNumber: 2]] "Later add priorSource and date and initials?"! ! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 16:03'! commentRemoteStr ^ classComment! ! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 16:03'! commentStamp "Answer the comment stamp for the class" ^ commentStamp! ! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 16:03'! commentStamp: aStamp commentStamp := aStamp! ! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 16:03'! dateCommentLastSubmitted "Answer a Date object indicating when my class comment was last submitted. If there is no date stamp, or one of the old-time guys, return nil" "RecentMessageSet organization dateCommentLastSubmitted" | aStamp tokens | (aStamp := self commentStamp) isEmptyOrNil ifTrue: [^ nil]. tokens := aStamp findBetweenSubStrs: ' '. "space is expected delimiter, but cr is sometimes seen, though of mysterious provenance" ^ tokens size > 1 ifTrue: [[tokens second asDate] ifError: [nil]] ifFalse: [nil]! ! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'marcus.denker 7/29/2009 15:26'! hasComment "Answer whether the class classified by the receiver has a comment." ^classComment notNil! ! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 16:04'! hasSubject ^ self subject notNil! ! !BasicClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 16:04'! subject ^ subject.! ! !BasicClassOrganizer methodsFor: 'fileIn/Out' stamp: 'NS 4/7/2004 16:03'! fileOutCommentOn: aFileStream moveSource: moveSource toFile: fileIndex "Copy the class comment to aFileStream. If moveSource is true (as in compressChanges or compressSources, then update classComment to point to the new file." | fileComment | classComment ifNotNil: [aFileStream cr. fileComment := RemoteString newString: classComment text onFileNumber: fileIndex toFile: aFileStream. moveSource ifTrue: [classComment := fileComment]]! ! !BasicClassOrganizer methodsFor: 'fileIn/Out' stamp: 'NS 4/7/2004 16:04'! moveChangedCommentToFile: aFileStream numbered: fileIndex "If the comment is in the changes file, then move it to a new file." (classComment ~~ nil and: [classComment sourceFileNumber > 1]) ifTrue: [self fileOutCommentOn: aFileStream moveSource: true toFile: fileIndex]! ! !BasicClassOrganizer methodsFor: 'fileIn/Out' stamp: 'NS 4/7/2004 16:04'! objectForDataStream: refStrm | dp | "I am about to be written on an object file. Write a path to me in the other system instead." self hasSubject ifTrue: [ (refStrm insideASegment and: [self subject isSystemDefined not]) ifTrue: [ ^ self]. "do trace me" (self subject isKindOf: Class) ifTrue: [ dp := DiskProxy global: self subject name selector: #organization args: #(). refStrm replace: self with: dp. ^ dp]]. ^ self "in desparation" ! ! !BasicClassOrganizer methodsFor: 'fileIn/Out' stamp: 'NS 4/7/2004 16:04'! putCommentOnFile: aFileStream numbered: sourceIndex moveSource: moveSource forClass: aClass "Store the comment about the class onto file, aFileStream." | header | classComment ifNotNil: [aFileStream cr; nextPut: $!!. header := String streamContents: [:strm | strm nextPutAll: aClass name; nextPutAll: ' commentStamp: '. commentStamp ifNil: [commentStamp := '']. commentStamp storeOn: strm. strm nextPutAll: ' prior: '; nextPutAll: '0']. aFileStream nextChunkPut: header. aClass organization fileOutCommentOn: aFileStream moveSource: moveSource toFile: sourceIndex. aFileStream cr]! ! !BasicClassOrganizer methodsFor: 'private' stamp: 'NS 4/7/2004 16:04'! setSubject: aClassDescription subject := aClassDescription! ! !BasicClassOrganizer methodsFor: 'deprecated' stamp: 'AndrewBlack 9/3/2009 01:08'! hasNoComment "Answer whether the class classified by the receiver has a comment." self deprecated: 'Use ''hasComment'' instead.' on: '29 July 2009' in: #Pharo1.0. ^classComment == nil! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BasicClassOrganizer class instanceVariableNames: ''! !BasicClassOrganizer class methodsFor: 'constants' stamp: 'NS 4/19/2004 15:52'! ambiguous ^ #ambiguous! ! !BasicClassOrganizer class methodsFor: 'instance creation' stamp: 'NS 4/7/2004 16:04'! class: aClassDescription ^ self new setSubject: aClassDescription! ! !BasicClassOrganizer class methodsFor: 'instance creation' stamp: 'NS 4/7/2004 16:04'! class: aClassDescription defaultList: aSortedCollection | inst | inst := self defaultList: aSortedCollection. inst setSubject: aClassDescription. ^ inst! ! Inspector subclass: #BasicInspector instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tools-Inspector'! !BasicInspector methodsFor: 'as yet unclassified' stamp: 'sd 11/20/2005 21:26'! inspect: anObject "Initialize the receiver so that it is inspecting anObject. There is no current selection." self initialize. object := anObject. selectionIndex := 0. contents := ''! ! Object subclass: #BasicRequestor instanceVariableNames: 'caption answer' classVariableNames: '' poolDictionaries: '' category: 'Services-Base'! !BasicRequestor commentStamp: 'rr 7/10/2006 14:44' prior: 0! This class is the root of the Requestor hierarchy. Requestors are interfaces between services and the system. ServiceActions are given an instance of a Requestor, and they ask it for the data they need. The requestor is determined by the model of the application. A class used as a model can implement the #requestor message to return the most suited requestor. A requestor knows how to query its model and the user if needed. Requestor are defined in hierarchies so that the protocol they rely on (methods starting with 'get') can be easily reused.! !BasicRequestor methodsFor: 'executing' stamp: 'rr 5/31/2004 22:43'! get: aString self caption: aString. ^ self getSymbol! ! !BasicRequestor methodsFor: 'generic requests' stamp: 'rr 6/1/2004 21:50'! caption: aString caption := aString! ! !BasicRequestor methodsFor: 'generic requests' stamp: 'DamienCassou 9/29/2009 09:02'! getString | result | result := UIManager default request:caption initialAnswer: answer contents. self newCaption. result isEmptyOrNil ifTrue:[ServiceCancelled signal]. ^ result! ! !BasicRequestor methodsFor: 'generic requests' stamp: 'rr 5/31/2004 22:18'! getStringCollection caption := caption, Character cr asString, 'Separate items with space'. ^ (self getString findTokens: ' ') collect: [:each | each copyWithoutAll: ' ' ]! ! !BasicRequestor methodsFor: 'generic requests' stamp: 'rr 5/31/2004 22:19'! getSymbol ^ self getString asSymbol! ! !BasicRequestor methodsFor: 'generic requests' stamp: 'rr 5/31/2004 22:20'! getSymbolCollection ^[self getStringCollection collect: [:each | each asSymbol]] on: ServiceCancelled do: [#()]! ! !BasicRequestor methodsFor: 'generic requests' stamp: 'PeterHugossonMiller 9/3/2009 00:12'! newCaption caption := 'Enter text'. answer := String new writeStream.! ! !BasicRequestor methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:42'! initialize super initialize. self newCaption! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BasicRequestor class instanceVariableNames: ''! TestCase subclass: #BecomeTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-VM'! !BecomeTest methodsFor: 'testing' stamp: 'brp 9/19/2003 15:28'! testBecome "Test the two way become. Note. we cannot use string literals for this test" | a b c d | a := 'ab' copy. b := 'cd' copy. c := a. d := b. a become: b. self assert: a = 'cd'; assert: b = 'ab'; assert: c = 'cd'; assert: d = 'ab'. ! ! !BecomeTest methodsFor: 'testing' stamp: 'brp 9/19/2003 15:28'! testBecomeForward "Test the forward become." | a b c d | a := 'ab' copy. b := 'cd' copy. c := a. d := b. a becomeForward: b. self assert: a = 'cd'; assert: b = 'cd'; assert: c = 'cd'; assert: d = 'cd'. ! ! !BecomeTest methodsFor: 'testing' stamp: 'brp 9/19/2003 17:36'! testBecomeForwardDontCopyIdentityHash "Check that 1. the argument to becomeForward: is NOT modified to have the receiver's identity hash. 2. the receiver's identity hash is unchanged." | a b hb | a := 'ab' copy. b := 'cd' copy. hb := b identityHash. a becomeForward: b copyHash: false. self assert: a identityHash = hb; assert: b identityHash = hb. ! ! !BecomeTest methodsFor: 'testing' stamp: 'brp 9/19/2003 15:29'! testBecomeForwardHash | a b c hb | a := 'ab' copy. b := 'cd' copy. c := a. hb := b hash. a becomeForward: b. self assert: a hash = hb; assert: b hash = hb; assert: c hash = hb. ! ! !BecomeTest methodsFor: 'testing' stamp: 'brp 9/19/2003 15:27'! testBecomeForwardIdentityHash "Check that 1. the argument to becomeForward: is modified to have the receiver's identity hash. 2. the receiver's identity hash is unchanged." | a b ha | a := 'ab' copy. b := 'cd' copy. ha := a identityHash. a becomeForward: b. self assert: a identityHash = ha; assert: b identityHash = ha. ! ! !BecomeTest methodsFor: 'testing' stamp: 'brp 9/19/2003 15:30'! testBecomeHash | a b c d ha hb | a := 'ab' copy. b := 'cd' copy. c := a. d := b. ha := a hash. hb := b hash. a become: b. self assert: a hash = hb; assert: b hash = ha; assert: c hash = hb; assert: d hash = ha. ! ! !BecomeTest methodsFor: 'testing' stamp: 'brp 9/19/2003 15:31'! testBecomeIdentityHash "Note. The identity hash of both objects seems to change after the become:" | a b c d | a := 'ab' copy. b := 'cd' copy. c := a. d := b. a become: b. self assert: a identityHash = c identityHash; assert: b identityHash = d identityHash; deny: a identityHash = b identityHash. ! ! Object subclass: #Beeper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Support'! !Beeper commentStamp: 'gk 2/26/2004 22:44' prior: 0! Beeper provides simple audio (or in some other way) feedback to the user. The recommended use is "Beeper beep" to give the user the equivalence of a beep. If you want to force the beep to use the primitive in the VM for beeping, then use "Beeper beepPrimitive". In either case, if sounds are disabled there will be no beep. The actual beeping, when you use "Beeper beep", is done by sending a #play message to a registered playable object. You can register your own playable object by invoking the class side method #setDefault: passing in an object that responds to the #play message. The default playable object is an instance of Beeper itself which implements #play on the instance side. That implementation delegates the playing of the beep to the default SoundService. Note that #play is introduced as a common interface between AbstractSound and Beeper. This way we can register instances of AbstractSound as playable entities, for example: Beeper setDefault: (SampledSound new setSamples: self coffeeCupClink samplingRate: 12000). Then "Beeper beep" will play the coffeeCup sound.! !Beeper methodsFor: 'play interface' stamp: 'gk 2/24/2004 23:25'! play "This is how the default Beeper makes a beep, by sending beep to the default sound service. The sound system will check if sounds are enabled." SoundService default beep! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Beeper class instanceVariableNames: 'default'! !Beeper class methodsFor: 'beeping' stamp: 'pavel.krivanek 3/11/2009 07:39'! beep "The preferred way of producing an audible feedback. The default playable entity (an instance of Beeper) also uses the pluggable SoundService mechanism, so it will use the primitive beep only if there is no other sound mechanism available." self default ifNil: [self beepPrimitive] ifNotNil: [ self default play]. ! ! !Beeper class methodsFor: 'beeping' stamp: 'gk 2/24/2004 08:38'! beepPrimitive "Make a primitive beep. Only use this if you want to force this to be a primitive beep. Otherwise use Beeper class>>beep since this method bypasses the current registered playable entity." Preferences soundsEnabled ifTrue: [ self primitiveBeep]! ! !Beeper class methodsFor: 'customize' stamp: 'gk 2/22/2004 17:51'! clearDefault "Clear the default playable. Will be lazily initialized in Beeper class >>default." default := nil! ! !Beeper class methodsFor: 'customize' stamp: 'gk 2/22/2004 17:55'! default "When the default is not defined it is initialized using #newDefault." default isNil ifTrue: [default := self newDefault ]. ^ default! ! !Beeper class methodsFor: 'customize' stamp: 'gk 2/24/2004 22:12'! newDefault "Subclasses may override me to provide a default beep. This base implementation returns an instance of Beeper which uses the pluggable sound service." ^ self new! ! !Beeper class methodsFor: 'customize' stamp: 'gk 2/22/2004 17:54'! setDefault: aPlayableEntity "Set the playable entity used when making a beep. The playable entity should implement the message #play." default := aPlayableEntity! ! !Beeper class methodsFor: 'private' stamp: 'gk 2/24/2004 23:51'! primitiveBeep "Make a primitive beep. Not to be called directly. It is much better to use Beeper class>>beep or Beeper class>>beepPrimitive since this method bypasses the current registered playable entity and does not check Preferences class>>soundsEnabled." self primitiveFailed! ! Object subclass: #Behavior uses: TPureBehavior instanceVariableNames: 'superclass methodDict format' classVariableNames: 'ObsoleteSubclasses' poolDictionaries: '' category: 'Kernel-Classes'! !Behavior commentStamp: 'al 12/8/2005 20:44' prior: 0! My instances describe the behavior of other objects. I provide 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 I am a good starting point for providing instance-specific behavior (as in Metaclass).! !Behavior methodsFor: '*system-support' stamp: 'tpr 12/17/2003 16:04'! allCallsOn "Answer a SortedCollection of all the methods that refer to me by name or as part of an association in a global dict." ^ (self systemNavigation allCallsOn: (self environment associationAt: self theNonMetaClass name)), (self systemNavigation allCallsOn: self theNonMetaClass name) ! ! !Behavior methodsFor: '*system-support' stamp: 'dvf 8/23/2003 12:43'! allCallsOn: aSymbol "Answer a SortedCollection of all the methods that call on aSymbol." ^ self systemNavigation allCallsOn: aSymbol from: self . ! ! !Behavior methodsFor: '*system-support' stamp: 'stephane.ducasse 10/12/2008 21:02'! allUnsentMessages "Answer an array of all the messages defined by the receiver that are not sent anywhere in the system." ^ SystemNavigation default allUnsentMessagesIn: self selectors! ! !Behavior methodsFor: '*traits'! providedSelectors ^ProvidedSelectors current for: self! ! !Behavior methodsFor: '*traits-requires' stamp: 'NS 5/26/2005 12:11'! classAndMethodFor: aSymbol do: binaryBlock ifAbsent: absentBlock "Looks up the selector aSymbol in the class chain. If it is found, binaryBlock is evaluated with the class that defines the selector and the associated method. Otherwise absentBlock is evaluated." | method | self withAllSuperclassesDo: [:class | method := class compiledMethodAt: aSymbol ifAbsent: [nil]. method ifNotNil: [^ binaryBlock value: class value: method]. ]. ^ absentBlock value.! ! !Behavior methodsFor: '*traits-requires' stamp: 'dvf 9/9/2005 19:45'! classesComposedWithMe ^{self}! ! !Behavior methodsFor: '*traits-requires' stamp: 'NS 5/26/2005 14:27'! computeSelfSendersFromInheritedSelfSenders: inheritedCollection localSelfSenders: localCollection "Compute the set of all self-senders from the set of inherited self-senders and the set of local self-senders." | result mDict | mDict := self methodDict. result := IdentitySet new: inheritedCollection size + localCollection size. "This if-statement is just a performance optimization. Both branches are semantically equivalent." inheritedCollection size > mDict size ifTrue: [ result addAll: inheritedCollection. mDict keysDo: [:each | result remove: each ifAbsent: []]. ] ifFalse: [ inheritedCollection do: [:each | (mDict includesKey: each) ifFalse: [result add: each]]. ]. result addAll: localCollection. ^ result.! ! !Behavior methodsFor: '*traits-requires' stamp: 'NS 5/26/2005 14:11'! computeTranslationsAndUpdateUnreachableSet: unreachableCollection "This method computes the set of unreachable selectors in the superclass by altering the set of unreachable selectors in this class. In addition, it builds a dictionary mapping super-sent selectors to the selectors of methods sending these selectors." | translations reachableSenders oldUnreachable | oldUnreachable := unreachableCollection copy. translations := IdentityDictionary new. "Add selectors implemented in this class to unreachable set." self methodDict keysDo: [:s | unreachableCollection add: s]. "Fill translation dictionary and remove super-reachable selectors from unreachable." self sendCaches superSentSelectorsAndSendersDo: [:sent :senders | reachableSenders := FixedIdentitySet readonlyWithAll: senders notIn: oldUnreachable. reachableSenders isEmpty ifFalse: [ translations at: sent put: reachableSenders. unreachableCollection remove: sent ifAbsent: []. ]. ]. ^ translations! ! !Behavior methodsFor: '*traits-requires' stamp: 'dvf 8/4/2005 16:48'! findSelfSendersOf: selector unreachable: unreachableCollection noInheritedSelfSenders: noInheritedBoolean "This method answers a subset of all the reachable methods (local or inherited) that self-send selector (empty set => no self-senders). See Nathanael Sch䲬i's PhD for more details." | selfSenders reachableSelfSenders translations | "Check whether there are local methods that self-send selector and are reachable." selfSenders := self sendCaches selfSendersOf: selector. reachableSelfSenders := FixedIdentitySet readonlyWithAll: selfSenders notIn: unreachableCollection. (self superclass isNil or: [noInheritedBoolean or: [reachableSelfSenders notEmpty]]) ifTrue: [^ reachableSelfSenders]. "Compute the set of unreachable superclass methods and super-send translations and recurse." translations := self computeTranslationsAndUpdateUnreachableSet: unreachableCollection. reachableSelfSenders := superclass findSelfSendersOf: selector unreachable: unreachableCollection noInheritedSelfSenders: false. "Use the translations to replace selectors that are super-sent with the methods that issue the super-sends." reachableSelfSenders := self translateReachableSelfSenders: reachableSelfSenders translations: translations. ^ reachableSelfSenders.! ! !Behavior methodsFor: '*traits-requires' stamp: 'dvf 9/12/2005 11:44'! requiredSelectors ^RequiredSelectors current for: self! ! !Behavior methodsFor: '*traits-requires' stamp: 'dvf 9/6/2005 13:14'! requiredSelectorsCache ^RequiredSelectors current cacheFor: self! ! !Behavior methodsFor: '*traits-requires' stamp: 'dvf 9/1/2005 16:36'! sendCaches ^LocalSends current for: self! ! !Behavior methodsFor: '*traits-requires' stamp: 'NS 5/24/2005 16:38'! translateReachableSelfSenders: senderCollection translations: translationDictionary | result superSenders | (translationDictionary isEmptyOrNil or: [senderCollection isEmpty]) ifTrue: [^ senderCollection]. result := FixedIdentitySet new. senderCollection do: [:s | superSenders := translationDictionary at: s ifAbsent: [nil]. superSenders isNil ifTrue: [result add: s] ifFalse: [result addAll: superSenders]. result isFull ifTrue: [^ result]. ]. ^ result.! ! !Behavior methodsFor: '*traits-requires' stamp: 'dvf 9/12/2005 18:28'! updateRequiredStatusFor: selector inSubclasses: someClasses "Updates the requirements cache to reflect whether selector is required in this class and some of its subclasses." | inheritedMethod | inheritedMethod := self superclass ifNotNil: [self superclass lookupSelector: selector]. ^self updateRequiredStatusFor: selector inSubclasses: someClasses parentSelfSenders: FixedIdentitySet new providedInParent: inheritedMethod noInheritedSelfSenders: false accumulatingInto: IdentitySet new.! ! !Behavior methodsFor: '*traits-requires' stamp: 'dvf 8/9/2005 17:02'! updateRequiredStatusFor: selector inSubclasses: someClasses parentSelfSenders: inheritedSelfSenders providedInParent: providedBoolean noInheritedSelfSenders: noInheritedBoolean "Updates the requirements cache to reflect whether selector is required in this class and all of its subclasses. The parameter inheritedSelfSenders is a subset of the methods in the parent of this class that are known to self-send selector. providedBoolean indicates whether selector is provided in the parent. noInheritedBoolean is true if no self-senders could be found in the superclass. See Nathanael Sch䲬i's PhD for more details." | selfSenders provided m | "Remove from the inherited selfSenders methods that are potentially unreachable." selfSenders := inheritedSelfSenders reject: [:each | self includesSelector: each]. "Check whether the method is provided." m := self compiledMethodAt: selector ifAbsent: [nil]. providedBoolean ifTrue: [ provided := m isNil or: [m isDisabled not and: [m isExplicitlyRequired not and: [m isSubclassResponsibility not]]]. ] ifFalse: [ provided := m notNil and: [m isProvided]. ]. provided ifTrue: [ "If it is provided, it cannot be required." self setRequiredStatusOf: selector to: false. ] ifFalse: [ "If there are non-overridden inherited selfSenders we know that it must be required. Otherwise, we search for self-senders." selfSenders isEmpty ifTrue: [selfSenders := self findSelfSendersOf: selector unreachable: IdentitySet new noInheritedSelfSenders: noInheritedBoolean]. self setRequiredStatusOf: selector to: selfSenders notEmpty. ]. "Do the same for all subclasses." self subclassesDo: [:each | (someClasses includes: each) ifTrue: [each updateRequiredStatusFor: selector inSubclasses: someClasses parentSelfSenders: selfSenders providedInParent: provided noInheritedSelfSenders: (provided not and: [selfSenders isEmpty])]].! ! !Behavior methodsFor: '*traits-requires' stamp: 'dvf 9/12/2005 19:43'! updateRequiredStatusFor: selector inSubclasses: someClasses parentSelfSenders: inheritedSelfSenders providedInParent: inheritedMethod noInheritedSelfSenders: noInheritedBoolean accumulatingInto: requiringClasses "Updates the requirements cache to reflect whether selector is required in this class and all of its subclasses. The parameter inheritedSelfSenders is a subset of the methods in the parent of this class that are known to self-send selector. providedBoolean indicates whether selector is provided in the parent. noInheritedBoolean is true if no self-senders could be found in the superclass. See Nathanael Sch䲬i's PhD for more details." "Remove from the inherited selfSenders methods that are potentially unreachable." | selfSenders m relevantMethod required lookedForInheritedSelfSenders | lookedForInheritedSelfSenders := false. selfSenders := inheritedSelfSenders reject: [:each | self includesSelector: each]. "Check whether the method is provided." m := self compiledMethodAt: selector ifAbsent: [nil]. relevantMethod := m ifNotNil: [m] ifNil: [inheritedMethod]. relevantMethod ifNotNil: [required := relevantMethod isSubclassResponsibility or: [ relevantMethod isDisabled or: [ relevantMethod isExplicitlyRequired]]] ifNil: ["If there are non-overridden inherited selfSenders we know that it must be required. Otherwise, we search for self-senders." selfSenders isEmpty ifTrue: [selfSenders := self findSelfSendersOf: selector unreachable: IdentitySet new noInheritedSelfSenders: noInheritedBoolean. lookedForInheritedSelfSenders := true]. required := selfSenders notEmpty]. required ifTrue: [requiringClasses add: self]. "Do the same for all subclasses." self subclassesDo: [:each | (someClasses includes: each) ifTrue: [each updateRequiredStatusFor: selector inSubclasses: someClasses parentSelfSenders: selfSenders providedInParent: relevantMethod noInheritedSelfSenders: (lookedForInheritedSelfSenders and: [selfSenders isEmpty]) accumulatingInto: requiringClasses]]. ^requiringClasses! ! !Behavior methodsFor: '*traits-requires' stamp: 'dvf 8/9/2005 15:39'! withInheritanceTraitCompositionIncludes: aTrait ^self withAllSuperclasses anySatisfy: [:c | c traitCompositionIncludes: aTrait]! ! !Behavior methodsFor: 'accessing' stamp: 'ajh 9/19/2001 17:30'! classDepth superclass ifNil: [^ 1]. ^ superclass classDepth + 1! ! !Behavior methodsFor: 'accessing'! compilerClass "Answer a compiler class appropriate for source methods of this class." ^Compiler! ! !Behavior methodsFor: 'accessing'! decompilerClass "Answer a decompiler class appropriate for compiled methods of this class." ^ self compilerClass decompilerClass! ! !Behavior methodsFor: 'accessing'! environment "Return the environment in which the receiver is visible" ^Smalltalk! ! !Behavior methodsFor: 'accessing'! evaluatorClass "Answer an evaluator class appropriate for evaluating expressions in the context of this class." ^Compiler! ! !Behavior methodsFor: 'accessing'! format "Answer an Integer that encodes the kinds and numbers of variables of instances of the receiver." ^format! ! !Behavior methodsFor: 'accessing' stamp: 'di 3/7/2001 17:05'! methodDict methodDict == nil ifTrue: [self recoverFromMDFaultWithTrace]. ^ methodDict! ! !Behavior methodsFor: 'accessing' stamp: 'rca 7/26/2000 16:53'! name "Answer a String that is the name of the receiver." ^'a subclass of ', superclass name! ! !Behavior methodsFor: 'accessing'! parserClass "Answer a parser class to use for parsing method headers." ^self compilerClass parserClass! ! !Behavior methodsFor: 'accessing'! sourceCodeTemplate "Answer an expression to be edited and evaluated in order to define methods in this class or trait." ^'message selector and argument names "comment stating purpose of message" | temporary variable names | statements'! ! !Behavior methodsFor: 'accessing'! subclassDefinerClass "Answer an evaluator class appropriate for evaluating definitions of new subclasses of this class." ^Compiler! ! !Behavior methodsFor: 'accessing' stamp: 'ar 7/13/1999 22:00'! typeOfClass "Answer a symbol uniquely describing the type of the receiver" self instSpec = CompiledMethod instSpec ifTrue:[^#compiledMethod]. "Very special!!" self isBytes ifTrue:[^#bytes]. (self isWords and:[self isPointers not]) ifTrue:[^#words]. self isWeak ifTrue:[^#weak]. self isVariable ifTrue:[^#variable]. ^#normal.! ! !Behavior methodsFor: 'accessing class hierarchy' stamp: 'nb 5/6/2003 17:11'! allSubclasses "Answer a Set of the receiver's and the receiver's descendent's subclasses. " | scan scanTop | scan := OrderedCollection withAll: self subclasses. scanTop := 1. [scanTop > scan size] whileFalse: [scan addAll: (scan at: scanTop) subclasses. scanTop := scanTop + 1]. ^ scan asSet! ! !Behavior methodsFor: 'accessing class hierarchy' stamp: 'sd 3/28/2003 15:06'! allSubclassesWithLevelDo: classAndLevelBlock startingLevel: level "Walk the tree of subclasses, giving the class and its level" | subclassNames | classAndLevelBlock value: self value: level. self == Class ifTrue: [^ self]. "Don't visit all the metaclasses" "Visit subclasses in alphabetical order" subclassNames := SortedCollection new. self subclassesDo: [:subC | subclassNames add: subC name]. subclassNames do: [:name | (self environment at: name) allSubclassesWithLevelDo: classAndLevelBlock startingLevel: level+1]! ! !Behavior methodsFor: 'accessing class hierarchy'! allSuperclasses "Answer an OrderedCollection of the receiver's and the receiver's ancestor's superclasses. The first element is the receiver's immediate superclass, followed by its superclass; the last element is Object." | temp | ^ superclass == nil ifTrue: [ OrderedCollection new] ifFalse: [temp := superclass allSuperclasses. temp addFirst: superclass. temp]! ! !Behavior methodsFor: 'accessing class hierarchy' stamp: 'sd 1/28/2009 14:20'! allSuperclassesIncluding: aClass "Answer an OrderedCollection of the receiver's and the receiver's ancestor's superclasses up to aClass included. The first element is the receiver's immediate superclass up to aClass included." | temp | ^ superclass == aClass ifTrue: [ OrderedCollection with: aClass] ifFalse: [temp := superclass allSuperclassesIncluding: aClass. temp addFirst: superclass. temp]! ! !Behavior methodsFor: 'accessing class hierarchy' stamp: 'sd 3/14/2004 18:09'! subclasses "slow implementation since Behavior does not keep trace of subclasses" ^ self class allInstances select: [:each | each superclass = self ]! ! !Behavior methodsFor: 'accessing class hierarchy'! superclass "Answer the receiver's superclass, a Class." ^superclass! ! !Behavior methodsFor: 'accessing class hierarchy' stamp: 'ar 7/10/1999 12:10'! superclass: aClass "Change the receiver's superclass to be aClass." "Note: Do not use 'aClass isKindOf: Behavior' here in case we recompile from Behavior itself." (aClass == nil or: [aClass isBehavior]) ifTrue: [superclass := aClass. Object flushCache] ifFalse: [self error: 'superclass must be a class-describing object']! ! !Behavior methodsFor: 'accessing class hierarchy'! withAllSubclasses "Answer a Set of the receiver, the receiver's descendent's, and the receiver's descendent's subclasses." ^ self allSubclasses add: self; yourself! ! !Behavior methodsFor: 'accessing class hierarchy'! withAllSuperclasses "Answer an OrderedCollection of the receiver and the receiver's superclasses. The first element is the receiver, followed by its superclass; the last element is Object." | temp | temp := self allSuperclasses. temp addFirst: self. ^ temp! ! !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." ^superclass allClassVarNames! ! !Behavior methodsFor: 'accessing instances and variables'! allInstVarNames "Answer an Array of the names of the receiver's instance variables. The Array ordering is the order in which the variables are stored and accessed by the interpreter." | vars | superclass == nil ifTrue: [vars := self instVarNames copy] "Guarantee a copy is answered." ifFalse: [vars := superclass allInstVarNames , self instVarNames]. ^vars! ! !Behavior methodsFor: 'accessing instances and variables' stamp: 'MarcusDenker 10/17/2009 16:49'! allInstances "Answer a collection of all current instances of the receiver." | all inst next | all := OrderedCollection new. inst := self someInstance. [inst == nil] whileFalse: [ next := inst nextInstance. inst == all ifFalse: [all add: inst]. inst := next]. ^ all asArray! ! !Behavior methodsFor: 'accessing instances and variables' stamp: 'tpr 5/30/2003 13:04'! allSharedPools "Answer a Set of the names of the pools (Dictionaries or SharedPool subclasses) that the receiver and the receiver's ancestors share." ^superclass allSharedPools! ! !Behavior methodsFor: 'accessing instances and variables' stamp: 'di 6/20/97 10:51'! allSubInstances "Answer a list of all current instances of the receiver and all of its subclasses." | aCollection | aCollection := OrderedCollection new. self allSubInstancesDo: [:x | x == aCollection ifFalse: [aCollection add: x]]. ^ aCollection! ! !Behavior methodsFor: 'accessing instances and variables' stamp: 'ajh 10/17/2002 11:03'! allowsSubInstVars "Classes that allow instances to change classes among its subclasses will want to override this and return false, so inst vars are not accidentally added to its subclasses." ^ true! ! !Behavior methodsFor: 'accessing instances and variables'! classVarNames "Answer a Set of the receiver's class variable names." ^Set new! ! !Behavior methodsFor: 'accessing instances and variables' stamp: 'sw 5/21/2001 22:51'! inspectAllInstances "Inpsect all instances of the receiver. 1/26/96 sw" | all allSize prefix | all := self allInstances. (allSize := all size) == 0 ifTrue: [^ self inform: 'There are no instances of ', self name]. prefix := allSize == 1 ifTrue: ['The lone instance'] ifFalse: ['The ', allSize printString, ' instances']. all asArray inspectWithLabel: (prefix, ' of ', self name)! ! !Behavior methodsFor: 'accessing instances and variables' stamp: 'sw 5/21/2001 22:51'! inspectSubInstances "Inspect all instances of the receiver and all its subclasses. CAUTION - don't do this for something as generic as Object!! 1/26/96 sw" | all allSize prefix | all := self allSubInstances. (allSize := all size) == 0 ifTrue: [^ self inform: 'There are no instances of ', self name, ' or any of its subclasses']. prefix := allSize == 1 ifTrue: ['The lone instance'] ifFalse: ['The ', allSize printString, ' instances']. all asArray inspectWithLabel: (prefix, ' of ', self name, ' & its subclasses')! ! !Behavior methodsFor: 'accessing instances and variables'! 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: 'accessing instances and variables'! instanceCount "Answer the number of instances of the receiver that are currently in use." | count | count := 0. self allInstancesDo: [:x | count := count + 1]. ^count! ! !Behavior methodsFor: 'accessing instances and variables'! sharedPools "Answer a Set of the names of the pools (Dictionaries) that the receiver shares. 9/12/96 tk sharedPools have an order now" ^ OrderedCollection new! ! !Behavior methodsFor: 'accessing instances and variables'! someInstance "Primitive. Answer the first instance in the enumeration of all instances of the receiver. Fails if there are none. Essential. See Object documentation whatIsAPrimitive." ^nil! ! !Behavior methodsFor: 'accessing instances and variables'! subclassInstVarNames "Answer a Set of the names of the receiver's subclasses' instance variables." | vars | vars := Set new. self allSubclasses do: [:aSubclass | vars addAll: aSubclass instVarNames]. ^vars! ! !Behavior methodsFor: 'accessing method dictionary'! >> selector "Answer the compiled method associated with the argument, selector (a Symbol), a message selector in the receiver's method dictionary. If the selector is not in the dictionary, create an error notification." ^self compiledMethodAt: selector ! ! !Behavior methodsFor: 'accessing method dictionary'! addSelector: selector withMethod: compiledMethod ^ self addSelector: selector withMethod: compiledMethod notifying: nil! ! !Behavior methodsFor: 'accessing method dictionary'! addSelector: selector withMethod: compiledMethod notifying: requestor ^ self addSelectorSilently: selector withMethod: compiledMethod! ! !Behavior methodsFor: 'accessing method dictionary'! addSelectorSilently: selector withMethod: compiledMethod self methodDictAddSelectorSilently: selector withMethod: compiledMethod. self registerLocalSelector: selector! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'kph 8/27/2008 22:31'! allSelectors "Answer all selectors understood by instances of the receiver" ^ self allSelectorsBelow: nil! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'sd 1/28/2009 14:29'! allSelectorsAbove ^ self allSelectorsAboveUntil: ProtoObject ! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'sd 1/28/2009 14:28'! allSelectorsAboveUntil: aRootClass | coll | coll := IdentitySet new. (self allSuperclassesIncluding: aRootClass) do: [:aClass | aClass selectorsDo: [ :sel | coll add: sel ]]. ^ coll ! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'dc 9/28/2008 15:54'! allSelectorsBelow: topClass | coll | coll := IdentitySet new. self withAllSuperclassesDo: [:aClass | aClass = topClass ifTrue: [^ coll ] ifFalse: [aClass selectorsDo: [ :sel | coll add: sel ]]]. ^ coll ! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'al 6/12/2006 10:48'! basicLocalSelectors "Direct accessor for the instance variable localSelectors. Because of hardcoded ivar indexes of Behavior and Class in the VM, Class and Metaclass declare the needed ivar and override this method as an accessor. By returning nil instead of declaring this method as a subclass responsibility, Behavior can be instantiated for creating anonymous classes." ^nil! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'al 3/25/2006 13:17'! basicLocalSelectors: aSetOrNil self subclassResponsibility ! ! !Behavior methodsFor: 'accessing method dictionary'! changeRecordsAt: selector "Return a list of ChangeRecords for all versions of the method at selector. Source code can be retrieved by sending string to any one. Return nil if the method is absent." "(Pen changeRecordsAt: #go:) collect: [:cRec | cRec string]" ^ChangeSet scanVersionsOf: (self compiledMethodAt: selector ifAbsent: [^ nil]) class: self meta: self isMeta category: (self whichCategoryIncludesSelector: selector) selector: selector.! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'mga 3/20/2005 11:11'! commentsAt: selector "Answer a string representing the first comment in the method associated with selector. Return an empty string if the relevant source file is not available, or if the method's source code does not contain a comment. Not smart enough to bypass quotes in string constants, but does map doubled quote into a single quote." ^self commentsIn: (self sourceCodeAt: selector) asString. "Behavior commentsAt: #commentsAt:"! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'mga 3/21/2005 10:53'! commentsIn: sourceString | commentStart nextQuotePos someComments aPos | ('*"*' match: sourceString) ifFalse: [^#()]. someComments:= OrderedCollection new. sourceString size == 0 ifTrue: [^ someComments]. aPos:=1. nextQuotePos:= 0. [commentStart := sourceString findString: '"' startingAt: aPos. nextQuotePos:= self nextQuotePosIn: sourceString startingFrom: commentStart. (commentStart ~= 0 and: [nextQuotePos >commentStart])] whileTrue: [ commentStart ~= nextQuotePos ifTrue: [ someComments add: ((sourceString copyFrom: commentStart + 1 to: nextQuotePos - 1) copyReplaceAll: '""' with: '"').]. aPos := nextQuotePos+1]. ^someComments! ! !Behavior methodsFor: 'accessing method dictionary'! compiledMethodAt: selector "Answer the compiled method associated with the argument, selector (a Symbol), a message selector in the receiver's method dictionary. If the selector is not in the dictionary, create an error notification." ^ self methodDict at: selector! ! !Behavior methodsFor: 'accessing method dictionary'! compiledMethodAt: selector ifAbsent: aBlock "Answer the compiled method associated with the argument, selector (a Symbol), a message selector in the receiver's method dictionary. If the selector is not in the dictionary, return the value of aBlock" ^ self methodDict at: selector ifAbsent: [aBlock value]! ! !Behavior methodsFor: 'accessing method dictionary'! compress "Compact the method dictionary of the receiver." self methodDict rehash! ! !Behavior methodsFor: 'accessing method dictionary'! compressedSourceCodeAt: selector "(Paragraph compressedSourceCodeAt: #displayLines:affectedRectangle:) size 721 1921 Paragraph selectors inject: 0 into: [:tot :sel | tot + (Paragraph compressedSourceCodeAt: sel) size] 13606 31450" | rawText parse | rawText := (self sourceCodeAt: selector) asString. parse := self compilerClass new parse: rawText in: self notifying: nil. ^ rawText compressWithTable: ((selector keywords , parse tempNames , self instVarNames , #(self super ifTrue: ifFalse:) , ((0 to: 7) collect: [:i | String streamContents: [:s | s cr. i timesRepeat: [s tab]]]) , (self compiledMethodAt: selector) literalStrings) asSortedCollection: [:a :b | a size > b size])! ! !Behavior methodsFor: 'accessing method dictionary'! deregisterLocalSelector: aSymbol self basicLocalSelectors notNil ifTrue: [ self basicLocalSelectors remove: aSymbol ifAbsent: []]! ! !Behavior methodsFor: 'accessing method dictionary'! firstCommentAt: selector "Answer a string representing the first comment in the method associated with selector. Return an empty string if the relevant source file is not available, or if the method's source code does not contain a comment. Not smart enough to bypass quotes in string constants, but does map doubled quote into a single quote." |someComments| someComments := self commentsAt: selector. ^someComments isEmpty ifTrue: [''] ifFalse: [someComments first] "Behavior firstCommentAt: #firstCommentAt:"! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'damiencassou 5/30/2008 10:56'! firstPrecodeCommentFor: selector "If there is a comment in the source code at the given selector that preceeds the body of the method, return it here, else return nil" "Behavior firstPrecodeCommentFor: #firstPrecodeCommentFor:" | parser source tree | (#(#Comment #Definition #Hierarchy ) includes: selector) ifTrue: [ "Not really a selector" ^ nil ]. source := self sourceCodeAt: selector asSymbol ifAbsent: [ ^ nil ]. parser := self parserClass new. tree := parser parse: source readStream class: self noPattern: false context: nil notifying: nil ifFail: [ ^ nil ]. ^ (tree comment ifNil: [ ^ nil ]) first! ! !Behavior methodsFor: 'accessing method dictionary'! "popeye" formalHeaderPartsFor: "olive oil" aSelector "RELAX!! The warning you may have just seen about possibly having a bad source file does not apply here, because this method *intends* to have its source code start with a comment. This method returns a collection giving the parts in the formal declaration for aSelector. This parse is in support of schemes in which adjutant properties of a method can be declared via special comments secreted in the formal header The result will have 3 elements for a simple, argumentless selector. 5 elements for a single-argument selector 9 elements for a two-argument selector 13 elements for a three-argument, selector etc... The syntactic elements are: 1 comment preceding initial selector fragment 2 first selector fragment 3 comment following first selector fragment (nil if selector has no arguments) ---------------------- (ends here for, e.g., #copy) 4 first formal argument 5 comment following first formal argument (nil if selector has only one argument) ---------------------- (ends here for, e.g., #copyFrom:) 6 second keyword 7 comment following second keyword 8 second formal argument 9 comment following second formal argument (nil if selector has only two arguments) ---------------------- (ends here for, e.g., #copyFrom:to:) Any nil element signifies an absent comment. NOTE: The comment following the final formal argument is *not* successfully retrieved by this method in its current form, though it can be obtained, if needed, by other means (e.g. calling #firstPrecodeCommentFor:). Thus, the *final* element in the structure returned by this method is always going to be nil." ^ Scanner new scanMessageParts: (self methodHeaderFor: aSelector) " Behavior class formalHeaderPartsFor: #formalHeaderPartsFor: " ! ! !Behavior methodsFor: 'accessing method dictionary'! formalParametersAt: aSelector "Return the names of the arguments used in this method." | source parser message list params | source := self sourceCodeAt: aSelector ifAbsent: [^ #()]. "for now" (parser := self parserClass new) parseSelector: source. message := source copyFrom: 1 to: (parser endOfLastToken min: source size). list := message string findTokens: Character separators. params := OrderedCollection new. list withIndexDo: [:token :ind | ind even ifTrue: [params addLast: token]]. ^ params! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'di 1/2/1999 15:45'! lookupSelector: selector "Look up the given selector in my methodDictionary. Return the corresponding method if found. Otherwise chase the superclass chain and try again. Return nil if no method is found." | lookupClass | lookupClass := self. [lookupClass == nil] whileFalse: [(lookupClass includesSelector: selector) ifTrue: [^ lookupClass compiledMethodAt: selector]. lookupClass := lookupClass superclass]. ^ nil! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'dvf 9/27/2005 17:08'! methodDict: aDictionary methodDict := aDictionary! ! !Behavior methodsFor: 'accessing method dictionary'! methodDictionary "Convenience" ^self methodDict! ! !Behavior methodsFor: 'accessing method dictionary'! methodDictionary: aDictionary self methodDict: aDictionary! ! !Behavior methodsFor: 'accessing method dictionary'! methodHeaderFor: selector "Answer the string corresponding to the method header for the given selector" | sourceString parser | sourceString := self ultimateSourceCodeAt: selector ifAbsent: [self standardMethodHeaderFor: selector]. (parser := self parserClass new) parseSelector: sourceString. ^ sourceString asString copyFrom: 1 to: (parser endOfLastToken min: sourceString size) "Behavior methodHeaderFor: #methodHeaderFor: " ! ! !Behavior methodsFor: 'accessing method dictionary'! methodsDo: aBlock "Evaluate aBlock for all the compiled methods in my method dictionary." ^ self methodDict valuesDo: aBlock! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'mga 3/21/2005 12:04'! nextQuotePosIn: sourceString startingFrom: commentStart | pos nextQuotePos | pos := commentStart + 1. [((nextQuotePos := sourceString findString: '"' startingAt: pos) == (sourceString findString: '""' startingAt: pos)) and: [nextQuotePos ~= 0]] whileTrue: [pos := nextQuotePos + 2]. ^nextQuotePos! ! !Behavior methodsFor: 'accessing method dictionary'! precodeCommentOrInheritedCommentFor: selector "Answer a string representing the first comment in the method associated with selector, considering however only comments that occur before the beginning of the actual code. If the version recorded in the receiver is uncommented, look up the inheritance chain. Return nil if none found." | aSuper aComment | ^ (aComment := self firstPrecodeCommentFor: selector) isEmptyOrNil ifTrue: [(self == Behavior or: [superclass == nil or: [(aSuper := superclass whichClassIncludesSelector: selector) == nil]]) ifFalse: [aSuper precodeCommentOrInheritedCommentFor: selector] "ActorState precodeCommentOrInheritedCommentFor: #printOn:"] ifFalse: [aComment]! ! !Behavior methodsFor: 'accessing method dictionary'! registerLocalSelector: aSymbol self basicLocalSelectors notNil ifTrue: [ self basicLocalSelectors add: aSymbol]! ! !Behavior methodsFor: 'accessing method dictionary'! removeSelector: aSelector "Assuming that the argument, selector (a Symbol), is a message selector in my method dictionary, remove it and its method. If the method to remove will be replaced by a method from my trait composition, the current method does not have to be removed because we mark it as non-local. If it is not identical to the actual method from the trait it will be replaced automatically by #noteChangedSelectors:. This is useful to avoid bootstrapping problems when moving methods to a trait (e.g., from TPureBehavior to TMethodDictionaryBehavior). Manual moving (implementing the method in the trait and then remove it from the class) does not work if the methods themselves are used for this process (such as compiledMethodAt:, includesLocalSelector: or addTraitSelector:withMethod:)" | changeFromLocalToTraitMethod | changeFromLocalToTraitMethod := (self includesLocalSelector: aSelector) and: [self hasTraitComposition] and: [self traitComposition includesMethod: aSelector]. changeFromLocalToTraitMethod ifFalse: [self basicRemoveSelector: aSelector] ifTrue: [self ensureLocalSelectors]. self deregisterLocalSelector: aSelector. self noteChangedSelectors: (Array with: aSelector) ! ! !Behavior methodsFor: 'accessing method dictionary'! removeSelectorSilently: selector "Remove selector without sending system change notifications" ^ SystemChangeNotifier uniqueInstance doSilently: [self removeSelector: selector].! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'di 3/27/1999 13:02'! rootStubInImageSegment: imageSegment ^ ImageSegmentRootStub new xxSuperclass: superclass format: format segment: imageSegment! ! !Behavior methodsFor: 'accessing method dictionary'! selectors "Answer a Set of all the message selectors specified in the receiver's method dictionary." ^ self methodDict keys! ! !Behavior methodsFor: 'accessing method dictionary'! selectorsAndMethodsDo: aBlock "Evaluate selectorBlock for all the message selectors in my method dictionary." ^ self methodDict keysAndValuesDo: aBlock! ! !Behavior methodsFor: 'accessing method dictionary'! selectorsDo: selectorBlock "Evaluate selectorBlock for all the message selectors in my method dictionary." ^ self methodDict keysDo: selectorBlock! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'md 1/2/2006 18:56'! selectorsWithArgs: numberOfArgs "Return all selectors defined in this class that take this number of arguments" ^ self selectors select: [:selector | selector numArgs = numberOfArgs]! ! !Behavior methodsFor: 'accessing method dictionary'! sourceCodeAt: selector ^ (self methodDict at: selector) getSourceFor: selector in: self! ! !Behavior methodsFor: 'accessing method dictionary'! sourceCodeAt: selector ifAbsent: aBlock ^ (self methodDict at: selector ifAbsent: [^ aBlock value]) getSourceFor: selector in: self! ! !Behavior methodsFor: 'accessing method dictionary'! sourceMethodAt: selector "Answer the paragraph corresponding to the source code for the argument." ^(self sourceCodeAt: selector) asText makeSelectorBoldIn: self! ! !Behavior methodsFor: 'accessing method dictionary'! sourceMethodAt: selector ifAbsent: aBlock "Answer the paragraph corresponding to the source code for the argument." ^ (self sourceCodeAt: selector ifAbsent: [^ aBlock value]) asText makeSelectorBoldIn: self! ! !Behavior methodsFor: 'accessing method dictionary'! standardMethodHeaderFor: aSelector | args | args := (1 to: aSelector numArgs) collect:[:i| 'arg', i printString]. args size = 0 ifTrue:[^aSelector asString]. args size = 1 ifTrue:[^aSelector,' arg1']. ^String streamContents:[:s| (aSelector findTokens:':') with: args do:[:tok :arg| s nextPutAll: tok; nextPutAll:': '; nextPutAll: arg; nextPutAll:' '. ]. ]. ! ! !Behavior methodsFor: 'accessing method dictionary'! supermostPrecodeCommentFor: selector "Answer a string representing the precode comment in the most distant superclass's implementation of the selector. Return nil if none found." | aSuper superComment | (self == Behavior or: [superclass == nil or: [(aSuper := superclass whichClassIncludesSelector: selector) == nil]]) ifFalse: ["There is a super implementor" superComment := aSuper supermostPrecodeCommentFor: selector]. ^ superComment ifNil: [self firstPrecodeCommentFor: selector "ActorState supermostPrecodeCommentFor: #printOn:"]! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'al 12/6/2004 11:36'! ultimateSourceCodeAt: selector ifAbsent: aBlock "Return the source code at selector, deferring to superclass if necessary" ^ self sourceCodeAt: selector ifAbsent: [superclass ifNil: [aBlock value] ifNotNil: [superclass ultimateSourceCodeAt: selector ifAbsent: aBlock]]! ! !Behavior methodsFor: 'accessing method dictionary' stamp: 'sd 11/19/2004 15:18'! zapAllMethods "Remove all methods in this class which is assumed to be obsolete" methodDict := self emptyMethodDictionary. self class isMeta ifTrue: [self class zapAllMethods]! ! !Behavior methodsFor: 'adding/removing methods'! basicAddSelector: selector withMethod: compiledMethod "Add the message selector with the corresponding compiled method to the receiver's method dictionary. Do this without sending system change notifications" | oldMethodOrNil | oldMethodOrNil := self lookupSelector: selector. self methodDict at: selector put: compiledMethod. compiledMethod methodClass: self. compiledMethod selector: selector. "Now flush Squeak's method cache, either by selector or by method" oldMethodOrNil ifNotNil: [oldMethodOrNil flushCache]. selector flushCache.! ! !Behavior methodsFor: 'adding/removing methods'! localSelectors "Return a set of selectors defined locally. The instance variable is lazily initialized. If it is nil then there are no non-local selectors" ^ self basicLocalSelectors isNil ifTrue: [self selectors] ifFalse: [self basicLocalSelectors].! ! !Behavior methodsFor: 'adding/removing methods'! methodDictAddSelectorSilently: selector withMethod: compiledMethod self basicAddSelector: selector withMethod: compiledMethod! ! !Behavior methodsFor: 'compiling'! binding ^ nil -> self! ! !Behavior methodsFor: 'compiling'! compile: code "Compile the argument, code, as source code in the context of the receiver. Create an error notification if the code can not be compiled. The argument is either a string or an object that converts to a string or a PositionableStream on an object that converts to a string." ^self compile: code notifying: nil! ! !Behavior methodsFor: 'compiling'! compile: code classified: category notifying: requestor trailer: bytes ifFail: failBlock "Compile code without logging the source in the changes file" | methodNode | methodNode := self compilerClass new compile: code in: self classified: category notifying: requestor ifFail: failBlock. ^ CompiledMethodWithNode generateMethodFromNode: methodNode trailer: bytes.! ! !Behavior methodsFor: 'compiling'! compile: code notifying: requestor "Compile the argument, code, as source code in the context of the receiver and insEtall the result in the receiver's method dictionary. The second argument, requestor, is to be notified if an error occurs. The argument code is either a string or an object that converts to a string or a PositionableStream. This method also saves the source code." | methodAndNode | methodAndNode := self compile: code "a Text" classified: nil notifying: requestor trailer: self defaultMethodTrailer ifFail: [^nil]. methodAndNode method putSource: code fromParseNode: methodAndNode node inFile: 2 withPreamble: [:f | f cr; nextPut: $!!; nextChunkPut: 'Behavior method'; cr]. self addSelector: methodAndNode selector withMethod: methodAndNode method notifying: requestor. ^ methodAndNode selector! ! !Behavior methodsFor: 'compiling'! compileAll ^ self compileAllFrom: self! ! !Behavior methodsFor: 'compiling'! compileAllFrom: oldClass "Compile all the methods in the receiver's method dictionary. This validates sourceCode and variable references and forces all methods to use the current bytecode set" "ar 7/10/1999: Use oldClass selectors not self selectors" oldClass selectorsDo: [:sel | self recompile: sel from: oldClass]. self environment currentProjectDo: [:proj | proj compileAllIsolated: self from: oldClass].! ! !Behavior methodsFor: 'compiling'! decompile: selector "Find the compiled code associated with the argument, selector, as a message selector in the receiver's method dictionary and decompile it. Answer the resulting source code as a string. Create an error notification if the selector is not in the receiver's method dictionary." ^self decompilerClass new decompile: selector in: self! ! !Behavior methodsFor: 'compiling'! defaultMethodTrailer ^ #(0 0 0 0)! ! !Behavior methodsFor: 'compiling' stamp: 'eem 5/13/2008 09:50'! instVarNamesAndOffsetsDo: aBinaryBlock "This is part of the interface between the compiler and a class's instance or field names. The class should enumerate aBinaryBlock with the instance variable name strings and their integer offsets. The order is important. Names evaluated later will override the same names occurring earlier." "Nothing to do here; ClassDescription introduces named instance variables" ^self! ! !Behavior methodsFor: 'compiling'! recompile: selector "Compile the method associated with selector in the receiver's method dictionary." ^self recompile: selector from: self! ! !Behavior methodsFor: 'compiling'! recompile: selector from: oldClass "Compile the method associated with selector in the receiver's method dictionary." "ar 7/10/1999: Use oldClass compiledMethodAt: not self compiledMethodAt:" | method trailer methodNode | method := oldClass compiledMethodAt: selector. trailer := method trailer. methodNode := self compilerClass new compile: (oldClass sourceCodeAt: selector) in: self notifying: nil ifFail: [^ self]. "Assume OK after proceed from SyntaxError" selector == methodNode selector ifFalse: [self error: 'selector changed!!']. self basicAddSelector: selector withMethod: (methodNode generate: trailer). ! ! !Behavior methodsFor: 'compiling'! recompileChanges "Compile all the methods that are in the changes file. This validates sourceCode and variable references and forces methods to use the current bytecode set" self selectorsDo: [:sel | (self compiledMethodAt: sel) fileIndex > 1 ifTrue: [self recompile: sel from: self]]! ! !Behavior methodsFor: 'compiling'! recompileNonResidentMethod: method atSelector: selector from: oldClass "Recompile the method supplied in the context of this class." | trailer methodNode | trailer := method trailer. methodNode := self compilerClass new compile: (method getSourceFor: selector in: oldClass) in: self notifying: nil ifFail: ["We're in deep doo-doo if this fails (syntax error). Presumably the user will correct something and proceed, thus installing the result in this methodDict. We must retrieve that new method, and restore the original (or remove) and then return the method we retrieved." ^ self error: 'see comment']. selector == methodNode selector ifFalse: [self error: 'selector changed!!']. ^ methodNode generate: trailer ! ! !Behavior methodsFor: 'compiling' stamp: 'eem 6/19/2008 09:08'! variablesAndOffsetsDo: aBinaryBlock "This is the interface between the compiler and a class's instance or field names. The class should enumerate aBinaryBlock with the field definitions (with nil offsets) followed by the instance variable name strings and their integer offsets (1-relative). The order is important; names evaluated later will override the same names occurring earlier." "Only need to do instance variables here. CProtoObject introduces field definitions." self instVarNamesAndOffsetsDo: aBinaryBlock! ! !Behavior methodsFor: 'copying'! copy "Answer a copy of the receiver without a list of subclasses." | myCopy | myCopy := self shallowCopy. ^myCopy methodDictionary: self copyOfMethodDictionary! ! !Behavior methodsFor: 'copying'! copyOfMethodDictionary "Return a copy of the receiver's method dictionary" ^ self methodDict copy! ! !Behavior methodsFor: 'copying'! deepCopy "Classes should only be shallowCopied or made anew." ^ self shallowCopy! ! !Behavior methodsFor: 'enumerating' stamp: 'apb 7/13/2004 00:40'! allInstancesDo: aBlock "Evaluate the argument, aBlock, for each of the current instances of the receiver. Because aBlock might change the class of inst (for example, using become:), it is essential to compute next before aBlock value: inst." | inst next | self == UndefinedObject ifTrue: [^ aBlock value: nil]. inst := self someInstance. [inst == nil] whileFalse: [ next := inst nextInstance. aBlock value: inst. inst := next]! ! !Behavior methodsFor: 'enumerating' stamp: 'tk 11/12/1999 11:36'! allInstancesEverywhereDo: aBlock "Evaluate the argument, aBlock, for each of the current instances of the receiver. Including those in ImageSegments that are out on the disk. Bring each in briefly." self == UndefinedObject ifTrue: [^ aBlock value: nil]. self allInstancesDo: aBlock. "Now iterate over instances in segments that are out on the disk." ImageSegment allSubInstancesDo: [:seg | seg allInstancesOf: self do: aBlock]. ! ! !Behavior methodsFor: 'enumerating' stamp: 'di 6/20/97 10:50'! allSubInstancesDo: aBlock "Evaluate the argument, aBlock, for each of the current instances of the receiver and all its subclasses." self allInstancesDo: aBlock. self allSubclassesDo: [:sub | sub allInstancesDo: aBlock]! ! !Behavior methodsFor: 'enumerating'! allSubclassesDo: aBlock "Evaluate the argument, aBlock, for each of the receiver's subclasses." self subclassesDo: [:cl | aBlock value: cl. cl allSubclassesDo: aBlock]! ! !Behavior methodsFor: 'enumerating' stamp: 'tk 8/18/1999 17:38'! allSubclassesDoGently: aBlock "Evaluate the argument, aBlock, for each of the receiver's subclasses." self subclassesDoGently: [:cl | cl isInMemory ifTrue: [ aBlock value: cl. cl allSubclassesDoGently: aBlock]]! ! !Behavior methodsFor: 'enumerating'! allSuperclassesDo: aBlock "Evaluate the argument, aBlock, for each of the receiver's superclasses." superclass == nil ifFalse: [aBlock value: superclass. superclass allSuperclassesDo: aBlock]! ! !Behavior methodsFor: 'enumerating'! selectSubclasses: aBlock "Evaluate the argument, aBlock, with each of the receiver's (next level) subclasses as its argument. Collect into a Set only those subclasses for which aBlock evaluates to true. In addition, evaluate aBlock for the subclasses of each of these successful subclasses and collect into the set those for which aBlock evaluates true. Answer the resulting set." | aSet | aSet := Set new. self allSubclasses do: [:aSubclass | (aBlock value: aSubclass) ifTrue: [aSet add: aSubclass]]. ^aSet! ! !Behavior methodsFor: 'enumerating'! selectSuperclasses: aBlock "Evaluate the argument, aBlock, with the receiver's superclasses as the argument. Collect into an OrderedCollection only those superclasses for which aBlock evaluates to true. In addition, evaluate aBlock for the superclasses of each of these successful superclasses and collect into the OrderedCollection ones for which aBlock evaluates to true. Answer the resulting OrderedCollection." | aSet | aSet := Set new. self allSuperclasses do: [:aSuperclass | (aBlock value: aSuperclass) ifTrue: [aSet add: aSuperclass]]. ^aSet! ! !Behavior methodsFor: 'enumerating'! withAllSubclassesDo: aBlock "Evaluate the argument, aBlock, for the receiver and each of its subclasses." aBlock value: self. self allSubclassesDo: aBlock! ! !Behavior methodsFor: 'enumerating' stamp: 'nk 2/14/2001 12:09'! withAllSuperAndSubclassesDoGently: aBlock self allSuperclassesDo: aBlock. aBlock value: self. self allSubclassesDoGently: aBlock! ! !Behavior methodsFor: 'enumerating' stamp: 'ar 7/11/1999 04:21'! withAllSuperclassesDo: aBlock "Evaluate the argument, aBlock, for each of the receiver's superclasses." aBlock value: self. superclass == nil ifFalse: [superclass withAllSuperclassesDo: aBlock]! ! !Behavior methodsFor: 'initialize-release'! emptyMethodDictionary ^ MethodDictionary new! ! !Behavior methodsFor: 'initialize-release' stamp: 'NS 1/28/2004 11:17'! forgetDoIts "get rid of old DoIt methods" self basicRemoveSelector: #DoIt; basicRemoveSelector: #DoItIn:! ! !Behavior methodsFor: 'initialize-release' stamp: 'alain.plantec 5/28/2009 09:43'! initialize "moved here from the class side's #new" super initialize. superclass := Object. "no longer sending any messages, some of them crash the VM" methodDict := self emptyMethodDictionary. format := Object format! ! !Behavior methodsFor: 'initialize-release' stamp: 'sd 3/28/2003 15:07'! nonObsoleteClass "Attempt to find and return the current version of this obsolete class" | obsName | obsName := self name. [obsName beginsWith: 'AnObsolete'] whileTrue: [obsName := obsName copyFrom: 'AnObsolete' size + 1 to: obsName size]. ^ self environment at: obsName asSymbol! ! !Behavior methodsFor: 'initialize-release'! obsolete "Invalidate and recycle local methods, e.g., zap the method dictionary if can be done safely." self canZapMethodDictionary ifTrue: [self methodDict: self emptyMethodDictionary]. self hasTraitComposition ifTrue: [ self traitComposition traits do: [:each | each removeUser: self]]! ! !Behavior methodsFor: 'initialize-release' stamp: 'al 12/12/2003 20:59'! superclass: aClass methodDictionary: mDict format: fmt "Basic initialization of the receiver. Must only be sent to a new instance; else we would need Object flushCache." superclass := aClass. format := fmt. methodDict := mDict. self traitComposition: nil! ! !Behavior methodsFor: 'instance creation' stamp: 'sd 3/28/2003 15:06'! basicNew "Primitive. Answer an instance of the receiver (which is a class) with no indexable variables. Fail if the class is indexable. Essential. See Object documentation whatIsAPrimitive." self isVariable ifTrue: [ ^ self basicNew: 0 ]. "space must be low" self environment signalLowSpace. ^ self basicNew "retry if user proceeds" ! ! !Behavior methodsFor: 'instance creation' stamp: 'sd 3/28/2003 15:06'! basicNew: sizeRequested "Primitive. Answer an instance of this class with the number of indexable variables specified by the argument, sizeRequested. Fail if this class is not indexable or if the argument is not a positive Integer, or if there is not enough memory available. Essential. See Object documentation whatIsAPrimitive." self isVariable ifFalse: [self error: self printString, ' cannot have variable sized instances']. (sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue: ["arg okay; space must be low." self environment signalLowSpace. ^ self basicNew: sizeRequested "retry if user proceeds"]. self primitiveFailed! ! !Behavior methodsFor: 'instance creation' stamp: 'sw 5/4/2000 20:47'! initializedInstance "Answer an instance of the receiver which in some sense is initialized. In the case of Morphs, this will yield an instance that can be attached to the Hand after having received the same kind of basic initialization that would be obtained from an instance chosen from the 'new morph' menu. Return nil if the receiver is reluctant for some reason to return such a thing" ^ self new! ! !Behavior methodsFor: 'instance creation' stamp: 'Noury Bouraqadi 8/23/2003 14:51'! new "Answer a new initialized instance of the receiver (which is a class) with no indexable variables. Fail if the class is indexable." ^ self basicNew initialize ! ! !Behavior methodsFor: 'instance creation' stamp: 'sd 5/20/2004 11:20'! new: sizeRequested "Answer an initialized instance of this class with the number of indexable variables specified by the argument, sizeRequested." ^ (self basicNew: sizeRequested) initialize ! ! !Behavior methodsFor: 'newcompiler'! parseScope ^ Smalltalk at: #ClassScope ifPresent: [:class | class new class: self]! ! !Behavior methodsFor: 'obsolete subclasses' stamp: 'apb 7/12/2004 23:13'! addObsoleteSubclass: aClass "Weakly remember that aClass was a subclass of the receiver and is now obsolete" | obs | obs := ObsoleteSubclasses at: self ifAbsent:[WeakArray new]. (obs includes: aClass) ifTrue:[^self]. obs := obs copyWithout: nil. obs := obs copyWith: aClass. ObsoleteSubclasses at: self put: obs. ! ! !Behavior methodsFor: 'obsolete subclasses' stamp: 'apb 7/12/2004 23:20'! obsoleteSubclasses "Return all the weakly remembered obsolete subclasses of the receiver" | obs | obs := ObsoleteSubclasses at: self ifAbsent: [^ #()]. ^ obs copyWithout: nil! ! !Behavior methodsFor: 'obsolete subclasses' stamp: 'apb 7/12/2004 23:21'! removeAllObsoleteSubclasses "Remove all the obsolete subclasses of the receiver" ObsoleteSubclasses removeKey: self ifAbsent: []. ! ! !Behavior methodsFor: 'obsolete subclasses' stamp: 'apb 7/12/2004 23:22'! removeObsoleteSubclass: aClass "Remove aClass from the weakly remembered obsolete subclasses" | obs | obs := ObsoleteSubclasses at: self ifAbsent:[^ self]. (obs includes: aClass) ifFalse:[^self]. obs := obs copyWithout: aClass. obs := obs copyWithout: nil. ObsoleteSubclasses at: self put: obs! ! !Behavior methodsFor: 'printing'! defaultNameStemForInstances "Answer a basis for external names for default instances of the receiver. For classees, the class-name itself is a good one." ^ self name! ! !Behavior methodsFor: 'printing'! literalScannedAs: scannedLiteral notifying: requestor "Postprocesses a literal scanned by Scanner scanToken (esp. xLitQuote). If scannedLiteral is not an association, answer it. Else, if it is of the form: nil->#NameOfMetaclass answer nil->theMetaclass, if any has that name, else report an error. Else, if it is of the form: #NameOfGlobalVariable->anythiEng answer the global, class, or pool association with that nameE, if any, else add it to Undeclared a answer the new Association." | key value | (scannedLiteral isVariableBinding) ifFalse: [^ scannedLiteral]. key := scannedLiteral key. value := scannedLiteral value. key isNil ifTrue: "###" [(self bindingOf: value) ifNotNil:[:assoc| (assoc value isKindOf: Behavior) ifTrue: [^ nil->assoc value class]]. requestor notify: 'No such metaclass'. ^false]. (key isSymbol) ifTrue: "##" [(self bindingOf: key) ifNotNil:[:assoc | ^assoc]. Undeclared at: key put: nil. ^Undeclared bindingOf: key]. requestor notify: '## must be followed by a non-local variable name'. ^false " Form literalScannedAs: 14 notifying: nil 14 Form literalScannedAs: #OneBitForm notiEfying: nil OneBitForm Form literalScannedAs: ##OneBitForm notifying: nil OneBitForm->a Form Form literalScannedAs: ##Form notifying: nil Form->Form Form literalScannedAs: ###Form notifying: nil nilE->Form class "! ! !Behavior methodsFor: 'printing'! longPrintOn: aStream "Append to the argument, aStream, the names and values of all of the receiver's instance variables. But, not useful for a class with a method dictionary." aStream nextPutAll: '<>'; cr.! ! !Behavior methodsFor: 'printing'! prettyPrinterClass ^ PrettyPrinting prettyPrinterClassFor: self! ! !Behavior methodsFor: 'printing' stamp: 'PeterHugossonMiller 9/3/2009 00:11'! 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 := (String new: 16) writeStream. 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! ! !Behavior methodsFor: 'printing'! printOn: aStream "Refer to the comment in Object|printOn:." aStream nextPutAll: 'a descendent of '. superclass printOn: aStream! ! !Behavior methodsFor: 'printing' stamp: 'MPW 1/1/1901 21:56'! printOnStream: aStream "Refer to the comment in Object|printOn:." aStream print: 'a descendent of '; write:superclass.! ! !Behavior methodsFor: 'printing' stamp: 'eem 6/2/2008 11:47'! printWithClosureAnalysisOn: aStream "Refer to the comment in Object|printOn:." aStream nextPutAll: 'a descendent of '. superclass printWithClosureAnalysisOn: aStream! ! !Behavior methodsFor: 'printing'! storeLiteral: aCodeLiteral on: aStream "Store aCodeLiteral on aStream, changing an Association to ##GlobalName or ###MetaclassSoleInstanceName format if appropriate" | key value | (aCodeLiteral isVariableBinding) ifFalse: [aCodeLiteral storeOn: aStream. ^self]. key := aCodeLiteral key. (key isNil and: [(value := aCodeLiteral value) isMemberOf: Metaclass]) ifTrue: [aStream nextPutAll: '###'; nextPutAll: value soleInstance name. ^self]. (key isSymbol and: [(self bindingOf: key) notNil]) ifTrue: [aStream nextPutAll: '##'; nextPutAll: key. ^self]. aCodeLiteral storeOn: aStream! ! !Behavior methodsFor: 'queries' stamp: 'dvf 9/17/2001 00:18'! whichClassDefinesClassVar: aString ^self whichSuperclassSatisfies: [:aClass | (aClass classVarNames collect: [:each | each asString]) includes: aString asString]! ! !Behavior methodsFor: 'queries' stamp: 'dvf 9/17/2001 00:18'! whichClassDefinesInstVar: aString ^self whichSuperclassSatisfies: [:aClass | aClass instVarNames includes: aString]! ! !Behavior methodsFor: 'queries' stamp: 'bh 3/6/2000 00:51'! whichSelectorsAssign: instVarName "Answer a Set of selectors whose methods store into the argument, instVarName, as a named instance variable." ^self whichSelectorsStoreInto: instVarName! ! !Behavior methodsFor: 'queries' stamp: 'bh 3/6/2000 00:52'! whichSelectorsRead: instVarName "Answer a Set of selectors whose methods access the argument, instVarName, as a named instance variable." ^self whichSelectorsAccess: instVarName! ! !Behavior methodsFor: 'queries' stamp: 'dvf 9/17/2001 00:18'! whichSuperclassSatisfies: aBlock (aBlock value: self) ifTrue: [^self]. ^superclass isNil ifTrue: [nil] ifFalse: [superclass whichSuperclassSatisfies: aBlock]! ! !Behavior methodsFor: 'send caches'! clearSendCaches LocalSends current clearOut: self! ! !Behavior methodsFor: 'send caches'! hasRequiredSelectors ^ self requiredSelectors notEmpty! ! !Behavior methodsFor: 'send caches'! requirements ^ self requiredSelectorsCache ifNil: [#()] ifNotNilDo: [:rsc | rsc requirements]! ! !Behavior methodsFor: 'send caches'! sendCaches: aSendCaches ^ self explicitRequirement! ! !Behavior methodsFor: 'send caches'! setRequiredStatusOf: selector to: aBoolean aBoolean ifTrue: [self requiredSelectorsCache addRequirement: selector] ifFalse: [self requiredSelectorsCache removeRequirement: selector].! ! !Behavior methodsFor: 'send caches'! superRequirements ^ self requiredSelectorsCache superRequirements! ! !Behavior methodsFor: 'system startup' stamp: 'ar 11/16/1999 20:15'! shutDown "This message is sent on system shutdown to registered classes" ! ! !Behavior methodsFor: 'system startup' stamp: 'ar 11/16/1999 20:15'! shutDown: quitting "This message is sent on system shutdown to registered classes" ^self shutDown.! ! !Behavior methodsFor: 'system startup' stamp: 'ar 11/16/1999 20:15'! startUp "This message is sent to registered classes when the system is coming up." ! ! !Behavior methodsFor: 'system startup' stamp: 'ar 11/16/1999 20:15'! startUp: resuming "This message is sent to registered classes when the system is coming up." ^self startUp! ! !Behavior methodsFor: 'system startup' stamp: 'tk 10/26/2001 16:06'! startUpFrom: anImageSegment "Override this when a per-instance startUp message needs to be sent. For example, to correct the order of 16-bit non-pointer data when it came from a different endian machine." ^ nil! ! !Behavior methodsFor: 'testing'! canZapMethodDictionary "Return true if it is safe to zap the method dictionary on #obsolete" ^true! ! !Behavior methodsFor: 'testing'! instSize "Answer the number of named instance variables (as opposed to indexed variables) of the receiver." self flag: #instSizeChange. "Smalltalk browseAllCallsOn: #instSizeChange" " NOTE: This code supports the backward-compatible extension to 8 bits of instSize. When we revise the image format, it should become... ^ ((format bitShift: -1) bitAnd: 16rFF) - 1 Note also that every other method in this category will require 2 bits more of right shift after the change. " ^ ((format bitShift: -10) bitAnd: 16rC0) + ((format bitShift: -1) bitAnd: 16r3F) - 1! ! !Behavior methodsFor: 'testing'! instSpec ^ (format bitShift: -7) bitAnd: 16rF! ! !Behavior methodsFor: 'testing' stamp: 'ar 7/9/1999 18:18'! isBehavior "Return true if the receiver is a behavior" ^true! ! !Behavior methodsFor: 'testing'! isBits "Answer whether the receiver contains just bits (not pointers)." ^ self instSpec >= 6! ! !Behavior methodsFor: 'testing'! isBytes "Answer whether the receiver has 8-bit instance variables." ^ self instSpec >= 8! ! !Behavior methodsFor: 'testing'! isFixed "Answer whether the receiver does not have a variable (indexable) part." ^self isVariable not! ! !Behavior methodsFor: 'testing' stamp: 'dvf 9/27/2005 14:57'! isMeta ^ false! ! !Behavior methodsFor: 'testing' stamp: 'ar 7/14/1999 02:38'! isObsolete "Return true if the receiver is obsolete." ^self instanceCount = 0! ! !Behavior methodsFor: 'testing'! isPointers "Answer whether the receiver contains just pointers (not bits)." ^self isBits not! ! !Behavior methodsFor: 'testing'! isVariable "Answer whether the receiver has indexable variables." ^ self instSpec >= 2! ! !Behavior methodsFor: 'testing' stamp: 'ar 3/21/98 02:36'! isWeak "Answer whether the receiver has contains weak references." ^ self instSpec = 4! ! !Behavior methodsFor: 'testing'! isWords "Answer whether the receiver has 16-bit instance variables." ^self isBytes not! ! !Behavior methodsFor: 'testing' stamp: 'sd 3/28/2003 15:07'! shouldNotBeRedefined "Return true if the receiver should not be redefined. The assumption is that compact classes, classes in Smalltalk specialObjects and Behaviors should not be redefined" ^(self environment compactClassesArray includes: self) or:[(self environment specialObjectsArray includes: self) or:[self isKindOf: self]]! ! !Behavior methodsFor: 'testing class hierarchy' stamp: 'ar 3/12/98 12:36'! includesBehavior: aClass ^self == aClass or:[self inheritsFrom: aClass]! ! !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: 'testing class hierarchy'! kindOfSubclass "Answer a String that is the keyword that describes the receiver's kind of subclass, either a regular subclass, a variableSubclass, a variableByteSubclass, a variableWordSubclass, or a weakSubclass." self isWeak ifTrue: [^ ' weakSubclass: ']. ^ self isVariable ifTrue: [self isBits ifTrue: [self isBytes ifTrue: [ ' variableByteSubclass: '] ifFalse: [ ' variableWordSubclass: ']] ifFalse: [ ' variableSubclass: ']] ifFalse: [ ' subclass: ']! ! !Behavior methodsFor: 'testing method dictionary' stamp: 'al 2/29/2004 14:18'! bindingOf: varName "Answer the binding of some variable resolved in the scope of the receiver" ^superclass bindingOf: varName! ! !Behavior methodsFor: 'testing method dictionary' stamp: 'sd 5/7/2006 09:58'! canPerform: selector "Answer whether the receiver can safely perform to the message whose selector is the argument: it is not an abstract or cancelled method" ^ self classAndMethodFor: selector do: [:c :m | m isProvided] ifAbsent: [false].! ! !Behavior methodsFor: 'testing method dictionary'! canUnderstand: selector "Answer whether the receiver can respond to the message whose selector is the argument. The selector can be in the method dictionary of the receiver's class or any of its superclasses." (self includesSelector: selector) ifTrue: [^true]. superclass == nil ifTrue: [^false]. ^superclass canUnderstand: selector! ! !Behavior methodsFor: 'testing method dictionary' stamp: 'ar 5/18/2003 18:13'! classBindingOf: varName "Answer the binding of some variable resolved in the scope of the receiver's class" ^self bindingOf: varName! ! !Behavior methodsFor: 'testing method dictionary'! hasMethods "Answer whether the receiver has any methods in its method dictionary." ^ self methodDict notEmpty! ! !Behavior methodsFor: 'testing method dictionary'! includesLocalSelector: aSymbol ^self basicLocalSelectors isNil ifTrue: [self includesSelector: aSymbol] ifFalse: [self localSelectors includes: aSymbol]! ! !Behavior methodsFor: 'testing method dictionary'! includesSelector: aSymbol "Answer whether the message whose selector is the argument is in the method dictionary of the receiver's class." ^ self methodDict includesKey: aSymbol! ! !Behavior methodsFor: 'testing method dictionary'! isAliasSelector: aSymbol "Return true if the selector aSymbol is an alias defined in my or in another composition somewhere deeper in the tree of traits compositions." ^(self includesLocalSelector: aSymbol) not and: [self hasTraitComposition] and: [self traitComposition isAliasSelector: aSymbol]! ! !Behavior methodsFor: 'testing method dictionary'! isDisabledSelector: selector ^ self classAndMethodFor: selector do: [:c :m | m isDisabled] ifAbsent: [false]! ! !Behavior methodsFor: 'testing method dictionary'! isLocalAliasSelector: aSymbol "Return true if the selector aSymbol is an alias defined in my trait composition." ^(self includesLocalSelector: aSymbol) not and: [self hasTraitComposition] and: [self traitComposition isLocalAliasSelector: aSymbol]! ! !Behavior methodsFor: 'testing method dictionary'! isProvidedSelector: selector ^ ProvidedSelectors current isSelector: selector providedIn: self ! ! !Behavior methodsFor: 'testing method dictionary' stamp: 'G.C 10/22/2008 09:59'! thoroughWhichSelectorsReferTo: literal special: specialFlag byte: specialByte "Answer a set of selectors whose methods access the argument as a literal. Dives into the compact literal notation, making it slow but thorough " | selectors | selectors := IdentitySet new. self selectorsAndMethodsDo: [ :sel :method | ((method refersToLiteral: literal) or: [ specialFlag and: [ method scanFor: specialByte ] ]) ifTrue: [ selectors add: sel ] ]. ^ selectors! ! !Behavior methodsFor: 'testing method dictionary'! whichClassIncludesSelector: aSymbol "Answer the class on the receiver's superclass chain where the argument, aSymbol (a message selector), will be found. Answer nil if none found." "Rectangle whichClassIncludesSelector: #inspect." (self includesSelector: aSymbol) ifTrue: [^ self]. superclass == nil ifTrue: [^ nil]. ^ superclass whichClassIncludesSelector: aSymbol! ! !Behavior methodsFor: 'testing method dictionary' stamp: 'eem 2/1/2007 14:14'! whichSelectorsAccess: instVarName "Answer a set of selectors whose methods access the argument, instVarName, as a named instance variable." | instVarIndex | instVarIndex := self instVarIndexFor: instVarName ifAbsent: [^IdentitySet new]. ^ self methodDict keys select: [:sel | ((self methodDict at: sel) readsField: instVarIndex) or: [(self methodDict at: sel) writesField: instVarIndex]] "Point whichSelectorsAccess: 'x'."! ! !Behavior methodsFor: 'testing method dictionary'! whichSelectorsReferTo: literal "Answer a Set of selectors whose methods access the argument as a literal." | special byte | special := self environment hasSpecialSelector: literal ifTrueSetByte: [:b | byte := b]. ^self whichSelectorsReferTo: literal special: special byte: byte "Rectangle whichSelectorsReferTo: #+."! ! !Behavior methodsFor: 'testing method dictionary'! whichSelectorsReferTo: literal special: specialFlag byte: specialByte "Answer a set of selectors whose methods access the argument as a literal." | who | who := IdentitySet new. self selectorsAndMethodsDo: [:sel :method | ((method hasLiteral: literal) or: [specialFlag and: [method scanFor: specialByte]]) ifTrue: [((literal isVariableBinding) not or: [method literals allButLast includes: literal]) ifTrue: [who add: sel]]]. ^ who! ! !Behavior methodsFor: 'testing method dictionary' stamp: 'eem 2/1/2007 14:15'! whichSelectorsStoreInto: instVarName "Answer a Set of selectors whose methods access the argument, instVarName, as a named instance variable." | instVarIndex | instVarIndex := self instVarIndexFor: instVarName ifAbsent: [^IdentitySet new]. ^ self methodDict keys select: [:sel | (self methodDict at: sel) writesField: instVarIndex] "Point whichSelectorsStoreInto: 'x'."! ! !Behavior methodsFor: 'traits'! addExclusionOf: aSymbol to: aTrait self setTraitComposition: ( self traitComposition copyWithExclusionOf: aSymbol to: aTrait)! ! !Behavior methodsFor: 'traits'! addToComposition: aTrait self setTraitComposition: (self traitComposition copyTraitExpression add: aTrait; yourself)! ! !Behavior methodsFor: 'traits'! addTraitSelector: aSymbol withMethod: aCompiledMethod "Add aMethod with selector aSymbol to my methodDict. aMethod must not be defined locally." | source methodAndNode | self assert: [(self includesLocalSelector: aSymbol) not]. self ensureLocalSelectors. source := aCompiledMethod getSourceReplacingSelectorWith: aSymbol. methodAndNode := self compile: source classified: nil notifying: nil trailer: #(0 0 0 0) ifFail: [^nil]. methodAndNode method putSource: source fromParseNode: methodAndNode node inFile: 2 withPreamble: [:f | f cr; nextPut: $!!; nextChunkPut: 'Trait method'; cr]. self basicAddSelector: aSymbol withMethod: methodAndNode method! ! !Behavior methodsFor: 'traits'! applyChangesOfNewTraitCompositionReplacing: oldComposition | changedSelectors | changedSelectors := self traitComposition changedSelectorsComparedTo: oldComposition. changedSelectors isEmpty ifFalse: [ self noteChangedSelectors: changedSelectors]. self traitComposition isEmpty ifTrue: [ self purgeLocalSelectors]. ^changedSelectors! ! !Behavior methodsFor: 'traits'! ensureLocalSelectors "Ensures that the instance variable localSelectors is effectively used to maintain the set of local selectors. This method must be called before any non-local selectors are added to the method dictionary!!" self basicLocalSelectors isNil ifTrue: [self basicLocalSelectors: self selectors]! ! !Behavior methodsFor: 'traits'! flattenDown: aTrait | selectors | self assert: [self hasTraitComposition and: [self traitComposition allTraits includes: aTrait]]. selectors := (self traitComposition transformationOfTrait: aTrait) selectors. self basicLocalSelectors: self basicLocalSelectors , selectors. self removeFromComposition: aTrait.! ! !Behavior methodsFor: 'traits'! flattenDownAllTraits self traitComposition allTraits do: [:each | self flattenDown: each]. self assert: [ self traitComposition isEmpty ]. self traitComposition: nil.! ! !Behavior methodsFor: 'traits' stamp: 'al 3/25/2006 12:39'! hasTraitComposition self subclassResponsibility ! ! !Behavior methodsFor: 'traits'! noteChangedSelectors: aCollection "Start update of my methodDict (after changes to traits in traitComposition or after a local method was removed from my methodDict). The argument is a collection of method selectors that may have been changed. Most of the time aCollection only holds one selector. But when there are aliases involved there may be several method changes that have to be propagated to users." | affectedSelectors | affectedSelectors := IdentitySet new. aCollection do: [:selector | affectedSelectors addAll: (self updateMethodDictionarySelector: selector)]. self notifyUsersOfChangedSelectors: affectedSelectors. ^ affectedSelectors! ! !Behavior methodsFor: 'traits'! notifyUsersOfChangedSelector: aSelector self notifyUsersOfChangedSelectors: (Array with: aSelector)! ! !Behavior methodsFor: 'traits'! notifyUsersOfChangedSelectors: aCollection! ! !Behavior methodsFor: 'traits'! purgeLocalSelectors self basicLocalSelectors: nil! ! !Behavior methodsFor: 'traits'! removeAlias: aSymbol of: aTrait self setTraitComposition: ( self traitComposition copyWithoutAlias: aSymbol of: aTrait)! ! !Behavior methodsFor: 'traits'! removeFromComposition: aTrait self setTraitComposition: (self traitComposition copyTraitExpression removeFromComposition: aTrait)! ! !Behavior methodsFor: 'traits'! removeTraitSelector: aSymbol self assert: [(self includesLocalSelector: aSymbol) not]. self basicRemoveSelector: aSymbol! ! !Behavior methodsFor: 'traits'! selfSentSelectorsFromSelectors: interestingSelectors | m result info | result := IdentitySet new. interestingSelectors collect: [:sel | m := self compiledMethodAt: sel ifAbsent: []. m ifNotNil: [info := (SendInfo on: m) collectSends. info selfSentSelectors do: [:sentSelector | result add: sentSelector]]]. ^result! ! !Behavior methodsFor: 'traits'! setTraitComposition: aTraitComposition | oldComposition | (self hasTraitComposition not and: [aTraitComposition isEmpty]) ifTrue: [^self]. aTraitComposition assertValidUser: self. oldComposition := self traitComposition. self traitComposition: aTraitComposition. self applyChangesOfNewTraitCompositionReplacing: oldComposition. oldComposition traits do: [:each | each removeUser: self]. aTraitComposition traits do: [:each | each addUser: self]! ! !Behavior methodsFor: 'traits'! setTraitCompositionFrom: aTraitExpression ^ self setTraitComposition: aTraitExpression asTraitComposition! ! !Behavior methodsFor: 'traits' stamp: 'al 3/25/2006 12:36'! traitComposition self subclassResponsibility! ! !Behavior methodsFor: 'traits' stamp: 'al 3/25/2006 12:39'! traitComposition: aTraitComposition self subclassResponsibility ! ! !Behavior methodsFor: 'traits'! traitCompositionIncludes: aTrait ^self == aTrait or: [self hasTraitComposition and: [self traitComposition allTraits includes: aTrait]]! ! !Behavior methodsFor: 'traits'! traitCompositionString ^self hasTraitComposition ifTrue: [self traitComposition asString] ifFalse: ['{}']! ! !Behavior methodsFor: 'traits'! traitOrClassOfSelector: aSymbol "Return the trait or the class which originally defines the method aSymbol or return self if locally defined or if it is a conflict marker method. This is primarly used by Debugger to determin the behavior in which a recompiled method should be put. If a conflict method is recompiled it should be put into the class, thus return self. Also see TraitComposition>>traitProvidingSelector:" ((self includesLocalSelector: aSymbol) or: [ self hasTraitComposition not]) ifTrue: [^self]. ^(self traitComposition traitProvidingSelector: aSymbol) ifNil: [self]! ! !Behavior methodsFor: 'traits'! traitTransformations ^ self traitComposition transformations ! ! !Behavior methodsFor: 'traits'! traits "Returns a collection of all traits used by the receiver" ^ self traitComposition traits! ! !Behavior methodsFor: 'traits'! traitsProvidingSelector: aSymbol | result | result := OrderedCollection new. self hasTraitComposition ifFalse: [^result]. (self traitComposition methodDescriptionsForSelector: aSymbol) do: [:methodDescription | methodDescription selector = aSymbol ifTrue: [ result addAll: (methodDescription locatedMethods collect: [:each | each location])]]. ^result! ! !Behavior methodsFor: 'traits'! updateMethodDictionarySelector: aSymbol "A method with selector aSymbol in myself or my traitComposition has been changed. Do the appropriate update to my methodDict (remove or update method) and return all affected selectors of me so that my useres get notified." | effectiveMethod modifiedSelectors descriptions selector | modifiedSelectors := IdentitySet new. descriptions := self hasTraitComposition ifTrue: [ self traitComposition methodDescriptionsForSelector: aSymbol ] ifFalse: [ #() ]. descriptions do: [:methodDescription | selector := methodDescription selector. (self includesLocalSelector: selector) ifFalse: [ methodDescription isEmpty ifTrue: [ self removeTraitSelector: selector. modifiedSelectors add: selector] ifFalse: [ effectiveMethod := methodDescription effectiveMethod. self addTraitSelector: selector withMethod: effectiveMethod. modifiedSelectors add: selector]]]. ^modifiedSelectors! ! !Behavior methodsFor: 'user interface' stamp: 'md 8/27/2005 17:18'! allLocalCallsOn: aSymbol "Answer a SortedCollection of all the methods that call on aSymbol, anywhere in my class hierarchy." | aSet special byte cls | aSet := Set new. cls := self theNonMetaClass. special := self environment hasSpecialSelector: aSymbol ifTrueSetByte: [:b | byte := b ]. cls withAllSuperAndSubclassesDoGently: [ :class | (class whichSelectorsReferTo: aSymbol special: special byte: byte) do: [:sel | sel isDoIt ifFalse: [aSet add: class name , ' ', sel]]]. cls class withAllSuperAndSubclassesDoGently: [ :class | (class whichSelectorsReferTo: aSymbol special: special byte: byte) do: [:sel | sel isDoIt ifFalse: [aSet add: class name , ' ', sel]]]. ^aSet! ! !Behavior methodsFor: 'user interface' stamp: 'marcus.denker 9/29/2008 15:17'! allUnreferencedInstanceVariables "Return a list of the instance variables known to the receiver which are not referenced in the receiver or any of its subclasses OR superclasses" ^ self allInstVarNames reject: [:ivn | | definingClass | definingClass := self classThatDefinesInstanceVariable: ivn. definingClass withAllSubclasses anySatisfy: [:class | (class whichSelectorsAccess: ivn asSymbol) notEmpty]]! ! !Behavior methodsFor: 'user interface'! crossReference "Answer an Array of arrays of size 2 whose first element is a message selector in the receiver's method dictionary and whose second element is a set of all message selectors in the method dictionary whose methods send a message with that selector. Subclasses are not included." ^self selectors asSortedCollection asArray collect: [:x | Array with: (String with: Character cr), x with: (self whichSelectorsReferTo: x)] "Point crossReference."! ! !Behavior methodsFor: 'user interface' stamp: 'marcus.denker 9/29/2008 13:01'! unreferencedInstanceVariables "Return a list of the instance variables defined in the receiver which are not referenced in the receiver or any of its subclasses." ^ self instVarNames reject: [:ivn | self withAllSubclasses anySatisfy: [:class | (class whichSelectorsAccess: ivn) notEmpty]]! ! !Behavior methodsFor: 'user interface' stamp: 'RAA 5/28/2001 12:00'! withAllSubAndSuperclassesDo: aBlock self withAllSubclassesDo: aBlock. self allSuperclassesDo: aBlock. ! ! !Behavior methodsFor: 'private'! basicRemoveSelector: selector "Assuming that the argument, selector (a Symbol), is a message selector in my method dictionary, remove it and its method." | oldMethod | oldMethod := self methodDict at: selector ifAbsent: [^ self]. self methodDict removeKey: selector. "Now flush Squeak's method cache, either by selector or by method" oldMethod flushCache. selector flushCache! ! !Behavior methodsFor: 'private' stamp: 'sd 3/28/2003 15:06'! becomeCompact "Here are the restrictions on compact classes in order for export segments to work: A compact class index may not be reused. If a class was compact in a release of Squeak, no other class may use that index. The class might not be compact later, and there should be nil in its place in the array." | cct index | self isWeak ifTrue:[^ self halt: 'You must not make a weak class compact']. cct := self environment compactClassesArray. (self indexIfCompact > 0 or: [cct includes: self]) ifTrue: [^ self halt: self name , 'is already compact']. index := cct indexOf: nil ifAbsent: [^ self halt: 'compact class table is full']. "Install this class in the compact class table" cct at: index put: self. "Update instspec so future instances will be compact" format := format + (index bitShift: 11). "Make up new instances and become old ones into them" self updateInstancesFrom: self. "Purge any old instances" Smalltalk garbageCollect.! ! !Behavior methodsFor: 'private' stamp: 'sd 3/28/2003 15:06'! becomeCompactSimplyAt: index "Make me compact, but don't update the instances. For importing segments." "Here are the restrictions on compact classes in order for export segments to work: A compact class index may not be reused. If a class was compact in a release of Squeak, no other class may use that index. The class might not be compact later, and there should be nil in its place in the array." | cct | self isWeak ifTrue:[^ self halt: 'You must not make a weak class compact']. cct := self environment compactClassesArray. (self indexIfCompact > 0 or: [cct includes: self]) ifTrue: [^ self halt: self name , 'is already compact']. (cct at: index) ifNotNil: [^ self halt: 'compact table slot already in use']. "Install this class in the compact class table" cct at: index put: self. "Update instspec so future instances will be compact" format := format + (index bitShift: 11). "Caller must convert the instances" ! ! !Behavior methodsFor: 'private' stamp: 'sd 3/28/2003 15:06'! becomeUncompact | cct index | cct := self environment compactClassesArray. (index := self indexIfCompact) = 0 ifTrue: [^ self]. (cct includes: self) ifFalse: [^ self halt "inconsistent state"]. "Update instspec so future instances will not be compact" format := format - (index bitShift: 11). "Make up new instances and become old ones into them" self updateInstancesFrom: self. "Make sure there are no compact ones left around" Smalltalk garbageCollect. "Remove this class from the compact class table" cct at: index put: nil. ! ! !Behavior methodsFor: 'private'! flushCache "Tell the interpreter to remove the contents of its method lookup cache, if it has one. Essential. See Object documentation whatIsAPrimitive." self primitiveFailed! ! !Behavior methodsFor: 'private'! indexIfCompact "If these 5 bits are non-zero, then instances of this class will be compact. It is crucial that there be an entry in Smalltalk compactClassesArray for any class so optimized. See the msgs becomeCompact and becomeUncompact." ^ (format bitShift: -11) bitAnd: 16r1F " Smalltalk compactClassesArray doWithIndex: [:c :i | c == nil ifFalse: [c indexIfCompact = i ifFalse: [self halt]]] "! ! !Behavior methodsFor: 'private' stamp: 'sd 11/19/2004 15:13'! setFormat: aFormatInstanceDescription "only use this method with extreme care since it modifies the format of the class ie a description of the number of instance variables and whether the class is compact, variable sized" format := aFormatInstanceDescription ! ! !Behavior methodsFor: 'private'! spaceUsed "Answer a rough estimate of number of bytes used by this class and its metaclass. Does not include space used by class variables." | space | space := 0. self selectorsDo: [:sel | | method | space := space + 16. "dict and org'n space" method := self compiledMethodAt: sel. space := space + (method size + 6 "hdr + avg pad"). method literalsDo: [:lit | (lit isMemberOf: Array) ifTrue: [space := space + ((lit size + 1) * 4)]. (lit isMemberOf: Float) ifTrue: [space := space + 12]. (lit isMemberOf: ByteString) ifTrue: [space := space + (lit size + 6)]. (lit isMemberOf: LargeNegativeInteger) ifTrue: [space := space + ((lit size + 1) * 4)]. (lit isMemberOf: LargePositiveInteger) ifTrue: [space := space + ((lit size + 1) * 4)]]]. ^ space! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Behavior class uses: TPureBehavior classTrait instanceVariableNames: ''! !Behavior class methodsFor: 'class initialization' stamp: 'apb 7/12/2004 23:23'! flushObsoleteSubclasses "Behavior flushObsoleteSubclasses" ObsoleteSubclasses finalizeValues.! ! !Behavior class methodsFor: 'class initialization' stamp: 'apb 7/12/2004 23:51'! initialize "Behavior initialize" "Never called for real" ObsoleteSubclasses ifNil: [self initializeObsoleteSubclasses] ifNotNil: [| newDict | newDict := WeakKeyToCollectionDictionary newFrom: ObsoleteSubclasses. newDict rehash. ObsoleteSubclasses := newDict]! ! !Behavior class methodsFor: 'class initialization' stamp: 'apb 7/12/2004 23:46'! initializeObsoleteSubclasses ObsoleteSubclasses := WeakKeyToCollectionDictionary new.! ! !Behavior class methodsFor: 'testing' stamp: 'dvf 9/27/2005 16:12'! canZapMethodDictionary "Return false since zapping the method dictionary of Behavior class or its subclasses will cause the system to fail." ^false! ! TestCase subclass: #BehaviorTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Classes'! !BehaviorTest methodsFor: 'tests' stamp: 'dc 9/28/2008 16:46'! testAllSelectors self assert: ProtoObject allSelectors = ProtoObject selectors. self assert: Object allSelectors = (Object selectors union: ProtoObject selectors). self assert: (Object allSelectorsBelow: ProtoObject) = (Object selectors).! ! !BehaviorTest methodsFor: 'tests' stamp: 'sd 1/28/2009 14:32'! testAllSelectorsAbove "self debug: #testAllSelectorsAbove" |sels | sels := Morph allSelectorsAbove. self deny: (sels includes: #submorphs). self deny: (sels includes: #submorphs). self assert: (sels includes: #clearHaltOnce). self assert: (sels includes: #cannotInterpret: ) ! ! !BehaviorTest methodsFor: 'tests' stamp: 'sd 1/28/2009 14:31'! testAllSelectorsAboveUntil "self debug: #testAllSelectorsAboveUntil" |sels | sels := Morph allSelectorsAboveUntil: Object.. self deny: (sels includes: #submorphs). self deny: (sels includes: #submorphs). self assert: (sels includes: #clearHaltOnce). self deny: (sels includes: #cannotInterpret: ) ! ! !BehaviorTest methodsFor: 'tests' stamp: 'sd 3/14/2004 18:11'! testBehaviorSubclasses "self run: #testBehaviorSubclasses" | b b2 | b := Behavior new. b superclass: OrderedCollection. b methodDictionary: MethodDictionary new. self shouldnt: [b subclasses ] raise: Error. self shouldnt: [b withAllSubclasses] raise: Error. self shouldnt: [b allSubclasses] raise: Error. b2 := Behavior new. b2 superclass: b. b2 methodDictionary: MethodDictionary new. self assert: (b subclasses includes: b2). self assert: (b withAllSubclasses includes: b).! ! !BehaviorTest methodsFor: 'tests' stamp: 'sd 11/19/2004 15:38'! testBehaviornewnewShouldNotCrash Behavior new new. "still not working correctly but at least does not crash the image" ! ! !BehaviorTest methodsFor: 'tests' stamp: 'marcus.denker 9/14/2008 21:14'! testBinding self assert: Object binding value = Object. self assert: Object binding key = #Object. self assert: Object class binding value = Object class. "returns nil for Metaclasses... like Encoder>>#associationFor:" self assert: Object class binding key isNil.! ! !BehaviorTest methodsFor: 'tests' stamp: 'ar 9/27/2005 21:43'! testChange "self debug: #testChange" | behavior model | behavior := Behavior new. behavior superclass: Model. behavior setFormat: Model format. model := Model new. model primitiveChangeClassTo: behavior new. behavior compile: 'thisIsATest ^ 2'. self assert: model thisIsATest = 2. self should: [Model new thisIsATest] raise: MessageNotUnderstood. ! ! !BehaviorTest methodsFor: 'tests' stamp: 'sd 1/28/2009 14:25'! testallSuperclassesIncluding "self debug: #testallSuperclassesIncluding" |cls | cls := ArrayedCollection allSuperclassesIncluding: Collection. self deny: (cls includes: ArrayedCollection). self deny: (cls includes: Object). self assert: (cls includes: Collection). self assert: (cls includes: SequenceableCollection). ! ! !BehaviorTest methodsFor: 'tests - testing method dictionary' stamp: 'marcus.denker 9/29/2008 15:11'! testWhichSelectorsAccess self assert: ((Point whichSelectorsAccess: 'x') includes: #x). self deny: ((Point whichSelectorsAccess: 'y') includes: #x).! ! LineSegment subclass: #Bezier2Segment instanceVariableNames: 'via' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Geometry'! !Bezier2Segment commentStamp: '' prior: 0! This class represents a quadratic bezier segment between two points Instance variables: via The additional control point (OFF the curve)! !Bezier2Segment methodsFor: 'accessing' stamp: 'ar 11/2/1998 12:14'! bounds "Return the bounds containing the receiver" ^super bounds encompass: via! ! !Bezier2Segment methodsFor: 'accessing' stamp: 'ar 6/8/2003 00:07'! degree ^2! ! !Bezier2Segment methodsFor: 'accessing' stamp: 'ar 11/2/1998 12:14'! via "Return the control point" ^via! ! !Bezier2Segment methodsFor: 'bezier clipping' stamp: 'ar 6/7/2003 23:45'! bezierClipHeight: dir | dirX dirY uMin uMax dx dy u | dirX := dir x. dirY := dir y. uMin := 0.0. uMax := (dirX * dirX) + (dirY * dirY). dx := via x - start x. dy := via y - start y. u := (dirX * dx) + (dirY * dy). u < uMin ifTrue:[uMin := u]. u > uMax ifTrue:[uMax := u]. ^uMin@uMax! ! !Bezier2Segment methodsFor: 'converting' stamp: 'ar 6/8/2003 04:19'! asBezier2Points: error ^Array with: start with: via with: end! ! !Bezier2Segment methodsFor: 'converting' stamp: 'ar 11/2/1998 12:17'! asBezier2Segment "Represent the receiver as quadratic bezier segment" ^self! ! !Bezier2Segment methodsFor: 'converting' stamp: 'ar 6/7/2003 21:05'! asBezier3Segment "Represent the receiver as cubic bezier segment" ^Bezier3Segment from: start via: 2*via+start / 3.0 and: 2*via+end / 3.0 to: end! ! !Bezier2Segment methodsFor: 'converting' stamp: 'ar 11/2/1998 12:18'! asIntegerSegment "Convert the receiver into integer representation" ^self species from: start asIntegerPoint to: end asIntegerPoint via: via asIntegerPoint! ! !Bezier2Segment methodsFor: 'converting' stamp: 'ar 6/7/2003 20:58'! asTangentSegment ^LineSegment from: via-start to: end-via! ! !Bezier2Segment methodsFor: 'initialize' stamp: 'ar 11/2/1998 12:13'! from: startPoint to: endPoint "Initialize the receiver as straight line" start := startPoint. end := endPoint. via := (start + end) // 2.! ! !Bezier2Segment methodsFor: 'initialize' stamp: 'ar 11/2/1998 12:13'! from: startPoint to: endPoint via: viaPoint "Initialize the receiver" start := startPoint. end := endPoint. via := viaPoint.! ! !Bezier2Segment methodsFor: 'initialize' stamp: 'ar 6/7/2003 22:37'! from: startPoint to: endPoint withMidPoint: pointOnCurve "Initialize the receiver with the pointOnCurve assumed at the parametric value 0.5" start := startPoint. end := endPoint. "Compute via" via := (pointOnCurve * 2) - (start + end * 0.5).! ! !Bezier2Segment methodsFor: 'initialize' stamp: 'ar 6/6/2003 03:03'! from: startPoint to: endPoint withMidPoint: pointOnCurve at: parameter "Initialize the receiver with the pointOnCurve at the given parametric value" | t1 t2 t3 | start := startPoint. end := endPoint. "Compute via" t1 := (1.0 - parameter) squared. t2 := 1.0 / (2 * parameter * (1.0 - parameter)). t3 := parameter squared. via := (pointOnCurve - (start * t1) - (end * t3)) * t2! ! !Bezier2Segment methodsFor: 'initialize' stamp: 'ar 6/7/2003 00:09'! initializeFrom: controlPoints controlPoints size = 3 ifFalse:[self error:'Wrong number of control points']. start := controlPoints at: 1. via := controlPoints at: 2. end := controlPoints at: 3.! ! !Bezier2Segment methodsFor: 'printing' stamp: 'ar 11/2/1998 12:18'! printOn: aStream "Print the receiver on aStream" aStream nextPutAll: self class name; nextPutAll:' from: '; print: start; nextPutAll: ' via: '; print: via; nextPutAll: ' to: '; print: end; space.! ! !Bezier2Segment methodsFor: 'printing' stamp: 'MPW 1/1/1901 21:59'! printOnStream: aStream aStream print: self class name; print:'from: '; write: start; print:'via: '; write: via; print:'to: '; write: end; print:' '.! ! !Bezier2Segment methodsFor: 'testing' stamp: 'ar 11/2/1998 12:15'! hasZeroLength "Return true if the receiver has zero length" ^start = end and:[start = via]! ! !Bezier2Segment methodsFor: 'testing' stamp: 'ar 11/2/1998 12:15'! isBezier2Segment "Return true if the receiver is a quadratic bezier segment" ^true! ! !Bezier2Segment methodsFor: 'testing' stamp: 'ar 11/2/1998 12:15'! isStraight "Return true if the receiver represents a straight line" ^(self tangentAtStart crossProduct: self tangentAtEnd) = 0! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 6/7/2003 00:08'! controlPoints ^{start. via. end}! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 6/7/2003 23:39'! controlPointsDo: aBlock aBlock value: start; value: via; value: end! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 6/8/2003 00:08'! curveFrom: param1 to: param2 "Return a new curve from param1 to param2" | newStart newEnd newVia tan1 tan2 d1 d2 | tan1 := via - start. tan2 := end - via. param1 <= 0.0 ifTrue:[ newStart := start. ] ifFalse:[ d1 := tan1 * param1 + start. d2 := tan2 * param1 + via. newStart := (d2 - d1) * param1 + d1 ]. param2 >= 1.0 ifTrue:[ newEnd := end. ] ifFalse:[ d1 := tan1 * param2 + start. d2 := tan2 * param2 + via. newEnd := (d2 - d1) * param2 + d1. ]. tan2 := (tan2 - tan1 * param1 + tan1) * (param2 - param1). newVia := newStart + tan2. ^self clone from: newStart to: newEnd via: newVia.! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 11/2/1998 12:15'! length "Return the length of the receiver" "Note: Overestimates the length" ^(start dist: via) + (via dist: end)! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 11/6/1998 23:39'! lineSegmentsDo: aBlock "Evaluate aBlock with the receiver's line segments" "Note: We could use forward differencing here." | steps last deltaStep t next | steps := 1 max: (self length // 10). "Assume 10 pixels per step" last := start. deltaStep := 1.0 / steps asFloat. t := deltaStep. 1 to: steps do:[:i| next := self valueAt: t. aBlock value: last value: next. last := next. t := t + deltaStep].! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 6/7/2003 17:21'! lineSegments: steps do: aBlock "Evaluate aBlock with the receiver's line segments" "Note: We could use forward differencing here." | last deltaStep t next | last := start. deltaStep := 1.0 / steps asFloat. t := deltaStep. 1 to: steps do:[:i| next := self valueAt: t. aBlock value: last value: next. last := next. t := t + deltaStep].! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 6/7/2003 00:04'! outlineSegment: width | delta newStart newEnd param newMid | delta := self tangentAtStart normalized * width. delta := delta y @ delta x negated. newStart := start + delta. delta := self tangentAtEnd normalized * width. delta := delta y @ delta x negated. newEnd := end + delta. param := 0.5. "self tangentAtStart r / (self tangentAtStart r + self tangentAtEnd r)." delta := (self tangentAt: param) normalized * width. delta := delta y @ delta x negated. newMid := (self valueAt: param) + delta. ^self class from: newStart to: newEnd withMidPoint: newMid at: param! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 6/9/2003 03:43'! parameterAtExtremeX "Note: Only valid for non-monoton receivers" ^self parameterAtExtreme: 0.0@1.0. ! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 6/9/2003 03:43'! parameterAtExtremeY "Note: Only valid for non-monoton receivers" ^self parameterAtExtreme: 1.0@0.0. ! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 6/9/2003 03:43'! parameterAtExtreme: tangentDirection "Compute the parameter value at which the tangent reaches tangentDirection. We need to find the parameter value t at which the following holds ((t * dir + in) crossProduct: tangentDirection) = 0. Since this is pretty ugly we use the normal direction rather than the tangent and compute the equivalent relation using the dot product as ((t * dir + in) dotProduct: nrm) = 0. Reformulation yields ((t * dir x + in x) * nrm x) + ((t * dir y + in y) * nrm y) = 0. (t * dir x * nrm x) + (in x * nrm x) + (t * dir y * nrm y) + (in y * nrm y) = 0. (t * dir x * nrm x) + (t * dir y * nrm y) = 0 - ((in x * nrm x) + (in y * nrm y)). (in x * nrm x) + (in y * nrm y) t = 0 - --------------------------------------- (dir x * nrm x) + (dir y * nrm y) And that's that. Note that we can get rid of the negation by computing 'dir' the other way around (e.g., in the above it would read '-dir') which is trivial to do. Note also that the above does not generalize easily beyond 2D since its not clear how to express the 'normal direction' of a tangent plane. " | inX inY dirX dirY nrmX nrmY | "Compute in" inX := via x - start x. inY := via y - start y. "Compute -dir" dirX := inX - (end x - via x). dirY := inY - (end y - via y). "Compute nrm" nrmX := tangentDirection y. nrmY := 0 - tangentDirection x. "Compute result" ^((inX * nrmX) + (inY * nrmY)) / ((dirX * nrmX) + (dirY * nrmY))! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'nk 12/27/2003 13:00'! roundTo: quantum super roundTo: quantum. via := via roundTo: quantum. ! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 6/8/2003 00:54'! tangentAtMid "Return the tangent at the given parametric value along the receiver" | in out | in := self tangentAtStart. out := self tangentAtEnd. ^in + out * 0.5! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 11/2/1998 12:16'! tangentAt: parameter "Return the tangent at the given parametric value along the receiver" | in out | in := self tangentAtStart. out := self tangentAtEnd. ^in + (out - in * parameter)! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 11/2/1998 12:16'! tangentAtEnd "Return the tangent for the last point" ^end - via! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 11/2/1998 12:16'! tangentAtStart "Return the tangent for the first point" ^via - start! ! !Bezier2Segment methodsFor: 'vector functions' stamp: 'ar 11/2/1998 12:17'! valueAt: parameter "Evaluate the receiver at the given parametric value" "Return the point at the parametric value t: p(t) = (1-t)^2 * p1 + 2*t*(1-t) * p2 + t^2 * p3. " | t1 t2 t3 | t1 := (1.0 - parameter) squared. t2 := 2 * parameter * (1.0 - parameter). t3 := parameter squared. ^(start * t1) + (via * t2) + (end * t3)! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Bezier2Segment class instanceVariableNames: ''! !Bezier2Segment class methodsFor: 'instance creation' stamp: 'ar 11/1/1998 21:14'! from: startPoint to: endPoint via: viaPoint ^self new from: startPoint to: endPoint via: viaPoint! ! !Bezier2Segment class methodsFor: 'instance creation' stamp: 'ar 11/1/1998 21:30'! from: startPoint to: endPoint withMidPoint: pointOnCurve ^self new from: startPoint to: endPoint withMidPoint: pointOnCurve! ! !Bezier2Segment class methodsFor: 'instance creation' stamp: 'ar 11/1/1998 21:32'! from: startPoint to: endPoint withMidPoint: pointOnCurve at: parameter ^self new from: startPoint to: endPoint withMidPoint: pointOnCurve at: parameter! ! !Bezier2Segment class methodsFor: 'instance creation' stamp: 'ar 11/1/1998 21:30'! from: startPoint via: viaPoint to: endPoint ^self new from: startPoint to: endPoint via: viaPoint! ! !Bezier2Segment class methodsFor: 'instance creation' stamp: 'ar 11/1/1998 21:32'! from: startPoint withMidPoint: pointOnCurve at: parameter to: endPoint ^self new from: startPoint to: endPoint withMidPoint: pointOnCurve at: parameter! ! !Bezier2Segment class methodsFor: 'instance creation' stamp: 'ar 11/1/1998 21:30'! from: startPoint withMidPoint: pointOnCurve to: endPoint ^self new from: startPoint to: endPoint withMidPoint: pointOnCurve! ! !Bezier2Segment class methodsFor: 'utilities' stamp: 'ar 6/7/2003 18:33'! makeEllipseSegments: aRectangle "Answer a set of bezier segments approximating an ellipsoid fitting the given rectangle. This method creates eight bezier segments (two for each quadrant) approximating the oval." "EXAMPLE: This example draws an oval with a red border and overlays the approximating bezier segments on top of the oval (drawn in black), thus giving an impression of how closely the bezier resembles the oval. Change the rectangle to see how accurate the approximation is for various radii of the oval. | rect | rect := 100@100 extent: 1200@500. Display getCanvas fillOval: rect color: Color yellow borderWidth: 1 borderColor: Color red. (Bezier2Segment makeEllipseSegments: rect) do:[:seg| seg lineSegmentsDo:[:last :next| Display getCanvas line: last to: next width: 1 color: Color black]]. " "EXAMPLE: | minRadius maxRadius | maxRadius := 300. minRadius := 20. maxRadius to: minRadius by: -10 do:[:rad| | rect | rect := 400@400 - rad corner: 400@400 + rad. Display getCanvas fillOval: rect color: Color yellow borderWidth: 1 borderColor: Color red. (Bezier2Segment makeEllipseSegments: rect) do:[:seg| seg lineSegmentsDo:[:last :next| Display getCanvas line: last to: next width: 1 color: Color black]]]. " | nrm topCenter leftCenter rightCenter bottomCenter dir scale seg1a topRight seg1b seg2a bottomRight seg2b center bottomLeft topLeft seg3a seg3b seg4a seg4b | dir := aRectangle width * 0.5. nrm := aRectangle height * 0.5. "Compute the eight control points on the oval" scale := 0.7071067811865475. "45 degreesToRadians cos = 45 degreesToRadians sin = 2 sqrt / 2" center := aRectangle origin + aRectangle corner * 0.5. topCenter := aRectangle topCenter. rightCenter := aRectangle rightCenter. leftCenter := aRectangle leftCenter. bottomCenter := aRectangle bottomCenter. topRight := (center x + (dir * scale)) @ (center y - (nrm * scale)). bottomRight := (center x + (dir * scale)) @ (center y + (nrm * scale)). bottomLeft := (center x - (dir * scale)) @ (center y + (nrm * scale)). topLeft := (center x - (dir * scale)) @ (center y - (nrm * scale)). scale := 0.414213562373095. "2 sqrt - 1" dir := (dir * scale) @ 0. nrm := 0 @ (nrm * scale). seg1a := self from: topCenter via: topCenter + dir to: topRight. seg1b := self from: topRight via: rightCenter - nrm to: rightCenter. seg2a := self from: rightCenter via: rightCenter + nrm to: bottomRight. seg2b := self from: bottomRight via: bottomCenter + dir to: bottomCenter. seg3a := self from: bottomCenter via: bottomCenter - dir to: bottomLeft. seg3b := self from: bottomLeft via: leftCenter + nrm to: leftCenter. seg4a := self from: leftCenter via: leftCenter - nrm to: topLeft. seg4b := self from: topLeft via: topCenter - dir to: topCenter. ^{seg1a. seg1b. seg2a. seg2b. seg3a. seg3b. seg4a. seg4b}! ! LineSegment subclass: #Bezier3Segment instanceVariableNames: 'via1 via2' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Geometry'! !Bezier3Segment commentStamp: '' prior: 0! This class represents a cubic bezier segment between two points Instance variables: via1, via2 The additional control points (OFF the curve)! !Bezier3Segment methodsFor: 'accessing' stamp: 'DSM 10/15/1999 15:20'! bounds ^ ((super bounds encompassing: via1) encompassing: via2)! ! !Bezier3Segment methodsFor: 'accessing' stamp: 'ar 6/8/2003 00:07'! degree ^3! ! !Bezier3Segment methodsFor: 'accessing' stamp: 'ar 6/6/2003 21:59'! length "Answer a gross approximation of the length of the receiver" ^(start dist: via1) + (via1 dist: via2) + (via2 dist: end)! ! !Bezier3Segment methodsFor: 'accessing' stamp: 'DSM 10/15/1999 15:01'! valueAt: t | a b c d | "| p1 p2 p3 | p1 := start interpolateTo: via1 at: t. p2 := via1 interpolateTo: via2 at: t. p3 := via2 interpolateTo: end at: t. p1 := p1 interpolateTo: p2 at: t. p2 := p2 interpolateTo: p3 at: t. ^ p1 interpolateTo: p2 at: t" a := (start negated) + (3 * via1) - (3 * via2) + (end). b := (3 * start) - (6 * via1) + (3 * via2). c := (3 * start negated) + (3 * via1). d := start. ^ ((a * t + b) * t + c) * t + d ! ! !Bezier3Segment methodsFor: 'accessing' stamp: 'ar 6/6/2003 22:37'! via1 ^via1! ! !Bezier3Segment methodsFor: 'accessing' stamp: 'DSM 10/14/1999 15:31'! via1: aPoint via1 := aPoint! ! !Bezier3Segment methodsFor: 'accessing' stamp: 'ar 6/6/2003 22:37'! via2 ^via2! ! !Bezier3Segment methodsFor: 'accessing' stamp: 'DSM 10/14/1999 15:31'! via2: aPoint via2 := aPoint! ! !Bezier3Segment methodsFor: 'bezier clipping' stamp: 'ar 6/7/2003 23:45'! bezierClipHeight: dir "Check if the argument overlaps the receiver somewhere along the line from start to end. Optimized for speed." | u dirX dirY dx dy uMin uMax | dirX := dir x. dirY := dir y. uMin := 0.0. uMax := (dirX * dirX) + (dirY * dirY). dx := via1 x - start x. dy := via1 y - start y. u := (dirX * dx) + (dirY * dy). u < uMin ifTrue:[uMin := u]. u > uMax ifTrue:[uMax := u]. dx := via2 x - start x. dy := via2 y - start y. u := (dirX * dx) + (dirY * dy). u < uMin ifTrue:[uMin := u]. u > uMax ifTrue:[uMax := u]. ^uMin@uMax! ! !Bezier3Segment methodsFor: 'converting' stamp: 'ar 6/7/2003 21:07'! asBezier2Points: error "Demote a cubic bezier to a set of approximating quadratic beziers. Should convert to forward differencing someday" | curves pts step prev index a b f | curves := self bezier2SegmentCount: error. pts := Array new: curves * 3. step := 1.0 / (curves * 2). prev := start. 1 to: curves do: [ :c | index := 3*c. a := pts at: index-2 put: prev. b := (self valueAt: (c*2-1)*step). f := pts at: index put: (self valueAt: (c*2)*step). pts at: index-1 put: (4 * b - a - f) / 2. prev := pts at: index. ]. ^ pts. ! ! !Bezier3Segment methodsFor: 'converting' stamp: 'ar 6/7/2003 21:07'! asBezier2Segments "Demote a cubic bezier to a set of approximating quadratic beziers." ^self asBezier2Segments: 0.5! ! !Bezier3Segment methodsFor: 'converting' stamp: 'ar 6/6/2003 22:23'! asBezierShape "Demote a cubic bezier to a set of approximating quadratic beziers." ^self asBezierShape: 0.5! ! !Bezier3Segment methodsFor: 'converting' stamp: 'ar 6/7/2003 21:09'! asBezierShape: error "Demote a cubic bezier to a set of approximating quadratic beziers. Should convert to forward differencing someday" ^(self asBezier2Points: error) asPointArray.! ! !Bezier3Segment methodsFor: 'converting' stamp: 'DSM 10/15/1999 15:45'! asPointArray | p | p := PointArray new: 4. p at: 1 put: start. p at: 2 put: via1. p at: 3 put: via2. p at: 4 put: end. ^ p! ! !Bezier3Segment methodsFor: 'converting' stamp: 'ar 6/7/2003 20:58'! asTangentSegment ^Bezier2Segment from: via1-start via: via2-via1 to: end-via2! ! !Bezier3Segment methodsFor: 'converting' stamp: 'DSM 3/10/2000 12:10'! bezier2SegmentCount: pixelError "Compute the number of quadratic bezier segments needed to approximate this cubic with no more than a specified error" | a | a := (start x negated @ start y negated) + (3 * via1) - (3 * via2) + (end). ^ (((a r / (20.0 * pixelError)) raisedTo: 0.333333) ceiling) max: 1. ! ! !Bezier3Segment methodsFor: 'initialization' stamp: 'DSM 10/14/1999 15:33'! from: aPoint1 via: aPoint2 and: aPoint3 to: aPoint4 start := aPoint1. via1 := aPoint2. via2 := aPoint3. end := aPoint4! ! !Bezier3Segment methodsFor: 'initialization' stamp: 'ar 6/7/2003 00:09'! initializeFrom: controlPoints controlPoints size = 4 ifFalse:[self error:'Wrong number of control points']. start := controlPoints at: 1. via1 := controlPoints at: 2. via2 := controlPoints at: 3. end := controlPoints at: 4.! ! !Bezier3Segment methodsFor: 'vector functions' stamp: 'ar 6/7/2003 00:08'! controlPoints ^{start. via1. via2. end}! ! !Bezier3Segment methodsFor: 'vector functions' stamp: 'ar 6/7/2003 23:39'! controlPointsDo: aBlock aBlock value: start; value: via1; value: via2; value: end! ! !Bezier3Segment methodsFor: 'vector functions' stamp: 'ar 6/6/2003 21:52'! lineSegmentsDo: aBlock "Evaluate aBlock with the receiver's line segments" "Note: We could use forward differencing here." | steps last deltaStep t next | steps := 1 max: (self length // 10). "Assume 10 pixels per step" last := start. deltaStep := 1.0 / steps asFloat. t := deltaStep. 1 to: steps do:[:i| next := self valueAt: t. aBlock value: last value: next. last := next. t := t + deltaStep].! ! !Bezier3Segment methodsFor: 'vector functions' stamp: 'ar 6/7/2003 17:21'! lineSegments: steps do: aBlock "Evaluate aBlock with the receiver's line segments" "Note: We could use forward differencing here." | last deltaStep t next | last := start. deltaStep := 1.0 / steps asFloat. t := deltaStep. 1 to: steps do:[:i| next := self valueAt: t. aBlock value: last value: next. last := next. t := t + deltaStep].! ! !Bezier3Segment methodsFor: 'vector functions' stamp: 'ar 6/7/2003 00:04'! outlineSegment: width | tan1 nrm1 tan2 nrm2 newStart newVia1 newEnd newVia2 dist | tan1 := (via1 - start) normalized. nrm1 := tan1 * width. nrm1 := nrm1 y @ nrm1 x negated. tan2 := (end - via2) normalized. nrm2 := tan2 * width. nrm2 := nrm2 y @ nrm2 x negated. newStart := start + nrm1. newEnd := end + nrm2. dist := (newStart dist: newEnd) * 0.3. newVia1 := newStart + (tan1 * dist). newVia2 := newEnd - (tan2 * dist). ^self class from: newStart via: newVia1 and: newVia2 to: newEnd. ! ! !Bezier3Segment methodsFor: 'vector functions' stamp: 'ar 6/6/2003 22:02'! tangentAtEnd ^end - via2! ! !Bezier3Segment methodsFor: 'vector functions' stamp: 'ar 6/8/2003 00:56'! tangentAtMid | tan1 tan2 tan3 | tan1 := via1 - start. tan2 := via2 - via1. tan3 := end - via2. ^(tan1 + (2*tan2) + tan3) * 0.25 ! ! !Bezier3Segment methodsFor: 'vector functions' stamp: 'ar 6/6/2003 22:01'! tangentAtStart ^via1 - start! ! !Bezier3Segment methodsFor: 'vector functions' stamp: 'ar 6/7/2003 19:25'! tangentAt: parameter | tan1 tan2 tan3 t1 t2 t3 | tan1 := via1 - start. tan2 := via2 - via1. tan3 := end - via2. t1 := (1.0 - parameter) squared. t2 := 2 * parameter * (1.0 - parameter). t3 := parameter squared. ^(tan1 * t1) + (tan2 * t2) + (tan3 * t3)! ! !Bezier3Segment methodsFor: 'private' stamp: 'DSM 10/14/1999 16:25'! bezier2SegmentCount "Compute the number of quadratic bezier segments needed to approximate this cubic with less than a 1-pixel error" ^ self bezier2SegmentCount: 1.0! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Bezier3Segment class instanceVariableNames: ''! !Bezier3Segment class methodsFor: 'examples' stamp: 'DSM 10/15/1999 15:49'! example1 | c | c := Bezier3Segment new from: 0@0 via: 0@100 and: 100@0 to: 100@100. ^ c asBezierShape! ! !Bezier3Segment class methodsFor: 'examples' stamp: 'DSM 10/15/1999 16:00'! example2 "draws a cubic bezier on the screen" | c canvas | c := Bezier3Segment new from: 0 @ 0 via: 0 @ 100 and: 100 @ 0 to: 100 @ 100. canvas := BalloonCanvas on: Display. canvas aaLevel: 4. canvas drawBezier3Shape: c asPointArray color: Color transparent borderWidth: 1 borderColor: Color black! ! !Bezier3Segment class methodsFor: 'instance creation' stamp: 'DSM 10/15/1999 15:23'! from: p1 to: p2 ^ self new from: p1 via: (p1 interpolateTo: p2 at: 0.3333) and: (p1 interpolateTo: p2 at: 0.66667) to: p2! ! !Bezier3Segment class methodsFor: 'instance creation' stamp: 'DSM 10/15/1999 15:24'! from: p1 via: p2 and: p3 to: p4 ^ self new from: p1 via: p2 and: p3 to: p4! ! !Bezier3Segment class methodsFor: 'utilities' stamp: 'DSM 10/15/1999 16:06'! convertBezier3ToBezier2: vertices | pa pts index c | pts := OrderedCollection new. 1 to: vertices size // 4 do: [:i | index := i * 4 - 3. c := Bezier3Segment new from: (vertices at: index) via: (vertices at: index + 1) and: (vertices at: index + 2) to: (vertices at: index + 3). pts addAll: c asBezierShape]. pa := PointArray new: pts size. pts withIndexDo: [:p :i | pa at: i put: p ]. ^ pa! ! !Bezier3Segment class methodsFor: 'utilities' stamp: 'ar 6/8/2003 03:25'! makeEllipseSegments: aRectangle "Answer a set of bezier segments approximating an ellipsoid fitting the given rectangle. This method creates four bezier segments (one for each quadrant) approximating the oval." "EXAMPLE: This example draws an oval with a red border and overlays the approximating bezier segments on top of the oval (drawn in black), thus giving an impression of how closely the bezier resembles the oval. Change the rectangle to see how accurate the approximation is for various radii of the oval. | rect | rect := 100@100 extent: 500@200. Display getCanvas fillOval: rect color: Color yellow borderWidth: 1 borderColor: Color red. (Bezier3Segment makeEllipseSegments: rect) do:[:seg| seg lineSegmentsDo:[:last :next| Display getCanvas line: last to: next width: 1 color: Color black]]. " "EXAMPLE: | minRadius maxRadius | maxRadius := 300. minRadius := 20. maxRadius to: minRadius by: -10 do:[:rad| | rect | rect := 400@400 - rad corner: 400@400 + rad. Display getCanvas fillOval: rect color: Color yellow borderWidth: 1 borderColor: Color red. (Bezier3Segment makeEllipseSegments: rect) do:[:seg| seg lineSegmentsDo:[:last :next| Display getCanvas line: last to: next width: 1 color: Color black]]]. " ^self makeEllipseSegments: aRectangle count: 4! ! !Bezier3Segment class methodsFor: 'utilities' stamp: 'eem 6/11/2008 16:08'! makeEllipseSegments: aRectangle count: segmentCount "Answer a set of bezier segments approximating an ellipsoid fitting the given rectangle. This method creates segmentCount bezier segments (one for each quadrant) approximating the oval." | count angle center scale | center := aRectangle origin + aRectangle corner * 0.5. scale := aRectangle extent * 0.5. count := segmentCount max: 2. "need at least two segments" angle := 360.0 / count. ^(1 to: count) collect:[:i| | seg | seg := self makeUnitPieSegmentFrom: i-1*angle to: i*angle. self controlPoints: (seg controlPoints collect:[:pt| pt * scale + center]) ].! ! !Bezier3Segment class methodsFor: 'utilities' stamp: 'ar 6/8/2003 03:53'! makePieSegments: aRectangle from: angle1 to: angle2 "Create a series of cubic bezier segments for the oval inscribed in aRectangle between angle1 and angle2. The segments are oriented clockwise, to get counter-clockwise segments simply switch angle1 and angle2." angle2 < angle1 ifTrue:[ "ccw segments" ^(self makePieSegments: aRectangle from: angle2 to: angle1) reversed collect:[:seg| seg reversed] ]. "Split up segments if larger than 120 degrees" angle2 - angle1 > 120 ifTrue:["subdivide" | midAngle | midAngle := angle1 + angle2 * 0.5. ^(self makePieSegments: aRectangle from: angle1 to: midAngle), (self makePieSegments: aRectangle from: midAngle to: angle2). ]. "Create actual pie segment" ^self makePieSegment: aRectangle from: angle1 to: angle2 ! ! !Bezier3Segment class methodsFor: 'utilities' stamp: 'ar 6/8/2003 03:26'! makePieSegment: aRectangle from: angle1 to: angle2 "Create a single pie segment for the oval inscribed in aRectangle between angle1 and angle2. If angle1 is less than angle2 this method creates a CW pie segment, otherwise it creates a CCW pie segment." | seg center scale | angle1 > angle2 ifTrue:["ccw" ^(self makePieSegment: aRectangle from: angle2 to: angle1) reversed ]. "create a unit circle pie segment from angle1 to angle2" seg := self makeUnitPieSegmentFrom: angle1 to: angle2. "scale the segment to fit aRectangle" center := aRectangle origin + aRectangle corner * 0.5. scale := aRectangle extent * 0.5. ^self controlPoints: (seg controlPoints collect:[:pt| pt * scale + center])! ! !Bezier3Segment class methodsFor: 'utilities' stamp: 'ar 6/8/2003 03:59'! makeUnitPieSegmentFrom: angle1 to: angle2 "Create a clockwise unit pie segment from angle1 to angle2, that is a pie segment for a circle centered at zero with radius one. Note: This method can be used to create at most a quarter circle." | pt1 pt2 rad1 rad2 | rad1 := angle1 degreesToRadians. rad2 := angle2 degreesToRadians. pt1 := rad1 sin @ rad1 cos negated. pt2 := rad2 sin @ rad2 cos negated. ^self makeUnitPieSegmentWith: pt1 and: pt2! ! !Bezier3Segment class methodsFor: 'utilities' stamp: 'ar 6/8/2003 04:45'! makeUnitPieSegmentWith: point1 and: point2 "Create a clockwise unit pie segment from point1 to point2, that is a pie segment for a circle centered at zero with radius one." | pt1 pt2 dir1 dir2 mid length scale cp1 cp2 pt3 magic | "point1 and point2 are the points on the unit circle for accuracy (or broken input), renormalize them." pt1 := point1 normalized. pt2 := point2 normalized. "compute the normal vectors - those are tangent directions for the bezier" dir1 := pt1 y negated @ pt1 x. dir2 := pt2 y negated @ pt2 x. "Okay, now that we have the points and tangents on the unit circle, let's do the magic. For fitting a cubic bezier onto a circle section we know that we want the end points be on the circle and the tangents to point towards the right direction (both of which we have in the above). What we do NOT know is how to scale the tangents so that midpoint of the bezier is exactly on the circle. The good news is that there is a linear relation between the length of the tangent vectors and the distance of the midpoint from the circle's origin. The bad news is that I don't know how to derive it analytically. So what I do here is simply sampling the bezier twice (not really - the first sample is free) and then to compute the distance from the sample." "The first sample is just between the two points on the curve" mid := pt1 + pt2 * 0.5. "The second sample will be taken from the curve with coincident control points at the intersection of dir1 and dir2, which simplifies significantly with a little understanding about trigonometry, since the angle formed between mid, pt1 and the intersection is the same as between the center, pt1 and mid." length := mid r. "length is not only the distance from the center of the unit circle but also the sine of the angle between the circle's center, pt1 and mid (since center is at zero and pt1 has unit length). Therefore, to scale dir1 to the intersection with dir2 we can use mid's distance from pt1 and simply divide it by the sine value." scale := (mid dist: pt1). length > 0.0 ifTrue:[ scale := scale / length]. "now sample the cubic bezier (optimized version for coincident control points)" cp1 := pt1 + (dir1 * (scale * 0.75)). cp2 := pt2 - (dir2 * (scale * 0.75)). pt3 := cp1 + cp2 * 0.5. "compute the magic constant" scale := (pt3 - mid) r / scale. magic := 1.0 - length / scale. "and finally answer the pie segment" ^self from: pt1 via: pt1 + (dir1 * magic) and: pt2 - (dir2 * magic) to: pt2! ! Object subclass: #BitBlt instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight colorMap' classVariableNames: 'CachedFontColorMaps ColorConvertingMaps' poolDictionaries: '' category: 'Graphics-Primitives'! !BitBlt commentStamp: '' prior: 0! I represent a block transfer (BLT) of pixels into a rectangle (destX, destY, width, height) of the destinationForm. The source of pixels may be a similar rectangle (at sourceX, sourceY) in the sourceForm, or a constant color, currently called halftoneForm. If both are specified, their pixel values are combined with a logical AND function prior to transfer. In any case, the pixels from the source are combined with those of the destination by as specified by the combinationRule. The combination rule whose value is 0 through 15 programs the transfer to produce 1 or 0 according to its 4-bit representation as follows: 8: if source is 0 and destination is 0 4: if source is 0 and destination is 1 2: if source is 1 and destination is 0 1: if source is 1 and destination is 1. At each pixel the corresponding bits of the source and destination pixel values determine one of these conditions; if the combination rule has a 1 in the corresponding bit position, then the new destination value will be 1, otherwise it will be zero. Forms may be of different depths, see the comment in class Form. In addition to the original 16 combination rules, this BitBlt supports 16 fails (to simulate paint bits) 17 fails (to simulate erase bits) 18 sourceWord + destinationWord 19 sourceWord - destinationWord 20 rgbAdd: sourceWord with: destinationWord. Sum of color components 21 rgbSub: sourceWord with: destinationWord. Difference of color components 22 OLDrgbDiff: sourceWord with: destinationWord. Sum of abs of differences in components 23 OLDtallyIntoMap: destinationWord. Tallies pixValues into a colorMap these old versions don't do bitwise dest clipping. Use 32 and 33 now. 24 alphaBlend: sourceWord with: destinationWord. 32-bit source and dest only 25 pixPaint: sourceWord with: destinationWord. Wherever the sourceForm is non-zero, it replaces the destination. Can be used with a 1-bit source color mapped to (0, FFFFFFFF), and a fillColor to fill the dest with that color wherever the source is 1. 26 pixMask: sourceWord with: destinationWord. Like pixPaint, but fills with 0. 27 rgbMax: sourceWord with: destinationWord. Max of each color component. 28 rgbMin: sourceWord with: destinationWord. Min of each color component. 29 rgbMin: sourceWord bitInvert32 with: destinationWord. Min with (max-source) 30 alphaBlendConst: sourceWord with: destinationWord. alpha is an arg. works in 16 bits. 31 alphaPaintConst: sourceWord with: destinationWord. alpha is an arg. works in 16 bits. 32 rgbDiff: sourceWord with: destinationWord. Sum of abs of differences in components 33 tallyIntoMap: destinationWord. Tallies pixValues into a colorMap 34 alphaBlendScaled: srcWord with: dstWord. Alpha blend of scaled srcWord and destWord. The color specified by halftoneForm may be either a Color or a Pattern. A Color is converted to a pixelValue for the depth of the destinationForm. If a Pattern, BitBlt will simply interpret its bitmap as an array of Color pixelValues. BitBlt aligns the first element of this array with the top scanline of the destinationForm, the second with the second, and so on, cycling through the color array as necessary. Within each scan line the 32-bit value is repeated from left to right across the form. If the value repeats on pixels boudaries, the effect will be a constant color; if not, it will produce a halftone that repeats on 32-bit boundaries. Any transfer specified is further clipped by the specified rectangle (clipX, clipY, clipWidth, clipHeight), and also by the bounds of the source and destination forms. To make a small Form repeat and fill a big form, use an InfiniteForm as the source. To write on a form and leave with both transparent and opapue areas, use a MaskedForm as the source. Pixels from a source to a destination whose pixels have a different depth are converted based on the optional colorMap. If colorMap is nil, then conversion to more bits is done by filling the new high-order bits with zero, and conversion to fewer bits is done by truncating the lost high-order bits. The colorMap, if specified, must be a either word array (ie Bitmap) with 2^n elements, where n is the pixel depth of the source, or a fully specified ColorMap which may contain a lookup table (ie Bitmap) and/or four separate masks and shifts which are applied to the pixels. For every source pixel, BitBlt will first perform masking and shifting and then index the lookup table, and select the corresponding pixelValue and mask it to the destination pixel size before storing. When blitting from a 32 or 16 bit deep Form to one 8 bits or less, the default is truncation. This will produce very strange colors, since truncation of the high bits does not produce the nearest encoded color. Supply a 512 long colorMap, and red, green, and blue will be shifted down to 3 bits each, and mapped. The message copybits...stdColors will use the best map to the standard colors for destinations of depths 8, 4, 2 and 1. Two other sized of colorMaps are allowed, 4096 (4 bits per color) and 32786 (five bits per color). Normal blits between 16 and 32 bit forms truncates or pads the colors automatically to provide the best preservation of colors. Colors can be remapped at the same depth. Sometimes a Form is in terms of colors that are not the standard colors for this depth, for example in a GIF file. Convert the Form to a MaskedForm and send colorMap: the list of colors that the picture is in terms of. MaskedForm will use the colorMap when copying to the display or another Form. (Note also that a Form can be copied to itself, and transformed in the process, if a non-nil colorMap is supplied.)! !BitBlt methodsFor: '*FreeType-addition' stamp: 'tween 8/1/2006 17:52'! combinationRule "Answer the receiver's combinationRule" ^combinationRule! ! !BitBlt methodsFor: '*FreeType-addition' stamp: 'tween 7/28/2006 17:54'! copyBitsColor: argbColorSmallInteger alpha: argbAlphaSmallInteger gammaTable: gammaByteArray ungammaTable: ungammaByteArray "This entry point to BitBlt supplies an extra argument to specify the fore color argb value for operation 41. This is split into an alpha value and an rgb value, so that both can be passed as smallIntegers to the primitive. rgbColorInteger must be a smallInteger between 0 and 16rFFFFFF. alpha must be a smallInteger between 0 and 16rFF." "Check for compressed source, destination or halftone forms" ((sourceForm isForm) and: [sourceForm unhibernate]) ifTrue: [^ self copyBitsColor: argbColorSmallInteger alpha: argbAlphaSmallInteger gammaTable: gammaByteArray ungammaTable: ungammaByteArray]. ((destForm isForm) and: [destForm unhibernate ]) ifTrue: [^ self copyBitsColor: argbColorSmallInteger alpha: argbAlphaSmallInteger gammaTable: gammaByteArray ungammaTable: ungammaByteArray]. ((halftoneForm isForm) and: [halftoneForm unhibernate]) ifTrue: [^ self copyBitsColor: argbColorSmallInteger alpha: argbAlphaSmallInteger gammaTable: gammaByteArray ungammaTable: ungammaByteArray]. self primitiveFailed "Later do nicer error recovery -- share copyBits recovery"! ! !BitBlt methodsFor: '*FreeType-addition' stamp: 'tween 4/4/2007 20:59'! installFreeTypeFont: aFreeTypeFont foregroundColor: foregroundColor backgroundColor: backgroundColor "Set up the parameters. Since the glyphs in a TTCFont is 32bit depth form, it tries to use rule=34 to get better AA result if possible." (FreeTypeSettings current bitBltSubPixelAvailable and: [destForm depth >= 8]) ifTrue:[ self combinationRule: 41. destForm depth = 8 ifTrue:[self colorMap: (self cachedFontColormapFrom: 32 to: destForm depth)] ifFalse:[self colorMap: nil]] ifFalse:[ "use combination rule 34 when rule 41 is not available in the BitBlt plugin, or the destination form depth <= 8" destForm depth <= 8 ifTrue: [ self colorMap: (self cachedFontColormapFrom: 32 to: destForm depth). self combinationRule: Form paint.] ifFalse: [ self colorMap: nil. self combinationRule: 34]]. halftoneForm := nil. sourceX := sourceY := 0. height := aFreeTypeFont height. ! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! clipBy: aRectangle | aPoint right bottom | right := clipX + clipWidth. bottom := clipY + clipHeight. aPoint := aRectangle origin. aPoint x > clipX ifTrue: [ clipX := aPoint x ]. aPoint y > clipY ifTrue: [ clipY := aPoint y ]. aPoint := aRectangle corner. aPoint x < right ifTrue: [ right := aPoint x ]. aPoint y < bottom ifTrue: [ bottom := aPoint y ]. clipWidth := right - clipX. clipHeight := bottom - clipY. clipWidth < 0 ifTrue: [ clipWidth := 0 ]. clipHeight < 0 ifTrue: [ clipHeight := 0 ]! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! clipByX1: x1 y1: y1 x2: x2 y2: y2 | right bottom | right := clipX + clipWidth. bottom := clipY + clipHeight. x1 > clipX ifTrue: [ clipX := x1 ]. y1 > clipY ifTrue: [ clipY := y1 ]. x2 < right ifTrue: [ right := x2 ]. y2 < bottom ifTrue: [ bottom := y2 ]. clipWidth := right - clipX. clipHeight := bottom - clipY. clipWidth < 0 ifTrue: [ clipWidth := 0 ]. clipHeight < 0 ifTrue: [ clipHeight := 0 ]! ! !BitBlt methodsFor: 'accessing' stamp: 'ar 5/17/2000 18:58'! clipHeight ^clipHeight! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! clipHeight: anInteger "Set the receiver's clipping area height to be the argument, anInteger." clipHeight := anInteger! ! !BitBlt methodsFor: 'accessing'! clipRect "Answer the receiver's clipping area rectangle." ^clipX @ clipY extent: clipWidth @ clipHeight! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! clipRect: aRectangle "Set the receiver's clipping area rectangle to be the argument, aRectangle." clipX := aRectangle left truncated. clipY := aRectangle top truncated. clipWidth := aRectangle right truncated - clipX. clipHeight := aRectangle bottom truncated - clipY! ! !BitBlt methodsFor: 'accessing' stamp: 'ar 5/17/2000 18:58'! clipWidth ^clipWidth! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! clipWidth: anInteger "Set the receiver's clipping area width to be the argument, anInteger." clipWidth := anInteger! ! !BitBlt methodsFor: 'accessing' stamp: 'ar 5/17/2000 18:58'! clipX ^clipX! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! clipX: anInteger "Set the receiver's clipping area top left x coordinate to be the argument, anInteger." clipX := anInteger! ! !BitBlt methodsFor: 'accessing' stamp: 'ar 5/17/2000 18:58'! clipY ^clipY! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! clipY: anInteger "Set the receiver's clipping area top left y coordinate to be the argument, anInteger." clipY := anInteger! ! !BitBlt methodsFor: 'accessing' stamp: 'tk 8/15/2001 10:56'! color "Return the current fill color as a Color. Gives the wrong answer if the halftoneForm is a complex pattern of more than one word." halftoneForm ifNil: [^ Color black]. ^ Color colorFromPixelValue: halftoneForm first depth: destForm depth! ! !BitBlt methodsFor: 'accessing'! colorMap ^ colorMap! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! colorMap: map "See last part of BitBlt comment. 6/18/96 tk" colorMap := map! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! combinationRule: anInteger "Set the receiver's combination rule to be the argument, anInteger, a number in the range 0-15." combinationRule := anInteger! ! !BitBlt methodsFor: 'accessing'! destForm ^ destForm! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! destOrigin: aPoint "Set the receiver's destination top left coordinates to be those of the argument, aPoint." destX := aPoint x. destY := aPoint y! ! !BitBlt methodsFor: 'accessing' stamp: 'tk 3/19/97'! destRect "The rectangle we are about to blit to or just blitted to. " ^ destX @ destY extent: width @ height! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! destRect: aRectangle "Set the receiver's destination form top left coordinates to be the origin of the argument, aRectangle, and set the width and height of the receiver's destination form to be the width and height of aRectangle." destX := aRectangle left. destY := aRectangle top. width := aRectangle width. height := aRectangle height! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! destX: anInteger "Set the top left x coordinate of the receiver's destination form to be the argument, anInteger." destX := anInteger! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! destX: x destY: y width: w height: h "Combined init message saves 3 sends from DisplayScanner" destX := x. destY := y. width := w. height := h! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! destY: anInteger "Set the top left y coordinate of the receiver's destination form to be the argument, anInteger." destY := anInteger! ! !BitBlt methodsFor: 'accessing'! fillColor ^ halftoneForm! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! fillColor: aColorOrPattern "The destForm will be filled with this color or pattern of colors. May be an old Color, a new type Color, a Bitmap (see BitBlt comment), a Pattern, or a Form. 6/18/96 tk" aColorOrPattern == nil ifTrue: [ halftoneForm := nil. ^ self ]. destForm == nil ifTrue: [ self error: 'Must set destForm first' ]. halftoneForm := destForm bitPatternFor: aColorOrPattern! ! !BitBlt methodsFor: 'accessing' stamp: 'tbn 9/14/2004 20:38'! halftoneForm "Returns the receivers half tone form. See class commment." ^halftoneForm! ! !BitBlt methodsFor: 'accessing' stamp: 'tbn 9/14/2004 20:39'! halftoneForm: aBitmap "Sets the receivers half tone form. See class commment." halftoneForm := aBitmap ! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! height: anInteger "Set the receiver's destination form height to be the argument, anInteger." height := anInteger! ! !BitBlt methodsFor: 'accessing'! sourceForm ^ sourceForm! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! sourceForm: aForm "Set the receiver's source form to be the argument, aForm." sourceForm := aForm! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! sourceOrigin: aPoint "Set the receiver's source form coordinates to be those of the argument, aPoint." sourceX := aPoint x. sourceY := aPoint y! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! sourceRect: aRectangle "Set the receiver's source form top left x and y, width and height to be the top left coordinate and extent of the argument, aRectangle." sourceX := aRectangle left. sourceY := aRectangle top. width := aRectangle width. height := aRectangle height! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! sourceX: anInteger "Set the receiver's source form top left x to be the argument, anInteger." sourceX := anInteger! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! sourceY: anInteger "Set the receiver's source form top left y to be the argument, anInteger." sourceY := anInteger! ! !BitBlt methodsFor: 'accessing' stamp: 'ar 5/25/2000 19:39'! tallyMap "Return the map used for tallying pixels" ^colorMap! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! tallyMap: aBitmap "Install the map used for tallying pixels" colorMap := aBitmap! ! !BitBlt methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! width: anInteger "Set the receiver's destination form width to be the argument, anInteger." width := anInteger! ! !BitBlt methodsFor: 'copying' stamp: 'jmv 8/4/2009 16:29'! basicDisplayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta destY := aPoint y. destX := aPoint x. "the following are not really needed, but theBitBlt primitive will fail if not set" sourceX ifNil: [sourceX := 100]. width ifNil: [width := 100]. self primDisplayString: aString from: startIndex to: stopIndex map: font characterToGlyphMap xTable: font xTable kern: kernDelta. ^ destX@destY. ! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! copy: destRectangle from: sourcePt in: srcForm | destOrigin | sourceForm := srcForm. halftoneForm := nil. combinationRule := 3. "store" destOrigin := destRectangle origin. destX := destOrigin x. destY := destOrigin y. sourceX := sourcePt x. sourceY := sourcePt y. width := destRectangle width. height := destRectangle height. self copyBits! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! copy: destRectangle from: sourcePt in: srcForm fillColor: hf rule: rule "Specify a Color to fill, not a Form. 6/18/96 tk" | destOrigin | sourceForm := srcForm. self fillColor: hf. "sets halftoneForm" combinationRule := rule. destOrigin := destRectangle origin. destX := destOrigin x. destY := destOrigin y. sourceX := sourcePt x. sourceY := sourcePt y. width := destRectangle width. height := destRectangle height. srcForm == nil ifFalse: [ colorMap := srcForm colormapIfNeededFor: destForm ]. ^ self copyBits! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! copy: destRectangle from: sourcePt in: srcForm halftoneForm: hf rule: rule | destOrigin | sourceForm := srcForm. self fillColor: hf. "sets halftoneForm" combinationRule := rule. destOrigin := destRectangle origin. destX := destOrigin x. destY := destOrigin y. sourceX := sourcePt x. sourceY := sourcePt y. width := destRectangle width. height := destRectangle height. self copyBits! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! copyBits "Primitive. Perform the movement of bits from the source form to the destination form. Fail if any variables are not of the right type (Integer, Float, or Form) or if the combination rule is not implemented. In addition to the original 16 combination rules, this BitBlt supports 16 fail (to simulate paint) 17 fail (to simulate mask) 18 sourceWord + destinationWord 19 sourceWord - destinationWord 20 rgbAdd: sourceWord with: destinationWord 21 rgbSub: sourceWord with: destinationWord 22 rgbDiff: sourceWord with: destinationWord 23 tallyIntoMap: destinationWord 24 alphaBlend: sourceWord with: destinationWord 25 pixPaint: sourceWord with: destinationWord 26 pixMask: sourceWord with: destinationWord 27 rgbMax: sourceWord with: destinationWord 28 rgbMin: sourceWord with: destinationWord 29 rgbMin: sourceWord bitInvert32 with: destinationWord " "Check for compressed source, destination or halftone forms" (combinationRule >= 30 and: [ combinationRule <= 31 ]) ifTrue: [ "No alpha specified -- re-run with alpha = 1.0" ^ self copyBitsTranslucent: 255 ]. (sourceForm isForm and: [ sourceForm unhibernate ]) ifTrue: [ ^ self copyBits ]. (destForm isForm and: [ destForm unhibernate ]) ifTrue: [ ^ self copyBits ]. (halftoneForm isForm and: [ halftoneForm unhibernate ]) ifTrue: [ ^ self copyBits ]. "Check for unimplmented rules" combinationRule = Form oldPaint ifTrue: [ ^ self paintBits ]. combinationRule = Form oldErase1bitShape ifTrue: [ ^ self eraseBits ]. "Check if BitBlt doesn't support full color maps" (colorMap notNil and: [ colorMap isColormap ]) ifTrue: [ colorMap := colorMap colors. ^ self copyBits ]. "Check if clipping gots us way out of range" self clipRange ifTrue: [ self roundVariables. ^ self copyBitsAgain ]. self error: 'Bad BitBlt arg (Fraction?); proceed to convert.'. "Convert all numeric parameters to integers and try again." self roundVariables. ^ self copyBitsAgain! ! !BitBlt methodsFor: 'copying' stamp: 'nk 4/17/2004 19:42'! copyBitsTranslucent: factor "This entry point to BitBlt supplies an extra argument to specify translucency for operations 30 and 31. The argument must be an integer between 0 and 255." "Check for compressed source, destination or halftone forms" ((sourceForm isForm) and: [sourceForm unhibernate]) ifTrue: [^ self copyBitsTranslucent: factor]. ((destForm isForm) and: [destForm unhibernate]) ifTrue: [^ self copyBitsTranslucent: factor]. ((halftoneForm isForm) and: [halftoneForm unhibernate]) ifTrue: [^ self copyBitsTranslucent: factor]. self primitiveFailed "Later do nicer error recovery -- share copyBits recovery"! ! !BitBlt methodsFor: 'copying' stamp: 'ar 5/14/2001 23:32'! copyForm: srcForm to: destPt rule: rule ^ self copyForm: srcForm to: destPt rule: rule colorMap: (srcForm colormapIfNeededFor: destForm)! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! copyForm: srcForm to: destPt rule: rule color: color sourceForm := srcForm. halftoneForm := color. combinationRule := rule. destX := destPt x + sourceForm offset x. destY := destPt y + sourceForm offset y. sourceX := 0. sourceY := 0. width := sourceForm width. height := sourceForm height. self copyBits! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! copyForm: srcForm to: destPt rule: rule colorMap: map sourceForm := srcForm. halftoneForm := nil. combinationRule := rule. destX := destPt x + sourceForm offset x. destY := destPt y + sourceForm offset y. sourceX := 0. sourceY := 0. width := sourceForm width. height := sourceForm height. colorMap := map. self copyBits! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! copyForm: srcForm to: destPt rule: rule fillColor: color sourceForm := srcForm. self fillColor: color. "sets halftoneForm" combinationRule := rule. destX := destPt x + sourceForm offset x. destY := destPt y + sourceForm offset y. sourceX := 0. sourceY := 0. width := sourceForm width. height := sourceForm height. self copyBits! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! copyFrom: sourceRectangle in: srcForm to: destPt | sourceOrigin | sourceForm := srcForm. halftoneForm := nil. combinationRule := 3. "store" destX := destPt x. destY := destPt y. sourceOrigin := sourceRectangle origin. sourceX := sourceOrigin x. sourceY := sourceOrigin y. width := sourceRectangle width. height := sourceRectangle height. colorMap := srcForm colormapIfNeededFor: destForm. self copyBits! ! !BitBlt methodsFor: 'copying' stamp: 'JuanVuletich 8/22/2009 23:39'! displayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta "If required, do a second pass with new rule and colorMap. This happens when #installStrikeFont:foregroundColor:backgroundColor: sets rule 37 (rgbMul). the desired effect is to do two bitblt calls. The first one is with rule 37 and special colormap. The second one is rule 34, with a colormap for applying the requested foreground color. This two together do component alpha blending, i.e. alpha blend red, green and blue separatedly. This is needed for arbitrary color over abitrary background text with subpixel AA." | answer prevRule secondPassMap | "If combinationRule is rgbMul, we might need the special two-pass technique for component alpha blending. If not, do it simply" combinationRule = 37 "rgbMul" ifFalse: [ ^self basicDisplayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta ]. "We need to do a second pass. The colormap set is for use in the second pass." secondPassMap := colorMap. colorMap := sourceForm depth ~= destForm depth ifTrue: [ self cachedFontColormapFrom: sourceForm depth to: destForm depth ]. answer := self basicDisplayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta. colorMap := secondPassMap. secondPassMap ifNotNil: [ prevRule := combinationRule. combinationRule := 20. "rgbAdd" self basicDisplayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta. combinationRule := prevRule ]. ^answer! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! fill: destRect fillColor: grayForm rule: rule "Fill with a Color, not a Form. 6/18/96 tk" sourceForm := nil. self fillColor: grayForm. "sets halftoneForm" combinationRule := rule. destX := destRect left. destY := destRect top. sourceX := 0. sourceY := 0. width := destRect width. height := destRect height. self copyBits! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! pixelAt: aPoint "Assumes this BitBlt has been set up specially (see the init message, BitBlt bitPeekerFromForm:. Returns the pixel at aPoint." sourceX := aPoint x. sourceY := aPoint y. destForm unhibernate. "before poking" destForm bits at: 1 put: 0. "Just to be sure" self copyBits. ^ destForm bits at: 1! ! !BitBlt methodsFor: 'copying' stamp: 'lr 7/4/2009 10:42'! pixelAt: aPoint put: pixelValue "Assumes this BitBlt has been set up specially (see the init message, BitBlt bitPokerToForm:. Overwrites the pixel at aPoint." destX := aPoint x. destY := aPoint y. sourceForm unhibernate. "before poking" sourceForm bits at: 1 put: pixelValue. self copyBits " | bb | bb _ (BitBlt bitPokerToForm: Display). [Sensor anyButtonPressed] whileFalse: [bb pixelAt: Sensor cursorPoint put: 55] "! ! !BitBlt methodsFor: 'line drawing'! drawFrom: startPoint to: stopPoint ^ self drawFrom: startPoint to: stopPoint withFirstPoint: true! ! !BitBlt methodsFor: 'line drawing' stamp: 'lr 7/4/2009 10:42'! drawFrom: startPoint to: stopPoint withFirstPoint: drawFirstPoint "Draw a line whose end points are startPoint and stopPoint. The line is formed by repeatedly calling copyBits at every point along the line. If drawFirstPoint is false, then omit the first point so as not to overstrike at line junctions." "Always draw down, or at least left-to-right" | offset point1 point2 forwards | forwards := (startPoint y = stopPoint y and: [ startPoint x < stopPoint x ]) or: [ startPoint y < stopPoint y ]. forwards ifTrue: [ point1 := startPoint. point2 := stopPoint ] ifFalse: [ point1 := stopPoint. point2 := startPoint ]. sourceForm == nil ifTrue: [ destX := point1 x. destY := point1 y ] ifFalse: [ width := sourceForm width. height := sourceForm height. offset := sourceForm offset. destX := (point1 x + offset x) rounded. destY := (point1 y + offset y) rounded ]. "Note that if not forwards, then the first point is the last and vice versa. We agree to always paint stopPoint, and to optionally paint startPoint." (drawFirstPoint or: [ forwards == false "ie this is stopPoint" ]) ifTrue: [ self copyBits ]. self drawLoopX: (point2 x - point1 x) rounded Y: (point2 y - point1 y) rounded. (drawFirstPoint or: [ "ie this is stopPoint" forwards ]) ifTrue: [ self copyBits ]! ! !BitBlt methodsFor: 'line drawing' stamp: 'lr 7/4/2009 10:42'! drawLoopX: xDelta Y: yDelta "Primitive. Implements the Bresenham plotting algorithm (IBM Systems Journal, Vol. 4 No. 1, 1965). It chooses a principal direction, and maintains a potential, P. When P's sign changes, it is time to move in the minor direction as well. This particular version does not write the first and last points, so that these can be called for as needed in client code. Optional. See Object documentation whatIsAPrimitive." | dx dy px py P | dx := xDelta sign. dy := yDelta sign. px := yDelta abs. py := xDelta abs. "self copyBits." py > px ifTrue: [ "more horizontal" P := py // 2. 1 to: py do: [ :i | destX := destX + dx. (P := P - px) < 0 ifTrue: [ destY := destY + dy. P := P + py ]. i < py ifTrue: [ self copyBits ] ] ] ifFalse: [ "more vertical" P := px // 2. 1 to: px do: [ :i | destY := destY + dy. (P := P - py) < 0 ifTrue: [ destX := destX + dx. P := P + px ]. i < px ifTrue: [ self copyBits ] ] ]! ! !BitBlt methodsFor: 'text display' stamp: 'ar 10/24/2005 21:49'! displayString: aString from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY font: aFont "Double dispatch into the font. This method is present so that other-than-bitblt entities can be used by CharacterScanner and friends to display text." ^ aFont displayString: aString on: self from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY! ! !BitBlt methodsFor: 'text display' stamp: 'ar 10/25/2005 01:12'! displayString: aString from: startIndex to: stopIndex at: aPoint kern: kernDelta font: aFont "Double dispatch into the font. This method is present so that other-than-bitblt entities can be used by CharacterScanner and friends to display text." ^ aFont displayString: aString on: self from: startIndex to: stopIndex at: aPoint kern: kernDelta! ! !BitBlt methodsFor: 'text display' stamp: 'ar 10/24/2005 21:48'! installFont: aFont foregroundColor: foregroundColor backgroundColor: backgroundColor "Double dispatch into the font. This method is present so that other-than-bitblt entities can be used by CharacterScanner and friends to display text." ^aFont installOn: self foregroundColor: foregroundColor backgroundColor: backgroundColor! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! cachedFontColormapFrom: sourceDepth to: destDepth "Modified from computeColormapFrom:to:." | srcIndex map | CachedFontColorMaps class == Array ifFalse: [ CachedFontColorMaps := (1 to: 9) collect: [ :i | Array new: 32 ] ]. srcIndex := sourceDepth. sourceDepth > 8 ifTrue: [ srcIndex := 9 ]. (map := (CachedFontColorMaps at: srcIndex) at: destDepth) ~~ nil ifTrue: [ ^ map ]. map := (Color cachedColormapFrom: sourceDepth to: destDepth) copy. (CachedFontColorMaps at: srcIndex) at: destDepth put: map. ^ map! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! clipRange "clip and adjust source origin and extent appropriately" "first in x" "fill in the lazy state if needed" | sx sy dx dy bbW bbH | destX ifNil: [ destX := 0 ]. destY ifNil: [ destY := 0 ]. width ifNil: [ width := destForm width ]. height ifNil: [ height := destForm height ]. sourceX ifNil: [ sourceX := 0 ]. sourceY ifNil: [ sourceY := 0 ]. clipX ifNil: [ clipX := 0 ]. clipY ifNil: [ clipY := 0 ]. clipWidth ifNil: [ clipWidth := destForm width ]. clipHeight ifNil: [ clipHeight := destForm height ]. destX >= clipX ifTrue: [ sx := sourceX. dx := destX. bbW := width ] ifFalse: [ sx := sourceX + (clipX - destX). bbW := width - (clipX - destX). dx := clipX ]. dx + bbW > (clipX + clipWidth) ifTrue: [ bbW := bbW - (dx + bbW - (clipX + clipWidth)) ]. "then in y" destY >= clipY ifTrue: [ sy := sourceY. dy := destY. bbH := height ] ifFalse: [ sy := sourceY + clipY - destY. bbH := height - (clipY - destY). dy := clipY ]. dy + bbH > (clipY + clipHeight) ifTrue: [ bbH := bbH - (dy + bbH - (clipY + clipHeight)) ]. sourceForm ifNotNil: [ sx < 0 ifTrue: [ dx := dx - sx. bbW := bbW + sx. sx := 0 ]. sx + bbW > sourceForm width ifTrue: [ bbW := bbW - (sx + bbW - sourceForm width) ]. sy < 0 ifTrue: [ dy := dy - sy. bbH := bbH + sy. sy := 0 ]. sy + bbH > sourceForm height ifTrue: [ bbH := bbH - (sy + bbH - sourceForm height) ] ]. (bbW <= 0 or: [ bbH <= 0 ]) ifTrue: [ sourceX := sourceY := destX := destY := clipX := clipY := width := height := 0. ^ true ]. (sx = sourceX and: [ sy = sourceY and: [ dx = destX and: [ dy = destY and: [ bbW = width and: [ bbH = height ] ] ] ] ]) ifTrue: [ ^ false ]. sourceX := sx. sourceY := sy. destX := dx. destY := dy. width := bbW. height := bbH. ^ true! ! !BitBlt methodsFor: 'private' stamp: 'StephaneDucasse 10/17/2009 17:15'! colorConvertingMap: targetColor from: sourceDepth to: destDepth keepSubPixelAA: keepSubPix | srcIndex map mapsForSource mapsForSourceAndDest | ColorConvertingMaps class == Array ifFalse: [ ColorConvertingMaps := (1 to: 10) collect: [ :i | Array new: 32 ] ]. srcIndex := sourceDepth. sourceDepth > 8 ifTrue: [ srcIndex := keepSubPix ifTrue: [ 9 ] ifFalse: [ 10 ] ]. mapsForSource := ColorConvertingMaps at: srcIndex. (mapsForSourceAndDest := mapsForSource at: destDepth) isNil ifTrue: [ mapsForSourceAndDest := mapsForSource at: destDepth put: Dictionary new ]. map := mapsForSourceAndDest at: targetColor ifAbsentPut: [ Color computeColorConvertingMap: targetColor from: sourceDepth to: destDepth keepSubPixelAA: keepSubPix ]. ^ map! ! !BitBlt methodsFor: 'private' stamp: 'ar 2/2/2001 15:09'! copyBitsAgain "Primitive. See BitBlt|copyBits, also a Primitive. Essential. See Object documentation whatIsAPrimitive." self primitiveFailed! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! copyBitsFrom: x0 to: x1 at: y destX := x0. destY := y. sourceX := x0. width := x1 - x0. self copyBits! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! eraseBits "Perform the erase operation, which puts 0's in the destination wherever the source (which is assumed to be just 1 bit deep) has a 1. This requires the colorMap to be set in order to AND all 1's into the destFrom pixels regardless of their size." | oldMask oldMap | oldMask := halftoneForm. halftoneForm := nil. oldMap := colorMap. self colorMap: (Bitmap with: 0 with: 4294967295). combinationRule := Form erase. self copyBits. "Erase the dest wherever the source is 1" halftoneForm := oldMask. "already converted to a Bitmap" colorMap := oldMap! ! !BitBlt methodsFor: 'private' stamp: 'ar 5/26/2000 16:38'! getPluginName "Private. Return the name of the plugin representing BitBlt. Used for dynamically switching between different BB representations only." ^'BitBltPlugin'! ! !BitBlt methodsFor: 'private' stamp: 'jmv 9/7/2009 09:27'! installStrikeFont: aStrikeFont foregroundColor: foregroundColor backgroundColor: backgroundColor | lastSourceDepth targetColor | sourceForm ifNotNil:[lastSourceDepth := sourceForm depth]. sourceForm := aStrikeFont glyphs. "Ignore any halftone pattern since we use a color map approach here" halftoneForm := nil. sourceY := 0. height := aStrikeFont height. sourceForm depth = 1 ifTrue: [ self combinationRule: Form paint. (colorMap notNil and:[lastSourceDepth = sourceForm depth]) ifFalse: [ "Set up color map for a different source depth (color font)" "Uses caching for reasonable efficiency" colorMap := self cachedFontColormapFrom: sourceForm depth to: destForm depth. colorMap at: 1 put: (destForm pixelValueFor: backgroundColor)]. colorMap at: 2 put: (destForm pixelValueFor: foregroundColor). ] ifFalse: [ (Preferences subPixelRenderFonts and: [ foregroundColor = Color black or: [ Preferences subPixelRenderColorFonts ]]) ifTrue: [ destForm depth > 8 ifTrue: [ "rgbMul is equivalent to component alpha blend if text is black (only faster, hehe)" self combinationRule: 37. "RGBMul" colorMap := (destForm depth = 32 or: [ (foregroundColor = Color black) not ]) ifTrue: [ "rgbMul / rgbAdd IS component alpha blend for any color of text (neat trick, eh!!)" "This colorMap is to be used on the second pass with rule 20 (rgbAdd) See #displayString:from:to:at:strikeFont:kern:" "Note: In 32bpp we always need the second pass, as the source could have transparent pixels, and we need to add to the alpha channel" self colorConvertingMap: foregroundColor from: sourceForm depth to: destForm depth keepSubPixelAA: true]] ifFalse: [ self combinationRule: 25. "Paint" targetColor := foregroundColor = Color black ifFalse: [ foregroundColor ]. colorMap := self colorConvertingMap: targetColor from: sourceForm depth to: destForm depth keepSubPixelAA: true] ] ifFalse: [ "Do not use rule 34 for 16bpp display. TTCFont uses it, but it builds a glyphs cache for each color used!!" self combinationRule: (destForm depth = 32 ifTrue: [34 "alphaBlendScaled"] ifFalse: [25 "Paint"]). colorMap := self colorConvertingMap: foregroundColor from: sourceForm depth to: destForm depth keepSubPixelAA: false ] ].! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! installTTCFont: aTTCFont foregroundColor: foregroundColor backgroundColor: backgroundColor "Set up the parameters. Since the glyphs in a TTCFont is 32bit depth form, it tries to use rule=34 to get better AA result if possible." aTTCFont depth = 32 ifTrue: [ destForm depth <= 8 ifTrue: [ self colorMap: (self cachedFontColormapFrom: aTTCFont depth to: destForm depth). self combinationRule: Form paint ] ifFalse: [ self colorMap: nil. self combinationRule: 34 ]. halftoneForm := nil. sourceY := 0. height := aTTCFont height ]! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! paintBits "Perform the paint operation, which requires two calls to BitBlt." | color oldMap saveRule | sourceForm depth = 1 ifFalse: [ ^ self halt: 'paint operation is only defined for 1-bit deep sourceForms' ]. saveRule := combinationRule. color := halftoneForm. halftoneForm := nil. oldMap := colorMap. "Map 1's to ALL ones, not just one" self colorMap: (Bitmap with: 0 with: 4294967295). combinationRule := Form erase. self copyBits. "Erase the dest wherever the source is 1" halftoneForm := color. combinationRule := Form under. self copyBits. "then OR, with whatever color, into the hole" colorMap := oldMap. combinationRule := saveRule " | dot | dot _ Form dotOfSize: 32. ((BitBlt destForm: Display sourceForm: dot fillColor: Color lightGray combinationRule: Form paint destOrigin: Sensor cursorPoint sourceOrigin: 0@0 extent: dot extent clipRect: Display boundingBox) colorMap: (Bitmap with: 0 with: 16rFFFFFFFF)) copyBits"! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! primDisplayString: aString from: startIndex to: stopIndex map: glyphMap xTable: xTable kern: kernDelta | ascii | startIndex to: stopIndex do: [ :charIndex | ascii := (aString at: charIndex) asciiValue. sourceX := xTable at: ascii + 1. width := (xTable at: ascii + 2) - sourceX. self copyBits. destX := destX + width + kernDelta ]! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! roundVariables | maxVal minVal | maxVal := SmallInteger maxVal. minVal := SmallInteger minVal. destX := destX asInteger min: maxVal max: minVal. destY := destY asInteger min: maxVal max: minVal. width := width asInteger min: maxVal max: minVal. height := height asInteger min: maxVal max: minVal. sourceX := sourceX asInteger min: maxVal max: minVal. sourceY := sourceY asInteger min: maxVal max: minVal. clipX := clipX asInteger min: maxVal max: minVal. clipY := clipY asInteger min: maxVal max: minVal. clipWidth := clipWidth asInteger min: maxVal max: minVal. clipHeight := clipHeight asInteger min: maxVal max: minVal! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setDestForm: df | bb | bb := df boundingBox. destForm := df. clipX := bb left. clipY := bb top. clipWidth := bb width. clipHeight := bb height! ! !BitBlt methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setDestForm: df sourceForm: sf fillColor: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: sourceOrigin extent: extent clipRect: clipRect | aPoint | destForm := df. sourceForm := sf. self fillColor: hf. "sets halftoneForm" combinationRule := cr. destX := destOrigin x. destY := destOrigin y. sourceX := sourceOrigin x. sourceY := sourceOrigin y. width := extent x. height := extent y. aPoint := clipRect origin. clipX := aPoint x. clipY := aPoint y. aPoint := clipRect corner. clipWidth := aPoint x - clipX. clipHeight := aPoint y - clipY. sourceForm == nil ifFalse: [ colorMap := sourceForm colormapIfNeededFor: destForm ]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BitBlt class instanceVariableNames: ''! !BitBlt class methodsFor: 'benchmarks' stamp: 'PeterHugossonMiller 9/3/2009 00:12'! benchDiffsFrom: before to: afterwards "Given two outputs of BitBlt>>benchmark show the relative improvements." | old new log oldLine newLine oldVal newVal improvement | log := String new writeStream. old := before readStream. new := afterwards readStream. [ old atEnd or: [ new atEnd ] ] whileFalse: [ oldLine := old upTo: Character cr. newLine := new upTo: Character cr. (oldLine includes: Character tab) ifTrue: [ oldLine := oldLine readStream. newLine := newLine readStream. Transcript cr; show: (oldLine upTo: Character tab); tab. log cr; nextPutAll: (newLine upTo: Character tab); tab. [ oldLine skipSeparators. newLine skipSeparators. oldLine atEnd ] whileFalse: [ oldVal := Integer readFrom: oldLine. newVal := Integer readFrom: newLine. improvement := oldVal asFloat / newVal asFloat roundTo: 0.01. Transcript show: improvement printString; tab; tab. log print: improvement; tab; tab ] ] ifFalse: [ Transcript cr; show: oldLine. log cr; nextPutAll: oldLine ] ]. ^ log contents! ! !BitBlt class methodsFor: 'benchmarks' stamp: 'PeterHugossonMiller 9/3/2009 00:13'! benchmark "BitBlt benchmark" "Run a benchmark on different combinations rules, source/destination depths and BitBlt modes. Note: This benchmark doesn't give you any 'absolute' value - it is intended only for benchmarking improvements in the bitblt code and nothing else. Attention: *this*may*take*a*while*" | bb source dest destRect log t | log := String new writeStream. destRect := 0 @ 0 extent: 600 @ 600. "Form paint/Form over - the most common rules" #(25 3 ) do: [ :rule | Transcript cr; show: '---- Combination rule: ' , rule printString , ' ----'. log cr; nextPutAll: '---- Combination rule: ' , rule printString , ' ----'. #(1 2 4 8 16 32 ) do: [ :destDepth | dest := nil. dest := Form extent: destRect extent depth: destDepth. Transcript cr. log cr. #(1 2 4 8 16 32 ) do: [ :sourceDepth | Transcript cr; show: sourceDepth printString , ' => ' , destDepth printString. log cr; nextPutAll: sourceDepth printString , ' => ' , destDepth printString. source := nil. bb := nil. source := Form extent: destRect extent depth: sourceDepth. source getCanvas fillOval: dest boundingBox color: Color yellow borderWidth: 30 borderColor: Color black. bb := WarpBlt toForm: dest. bb sourceForm: source. bb sourceRect: source boundingBox. bb destRect: dest boundingBox. bb colorMap: (source colormapIfNeededFor: dest). bb combinationRule: rule. "Measure speed of copyBits" t := Time millisecondsToRun: [ bb copyBits ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString. bb sourceForm: source destRect: source boundingBox. "Measure speed of 1x1 warpBits" bb cellSize: 1. t := Time millisecondsToRun: [ bb warpBits ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString. "Measure speed of 2x2 warpBits" bb cellSize: 2. t := Time millisecondsToRun: [ bb warpBits ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString. "Measure speed of 3x3 warpBits" bb cellSize: 3. t := Time millisecondsToRun: [ bb warpBits ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString ] ] ]. ^ log contents! ! !BitBlt class methodsFor: 'benchmarks' stamp: 'PeterHugossonMiller 9/3/2009 00:14'! benchmark2 "BitBlt benchmark" "Run a benchmark on different combinations rules, source/destination depths and BitBlt modes. Note: This benchmark doesn't give you any 'absolute' value - it is intended only for benchmarking improvements in the bitblt code and nothing else. Attention: *this*may*take*a*while*" | bb source dest destRect log t | log := String new writeStream. destRect := 0 @ 0 extent: 600 @ 600. "Form paint/Form over - the most common rules" #(25 3 ) do: [ :rule | Transcript cr; show: '---- Combination rule: ' , rule printString , ' ----'. log cr; nextPutAll: '---- Combination rule: ' , rule printString , ' ----'. #(1 2 4 8 16 32 ) do: [ :destDepth | dest := nil. dest := Form extent: destRect extent depth: destDepth. Transcript cr. log cr. #(1 2 4 8 16 32 ) do: [ :sourceDepth | Transcript cr; show: sourceDepth printString , ' => ' , destDepth printString. log cr; nextPutAll: sourceDepth printString , ' => ' , destDepth printString. source := nil. bb := nil. source := Form extent: destRect extent depth: sourceDepth. source getCanvas fillOval: dest boundingBox color: Color yellow borderWidth: 30 borderColor: Color black. bb := WarpBlt toForm: dest. bb sourceForm: source. bb sourceRect: source boundingBox. bb destRect: dest boundingBox. bb colorMap: (source colormapIfNeededFor: dest). bb combinationRule: rule. "Measure speed of copyBits" t := Time millisecondsToRun: [ 1 to: 10 do: [ :i | bb copyBits ] ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString. bb sourceForm: source destRect: source boundingBox. "Measure speed of 1x1 warpBits" bb cellSize: 1. t := Time millisecondsToRun: [ 1 to: 4 do: [ :i | bb warpBits ] ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString. "Measure speed of 2x2 warpBits" bb cellSize: 2. t := Time millisecondsToRun: [ bb warpBits ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString. "Measure speed of 3x3 warpBits" bb cellSize: 3. t := Time millisecondsToRun: [ bb warpBits ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString ] ] ]. ^ log contents! ! !BitBlt class methodsFor: 'benchmarks' stamp: 'PeterHugossonMiller 9/3/2009 00:14'! benchmark3 "BitBlt benchmark" "Run a benchmark on different combinations rules, source/destination depths and BitBlt modes. Note: This benchmark doesn't give you any 'absolute' value - it is intended only for benchmarking improvements in the bitblt code and nothing else. Attention: *this*may*take*a*while*" | bb source dest destRect log t | log := String new writeStream. destRect := 0 @ 0 extent: 600 @ 600. "Form paint/Form over - the most common rules" #(25 3 ) do: [ :rule | Transcript cr; show: '---- Combination rule: ' , rule printString , ' ----'. log cr; nextPutAll: '---- Combination rule: ' , rule printString , ' ----'. #(1 2 4 8 16 32 ) do: [ :destDepth | dest := nil. dest := Form extent: destRect extent depth: destDepth. Transcript cr. log cr. #(1 2 4 8 16 32 ) do: [ :sourceDepth | Transcript cr; show: sourceDepth printString , ' => ' , destDepth printString. log cr; nextPutAll: sourceDepth printString , ' => ' , destDepth printString. source := nil. bb := nil. source := Form extent: destRect extent depth: sourceDepth. source getCanvas fillOval: dest boundingBox color: Color yellow borderWidth: 30 borderColor: Color black. bb := WarpBlt toForm: dest. bb sourceForm: source. bb sourceRect: source boundingBox. bb destRect: dest boundingBox. bb colorMap: (source colormapIfNeededFor: dest). bb combinationRule: rule. "Measure speed of copyBits" t := Time millisecondsToRun: [ 1 to: 10 do: [ :i | bb copyBits ] ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString. bb sourceForm: source destRect: source boundingBox. "Measure speed of 1x1 warpBits" bb cellSize: 1. t := Time millisecondsToRun: [ 1 to: 4 do: [ :i | bb warpBits ] ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString. "Measure speed of 2x2 warpBits" bb cellSize: 2. t := Time millisecondsToRun: [ bb warpBits ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString. "Measure speed of 3x3 warpBits" bb cellSize: 3. t := Time millisecondsToRun: [ bb warpBits ]. Transcript tab; show: t printString. log tab; nextPutAll: t printString ] ] ]. ^ log contents! ! !BitBlt class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! alphaBlendDemo "To run this demo, use... Display restoreAfter: [BitBlt alphaBlendDemo] Displays 10 alphas, then lets you paint. Option-Click to stop painting." "This code exhibits alpha blending in any display depth by performing the blend in an off-screen buffer with 32-bit pixels, and then copying the result back onto the screen with an appropriate color map. - tk 3/10/97" "This version uses a sliding buffer for painting that keeps pixels in 32 bits as long as they are in the buffer, so as not to lose info by converting down to display resolution and back up to 32 bits at each operation. - di 3/15/97" "compute color maps if needed" | brush buff dispToBuff buffToDisplay mapDto32 map32toD prevP p brushToBuff theta buffRect buffSize buffToBuff brushRect delta newBuffRect updateRect | Display depth <= 8 ifTrue: [ mapDto32 := Color cachedColormapFrom: Display depth to: 32. map32toD := Color cachedColormapFrom: 32 to: Display depth ]. "display 10 different alphas, across top of screen" buff := Form extent: 500 @ 50 depth: 32. dispToBuff := BitBlt toForm: buff. dispToBuff colorMap: mapDto32. dispToBuff copyFrom: (50 @ 10 extent: 500 @ 50) in: Display to: 0 @ 0. 1 to: 10 do: [ :i | dispToBuff fill: ((50 * (i - 1)) @ 0 extent: 50 @ 50) fillColor: (Color red alpha: i / 10) rule: Form blend ]. buffToDisplay := BitBlt toForm: Display. buffToDisplay colorMap: map32toD. buffToDisplay copyFrom: buff boundingBox in: buff to: 50 @ 10. "Create a brush with radially varying alpha" brush := Form extent: 30 @ 30 depth: 32. 1 to: 5 do: [ :i | brush fillShape: (Form dotOfSize: brush width * (6 - i) // 5) fillColor: (Color red alpha: 0.02 * i - 0.01) at: brush extent // 2 ]. "Now paint with the brush using alpha blending." buffSize := 100. buff := Form extent: brush extent + buffSize depth: 32. "Travelling 32-bit buffer" dispToBuff := BitBlt toForm: buff. "This is from Display to buff" dispToBuff colorMap: mapDto32. brushToBuff := BitBlt toForm: buff. "This is from brush to buff" brushToBuff sourceForm: brush; sourceOrigin: 0 @ 0. brushToBuff combinationRule: Form blend. buffToBuff := BitBlt toForm: buff. "This is for slewing the buffer" [ Sensor yellowButtonPressed ] whileFalse: [ prevP := nil. buffRect := Sensor cursorPoint - (buffSize // 2) extent: buff extent. dispToBuff copyFrom: buffRect in: Display to: 0 @ 0. [ Sensor redButtonPressed ] whileTrue: [ "Here is the painting loop" p := Sensor cursorPoint - (brush extent // 2). (prevP == nil or: [ prevP ~= p ]) ifTrue: [ prevP == nil ifTrue: [ prevP := p ]. (p dist: prevP) > buffSize ifTrue: [ "Stroke too long to fit in buffer -- clip to buffer, and next time through will do more of it" theta := (p - prevP) theta. p := (theta cos @ theta sin * buffSize asFloat + prevP) truncated ]. brushRect := p extent: brush extent. (buffRect containsRect: brushRect) ifFalse: [ "Brush is out of buffer region. Scroll the buffer, and fill vacated regions from the display" delta := brushRect amountToTranslateWithin: buffRect. buffToBuff copyFrom: buff boundingBox in: buff to: delta. newBuffRect := buffRect translateBy: delta negated. (newBuffRect areasOutside: buffRect) do: [ :r | dispToBuff copyFrom: r in: Display to: r origin - newBuffRect origin ]. buffRect := newBuffRect ]. "Interpolate from prevP to p..." brushToBuff drawFrom: prevP - buffRect origin to: p - buffRect origin withFirstPoint: false. "Update (only) the altered pixels of the destination" updateRect := (p min: prevP) corner: (p max: prevP) + brush extent. buffToDisplay copy: updateRect from: updateRect origin - buffRect origin in: buff. prevP := p ] ] ]! ! !BitBlt class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! antiAliasDemo "To run this demo, use... Display restoreAfter: [BitBlt antiAliasDemo] Goes immediately into on-screen paint mode. Option-Click to stop painting." "This code exhibits alpha blending in any display depth by performing the blend in an off-screen buffer with 32-bit pixels, and then copying the result back onto the screen with an appropriate color map. - tk 3/10/97" "This version uses a sliding buffer for painting that keeps pixels in 32 bits as long as they are in the buffer, so as not to lose info by converting down to display resolution and back up to 32 bits at each operation. - di 3/15/97" "This version also uses WarpBlt to paint into twice as large a buffer, and then use smoothing when reducing back down to the display. In fact this same routine will now work for 3x3 soothing as well. Remove the statements 'buff displayAt: 0@0' to hide the buffer. - di 3/19/97" "compute color maps if needed" | brush buff dispToBuff buffToDisplay mapDto32 map32toD prevP p brushToBuff theta buffRect buffSize buffToBuff brushRect delta newBuffRect updateRect scale p0 | Display depth <= 8 ifTrue: [ mapDto32 := Color cachedColormapFrom: Display depth to: 32. map32toD := Color cachedColormapFrom: 32 to: Display depth ]. "Create a brush with radially varying alpha" brush := Form extent: 3 @ 3 depth: 32. brush fill: brush boundingBox fillColor: (Color red alpha: 0.05). brush fill: (1 @ 1 extent: 1 @ 1) fillColor: (Color red alpha: 0.2). scale := 2. "Actual drawing happens at this magnification" "Scale brush up for painting in magnified buffer" brush := brush magnify: brush boundingBox by: scale. "Now paint with the brush using alpha blending." buffSize := 100. buff := Form extent: (brush extent + buffSize) * scale depth: 32. "Travelling 32-bit buffer" dispToBuff := (WarpBlt toForm: buff) sourceForm: Display; colorMap: mapDto32; combinationRule: Form over. "From Display to buff - magnify by 2" brushToBuff := (BitBlt toForm: buff) sourceForm: brush; sourceOrigin: 0 @ 0; combinationRule: Form blend. "From brush to buff" buffToDisplay := (WarpBlt toForm: Display) sourceForm: buff; colorMap: map32toD; cellSize: scale; combinationRule: Form over. "From buff to Display - shrink by 2" "...and use smoothing" buffToBuff := BitBlt toForm: buff. "This is for slewing the buffer" [ Sensor yellowButtonPressed ] whileFalse: [ prevP := nil. buffRect := Sensor cursorPoint - (buff extent // scale // 2) extent: buff extent // scale. p0 := buff extent // 2 - (buffRect extent // 2). dispToBuff copyQuad: buffRect innerCorners toRect: buff boundingBox. buff displayAt: 0 @ 0. "** remove to hide sliding buffer **" [ Sensor redButtonPressed ] whileTrue: [ "Here is the painting loop" p := Sensor cursorPoint - buffRect origin + p0. "p, prevP are rel to buff origin" (prevP == nil or: [ prevP ~= p ]) ifTrue: [ prevP == nil ifTrue: [ prevP := p ]. (p dist: prevP) > (buffSize - 1) ifTrue: [ "Stroke too long to fit in buffer -- clip to buffer, and next time through will do more of it" theta := (p - prevP) theta. p := (theta cos @ theta sin * (buffSize - 2) asFloat + prevP) truncated ]. brushRect := p extent: brush extent. ((buff boundingBox insetBy: scale) containsRect: brushRect) ifFalse: [ "Brush is out of buffer region. Scroll the buffer, and fill vacated regions from the display" delta := (brushRect amountToTranslateWithin: (buff boundingBox insetBy: scale)) // scale. buffToBuff copyFrom: buff boundingBox in: buff to: delta * scale. newBuffRect := buffRect translateBy: delta negated. p := p translateBy: delta * scale. prevP := prevP translateBy: delta * scale. (newBuffRect areasOutside: buffRect) do: [ :r | dispToBuff copyQuad: r innerCorners toRect: ((r origin - newBuffRect origin) * scale extent: r extent * scale) ]. buffRect := newBuffRect ]. "Interpolate from prevP to p..." brushToBuff drawFrom: prevP to: p withFirstPoint: false. buff displayAt: 0 @ 0. "** remove to hide sliding buffer **" "Update (only) the altered pixels of the destination" updateRect := (p min: prevP) corner: (p max: prevP) + brush extent. updateRect := updateRect origin // scale * scale corner: (updateRect corner + scale) // scale * scale. buffToDisplay copyQuad: updateRect innerCorners toRect: (updateRect origin // scale + buffRect origin extent: updateRect extent // scale). prevP := p ] ] ]! ! !BitBlt class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! exampleColorMap "BitBlt exampleColorMap" "This example shows what one can do with the fixed part of a color map. The color map, as setup below, rotates the bits of a pixel all the way around. Thus you'll get a (sometime strange looking ;-) animation of colors which will end up exactly the way it looked at the beginning. The example is given to make you understand that the masks and shifts can be used for a lot more than simply color converting pixels. In this example, for instance, we use only two of the four independent shifters." | cc bb | cc := ColorMap masks: { (1 << (Display depth - 1)). "mask out high bit of color component" ((1 << (Display depth - 1)) - 1). "mask all other bits" 0. 0 } shifts: { (1 - Display depth). "shift right to bottom most position" 1. "shift all other pixels one bit left" 0. 0 }. bb := BitBlt toForm: Display. bb sourceForm: Display; combinationRule: 3; colorMap: cc. 1 to: Display depth do: [ :i | bb copyBits. Display forceDisplayUpdate ]! ! !BitBlt class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! exampleOne "This tests BitBlt by displaying the result of all sixteen combination rules that BitBlt is capable of using. (Please see the comment in BitBlt for the meaning of the combination rules). This only works at Display depth of 1. (Rule 15 does not work?)" | path displayDepth | displayDepth := Display depth. Display newDepth: 1. path := Path new. 0 to: 3 do: [ :i | 0 to: 3 do: [ :j | path add: (j * 100) @ (i * 75) ] ]. Display fillWhite. path := path translateBy: 60 @ 40. 1 to: 16 do: [ :index | BitBlt exampleAt: (path at: index) rule: index - 1 fillColor: nil ]. [ Sensor anyButtonPressed ] whileFalse: [ ]. Display newDepth: displayDepth "BitBlt exampleOne"! ! !BitBlt class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! exampleTwo "This is to test painting with a gray tone. It also tests that the seaming with gray patterns is correct in the microcode. Lets you paint for a while and then automatically stops. This only works at Depth of 1." "create a small black Form source as a brush. " | f aBitBlt displayDepth | displayDepth := Display depth. Display newDepth: 1. f := Form extent: 20 @ 20. f fillBlack. "create a BitBlt which will OR gray into the display. " aBitBlt := BitBlt destForm: Display sourceForm: f fillColor: Color gray combinationRule: Form over destOrigin: Sensor cursorPoint sourceOrigin: 0 @ 0 extent: f extent clipRect: Display computeBoundingBox. "paint the gray Form on the screen for a while. " [ Sensor anyButtonPressed ] whileFalse: [ aBitBlt destOrigin: Sensor cursorPoint. aBitBlt copyBits ]. Display newDepth: displayDepth "BitBlt exampleTwo"! ! !BitBlt class methodsFor: 'instance creation' stamp: 'ar 5/28/2000 12:04'! asGrafPort "Return the GrafPort associated with the receiver" ^GrafPort! ! !BitBlt class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! bitPeekerFromForm: sourceForm "Answer an instance to be used extract individual pixels from the given Form. The destination for a 1x1 copyBits will be the low order bits of (bits at: 1)." | pixPerWord | pixPerWord := 32 // sourceForm depth. sourceForm unhibernate. ^ self destForm: (Form extent: pixPerWord @ 1 depth: sourceForm depth) sourceForm: sourceForm halftoneForm: nil combinationRule: Form over destOrigin: (pixPerWord - 1) @ 0 sourceOrigin: 0 @ 0 extent: 1 @ 1 clipRect: (0 @ 0 extent: pixPerWord @ 1)! ! !BitBlt class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! bitPokerToForm: destForm "Answer an instance to be used for valueAt: aPoint put: pixValue. The source for a 1x1 copyBits will be the low order of (bits at: 1)" | pixPerWord | pixPerWord := 32 // destForm depth. destForm unhibernate. ^ self destForm: destForm sourceForm: (Form extent: pixPerWord @ 1 depth: destForm depth) halftoneForm: nil combinationRule: Form over destOrigin: 0 @ 0 sourceOrigin: (pixPerWord - 1) @ 0 extent: 1 @ 1 clipRect: (0 @ 0 extent: destForm extent)! ! !BitBlt class methodsFor: 'instance creation' stamp: 'ar 5/28/2000 12:00'! current "Return the class currently to be used for BitBlt" ^Display defaultBitBltClass! ! !BitBlt class methodsFor: 'instance creation'! destForm: df sourceForm: sf fillColor: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: sourceOrigin extent: extent clipRect: clipRect "Answer an instance of me with values set according to the arguments." ^ self new setDestForm: df sourceForm: sf fillColor: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: sourceOrigin extent: extent clipRect: clipRect! ! !BitBlt class methodsFor: 'instance creation'! destForm: df sourceForm: sf halftoneForm: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: sourceOrigin extent: extent clipRect: clipRect "Answer an instance of me with values set according to the arguments." ^ self new setDestForm: df sourceForm: sf fillColor: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: sourceOrigin extent: extent clipRect: clipRect! ! !BitBlt class methodsFor: 'instance creation'! toForm: aForm ^ self new setDestForm: aForm! ! !BitBlt class methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! exampleAt: originPoint rule: rule fillColor: mask "This builds a source and destination form and copies the source to the destination using the specifed rule and mask. It is called from the method named exampleOne. Only works with Display depth of 1" | s d border aBitBlt | border := Form extent: 32 @ 32. border fillBlack. border fill: (1 @ 1 extent: 30 @ 30) fillColor: Color white. s := Form extent: 32 @ 32. s fillWhite. s fillBlack: (7 @ 7 corner: 25 @ 25). d := Form extent: 32 @ 32. d fillWhite. d fillBlack: (0 @ 0 corner: 32 @ 16). s displayOn: Display at: originPoint. border displayOn: Display at: originPoint rule: Form under. d displayOn: Display at: originPoint + (s width @ 0). border displayOn: Display at: originPoint + (s width @ 0) rule: Form under. d displayOn: Display at: originPoint + (s extent // (2 @ 1)). aBitBlt := BitBlt destForm: Display sourceForm: s fillColor: mask combinationRule: rule destOrigin: originPoint + (s extent // (2 @ 1)) sourceOrigin: 0 @ 0 extent: s extent clipRect: Display computeBoundingBox. aBitBlt copyBits. border displayOn: Display at: originPoint + (s extent // (2 @ 1)) rule: Form under "BitBlt exampleAt: 100@100 rule: 0 fillColor: nil"! ! !BitBlt class methodsFor: 'private' stamp: 'StephaneDucasse 10/17/2009 17:15'! recreateColorMaps CachedFontColorMaps := ColorConvertingMaps := nil! ! !BitBlt class methodsFor: 'class initialization' stamp: 'jmv 9/7/2009 09:32'! initialize self recreateColorMaps! ! TestCase subclass: #BitBltClipBugs instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Bugs'! !BitBltClipBugs methodsFor: 'as yet unclassified' stamp: 'ar 3/8/2003 00:33'! testDrawingWayOutside | f1 bb f2 | f1 := Form extent: 100@100 depth: 1. f2 := Form extent: 100@100 depth: 1. bb := BitBlt toForm: f1. bb combinationRule: 3. bb sourceForm: f2. bb destOrigin: SmallInteger maxVal squared asPoint. bb width: 100; height: 100. self shouldnt:[bb copyBits] raise: Error. ! ! !BitBltClipBugs methodsFor: 'as yet unclassified' stamp: 'ar 3/8/2003 00:33'! testDrawingWayOutside2 | f1 bb f2 | f1 := Form extent: 100@100 depth: 1. f2 := Form extent: 100@100 depth: 1. bb := BitBlt toForm: f1. bb combinationRule: 3. bb sourceForm: f2. bb destOrigin: 0@0. bb width: SmallInteger maxVal squared; height: SmallInteger maxVal squared. self shouldnt:[bb copyBits] raise: Error.! ! !BitBltClipBugs methodsFor: 'as yet unclassified' stamp: 'ar 3/8/2003 00:33'! testDrawingWayOutside3 | f1 bb f2 | f1 := Form extent: 100@100 depth: 1. f2 := Form extent: 100@100 depth: 1. bb := BitBlt toForm: f1. bb combinationRule: 3. bb sourceForm: f2. bb destOrigin: SmallInteger maxVal squared asPoint. bb width: SmallInteger maxVal squared; height: SmallInteger maxVal squared. self shouldnt:[bb copyBits] raise: Error. ! ! !BitBltClipBugs methodsFor: 'as yet unclassified' stamp: 'ar 3/8/2003 00:34'! testDrawingWayOutside4 | f1 bb f2 | f1 := Form extent: 100@100 depth: 1. f2 := Form extent: 100@100 depth: 1. bb := BitBlt toForm: f1. bb combinationRule: 3. bb sourceForm: f2. bb destOrigin: SmallInteger maxVal squared asPoint. bb width: 100; height: 100. bb sourceOrigin: SmallInteger maxVal squared asPoint. self shouldnt:[bb copyBits] raise: Error. ! ! !BitBltClipBugs methodsFor: 'as yet unclassified' stamp: 'ar 3/8/2003 00:34'! testDrawingWayOutside5 | f1 bb f2 | f1 := Form extent: 100@100 depth: 1. f2 := Form extent: 100@100 depth: 1. bb := BitBlt toForm: f1. bb combinationRule: 3. bb sourceForm: f2. bb destOrigin: 0@0. bb width: SmallInteger maxVal squared; height: SmallInteger maxVal squared. bb sourceOrigin: SmallInteger maxVal squared asPoint. self shouldnt:[bb copyBits] raise: Error.! ! !BitBltClipBugs methodsFor: 'as yet unclassified' stamp: 'ar 3/8/2003 00:34'! testDrawingWayOutside6 | f1 bb f2 | f1 := Form extent: 100@100 depth: 1. f2 := Form extent: 100@100 depth: 1. bb := BitBlt toForm: f1. bb combinationRule: 3. bb sourceForm: f2. bb destOrigin: SmallInteger maxVal squared asPoint. bb width: SmallInteger maxVal squared; height: SmallInteger maxVal squared. bb sourceOrigin: SmallInteger maxVal squared asPoint. self shouldnt:[bb copyBits] raise: Error. ! ! !BitBltClipBugs methodsFor: 'as yet unclassified' stamp: 'ar 3/8/2003 00:32'! testFillingWayOutside | f1 bb | f1 := Form extent: 100@100 depth: 1. bb := BitBlt toForm: f1. bb combinationRule: 3. bb fillColor: Color black. bb destOrigin: SmallInteger maxVal squared asPoint. bb width: 100; height: 100. self shouldnt:[bb copyBits] raise: Error. ! ! !BitBltClipBugs methodsFor: 'as yet unclassified' stamp: 'ar 3/8/2003 00:32'! testFillingWayOutside2 | f1 bb | f1 := Form extent: 100@100 depth: 1. bb := BitBlt toForm: f1. bb combinationRule: 3. bb fillColor: Color black. bb destOrigin: 0@0. bb width: SmallInteger maxVal squared; height: SmallInteger maxVal squared. self shouldnt:[bb copyBits] raise: Error.! ! !BitBltClipBugs methodsFor: 'as yet unclassified' stamp: 'ar 3/8/2003 00:32'! testFillingWayOutside3 | f1 bb | f1 := Form extent: 100@100 depth: 1. bb := BitBlt toForm: f1. bb combinationRule: 3. bb fillColor: Color black. bb destOrigin: SmallInteger maxVal squared asPoint. bb width: SmallInteger maxVal squared; height: SmallInteger maxVal squared. self shouldnt:[bb copyBits] raise: Error. ! ! ClassTestCase subclass: #BitBltTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'GraphicsTests-Primitives'! !BitBltTest methodsFor: 'bugs' stamp: 'sd 6/5/2005 10:12'! testAlphaCompositing "self run: #testAlphaCompositing" | bb f1 f2 mixColor result eps | f1 := Form extent: 1@1 depth: 32. f2 := Form extent: 1@1 depth: 32. eps := 0.5 / 255. 0 to: 255 do:[:i| f1 colorAt: 0@0 put: Color blue. mixColor := Color red alpha: i / 255.0. f2 colorAt: 0@0 put: mixColor. mixColor := f2 colorAt: 0@0. bb := BitBlt toForm: f1. bb sourceForm: f2. bb combinationRule: Form blend. bb copyBits. result := f1 colorAt: 0@0. self assert: (result red - mixColor alpha) abs < eps. self assert: (result blue - (1.0 - mixColor alpha)) abs < eps. self assert: result alpha = 1.0. ].! ! !BitBltTest methodsFor: 'bugs' stamp: 'sd 6/5/2005 10:12'! testAlphaCompositing2 "self run: #testAlphaCompositing2" | bb f1 f2 mixColor result eps | f1 := Form extent: 1@1 depth: 32. f2 := Form extent: 1@1 depth: 32. eps := 0.5 / 255. 0 to: 255 do:[:i| f1 colorAt: 0@0 put: Color transparent. mixColor := Color red alpha: i / 255.0. f2 colorAt: 0@0 put: mixColor. mixColor := f2 colorAt: 0@0. bb := BitBlt toForm: f1. bb sourceForm: f2. bb combinationRule: Form blend. bb copyBits. result := f1 colorAt: 0@0. self assert: (result red - mixColor alpha) abs < eps. self assert: result alpha = mixColor alpha. ].! ! !BitBltTest methodsFor: 'bugs' stamp: 'NorbertHartl 6/20/2008 21:37'! testAlphaCompositing2Simulated "self run: #testAlphaCompositing2Simulated" | bb f1 f2 mixColor result eps | Smalltalk at: #BitBltSimulation ifPresent: [:bitblt| f1 := Form extent: 1@1 depth: 32. f2 := Form extent: 1@1 depth: 32. eps := 0.5 / 255. 0 to: 255 do:[:i| f1 colorAt: 0@0 put: Color transparent. mixColor := Color red alpha: i / 255.0. f2 colorAt: 0@0 put: mixColor. mixColor := f2 colorAt: 0@0. bb := BitBlt toForm: f1. bb sourceForm: f2. bb combinationRule: Form blend. result := f1 colorAt: 0@0. self assert: (result red - mixColor alpha) abs < eps. self assert: result alpha = mixColor alpha. ].]! ! !BitBltTest methodsFor: 'bugs' stamp: 'NorbertHartl 6/20/2008 21:37'! testAlphaCompositingSimulated "self run: #testAlphaCompositingSimulated" | bb f1 f2 mixColor result eps | Smalltalk at: #BitBltSimulation ifPresent:[:bitblt| f1 := Form extent: 1@1 depth: 32. f2 := Form extent: 1@1 depth: 32. eps := 0.5 / 255. 0 to: 255 do:[:i| f1 colorAt: 0@0 put: Color blue. mixColor := Color red alpha: i / 255.0. f2 colorAt: 0@0 put: mixColor. mixColor := f2 colorAt: 0@0. bb := BitBlt toForm: f1. bb sourceForm: f2. bb combinationRule: Form blend. result := f1 colorAt: 0@0. self assert: (result red - mixColor alpha) abs < eps. self assert: (result blue - (1.0 - mixColor alpha)) abs < eps. self assert: result alpha = 1.0. ]].! ! !BitBltTest methodsFor: 'bugs' stamp: 'sd 6/5/2005 10:13'! testPeekerUnhibernateBug "self run: #testPeekerUnhibernateBug" | bitBlt | bitBlt := BitBlt bitPeekerFromForm: Display. bitBlt destForm hibernate. self shouldnt:[bitBlt pixelAt: 1@1] raise: Error.! ! !BitBltTest methodsFor: 'bugs' stamp: 'sd 6/5/2005 10:14'! testPokerUnhibernateBug "self run: #testPokerUnhibernateBug" | bitBlt | bitBlt := BitBlt bitPokerToForm: Display. bitBlt sourceForm hibernate. self shouldnt:[bitBlt pixelAt: 1@1 put: 0] raise: Error.! ! ArrayedCollection variableWordSubclass: #Bitmap instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Primitives'! !Bitmap commentStamp: '' prior: 0! My instances provide contiguous storage of bits, primarily to hold the graphical data of Forms. Forms and their subclasses provide the additional structural information as to how the bits should be interpreted in two dimensions.! !Bitmap methodsFor: 'accessing' stamp: 'ar 3/3/2001 16:11'! atAllPut: value "Fill the receiver, an indexable bytes or words object, with the given positive integer. The range of possible fill values is [0..255] for byte arrays and [0..(2^32 - 1)] for word arrays." super atAllPut: value.! ! !Bitmap methodsFor: 'accessing'! bitPatternForDepth: depth "The raw call on BitBlt needs a Bitmap to represent this color. I already am Bitmap like. I am already adjusted for a specific depth. Interpret me as an array of (32/depth) Color pixelValues. BitBlt aligns the first element of this array with the top scanline of the destinationForm, the second with the second, and so on, cycling through the color array as necessary. 6/18/96 tk" ^ self! ! !Bitmap methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! byteAt: byteAddress "Extract a byte from a Bitmap. Note that this is a byte address and it is one-order. For repeated use, create an instance of BitBlt and use pixelAt:. See Form pixelAt: 7/1/96 tk" | lowBits | lowBits := byteAddress - 1 bitAnd: 3. ^ ((self at: (byteAddress - 1 - lowBits) // 4 + 1) bitShift: (lowBits - 3) * 8) bitAnd: 255! ! !Bitmap methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! byteAt: byteAddress put: byte "Insert a byte into a Bitmap. Note that this is a byte address and it is one-order. For repeated use, create an instance of BitBlt and use pixelAt:put:. See Form pixelAt:put: 7/1/96 tk" | longWord shift lowBits longAddr | (byte < 0 or: [ byte > 255 ]) ifTrue: [ ^ self errorImproperStore ]. lowBits := byteAddress - 1 bitAnd: 3. longWord := self at: (longAddr := (byteAddress - 1 - lowBits) // 4 + 1). shift := (3 - lowBits) * 8. longWord := longWord - (longWord bitAnd: (255 bitShift: shift)) + (byte bitShift: shift). self at: longAddr put: longWord. ^ byte! ! !Bitmap methodsFor: 'accessing' stamp: 'ar 3/3/2001 16:18'! byteSize ^self size * 4! ! !Bitmap methodsFor: 'accessing' stamp: 'nk 7/30/2004 17:53'! copyFromByteArray: byteArray "This method should work with either byte orderings" | myHack byteHack | myHack := Form new hackBits: self. byteHack := Form new hackBits: byteArray. SmalltalkImage current isLittleEndian ifTrue: [byteHack swapEndianness]. byteHack displayOn: myHack! ! !Bitmap methodsFor: 'accessing' stamp: 'ar 11/2/1998 12:19'! defaultElement "Return the default element of the receiver" ^0! ! !Bitmap methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! integerAt: index "Return the integer at the given index" | word | word := self basicAt: index. word < 1073741823 ifTrue: [ ^ word ]. "Avoid LargeInteger computations" ^ word >= 2147483648 ifTrue: [ "Negative?!!" "word - 16r100000000" (word bitInvert32 + 1) negated ] ifFalse: [ word ]! ! !Bitmap methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! integerAt: index put: anInteger "Store the integer at the given index" | word | anInteger < 0 ifTrue: [ "word _ 16r100000000 + anInteger" word := (anInteger + 1) negated bitInvert32 ] ifFalse: [ word := anInteger ]. self basicAt: index put: word. ^ anInteger! ! !Bitmap methodsFor: 'accessing' stamp: 'tk 3/15/97'! pixelValueForDepth: depth "Self is being used to represent a single color. Answer bits that appear in ONE pixel of this color in a Bitmap of the given depth. The depth must be one of 1, 2, 4, 8, 16, or 32. Returns an integer. First pixel only. " ^ (self at: 1) bitAnd: (1 bitShift: depth) - 1! ! !Bitmap methodsFor: 'accessing'! primFill: aPositiveInteger "Fill the receiver, an indexable bytes or words object, with the given positive integer. The range of possible fill values is [0..255] for byte arrays and [0..(2^32 - 1)] for word arrays." self errorImproperStore.! ! !Bitmap methodsFor: 'accessing'! replaceFrom: start to: stop with: replacement startingAt: repStart "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive." super replaceFrom: start to: stop with: replacement startingAt: repStart! ! !Bitmap methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! asByteArray "Faster way to make a byte array from me. copyFromByteArray: makes equal Bitmap." | f bytes hack | f := Form extent: 4 @ self size depth: 8 bits: self. bytes := ByteArray new: self size * 4. hack := Form new hackBits: bytes. SmalltalkImage current isLittleEndian ifTrue: [ hack swapEndianness ]. hack copyBits: f boundingBox from: f at: 0 @ 0 clippingBox: hack boundingBox rule: Form over fillColor: nil map: nil. "f displayOn: hack." ^ bytes! ! !Bitmap methodsFor: 'as yet unclassified' stamp: 'RAA 7/28/2000 21:51'! copy ^self clone! ! !Bitmap methodsFor: 'filing' stamp: 'lr 7/4/2009 10:42'! compress: bm toByteArray: ba "Store a run-coded compression of the receiver into the byteArray ba, and return the last index stored into. ba is assumed to be large enough. The encoding is as follows... S {N D}*. S is the size of the original bitmap, followed by run-coded pairs. N is a run-length * 4 + data code. D, the data, depends on the data code... 0 skip N words, D is absent 1 N words with all 4 bytes = D (1 byte) 2 N words all = D (4 bytes) 3 N words follow in D (4N bytes) S and N are encoded as follows... 0-223 0-223 224-254 (0-30)*256 + next byte (0-7935) 255 next 4 bytes" | size k word j lowByte eqBytes i | self var: #bm declareC: 'int *bm'. self var: #ba declareC: 'unsigned char *ba'. size := bm size. i := self encodeInt: size in: ba at: 1. k := 1. [ k <= size ] whileTrue: [ word := bm at: k. lowByte := word bitAnd: 255. eqBytes := (word >> 8 bitAnd: 255) = lowByte and: [ (word >> 16 bitAnd: 255) = lowByte and: [ (word >> 24 bitAnd: 255) = lowByte ] ]. j := k. [ j < size and: [ word = (bm at: j + 1) ] "scan for = words..." ] whileTrue: [ j := j + 1 ]. j > k ifTrue: [ "We have two or more = words, ending at j" eqBytes ifTrue: [ "Actually words of = bytes" i := self encodeInt: (j - k + 1) * 4 + 1 in: ba at: i. ba at: i put: lowByte. i := i + 1 ] ifFalse: [ i := self encodeInt: (j - k + 1) * 4 + 2 in: ba at: i. i := self encodeBytesOf: word in: ba at: i ]. k := j + 1 ] ifFalse: [ "Check for word of 4 = bytes" eqBytes ifTrue: [ "Note 1 word of 4 = bytes" i := self encodeInt: 1 * 4 + 1 in: ba at: i. ba at: i put: lowByte. i := i + 1. k := k + 1 ] ifFalse: [ "Finally, check for junk" [ j < size and: [ (bm at: j) ~= (bm at: j + 1) ] "scan for ~= words..." ] whileTrue: [ j := j + 1 ]. j = size ifTrue: [ j := j + 1 ]. "We have one or more unmatching words, ending at j-1" i := self encodeInt: (j - k) * 4 + 3 in: ba at: i. k to: j - 1 do: [ :m | i := self encodeBytesOf: (bm at: m) in: ba at: i ]. k := j ] ] ]. ^ i - 1 "number of bytes actually stored" " Space check: | n rawBytes myBytes b | n _ rawBytes _ myBytes _ 0. Form allInstancesDo: [:f | f unhibernate. b _ f bits. n _ n + 1. rawBytes _ rawBytes + (b size*4). myBytes _ myBytes + (b compressToByteArray size). f hibernate]. Array with: n with: rawBytes with: myBytes ColorForms: (116 230324 160318 ) Forms: (113 1887808 1325055 ) Integerity check: Form allInstances do: [:f | f unhibernate. f bits = (Bitmap decompressFromByteArray: f bits compressToByteArray) ifFalse: [self halt]. f hibernate] Speed test: MessageTally spyOn: [Form allInstances do: [:f | Bitmap decompressFromByteArray: f bits compressToByteArray]] "! ! !Bitmap methodsFor: 'filing' stamp: 'lr 7/4/2009 10:42'! compressGZip "just hacking around to see if further compression would help Nebraska" | ba hackwa hackba blt rowsAtATime sourceOrigin rowsRemaining bufferStream gZipStream | bufferStream := RWBinaryOrTextStream on: (ByteArray new: 5000). gZipStream := GZipWriteStream on: bufferStream. ba := nil. rowsAtATime := 20000. "or 80000 bytes" hackwa := Form new hackBits: self. sourceOrigin := 0 @ 0. [ (rowsRemaining := hackwa height - sourceOrigin y) > 0 ] whileTrue: [ rowsAtATime := rowsAtATime min: rowsRemaining. (ba isNil or: [ ba size ~= (rowsAtATime * 4) ]) ifTrue: [ ba := ByteArray new: rowsAtATime * 4. hackba := Form new hackBits: ba. blt := (BitBlt toForm: hackba) sourceForm: hackwa ]. blt combinationRule: Form over; sourceOrigin: sourceOrigin; destX: 0 destY: 0 width: 4 height: rowsAtATime; copyBits. "bufferStream nextPutAll: ba." sourceOrigin := sourceOrigin x @ (sourceOrigin y + rowsAtATime) ]. gZipStream close. ^ bufferStream contents! ! !Bitmap methodsFor: 'filing' stamp: 'lr 7/4/2009 10:42'! compressToByteArray "Return a run-coded compression of this bitmap into a byteArray" "Without skip codes, it is unlikely that the compressed bitmap will be any larger than was the original. The run-code cases are... N >= 1 words of equal bytes: 4N bytes -> 2 bytes (at worst 4 -> 2) N > 1 equal words: 4N bytes -> 5 bytes (at worst 8 -> 5) N > 1 unequal words: 4N bytes -> 4N + M, where M is the number of bytes required to encode the run length. The worst that can happen is that the method begins with unequal words, and than has interspersed occurrences of a word with equal bytes. Thus we require a run-length at the beginning, and after every interspersed word of equal bytes. However, each of these saves 2 bytes, so it must be followed by a run of 1984 (7936//4) or more (for which M jumps from 2 to 5) to add any extra overhead. Therefore the worst case is a series of runs of 1984 or more, with single interspersed words of equal bytes. At each break we save 2 bytes, but add 5. Thus the overhead would be no more than 5 (encoded size) + 2 (first run len) + (S//1984*3)." "NOTE: This code is copied in Form hibernate for reasons given there." | byteArray lastByte | byteArray := ByteArray new: self size * 4 + 7 + (self size // 1984 * 3). lastByte := self compress: self toByteArray: byteArray. ^ byteArray copyFrom: 1 to: lastByte! ! !Bitmap methodsFor: 'filing' stamp: 'lr 7/4/2009 10:42'! decompress: bm fromByteArray: ba at: index "Decompress the body of a byteArray encoded by compressToByteArray (qv)... The format is simply a sequence of run-coded pairs, {N D}*. N is a run-length * 4 + data code. D, the data, depends on the data code... 0 skip N words, D is absent (could be used to skip from one raster line to the next) 1 N words with all 4 bytes = D (1 byte) 2 N words all = D (4 bytes) 3 N words follow in D (4N bytes) S and N are encoded as follows (see decodeIntFrom:)... 0-223 0-223 224-254 (0-30)*256 + next byte (0-7935) 255 next 4 bytes" "NOTE: If fed with garbage, this routine could read past the end of ba, but it should fail before writing past the ned of bm." | i code n anInt data end k pastEnd | self var: #bm declareC: 'int *bm'. self var: #ba declareC: 'unsigned char *ba'. i := index. "byteArray read index" end := ba size. k := 1. "bitmap write index" pastEnd := bm size + 1. [ i <= end ] whileTrue: [ "Decode next run start N" anInt := ba at: i. i := i + 1. anInt <= 223 ifFalse: [ anInt <= 254 ifTrue: [ anInt := (anInt - 224) * 256 + (ba at: i). i := i + 1 ] ifFalse: [ anInt := 0. 1 to: 4 do: [ :j | anInt := (anInt bitShift: 8) + (ba at: i). i := i + 1 ] ] ]. n := anInt >> 2. k + n > pastEnd ifTrue: [ ^ self primitiveFailed ]. code := anInt bitAnd: 3. code = 0 ifTrue: [ "skip" ]. code = 1 ifTrue: [ "n consecutive words of 4 bytes = the following byte" data := ba at: i. i := i + 1. data := data bitOr: (data bitShift: 8). data := data bitOr: (data bitShift: 16). 1 to: n do: [ :j | bm at: k put: data. k := k + 1 ] ]. code = 2 ifTrue: [ "n consecutive words = 4 following bytes" data := 0. 1 to: 4 do: [ :j | data := (data bitShift: 8) bitOr: (ba at: i). i := i + 1 ]. 1 to: n do: [ :j | bm at: k put: data. k := k + 1 ] ]. code = 3 ifTrue: [ "n consecutive words from the data..." 1 to: n do: [ :m | data := 0. 1 to: 4 do: [ :j | data := (data bitShift: 8) bitOr: (ba at: i). i := i + 1 ]. bm at: k put: data. k := k + 1 ] ] ]! ! !Bitmap methodsFor: 'filing' stamp: 'jm 2/15/98 17:27'! encodeBytesOf: anInt in: ba at: i "Copy the integer anInt into byteArray ba at index i, and return the next index" self inline: true. self var: #ba declareC: 'unsigned char *ba'. 0 to: 3 do: [:j | ba at: i+j put: (anInt >> (3-j*8) bitAnd: 16rFF)]. ^ i+4! ! !Bitmap methodsFor: 'filing' stamp: 'lr 7/4/2009 10:42'! encodeInt: int "Encode the integer int as per encodeInt:in:at:, and return it as a ByteArray" | byteArray next | byteArray := ByteArray new: 5. next := self encodeInt: int in: byteArray at: 1. ^ byteArray copyFrom: 1 to: next - 1! ! !Bitmap methodsFor: 'filing' stamp: 'jm 2/15/98 17:26'! encodeInt: anInt in: ba at: i "Encode the integer anInt in byteArray ba at index i, and return the next index. The encoding is as follows... 0-223 0-223 224-254 (0-30)*256 + next byte (0-7935) 255 next 4 bytes" self inline: true. self var: #ba declareC: 'unsigned char *ba'. anInt <= 223 ifTrue: [ba at: i put: anInt. ^ i+1]. anInt <= 7935 ifTrue: [ba at: i put: anInt//256+224. ba at: i+1 put: anInt\\256. ^ i+2]. ba at: i put: 255. ^ self encodeBytesOf: anInt in: ba at: i+1! ! !Bitmap methodsFor: 'filing' stamp: 'PeterHugossonMiller 9/3/2009 00:15'! readCompressedFrom: strm "Decompress an old-style run-coded stream into this bitmap: [0 means end of runs] [n = 1..127] [(n+3) copies of next byte] [n = 128..191] [(n-127) next bytes as is] [n = 192..255] [(n-190) copies of next 4 bytes]" | n byte out outBuff bytes | out := (outBuff := ByteArray new: self size * 4) writeStream. [ (n := strm next) > 0 ] whileTrue: [ (n between: 1 and: 127) ifTrue: [ byte := strm next. 1 to: n + 3 do: [ :i | out nextPut: byte ] ]. (n between: 128 and: 191) ifTrue: [ 1 to: n - 127 do: [ :i | out nextPut: strm next ] ]. (n between: 192 and: 255) ifTrue: [ bytes := (1 to: 4) collect: [ :i | strm next ]. 1 to: n - 190 do: [ :i | bytes do: [ :b | out nextPut: b ] ] ] ]. out position = outBuff size ifFalse: [ self error: 'Decompression size error' ]. "Copy the final byteArray into self" self copyFromByteArray: outBuff! ! !Bitmap methodsFor: 'filing' stamp: 'tk 1/24/2000 22:37'! restoreEndianness "This word object was just read in from a stream. Bitmaps are always compressed and serialized in a machine-independent way. Do not correct the Endianness." "^ self" ! ! !Bitmap methodsFor: 'filing' stamp: 'nk 12/31/2003 16:02'! storeBits: startBit to: stopBit on: aStream "Store my bits as a hex string, breaking the lines every 100 bytes or so to comply with the maximum line length limits of Postscript (255 bytes). " | lineWidth | lineWidth := 0. self do: [:word | startBit to: stopBit by: -4 do: [:shift | aStream nextPut: (word >> shift bitAnd: 15) asHexDigit. lineWidth := lineWidth + 1]. (lineWidth > 100) ifTrue: [aStream cr. lineWidth := 0]]. lineWidth > 0 ifTrue: [ aStream cr ].! ! !Bitmap methodsFor: 'filing' stamp: 'lr 7/4/2009 10:42'! writeOn: aStream "Store the array of bits onto the argument, aStream. A leading byte of 16r80 identifies this as compressed by compressToByteArray (qv)." | b | aStream nextPut: 128. b := self compressToByteArray. aStream nextPutAll: (self encodeInt: b size); nextPutAll: b! ! !Bitmap methodsFor: 'filing' stamp: 'tk 2/19/1999 07:36'! writeUncompressedOn: aStream "Store the array of bits onto the argument, aStream. (leading byte ~= 16r80) identifies this as raw bits (uncompressed)." aStream nextInt32Put: self size. aStream nextPutAll: self ! ! !Bitmap methodsFor: 'initialization' stamp: 'ar 12/23/1999 14:35'! fromByteStream: aStream "Initialize the array of bits by reading integers from the argument, aStream." aStream nextWordsInto: self! ! !Bitmap methodsFor: 'printing' stamp: 'sma 6/1/2000 09:42'! printOn: aStream self printNameOn: aStream. aStream nextPutAll: ' of length '; print: self size! ! !Bitmap methodsFor: 'printing' stamp: 'MPW 1/1/1901 22:00'! printOnStream: aStream aStream print: 'a Bitmap of length '; write:self size. ! ! !Bitmap methodsFor: 'testing' stamp: 'ar 5/25/2000 19:42'! isColormap "Bitmaps were used as color maps for BitBlt. This method allows to recognize real color maps." ^false! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Bitmap class instanceVariableNames: ''! !Bitmap class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! decodeIntFrom: s "Decode an integer in stream s as follows... 0-223 0-223 224-254 (0-30)*256 + next byte (0-7935) 255 next 4 bytes " | int | int := s next. int <= 223 ifTrue: [ ^ int ]. int <= 254 ifTrue: [ ^ (int - 224) * 256 + s next ]. int := s next. 1 to: 3 do: [ :j | int := (int bitShift: 8) + s next ]. ^ int! ! !Bitmap class methodsFor: 'instance creation' stamp: 'damiencassou 5/30/2008 14:51'! decompressFromByteArray: byteArray | s bitmap size | s := byteArray readStream. size := self decodeIntFrom: s. bitmap := self new: size. bitmap decompress: bitmap fromByteArray: byteArray at: s position + 1. ^ bitmap! ! !Bitmap class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! newFromStream: s | len | s next = 128 ifTrue: [ "New compressed format" len := self decodeIntFrom: s. ^ Bitmap decompressFromByteArray: (s nextInto: (ByteArray new: len)) ]. s skip: -1. len := s nextInt32. len <= 0 ifTrue: [ "Old compressed format" ^ (self new: len negated) readCompressedFrom: s ] ifFalse: [ "Old raw data format" ^ s nextWordsInto: (self new: len) ]! ! !Bitmap class methodsFor: 'utilities' stamp: 'lr 7/4/2009 10:42'! swapBytesIn: aNonPointerThing from: start to: stop "Perform a bigEndian/littleEndian byte reversal of my words. We only intend this for non-pointer arrays. Do nothing if I contain pointers." "The implementation is a hack, but fast for large ranges" | hack blt | hack := Form new hackBits: aNonPointerThing. blt := (BitBlt toForm: hack) sourceForm: hack. blt combinationRule: Form reverse. "XOR" blt sourceY: start - 1; destY: start - 1; height: stop - start + 1; width: 1. blt sourceX: 0; destX: 3; copyBits. "Exchange bytes 0 and 3" blt sourceX: 3; destX: 0; copyBits. blt sourceX: 0; destX: 3; copyBits. blt sourceX: 1; destX: 2; copyBits. "Exchange bytes 1 and 2" blt sourceX: 2; destX: 1; copyBits. blt sourceX: 1; destX: 2; copyBits! ! TestCase subclass: #BitmapBugz instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Bugs'! !BitmapBugz methodsFor: 'as yet unclassified' stamp: 'ar 8/2/2003 19:21'! testBitmapByteAt | bm | bm := Bitmap new: 1. 1 to: 4 do:[:i| self should:[bm byteAt: i put: 1000] raise: Error. ].! ! OrientedFillStyle subclass: #BitmapFillStyle instanceVariableNames: 'form tileFlag' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Fills'! !BitmapFillStyle commentStamp: '' prior: 0! A BitmapFillStyle fills using any kind of form. Instance variables: form
The form to be used as fill. tileFlag If true, then the form is repeatedly drawn to fill the area.! !BitmapFillStyle methodsFor: '*morphic-balloon' stamp: 'wiz 8/30/2003 16:54'! grabNewGraphicIn: aMorph event: evt "Used by any morph that can be represented by a graphic" | fill | fill := Form fromUser. fill boundingBox area = 0 ifTrue: [^ self]. self form: fill. self direction: fill width @ 0. self normal: 0 @ fill height. aMorph changed! ! !BitmapFillStyle methodsFor: '*morphic-balloon' stamp: 'ar 6/25/1999 11:57'! newForm: aForm forMorph: aMorph self form: aForm. self direction: (aForm width @ 0). self normal: (0 @ aForm height). aMorph changed.! ! !BitmapFillStyle methodsFor: 'accessing' stamp: 'wiz 1/16/2005 20:17'! direction ^direction ifNil:[direction :=( (normal y @ normal x negated) * form width / form height ) rounded]! ! !BitmapFillStyle methodsFor: 'accessing' stamp: 'ar 11/11/1998 22:40'! form ^form! ! !BitmapFillStyle methodsFor: 'accessing' stamp: 'ar 11/11/1998 22:40'! form: aForm form := aForm! ! !BitmapFillStyle methodsFor: 'accessing' stamp: 'wiz 1/16/2005 20:18'! normal ^normal ifNil:[normal := ((direction y negated @ direction x) * form height / form width ) rounded]! ! !BitmapFillStyle methodsFor: 'accessing' stamp: 'ar 11/27/1998 14:37'! tileFlag ^tileFlag! ! !BitmapFillStyle methodsFor: 'accessing' stamp: 'ar 11/27/1998 14:30'! tileFlag: aBoolean tileFlag := aBoolean! ! !BitmapFillStyle methodsFor: 'converting' stamp: 'ar 11/11/1998 22:41'! asColor ^form colorAt: 0@0! ! !BitmapFillStyle methodsFor: 'testing' stamp: 'ar 11/11/1998 22:40'! isBitmapFill ^true! ! !BitmapFillStyle methodsFor: 'testing' stamp: 'ar 11/27/1998 14:37'! isTiled "Return true if the receiver should be repeated if the fill shape is larger than the form" ^tileFlag == true! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BitmapFillStyle class instanceVariableNames: ''! !BitmapFillStyle class methodsFor: 'instance creation' stamp: 'ar 11/13/1998 20:32'! form: aForm ^self new form: aForm! ! !BitmapFillStyle class methodsFor: 'instance creation' stamp: 'KLC 1/27/2004 13:33'! fromForm: aForm | fs | fs := self form: aForm. fs origin: 0@0. fs direction: aForm width @ 0. fs normal: 0 @ aForm height. fs tileFlag: true. ^fs! ! !BitmapFillStyle class methodsFor: 'instance creation' stamp: 'ar 6/18/1999 07:09'! fromUser | fill | fill := self form: Form fromUser. fill origin: 0@0. fill direction: fill form width @ 0. fill normal: 0 @ fill form height. fill tileFlag: true. "So that we can fill arbitrary objects" ^fill! ! TestCase subclass: #BitmapStreamTests instanceVariableNames: 'random array stream filename' classVariableNames: '' poolDictionaries: '' category: 'Tests-Bugs'! !BitmapStreamTests commentStamp: 'nk 3/7/2004 14:26' prior: 0! This is an incomplete test suite for storing and reading various word- and short-word subclasses of ArrayedCollection. It demonstrates some problems with filing in of certain kinds of arrayed objects, including: ShortPointArray ShortIntegerArray ShortRunArray WordArray MatrixTransform2x3 In 3.6b-5331, I get 8 passed/6 failed/6 errors (not counting the MatrixTransform2x3 tests, which were added later). I ran into problems when trying to read back the SqueakLogo flash character morph, after I'd done a 'save morph to disk' from its debug menu. The words within the ShortPointArrays and ShortRunArrays were reversed. ! !BitmapStreamTests methodsFor: 'running' stamp: 'SergeStinckwich 5/27/2008 22:58'! setUp filename := 'bitmapStreamTest.ref'. random := Random new! ! !BitmapStreamTests methodsFor: 'running' stamp: 'SergeStinckwich 5/27/2008 22:59'! tearDown FileDirectory default deleteFileNamed: filename ifAbsent: []! ! !BitmapStreamTests methodsFor: 'tests-matrixtransform2x3' stamp: 'stephaneducasse 2/3/2006 22:39'! testMatrixTransform2x3WithImageSegment array := MatrixTransform2x3 new. 1 to: 6 do: [ :i | array at: i put: self randomFloat ]. self validateImageSegment ! ! !BitmapStreamTests methodsFor: 'tests-matrixtransform2x3' stamp: 'stephaneducasse 2/3/2006 22:39'! testMatrixTransform2x3WithRefStream array := MatrixTransform2x3 new. 1 to: 6 do: [ :i | array at: i put: self randomFloat ]. self validateRefStream ! ! !BitmapStreamTests methodsFor: 'tests-matrixtransform2x3' stamp: 'stephaneducasse 2/3/2006 22:39'! testMatrixTransform2x3WithRefStreamOnDisk array := MatrixTransform2x3 new. 1 to: 6 do: [ :i | array at: i put: self randomFloat ]. self validateRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'tests-matrixtransform2x3' stamp: 'stephaneducasse 2/3/2006 22:39'! testMatrixTransform2x3WithSmartRefStream array := MatrixTransform2x3 new. 1 to: 6 do: [ :i | array at: i put: self randomFloat ]. self validateSmartRefStream ! ! !BitmapStreamTests methodsFor: 'tests-matrixtransform2x3' stamp: 'stephaneducasse 2/3/2006 22:39'! testMatrixTransform2x3WithSmartRefStreamOnDisk array := MatrixTransform2x3 new. 1 to: 6 do: [ :i | array at: i put: self randomFloat ]. self validateSmartRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'tests-misc' stamp: 'DouglasBrebner 9/2/2009 19:18'! testOtherClasses #(WordArrayForSegment FloatArray PointArray IntegerArray String ShortPointArray ShortIntegerArray WordArray Array DependentsArray ByteArray Bitmap ColorArray ) do: [:s | | a | a := (Smalltalk at: s) new: 3. self assert: (a basicSize * a bytesPerBasicElement = a byteSize). ] ! ! !BitmapStreamTests methodsFor: 'tests-shortintegerarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortIntegerArrayReadRefStream2 |refStrm| refStrm := ReferenceStream on: ((RWBinaryOrTextStream with: (ByteArray withAll: #(20 6 17 83 104 111 114 116 73 110 116 101 103 101 114 65 114 114 97 121 0 0 0 2 0 0 0 1 0 2 0 3))) reset; binary). self assert: (refStrm next = (ShortIntegerArray with: 0 with: 1 with: 2 with: 3)).! ! !BitmapStreamTests methodsFor: 'tests-shortintegerarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortIntegerArrayWithImageSegment array := ShortIntegerArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomShortInt ]. self validateImageSegment ! ! !BitmapStreamTests methodsFor: 'tests-shortintegerarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortIntegerArrayWithRefStream array := ShortIntegerArray with: 0 with: 1 with: 2 with: 3. self validateRefStream ! ! !BitmapStreamTests methodsFor: 'tests-shortintegerarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortIntegerArrayWithRefStream2 array := ShortIntegerArray with: 0 with: 1 with: 2 with: 3. self validateRefStream. self assert: stream byteStream contents = (ByteArray withAll: #(20 6 17 83 104 111 114 116 73 110 116 101 103 101 114 65 114 114 97 121 0 0 0 2 0 0 0 1 0 2 0 3)) ! ! !BitmapStreamTests methodsFor: 'tests-shortintegerarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortIntegerArrayWithRefStreamOnDisk array := ShortIntegerArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomShortInt ]. self validateRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'tests-shortintegerarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortIntegerArrayWithSmartRefStream array := ShortIntegerArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomShortInt ]. self validateSmartRefStream ! ! !BitmapStreamTests methodsFor: 'tests-shortintegerarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortIntegerArrayWithSmartRefStream2 array := ShortIntegerArray with: 0 with: 1 with: 2 with: 3. self validateSmartRefStream. self assert: (stream contents asByteArray last: 15) = (ByteArray withAll: #(0 0 0 2 0 0 0 1 0 2 0 3 33 13 13)) ! ! !BitmapStreamTests methodsFor: 'tests-shortintegerarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortIntegerArrayWithSmartRefStreamOnDisk array := ShortIntegerArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomShortInt ]. self validateSmartRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'tests-shortpointarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortPointArrayWithImageSegment array := ShortPointArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomShortPoint ]. self validateImageSegment ! ! !BitmapStreamTests methodsFor: 'tests-shortpointarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortPointArrayWithRefStream array := ShortPointArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomShortPoint ]. self validateRefStream ! ! !BitmapStreamTests methodsFor: 'tests-shortpointarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortPointArrayWithRefStream2 array := ShortPointArray with: 0@1 with: 2@3. self validateRefStream. self assert: stream byteStream contents = (ByteArray withAll: #(20 6 15 83 104 111 114 116 80 111 105 110 116 65 114 114 97 121 0 0 0 2 0 0 0 1 0 2 0 3 )) ! ! !BitmapStreamTests methodsFor: 'tests-shortpointarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortPointArrayWithRefStreamOnDisk array := ShortPointArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomShortPoint ]. self validateRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'tests-shortpointarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortPointArrayWithSmartRefStream array := ShortPointArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomShortPoint ]. self validateSmartRefStream ! ! !BitmapStreamTests methodsFor: 'tests-shortpointarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortPointArrayWithSmartRefStream2 array := ShortPointArray with: 0@1 with: 2@3. self validateSmartRefStream. self assert: (stream contents asByteArray last: 15) = (ByteArray withAll: #(0 0 0 2 0 0 0 1 0 2 0 3 33 13 13)) ! ! !BitmapStreamTests methodsFor: 'tests-shortpointarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortPointArrayWithSmartRefStreamOnDisk array := ShortPointArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomShortPoint ]. self validateSmartRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'tests-shortrunarray' stamp: 'nk 3/17/2004 16:39'! createSampleShortRunArray ^ShortRunArray newFrom: { 0. 1. 1. 2. 2. 2. 3. 3. 3. 3 }! ! !BitmapStreamTests methodsFor: 'tests-shortrunarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortRunArrayWithImageSegment array := self createSampleShortRunArray. self validateImageSegment ! ! !BitmapStreamTests methodsFor: 'tests-shortrunarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortRunArrayWithRefStream array := self createSampleShortRunArray. self validateRefStream ! ! !BitmapStreamTests methodsFor: 'tests-shortrunarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortRunArrayWithRefStreamOnDisk array := self createSampleShortRunArray. self validateRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'tests-shortrunarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortRunArrayWithSmartRefStream array := self createSampleShortRunArray. self validateSmartRefStream ! ! !BitmapStreamTests methodsFor: 'tests-shortrunarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortRunArrayWithSmartRefStream2 array := self createSampleShortRunArray. self validateSmartRefStream. self assert: (stream contents asByteArray last: 23) = (ByteArray withAll: #(0 0 0 4 0 1 0 0 0 2 0 1 0 3 0 2 0 4 0 3 33 13 13)) ! ! !BitmapStreamTests methodsFor: 'tests-shortrunarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testShortRunArrayWithSmartRefStreamOnDisk array := self createSampleShortRunArray. self validateSmartRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'tests-wordarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testWordArrayWithImageSegment array := WordArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomWord ]. self validateImageSegment ! ! !BitmapStreamTests methodsFor: 'tests-wordarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testWordArrayWithRefStream array := WordArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomWord ]. self validateRefStream ! ! !BitmapStreamTests methodsFor: 'tests-wordarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testWordArrayWithRefStreamOnDisk array := WordArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomWord ]. self validateRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'tests-wordarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testWordArrayWithSmartRefStream array := WordArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomWord ]. self validateSmartRefStream ! ! !BitmapStreamTests methodsFor: 'tests-wordarray' stamp: 'stephaneducasse 2/3/2006 22:39'! testWordArrayWithSmartRefStreamOnDisk array := WordArray new: 10. 1 to: 10 do: [ :i | array at: i put: self randomWord ]. self validateSmartRefStreamOnDisk ! ! !BitmapStreamTests methodsFor: 'private' stamp: 'stephaneducasse 2/3/2006 22:39'! randomFloat "Answer a random 32-bit float" | w | random seed: (w := random nextValue). ^w! ! !BitmapStreamTests methodsFor: 'private' stamp: 'nk 7/5/2003 16:33'! randomShortInt ^((random next * 65536) - 32768) truncated! ! !BitmapStreamTests methodsFor: 'private' stamp: 'nk 7/5/2003 16:00'! randomShortPoint ^(((random next * 65536) @ (random next * 65536)) - (32768 @ 32768)) truncated! ! !BitmapStreamTests methodsFor: 'private' stamp: 'stephaneducasse 2/3/2006 22:39'! randomWord "Answer a random 32-bit integer" | w | random seed: (w := random nextValue). ^w truncated! ! !BitmapStreamTests methodsFor: 'private' stamp: 'al 6/14/2008 19:12'! validateImageSegment | other externalSegmentFilename | externalSegmentFilename := 'bitmapStreamTest.extSeg'. [ (ImageSegment new copyFromRootsForExport: (Array with: array)) writeForExport: externalSegmentFilename. other := (FileDirectory default readOnlyFileNamed: externalSegmentFilename) fileInObjectAndCode ] ensure: [ FileDirectory default deleteFileNamed: externalSegmentFilename ifAbsent: [ ] ]. self assert: array = other originalRoots first! ! !BitmapStreamTests methodsFor: 'private' stamp: 'stephaneducasse 2/3/2006 22:39'! validateRefStream "array is set up with an array." | other rwstream | rwstream := RWBinaryOrTextStream on: (ByteArray new: array basicSize * 6). stream := ReferenceStream on: rwstream. stream nextPut: array; close. rwstream position: 0. stream := ReferenceStream on: rwstream. other := stream next. stream close. self assert: array = other! ! !BitmapStreamTests methodsFor: 'private' stamp: 'SergeStinckwich 5/27/2008 22:59'! validateRefStreamOnDisk "array is set up with an array." | other | FileDirectory default deleteFileNamed: filename ifAbsent: [ ]. stream := ReferenceStream fileNamed: filename. stream nextPut: array; close. stream := ReferenceStream fileNamed: filename. other := stream next. stream close. self assert: array = other! ! !BitmapStreamTests methodsFor: 'private' stamp: 'stephaneducasse 2/3/2006 22:39'! validateSmartRefStream "array is set up with an array." | other | stream := RWBinaryOrTextStream on: (ByteArray new: array basicSize * 6). stream binary. stream fileOutClass: nil andObject: array. stream position: 0. stream binary. other := stream fileInObjectAndCode. self assert: array = other! ! !BitmapStreamTests methodsFor: 'private' stamp: 'SergeStinckwich 5/27/2008 22:59'! validateSmartRefStreamOnDisk "array is set up with an array." | other | FileDirectory default deleteFileNamed: filename ifAbsent: [ ]. stream := FileDirectory default fileNamed: filename. stream fileOutClass: nil andObject: array. stream close. stream := FileDirectory default fileNamed: filename. other := stream fileInObjectAndCode. stream close. self assert: array = other! ! Error subclass: #BlockCannotReturn instanceVariableNames: 'result deadHome' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !BlockCannotReturn commentStamp: '' prior: 0! This class is private to the EHS implementation. Its use allows for ensured execution to survive code such as: [self doThis. ^nil] ensure: [self doThat] Signaling or handling this exception is not recommended.! !BlockCannotReturn methodsFor: 'accessing' stamp: 'ajh 2/6/2002 11:12'! deadHome ^ deadHome! ! !BlockCannotReturn methodsFor: 'accessing' stamp: 'ajh 2/6/2002 11:12'! deadHome: context deadHome := context! ! !BlockCannotReturn methodsFor: 'accessing' stamp: 'tfei 3/30/1999 12:54'! result ^result! ! !BlockCannotReturn methodsFor: 'accessing' stamp: 'tfei 3/30/1999 12:54'! result: r result := r! ! !BlockCannotReturn methodsFor: 'exceptiondescription' stamp: 'tfei 3/30/1999 12:55'! defaultAction self messageText: 'Block cannot return'. ^super defaultAction! ! !BlockCannotReturn methodsFor: 'exceptiondescription' stamp: 'tfei 4/2/1999 15:49'! isResumable ^true! ! Object variableSubclass: #BlockClosure instanceVariableNames: 'outerContext startpc numArgs' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Methods'! !BlockClosure commentStamp: '' prior: 0! I am a block closure for Eliot's closure implementation. Not to be confused with the old BlockClosure.! ]style[(103)i! !BlockClosure methodsFor: '*services-base' stamp: 'rr 3/21/2006 11:53'! valueWithRequestor: aRequestor "To do later: make the fillInTheBlank display more informative captions. Include the description of the service, and maybe record steps" ^ self numArgs isZero ifTrue: [self value] ifFalse: [self value: aRequestor]! ! !BlockClosure methodsFor: '*splitjoin' stamp: 'stephane.ducasse 4/13/2009 22:03'! split: aSequenceableCollection | result position | result := OrderedCollection new. position := 1. aSequenceableCollection withIndexDo: [:element :idx | (self value: element) ifTrue: [result add: (aSequenceableCollection copyFrom: position to: idx - 1). position := idx + 1]]. result add: (aSequenceableCollection copyFrom: position to: aSequenceableCollection size). ^ result! ! !BlockClosure methodsFor: 'accessing' stamp: 'stephane.ducasse 5/20/2009 21:19'! argumentCount "Answer the number of arguments that must be used to evaluate this block" ^numArgs ! ! !BlockClosure methodsFor: 'accessing' stamp: 'eem 9/3/2008 13:57'! copiedValueAt: i ^self basicAt: i! ! !BlockClosure methodsFor: 'accessing' stamp: 'eem 7/28/2008 13:58'! home ^outerContext home! ! !BlockClosure methodsFor: 'accessing' stamp: 'ajh 1/21/2003 13:16'! isBlock ^ true! ! !BlockClosure methodsFor: 'accessing' stamp: 'eem 5/29/2008 12:18'! method ^outerContext method! ! !BlockClosure methodsFor: 'accessing' stamp: 'eem 5/28/2008 16:02'! numArgs "Answer the number of arguments that must be used to evaluate this block" ^numArgs! ! !BlockClosure methodsFor: 'accessing' stamp: 'eem 9/3/2008 14:07'! numCopiedValues "Answer the number of copied values of the receiver. Since these are stored in the receiver's indexable fields this is the receiver's basic size. Primitive. Answer the number of indexable variables in the receiver. This value is the same as the largest legal subscript." ^self basicSize! ! !BlockClosure methodsFor: 'accessing' stamp: 'eem 5/24/2008 11:21'! outerContext ^outerContext! ! !BlockClosure methodsFor: 'accessing' stamp: 'eem 6/26/2008 09:17'! receiver ^outerContext receiver! ! !BlockClosure methodsFor: 'accessing' stamp: 'eem 6/1/2008 09:39'! startpc ^startpc! ! !BlockClosure methodsFor: 'controlling' stamp: 'jf 9/3/2003 16:45'! doWhileFalse: conditionBlock "Evaluate the receiver once, then again as long the value of conditionBlock is false." | result | [result := self value. conditionBlock value] whileFalse. ^ result! ! !BlockClosure methodsFor: 'controlling' stamp: 'jf 9/3/2003 16:39'! doWhileTrue: conditionBlock "Evaluate the receiver once, then again as long the value of conditionBlock is true." | result | [result := self value. conditionBlock value] whileTrue. ^ result! ! !BlockClosure methodsFor: 'controlling' stamp: 'sma 5/12/2000 13:22'! repeat "Evaluate the receiver repeatedly, ending only if the block explicitly returns." [self value. true] whileTrue! ! !BlockClosure methodsFor: 'controlling' stamp: 'ls 9/24/1999 09:45'! repeatWithGCIf: testBlock | ans | "run the receiver, and if testBlock returns true, garbage collect and run the receiver again" ans := self value. (testBlock value: ans) ifTrue: [ Smalltalk garbageCollect. ans := self value ]. ^ans! ! !BlockClosure methodsFor: 'controlling'! whileFalse "Ordinarily compiled in-line, and therefore not overridable. This is in case the message is sent to other than a literal block. Evaluate the receiver, as long as its value is false." ^ [self value] whileFalse: []! ! !BlockClosure methodsFor: 'controlling'! whileFalse: aBlock "Ordinarily compiled in-line, and therefore not overridable. This is in case the message is sent to other than a literal block. Evaluate the argument, aBlock, as long as the value of the receiver is false." ^ [self value] whileFalse: [aBlock value]! ! !BlockClosure methodsFor: 'controlling' stamp: 'jcg 7/8/2007 18:25'! whileNil: aBlock "Unlike #whileTrue/False: this is not compiled inline." ^ [self value isNil] whileTrue: [aBlock value] ! ! !BlockClosure methodsFor: 'controlling' stamp: 'jcg 7/8/2007 18:25'! whileNotNil: aBlock "Unlike #whileTrue/False: this is not compiled inline." ^ [self value notNil] whileTrue: [aBlock value] ! ! !BlockClosure methodsFor: 'controlling'! whileTrue "Ordinarily compiled in-line, and therefore not overridable. This is in case the message is sent to other than a literal block. Evaluate the receiver, as long as its value is true." ^ [self value] whileTrue: []! ! !BlockClosure methodsFor: 'controlling'! whileTrue: aBlock "Ordinarily compiled in-line, and therefore not overridable. This is in case the message is sent to other than a literal block. Evaluate the argument, aBlock, as long as the value of the receiver is true." ^ [self value] whileTrue: [aBlock value]! ! !BlockClosure methodsFor: 'copying' stamp: 'eem 5/28/2008 14:53'! postCopy "To render a copy safe we need to provide a new outerContext that cannot be returned from and a copy of any remoteTemp vectors. When a block is active it makes no reference to state in its nested contexts (this is the whole point of the indirect temps scheme; any indirect state is either copied or in indirect temp vectors. So we need to substitute a dummy outerContext and copy the copiedValues, copying anything looking like a remote temp vector. if we accidentally copy an Array that isn't actually an indirect temp vector we do extra work but don't break anything." outerContext := MethodContext sender: nil receiver: outerContext receiver method: outerContext method arguments: #(). self fixTemps! ! !BlockClosure methodsFor: 'debugger access' stamp: 'nice 4/14/2009 19:09'! sender "Answer the context that sent the message that created the receiver." ^outerContext sender! ! !BlockClosure methodsFor: 'error handing' stamp: 'eem 11/26/2008 20:03'! numArgsError: numArgsForInvocation | printNArgs | printNArgs := [:n| n printString, ' argument', (n = 1 ifTrue: [''] ifFalse:['s'])]. self error: 'This block accepts ', (printNArgs value: numArgs), ', but was called with ', (printNArgs value: numArgsForInvocation), '.'! ! !BlockClosure methodsFor: 'evaluating' stamp: 'cmm 2/16/2003 16:08'! bench "See how many times I can value in 5 seconds. I'll answer a meaningful description." | startTime endTime count | count := 0. endTime := Time millisecondClockValue + 5000. startTime := Time millisecondClockValue. [ Time millisecondClockValue > endTime ] whileFalse: [ self value. count := count + 1 ]. endTime := Time millisecondClockValue. ^count = 1 ifTrue: [ ((endTime - startTime) // 1000) printString, ' seconds.' ] ifFalse: [ ((count * 1000) / (endTime - startTime)) asFloat printString, ' per second.' ]! ! !BlockClosure methodsFor: 'evaluating' stamp: 'brp 9/25/2003 13:49'! durationToRun "Answer the duration taken to execute this block." ^ Duration milliSeconds: self timeToRun ! ! !BlockClosure methodsFor: 'evaluating' stamp: 'ajh 1/13/2002 13:36'! ifError: errorHandlerBlock "Evaluate the block represented by the receiver, and normally return it's value. If an error occurs, the errorHandlerBlock is evaluated, and it's value is instead returned. The errorHandlerBlock must accept zero, one, or two parameters (the error message and the receiver)." "Examples: [1 whatsUpDoc] ifError: [:err :rcvr | 'huh?']. [1 / 0] ifError: [:err :rcvr | 'ZeroDivide' = err ifTrue: [Float infinity] ifFalse: [self error: err]] " ^ self on: Error do: [:ex | errorHandlerBlock valueWithPossibleArgs: {ex description. ex receiver}]! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 9/5/2009 13:05'! simulateValueWithArguments: anArray caller: aContext | newContext sz | (anArray class ~~ Array or: [numArgs ~= anArray size]) ifTrue: [^ContextPart primitiveFailToken]. newContext := (MethodContext newForMethod: outerContext method) setSender: aContext receiver: outerContext receiver method: outerContext method closure: self startpc: startpc. sz := self basicSize. newContext stackp: sz + numArgs. 1 to: numArgs do: [:i| newContext at: i put: (anArray at: i)]. 1 to: sz do: [:i| newContext at: i + numArgs put: (self at: i)]. ^newContext! ! !BlockClosure methodsFor: 'evaluating' stamp: 'jm 6/3/1998 14:25'! timeToRun "Answer the number of milliseconds taken to execute this block." ^ Time millisecondsToRun: self ! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 9/3/2008 14:09'! value "Activate the receiver, creating a closure activation (MethodContext) whose closure is the receiver and whose caller is the sender of this message. Supply the copied values to the activation as its arguments and copied temps. Primitive. Optional (but you're going to want this for performance)." | newContext ncv | numArgs ~= 0 ifTrue: [self numArgsError: 0]. newContext := self asContextWithSender: thisContext sender. (ncv := self numCopiedValues) > 0 ifTrue: [newContext stackp: ncv. 1 to: ncv do: "nil basicSize = 0" [:i| newContext at: i put: (self at: i)]]. thisContext privSender: newContext! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 9/3/2008 14:09'! value: anArg "Activate the receiver, creating a closure activation (MethodContext) whose closure is the receiver and whose caller is the sender of this message. Supply the argument and copied values to the activation as its arguments and copied temps. Primitive. Optional (but you're going to want this for performance)." | newContext ncv | numArgs ~= 1 ifTrue: [self numArgsError: 1]. newContext := self asContextWithSender: thisContext sender. ncv := self numCopiedValues. newContext stackp: ncv + 1. newContext at: 1 put: anArg. 1 to: ncv do: [:i| newContext at: i + 1 put: (self at: i)]. thisContext privSender: newContext! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 9/3/2008 14:10'! value: firstArg value: secondArg "Activate the receiver, creating a closure activation (MethodContext) whose closure is the receiver and whose caller is the sender of this message. Supply the arguments and copied values to the activation as its arguments and copied temps. Primitive. Optional (but you're going to want this for performance)." | newContext ncv | numArgs ~= 2 ifTrue: [self numArgsError: 2]. newContext := self asContextWithSender: thisContext sender. ncv := self numCopiedValues. newContext stackp: ncv + 2. newContext at: 1 put: firstArg. newContext at: 2 put: secondArg. 1 to: ncv do: [:i| newContext at: i + 2 put: (self at: i)]. thisContext privSender: newContext! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 9/3/2008 14:11'! value: firstArg value: secondArg value: thirdArg "Activate the receiver, creating a closure activation (MethodContext) whose closure is the receiver and whose caller is the sender of this message. Supply the arguments and copied values to the activation as its arguments and copied temps. Primitive. Optional (but you're going to want this for performance)." | newContext ncv | numArgs ~= 3 ifTrue: [self numArgsError: 3]. newContext := self asContextWithSender: thisContext sender. ncv := self numCopiedValues. newContext stackp: ncv + 3. newContext at: 1 put: firstArg. newContext at: 2 put: secondArg. newContext at: 3 put: thirdArg. 1 to: ncv do: [:i| newContext at: i + 3 put: (self at: i)]. thisContext privSender: newContext! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 9/3/2008 14:11'! value: firstArg value: secondArg value: thirdArg value: fourthArg "Activate the receiver, creating a closure activation (MethodContext) whose closure is the receiver and whose caller is the sender of this message. Supply the arguments and copied values to the activation as its arguments and copied temps. Primitive. Optional (but you're going to want this for performance)." | newContext ncv | numArgs ~= 4 ifTrue: [self numArgsError: 4]. newContext := self asContextWithSender: thisContext sender. ncv := self numCopiedValues. newContext stackp: ncv + 4. newContext at: 1 put: firstArg. newContext at: 2 put: secondArg. newContext at: 3 put: thirdArg. newContext at: 4 put: fourthArg. 1 to: ncv do: [:i| newContext at: i + 4 put: (self at: i)]. thisContext privSender: newContext! ! !BlockClosure methodsFor: 'evaluating' stamp: 'al 4/3/2009 18:22'! valueAt: blockPriority "Evaluate the receiver (block), with another priority as the actual one and restore it afterwards. The caller should be careful with using higher priorities." | activeProcess result outsidePriority | activeProcess := Processor activeProcess. outsidePriority := activeProcess priority. activeProcess priority: blockPriority. result := self ensure: [activeProcess priority: outsidePriority]. "Yield after restoring lower priority to give the preempted processes a chance to run." blockPriority > outsidePriority ifTrue: [Processor yield]. ^ result! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 8/22/2008 14:21'! valueNoContextSwitch "An exact copy of BlockClosure>>value except that this version will not preempt the current process on block activation if a higher-priority process is runnable. Primitive. Essential." numArgs ~= 0 ifTrue: [self numArgsError: 0]. self primitiveFailed! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 8/22/2008 14:21'! valueNoContextSwitch: anArg "An exact copy of BlockClosure>>value: except that this version will not preempt the current process on block activation if a higher-priority process is runnable. Primitive. Essential." numArgs ~= 1 ifTrue: [self numArgsError: 1]. self primitiveFailed! ! !BlockClosure methodsFor: 'evaluating' stamp: 'al 4/3/2009 18:23'! valueSupplyingAnswer: anObject ^ (anObject isCollection and: [anObject isString not]) ifTrue: [self valueSupplyingAnswers: {anObject}] ifFalse: [self valueSupplyingAnswers: {{'*'. anObject}}]! ! !BlockClosure methodsFor: 'evaluating' stamp: 'al 4/3/2009 18:24'! valueSupplyingAnswers: aListOfPairs "evaluate the block using a list of questions / answers that might be called upon to automatically respond to Object>>confirm: or FillInTheBlank requests" ^ [self value] on: ProvideAnswerNotification do: [:notify | | answer caption | caption := notify messageText withSeparatorsCompacted. "to remove new lines" answer := aListOfPairs detect: [:each | caption = each first or: [(caption includesSubstring: each first caseSensitive: false) or: [(each first match: caption) or: [(String includesSelector: #matchesRegex:) and: [caption matchesRegex: each first]]]]] ifNone: [nil]. answer ifNotNil: [notify resume: answer second] ifNil: [ | outerAnswer | outerAnswer := ProvideAnswerNotification signal: notify messageText. outerAnswer ifNil: [notify resume] ifNotNil: [notify resume: outerAnswer]]]! ! !BlockClosure methodsFor: 'evaluating' stamp: 'jrp 10/10/2004 22:28'! valueSuppressingAllMessages ^ self valueSuppressingMessages: #('*')! ! !BlockClosure methodsFor: 'evaluating' stamp: 'al 4/3/2009 18:24'! valueSuppressingMessages: aListOfStrings ^ self valueSuppressingMessages: aListOfStrings supplyingAnswers: #()! ! !BlockClosure methodsFor: 'evaluating' stamp: 'al 4/3/2009 18:24'! valueSuppressingMessages: aListOfStrings supplyingAnswers: aListOfPairs ^ self valueSupplyingAnswers: aListOfPairs, (aListOfStrings collect: [:each | {each. true}])! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 9/3/2008 14:08'! valueWithArguments: anArray "Activate the receiver, creating a closure activation (MethodContext) whose closure is the receiver and whose caller is the sender of this message. Supply the arguments in an anArray and copied values to the activation as its arguments and copied temps. Primitive. Optional (but you're going to want this for performance)." | newContext ncv | numArgs ~= anArray size ifTrue: [self numArgsError: anArray size]. newContext := self asContextWithSender: thisContext sender. ncv := self numCopiedValues. newContext stackp: ncv + numArgs. 1 to: numArgs do: [:i| newContext at: i put: (anArray at: i)]. 1 to: ncv do: [:i| newContext at: i + numArgs put: (self at: i)]. thisContext privSender: newContext! ! !BlockClosure methodsFor: 'evaluating' stamp: 'nk 3/11/2001 11:49'! valueWithEnoughArguments: anArray "call me with enough arguments from anArray" | args | (anArray size == self numArgs) ifTrue: [ ^self valueWithArguments: anArray ]. args := Array new: self numArgs. args replaceFrom: 1 to: (anArray size min: args size) with: anArray startingAt: 1. ^ self valueWithArguments: args! ! !BlockClosure methodsFor: 'evaluating' stamp: 'md 3/28/2006 20:17'! valueWithExit self value: [ ^nil ]! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 5/28/2008 15:03'! valueWithPossibleArgs: anArray ^numArgs = 0 ifTrue: [self value] ifFalse: [self valueWithArguments: (numArgs = anArray size ifTrue: [anArray] ifFalse: [numArgs > anArray size ifTrue: [anArray, (Array new: numArgs - anArray size)] ifFalse: [anArray copyFrom: 1 to: numArgs]])]! ! !BlockClosure methodsFor: 'evaluating' stamp: 'eem 5/25/2008 14:47'! valueWithPossibleArgument: anArg "Evaluate the block represented by the receiver. If the block requires one argument, use anArg, if it requires more than one, fill up the rest with nils." | a | numArgs = 0 ifTrue: [^self value]. numArgs = 1 ifTrue: [^self value: anArg]. a := Array new: numArgs. a at: 1 put: anArg. ^self valueWithArguments: a! ! !BlockClosure methodsFor: 'evaluating' stamp: 'ar 8/17/2007 13:15'! valueWithin: aDuration onTimeout: timeoutBlock "Evaluate the receiver. If the evaluation does not complete in less than aDuration evaluate the timeoutBlock instead" | theProcess delay watchdog | aDuration <= Duration zero ifTrue: [^ timeoutBlock value ]. "the block will be executed in the current process" theProcess := Processor activeProcess. delay := aDuration asDelay. "make a watchdog process" watchdog := [ delay wait. "wait for timeout or completion" theProcess ifNotNil:[ theProcess signalException: TimedOut ] ] newProcess. "Watchdog needs to run at high priority to do its job (but not at timing priority)" watchdog priority: Processor timingPriority-1. "catch the timeout signal" ^ [ watchdog resume. "start up the watchdog" self ensure:[ "evaluate the receiver" theProcess := nil. "it has completed, so ..." delay delaySemaphore signal. "arrange for the watchdog to exit" ]] on: TimedOut do: [ :e | timeoutBlock value ]. ! ! !BlockClosure methodsFor: 'exceptions' stamp: 'sma 5/11/2000 19:38'! assert self assert: self! ! !BlockClosure methodsFor: 'exceptions' stamp: 'eem 8/22/2008 14:22'! ensure: aBlock "Evaluate a termination block after evaluating the receiver, regardless of whether the receiver's evaluation completes." | returnValue b | returnValue := self valueNoContextSwitch. "aBlock wasn't nil when execution of this method began; it is nil'd out by the unwind machinery, and that's how we know it's already been evaluated ... otherwise, obviously, it needs to be evaluated" aBlock == nil ifFalse: [ "nil out aBlock temp before evaluating aBlock so it is not executed again if aBlock remote returns" b := aBlock. thisContext tempAt: 1 put: nil. "Could be aBlock := nil, but arguments cannot be modified" b value. ]. ^ returnValue! ! !BlockClosure methodsFor: 'exceptions' stamp: 'eem 8/22/2008 14:29'! ifCurtailed: aBlock "Evaluate the receiver with an abnormal termination action. Evaluate aBlock only if execution is unwound during execution of the receiver. If execution of the receiver finishes normally do not evaluate aBlock." ^self valueNoContextSwitch! ! !BlockClosure methodsFor: 'exceptions' stamp: 'ajh 2/1/2003 00:30'! on: exception do: handlerAction "Evaluate the receiver in the scope of an exception handler." | handlerActive | "just a marker, fail and execute the following" handlerActive := true. ^ self value! ! !BlockClosure methodsFor: 'exceptions' stamp: 'ajh 10/9/2001 16:51'! onDNU: selector do: handleBlock "Catch MessageNotUnderstood exceptions but only those of the given selector (DNU stands for doesNotUnderstand:)" ^ self on: MessageNotUnderstood do: [:exception | exception message selector = selector ifTrue: [handleBlock valueWithPossibleArgs: {exception}] ifFalse: [exception pass] ]! ! !BlockClosure methodsFor: 'exceptions' stamp: 'ajh 7/26/2002 11:49'! valueUninterruptably "Prevent remote returns from escaping the sender. Even attempts to terminate (unwind) this process will be halted and the process will resume here. A terminate message is needed for every one of these in the sender chain to get the entire process unwound." ^ self ifCurtailed: [^ self]! ! !BlockClosure methodsFor: 'initialize-release' stamp: 'eem 9/3/2008 14:08'! outerContext: aContext startpc: aStartpc numArgs: argCount copiedValues: anArrayOrNil outerContext := aContext. startpc := aStartpc. numArgs := argCount. 1 to: self numCopiedValues do: [:i| self at: i put: (anArrayOrNil at: i)]! ! !BlockClosure methodsFor: 'printing' stamp: 'stephane.ducasse 4/21/2009 11:52'! asText ^ self asString asText! ! !BlockClosure methodsFor: 'printing' stamp: 'eem 7/28/2008 14:06'! decompile ^Decompiler new decompileBlock: self! ! !BlockClosure methodsFor: 'printing' stamp: 'eem 7/28/2008 14:09'! fullPrintOn: aStream aStream print: self; cr. (self decompile ifNil: ['--source missing--']) printOn: aStream indent: 0! ! !BlockClosure methodsFor: 'printing' stamp: 'eem 5/24/2008 11:23'! printOn: aStream aStream nextPutAll: '[closure] in '. outerContext printOn: aStream! ! !BlockClosure methodsFor: 'scheduling' stamp: 'eem 5/28/2008 16:16'! asContext "Create a MethodContext that is ready to execute self. Assumes self takes no args (if it does the args will be nil)" ^self asContextWithSender: nil! ! !BlockClosure methodsFor: 'scheduling' stamp: 'ajh 7/15/2001 16:03'! fork "Create and schedule a Process running the code in the receiver." ^ self newProcess resume! ! !BlockClosure methodsFor: 'scheduling' stamp: 'ajh 10/16/2002 11:14'! forkAndWait "Suspend current process and execute self in new process, when it completes resume current process" | semaphore | semaphore := Semaphore new. [self ensure: [semaphore signal]] fork. semaphore wait. ! ! !BlockClosure methodsFor: 'scheduling' stamp: 'ajh 9/29/2001 21:00'! forkAt: priority "Create and schedule a Process running the code in the receiver at the given priority. Answer the newly created process." ^ self newProcess priority: priority; resume! ! !BlockClosure methodsFor: 'scheduling' stamp: 'svp 6/23/2003 10:59'! forkAt: priority named: name "Create and schedule a Process running the code in the receiver at the given priority and having the given name. Answer the newly created process." | forkedProcess | forkedProcess := self newProcess. forkedProcess priority: priority. forkedProcess name: name. ^ forkedProcess resume! ! !BlockClosure methodsFor: 'scheduling' stamp: 'svp 6/23/2003 10:59'! forkNamed: aString "Create and schedule a Process running the code in the receiver and having the given name." ^ self newProcess name: aString; resume! ! !BlockClosure methodsFor: 'scheduling' stamp: 'ajh 2/10/2003 14:25'! newProcess "Answer a Process running the code in the receiver. The process is not scheduled." "Simulation guard" ^Process forContext: [self value. Processor terminateActive] asContext priority: Processor activePriority! ! !BlockClosure methodsFor: 'scheduling' stamp: 'marcus.denker 6/10/2009 20:28'! newProcessWith: anArray "Answer a Process running the code in the receiver. The receiver's block arguments are bound to the contents of the argument, anArray. The process is not scheduled." "Simulation guard" ^Process forContext: [self valueWithArguments: anArray. Processor terminateActive] asContext priority: Processor activePriority! ! !BlockClosure methodsFor: 'testing' stamp: 'eem 5/29/2008 12:20'! hasMethodReturn "Answer whether the receiver has a method-return ('^') in its code." | myMethod scanner preceedingBytecodeMessage end | "Determine end of block from the instruction preceding it. Find the instruction by using an MNU handler to capture the instruction message sent by the scanner." myMethod := outerContext method. scanner := InstructionStream new method: myMethod pc: myMethod initialPC. [scanner pc < startpc] whileTrue: [[scanner interpretNextInstructionFor: nil] on: MessageNotUnderstood do: [:ex| preceedingBytecodeMessage := ex message]]. end := preceedingBytecodeMessage arguments last + startpc - 1. scanner method: myMethod pc: startpc. scanner scanFor: [:byte | (byte between: 120 and: 124) or: [scanner pc > end]]. ^scanner pc <= end! ! !BlockClosure methodsFor: 'testing' stamp: 'eem 5/23/2008 13:48'! isClosure ^true! ! !BlockClosure methodsFor: 'testing' stamp: 'eem 11/26/2008 20:27'! isDead "Has self finished" ^false! ! !BlockClosure methodsFor: 'private' stamp: 'eem 6/11/2008 11:38'! asContextWithSender: aContext "Inner private support method for evaluation. Do not use unless you know what you're doing." ^(MethodContext newForMethod: outerContext method) setSender: aContext receiver: outerContext receiver method: outerContext method closure: self startpc: startpc! ! !BlockClosure methodsFor: 'private' stamp: 'sd 3/22/2009 19:33'! asMinimalRepresentation "Answer the receiver." ^self! ! !BlockClosure methodsFor: 'private' stamp: 'eem 5/28/2008 14:50'! copyForSaving "Answer a copy of the receiver suitable for serialization. Notionally, if the receiver's outerContext has been returned from then nothing needs to be done and we can use the receiver. But there's a race condition determining if the receiver has been returned from (it could be executing in a different process). So answer a copy anyway." ^self shallowCopy postCopy! ! !BlockClosure methodsFor: 'private' stamp: 'eem 12/14/2008 16:47'! fixTemps "Fix the values of the temporary variables used in the block that are ordinarily shared with the method in which the block is defined. This is a no-op for closures, provided for backward-compatibility with old BlockContexts that needed the fixTemps hack to persist."! ! !BlockClosure methodsFor: 'private' stamp: 'sd 3/22/2009 19:33'! isValid "Answer the receiver." ^true! ! !BlockClosure methodsFor: 'private' stamp: 'eem 5/28/2008 14:56'! reentrant "Answer a version of the recever that can be reentered. Closures are reentrant (unlike BlockContect) so simply answer self." ^self! ! !BlockClosure methodsFor: 'private' stamp: 'ar 3/2/2001 01:16'! valueUnpreemptively "Evaluate the receiver (block), without the possibility of preemption by higher priority processes. Use this facility VERY sparingly!!" "Think about using Block>>valueUninterruptably first, and think about using Semaphore>>critical: before that, and think about redesigning your application even before that!! After you've done all that thinking, go right ahead and use it..." | activeProcess oldPriority result | activeProcess := Processor activeProcess. oldPriority := activeProcess priority. activeProcess priority: Processor highestPriority. result := self ensure: [activeProcess priority: oldPriority]. "Yield after restoring priority to give the preempted processes a chance to run" Processor yield. ^result! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BlockClosure class instanceVariableNames: ''! !BlockClosure class methodsFor: 'instance creation' stamp: 'eem 9/3/2008 14:02'! outerContext: aContext startpc: aStartpc numArgs: argCount copiedValues: anArrayOrNil ^(self new: anArrayOrNil basicSize) outerContext: aContext startpc: aStartpc numArgs: argCount copiedValues: anArrayOrNil! ! TestCase subclass: #BlockClosuresTestCase instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'! !BlockClosuresTestCase commentStamp: '' prior: 0! This test case collects examples for block uses that require full block closures.! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'rw 1/26/2002 01:20'! constructCannotReturnBlockInDeadFrame ^ [:arg | ^arg]. ! ! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'rw 1/26/2002 01:14'! constructFibonacciBlockInDeadFrame | fib | fib := [:val | (val <= 0) ifTrue: [self error: 'not a natural number']. (val <= 2) ifTrue: [1] ifFalse: [(fib value: (val - 1)) + (fib value: (val - 2))]]. ^fib ! ! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'rw 1/26/2002 01:14'! constructFibonacciBlockWithBlockArgumentInDeadFrame ^ [:val :blk | (val <= 0) ifTrue: [self error: 'not a natural number']. (val <= 2) ifTrue: [1] ifFalse: [(blk value: (val - 1) value: blk) + (blk value: (val - 2) value: blk)]]. ! ! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'rw 1/26/2002 01:15'! constructSharedClosureEnvironmentInDeadFrame |array result| result := 10. array := Array new: 2. array at: 1 put: [:arg | result := arg]. array at: 2 put: [result]. ^array ! ! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'BG 1/24/2002 17:44'! continuationExample1: aCollection " see comment below. Here we simply collect the values of a value with continuation block " | streamCreator collector | streamCreator := [:collection | | i localBlock | i := 1. localBlock := [ | current | current := collection at: i. i := i + 1. Array with: current with: (i<= collection size ifTrue: [localBlock] ifFalse: [nil]) ]. ]. collector := [:valueWithContinuation | | oc | oc := OrderedCollection new. [ | local | local := valueWithContinuation value. oc add: local first. local last notNil] whileTrue: []. oc. ]. ^collector value: (streamCreator value: aCollection). "The continuation examples are examples of a 'back to LISP' style. These examples use blocks to process the elements of a collection in a fashion that is similar to streaming. The creator block creates a blocks that act like a stream. In the following, this block is called a 'value with continuation block'. When such a value with continuation block receives the message value, it returns a Array of two elements, the value and the continuation 1. the next collection element 2. a so-called continuation, which is either nil or a block that can return the next value with continuation. To collect all elements of a value with continuation stream, use the collector block. " ! ! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'BG 1/24/2002 17:44'! continuationExample2: aCollection " see comment in method continuationExample1:. The block named 'processor' takes a value with contiuation and a processing block. It creates a new value with continuation. Again we use a collector to collect all values. " | stream processor collector | stream := [:collection | | i localBlock | i := 1. localBlock := [ | current | current := collection at: i. i := i + 1. Array with: current with: (i<= collection size ifTrue: [localBlock] ifFalse: [nil]) ]. ]. processor := [:valueWithContinuation :activity | | localBlock | localBlock := [ | current | current := valueWithContinuation value. Array with: (activity value: current first) with: (current last notNil ifTrue: [localBlock])]. localBlock ]. collector := [:valueWithContinuation | | oc | oc := OrderedCollection new. [ | local | local := valueWithContinuation value. oc add: local first. local last notNil] whileTrue: []. oc. ]. ^collector value: (processor value: (stream value: aCollection) value: [:x | x * x]).! ! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'BG 1/24/2002 17:27'! continuationExample3: aCollection " see comment in method continuationExample1:. The block named 'processor' takes a value with contiuation and a processing block. It creates a new value with continuation. Here we set up a chain of three values with continuation: one data source and two value processors. Again we use a collector to collect all values. " | stream processor collector | stream := [:collection | | i localBlock | i := 1. localBlock := [ | current | current := collection at: i. i := i + 1. Array with: current with: (i<= collection size ifTrue: [localBlock] ifFalse: [nil]) ]. ]. processor := [:valueWithContinuation :activity | | localBlock | localBlock := [ | current | current := valueWithContinuation value. Array with: (activity value: current first) with: (current last notNil ifTrue: [localBlock])]. localBlock ]. collector := [:valueWithContinuation | | oc | oc := OrderedCollection new. [ | local | local := valueWithContinuation value. oc add: local first. local last notNil] whileTrue: []. oc. ]. ^collector value: (processor value: (processor value: (stream value: aCollection) value: [:x | x * x]) value: [:x | x - 10]).! ! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'BG 1/24/2002 17:44'! example1: anInteger " this example is very simple. A named block recursively computes the factorial. The example tests whether the value of x is still available after the recursive call. Note that the recursive call precedes the multiplication. For the purpose of the test this is essential. (When you commute the factors, the example will work also in some system without block closures, but not in Squeak.) " | factorial | factorial := [:x | x = 1 ifTrue: [1] ifFalse: [(factorial value: x - 1)* x]]. ^ factorial value: anInteger ! ! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'lr 3/31/2009 09:31'! example2: anInteger " BlockClosuresTestCase new example2: 6" " to complicate the example1, we set up a dynamic reference chain that is used to dump all calls of facorial when recursion depth is maximal. The return value is an instance of orderedCollection, the trace. " | factorial trace | trace := OrderedCollection new. factorial := [:x :dumper :trace2 | | localDumper | localDumper := [ :collection | collection add: x. dumper value: collection.]. x = 1 ifTrue: [localDumper value: trace2. 1] ifFalse: [(factorial value: x - 1 value: localDumper value: trace2)* x. ] ]. factorial value: anInteger value: [ :collection | ] value: trace. ^trace! ! !BlockClosuresTestCase methodsFor: 'examples' stamp: 'PeterHugossonMiller 9/2/2009 16:19'! nestedLoopsExample: arrays " A while ago, Hans Baveco asked for a way to dynamically nest loops. Better solutions than this one were proposed, but this one is a beautiful test for recursive block usage. " | result sizeOfResult streams block | "arrays := OrderedCollection new. arrays add: #(#a #b); add: #(1 2 3 4); add: #('w' 'x' 'y' 'z')." sizeOfResult := arrays inject: 1 into: [:prod :array | prod * array size]. streams := arrays collect: [:a | a readStream]. " This is an OrderedCollection of Streams " result := OrderedCollection new: sizeOfResult. block := [:r :tupel :allStreams | | innerBlock | innerBlock := [:myIdx | [myIdx = allStreams size ifTrue: [1 to: allStreams size do: [:i | tupel at: i put: (allStreams at: i) peek]. r addLast: tupel shallowCopy] ifFalse: [innerBlock value: myIdx + 1]. (allStreams at: myIdx) next. (allStreams at: myIdx) atEnd ] whileFalse: []. (allStreams at: myIdx) reset. ]. innerBlock value: 1. r ]. block value: result value: (Array new: streams size) " this is a buffer " value: streams. ^result ! ! !BlockClosuresTestCase methodsFor: 'jensen device examples' stamp: 'BG 1/25/2002 10:01'! comment " The Jensen device was something very sophisticated in the days of Algol 60. Essentially it was tricky use of a parameter passing policy that was called 'call by name'. In modern terminology, a call by name parameter was a pair of blocks (in a system with full block closures, of course.) For the lovers of Algol 60, here is a short example: BEGIN REAL PROCEDURE JensenSum (A, I, N); REAL A; INTEGER I, N; BEGIN REAL S; S := 0.0; FOR I := 1 STEP 1 UNTIL N DO S := S + A; JensenSum := S; END; ARRAY X [1:10], Y[1:10, 1:10]; COMMENT Do array initialization here ; JensenSum (X[I], I, 10); JensenSum (Y[I, I], I, 10); JensenSum(JensenSum(Y[I, J], J, 10), I, 10); END; The first call sums the elements of X, the second sums the diagonal elements of Y and the third call sums up all elements of Y. It is possible to reimplement all this with blocks only and that is what is done in the jensen device examples. Additional remark: The Jensen device was something for clever minds. I remember an artice written by Donald Knuth and published in the Communications of the ACM (I think in 1962, but I may err) about that programming trick. That article showed how a simple procedure (called the general problem solver) could be used to do almost anything. The problem was of course to find out the right parameters. I seached my collection of photocopies for that article, but regrettably I could not find it. Perhaps I can find it later. "! ! !BlockClosuresTestCase methodsFor: 'jensen device examples' stamp: 'BG 1/24/2002 18:00'! gpsExample1: aCollection " BlockClosuresTestCase new gpsExample1: (1 to: 100) asArray" | gps i s | gps := [:idx :exp :sum | | cnt | cnt := 1. sum first value: 0. [idx first value: cnt. sum first value: (sum last value + exp last value). cnt := cnt + 1. cnt <= aCollection size] whileTrue: [ ]. sum last value ]. ^gps value: (Array with: [:val | i := val] with: [ i]) value: (Array with: [:val | aCollection at: i put: val] with: [ aCollection at: i]) value: (Array with: [:val | s := val] with: [ s]) ! ! !BlockClosuresTestCase methodsFor: 'jensen device examples' stamp: 'BG 1/25/2002 10:03'! gpsExample2: aCollection " BlockClosuresTestCase new gpsExample2: #(#(1 2 3 4 5) #(6 7 8 9 10) #(11 12 13 14 15) #(16 17 18 19 20) #(21 22 23 24 25))" | js i j | " js is the translation of the Algol procedure from method comment. " js := [:a :idx :n | | sum | sum := 0. idx first value: 1. [idx last value <= n last value] whileTrue: [sum := sum + a last value. idx first value: idx last value + 1.]. sum ]. " This is the most complicated call that is mentioned in method comment. Note that js is called recursively. " ^ js value: (Array with: [:val | self error: 'can not assign to procedure'] with: [ js value: (Array with: [:val | (aCollection at: i) at: j put: val] with: [ (aCollection at: i) at: j]) value: (Array with:[:val | j := val] with: [ j]) value: (Array with: [:val | self error: 'can not assign to constant'] with: [ aCollection size]) ] ) value: (Array with:[:val | i := val] with: [ i]) value: (Array with: [:val | self error: 'can not assign to constant'] with: [ aCollection size]) ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'rw 1/26/2002 01:22'! testCannotReturn | blk | blk := self constructCannotReturnBlockInDeadFrame. self should: [blk value: 1] raise: Exception ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'BG 1/24/2002 17:45'! testContinuationExample1 | array | array := (1 to: 20) asOrderedCollection. self assert: ((self continuationExample1: array) = array) ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'BG 1/24/2002 17:45'! testContinuationExample2 | array | array := (1 to: 20) asOrderedCollection. self assert: ((self continuationExample2: array) = (array collect: [:x | x * x])) ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'BG 1/24/2002 17:45'! testContinuationExample3 | array | array := (1 to: 20) asOrderedCollection. self assert: ((self continuationExample3: array) = (array collect: [:x | x * x - 10])) ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'BG 1/24/2002 16:05'! testExample1 self assert: ((self example1: 5) = 5 factorial) ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'BG 1/24/2002 18:28'! testExample2 self assert: ((self example2: 5) = (1 to: 5) asOrderedCollection) ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'BG 1/24/2002 17:59'! testGpsExample1 | result array | array := (1 to: 100) asArray. result := array inject: 0 into: [:sum :val | sum + val]. self assert: ((self gpsExample1: array) = result) ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'BG 1/25/2002 09:57'! testGpsExample2 | result array | " integer matrix elements should be used for the purpose of this test. " array := #(#(1 2 3 4 5) #(6 7 8 9 10) #(11 12 13 14 15) #(16 17 18 19 20) #(21 22 23 24 25)). result := array inject: 0 into: [:sum :subarray | sum + (subarray inject: 0 into: [:s :elem | s + elem])]. self assert: ((self gpsExample2: array) = result) ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'BG 1/24/2002 16:40'! testNestedLoopsExample1 | arrays result | arrays := OrderedCollection new. arrays add: #(#a #b); add: #(1 2 3 4); add: #('w' 'x' 'y' 'z'). result := OrderedCollection new. CollectionCombinator new forArrays: arrays processWith: [:item |result addLast: item]. self assert: ((self nestedLoopsExample: arrays) = result) ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'rw 1/26/2002 01:17'! testReentrantBlock | fib | fib := [:val | (val <= 0) ifTrue: [self error: 'not a natural number']. (val <= 2) ifTrue: [1] ifFalse: [(fib value: (val - 1)) + (fib value: (val - 2))]]. self should: [fib value: 0] raise: TestResult error. self assert: ((fib value: 1) == 1). self assert: ((fib value: 2) == 1). self assert: ((fib value: 3) == 2). self assert: ((fib value: 4) == 3). self assert: ((fib value: 5) == 5). self assert: ((fib value: 6) == 8). ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'rw 1/26/2002 01:17'! testReentrantBlockOldEnvironment | fib | fib := self constructFibonacciBlockInDeadFrame. self should: [fib value: 0] raise: TestResult error. self assert: ((fib value: 1) == 1). self assert: ((fib value: 2) == 1). self assert: ((fib value: 3) == 2). self assert: ((fib value: 4) == 3). self assert: ((fib value: 5) == 5). self assert: ((fib value: 6) == 8). ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'rw 1/26/2002 01:18'! testReentrantBlockOldEnvironmentWithBlockArguement | fib | fib := self constructFibonacciBlockWithBlockArgumentInDeadFrame. self should: [fib value: 0 value: fib] raise: TestResult error. self assert: ((fib value: 1 value: fib) == 1). self assert: ((fib value: 2 value: fib) == 1). self assert: ((fib value: 3 value: fib) == 2). self assert: ((fib value: 4 value: fib) == 3). self assert: ((fib value: 5 value: fib) == 5). self assert: ((fib value: 6 value: fib) == 8). ! ! !BlockClosuresTestCase methodsFor: 'testing' stamp: 'rw 1/26/2002 01:18'! testSharedClosureEnvironment |blockArray| blockArray := self constructSharedClosureEnvironmentInDeadFrame. self assert: ((blockArray at: 2) value == 10). self assert: (((blockArray at: 1) value: 5) == 5). self assert: ((blockArray at: 2) value == 5). ! ! ContextPart variableSubclass: #BlockContext instanceVariableNames: 'nargs startpc home' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Methods'! !BlockContext commentStamp: '' prior: 0! My instances function similarly to instances of MethodContext, but they hold the dynamic state for execution of a block in Smalltalk. They access all temporary variables and the method sender via their home pointer, so that those values are effectively shared. Their indexable part is used to store their independent value stack during execution. My instance must hold onto its home in order to work. This can cause circularities if the home is also pointing (via a temp, perhaps) to the instance. In the rare event that this happens (as in SortedCollection sortBlock:) the message fixTemps will replace home with a copy of home, thus defeating the sharing of temps but, nonetheless, eliminating the circularity. BlockContexts must only be created using the method newForMethod:. Note that it is impossible to determine the real object size of a BlockContext except by asking for the frameSize of its method. Any fields above the stack pointer (stackp) are truly invisible -- even (and especially!!) to the garbage collector. Any store into stackp other than by the primitive method stackp: is potentially fatal.! !BlockContext methodsFor: '*Polymorph-EventEnhancements' stamp: 'gvc 10/26/2005 16:16'! asMinimalRepresentation "Answer the receiver." ^self! ! !BlockContext methodsFor: '*Polymorph-EventEnhancements' stamp: 'gvc 10/26/2005 15:52'! isValid "Answer true so we can be used in event dispatching." ^true! ! !BlockContext methodsFor: '*services-base' stamp: 'rr 3/21/2006 11:53'! valueWithRequestor: aRequestor "To do later: make the fillInTheBlank display more informative captions. Include the description of the service, and maybe record steps" ^ self numArgs isZero ifTrue: [self value] ifFalse: [self value: aRequestor]! ! !BlockContext methodsFor: '*splitjoin' stamp: 'onierstrasz 4/12/2009 20:12'! split: aSequenceableCollection | result position | result := OrderedCollection new. position := 1. aSequenceableCollection withIndexDo: [:element :idx | (self value: element) ifTrue: [result add: (aSequenceableCollection copyFrom: position to: idx - 1). position := idx + 1]]. result add: (aSequenceableCollection copyFrom: position to: aSequenceableCollection size). ^ result! ! !BlockContext methodsFor: 'accessing' stamp: 'eem 5/28/2008 10:43'! activeHome "Search senders for the home context. If the home context is not found on the sender chain answer nil." ^self caller findContextSuchThat: [:ctxt | ctxt = home]! ! !BlockContext methodsFor: 'accessing' stamp: 'GabrielOmarCotelli 5/25/2009 15:52'! argumentCount "Added for ANSI compatibility." ^ self numArgs! ! !BlockContext methodsFor: 'accessing' stamp: 'eem 5/29/2008 13:14'! caller ^sender! ! !BlockContext methodsFor: 'accessing' stamp: 'eem 5/24/2008 11:20'! closureHome "Answer the context from which an ^-return should return from." ^self home! ! !BlockContext methodsFor: 'accessing' stamp: 'eem 6/15/2008 11:32'! contextForLocalVariables "Answer the context in which local variables (temporaries) are stored." ^home! ! !BlockContext methodsFor: 'accessing' stamp: 'di 9/9/2000 10:44'! copyForSaving "Fix the values of the temporary variables used in the block that are ordinarily shared with the method in which the block is defined." home := home copy. home swapSender: nil! ! !BlockContext methodsFor: 'accessing'! fixTemps "Fix the values of the temporary variables used in the block that are ordinarily shared with the method in which the block is defined." home := home copy. home swapSender: nil! ! !BlockContext methodsFor: 'accessing' stamp: 'md 4/27/2006 15:14'! hasInstVarRef "Answer whether the receiver references an instance variable." | method scanner end printer | home ifNil: [^false]. method := self method. end := self endPC. scanner := InstructionStream new method: method pc: startpc. printer := InstVarRefLocator new. [scanner pc <= end] whileTrue: [ (printer interpretNextInstructionUsing: scanner) ifTrue: [^true]. ]. ^false! ! !BlockContext methodsFor: 'accessing'! hasMethodReturn "Answer whether the receiver has a return ('^') in its code." | method scanner end | method := self method. "Determine end of block from long jump preceding it" end := (method at: startpc-2)\\16-4*256 + (method at: startpc-1) + startpc - 1. scanner := InstructionStream new method: method pc: startpc. scanner scanFor: [:byte | (byte between: 120 and: 124) or: [scanner pc > end]]. ^scanner pc <= end! ! !BlockContext methodsFor: 'accessing'! home "Answer the context in which the receiver was defined." ^home! ! !BlockContext methodsFor: 'accessing' stamp: 'ajh 1/21/2003 13:16'! isBlock ^ true! ! !BlockContext methodsFor: 'accessing' stamp: 'ajh 1/31/2003 12:12'! isExecutingBlock ^ true! ! !BlockContext methodsFor: 'accessing'! method "Answer the compiled method in which the receiver was defined." ^home method! ! !BlockContext methodsFor: 'accessing' stamp: 'eem 6/15/2008 11:33'! methodReturnContext "Answer the context from which an ^-return should return from." ^home! ! !BlockContext methodsFor: 'accessing' stamp: 'mdr 4/10/2001 10:34'! numArgs "Answer the number of arguments that must be used to evaluate this block" ^nargs! ! !BlockContext methodsFor: 'accessing'! receiver "Refer to the comment in ContextPart|receiver." ^home receiver! ! !BlockContext methodsFor: 'accessing' stamp: 'ajh 1/30/2003 15:45'! reentrant "Copy before calling so multiple activations can exist" ^ self copy! ! !BlockContext methodsFor: 'accessing'! tempAt: index "Refer to the comment in ContextPart|tempAt:." ^home at: index! ! !BlockContext methodsFor: 'accessing'! tempAt: index put: value "Refer to the comment in ContextPart|tempAt:put:." ^home at: index put: value! ! !BlockContext methodsFor: 'accessing' stamp: 'md 2/9/2007 19:11'! tempNamed: aName ^self home tempNamed: aName! ! !BlockContext methodsFor: 'accessing' stamp: 'md 2/9/2007 19:12'! tempNamed: aName put: anObject ^self home tempNamed: aName put: anObject! ! !BlockContext methodsFor: 'controlling' stamp: 'jf 9/3/2003 16:45'! doWhileFalse: conditionBlock "Evaluate the receiver once, then again as long the value of conditionBlock is false." | result | [result := self value. conditionBlock value] whileFalse. ^ result! ! !BlockContext methodsFor: 'controlling' stamp: 'jf 9/3/2003 16:39'! doWhileTrue: conditionBlock "Evaluate the receiver once, then again as long the value of conditionBlock is true." | result | [result := self value. conditionBlock value] whileTrue. ^ result! ! !BlockContext methodsFor: 'controlling' stamp: 'sma 5/12/2000 13:22'! repeat "Evaluate the receiver repeatedly, ending only if the block explicitly returns." [self value. true] whileTrue! ! !BlockContext methodsFor: 'controlling' stamp: 'ls 9/24/1999 09:45'! repeatWithGCIf: testBlock | ans | "run the receiver, and if testBlock returns true, garbage collect and run the receiver again" ans := self value. (testBlock value: ans) ifTrue: [ Smalltalk garbageCollect. ans := self value ]. ^ans! ! !BlockContext methodsFor: 'controlling'! whileFalse "Ordinarily compiled in-line, and therefore not overridable. This is in case the message is sent to other than a literal block. Evaluate the receiver, as long as its value is false." ^ [self value] whileFalse: []! ! !BlockContext methodsFor: 'controlling'! whileFalse: aBlock "Ordinarily compiled in-line, and therefore not overridable. This is in case the message is sent to other than a literal block. Evaluate the argument, aBlock, as long as the value of the receiver is false." ^ [self value] whileFalse: [aBlock value]! ! !BlockContext methodsFor: 'controlling'! whileTrue "Ordinarily compiled in-line, and therefore not overridable. This is in case the message is sent to other than a literal block. Evaluate the receiver, as long as its value is true." ^ [self value] whileTrue: []! ! !BlockContext methodsFor: 'controlling'! whileTrue: aBlock "Ordinarily compiled in-line, and therefore not overridable. This is in case the message is sent to other than a literal block. Evaluate the argument, aBlock, as long as the value of the receiver is true." ^ [self value] whileTrue: [aBlock value]! ! !BlockContext methodsFor: 'evaluating' stamp: 'cmm 2/16/2003 16:08'! bench "See how many times I can value in 5 seconds. I'll answer a meaningful description." | startTime endTime count | count := 0. endTime := Time millisecondClockValue + 5000. startTime := Time millisecondClockValue. [ Time millisecondClockValue > endTime ] whileFalse: [ self value. count := count + 1 ]. endTime := Time millisecondClockValue. ^count = 1 ifTrue: [ ((endTime - startTime) // 1000) printString, ' seconds.' ] ifFalse: [ ((count * 1000) / (endTime - startTime)) asFloat printString, ' per second.' ]! ! !BlockContext methodsFor: 'evaluating' stamp: 'brp 9/25/2003 13:49'! durationToRun "Answer the duration taken to execute this block." ^ Duration milliSeconds: self timeToRun ! ! !BlockContext methodsFor: 'evaluating' stamp: 'ajh 1/13/2002 13:36'! ifError: errorHandlerBlock "Evaluate the block represented by the receiver, and normally return it's value. If an error occurs, the errorHandlerBlock is evaluated, and it's value is instead returned. The errorHandlerBlock must accept zero, one, or two parameters (the error message and the receiver)." "Examples: [1 whatsUpDoc] ifError: [:err :rcvr | 'huh?']. [1 / 0] ifError: [:err :rcvr | 'ZeroDivide' = err ifTrue: [Float infinity] ifFalse: [self error: err]] " ^ self on: Error do: [:ex | errorHandlerBlock valueWithPossibleArgs: {ex description. ex receiver}]! ! !BlockContext methodsFor: 'evaluating' stamp: 'jm 6/3/1998 14:25'! timeToRun "Answer the number of milliseconds taken to execute this block." ^ Time millisecondsToRun: self ! ! !BlockContext methodsFor: 'evaluating'! value "Primitive. Evaluate the block represented by the receiver. Fail if the block expects any arguments or if the block is already being executed. Optional. No Lookup. See Object documentation whatIsAPrimitive." ^self valueWithArguments: #()! ! !BlockContext methodsFor: 'evaluating' stamp: 'nk 3/11/2001 11:49'! valueWithEnoughArguments: anArray "call me with enough arguments from anArray" | args | (anArray size == self numArgs) ifTrue: [ ^self valueWithArguments: anArray ]. args := Array new: self numArgs. args replaceFrom: 1 to: (anArray size min: args size) with: anArray startingAt: 1. ^ self valueWithArguments: args! ! !BlockContext methodsFor: 'evaluating' stamp: 'md 3/28/2006 20:17'! valueWithExit self value: [ ^nil ]! ! !BlockContext methodsFor: 'evaluating'! value: arg "Primitive. Evaluate the block represented by the receiver. Fail if the block expects other than one argument or if the block is already being executed. Optional. No Lookup. See Object documentation whatIsAPrimitive." ^self valueWithArguments: (Array with: arg)! ! !BlockContext methodsFor: 'evaluating'! value: arg1 value: arg2 "Primitive. Evaluate the block represented by the receiver. Fail if the block expects other than two arguments or if the block is already being executed. Optional. See Object documentation whatIsAPrimitive." ^self valueWithArguments: (Array with: arg1 with: arg2)! ! !BlockContext methodsFor: 'evaluating'! value: arg1 value: arg2 value: arg3 "Primitive. Evaluate the block represented by the receiver. Fail if the block expects other than three arguments or if the block is already being executed. Optional. See Object documentation whatIsAPrimitive." ^self valueWithArguments: (Array with: arg1 with: arg2 with: arg3)! ! !BlockContext methodsFor: 'evaluating' stamp: 'di 11/30/97 09:19'! value: arg1 value: arg2 value: arg3 value: arg4 "Primitive. Evaluate the block represented by the receiver. Fail if the block expects other than three arguments or if the block is already being executed. Optional. See Object documentation whatIsAPrimitive." ^self valueWithArguments: (Array with: arg1 with: arg2 with: arg3 with: arg4)! ! !BlockContext methodsFor: 'evaluating' stamp: 'jrp 10/10/2004 22:28'! valueSupplyingAnswer: anObject ^ (anObject isCollection and: [anObject isString not]) ifTrue: [self valueSupplyingAnswers: {anObject}] ifFalse: [self valueSupplyingAnswers: {{'*'. anObject}}]! ! !BlockContext methodsFor: 'evaluating' stamp: 'NicolasCellier 10/28/2008 00:43'! valueSupplyingAnswers: aListOfPairs "evaluate the block using a list of questions / answers that might be called upon to automatically respond to Object>>confirm: or FillInTheBlank requests" ^ [self value] on: ProvideAnswerNotification do: [:notify | | answer caption | caption := notify messageText withSeparatorsCompacted. "to remove new lines" answer := aListOfPairs detect: [:each | caption = each first or: [(caption includesSubstring: each first caseSensitive: false) or: [(each first match: caption) or: [(String includesSelector: #matchesRegex:) and: [caption matchesRegex: each first]]]]] ifNone: [nil]. answer ifNotNil: [notify resume: answer second] ifNil: [ | outerAnswer | outerAnswer := ProvideAnswerNotification signal: notify messageText. outerAnswer ifNil: [notify resume] ifNotNil: [notify resume: outerAnswer]]]! ! !BlockContext methodsFor: 'evaluating' stamp: 'jrp 10/10/2004 22:28'! valueSuppressingAllMessages ^ self valueSuppressingMessages: #('*')! ! !BlockContext methodsFor: 'evaluating' stamp: 'jrp 10/4/2004 18:59'! valueSuppressingMessages: aListOfStrings ^ self valueSuppressingMessages: aListOfStrings supplyingAnswers: #()! ! !BlockContext methodsFor: 'evaluating' stamp: 'jrp 10/4/2004 18:58'! valueSuppressingMessages: aListOfStrings supplyingAnswers: aListOfPairs ^ self valueSupplyingAnswers: aListOfPairs, (aListOfStrings collect: [:each | {each. true}])! ! !BlockContext methodsFor: 'evaluating' stamp: 'md 7/30/2005 21:22'! valueWithArguments: anArray "Primitive. Evaluate the block represented by the receiver. The argument is an Array whose elements are the arguments for the block. Fail if the length of the Array is not the same as the the number of arguments that the block was expecting. Fail if the block is already being executed. Essential. See Object documentation whatIsAPrimitive." anArray isArray ifFalse: [^self error: 'valueWithArguments: expects an array']. self numArgs = anArray size ifTrue: [self error: 'Attempt to evaluate a block that is already being evaluated.'] ifFalse: [self error: 'This block accepts ' ,self numArgs printString, ' argument', (self numArgs = 1 ifTrue:[''] ifFalse:['s']) , ', but was called with ', anArray size printString, '.'] ! ! !BlockContext methodsFor: 'evaluating' stamp: 'md 10/7/2004 15:24'! valueWithPossibleArgs: anArray "Evaluate the block represented by the receiver. If the block requires arguments, take them from anArray. If anArray is too large, the rest is ignored, if it is too small, use nil for the other arguments" self numArgs = 0 ifTrue: [^self value]. self numArgs = anArray size ifTrue: [^self valueWithArguments: anArray]. self numArgs > anArray size ifTrue: [ ^self valueWithArguments: anArray, (Array new: (self numArgs - anArray size)) ]. ^self valueWithArguments: (anArray copyFrom: 1 to: self numArgs) ! ! !BlockContext methodsFor: 'evaluating' stamp: 'md 10/7/2004 15:26'! valueWithPossibleArgument: anArg "Evaluate the block represented by the receiver. If the block requires one argument, use anArg, if it requires more than one, fill up the rest with nils." self numArgs = 0 ifTrue: [^self value]. self numArgs = 1 ifTrue: [^self value: anArg]. self numArgs > 1 ifTrue: [^self valueWithArguments: {anArg}, (Array new: self numArgs - 1)]! ! !BlockContext methodsFor: 'evaluating' stamp: 'ar 8/17/2007 13:15'! valueWithin: aDuration onTimeout: timeoutBlock "Evaluate the receiver. If the evaluation does not complete in less than aDuration evaluate the timeoutBlock instead" | theProcess delay watchdog | aDuration <= Duration zero ifTrue: [^ timeoutBlock value ]. "the block will be executed in the current process" theProcess := Processor activeProcess. delay := aDuration asDelay. "make a watchdog process" watchdog := [ delay wait. "wait for timeout or completion" theProcess ifNotNil:[ theProcess signalException: TimedOut ] ] newProcess. "Watchdog needs to run at high priority to do its job (but not at timing priority)" watchdog priority: Processor timingPriority-1. "catch the timeout signal" ^ [ watchdog resume. "start up the watchdog" self ensure:[ "evaluate the receiver" theProcess := nil. "it has completed, so ..." delay delaySemaphore signal. "arrange for the watchdog to exit" ]] on: TimedOut do: [ :e | timeoutBlock value ]. ! ! !BlockContext methodsFor: 'exceptions' stamp: 'sma 5/11/2000 19:38'! assert self assert: self! ! !BlockContext methodsFor: 'exceptions' stamp: 'ajh 3/4/2004 22:36'! ensure: aBlock "Evaluate a termination block after evaluating the receiver, regardless of whether the receiver's evaluation completes." | returnValue b | returnValue := self value. "aBlock wasn't nil when execution of this method began; it is nil'd out by the unwind machinery, and that's how we know it's already been evaluated ... otherwise, obviously, it needs to be evaluated" aBlock == nil ifFalse: [ "nil out aBlock temp before evaluating aBlock so it is not executed again if aBlock remote returns" b := aBlock. thisContext tempAt: 1 put: nil. "aBlock := nil" b value. ]. ^ returnValue! ! !BlockContext methodsFor: 'exceptions' stamp: 'ajh 1/24/2003 21:43'! ifCurtailed: aBlock "Evaluate the receiver with an abnormal termination action." ^ self value! ! !BlockContext methodsFor: 'exceptions' stamp: 'ar 3/6/2001 14:25'! on: exception do: handlerAction "Evaluate the receiver in the scope of an exception handler." | handlerActive | handlerActive := true. ^self value! ! !BlockContext methodsFor: 'exceptions' stamp: 'ajh 10/9/2001 16:51'! onDNU: selector do: handleBlock "Catch MessageNotUnderstood exceptions but only those of the given selector (DNU stands for doesNotUnderstand:)" ^ self on: MessageNotUnderstood do: [:exception | exception message selector = selector ifTrue: [handleBlock valueWithPossibleArgs: {exception}] ifFalse: [exception pass] ]! ! !BlockContext methodsFor: 'exceptions' stamp: 'ajh 1/24/2003 21:53'! valueUninterruptably "Temporarily make my home Context unable to return control to its sender, to guard against circumlocution of the ensured behavior." ^ self ifCurtailed: [^ self]! ! !BlockContext methodsFor: 'initialize-release' stamp: 'ls 6/21/2000 17:42'! home: aContextPart startpc: position nargs: anInteger "This is the initialization message. The receiver has been initialized with the correct size only." home := aContextPart. pc := startpc := position. nargs := anInteger. stackp := 0.! ! !BlockContext methodsFor: 'initialize-release' stamp: 'ajh 7/18/2003 21:49'! privRefresh "Reinitialize the receiver so that it is in the state it was at its creation." pc := startpc. self stackp: 0. nargs timesRepeat: [ "skip arg popping" self nextInstruction selector = #popIntoTemporaryVariable: ifFalse: [self halt: 'unexpected bytecode instruction'] ]. ! ! !BlockContext methodsFor: 'instruction decoding' stamp: 'ajh 1/24/2003 16:35'! blockReturnTop "Simulate the interpreter's action when a ReturnTopOfStack bytecode is encountered in the receiver." | save dest | save := home. "Needed because return code will nil it" dest := self return: self pop from: self. home := save. sender := nil. ^ dest! ! !BlockContext methodsFor: 'printing' stamp: 'md 2/22/2006 15:53'! decompile ^ home method decompilerClass new decompileBlock: self! ! !BlockContext methodsFor: 'printing' stamp: 'md 2/20/2006 13:46'! decompileString ^self decompile decompileString.! ! !BlockContext methodsFor: 'printing' stamp: 'eem 7/28/2008 14:10'! fullPrintOn: aStream aStream print: self; cr. (self decompile ifNil: ['--source missing--']) printOn: aStream indent: 0! ! !BlockContext methodsFor: 'printing' stamp: 'eem 5/16/2008 12:03'! printOn: aStream | decompilation blockString truncatedBlockString | home == nil ifTrue: [^aStream nextPutAll: 'a BlockContext with home=nil']. aStream nextPutAll: '[] in '. super printOn: aStream. decompilation := [self decompile ifNil: ['--source missing--']] on: Error do: [:ex| ' (error in decompilation)']. blockString := ((decompilation isString ifTrue: [decompilation] ifFalse: [decompilation printString]) replaceAll: Character cr with: Character space) replaceAll: Character tab with: Character space. truncatedBlockString := blockString truncateWithElipsisTo: 80. truncatedBlockString size < blockString size ifTrue: [truncatedBlockString := truncatedBlockString, ']}']. aStream space; nextPutAll: truncatedBlockString! ! !BlockContext methodsFor: 'printing' stamp: 'MPW 1/1/1901 22:01'! printOnStream: aStream home == nil ifTrue: [^aStream print: 'a BlockContext with home=nil']. aStream print: '[] in '. super printOnStream: aStream! ! !BlockContext methodsFor: 'scheduling' stamp: 'ajh 2/10/2003 14:23'! asContext ^ self! ! !BlockContext methodsFor: 'scheduling' stamp: 'di 9/12/1998 11:53'! fork "Create and schedule a Process running the code in the receiver." ^ self newProcess resume! ! !BlockContext methodsFor: 'scheduling' stamp: 'ajh 10/16/2002 11:14'! forkAndWait "Suspend current process and execute self in new process, when it completes resume current process" | semaphore | semaphore := Semaphore new. [self ensure: [semaphore signal]] fork. semaphore wait. ! ! !BlockContext methodsFor: 'scheduling' stamp: 'jm 11/9/1998 10:16'! forkAt: priority "Create and schedule a Process running the code in the receiver at the given priority. Answer the newly created process." | forkedProcess | forkedProcess := self newProcess. forkedProcess priority: priority. ^ forkedProcess resume ! ! !BlockContext methodsFor: 'scheduling' stamp: 'svp 6/23/2003 10:59'! forkAt: priority named: name "Create and schedule a Process running the code in the receiver at the given priority and having the given name. Answer the newly created process." | forkedProcess | forkedProcess := self newProcess. forkedProcess priority: priority. forkedProcess name: name. ^ forkedProcess resume! ! !BlockContext methodsFor: 'scheduling' stamp: 'svp 6/23/2003 10:59'! forkNamed: aString "Create and schedule a Process running the code in the receiver and having the given name." ^ self newProcess name: aString; resume! ! !BlockContext methodsFor: 'scheduling' stamp: 'ajh 2/10/2003 14:25'! newProcess "Answer a Process running the code in the receiver. The process is not scheduled." "Simulation guard" ^Process forContext: [self value. Processor terminateActive] asContext priority: Processor activePriority! ! !BlockContext methodsFor: 'scheduling' stamp: 'ajh 2/10/2003 14:25'! newProcessWith: anArray "Answer a Process running the code in the receiver. The receiver's block arguments are bound to the contents of the argument, anArray. The process is not scheduled." "Simulation guard" ^Process forContext: [self valueWithArguments: anArray. Processor terminateActive] asContext priority: Processor activePriority! ! !BlockContext methodsFor: 'scheduling' stamp: 'sr 6/14/2004 15:19'! valueAt: blockPriority "Evaluate the receiver (block), with another priority as the actual one and restore it afterwards. The caller should be careful with using higher priorities." | activeProcess result outsidePriority | activeProcess := Processor activeProcess. outsidePriority := activeProcess priority. activeProcess priority: blockPriority. result := self ensure: [activeProcess priority: outsidePriority]. "Yield after restoring lower priority to give the preempted processes a chance to run." blockPriority > outsidePriority ifTrue: [Processor yield]. ^ result! ! !BlockContext methodsFor: 'system simulation' stamp: 'di 1/11/1999 10:24'! pushArgs: args from: sendr "Simulates action of the value primitive." args size ~= nargs ifTrue: [^self error: 'incorrect number of args']. self stackp: 0. args do: [:arg | self push: arg]. sender := sendr. pc := startpc! ! !BlockContext methodsFor: 'system simulation' stamp: 'hmm 7/30/2001 18:03'! stepToSendOrReturn pc = startpc ifTrue: [ "pop args first" self numArgs timesRepeat: [self step]]. ^super stepToSendOrReturn! ! !BlockContext methodsFor: 'testing' stamp: 'kph 1/21/2009 15:33'! = other self class == other class ifFalse: [^ false]. self home receiver == other home receiver ifFalse: [^ false]. self home selector == other home selector ifFalse: [^ false]. ^ self startpc == other startpc ! ! !BlockContext methodsFor: 'testing' stamp: 'kph 1/21/2009 15:33'! hash ^ self method hash! ! !BlockContext methodsFor: 'private' stamp: 'ajh 1/24/2003 20:36'! aboutToReturn: result through: firstUnwindContext "Called from VM when an unwindBlock is found between self and its home. Return to home's sender, executing unwind blocks on the way." self home return: result! ! !BlockContext methodsFor: 'private' stamp: 'tfei 3/31/1999 17:40'! cannotReturn: result "The receiver tried to return result to a method context that no longer exists." | ex newResult | ex := BlockCannotReturn new. ex result: result. newResult := ex signal. ^newResult! ! !BlockContext methodsFor: 'private' stamp: 'ajh 1/27/2003 21:18'! copyTo: aContext blocks: dict "Copy self and my sender chain down to, but not including, aContext. End of copied chain will have nil sender. BlockContexts whose home is also copied will point to the copy. However, blockContexts that are not on the stack but may be later will not have their home pointing in the new copied thread. So an error will be raised if one of these tries to return directly to its home." | copy | self == aContext ifTrue: [^ nil]. copy := self copy. (dict at: self home ifAbsentPut: [OrderedCollection new]) add: copy. self sender ifNotNil: [ copy privSender: (self sender copyTo: aContext blocks: dict)]. ^ copy! ! !BlockContext methodsFor: 'private' stamp: 'md 4/27/2006 15:14'! endPC "Determine end of block from long jump preceding it" ^(self method at: startpc - 2) \\ 16 - 4 * 256 + (self method at: startpc - 1) + startpc - 1.! ! !BlockContext methodsFor: 'private' stamp: 'di 1/14/1999 22:28'! instVarAt: index put: value index = 3 ifTrue: [self stackp: value. ^ value]. ^ super instVarAt: index put: value! ! !BlockContext methodsFor: 'private' stamp: 'ajh 7/7/2004 13:43'! myEnv "polymorphic with MethodContext" ^ nil! ! !BlockContext methodsFor: 'private' stamp: 'ajh 1/27/2003 21:08'! privHome: context home := context! ! !BlockContext methodsFor: 'private'! startpc "for use by the System Tracer only" ^startpc! ! !BlockContext methodsFor: 'private'! valueError self error: 'Incompatible number of args, or already active'! ! !BlockContext methodsFor: 'private' stamp: 'ar 3/2/2001 01:16'! valueUnpreemptively "Evaluate the receiver (block), without the possibility of preemption by higher priority processes. Use this facility VERY sparingly!!" "Think about using Block>>valueUninterruptably first, and think about using Semaphore>>critical: before that, and think about redesigning your application even before that!! After you've done all that thinking, go right ahead and use it..." | activeProcess oldPriority result | activeProcess := Processor activeProcess. oldPriority := activeProcess priority. activeProcess priority: Processor highestPriority. result := self ensure: [activeProcess priority: oldPriority]. "Yield after restoring priority to give the preempted processes a chance to run" Processor yield. ^result! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BlockContext class instanceVariableNames: ''! TestCase subclass: #BlockContextTest instanceVariableNames: 'aBlockContext contextOfaBlockContext' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'! !BlockContextTest commentStamp: 'jrp 10/17/2004 12:22' prior: 0! I am an SUnit Test of BlockContext and its supertype ContextPart. See also MethodContextTest. My fixtures are: aBlockContext - just some trivial block, i.e., [100@100 corner: 200@200]. NOTES ABOUT AUTOMATING USER INPUTS When executing non-interactive programs you will inevitably run into programs (like SqueakMap or Monticello installation packages -- and other programs, to be fair) that require user input during their execution and these sort of problems shoot the whole non-interactiveness of your enclosing program. BlockContext helper methods have been made available and tests of these helpers are provided in this class to demonstrate that it can intercept PopUpMenu and FillInTheBlankMorph requests for user interaction. Of course, PopUpMenu and FillInTheBlankMorph were modified to first signal a ProvideAnswerNotification and if someone handles that (e.g. the enclosing block) then the user interaction will be circumvented and the provided answer of the enclosing block will be used. The basic syntax looks like: [self confirm: 'Install spyware?'] valueSupplyingAnswer: #('Install spyware?' false) There a few variants on this theme making it easy to provide a literal list of answers for the block so that you can handle a bunch of questions in a block with appropriate answers. Additionally, it is possible to suppress Object>>inform: modal dialog boxes as these get in the way of automating anything. After applying this changeset you should be able to tryout the following code snippets to see the variants on this theme that are available. Examples: So you don't need any introduction here -- this one works like usual. [self inform: 'hello'. #done] value. Now let's suppress all inform: messages. [self inform: 'hello'; inform: 'there'. #done] valueSuppressingAllMessages. Here we can just suppress a single inform: message. [self inform: 'hi'; inform: 'there'. #done] valueSuppressingMessages: #('there') Here you see how you can suppress a list of messages. [self inform: 'hi'; inform: 'there'; inform: 'bill'. #done] valueSuppressingMessages: #('hi' 'there') Enough about inform:, let's look at confirm:. As you see this one works as expected. [self confirm: 'You like Squeak?'] value Let's supply answers to one of the questions -- check out the return value. [{self confirm: 'You like Smalltalk?'. self confirm: 'You like Squeak?'}] valueSupplyingAnswer: #('You like Smalltalk?' true) Here we supply answers using only substrings of the questions (for simplicity). [{self confirm: 'You like Squeak?'. self confirm: 'You like MVC?'}] valueSupplyingAnswers: #( ('Squeak' true) ('MVC' false) ) This time let's answer all questions exactly the same way. [{self confirm: 'You like Squeak?'. self confirm: 'You like Morphic?'}] valueSupplyingAnswer: true And, of course, we can answer FillInTheBlank questions in the same manner. [FillInTheBlank request: 'What day is it?'] valueSupplyingAnswer: 'the first day of the rest of your life' We can also return whatever the initialAnswer of the FillInTheBlank was by using the #default answer. [FillInTheBlank request: 'What day is it?' initialAnswer: DateAndTime now dayOfWeekName] valueSupplyingAnswer: #default Finally, you can also do regex matches on any of the question text (or inform text) (should you have VB-Regex enhancements in your image). [FillInTheBlank request: 'What day is it?'] valueSupplyingAnswers: { {'What day.*\?'. DateAndTime now dayOfWeekName} }! !BlockContextTest methodsFor: 'setup' stamp: 'md 9/6/2005 19:56'! setUp super setUp. aBlockContext := [100@100 corner: 200@200]. contextOfaBlockContext := thisContext.! ! !BlockContextTest methodsFor: 'testing' stamp: 'rbb 3/1/2005 10:23'! testSupplyAnswerOfFillInTheBlank self should: ['blue' = ([UIManager default request: 'Your favorite color?'] valueSupplyingAnswer: #('Your favorite color?' 'blue'))]! ! !BlockContextTest methodsFor: 'testing' stamp: 'rbb 3/1/2005 10:24'! testSupplyAnswerOfFillInTheBlankUsingDefaultAnswer self should: ['red' = ([UIManager default request: 'Your favorite color?' initialAnswer: 'red'] valueSupplyingAnswer: #('Your favorite color?' #default))]! ! !BlockContextTest methodsFor: 'tests' stamp: 'tlk 5/31/2004 13:13'! testNew self should: [ContextPart new: 5] raise: Error. [ContextPart new: 5] ifError: [:error :receiver | error = 'Error: Contexts must only be created with newForMethod:']. [ContextPart new] ifError: [:error :receiver | error = 'Error: Contexts must only be created with newForMethod:']. [ContextPart basicNew] ifError: [:error :receiver | error = 'Error: Contexts must only be created with newForMethod:']. ! ! !BlockContextTest methodsFor: 'tests' stamp: 'mjr 8/24/2003 18:27'! testNoArguments [10 timesRepeat: [:arg | 1 + 2]] ifError: [:err :rcvr | self deny: err = 'This block requires 1 arguments.']. [10 timesRepeat: [:arg1 :arg2 | 1 + 2]] ifError: [:err :rcvr | self deny: err = 'This block requires 2 arguments.'] ! ! !BlockContextTest methodsFor: 'tests' stamp: 'mjr 8/24/2003 18:25'! testOneArgument | c | c := OrderedCollection new. c add: 'hello'. [c do: [1 + 2]] ifError: [:err :rcvr | self deny: err = 'This block requires 0 arguments.']. [c do: [:arg1 :arg2 | 1 + 2]] ifError: [:err :rcvr | self deny: err = 'This block requires 2 arguments.'] ! ! !BlockContextTest methodsFor: 'tests' stamp: 'tlk 5/31/2004 12:50'! testRunSimulated self assert: (ContextPart runSimulated: aBlockContext) class = Rectangle.! ! !BlockContextTest methodsFor: 'tests' stamp: 'al 7/4/2009 19:01'! testSetUp "Note: In addition to verifying that the setUp worked the way it was expected to, testSetUp is used to illustrate the meaning of the simple access methods, methods that are not normally otherwise 'tested'" self deny: aBlockContext isPseudoContext. self assert: aBlockContext home = contextOfaBlockContext. self assert: aBlockContext receiver = self. self assert: (aBlockContext method isKindOf: CompiledMethod).! ! !BlockContextTest methodsFor: 'tests' stamp: 'jrp 10/10/2004 22:19'! testSupplyAnswerThroughNestedBlocks self should: [true = ([[self confirm: 'You like Smalltalk?'] valueSupplyingAnswer: #('Blub' false)] valueSupplyingAnswer: #('Smalltalk' true))]! ! !BlockContextTest methodsFor: 'tests' stamp: 'jrp 10/4/2004 19:27'! testSupplyAnswerUsingOnlySubstringOfQuestion self should: [false = ([self confirm: 'You like Smalltalk?'] valueSupplyingAnswer: #('like' false))]! ! !BlockContextTest methodsFor: 'tests' stamp: 'jrp 10/10/2004 22:31'! testSupplyAnswerUsingRegexMatchOfQuestion (String includesSelector: #matchesRegex:) ifFalse: [^ self]. self should: [true = ([self confirm: 'You like Smalltalk?'] valueSupplyingAnswer: #('.*Smalltalk\?' true))]! ! !BlockContextTest methodsFor: 'tests' stamp: 'jrp 10/10/2004 22:17'! testSupplyAnswerUsingTraditionalMatchOfQuestion self should: [true = ([self confirm: 'You like Smalltalk?'] valueSupplyingAnswer: #('*Smalltalk#' true))]! ! !BlockContextTest methodsFor: 'tests' stamp: 'jrp 10/4/2004 19:25'! testSupplySameAnswerToAllQuestions self should: [true = ([self confirm: 'You like Smalltalk?'] valueSupplyingAnswer: true)]. self should: [#(true true) = ([{self confirm: 'One'. self confirm: 'Two'}] valueSupplyingAnswer: true)].! ! !BlockContextTest methodsFor: 'tests' stamp: 'jrp 10/4/2004 19:39'! testSupplySeveralAnswersToSeveralQuestions self should: [#(false true) = ([{self confirm: 'One'. self confirm: 'Two'}] valueSupplyingAnswers: #( ('One' false) ('Two' true) ))]. self should: [#(true false) = ([{self confirm: 'One'. self confirm: 'Two'}] valueSupplyingAnswers: #( ('One' true) ('Two' false) ))]! ! !BlockContextTest methodsFor: 'tests' stamp: 'jrp 10/4/2004 19:26'! testSupplySpecificAnswerToQuestion self should: [false = ([self confirm: 'You like Smalltalk?'] valueSupplyingAnswer: #('You like Smalltalk?' false))]! ! !BlockContextTest methodsFor: 'tests' stamp: 'jrp 10/4/2004 19:35'! testSuppressInform self should: [[nil inform: 'Should not see this message or this test failed!!'] valueSuppressingAllMessages isNil]! ! !BlockContextTest methodsFor: 'tests' stamp: 'jrp 10/10/2004 22:29'! testSuppressInformUsingStringMatchOptions self should: [([nil inform: 'Should not see this message or this test failed!!'] valueSuppressingMessages: #('Should not see this message or this test failed!!')) isNil]. self should: [([nil inform: 'Should not see this message or this test failed!!'] valueSuppressingMessages: #('not see this message')) isNil]. self should: [([nil inform: 'Should not see this message or this test failed!!'] valueSuppressingMessages: #('*message*failed#')) isNil]. ! ! !BlockContextTest methodsFor: 'tests' stamp: 'md 9/6/2005 19:58'! testTallyInstructions self assert: (ContextPart tallyInstructions: aBlockContext) size = 15.! ! !BlockContextTest methodsFor: 'tests' stamp: 'md 9/6/2005 19:58'! testTallyMethods self assert: (ContextPart tallyMethods: aBlockContext) size = 3.! ! !BlockContextTest methodsFor: 'tests' stamp: 'tlk 5/31/2004 12:48'! testTrace self assert: (ContextPart trace: aBlockContext) class = Rectangle.! ! !BlockContextTest methodsFor: 'tests - evaluating' stamp: 'Henrik Sperre Johansen 3/23/2009 13:45'! testValueWithArguments self should: [aBlockContext valueWithArguments: #(1 )] raise: Error. self shouldnt: [aBlockContext valueWithArguments: #()] raise: Error. [aBlockContext valueWithArguments: #(1 )] ifError: [:err :rcvr | self assert: err = 'Error: This block accepts 0 arguments, but was called with 1 argument.']. [[:i | 3 + 4] valueWithArguments: #(1 2)] ifError: [:err :rcvr | self assert: err = 'Error: This block accepts 1 argument, but was called with 2 arguments.']! ! !BlockContextTest methodsFor: 'tests - evaluating' stamp: 'md 3/23/2006 13:52'! testValueWithExitBreak | val | [ :break | 1 to: 10 do: [ :i | val := i. i = 4 ifTrue: [break value]. ] ] valueWithExit. self assert: val = 4.! ! !BlockContextTest methodsFor: 'tests - evaluating' stamp: 'md 3/23/2006 13:52'! testValueWithExitContinue | val last | val := 0. 1 to: 10 do: [ :i | [ :continue | i = 4 ifTrue: [continue value]. val := val + 1. last := i ] valueWithExit. ]. self assert: val = 9. self assert: last = 10. ! ! !BlockContextTest methodsFor: 'tests - evaluating' stamp: 'md 10/7/2004 13:52'! testValueWithPossibleArgs | block blockWithArg blockWith2Arg | block := [1]. blockWithArg := [:arg | arg]. blockWith2Arg := [:arg1 :arg2 | {arg1. arg2}]. self assert: (block valueWithPossibleArgs: #()) = 1. self assert: (block valueWithPossibleArgs: #(1)) = 1. self assert: (blockWithArg valueWithPossibleArgs: #()) = nil. self assert: (blockWithArg valueWithPossibleArgs: #(1)) = 1. self assert: (blockWithArg valueWithPossibleArgs: #(1 2)) = 1. self assert: (blockWith2Arg valueWithPossibleArgs: #()) = {nil .nil}. self assert: (blockWith2Arg valueWithPossibleArgs: #(1)) = {1 . nil}. self assert: (blockWith2Arg valueWithPossibleArgs: #(1 2)) = #(1 2). self assert: (blockWith2Arg valueWithPossibleArgs: #(1 2 3)) = #(1 2). ! ! !BlockContextTest methodsFor: 'tests - evaluating' stamp: 'md 10/7/2004 13:59'! testValueWithPossibleArgument | block blockWithArg blockWith2Arg | block := [1]. blockWithArg := [:arg | arg]. blockWith2Arg := [:arg1 :arg2 | {arg1. arg2}]. self assert: (block valueWithPossibleArgument: 1) = 1. self assert: (blockWithArg valueWithPossibleArgument: 1) = 1. self assert: (blockWith2Arg valueWithPossibleArgument: 1) = {1 . nil}. ! ! !BlockContextTest methodsFor: 'tests - printing' stamp: 'md 2/22/2006 15:39'! testDecompile self assert: ([3 + 4] decompile printString = '{[3 + 4]}').! ! InstructionClient subclass: #BlockLocalTempCounter instanceVariableNames: 'stackPointer scanner blockEnd joinOffsets' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Support'! !BlockLocalTempCounter commentStamp: '' prior: 0! I am a support class for the decompiler that is used to find the number of local temps in a block by finding out what the stack offset is at the end of a block.! ]style[(160)i! !BlockLocalTempCounter methodsFor: 'initialize-release' stamp: 'eem 9/26/2008 13:40'! tempCountForBlockAt: pc in: method "Compute the number of local temporaries in a block. If the block begins with a sequence of push: nil bytecodes then some of These could be initializing local temps. We can only reliably disambuguate them from other uses of nil by parsing the stack and seeing what the offset of the stack pointer is at the end of the block. There are short-cuts. The ones we take here are - if there is no sequence of push nils there can be no local temps - we follow forward jumps to shorten the amount of scanning" stackPointer := 0. scanner := InstructionStream new method: method pc: pc. scanner interpretNextInstructionFor: self. blockEnd isNil ifTrue: [self error: 'pc is not that of a block']. scanner nextByte = Encoder pushNilCode ifTrue: [joinOffsets := Dictionary new. [scanner pc < blockEnd] whileTrue: [scanner interpretNextInstructionFor: self]]. ^stackPointer! ! !BlockLocalTempCounter methodsFor: 'initialize-release' stamp: 'eem 9/26/2008 13:41'! testTempCountForBlockAt: startPc in: method "Compute the number of local temporaries in a block. If the block begins with a sequence of push: nil bytecodes then some of These could be initializing local temps. We can only reliably disambuguate them from other uses of nil by parsing the stack and seeing what the offset of the stack pointer is at the end of the block.There are short-cuts. The only one we take here is - if there is no sequence of push nils there can be no local temps" | symbolicLines line prior thePc | symbolicLines := Dictionary new. method symbolicLinesDo: [:pc :lineForPC| symbolicLines at: pc put: lineForPC]. stackPointer := 0. scanner := InstructionStream new method: method pc: startPc. scanner interpretNextInstructionFor: self. blockEnd isNil ifTrue: [self error: 'pc is not that of a block']. scanner nextByte = Encoder pushNilCode ifTrue: [joinOffsets := Dictionary new. [scanner pc < blockEnd] whileTrue: [line := symbolicLines at: scanner pc. prior := stackPointer. thePc := scanner pc. scanner interpretNextInstructionFor: self. Transcript cr; print: prior; nextPutAll: '->'; print: stackPointer; tab; print: thePc; tab; nextPutAll: line; flush]]. ^stackPointer! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/26/2008 11:36'! blockReturnTop "Return Top Of Stack bytecode." stackPointer := stackPointer - 1. scanner pc < blockEnd ifTrue: [self doJoin]! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:13'! doDup "Duplicate Top Of Stack bytecode." stackPointer := stackPointer + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:17'! doPop "Remove Top Of Stack bytecode." stackPointer := stackPointer - 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/26/2008 13:40'! jump: offset "Unconditional Jump bytecode." offset > 0 ifTrue: [joinOffsets at: scanner pc + offset put: stackPointer. self doJoin]! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/26/2008 13:40'! jump: offset if: condition "Conditional Jump bytecode." stackPointer := stackPointer - 1. offset > 0 ifTrue: [joinOffsets at: scanner pc + offset put: stackPointer]! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/26/2008 11:36'! methodReturnConstant: value "Return Constant bytecode." self doJoin! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/26/2008 11:36'! methodReturnReceiver "Return Self bytecode." self doJoin! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/26/2008 11:36'! methodReturnTop "Return Top Of Stack bytecode." stackPointer := stackPointer - 1. self doJoin! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:19'! popIntoLiteralVariable: anAssociation "Remove Top Of Stack And Store Into Literal Variable bytecode." stackPointer := stackPointer - 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:19'! popIntoReceiverVariable: offset "Remove Top Of Stack And Store Into Instance Variable bytecode." stackPointer := stackPointer - 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:19'! popIntoRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex "Remove Top Of Stack And Store Into Offset of Temp Vector bytecode." stackPointer := stackPointer - 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:20'! popIntoTemporaryVariable: offset "Remove Top Of Stack And Store Into Temporary Variable bytecode." stackPointer := stackPointer - 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:20'! pushActiveContext "Push Active Context On Top Of Its Own Stack bytecode." stackPointer := stackPointer + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:16'! pushClosureCopyNumCopiedValues: numCopied numArgs: numArgs blockSize: blockSize "Push Closure bytecode. Either compute the end of the block if this is the block we're analysing, or skip it, adjusting the stack as appropriate." blockEnd ifNil: [blockEnd := scanner pc + blockSize] ifNotNil: [stackPointer := stackPointer - numCopied + 1. scanner pc: scanner pc + blockSize]! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:21'! pushConsArrayWithElements: numElements "Push Cons Array of size numElements popping numElements items from the stack into the array bytecode." stackPointer := stackPointer - numElements + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:21'! pushConstant: value "Push Constant, value, on Top Of Stack bytecode." stackPointer := stackPointer + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:22'! pushLiteralVariable: anAssociation "Push Contents Of anAssociation On Top Of Stack bytecode." stackPointer := stackPointer + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:22'! pushNewArrayOfSize: numElements "Push New Array of size numElements bytecode." stackPointer := stackPointer + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:22'! pushReceiver "Push Active Context's Receiver on Top Of Stack bytecode." stackPointer := stackPointer + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:23'! pushReceiverVariable: offset "Push Contents Of the Receiver's Instance Variable Whose Index is the argument, offset, On Top Of Stack bytecode." stackPointer := stackPointer + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:23'! pushRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex "Push Contents at Offset in Temp Vector bytecode." stackPointer := stackPointer + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:23'! pushTemporaryVariable: offset "Push Contents Of Temporary Variable Whose Index Is the argument, offset, On Top Of Stack bytecode." stackPointer := stackPointer + 1! ! !BlockLocalTempCounter methodsFor: 'instruction decoding' stamp: 'eem 9/23/2008 16:24'! send: selector super: supered numArgs: numberArguments "Send Message With Selector, selector, bytecode. The argument, supered, indicates whether the receiver of the message is specified with 'super' in the source method. The arguments of the message are found in the top numArguments locations on the stack and the receiver just below them." stackPointer := stackPointer - numberArguments! ! !BlockLocalTempCounter methodsFor: 'private' stamp: 'eem 9/26/2008 13:40'! doJoin scanner pc < blockEnd ifTrue: [stackPointer := joinOffsets at: scanner pc]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BlockLocalTempCounter class instanceVariableNames: ''! !BlockLocalTempCounter class methodsFor: 'instance creation' stamp: 'eem 9/23/2008 16:07'! tempCountForBlockAt: pc in: method ^self new tempCountForBlockAt: pc in: method! ! ParseNode subclass: #BlockNode instanceVariableNames: 'arguments statements returns nArgsNode size remoteCopyNode temporaries optimized actualScopeIfOptimized blockExtent remoteTempNode copiedValues closureCreationNode startOfLastStatement' classVariableNames: '' poolDictionaries: '' category: 'Compiler-ParseNodes'! !BlockNode commentStamp: '' prior: 0! I represent a bracketed block with 0 or more arguments and 1 or more statements. If I am initialized with no statements, I create one. I have a flag to tell whether my last statement returns a value from the enclosing method. My last three fields remember data needed for code generation. I can emit for value in the usual way, in which case I create a literal method (actually a context remotely copied) to be evaluated by sending it value: at run time. Or I can emit code to be evaluated in line; this only happens at the top level of a method and in conditionals and while-loops, none of which have arguments.! !BlockNode methodsFor: 'accessing' stamp: 'eem 6/2/2008 14:00'! addArgument: aTempVariableNode temporaries := temporaries copyWith: aTempVariableNode! ! !BlockNode methodsFor: 'accessing' stamp: 'eem 7/27/2008 15:57'! arguments ^arguments! ! !BlockNode methodsFor: 'accessing'! arguments: argNodes "Decompile." arguments := argNodes! ! !BlockNode methodsFor: 'accessing' stamp: 'tk 8/4/1999 22:53'! block ^ self! ! !BlockNode methodsFor: 'accessing' stamp: 'eem 8/22/2008 10:01'! closureCreationNode closureCreationNode ifNil: [closureCreationNode := LeafNode new key: #closureCreationNode code: nil]. ^closureCreationNode! ! !BlockNode methodsFor: 'accessing'! firstArgument ^ arguments first! ! !BlockNode methodsFor: 'accessing' stamp: 'eem 5/30/2008 12:12'! nArgsSlot "Private for the Encoder to use in bindArg" ^nArgsNode! ! !BlockNode methodsFor: 'accessing' stamp: 'eem 5/30/2008 12:12'! nArgsSlot: anInteger "Private for the Encoder to use in bindArg" nArgsNode := anInteger! ! !BlockNode methodsFor: 'accessing'! numberOfArguments ^arguments size! ! !BlockNode methodsFor: 'accessing' stamp: 'eem 7/24/2008 12:37'! optimized ^optimized! ! !BlockNode methodsFor: 'accessing'! returnLast self returns ifFalse: [returns := true. statements at: statements size put: statements last asReturnNode]! ! !BlockNode methodsFor: 'accessing' stamp: 'ar 11/17/2002 19:57'! returnNilIfNoOther self returns ifFalse: [statements last == NodeNil ifFalse: [statements add: NodeNil]. self returnLast]! ! !BlockNode methodsFor: 'accessing' stamp: 'gk 4/6/2006 11:29'! returnSelfIfNoOther: encoder self returns ifTrue:[^self]. statements last == NodeSelf ifFalse: [ statements := statements copyWith: (encoder encodeVariable: 'self'). ]. self returnLast. ! ! !BlockNode methodsFor: 'accessing' stamp: 'eem 8/4/2008 10:48'! startOfLastStatement ^startOfLastStatement! ! !BlockNode methodsFor: 'accessing' stamp: 'eem 8/4/2008 10:50'! startOfLastStatement: anInteger "Note the source index of the start of the last full statement. The last full statement is the value answered by a block and hence the expression the debugger should display as the value of the block." startOfLastStatement := anInteger! ! !BlockNode methodsFor: 'accessing' stamp: 'eem 7/27/2008 15:57'! temporaries ^temporaries! ! !BlockNode methodsFor: 'accessing' stamp: 'sma 2/27/2000 22:37'! temporaries: aCollection temporaries := aCollection! ! !BlockNode methodsFor: 'code generation'! code ^statements first code! ! !BlockNode methodsFor: 'code generation' stamp: 'di 11/19/1999 19:32'! emitExceptLast: stack on: aStream | nextToLast | nextToLast := statements size - 1. nextToLast < 1 ifTrue: [^ self]. "Only one statement" 1 to: nextToLast do: [:i | (statements at: i) emitForEffect: stack on: aStream]. ! ! !BlockNode methodsFor: 'code generation'! emitForEvaluatedEffect: stack on: aStream self returns ifTrue: [self emitForEvaluatedValue: stack on: aStream. stack pop: 1] ifFalse: [self emitExceptLast: stack on: aStream. statements last emitForEffect: stack on: aStream]! ! !BlockNode methodsFor: 'code generation' stamp: 'di 11/19/1999 19:44'! emitForEvaluatedValue: stack on: aStream self emitExceptLast: stack on: aStream. statements last emitForValue: stack on: aStream. ! ! !BlockNode methodsFor: 'code generation' stamp: 'hmm 7/17/2001 21:02'! emitForValue: stack on: aStream aStream nextPut: LdThisContext. stack push: 1. nArgsNode emitForValue: stack on: aStream. remoteCopyNode emit: stack args: 1 on: aStream. "Force a two byte jump." self emitLong: size code: JmpLong on: aStream. stack push: arguments size. arguments reverseDo: [:arg | arg emitStorePop: stack on: aStream]. self emitForEvaluatedValue: stack on: aStream. self returns ifFalse: [ aStream nextPut: EndRemote. pc := aStream position. ]. stack pop: 1! ! !BlockNode methodsFor: 'code generation' stamp: 'di 11/19/1999 19:33'! sizeExceptLast: encoder | codeSize nextToLast | nextToLast := statements size - 1. nextToLast < 1 ifTrue: [^ 0]. "Only one statement" codeSize := 0. 1 to: nextToLast do: [:i | codeSize := codeSize + ((statements at: i) sizeForEffect: encoder)]. ^ codeSize! ! !BlockNode methodsFor: 'code generation'! sizeForEvaluatedEffect: encoder self returns ifTrue: [^self sizeForEvaluatedValue: encoder]. ^(self sizeExceptLast: encoder) + (statements last sizeForEffect: encoder)! ! !BlockNode methodsFor: 'code generation'! sizeForEvaluatedValue: encoder ^(self sizeExceptLast: encoder) + (statements last sizeForValue: encoder)! ! !BlockNode methodsFor: 'code generation'! sizeForValue: encoder nArgsNode := encoder encodeLiteral: arguments size. remoteCopyNode := encoder encodeSelector: #blockCopy:. size := (self sizeForEvaluatedValue: encoder) + (self returns ifTrue: [0] ifFalse: [1]). "endBlock" arguments := arguments collect: "Chance to prepare debugger remote temps" [:arg | arg asStorableNode: encoder]. arguments do: [:arg | size := size + (arg sizeForStorePop: encoder)]. ^1 + (nArgsNode sizeForValue: encoder) + (remoteCopyNode size: encoder args: 1 super: false) + 2 + size! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 9/3/2009 12:55'! actualScope "Answer the actual scope for the receiver. If this is an unoptimized block then it is its actual scope, but if this is an optimized block then the actual scope is some outer block." ^actualScopeIfOptimized ifNil: [self]! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 8/4/2009 11:42'! addHoistedTemps: additionalTemporaries "" additionalTemporaries do: [:temp| temp definingScope ifNil: [temp definingScope: self]]. temporaries := (temporaries isNil or: [temporaries isEmpty]) ifTrue: [additionalTemporaries copy] ifFalse: [temporaries last isIndirectTempVector ifTrue: [temporaries allButLast, additionalTemporaries, { temporaries last }] ifFalse: [temporaries, additionalTemporaries]]! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 7/24/2009 16:43'! addRemoteTemp: aTempVariableNode rootNode: rootNode "" "Add aTempVariableNode to my actualScope's sequence of remote temps. If I am an optimized block then the actual scope is my actualScopeIfOptimized, otherwise it is myself." temporaries isArray ifTrue: [temporaries := temporaries asOrderedCollection]. remoteTempNode == nil ifTrue: [remoteTempNode := RemoteTempVectorNode new name: self remoteTempNodeName index: arguments size + temporaries size type: LdTempType scope: 0. actualScopeIfOptimized ifNil: [temporaries addLast: remoteTempNode. remoteTempNode definingScope: self] ifNotNil: [actualScopeIfOptimized addHoistedTemps: { remoteTempNode }]]. remoteTempNode addRemoteTemp: aTempVariableNode encoder: rootNode encoder. "use remove:ifAbsent: because the deferred analysis for optimized loops can result in the temp has already been hoised into the root." temporaries remove: aTempVariableNode ifAbsent: []. ^remoteTempNode! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 8/4/2009 13:29'! analyseArguments: methodArguments temporaries: methodTemporaries rootNode: rootNode "" "^>" "Top level entry-point for analysing temps within the hierarchy of blocks in the receiver's method. Answer the (possibly modified) sequence of temp vars. Need to hoist temps out of macro-optimized blocks into their actual blocks. Need to note reads and writes to temps from blocks other than their actual blocks to determine whether blocks can be local (simple slots within a block/method context) or remote (slots in indirection vectors that are shared between contexts by sharing indirection vectors). The algorithm is based on numbering temporary reads and writes and block extents. The index used for numbering starts at zero and is incremented on every block entry and block exit. So the following | a b blk r1 r2 t | a := 1. b := 2. t := 0. blk := [ | s | s := a + b. t := t + s]. r1 := blk value. b := -100. r2 := blk value. r1 -> r2 -> t is numbered as method block 0 to: 6: | a b blk r1 r2 t | a w@1 := 1. b w@1 := 2. t w@1 := 0. blk w@5 := [entry@2 | s | t w@3 := t r@3 + a r@3 + b r@3 ] exit@4. r1 w@5 := blk r@5 value. b w@5 := nil. r2 w@5 := blk r@5 value. r1 r@5 -> r2 r@5 -> t r@5 So: b and blk cannot be copied because for both there exists a write @5 that follows a read @4 within block 2 through 4 t must be remote because there exists a write @3 within block (2 to: 4) Complications are introduced by optimized blocks. In the following temp is written to after it is closed over by [ temp ] since the inlined block is executed more than once. | temp coll | coll := OrderedCollection new. 1 to: 5 do: [ :index | temp := index. coll add: [ temp ] ]. self assert: (coll collect: [:ea| ea value]) asArray = #(5 5 5 5 5) In the following i is local to the block and must be initialized each time around the loop but if the block is inlined it must be declared at method level. | col | col := OrderedCollection new. 1 to: 3 do: [ :each | | i | i := each. col add: [ i ]. i := i + 1 ]. self assert: (col collect: [ :each | each value ]) asArray = #(2 3 4)" self assert: (arguments isEmpty or: [arguments hasEqualElements: methodArguments]). arguments := methodArguments asArray. "won't change" self assert: (temporaries isNil or: [temporaries isEmpty or: [temporaries hasEqualElements: methodTemporaries]]). temporaries := OrderedCollection withAll: methodTemporaries. self assert: optimized not. "the top-level block should not be optimized." self analyseTempsWithin: self rootNode: rootNode assignmentPools: Dictionary new. "The top-level block needs to reindex temporaries since analysis may have rearranged them. This happens when temps are made remote and/or a remote node is added." temporaries withIndexDo: [:temp :offsetPlusOne| temp index: arguments size + offsetPlusOne - 1]. "Answer the (possibly modified) sequence of temps." ^temporaries asArray! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 8/4/2009 11:42'! analyseTempsWithin: scopeBlock "" rootNode: rootNode "" assignmentPools: assignmentPools "" | effectiveScope blockStart | effectiveScope := optimized ifTrue: [actualScopeIfOptimized := scopeBlock] ifFalse: [self]. arguments ifNotNil: [arguments do: [:temp| temp definingScope: self]]. temporaries ifNotNil: [temporaries do: [:temp| temp definingScope: self]]. optimized ifFalse: "if optimized this isn't an actual scope" [rootNode noteBlockEntry: [:entryNumber| blockExtent := (blockStart := entryNumber) to: 0]]. "Need to enumerate a copy because closure analysis can add a statement via ifHasRemoteTempNodeEnsureInitializationStatementExists:." statements copy do: [:statement| statement analyseTempsWithin: effectiveScope rootNode: rootNode assignmentPools: assignmentPools]. optimized ifFalse: "if optimized this isn't an actual scope" [rootNode noteBlockExit: [:exitNumber| blockExtent := blockStart to: exitNumber]]. "Now that the analysis is done move any temps that need to be moved." self postNumberingProcessTempsWithin: effectiveScope rootNode: rootNode. "This is simply a nicety for compiler developers..." temporaries do: [:temp| (temp isIndirectTempVector and: [temp name includes: $?]) ifTrue: [temp name: temp definingScope remoteTempNodeName]]! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 5/20/2008 12:16'! blockExtent "^" ^blockExtent! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 8/4/2009 11:56'! computeCopiedValues: rootNode | referencedValues | referencedValues := rootNode referencedValuesWithinBlockExtent: blockExtent. ^((referencedValues reject: [:temp| temp isDefinedWithinBlockExtent: blockExtent]) asSortedCollection: ParseNode tempSortBlock) asArray! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 8/4/2008 14:10'! constructClosureCreationNode: encoder copiedValues := self computeCopiedValues: encoder rootNode. encoder supportsClosureOpcodes ifTrue: [^self closureCreationNode]. "Without the bytecode we can still get by." ^MessageNode new receiver: (encoder encodeVariable: 'thisContext') selector: #closureCopy:copiedValues: arguments: (Array with: (encoder encodeLiteral: arguments size) with: (copiedValues isEmpty ifTrue: [NodeNil] ifFalse: [BraceNode new elements: copiedValues])) precedence: 3 from: encoder! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 8/4/2008 14:10'! emitCodeForClosureValue: stack encoder: encoder "if not supportsClosureOpcodes closureCreationSupportNode is the node for thisContext closureCopy: numArgs [ copiedValues: { values } ]" encoder supportsClosureOpcodes ifTrue: [copiedValues do: [:copiedValue| copiedValue emitCodeForValue: stack encoder: encoder]. closureCreationNode pc: encoder methodStreamPosition + 1. encoder genPushClosureCopyNumCopiedValues: copiedValues size numArgs: arguments size jumpSize: size. stack pop: copiedValues size; push: 1] ifFalse: [closureCreationNode emitCodeForValue: stack encoder: encoder. encoder genJumpLong: size]. "Force a two byte jump." "Emit the body of the block" self emitCodeForEvaluatedClosureValue: stack encoder: encoder! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 9/12/2008 10:55'! emitCodeForEvaluatedClosureValue: stack encoder: encoder | position | position := stack position. stack position: arguments size + copiedValues size. temporaries size timesRepeat: [NodeNil emitCodeForValue: stack encoder: encoder]. self reindexingLocalsDo: [self emitCodeForEvaluatedValue: stack encoder: encoder] encoder: encoder. self returns ifFalse: [encoder genReturnTopToCaller. pc := encoder methodStreamPosition]. stack position: position! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 7/24/2009 18:56'! ifHasRemoteTempNodeEnsureInitializationStatementExists: rootNode "If a remoteTempNode has been added ensure a statement exists to initialize it." remoteTempNode ~~ nil ifTrue: [(statements notEmpty and: [statements first isAssignmentNode and: [statements first variable isTemp and: [statements first variable isIndirectTempVector]]]) ifTrue: "If this is a decompiled tree, or if a temporary has been added later in the analysis then there already is a temp vector initialization node." [(statements first variable ~~ remoteTempNode) ifTrue: [statements first variable become: remoteTempNode]. statements first value numElements: remoteTempNode remoteTemps size] ifFalse: [statements addFirst: (remoteTempNode nodeToInitialize: rootNode encoder)]].! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 5/19/2008 17:12'! noteOptimized optimized := true! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 7/20/2009 09:52'! optimizedBlockHoistTempsInto: scopeBlock "" "This is a No-op for all nodes except non-optimized BlockNodes." "Let's assume the special > 0 guard in MessageNode>>analyseTempsWithin:forValue:encoder: is correct. Then we can simply hoist our temps up." self assert: (arguments isNil or: [arguments size <= 1]). (arguments notNil and: [arguments notEmpty]) ifTrue: [scopeBlock addHoistedTemps: arguments. arguments := #()]. temporaries notEmpty ifTrue: [scopeBlock addHoistedTemps: temporaries. temporaries := #()]! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 7/24/2009 16:23'! postNumberingProcessTempsWithin: scopeBlock "" rootNode: rootNode "" "A temp can be local (and copied) if it is not written to after it is captured. A temp cannot be local if it is written to remotely. Need to enumerate a copy of the temporaries because any temps becoming remote will be removed from temporaries in analyseClosure: (and a single remote temp node will get added)" temporaries copy do: [:each| each isIndirectTempVector ifFalse: [each analyseClosure: rootNode]]. "If this is an optimized node we need to hoist temporaries up into the relevant block scope." optimized ifTrue: [self optimizedBlockHoistTempsInto: scopeBlock]. "Now we may have added a remoteTempNode. So we need a statement to initialize it." self ifHasRemoteTempNodeEnsureInitializationStatementExists: rootNode. "Now add all arguments and locals to the pool so that copiedValues can be computed during sizing." rootNode addLocalsToPool: arguments; addLocalsToPool: temporaries! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 6/2/2008 16:37'! reindexingLocalsDo: aBlock encoder: encoderOrNil "Evaluate aBlock wih arguments, temporaries and copiedValues reindexed for their positions within the receiver's block, restoring the correct indices afterwards. If encoder is not nil remember the temps for this block's extent." | tempIndices result tempsToReindex | self assert: copiedValues notNil. tempsToReindex := arguments asArray, copiedValues, temporaries. tempIndices := tempsToReindex collect: [:temp| temp index]. tempsToReindex withIndexDo: [:temp :newIndex| temp index: newIndex - 1. self assert: temp index + 1 = newIndex]. encoderOrNil ifNotNil: [encoderOrNil noteBlockExtent: blockExtent hasLocals: tempsToReindex]. result := aBlock ensure: ["Horribly pragmatic hack. The copiedValues will have completely unrelated indices within the closure method and sub-method. Avoiding the effort of rebinding temps in the inner scope simply update the indices to their correct ones during the generation of the closure method and restore the indices immedately there-after." tempsToReindex with: tempIndices do: [:temp :oldIndex| temp index: oldIndex. self assert: temp index = oldIndex]]. ^result! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 7/22/2009 10:48'! remoteTempNodeName "Answer a useful name for a RemoteTempVectorNode in the receiver." | prefix scope extent | prefix := actualScopeIfOptimized ifNil: ['<'] ifNotNil: [ '<...']. scope := self. [extent := scope blockExtent. extent == nil and: [scope actualScope ~~ scope]] whileTrue: [scope := scope actualScope]. ^extent ifNil: [prefix, '?-?>'] ifNotNil: [prefix, extent first printString, '-', (extent last isZero ifTrue: ['?'] ifFalse: [extent last printString]), '>']! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 8/4/2008 14:11'! sizeCodeForClosureValue: encoder "Compute the size for the creation of the block and its code." "If we have the closure bytecodes constructClosureCreationNode: will note the copied values in the copiedValues inst var and answer #pushCopiedValues." closureCreationNode := self constructClosureCreationNode: encoder. "Remember size of body for emit time so we know the size of the jump around it." size := self sizeCodeForEvaluatedClosureValue: encoder. ^encoder supportsClosureOpcodes ifTrue: [(copiedValues inject: 0 into: [:sum :node| sum + (node sizeCodeForValue: encoder)]) + (encoder sizePushClosureCopyNumCopiedValues: copiedValues size numArgs: arguments size jumpSize: size) + size] ifFalse: ["closureCreationSupportNode is send closureCopy:copiedValues:" (closureCreationNode sizeCodeForValue: encoder) + (encoder sizeJumpLong: size) + size]! ! !BlockNode methodsFor: 'code generation (closures)' stamp: 'eem 5/31/2008 14:31'! sizeCodeForEvaluatedClosureValue: encoder "The closure value primitives push the arguments and the copied values. The compiler guarantees that any copied values come before all local temps. So on closure activation we only need to push nils for the remaining temporaries." ^temporaries size * (NodeNil sizeCodeForValue: encoder) + (self reindexingLocalsDo: [self sizeCodeForEvaluatedValue: encoder] encoder: nil "don't store temps yet") + (self returns ifTrue: [0] ifFalse: [encoder sizeReturnTopToCaller])! ! !BlockNode methodsFor: 'code generation (new scheme)' stamp: 'eem 6/2/2008 13:29'! emitCodeExceptLast: stack encoder: encoder | position nextToLast | position := stack position. nextToLast := statements size - 1. 1 to: nextToLast do: [:i | | statement | statement := statements at: i. statement emitCodeForEffect: stack encoder: encoder. self assert: stack position = position].! ! !BlockNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/21/2008 11:28'! emitCodeForEvaluatedEffect: stack encoder: encoder | position | position := stack position. self returns ifTrue: [self emitCodeForEvaluatedValue: stack encoder: encoder. stack pop: 1] ifFalse: [self emitCodeExceptLast: stack encoder: encoder. statements last emitCodeForEffect: stack encoder: encoder]. self assert: stack position = position! ! !BlockNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/21/2008 11:36'! emitCodeForEvaluatedValue: stack encoder: encoder | position | position := stack position. self emitCodeExceptLast: stack encoder: encoder. statements last emitCodeForBlockValue: stack encoder: encoder. self assert: stack position - 1 = position! ! !BlockNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/20/2008 16:55'! emitCodeForValue: stack encoder: encoder self generateAsClosure ifTrue: [^self emitCodeForClosureValue: stack encoder: encoder]. encoder genPushThisContext. stack push: 1. nArgsNode emitCodeForValue: stack encoder: encoder. remoteCopyNode emitCode: stack args: 1 encoder: encoder. "Force a two byte jump." encoder genJumpLong: size. stack push: arguments size. arguments reverseDo: [:arg | arg emitCodeForStorePop: stack encoder: encoder]. self emitCodeForEvaluatedValue: stack encoder: encoder. self returns ifFalse: [encoder genReturnTopToCaller. pc := encoder methodStreamPosition]. stack pop: 1! ! !BlockNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/29/2008 15:21'! sizeCodeExceptLast: encoder | codeSize | codeSize := 0. 1 to: statements size - 1 do: [:i | | statement | statement := statements at: i. codeSize := codeSize + (statement sizeCodeForEffect: encoder)]. ^codeSize! ! !BlockNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 17:13'! sizeCodeForEvaluatedEffect: encoder ^self returns ifTrue: [self sizeCodeForEvaluatedValue: encoder] ifFalse: [(self sizeCodeExceptLast: encoder) + (statements last sizeCodeForEffect: encoder)]! ! !BlockNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 14:52'! sizeCodeForEvaluatedValue: encoder ^(self sizeCodeExceptLast: encoder) + (statements last sizeCodeForBlockValue: encoder)! ! !BlockNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/20/2008 16:55'! sizeCodeForValue: encoder self generateAsClosure ifTrue: [^self sizeCodeForClosureValue: encoder]. nArgsNode := encoder encodeLiteral: arguments size. remoteCopyNode := encoder encodeSelector: #blockCopy:. size := self sizeCodeForEvaluatedValue: encoder. self returns ifFalse: [size := size + encoder sizeReturnTopToCaller]. "endBlock" arguments := arguments collect: "Chance to prepare debugger remote temps" [:arg | arg asStorableNode: encoder]. arguments do: [:arg | size := size + (arg sizeCodeForStorePop: encoder)]. ^encoder sizePushThisContext + (nArgsNode sizeCodeForValue: encoder) + (remoteCopyNode sizeCode: encoder args: 1 super: false) + (encoder sizeJumpLong: size) + size! ! !BlockNode methodsFor: 'equation translation'! statements ^statements! ! !BlockNode methodsFor: 'equation translation'! statements: val statements := val! ! !BlockNode methodsFor: 'initialize-release' stamp: 'eem 5/20/2008 13:40'! arguments: argNodes statements: statementsCollection returns: returnBool from: encoder "Compile." arguments := argNodes. statements := statementsCollection size > 0 ifTrue: [statementsCollection] ifFalse: [argNodes size > 0 ifTrue: [statementsCollection copyWith: arguments last] ifFalse: [Array with: NodeNil]]. optimized := false. returns := returnBool! ! !BlockNode methodsFor: 'initialize-release' stamp: 'eem 8/4/2008 14:12'! noteSourceRangeStart: start end: end encoder: encoder "Note two source ranges for this node. One is for the debugger and is of the last expression, the result of the block. One is for source analysis and is for the entire block." encoder noteSourceRange: (start to: end) forNode: self closureCreationNode. startOfLastStatement ifNil: [encoder noteSourceRange: (start to: end) forNode: self] ifNotNil: [encoder noteSourceRange: (startOfLastStatement to: end - 1) forNode: self]! ! !BlockNode methodsFor: 'initialize-release' stamp: 'eem 5/20/2008 13:40'! statements: statementsCollection returns: returnBool "Decompile." | returnLast | returnLast := returnBool. returns := false. statements := (statementsCollection size > 1 and: [(statementsCollection at: statementsCollection size - 1) isReturningIf]) ifTrue: [returnLast := false. statementsCollection allButLast] ifFalse: [statementsCollection size = 0 ifTrue: [Array with: NodeNil] ifFalse: [statementsCollection]]. arguments := #(). temporaries := #(). optimized := false. returnLast ifTrue: [self returnLast]! ! !BlockNode methodsFor: 'printing' stamp: 'alain.plantec 5/18/2009 15:34'! decompileString "Answer a string description of the parse tree whose root is the receiver." ^ self printString ! ! !BlockNode methodsFor: 'printing' stamp: 'eem 5/6/2008 14:28'! printArgumentsOn: aStream indent: level arguments size = 0 ifTrue: [^ self]. arguments do: [:arg | aStream nextPut: $:; nextPutAll: arg key; space]. aStream nextPut: $|; space. "If >0 args and >1 statement, put all statements on separate lines" statements size > 1 ifTrue: [aStream crtab: level]! ! !BlockNode methodsFor: 'printing' stamp: 'eem 9/25/2008 12:48'! printOn: aStream indent: level "statements size <= 1 ifFalse: [aStream crtab: level]." aStream nextPut: $[. self printArgumentsOn: aStream indent: level. (self printTemporaries: temporaries on: aStream doPrior: []) ifTrue: ["If >0 temps and >1 statement, put all statements on separate lines" statements size > 1 ifTrue: [aStream crtab: level] ifFalse: [aStream space]]. self printStatementsOn: aStream indent: level. aStream nextPut: $]! ! !BlockNode methodsFor: 'printing' stamp: 'eem 9/23/2008 15:05'! printStatementsOn: aStream indent: levelOrZero | len shown thisStatement level | level := 1 max: levelOrZero. comment == nil ifFalse: [self printCommentOn: aStream indent: level. aStream crtab: level]. len := shown := statements size. (levelOrZero = 0 "top level" and: [statements last isReturnSelf]) ifTrue: [shown := 1 max: shown - 1] ifFalse: ["should a trailing nil be printed or not? Not if it is an implicit result." (arguments size = 0 and: [len >= 1 and: [(statements at: len) == NodeNil and: [len = 1 or: [len > 1 and: [(statements at: len - 1) isMessageNode and: [(statements at: len - 1) isNilIf]]]]]]) ifTrue: [shown := shown - 1]]. 1 to: shown do: [:i | thisStatement := statements at: i. thisStatement printOn: aStream indent: level. i < shown ifTrue: [aStream nextPut: $.; crtab: level]. (thisStatement comment ~~ nil and: [thisStatement comment size > 0]) ifTrue: [i = shown ifTrue: [aStream crtab: level]. thisStatement printCommentOn: aStream indent: level. i < shown ifTrue: [aStream crtab: level]]]! ! !BlockNode methodsFor: 'printing' stamp: 'eem 7/21/2009 13:12'! printTemporaries: tempSequence on: aStream doPrior: aBlock "Print any in-scope temporaries. If there are any evaluate aBlock prior to printing. Answer whether any temporaries were printed." | tempStream seen | tempSequence ifNil: [^false]. tempStream := (String new: 16) writeStream. "This is for the decompiler which canmot work out which optimized block a particular temp is local to and hence may produce diplicates as in expr ifTrue: [| aTemp | ...] ifFalse: [| aTemp | ...]" seen := Set new. tempSequence do: [:tempNode | tempNode isIndirectTempVector ifTrue: [tempNode remoteTemps do: [:tempVariableNode| (tempVariableNode scope >= 0 and: [(seen includes: tempNode key) not]) ifTrue: [tempStream space; nextPutAll: (seen add: tempVariableNode key)]]] ifFalse: [(tempNode scope >= -1 and: ["This is for the decompiler which may create a block arg when converting a while into a to:do: but won't remove it form temporaries" tempNode isBlockArg not and: [(seen includes: tempNode key) not]]) ifTrue: [tempStream space; nextPutAll: (seen add: tempNode key)]]]. tempStream position = 0 ifTrue: [^false]. aBlock value. aStream nextPut: $|; nextPutAll: tempStream contents; space; nextPut: $|. ^true! ! !BlockNode methodsFor: 'printing' stamp: 'eem 6/2/2008 12:06'! printWithClosureAnalysisArgumentsOn: aStream indent: level arguments size = 0 ifTrue: [^self]. arguments do: [:tempNode | aStream space; nextPut: $:. tempNode printDefinitionForClosureAnalysisOn: aStream]. aStream nextPut: $|; space. "If >0 args and >1 statement, put all statements on separate lines" statements size > 1 ifTrue: [aStream crtab: level]! ! !BlockNode methodsFor: 'printing' stamp: 'eem 6/2/2008 11:53'! printWithClosureAnalysisOn: aStream indent: level aStream nextPut: $[. blockExtent ifNotNil: [aStream print: blockExtent]. self printWithClosureAnalysisArgumentsOn: aStream indent: level. self printWithClosureAnalysisTemporariesOn: aStream indent: level. self printWithClosureAnalysisStatementsOn: aStream indent: level. aStream nextPut: $]! ! !BlockNode methodsFor: 'printing' stamp: 'eem 6/2/2008 11:48'! printWithClosureAnalysisStatementsOn: aStream indent: levelOrZero | len shown thisStatement level | level := 1 max: levelOrZero. comment == nil ifFalse: [self printCommentOn: aStream indent: level. aStream crtab: level]. len := shown := statements size. (levelOrZero = 0 "top level" and: [statements last isReturnSelf]) ifTrue: [shown := 1 max: shown - 1] ifFalse: [(len = 1 and: [((statements at: 1) == NodeNil) & (arguments size = 0)]) ifTrue: [shown := shown - 1]]. 1 to: shown do: [:i | thisStatement := statements at: i. thisStatement printWithClosureAnalysisOn: aStream indent: level. i < shown ifTrue: [aStream nextPut: $.; crtab: level]. (thisStatement comment ~~ nil and: [thisStatement comment size > 0]) ifTrue: [i = shown ifTrue: [aStream crtab: level]. thisStatement printCommentOn: aStream indent: level. i < shown ifTrue: [aStream crtab: level]]]! ! !BlockNode methodsFor: 'printing' stamp: 'eem 6/2/2008 11:54'! printWithClosureAnalysisTemporariesOn: aStream indent: level (temporaries == nil or: [temporaries size = 0]) ifFalse: [aStream nextPut: $|. temporaries do: [:tempNode | aStream space. tempNode printDefinitionForClosureAnalysisOn: aStream]. aStream nextPutAll: ' | '. "If >0 args and >1 statement, put all statements on separate lines" statements size > 1 ifTrue: [aStream crtab: level]]! ! !BlockNode methodsFor: 'testing'! canBeSpecialArgument "Can I be an argument of (e.g.) ifTrue:?" ^arguments size = 0! ! !BlockNode methodsFor: 'testing' stamp: 'eem 7/17/2008 12:20'! generateAsClosure "Answer if we're compiling under the closure regime. If blockExtent has been set by analyseTempsWithin:rootNode: et al then we're compiling under the closure regime." ^blockExtent ~~ nil! ! !BlockNode methodsFor: 'testing' stamp: 'eem 9/25/2008 12:10'! isBlockNode ^true! ! !BlockNode methodsFor: 'testing'! isComplex ^statements size > 1 or: [statements size = 1 and: [statements first isComplex]]! ! !BlockNode methodsFor: 'testing'! isJust: node returns ifTrue: [^false]. ^statements size = 1 and: [statements first == node]! ! !BlockNode methodsFor: 'testing'! isJustCaseError ^ statements size = 1 and: [statements first isMessage: #caseError receiver: [:r | r==NodeSelf] arguments: nil]! ! !BlockNode methodsFor: 'testing'! isQuick ^ statements size = 1 and: [statements first isVariableReference or: [statements first isSpecialConstant]]! ! !BlockNode methodsFor: 'testing'! returns ^returns or: [statements last isReturningIf]! ! !BlockNode methodsFor: 'visiting' stamp: 'eem 9/10/2008 15:13'! accept: aVisitor aVisitor visitBlockNode: self! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BlockNode class instanceVariableNames: ''! !BlockNode class methodsFor: 'instance creation' stamp: 'sma 3/3/2000 13:34'! statements: statements returns: returns ^ self new statements: statements returns: returns! ! !BlockNode class methodsFor: 'instance creation' stamp: 'eem 5/19/2008 17:10'! withJust: aNode ^ self new statements: (Array with: aNode) returns: false! ! InstructionClient subclass: #BlockStartLocator instanceVariableNames: 'nextJumpIsAroundBlock' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Methods'! !BlockStartLocator methodsFor: 'initialize-release' stamp: 'alain.plantec 5/28/2009 09:43'! initialize super initialize. nextJumpIsAroundBlock := false! ! !BlockStartLocator methodsFor: 'instruction decoding' stamp: 'eem 5/31/2008 13:48'! jump: offset "If this jump is around a block answer the size of that block." nextJumpIsAroundBlock ifTrue: [nextJumpIsAroundBlock := false. ^offset]! ! !BlockStartLocator methodsFor: 'instruction decoding' stamp: 'eem 5/31/2008 13:54'! pushClosureCopyNumCopiedValues: numCopied numArgs: numArgs blockSize: blockSize "Answer the size of the block" ^blockSize! ! !BlockStartLocator methodsFor: 'instruction decoding' stamp: 'eem 5/31/2008 14:16'! send: selector super: supered numArgs: numberArguments nextJumpIsAroundBlock := #closureCopy:copiedValues: == selector "Don't use nextJumpIsAroundBlock := #(blockCopy: closureCopy:copiedValues:) includes: selector since BlueBook BlockContexts do not have their own temps."! ! Object subclass: #Boolean instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Objects'! !Boolean commentStamp: '' prior: 0! Boolean is an abstract class defining the protocol for logic testing operations and conditional control structures for the logical values represented by the instances of its subclasses True and False. Boolean redefines #new so no instances of Boolean can be created. It also redefines several messages in the 'copying' protocol to ensure that only one instance of each of its subclasses True (the global true, logical assertion) and False (the global false, logical negation) ever exist in the system.! !Boolean methodsFor: 'controlling'! and: alternativeBlock "Nonevaluating conjunction. If the receiver is true, answer the value of the argument, alternativeBlock; otherwise answer false without evaluating the argument." self subclassResponsibility! ! !Boolean methodsFor: 'controlling' stamp: 'zz 3/2/2004 23:44'! and: block1 and: block2 "Nonevaluating conjunction without deep nesting. The receiver is evaluated, followed by the blocks in order. If any of these evaluates as false, then return false immediately, without evaluating any further blocks. If all return true, then return true." self ifFalse: [^ false]. block1 value ifFalse: [^ false]. block2 value ifFalse: [^ false]. ^ true! ! !Boolean methodsFor: 'controlling' stamp: 'zz 3/2/2004 23:44'! and: block1 and: block2 and: block3 "Nonevaluating conjunction without deep nesting. The receiver is evaluated, followed by the blocks in order. If any of these evaluates as false, then return false immediately, without evaluating any further blocks. If all return true, then return true." self ifFalse: [^ false]. block1 value ifFalse: [^ false]. block2 value ifFalse: [^ false]. block3 value ifFalse: [^ false]. ^ true! ! !Boolean methodsFor: 'controlling' stamp: 'zz 3/2/2004 23:44'! and: block1 and: block2 and: block3 and: block4 "Nonevaluating conjunction without deep nesting. The receiver is evaluated, followed by the blocks in order. If any of these evaluates as false, then return false immediately, without evaluating any further blocks. If all return true, then return true." self ifFalse: [^ false]. block1 value ifFalse: [^ false]. block2 value ifFalse: [^ false]. block3 value ifFalse: [^ false]. block4 value ifFalse: [^ false]. ^ true! ! !Boolean methodsFor: 'controlling'! ifFalse: alternativeBlock "If the receiver is true (i.e., the condition is true), then the value is the true alternative, which is nil. Otherwise answer the result of evaluating the argument, alternativeBlock. Create an error notification if the receiver is nonBoolean. Execution does not actually reach here because the expression is compiled in-line." self subclassResponsibility! ! !Boolean methodsFor: 'controlling'! ifFalse: falseAlternativeBlock ifTrue: trueAlternativeBlock "Same as ifTrue:ifFalse:." self subclassResponsibility! ! !Boolean methodsFor: 'controlling'! ifTrue: alternativeBlock "If the receiver is false (i.e., the condition is false), then the value is the false alternative, which is nil. Otherwise answer the result of evaluating the argument, alternativeBlock. Create an error notification if the receiver is nonBoolean. Execution does not actually reach here because the expression is compiled in-line." self subclassResponsibility! ! !Boolean methodsFor: 'controlling'! ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock "If the receiver is true (i.e., the condition is true), then answer the value of the argument trueAlternativeBlock. If the receiver is false, answer the result of evaluating the argument falseAlternativeBlock. If the receiver is a nonBoolean then create an error notification. Execution does not actually reach here because the expression is compiled in-line." self subclassResponsibility! ! !Boolean methodsFor: 'controlling'! or: alternativeBlock "Nonevaluating disjunction. If the receiver is false, answer the value of the argument, alternativeBlock; otherwise answer true without evaluating the argument." self subclassResponsibility! ! !Boolean methodsFor: 'controlling' stamp: 'zz 3/2/2004 23:45'! or: block1 or: block2 "Nonevaluating alternation without deep nesting. The receiver is evaluated, followed by the blocks in order. If any of these evaluates as true, then return true immediately, without evaluating any further blocks. If all return false, then return false." self ifTrue: [^ true]. block1 value ifTrue: [^ true]. block2 value ifTrue: [^ true]. ^ false! ! !Boolean methodsFor: 'controlling' stamp: 'zz 3/2/2004 23:45'! or: block1 or: block2 or: block3 "Nonevaluating alternation without deep nesting. The receiver is evaluated, followed by the blocks in order. If any of these evaluates as true, then return true immediately, without evaluating any further blocks. If all return false, then return false." self ifTrue: [^ true]. block1 value ifTrue: [^ true]. block2 value ifTrue: [^ true]. block3 value ifTrue: [^ true]. ^ false! ! !Boolean methodsFor: 'controlling' stamp: 'zz 3/2/2004 23:45'! or: block1 or: block2 or: block3 or: block4 "Nonevaluating alternation without deep nesting. The receiver is evaluated, followed by the blocks in order. If any of these evaluates as true, then return true immediately, without evaluating any further blocks. If all return false, then return false." self ifTrue: [^ true]. block1 value ifTrue: [^ true]. block2 value ifTrue: [^ true]. block3 value ifTrue: [^ true]. block4 value ifTrue: [^ true]. ^ false! ! !Boolean methodsFor: 'controlling' stamp: 'dgd 9/26/2004 19:05'! or: block1 or: block2 or: block3 or: block4 or: block5 "Nonevaluating alternation without deep nesting. The receiver is evaluated, followed by the blocks in order. If any of these evaluates as true, then return true immediately, without evaluating any further blocks. If all return false, then return false." self ifTrue: [^ true]. block1 value ifTrue: [^ true]. block2 value ifTrue: [^ true]. block3 value ifTrue: [^ true]. block4 value ifTrue: [^ true]. block5 value ifTrue: [^ true]. ^ false! ! !Boolean methodsFor: 'copying' stamp: 'tk 6/26/1998 11:32'! clone "Receiver has two concrete subclasses, True and False. Only one instance of each should be made, so return self."! ! !Boolean methodsFor: 'copying'! deepCopy "Receiver has two concrete subclasses, True and False. Only one instance of each should be made, so return self."! ! !Boolean methodsFor: 'copying'! shallowCopy "Receiver has two concrete subclasses, True and False. Only one instance of each should be made, so return self."! ! !Boolean methodsFor: 'copying' stamp: 'tk 8/20/1998 16:07'! veryDeepCopyWith: deepCopier "Return self. I can't be copied. Do not record me."! ! !Boolean methodsFor: 'logical operations'! & aBoolean "Evaluating conjunction. Evaluate the argument. Then answer true if both the receiver and the argument are true." self subclassResponsibility! ! !Boolean methodsFor: 'logical operations' stamp: 'stephane.ducasse 5/20/2009 21:28'! ==> aBlock "The material conditional, also known as the material implication or truth functional conditional. Correspond to not ... or ... and does not correspond to the English if...then... construction. known as: b if a a implies b if a then b b is a consequence of a a therefore b (but note: 'it is raining therefore it is cloudy' is implication; 'it is autumn therefore the leaves are falling' is equivalence). Here is the truth table for material implication: p | q | p ==> q -------|-------|------------- T | T | T T | F | F F | T | T F | F | T " ^self not or: [aBlock value]! ! !Boolean methodsFor: 'logical operations'! eqv: aBoolean "Answer true if the receiver is equivalent to aBoolean." ^self == aBoolean! ! !Boolean methodsFor: 'logical operations'! not "Negation. Answer true if the receiver is false, answer false if the receiver is true." self subclassResponsibility! ! !Boolean methodsFor: 'logical operations'! | aBoolean "Evaluating disjunction (OR). Evaluate the argument. Then answer true if either the receiver or the argument is true." self subclassResponsibility! ! !Boolean methodsFor: 'printing' stamp: 'sw 9/27/2001 17:19'! basicType "Answer a symbol representing the inherent type of the receiver" ^ #Boolean! ! !Boolean methodsFor: 'printing' stamp: 'apb 4/21/2006 09:22'! isLiteral ^ true! ! !Boolean methodsFor: 'printing'! storeOn: aStream "Refer to the comment in Object|storeOn:." self printOn: aStream! ! !Boolean methodsFor: 'self evaluating' stamp: 'sd 7/31/2005 21:45'! isSelfEvaluating ^ true! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Boolean class instanceVariableNames: ''! !Boolean class methodsFor: 'instance creation' stamp: 'sw 5/5/2000 00:31'! initializedInstance ^ nil! ! !Boolean class methodsFor: 'instance creation'! new self error: 'You may not create any more Booleans - this is two-valued logic'! ! PreferenceView subclass: #BooleanPreferenceView instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Support'! !BooleanPreferenceView commentStamp: '' prior: 0! I am responsible for building the visual representation of a preference that accepts true and false values! !BooleanPreferenceView methodsFor: 'user interface' stamp: 'alain.plantec 5/30/2008 09:57'! offerPreferenceNameMenu: aPanel with: ignored1 in: ignored2 "the user clicked on a preference name -- put up a menu" | aMenu | ActiveHand showTemporaryCursor: nil. aMenu := MenuMorph new defaultTarget: self preference. aMenu addTitle: self preference name. (Preferences okayToChangeProjectLocalnessOf: self preference name) ifTrue: [aMenu addUpdating: #isProjectLocalString target: self preference action: #toggleProjectLocalness. aMenu balloonTextForLastItem: 'Some preferences are best applied uniformly to all projects, and others are best set by each individual project. If this item is checked, then this preference will be printed in bold and will have a separate value for each project']. aMenu add: 'browse senders' target: self systemNavigation selector: #browseAllCallsOn: argument: self preference name. aMenu balloonTextForLastItem: 'This will open a method-list browser on all methods that the send the preference "', self preference name, '".'. aMenu add: 'show category...' target: aPanel selector: #findCategoryFromPreference: argument: self preference name. aMenu balloonTextForLastItem: 'Allows you to find out which category, or categories, this preference belongs to.'. aMenu add: 'hand me a button for this preference' target: self selector: #tearOffButton. aMenu balloonTextForLastItem: 'Will give you a button that governs this preference, which you may deposit wherever you wish'. aMenu add: 'copy this name to clipboard' target: self preference selector: #copyName. aMenu balloonTextForLastItem: 'Copy the name of the preference to the text clipboard, so that you can paste into code somewhere'. aMenu popUpInWorld! ! !BooleanPreferenceView methodsFor: 'user interface' stamp: 'md 9/5/2005 15:40'! representativeButtonWithColor: aColor inPanel: aPreferencesPanel "Return a button that controls the setting of prefSymbol. It will keep up to date even if the preference value is changed in a different place" | outerButton aButton str miniWrapper | outerButton := AlignmentMorph newRow height: 24. outerButton color: (aColor ifNil: [Color r: 0.645 g: 1.0 b: 1.0]). outerButton hResizing: (aPreferencesPanel ifNil: [#shrinkWrap] ifNotNil: [#spaceFill]). outerButton vResizing: #shrinkWrap. outerButton addMorph: (aButton := UpdatingThreePhaseButtonMorph checkBox). aButton target: self preference; actionSelector: #togglePreferenceValue; getSelector: #preferenceValue. outerButton addTransparentSpacerOfSize: (2 @ 0). str := StringMorph contents: self preference name font: (StrikeFont familyName: 'NewYork' size: 12). self preference localToProject ifTrue: [str emphasis: TextEmphasis bold emphasisCode]. miniWrapper := AlignmentMorph newRow hResizing: #shrinkWrap; vResizing: #shrinkWrap. miniWrapper beTransparent addMorphBack: str lock. aPreferencesPanel ifNotNil: "We're in a Preferences panel" [miniWrapper on: #mouseDown send: #offerPreferenceNameMenu:with:in: to: self withValue: aPreferencesPanel. miniWrapper on: #mouseEnter send: #menuButtonMouseEnter: to: miniWrapper. miniWrapper on: #mouseLeave send: #menuButtonMouseLeave: to: miniWrapper. miniWrapper setBalloonText: 'Click here for a menu of options regarding this preference. Click on the checkbox to the left to toggle the setting of this preference'] ifNil: "We're a naked button, not in a panel" [miniWrapper setBalloonText: self preference helpString; setProperty: #balloonTarget toValue: aButton]. outerButton addMorphBack: miniWrapper. outerButton setNameTo: self preference name. aButton setBalloonText: self preference helpString. ^ outerButton "(Preferences preferenceAt: #balloonHelpEnabled) view tearOffButton"! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BooleanPreferenceView class instanceVariableNames: ''! !BooleanPreferenceView class methodsFor: 'initialization' stamp: 'hpt 9/26/2004 15:55'! initialize PreferenceViewRegistry ofBooleanPreferences register: self.! ! !BooleanPreferenceView class methodsFor: 'initialization' stamp: 'hpt 9/26/2004 15:55'! unload PreferenceViewRegistry ofBooleanPreferences unregister: self.! ! !BooleanPreferenceView class methodsFor: 'view registry' stamp: 'alain.plantec 6/6/2009 22:38'! handlesPanel: aPreferencePanel ^false! ! ClassTestCase subclass: #BooleanTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Objects'! !BooleanTest commentStamp: '' prior: 0! This is the unit test for the class Boolean. Unit tests are a good way to exercise the functionality of your system in a repeatable and automatic manner. They are therefore recommended if you plan to release anything. For more information, see: - http://www.c2.com/cgi/wiki?UnitTest - http://minnow.cc.gatech.edu/squeak/1547 - the sunit class category ! !BooleanTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:02'! testBooleanInitializedInstance self assert: (Boolean initializedInstance = nil).! ! !BooleanTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:02'! testBooleanNew self should: [Boolean new] raise: TestResult error. self should: [True new] raise: TestResult error. self should: [False new] raise: TestResult error. ! ! !BooleanTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:02'! testNew self should: [Boolean new] raise: TestResult error. ! ! Object subclass: #BorderStyle instanceVariableNames: '' classVariableNames: 'Default' poolDictionaries: '' category: 'Morphic-Borders'! !BorderStyle commentStamp: 'kfr 10/27/2003 10:19' prior: 0! See BorderedMorph BorderedMorh new borderStyle: (BorderStyle inset width: 2); openInWorld.! !BorderStyle methodsFor: '*Polymorph-Widgets' stamp: 'gvc 6/25/2008 12:09'! hasFillStyle "Answer false." ^false! ! !BorderStyle methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/14/2007 10:31'! isComposite "Answer false." ^false! ! !BorderStyle methodsFor: '*Polymorph-Widgets' stamp: 'gvc 2/25/2009 15:35'! printOn: aStream "Print a description of the receiver on the given stream." self storeOn: aStream! ! !BorderStyle methodsFor: '*Polymorph-Widgets' stamp: 'gvc 2/25/2009 15:34'! storeOn: aStream "Store a reconstructable representation of the receiver on the given stream." aStream nextPutAll: '(' , self class name; nextPutAll: ' width: '; print: self width; nextPutAll: ' color: '; print: self color; nextPutAll: ')'! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 8/25/2001 18:15'! baseColor ^Color transparent! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 8/25/2001 18:15'! baseColor: aColor "Ignored"! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:07'! color ^Color transparent! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:07'! color: aColor "Ignored"! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 11/26/2001 15:22'! colorsAtCorners ^Array new: 4 withAll: self color! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:07'! dotOfSize: diameter forDirection: aDirection | form | form := Form extent: diameter@diameter depth: Display depth. form getCanvas fillOval: form boundingBox color: self color. ^form! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 8/25/2001 17:51'! style ^#none! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:07'! width ^0! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:07'! width: aNumber "Ignored"! ! !BorderStyle methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:08'! widthForRounding ^self width! ! !BorderStyle methodsFor: 'color tracking' stamp: 'ar 8/25/2001 17:29'! trackColorFrom: aMorph "If necessary, update our color to reflect a change in aMorphs color"! ! !BorderStyle methodsFor: 'comparing' stamp: 'ar 8/25/2001 18:38'! = aBorderStyle ^self species = aBorderStyle species and:[self style == aBorderStyle style and:[self width = aBorderStyle width and:[self color = aBorderStyle color]]].! ! !BorderStyle methodsFor: 'comparing' stamp: 'ar 8/25/2001 16:08'! hash "hash is implemented because #= is implemented" ^self species hash bitXor: (self width hash bitXor: self color hash)! ! !BorderStyle methodsFor: 'drawing' stamp: 'ar 8/25/2001 17:01'! drawLineFrom: startPoint to: stopPoint on: aCanvas ^aCanvas line: startPoint to: stopPoint width: self width color: self color! ! !BorderStyle methodsFor: 'drawing' stamp: 'ar 8/25/2001 16:24'! frameOval: aRectangle on: aCanvas "Frame the given rectangle on aCanvas" aCanvas frameOval: aRectangle width: self width color: self color! ! !BorderStyle methodsFor: 'drawing' stamp: 'ar 8/25/2001 16:57'! framePolygon: vertices on: aCanvas "Frame the given rectangle on aCanvas" self framePolyline: vertices on: aCanvas. self drawLineFrom: vertices last to: vertices first on: aCanvas.! ! !BorderStyle methodsFor: 'drawing' stamp: 'dgd 2/21/2003 22:59'! framePolyline: vertices on: aCanvas "Frame the given rectangle on aCanvas" | prev next | prev := vertices first. 2 to: vertices size do: [:i | next := vertices at: i. self drawLineFrom: prev to: next on: aCanvas. prev := next]! ! !BorderStyle methodsFor: 'drawing' stamp: 'ar 8/25/2001 16:24'! frameRectangle: aRectangle on: aCanvas "Frame the given rectangle on aCanvas" aCanvas frameRectangle: aRectangle width: self width color: self color! ! !BorderStyle methodsFor: 'initialize' stamp: 'ar 8/25/2001 16:06'! releaseCachedState "Release any associated cached state"! ! !BorderStyle methodsFor: 'testing' stamp: 'ar 8/25/2001 16:08'! isBorderStyle ^true! ! !BorderStyle methodsFor: 'testing' stamp: 'ar 8/26/2001 19:30'! isComplex ^false! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BorderStyle class instanceVariableNames: ''! !BorderStyle class methodsFor: '*Polymorph-Widgets' stamp: 'gvc 8/8/2007 17:20'! dashed "Answer a dashed border style" ^DashedBorder new! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'sw 11/26/2001 16:05'! borderStyleChoices "Answer the superset of all supported borderStyle symbols" ^ #(simple inset raised complexAltFramed complexAltInset complexAltRaised complexFramed complexInset complexRaised)! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'yo 7/2/2004 17:21'! borderStyleForSymbol: sym "Answer a border style corresponding to the given symbol" | aSymbol | aSymbol := sym == #none ifTrue: [#simple] ifFalse: [sym]. ^ self perform: aSymbol " | aSymbol selector | aSymbol := sym == #none ifTrue: [#simple] ifFalse: [sym]. selector := Vocabulary eToyVocabulary translationKeyFor: aSymbol. selector isNil ifTrue: [selector := aSymbol]. ^ self perform: selector " ! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 8/25/2001 23:52'! color: aColor width: aNumber ^self width: aNumber color: aColor! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 11/26/2001 15:01'! complexAltFramed ^ComplexBorder style: #complexAltFramed! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 11/26/2001 15:01'! complexAltInset ^ComplexBorder style: #complexAltInset! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 11/26/2001 15:00'! complexAltRaised ^ComplexBorder style: #complexAltRaised! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 11/26/2001 15:00'! complexFramed ^ComplexBorder style: #complexFramed! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 11/26/2001 15:00'! complexInset ^ComplexBorder style: #complexInset! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 11/26/2001 15:00'! complexRaised ^ComplexBorder style: #complexRaised! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 8/25/2001 17:26'! default ^Default ifNil:[Default := self new]! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 11/26/2001 14:59'! inset ^InsetBorder new! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 11/26/2001 14:59'! raised ^RaisedBorder new! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'sw 11/27/2001 15:22'! simple "Answer a simple border style" ^ SimpleBorder new! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'rr 6/21/2005 13:50'! thinGray ^ self width: 1 color: Color gray! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 8/25/2001 16:19'! width: aNumber ^self width: aNumber color: Color black! ! !BorderStyle class methodsFor: 'instance creation' stamp: 'ar 8/25/2001 16:19'! width: aNumber color: aColor ^SimpleBorder new color: aColor; width: aNumber; yourself! ! Morph subclass: #BorderedMorph instanceVariableNames: 'borderWidth borderColor' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Kernel'! !BorderedMorph commentStamp: 'kfr 10/27/2003 11:17' prior: 0! BorderedMorph introduce borders to morph. Borders have the instanceVariables borderWidth and borderColor. BorderedMorph new borderColor: Color red; borderWidth: 10; openInWorld. BorderedMorph also have a varaity of border styles: simple, inset, raised, complexAltFramed, complexAltInset, complexAltRaised, complexFramed, complexInset, complexRaised. These styles are set using the classes BorderStyle, SimpleBorder, RaisedBorder, InsetBorder and ComplexBorder. BorderedMorph new borderStyle: (SimpleBorder width: 1 color: Color white); openInWorld. BorderedMorph new borderStyle: (BorderStyle inset width: 2); openInWorld. ! !BorderedMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 5/9/2006 15:50'! colorForInsets "Return the color to be used for shading inset borders." self owner isSystemWindow ifTrue: [^self owner colorForInsets]. ^super colorForInsets! ! !BorderedMorph methodsFor: 'accessing' stamp: 'sw 8/6/97 14:34'! borderColor ^ borderColor! ! !BorderedMorph methodsFor: 'accessing' stamp: 'ar 8/17/2001 16:52'! borderColor: colorOrSymbolOrNil self doesBevels ifFalse:[ colorOrSymbolOrNil isColor ifFalse:[^self]]. borderColor = colorOrSymbolOrNil ifFalse: [ borderColor := colorOrSymbolOrNil. self changed]. ! ! !BorderedMorph methodsFor: 'accessing' stamp: 'di 6/20/97 11:24'! borderInset self borderColor: #inset! ! !BorderedMorph methodsFor: 'accessing' stamp: 'di 6/20/97 11:25'! borderRaised self borderColor: #raised! ! !BorderedMorph methodsFor: 'accessing' stamp: 'aoy 2/17/2003 01:19'! borderStyle "Work around the borderWidth/borderColor pair" | style | borderColor ifNil: [^BorderStyle default]. borderWidth isZero ifTrue: [^BorderStyle default]. style := self valueOfProperty: #borderStyle ifAbsent: [BorderStyle default]. (borderWidth = style width and: ["Hah!! Try understanding this..." borderColor == style style or: ["#raised/#inset etc" #simple == style style and: [borderColor = style color]]]) ifFalse: [style := borderColor isColor ifTrue: [BorderStyle width: borderWidth color: borderColor] ifFalse: [(BorderStyle perform: borderColor) width: borderWidth "argh."]. self setProperty: #borderStyle toValue: style]. ^style trackColorFrom: self! ! !BorderedMorph methodsFor: 'accessing' stamp: 'dgd 2/21/2003 22:42'! borderStyle: aBorderStyle "Work around the borderWidth/borderColor pair" aBorderStyle = self borderStyle ifTrue: [^self]. "secure against invalid border styles" (self canDrawBorder: aBorderStyle) ifFalse: ["Replace the suggested border with a simple one" ^self borderStyle: (BorderStyle width: aBorderStyle width color: (aBorderStyle trackColorFrom: self) color)]. aBorderStyle width = self borderStyle width ifFalse: [self changed]. (aBorderStyle isNil or: [aBorderStyle == BorderStyle default]) ifTrue: [self removeProperty: #borderStyle. borderWidth := 0. ^self changed]. self setProperty: #borderStyle toValue: aBorderStyle. borderWidth := aBorderStyle width. borderColor := aBorderStyle style == #simple ifTrue: [aBorderStyle color] ifFalse: [aBorderStyle style]. self changed! ! !BorderedMorph methodsFor: 'accessing' stamp: 'di 6/20/97 11:09'! borderWidth ^ borderWidth! ! !BorderedMorph methodsFor: 'accessing' stamp: 'di 6/4/1999 09:42'! borderWidth: anInteger borderColor ifNil: [borderColor := Color black]. borderWidth := anInteger max: 0. self changed! ! !BorderedMorph methodsFor: 'accessing' stamp: 'di 6/20/97 11:19'! doesBevels "To return true means that this object can show bevelled borders, and therefore can accept, eg, #raised or #inset as valid borderColors. Must be overridden by subclasses that do not support bevelled borders." ^ true! ! !BorderedMorph methodsFor: 'accessing' stamp: 'di 1/3/1999 12:24'! hasTranslucentColor "Answer true if this any of this morph is translucent but not transparent." (color isColor and: [color isTranslucentColor]) ifTrue: [^ true]. (borderColor isColor and: [borderColor isTranslucentColor]) ifTrue: [^ true]. ^ false ! ! !BorderedMorph methodsFor: 'accessing' stamp: 'sw 11/29/1999 17:36'! useRoundedCorners self cornerStyle: #rounded! ! !BorderedMorph methodsFor: 'accessing' stamp: 'sw 11/29/1999 17:37'! useSquareCorners self cornerStyle: #square! ! !BorderedMorph methodsFor: 'geometry' stamp: 'sw 5/18/2001 22:52'! acquireBorderWidth: aBorderWidth "Gracefully acquire the new border width, keeping the interior area intact and not seeming to shift" | delta | (delta := aBorderWidth- self borderWidth) == 0 ifTrue: [^ self]. self bounds: ((self bounds origin - (delta @ delta)) corner: (self bounds corner + (delta @ delta))). self borderWidth: aBorderWidth. self layoutChanged! ! !BorderedMorph methodsFor: 'geometry' stamp: 'nk 4/5/2001 14:24'! closestPointTo: aPoint "account for round corners. Still has a couple of glitches at upper left and right corners" | pt | pt := self bounds pointNearestTo: aPoint. self wantsRoundedCorners ifFalse: [ ^pt ]. self bounds corners with: (self bounds insetBy: 6) corners do: [ :out :in | (pt - out) abs < (6@6) ifTrue: [ ^(in + (Point r: 5.0 degrees: (pt - in) degrees)) asIntegerPoint ]. ]. ^pt.! ! !BorderedMorph methodsFor: 'geometry' stamp: 'nk 4/5/2001 14:23'! intersectionWithLineSegmentFromCenterTo: aPoint "account for round corners. Still has a couple of glitches at upper left and right corners" | pt | pt := super intersectionWithLineSegmentFromCenterTo: aPoint. self wantsRoundedCorners ifFalse: [ ^pt ]. self bounds corners with: (self bounds insetBy: 6) corners do: [ :out :in | (pt - out) abs < (6@6) ifTrue: [ ^(in + (Point r: 5.0 degrees: (pt - in) degrees)) asIntegerPoint ]. ]. ^pt.! ! !BorderedMorph methodsFor: 'initialization' stamp: 'dgd 3/7/2003 15:53'! borderInitialize "initialize the receiver state related to border" borderColor:= self defaultBorderColor. borderWidth := self defaultBorderWidth! ! !BorderedMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:33'! defaultBorderColor "answer the default border color/fill style for the receiver" ^ Color black! ! !BorderedMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:36'! defaultBorderWidth "answer the default border width for the receiver" ^ 2! ! !BorderedMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 20:07'! initialize "initialize the state of the receiver" super initialize. "" self borderInitialize! ! !BorderedMorph methodsFor: 'lookenhancements' stamp: 'kfr 11/5/2006 21:36'! addCornerGrips self addMorphBack: (TopLeftGripMorph new target: self; position: self position). self addMorphBack: (TopRightGripMorph new target: self; position: self position). self addMorphBack: (BottomLeftGripMorph new target: self;position: self position). self addMorphBack: (BottomRightGripMorph new target: self;position: self position)! ! !BorderedMorph methodsFor: 'lookenhancements' stamp: 'kfr 11/5/2006 21:36'! addPaneHSplitterBetween: topMorph and: bottomMorphs | targetY minX maxX splitter | targetY := topMorph layoutFrame bottomFraction. minX := (bottomMorphs detectMin: [:each | each layoutFrame leftFraction]) layoutFrame leftFraction. maxX := (bottomMorphs detectMax: [:each | each layoutFrame rightFraction]) layoutFrame rightFraction. splitter := ProportionalSplitterMorph new beSplitsTopAndBottom; yourself. splitter layoutFrame: (LayoutFrame fractions: (minX @ targetY corner: maxX @ targetY) offsets: (((topMorph layoutFrame leftOffset ifNil: [0]) @ 0 corner: (topMorph layoutFrame rightOffset ifNil: [0]) @ 4) translateBy: 0 @ (topMorph layoutFrame bottomOffset ifNil: [0]))). self addMorphBack: (splitter position: self position).! ! !BorderedMorph methodsFor: 'lookenhancements' stamp: 'kfr 11/5/2006 21:34'! addPaneSplitters | splitter remaining target targetX sameX minY maxY targetY sameY minX maxX | self removePaneSplitters. self removeCornerGrips. remaining := submorphs reject: [:each | each layoutFrame rightFraction = 1]. [remaining notEmpty] whileTrue: [target := remaining first. targetX := target layoutFrame rightFraction. sameX := submorphs select: [:each | each layoutFrame rightFraction = targetX]. minY := (sameX detectMin: [:each | each layoutFrame topFraction]) layoutFrame topFraction. maxY := (sameX detectMax: [:each | each layoutFrame bottomFraction]) layoutFrame bottomFraction. splitter := ProportionalSplitterMorph new. splitter layoutFrame: (LayoutFrame fractions: (targetX @ minY corner: targetX @ maxY) offsets: ((0 @ (target layoutFrame topOffset ifNil: [0]) corner: 4 @ (target layoutFrame bottomOffset ifNil: [0])) translateBy: (target layoutFrame rightOffset ifNil: [0]) @ 0)). self addMorphBack: (splitter position: self position). remaining := remaining copyWithoutAll: sameX]. remaining := submorphs copy reject: [:each | each layoutFrame bottomFraction = 1]. [remaining notEmpty] whileTrue: [target := remaining first. targetY := target layoutFrame bottomFraction. sameY := submorphs select: [:each | each layoutFrame bottomFraction = targetY]. minX := (sameY detectMin: [:each | each layoutFrame leftFraction]) layoutFrame leftFraction. maxX := (sameY detectMax: [:each | each layoutFrame rightFraction]) layoutFrame rightFraction. splitter := ProportionalSplitterMorph new beSplitsTopAndBottom; yourself. splitter layoutFrame: (LayoutFrame fractions: (minX @ targetY corner: maxX @ targetY) offsets: (((target layoutFrame leftOffset ifNil: [0]) @ 0 corner: (target layoutFrame rightOffset ifNil: [0]) @ 4) translateBy: 0 @ (target layoutFrame bottomOffset ifNil: [0]))). self addMorphBack: (splitter position: self position). remaining := remaining copyWithoutAll: sameY]. self linkSubmorphsToSplitters. self splitters do: [:each | each comeToFront]. ! ! !BorderedMorph methodsFor: 'lookenhancements' stamp: 'kfr 11/5/2006 21:37'! addPaneVSplitterBetween: leftMorph and: rightMorphs | targetX minY maxY splitter | targetX := leftMorph layoutFrame rightFraction. minY := (rightMorphs detectMin: [:each | each layoutFrame topFraction]) layoutFrame topFraction. maxY := (rightMorphs detectMax: [:each | each layoutFrame bottomFraction]) layoutFrame bottomFraction. splitter := ProportionalSplitterMorph new. splitter layoutFrame: (LayoutFrame fractions: (targetX @ minY corner: targetX @ maxY) offsets: ((0 @ (leftMorph layoutFrame topOffset ifNil: [0]) corner: (4@ (leftMorph layoutFrame bottomOffset ifNil: [0]))) translateBy: (leftMorph layoutFrame rightOffset ifNil: [0]) @ 0)). self addMorphBack: (splitter position: self position).! ! !BorderedMorph methodsFor: 'lookenhancements' stamp: 'jrp 7/23/2005 22:16'! linkSubmorphsToSplitters self splitters do: [:each | each splitsTopAndBottom ifTrue: [self submorphsDo: [:eachMorph | (eachMorph ~= each and: [eachMorph layoutFrame bottomFraction = each layoutFrame topFraction]) ifTrue: [each addLeftOrTop: eachMorph]. (eachMorph ~= each and: [eachMorph layoutFrame topFraction = each layoutFrame bottomFraction]) ifTrue: [each addRightOrBottom: eachMorph]]] ifFalse: [self submorphsDo: [:eachMorph | (eachMorph ~= each and: [eachMorph layoutFrame rightFraction = each layoutFrame leftFraction]) ifTrue: [each addLeftOrTop: eachMorph]. (eachMorph ~= each and: [eachMorph layoutFrame leftFraction = each layoutFrame rightFraction]) ifTrue: [each addRightOrBottom: eachMorph]]]]! ! !BorderedMorph methodsFor: 'lookenhancements' stamp: 'jrp 7/23/2005 00:03'! removeCornerGrips | corners | corners := self submorphsSatisfying: [:each | each isKindOf: CornerGripMorph]. corners do: [:each | each delete]! ! !BorderedMorph methodsFor: 'lookenhancements' stamp: 'jrp 7/23/2005 22:28'! removePaneSplitters self splitters do: [:each | each delete]! ! !BorderedMorph methodsFor: 'lookenhancements' stamp: 'jrp 7/23/2005 22:16'! splitters ^ self submorphsSatisfying: [:each | each isKindOf: ProportionalSplitterMorph]! ! !BorderedMorph methodsFor: 'menu' stamp: 'dgd 9/18/2004 19:16'! addBorderStyleMenuItems: aMenu hand: aHandMorph "Add border-style menu items" | subMenu | subMenu := MenuMorph new defaultTarget: self. "subMenu addTitle: 'border' translated." subMenu addStayUpItemSpecial. subMenu addList: {{'border color...' translated. #changeBorderColor:}. {'border width...' translated. #changeBorderWidth:}}. subMenu addLine. BorderStyle borderStyleChoices do: [:sym | (self borderStyleForSymbol: sym) ifNotNil: [subMenu add: sym translated target: self selector: #setBorderStyle: argument: sym]]. aMenu add: 'border style' translated subMenu: subMenu ! ! !BorderedMorph methodsFor: 'menu' stamp: 'ar 10/5/2000 18:50'! changeBorderColor: evt | aHand | aHand := evt ifNotNil: [evt hand] ifNil: [self primaryHand]. self changeColorTarget: self selector: #borderColor: originalColor: self borderColor hand: aHand! ! !BorderedMorph methodsFor: 'menu' stamp: 'marcus.denker 11/10/2008 10:04'! changeBorderWidth: evt | handle origin aHand newWidth oldWidth | aHand := evt ifNil: [self primaryHand] ifNotNil: [evt hand]. origin := aHand position. oldWidth := borderWidth. handle := HandleMorph new forEachPointDo: [:newPoint | handle removeAllMorphs. handle addMorph: (LineMorph from: origin to: newPoint color: Color black width: 1). newWidth := (newPoint - origin) r asInteger // 5. self borderWidth: newWidth] lastPointDo: [:newPoint | handle deleteBalloon. self halo ifNotNil: [:halo | halo addHandles]. self rememberCommand: (Command new cmdWording: 'border change' translated; undoTarget: self selector: #borderWidth: argument: oldWidth; redoTarget: self selector: #borderWidth: argument: newWidth)]. aHand attachMorph: handle. handle setProperty: #helpAtCenter toValue: true. handle showBalloon: 'Move cursor farther from this point to increase border width. Click when done.' translated hand: evt hand. handle startStepping! ! !BorderedMorph methodsFor: 'private' stamp: 'di 6/20/97 11:21'! setBorderWidth: w borderColor: bc self borderWidth: w. self borderColor: bc.! ! !BorderedMorph methodsFor: 'private' stamp: 'di 6/20/97 11:22'! setColor: c borderWidth: w borderColor: bc self color: c. self borderWidth: w. self borderColor: bc.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BorderedMorph class instanceVariableNames: ''! !BorderedMorph class methodsFor: 'examples' stamp: 'StephaneDucasse 9/6/2009 15:53'! gradientExample "self gradientExample" | morph fs | morph := BorderedMorph new. fs := GradientFillStyle ramp: {0.0 -> Color red. 1.0 -> Color green}. fs origin: morph bounds center. fs direction: (morph bounds width // 2) @ 0. fs radial: true. morph fillStyle: fs. World primaryHand attachMorph: morph.! ! BorderedMorph subclass: #BorderedSubpaneDividerMorph instanceVariableNames: 'resizingEdge' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Windows'! !BorderedSubpaneDividerMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 4/2/2007 13:56'! adoptPaneColor: paneColor "Match the color." super adoptPaneColor: paneColor. paneColor ifNil: [^self]. self color: paneColor! ! !BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'! firstEnter: evt "The first time this divider is activated, find its window and redirect further interaction there." | window | window := self firstOwnerSuchThat: [:m | m respondsTo: #secondaryPaneTransition:divider:]. window ifNil: [ self suspendEventHandler. ^ self ]. "not working out" window secondaryPaneTransition: evt divider: self. self on: #mouseEnter send: #secondaryPaneTransition:divider: to: window. ! ! !BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'! horizontal self hResizing: #spaceFill.! ! !BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'! resizingEdge ^resizingEdge ! ! !BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'! resizingEdge: edgeSymbol (#(top bottom) includes: edgeSymbol) ifFalse: [ self error: 'resizingEdge must be #top or #bottom' ]. resizingEdge := edgeSymbol. self on: #mouseEnter send: #firstEnter: to: self. ! ! !BorderedSubpaneDividerMorph methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'! vertical self vResizing: #spaceFill.! ! !BorderedSubpaneDividerMorph methodsFor: 'initialization' stamp: 'dgd 3/7/2003 14:09'! defaultBorderWidth "answer the default border width for the receiver" ^ 0! ! !BorderedSubpaneDividerMorph methodsFor: 'initialization' stamp: 'dgd 3/7/2003 14:09'! defaultColor "answer the default color/fill style for the receiver" ^ Color black! ! !BorderedSubpaneDividerMorph methodsFor: 'initialization' stamp: 'dgd 3/7/2003 14:09'! initialize "initialize the state of the receiver" super initialize. "" self extent: 1 @ 1! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BorderedSubpaneDividerMorph class instanceVariableNames: ''! !BorderedSubpaneDividerMorph class methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:24'! forBottomEdge ^self new horizontal resizingEdge: #bottom! ! !BorderedSubpaneDividerMorph class methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:25'! forTopEdge ^self new horizontal resizingEdge: #top! ! !BorderedSubpaneDividerMorph class methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:25'! horizontal ^self new horizontal! ! !BorderedSubpaneDividerMorph class methodsFor: 'as yet unclassified' stamp: 'ar 8/15/2001 23:25'! vertical ^self new vertical! ! CornerGripMorph subclass: #BottomLeftGripMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Windows'! !BottomLeftGripMorph commentStamp: 'jmv 1/29/2006 17:17' prior: 0! I am the handle in the left bottom of windows used for resizing them.! !BottomLeftGripMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 7/30/2009 13:47'! containsPoint: aPoint "Answer true only if on edges." |w| ^(super containsPoint: aPoint) and: [ w := SystemWindow borderWidth. ((self bounds translateBy: w@w negated) containsPoint: aPoint) not]! ! !BottomLeftGripMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 5/13/2008 10:21'! drawOn: aCanvas "Draw the grip on the given canvas." | dotBounds alphaCanvas windowBorderWidth dotBounds2 | self shouldDraw ifFalse: [^self]. windowBorderWidth := SystemWindow borderWidth. alphaCanvas := aCanvas asAlphaBlendingCanvas: 0.7. "alphaCanvas frameRectangle: bounds color: Color blue." dotBounds := self bounds. dotBounds2 := dotBounds right: (dotBounds left + windowBorderWidth). dotBounds2 := dotBounds2 top: (dotBounds2 bottom - windowBorderWidth). alphaCanvas fillRectangle: dotBounds2 color: self handleColor. dotBounds2 := dotBounds left: (dotBounds left + windowBorderWidth). dotBounds2 := dotBounds2 top: (dotBounds2 bottom - windowBorderWidth). alphaCanvas fillRectangle: dotBounds2 color: self handleColor. dotBounds2 := dotBounds2 left: (dotBounds2 left + 7). dotBounds2 := dotBounds2 right: (dotBounds2 right - 7). alphaCanvas fillRectangle: dotBounds2 color: self dotColor. dotBounds2 := dotBounds right: (dotBounds left + windowBorderWidth). dotBounds2 := dotBounds2 bottom: (dotBounds2 bottom - windowBorderWidth). alphaCanvas fillRectangle: dotBounds2 color: self handleColor. dotBounds2 := dotBounds2 top: (dotBounds2 top + 7). dotBounds2 := dotBounds2 bottom: (dotBounds2 bottom - 7). alphaCanvas fillRectangle: dotBounds2 color: self dotColor! ! !BottomLeftGripMorph methodsFor: 'accessing' stamp: 'jmv 2/2/2006 14:26'! gripLayoutFrame ^ LayoutFrame fractions: (0 @ 1 corner: 0 @ 1) offsets: (0 @ (0 - self defaultHeight) corner: self defaultWidth @ 0)! ! !BottomLeftGripMorph methodsFor: 'accessing' stamp: 'md 2/24/2006 22:43'! ptName ^#bottomLeft! ! !BottomLeftGripMorph methodsFor: 'accessing' stamp: 'jmv 1/29/2006 17:52'! resizeCursor ^ Cursor resizeForEdge: #bottomLeft! ! !BottomLeftGripMorph methodsFor: 'target resize' stamp: 'jmv 1/29/2006 18:06'! apply: delta | oldBounds | oldBounds := target bounds. target bounds: (oldBounds origin + (delta x @ 0) corner: oldBounds corner + (0 @ delta y))! ! CornerGripMorph subclass: #BottomRightGripMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Windows'! !BottomRightGripMorph commentStamp: 'jmv 1/29/2006 17:18' prior: 0! I am the handle in the right bottom of windows used for resizing them.! !BottomRightGripMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/12/2007 10:52'! containsPoint: aPoint "Answer true only if on edges." |w| ^(super containsPoint: aPoint) and: [ w := SystemWindow borderWidth. ((self bounds translateBy: (w@w) negated) containsPoint: aPoint) not]! ! !BottomRightGripMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 5/13/2008 10:21'! drawOn: aCanvas "Draw the grip on the given canvas." | dotBounds alphaCanvas windowBorderWidth dotBounds2 | self shouldDraw ifFalse: [^self]. windowBorderWidth := SystemWindow borderWidth. alphaCanvas := aCanvas asAlphaBlendingCanvas: 0.7. "alphaCanvas frameRectangle: bounds color: Color blue." dotBounds := self bounds. dotBounds2 := dotBounds left: (dotBounds right - windowBorderWidth). dotBounds2 := dotBounds2 top: (dotBounds2 bottom - windowBorderWidth). alphaCanvas fillRectangle: dotBounds2 color: self handleColor. dotBounds2 := dotBounds right: (dotBounds right - windowBorderWidth). dotBounds2 := dotBounds2 top: (dotBounds2 bottom - windowBorderWidth). alphaCanvas fillRectangle: dotBounds2 color: self handleColor. dotBounds2 := dotBounds2 left: (dotBounds2 left + 7). dotBounds2 := dotBounds2 right: (dotBounds2 right - 7). alphaCanvas fillRectangle: dotBounds2 color: self dotColor. dotBounds2 := dotBounds left: (dotBounds right - windowBorderWidth). dotBounds2 := dotBounds2 bottom: (dotBounds2 bottom - windowBorderWidth). alphaCanvas fillRectangle: dotBounds2 color: self handleColor. dotBounds2 := dotBounds2 top: (dotBounds2 top + 7). dotBounds2 := dotBounds2 bottom: (dotBounds2 bottom - 7). alphaCanvas fillRectangle: dotBounds2 color: self dotColor! ! !BottomRightGripMorph methodsFor: 'accessing' stamp: 'jmv 2/2/2006 14:27'! gripLayoutFrame ^ LayoutFrame fractions: (1 @ 1 corner: 1 @ 1) offsets: (0 - self defaultWidth @ (0 - self defaultHeight) corner: 0 @ 0)! ! !BottomRightGripMorph methodsFor: 'accessing' stamp: 'md 2/24/2006 22:43'! ptName ^#bottomRight! ! !BottomRightGripMorph methodsFor: 'accessing' stamp: 'jmv 1/29/2006 17:51'! resizeCursor ^ Cursor resizeForEdge: #bottomRight! ! !BottomRightGripMorph methodsFor: 'target resize' stamp: 'jmv 1/29/2006 17:59'! apply: delta | oldBounds | oldBounds := target bounds. target bounds: (oldBounds origin corner: oldBounds corner + delta)! ! GradientFillStyle subclass: #BoundedGradientFillStyle instanceVariableNames: 'extent' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-FillStyles'! !BoundedGradientFillStyle commentStamp: 'gvc 3/13/2009 12:19' prior: 0! Gradient fillstyle that draws with optional extent.! !BoundedGradientFillStyle methodsFor: 'accessing' stamp: 'gvc 3/13/2009 12:22'! extent "Answer the value of extent" ^ extent! ! !BoundedGradientFillStyle methodsFor: 'accessing' stamp: 'gvc 3/13/2009 12:22'! extent: anObject "Set the value of extent" extent := anObject! ! !BoundedGradientFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 3/13/2009 12:39'! = aGradientFillStyle "Answer whether equal." ^super = aGradientFillStyle and: [self extent = aGradientFillStyle extent]! ! !BoundedGradientFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 3/13/2009 12:22'! fillRectangle: aRectangle on: aCanvas "Fill the given rectangle on the given canvas with the receiver." self extent ifNil: [^super fillRectangle: aRectangle on: aCanvas]. aCanvas fillRectangle: ((self origin extent: self extent) intersect: aRectangle) basicFillStyle: self! ! !BoundedGradientFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 3/13/2009 12:39'! hash "Hash is implemented because #= is implemented." ^super hash bitXor: self extent hash! ! ParseNode subclass: #BraceNode instanceVariableNames: 'elements sourceLocations emitNode' classVariableNames: '' poolDictionaries: '' category: 'Compiler-ParseNodes'! !BraceNode commentStamp: '' prior: 0! Used for compiling and decompiling brace constructs. These now compile into either a fast short form for 4 elements or less: Array braceWith: a with: b ... or a long form of indefinfite length: (Array braceStream: N) nextPut: a; nextPut: b; ...; braceArray. The erstwhile brace assignment form is no longer supported.! !BraceNode methodsFor: 'code generation' stamp: 'di 11/19/1999 08:58'! emitForValue: stack on: aStream ^ emitNode emitForValue: stack on: aStream! ! !BraceNode methodsFor: 'code generation' stamp: 'di 1/4/2000 11:24'! selectorForShortForm: nElements nElements > 4 ifTrue: [^ nil]. ^ #(braceWithNone braceWith: braceWith:with: braceWith:with:with: braceWith:with:with:with:) at: nElements + 1! ! !BraceNode methodsFor: 'code generation' stamp: 'di 11/19/1999 11:13'! sizeForValue: encoder emitNode := elements size <= 4 ifTrue: ["Short form: Array braceWith: a with: b ... " MessageNode new receiver: (encoder encodeVariable: #Array) selector: (self selectorForShortForm: elements size) arguments: elements precedence: 3 from: encoder] ifFalse: ["Long form: (Array braceStream: N) nextPut: a; nextPut: b; ...; braceArray" CascadeNode new receiver: (MessageNode new receiver: (encoder encodeVariable: #Array) selector: #braceStream: arguments: (Array with: (encoder encodeLiteral: elements size)) precedence: 3 from: encoder) messages: ((elements collect: [:elt | MessageNode new receiver: nil selector: #nextPut: arguments: (Array with: elt) precedence: 3 from: encoder]) copyWith: (MessageNode new receiver: nil selector: #braceArray arguments: (Array new) precedence: 1 from: encoder))]. ^ emitNode sizeForValue: encoder! ! !BraceNode methodsFor: 'code generation (closures)' stamp: 'eem 7/20/2009 09:33'! analyseTempsWithin: scopeBlock "" rootNode: rootNode "" assignmentPools: assignmentPools "" elements do: [:node| node analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools]! ! !BraceNode methodsFor: 'code generation (closures)' stamp: 'eem 5/21/2008 10:40'! elements ^elements! ! !BraceNode methodsFor: 'code generation (closures)' stamp: 'eem 5/30/2008 17:22'! maxElementsForConsArray "Hack; we have no way of knowing how much stack space is available during sizing" ^8! ! !BraceNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/30/2008 17:40'! emitCodeForValue: stack encoder: encoder (encoder supportsClosureOpcodes "Hack; we have no way of knowing how much stack space is available" and: [elements size <= self maxElementsForConsArray]) ifTrue: [elements do: [:node| node emitCodeForValue: stack encoder: encoder]. encoder genPushConsArray: elements size. stack pop: elements size; push: 1. ^self]. ^emitNode emitCodeForValue: stack encoder: encoder! ! !BraceNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/30/2008 17:22'! sizeCodeForValue: encoder (encoder supportsClosureOpcodes "Hack; we have no way of knowing how much stack space is available" and: [elements size <= self maxElementsForConsArray]) ifTrue: [^(elements inject: 0 into: [:sum :node| sum + (node sizeCodeForValue: encoder)]) + (encoder sizePushConsArray: elements size)]. emitNode := elements size <= 4 ifTrue: ["Short form: Array braceWith: a with: b ... " MessageNode new receiver: (encoder encodeVariable: #Array) selector: (self selectorForShortForm: elements size) arguments: elements precedence: 3 from: encoder] ifFalse: ["Long form: (Array braceStream: N) nextPut: a; nextPut: b; ...; braceArray" CascadeNode new receiver: (MessageNode new receiver: (encoder encodeVariable: #Array) selector: #braceStream: arguments: (Array with: (encoder encodeLiteral: elements size)) precedence: 3 from: encoder) messages: ((elements collect: [:elt | MessageNode new receiver: nil selector: #nextPut: arguments: (Array with: elt) precedence: 3 from: encoder]) copyWith: (MessageNode new receiver: nil selector: #braceArray arguments: (Array new) precedence: 1 from: encoder))]. ^emitNode sizeCodeForValue: encoder! ! !BraceNode methodsFor: 'enumerating'! casesForwardDo: aBlock "For each case in forward order, evaluate aBlock with three arguments: the key block, the value block, and whether it is the last case." | numCases case | 1 to: (numCases := elements size) do: [:i | case := elements at: i. aBlock value: case receiver value: case arguments first value: i=numCases]! ! !BraceNode methodsFor: 'enumerating'! casesReverseDo: aBlock "For each case in reverse order, evaluate aBlock with three arguments: the key block, the value block, and whether it is the last case." | numCases case | (numCases := elements size) to: 1 by: -1 do: [:i | case := elements at: i. aBlock value: case receiver value: case arguments first value: i=numCases]! ! !BraceNode methodsFor: 'initialize-release'! elements: collection "Decompile." elements := collection! ! !BraceNode methodsFor: 'initialize-release'! elements: collection sourceLocations: locations "Compile." elements := collection. sourceLocations := locations! ! !BraceNode methodsFor: 'initialize-release' stamp: 'di 11/19/1999 11:06'! matchBraceStreamReceiver: receiver messages: messages ((receiver isMessage: #braceStream: receiver: nil arguments: [:arg | arg isConstantNumber]) and: [messages last isMessage: #braceArray receiver: nil arguments: nil]) ifFalse: [^ nil "no match"]. "Appears to be a long form brace construct" self elements: (messages allButLast collect: [:msg | (msg isMessage: #nextPut: receiver: nil arguments: nil) ifFalse: [^ nil "not a brace element"]. msg arguments first])! ! !BraceNode methodsFor: 'initialize-release' stamp: 'di 11/19/1999 11:19'! matchBraceWithReceiver: receiver selector: selector arguments: arguments selector = (self selectorForShortForm: arguments size) ifFalse: [^ nil "no match"]. "Appears to be a short form brace construct" self elements: arguments! ! !BraceNode methodsFor: 'printing' stamp: 'di 11/19/1999 09:17'! printOn: aStream indent: level aStream nextPut: ${. 1 to: elements size do: [:i | (elements at: i) printOn: aStream indent: level. i < elements size ifTrue: [aStream nextPutAll: '. ']]. aStream nextPut: $}! ! !BraceNode methodsFor: 'printing' stamp: 'eem 6/2/2008 11:47'! printWithClosureAnalysisOn: aStream indent: level aStream nextPut: ${. 1 to: elements size do: [:i | (elements at: i) printWithClosureAnalysisOn: aStream indent: level. i < elements size ifTrue: [aStream nextPutAll: '. ']]. aStream nextPut: $}! ! !BraceNode methodsFor: 'testing' stamp: 'eem 9/25/2008 14:48'! blockAssociationCheck: encoder "If all elements are MessageNodes of the form [block]->[block], and there is at least one element, answer true. Otherwise, notify encoder of an error." elements size = 0 ifTrue: [^encoder notify: 'At least one case required']. elements with: sourceLocations do: [:x :loc | (x isMessage: #-> receiver: [:rcvr | rcvr isBlockNode and: [rcvr numberOfArguments = 0]] arguments: [:arg | arg isBlockNode and: [arg numberOfArguments = 0]]) ifFalse: [^encoder notify: 'Association between 0-argument blocks required' at: loc]]. ^true! ! !BraceNode methodsFor: 'testing'! numElements ^ elements size! ! !BraceNode methodsFor: 'visiting' stamp: 'eem 9/10/2008 15:14'! accept: aVisitor aVisitor visitBraceNode: self! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BraceNode class instanceVariableNames: ''! !BraceNode class methodsFor: 'examples' stamp: 'di 11/19/1999 09:05'! example "Test the {a. b. c} syntax." | x | x := {1. {2. 3}. 4}. ^ {x first. x second first. x second last. x last. 5} as: Set "BraceNode example Set (0 1 2 3 4 5 )" ! ! Morph subclass: #BracketMorph instanceVariableNames: 'orientation' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !BracketMorph commentStamp: 'gvc 5/18/2007 13:48' prior: 0! Morph displaying opposing arrows.! !BracketMorph methodsFor: 'accessing' stamp: 'gvc 9/21/2006 15:48'! horizontal "Answer whether horizontal or vertical." ^self orientation == #horizontal! ! !BracketMorph methodsFor: 'accessing' stamp: 'gvc 9/19/2006 15:54'! horizontal: aBoolean "Set whether horizontal or vertical." ^self orientation: (aBoolean ifTrue: [#horizontal] ifFalse: [#vertical])! ! !BracketMorph methodsFor: 'accessing' stamp: 'gvc 9/19/2006 15:51'! orientation "Answer the value of orientation" ^ orientation! ! !BracketMorph methodsFor: 'accessing' stamp: 'gvc 9/19/2006 15:52'! orientation: anObject "Set the value of orientation" orientation := anObject. self changed! ! !BracketMorph methodsFor: 'drawing' stamp: 'gvc 9/21/2006 16:16'! drawOn: aCanvas "Draw triangles at the edges." |r| r := self horizontal ifTrue: [self bounds insetBy: (2@1 corner: 2@1)] ifFalse: [self bounds insetBy: (1@2 corner: 1@2)]. aCanvas drawPolygon: (self leftOrTopVertices: self bounds) fillStyle: self borderColor; drawPolygon: (self leftOrTopVertices: r) fillStyle: self fillStyle; drawPolygon: (self rightOrBottomVertices: self bounds) fillStyle: self borderColor; drawPolygon: (self rightOrBottomVertices: r) fillStyle: self fillStyle! ! !BracketMorph methodsFor: 'geometry' stamp: 'gvc 9/21/2006 15:45'! leftOrTopVertices: r "Answer the vertices for a left or top bracket in the given rectangle." ^self orientation == #vertical ifTrue: [{r topLeft - (0@1). r left + (r height // 2 + (r height \\ 2))@(r center y - (r height + 1 \\ 2)). r left + (r height // 2 + (r height \\ 2))@(r center y). r bottomLeft}] ifFalse: [{r topLeft. (r center x - (r width + 1 \\ 2))@(r top + (r width // 2 + (r width \\ 2))). r center x@(r top + (r width // 2 + (r width \\ 2))). r topRight}]! ! !BracketMorph methodsFor: 'geometry' stamp: 'gvc 9/21/2006 16:18'! rightOrBottomVertices: r "Answer the vertices for a right or bottom bracket in the given rectangle." ^self orientation == #vertical ifTrue: [{r topRight - (0@1). r right - (r height // 2 + (r height \\ 2))@(r center y - (r height + 1 \\ 2)). r right - (r height // 2 + (r height \\ 2))@(r center y). r bottomRight}] ifFalse: [{(r center x)@(r bottom - 1 - (r width // 2 + (r width \\ 2))). r center x @(r bottom - 1 - (r width // 2 + (r width \\ 2))). r bottomRight. r bottomLeft - (1@0)}]! ! !BracketMorph methodsFor: 'initialization' stamp: 'gvc 9/19/2006 15:52'! initialize "Initialize the receiver." super initialize. self orientation: #horizontal! ! PluggableSliderMorph subclass: #BracketSliderMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !BracketSliderMorph commentStamp: 'gvc 5/18/2007 13:39' prior: 0! Abstract superclass for morphs that are used to select a component (R, G, B or A) of a colour.! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/3/2009 13:40'! defaultFillStyle "Answer the defauolt fill style." ^Color gray! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/3/2009 13:40'! extent: aPoint "Update the gradient directions." super extent: aPoint. self updateFillStyle! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 16:05'! fillStyleToUse "Answer the fillStyle that should be used for the receiver." ^self fillStyle! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/19/2006 14:06'! gradient "Answer the gradient." self subclassResponsibility! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/3/2009 13:39'! initialize "Initialize the receiver." super initialize. self fillStyle: self defaultFillStyle; borderStyle: (BorderStyle inset baseColor: self paneColor; width: 1); sliderColor: Color black; clipSubmorphs: true! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/19/2006 15:53'! initializeSlider "Make the slider raised." slider :=( BracketMorph newBounds: self totalSliderArea) horizontal: self bounds isWide; color: self thumbColor; borderStyle: (BorderStyle raised baseColor: Color white; width: 1). sliderShadow := (BracketMorph newBounds: self totalSliderArea) horizontal: self bounds isWide; color: self pagingArea color; borderStyle: (BorderStyle inset baseColor: (Color white alpha: 0.6); width: 1). slider on: #mouseMove send: #scrollAbsolute: to: self. slider on: #mouseDown send: #mouseDownInSlider: to: self. slider on: #mouseUp send: #mouseUpInSlider: to: self. "(the shadow must have the pagingArea as its owner to highlight properly)" self pagingArea addMorph: sliderShadow. sliderShadow hide. self addMorph: slider. self computeSlider. ! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/3/2009 13:41'! layoutBounds: aRectangle "Set the bounds for laying out children of the receiver. Note: written so that #layoutBounds can be changed without touching this method" super layoutBounds: aRectangle. self updateFillStyle. slider horizontal: self bounds isWide. sliderShadow horizontal: self bounds isWide! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/21/2006 11:34'! roomToMove "Allow to run off the edges a bit." ^self bounds isWide ifTrue: [self totalSliderArea insetBy: ((self sliderThickness // 2@0) negated corner: (self sliderThickness // 2 + 1)@0)] ifFalse: [self totalSliderArea insetBy: (0@(self sliderThickness // 2) negated corner: 0@(self sliderThickness // 2 - (self sliderThickness \\ 2) + 1))]! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/8/2009 13:29'! sliderColor: newColor "Set the slider colour." super sliderColor: (self enabled ifTrue: [Color black] ifFalse: [self sliderShadowColor]). slider ifNotNil: [slider borderStyle baseColor: Color white]! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/19/2006 15:43'! sliderShadowColor "Answer the color for the slider shadow." ^Color black alpha: 0.6! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/26/2006 12:02'! sliderThickness "Answer the thickness of the slider." ^((self bounds isWide ifTrue: [self height] ifFalse: [self width]) // 2 max: 8) // 2 * 2 + 1! ! !BracketSliderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/3/2009 13:41'! updateFillStyle "Update the fill style directions." |b fs| fs := self fillStyle. fs isOrientedFill ifTrue: [ b := self innerBounds. fs origin: b topLeft. fs direction: (b isWide ifTrue: [b width@0] ifFalse: [0@b height])]! ! Halt subclass: #BreakPoint instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Tools'! !BreakPoint commentStamp: 'md 11/18/2003 09:32' prior: 0! This exception is raised on executing a breakpoint. "BreakPoint signal" is called from "Object>>break".! Object subclass: #BreakpointManager instanceVariableNames: '' classVariableNames: 'Installed' poolDictionaries: '' category: 'System-Tools'! !BreakpointManager commentStamp: 'md 10/9/2008 20:17' prior: 0! This class manages methods that include breakpoints. It has several class methods to install and uninstall breakpoints. Evaluating "BreakpointManager clear" will remove all installed breakpoints in the system. Known issues: - currently, only break-on-entry type of breakpoints are supported - uninstalling the breakpoint doesn't auto-update other browsers - uninstalling a breakpoint while debugging should restart-simulate the current method Ernest Micklei, 2002 Send comments to emicklei@philemonworks.com! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BreakpointManager class instanceVariableNames: ''! !BreakpointManager class methodsFor: 'examples' stamp: 'emm 5/30/2002 14:12'! testBreakpoint "In the menu of the methodList, click on -toggle break on entry- and evaluate the following:" "BreakpointManager testBreakpoint" Transcript cr; show: 'Breakpoint test'! ! !BreakpointManager class methodsFor: 'install-uninstall' stamp: 'nice 4/10/2008 22:00'! installInClass: aClass selector: aSymbol "Install a new method containing a breakpoint. The receiver will remember this for unstalling it later" | breakMethod | breakMethod := self compilePrototype: aSymbol in: aClass. breakMethod isNil ifTrue: [^ nil]. self installed at: breakMethod put: aClass >> aSymbol. "old method" aClass basicAddSelector: aSymbol withMethod: breakMethod.! ! !BreakpointManager class methodsFor: 'install-uninstall' stamp: 'md 2/15/2006 21:25'! unInstall: breakMethod | class selector oldMethod | oldMethod := self installed at: breakMethod ifAbsent:[^self]. class := breakMethod methodClass. selector := breakMethod selector. (class>>selector) == breakMethod ifTrue:[ class methodDictionary at: selector put: oldMethod]. self installed removeKey: breakMethod! ! !BreakpointManager class methodsFor: 'intialization-release' stamp: 'marcus.denker 10/9/2008 20:35'! clear "BreakpointManager clear" self installed associations do: [:entry | self unInstall: entry key]. ! ! !BreakpointManager class methodsFor: 'testing' stamp: 'emm 5/30/2002 09:22'! methodHasBreakpoint: aMethod ^self installed includesKey: aMethod! ! !BreakpointManager class methodsFor: 'private' stamp: 'emm 5/30/2002 09:36'! breakpointMethodSourceFor: aSymbol in: aClass "Compose new source containing a break statement (currently it will be the first, later we want to insert it in any place)" | oldSource methodNode breakOnlyMethodNode sendBreakMessageNode | oldSource := aClass sourceCodeAt: aSymbol. methodNode := aClass compilerClass new compile: oldSource in: aClass notifying: nil ifFail: [self error: '[breakpoint] unable to install breakpoint']. breakOnlyMethodNode := aClass compilerClass new compile: 'temporaryMethodSelectorForBreakpoint self break. ^self' in: aClass notifying: nil ifFail: [self error: '[breakpoint] unable to install breakpoint']. sendBreakMessageNode := breakOnlyMethodNode block statements first. methodNode block statements addFirst: sendBreakMessageNode. ^methodNode printString ! ! !BreakpointManager class methodsFor: 'private' stamp: 'md 10/9/2008 20:14'! compilePrototype: aSymbol in: aClass "Compile and return a new method containing a break statement" | source node method | source := self breakpointMethodSourceFor: aSymbol in: aClass. node := aClass compilerClass new compile: source in: aClass notifying: nil ifFail: [self error: '[breakpoint] unable to install breakpoint']. node isNil ifTrue: [^nil]. method := node generate: (aClass>>aSymbol) trailer. ^method! ! !BreakpointManager class methodsFor: 'private' stamp: 'emm 4/24/2002 23:24'! installed Installed isNil ifTrue:[Installed := IdentityDictionary new]. ^Installed! ! CodeHolder subclass: #Browser instanceVariableNames: 'systemOrganizer classOrganizer metaClassOrganizer systemCategoryListIndex classListIndex messageCategoryListIndex messageListIndex editSelection metaClassIndicated' classVariableNames: 'RecentClasses' poolDictionaries: '' category: 'Tools-Browser'! !Browser commentStamp: '' prior: 0! I represent a query path into the class descriptions, the software of the system.! !Browser methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 9/1/2008 16:37'! buildMorphicSwitches | instanceSwitch commentSwitch classSwitch row | instanceSwitch := PluggableButtonMorph on: self getState: #instanceMessagesIndicated action: #indicateInstanceMessages. instanceSwitch label: 'instance'; askBeforeChanging: true; borderWidth: 1; borderColor: Color gray. commentSwitch := PluggableButtonMorph on: self getState: #classCommentIndicated action: #plusButtonHit. commentSwitch label: '?' asText allBold; askBeforeChanging: true; setBalloonText: 'class comment'; borderWidth: 1; borderColor: Color gray. classSwitch := PluggableButtonMorph on: self getState: #classMessagesIndicated action: #indicateClassMessages. classSwitch label: 'class'; askBeforeChanging: true; borderWidth: 1; borderColor: Color gray. row := AlignmentMorph newRow hResizing: #spaceFill; vResizing: #spaceFill; cellInset: 0; borderWidth: 0; layoutInset: 0; addMorphBack: instanceSwitch; addMorphBack: commentSwitch; addMorphBack: classSwitch. row color: Color white. {instanceSwitch. commentSwitch. classSwitch} do: [:m | m color: Color transparent; hResizing: #spaceFill; vResizing: #spaceFill.]. ^ row ! ! !Browser methodsFor: '*services-base' stamp: 'rr 6/28/2005 15:50'! browseReference: ref self okToChange ifTrue: [ self selectCategoryForClass: ref actualClass theNonMetaClass. self selectClass: ref actualClass theNonMetaClass . ref actualClass isMeta ifTrue: [self indicateClassMessages]. self changed: #classSelectionChanged. self selectMessageCategoryNamed: ref category. self selectedMessageName: ref methodSymbol. ]! ! !Browser methodsFor: '*services-base' stamp: 'rr 8/5/2005 10:03'! methodReference | cls sel | cls := self selectedClassOrMetaClass. sel := self selectedMessageName. cls isNil | sel isNil ifTrue: [^nil]. ^ MethodReference class: cls selector: sel! ! !Browser methodsFor: '*services-base' stamp: 'rr 3/10/2006 16:01'! optionalButtonRow ^ServiceGui browserButtonRow: self inlinedIn: super optionalButtonRow! ! !Browser methodsFor: '*services-base' stamp: 'rr 8/3/2005 17:16'! selectReference: ref self browseReference: ref! ! !Browser methodsFor: 'accessing' stamp: 'al 12/6/2005 22:36'! contents "Depending on the current selection, different information is retrieved. Answer a string description of that information. This information is the method of the currently selected class and message." | comment theClass latestCompiledMethod | latestCompiledMethod := currentCompiledMethod. currentCompiledMethod := nil. editSelection == #newTrait ifTrue: [^Trait newTemplateIn: self selectedSystemCategoryName]. editSelection == #none ifTrue: [^ '']. editSelection == #editSystemCategories ifTrue: [^ systemOrganizer printString]. editSelection == #newClass ifTrue: [^ (theClass := self selectedClass) ifNil: [Class template: self selectedSystemCategoryName] ifNotNil: [Class templateForSubclassOf: theClass category: self selectedSystemCategoryName]]. editSelection == #editClass ifTrue: [^self classDefinitionText]. editSelection == #editComment ifTrue: [(theClass := self selectedClass) ifNil: [^ '']. comment := theClass comment. currentCompiledMethod := theClass organization commentRemoteStr. ^ comment size = 0 ifTrue: ['This class has not yet been commented.'] ifFalse: [comment]]. editSelection == #hierarchy ifTrue: [ self selectedClassOrMetaClass isTrait ifTrue: [^''] ifFalse: [^self selectedClassOrMetaClass printHierarchy]]. editSelection == #editMessageCategories ifTrue: [^ self classOrMetaClassOrganizer printString]. editSelection == #newMessage ifTrue: [^ (theClass := self selectedClassOrMetaClass) ifNil: [''] ifNotNil: [theClass sourceCodeTemplate]]. editSelection == #editMessage ifTrue: [self showingByteCodes ifTrue: [^ self selectedBytecodes]. currentCompiledMethod := latestCompiledMethod. ^ self selectedMessage]. self error: 'Browser internal error: unknown edit selection.'! ! !Browser methodsFor: 'accessing' stamp: 'tak 9/25/2008 14:58'! contentsSelection "Return the interval of text in the code pane to select when I set the pane's contents" messageCategoryListIndex > 0 & (messageListIndex = 0) ifTrue: [^ 1 to: 500] "entire empty method template" ifFalse: [^ 1 to: 0] "null selection"! ! !Browser methodsFor: 'accessing' stamp: 'al 4/24/2004 12:01'! contents: input notifying: aController "The retrieved information has changed and its source must now be updated. The information can be a variety of things, depending on the list selections (such as templates for class or message definition, methods) or the user menu commands (such as definition, comment, hierarchy). Answer the result of updating the source." | aString aText theClass | self changed: #annotation. aString := input asString. aText := input asText. editSelection == #newTrait ifTrue: [^self defineTrait: input asString notifying: aController]. editSelection == #editSystemCategories ifTrue: [^ self changeSystemCategories: aString]. editSelection == #editClass | (editSelection == #newClass) ifTrue: [^ self defineClass: aString notifying: aController]. editSelection == #editComment ifTrue: [theClass := self selectedClass. theClass ifNil: [self inform: 'You must select a class before giving it a comment.'. ^ false]. theClass comment: aText stamp: Utilities changeStamp. self changed: #classCommentText. ^ true]. editSelection == #hierarchy ifTrue: [^ true]. editSelection == #editMessageCategories ifTrue: [^ self changeMessageCategories: aString]. editSelection == #editMessage | (editSelection == #newMessage) ifTrue: [^ self okayToAccept ifFalse: [false] ifTrue: [self compileMessage: aText notifying: aController]]. editSelection == #none ifTrue: [self inform: 'This text cannot be accepted in this part of the browser.'. ^ false]. self error: 'unacceptable accept'! ! !Browser methodsFor: 'accessing' stamp: 'alain.plantec 6/11/2008 13:46'! couldBrowseAnyClass "Answer whether the receiver is equipped to browse any class. This is in support of the system-brower feature that allows the browser to be redirected at the selected class name. This implementation is clearly ugly, but the feature it enables is handsome enough. 3/1/96 sw" self dependents detect: [:d | (d isKindOf: PluggableListMorph) and: [d getListSelector == #systemCategoryList]] ifNone: [^ false]. ^ true! ! !Browser methodsFor: 'accessing' stamp: 'sma 5/28/2000 11:28'! doItReceiver "This class's classPool has been jimmied to be the classPool of the class being browsed. A doIt in the code pane will let the user see the value of the class variables." ^ self selectedClass ifNil: [FakeClassPool new]! ! !Browser methodsFor: 'accessing'! editSelection ^editSelection! ! !Browser methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:26'! editSelection: aSelection "Set the editSelection as requested." editSelection := aSelection. self changed: #editSelection.! ! !Browser methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:26'! noteSelectionIndex: anInteger for: aSymbol aSymbol == #systemCategoryList ifTrue: [systemCategoryListIndex := anInteger]. aSymbol == #classList ifTrue: [classListIndex := anInteger]. aSymbol == #messageCategoryList ifTrue: [messageCategoryListIndex := anInteger]. aSymbol == #messageList ifTrue: [messageListIndex := anInteger].! ! !Browser methodsFor: 'accessing' stamp: 'rbb 3/1/2005 10:26'! request: prompt initialAnswer: initialAnswer ^ UIManager default request: prompt initialAnswer: initialAnswer ! ! !Browser methodsFor: 'accessing' stamp: 'sw 9/26/2002 17:56'! suggestCategoryToSpawnedBrowser: aBrowser "aBrowser is a message-category browser being spawned from the receiver. Tell it what it needs to know to get its category info properly set up." (self isMemberOf: Browser) "yecch, but I didn't invent the browser hierarchy" ifTrue: [aBrowser messageCategoryListIndex: (self messageCategoryList indexOf: self categoryOfCurrentMethod ifAbsent: [2])] ifFalse: [aBrowser setOriginalCategoryIndexForCurrentMethod]! ! !Browser methodsFor: 'annotation' stamp: 'sd 11/20/2005 21:26'! annotation "Provide a line of content for an annotation pane, representing information about the method associated with the selected class and selector in the receiver." | aSelector aClass | (aClass := self selectedClassOrMetaClass) == nil ifTrue: [^ '------']. self editSelection == #editComment ifTrue: [^ self annotationForSelector: #Comment ofClass: aClass]. self editSelection == #editClass ifTrue: [^ self annotationForSelector: #Definition ofClass: aClass]. (aSelector := self selectedMessageName) ifNil: [^ '------']. ^ self annotationForSelector: aSelector ofClass: aClass! ! !Browser methodsFor: 'breakpoints' stamp: 'marcus.denker 10/9/2008 20:32'! toggleBreakOnEntry "Install or uninstall a halt-on-entry breakpoint" super toggleBreakOnEntry. self changed: #messageList ! ! !Browser methodsFor: 'class comment pane' stamp: 'nk 2/15/2004 13:20'! buildMorphicCommentPane "Construct the pane that shows the class comment. Respect the Preference for standardCodeFont." | commentPane | commentPane := BrowserCommentTextMorph on: self text: #classCommentText accept: #classComment:notifying: readSelection: nil menu: #codePaneMenu:shifted:. commentPane font: Preferences standardCodeFont. ^ commentPane! ! !Browser methodsFor: 'class comment pane' stamp: 'dew 3/5/2005 23:10'! classComment: aText notifying: aPluggableTextMorph "The user has just entered aText. It may be all red (a side-effect of replacing the default comment), so remove the color if it is." | theClass cleanedText redRange | theClass := self selectedClassOrMetaClass. theClass ifNotNil: [cleanedText := aText asText. redRange := cleanedText rangeOf: TextColor red startingAt: 1. redRange size = cleanedText size ifTrue: [cleanedText removeAttribute: TextColor red from: 1 to: redRange last ]. theClass comment: aText stamp: Utilities changeStamp]. self changed: #classCommentText. ^ true! ! !Browser methodsFor: 'class comment pane' stamp: 'md 2/24/2006 15:23'! noCommentNagString ^ Text string: 'THIS CLASS HAS NO COMMENT!!' translated attribute: TextColor red. ! ! !Browser methodsFor: 'class functions' stamp: 'sd 11/20/2005 21:26'! addAllMethodsToCurrentChangeSet "Add all the methods in the selected class or metaclass to the current change set. You ought to know what you're doing before you invoke this!!" | aClass | (aClass := self selectedClassOrMetaClass) ifNotNil: [aClass selectors do: [:sel | ChangeSet current adoptSelector: sel forClass: aClass]. self changed: #annotation] ! ! !Browser methodsFor: 'class functions'! buildClassBrowser "Create and schedule a new class category browser for the current class selection, if one exists." self buildClassBrowserEditString: nil! ! !Browser methodsFor: 'class functions' stamp: 'sd 11/20/2005 21:26'! classCommentText "return the text to display for the comment of the currently selected class" | theClass | theClass := self selectedClassOrMetaClass. theClass ifNil: [ ^'']. ^ theClass hasComment ifTrue: [ theClass comment ] ifFalse: [ self noCommentNagString ]! ! !Browser methodsFor: 'class functions' stamp: 'eem 5/7/2008 12:04'! classDefinitionText "return the text to display for the definition of the currently selected class" | theClass | ^(theClass := self selectedClassOrMetaClass) ifNil: [''] ifNotNil: [theClass definition]! ! !Browser methodsFor: 'class functions' stamp: 'sw 12/6/2000 16:32'! classListMenu: aMenu "For backward compatibility with old browers stored in image segments" ^ self classListMenu: aMenu shifted: false! ! !Browser methodsFor: 'class functions' stamp: 'dc 7/18/2008 11:40'! classListMenu: aMenu shifted: shifted "Set up the menu to apply to the receiver's class list, honoring the #shifted boolean" ServiceGui browser: self classMenu: aMenu. ServiceGui onlyServices ifTrue: [^aMenu]. shifted ifTrue: [^ self shiftedClassListMenu: aMenu]. aMenu addList: #( - ('browse full (b)' browseMethodFull) ('browse hierarchy (h)' spawnHierarchy) ('browse protocol (p)' browseFullProtocol) - ('fileOut' fileOutClass) - ('show hierarchy' hierarchy) ('show definition' editClass) ('show comment' editComment) - ('inst var refs...' browseInstVarRefs) ('inst var defs...' browseInstVarDefs) - ('class var refs...' browseClassVarRefs) ('class vars' browseClassVariables) ('class refs (N)' browseClassRefs) - ('rename class ...' renameClass) ('copy class' copyClass) ('remove class (x)' removeClass) - ('find method...' findMethod) ('find method wildcard...' findMethodWithWildcard) - ('more...' offerShiftedClassListMenu)). ^ aMenu ! ! !Browser methodsFor: 'class functions' stamp: 'DamienCassou 9/29/2009 09:05'! copyClass | copysName | classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. copysName := self request: 'Please type new class name' initialAnswer: self selectedClass name. copysName isEmptyOrNil ifTrue: [^ self]. "Cancel returns ''" self selectedClass duplicateClassWithNewName: copysName. self classListIndex: 0. self changed: #classList! ! !Browser methodsFor: 'class functions' stamp: 'sd 11/20/2005 21:30'! createInstVarAccessors "Create getters and setters for all inst vars defined at the level of the current class selection, except do NOT clobber or override any selectors already understood by the instances of the selected class" | aClass newMessage setter | (aClass := self selectedClassOrMetaClass) ifNotNil: [aClass instVarNames do: [:aName | (aClass canUnderstand: aName asSymbol) ifFalse: [newMessage := aName, ' "Answer the value of ', aName, '" ^ ', aName. aClass compile: newMessage classified: 'accessing' notifying: nil]. (aClass canUnderstand: (setter := aName, ':') asSymbol) ifFalse: [newMessage := setter, ' anObject "Set the value of ', aName, '" ', aName, ' := anObject'. aClass compile: newMessage classified: 'accessing' notifying: nil]]]! ! !Browser methodsFor: 'class functions' stamp: 'md 3/3/2006 11:02'! defineClass: defString notifying: aController "The receiver's textual content is a request to define a new class. The source code is defString. If any errors occur in compilation, notify aController." | oldClass class newClassName defTokens keywdIx envt | oldClass := self selectedClassOrMetaClass. defTokens := defString findTokens: Character separators. ((defTokens first = 'Trait' and: [defTokens second = 'named:']) or: [defTokens second = 'classTrait']) ifTrue: [^self defineTrait: defString notifying: aController]. keywdIx := defTokens findFirst: [:x | x beginsWith: 'category']. envt := Smalltalk. keywdIx := defTokens findFirst: [:x | '*subclass*' match: x]. newClassName := (defTokens at: keywdIx+1) copyWithoutAll: '#()'. ((oldClass isNil or: [oldClass theNonMetaClass name asString ~= newClassName]) and: [envt includesKey: newClassName asSymbol]) ifTrue: ["Attempting to define new class over existing one when not looking at the original one in this browser..." (self confirm: ((newClassName , ' is an existing class in this system. Redefining it might cause serious problems. Is this really what you want to do?') asText makeBoldFrom: 1 to: newClassName size)) ifFalse: [^ false]]. "ar 8/29/1999: Use oldClass superclass for defining oldClass since oldClass superclass knows the definerClass of oldClass." oldClass ifNotNil:[oldClass := oldClass superclass]. class := oldClass subclassDefinerClass evaluate: defString notifying: aController logged: true. (class isKindOf: Behavior) ifTrue: [self changed: #systemCategoryList. self changed: #classList. self clearUserEditFlag. self setClass: class selector: nil. "self clearUserEditFlag; editClass." ^ true] ifFalse: [^ false]! ! !Browser methodsFor: 'class functions' stamp: 'nk 2/15/2004 13:23'! editClass "Retrieve the description of the class definition." classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. self messageCategoryListIndex: 0. self editSelection: #editClass. self changed: #contents. self changed: #classCommentText. ! ! !Browser methodsFor: 'class functions' stamp: 'sd 11/20/2005 21:26'! editComment "Retrieve the description of the class comment." classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. self messageCategoryListIndex: 0. metaClassIndicated := false. self editSelection: #editComment. self changed: #classSelectionChanged. self changed: #messageCategoryList. self changed: #messageList. self decorateButtons. self contentsChanged ! ! !Browser methodsFor: 'class functions' stamp: 'tk 4/2/98 13:50'! fileOutClass "Print a description of the selected class onto a file whose name is the category name followed by .st." Cursor write showWhile: [classListIndex ~= 0 ifTrue: [self selectedClass fileOut]]! ! !Browser methodsFor: 'class functions' stamp: 'alain.plantec 2/6/2009 16:29'! findMethod "Pop up a list of the current class's methods, and select the one chosen by the user" | aClass selectors reply cat messageCatIndex messageIndex choices | self classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. aClass := self selectedClassOrMetaClass. selectors := aClass selectors asSortedArray. selectors isEmpty ifTrue: [self inform: aClass name, ' has no methods.' translated. ^ self]. choices := (Array with: 'Enter Wildcard' translated), selectors. reply := UIManager default chooseFrom: choices lines: #(1). reply = 0 ifTrue: [^self]. reply = 1 ifTrue: [ reply := UIManager default request: 'Enter partial method name:' translated. (reply isNil or: [reply isEmpty]) ifTrue: [^self]. (reply includes: $*) ifFalse: [reply := '*', reply, '*']. selectors := selectors select: [:each | reply match: each]. selectors isEmpty ifTrue: [self inform: aClass name, ' has no matching methods.' translated. ^ self]. reply := selectors size = 1 ifTrue: [selectors first] ifFalse: [ UIManager default chooseFrom: selectors values: selectors]. reply isNil ifTrue: [^self]] ifFalse: [reply := choices at: reply]. cat := aClass whichCategoryIncludesSelector: reply. messageCatIndex := self messageCategoryList indexOf: cat. self messageCategoryListIndex: messageCatIndex. messageIndex := (self messageList indexOf: reply). self messageListIndex: messageIndex! ! !Browser methodsFor: 'class functions' stamp: 'alain.plantec 2/6/2009 16:30'! findMethodWithWildcard "Pop up a list of the current class's methods, and select the one chosen by the user" | aClass selectors reply cat messageCatIndex messageIndex | self classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. aClass := self selectedClassOrMetaClass. selectors := aClass selectors asSortedArray. selectors isEmpty ifTrue: [self inform: aClass name, ' has no methods.' translated. ^ self]. reply := UIManager default request: 'Enter partial method name:' translated. (reply isNil or: [reply isEmpty]) ifTrue: [^self]. (reply includes: $*) ifFalse: [reply := '*', reply, '*']. selectors := selectors select: [:each | reply match: each]. selectors isEmpty ifTrue: [self inform: aClass name, ' has no matching methods.'. ^ self]. reply := selectors size = 1 ifTrue: [selectors first] ifFalse: [UIManager default chooseFrom: selectors values: selectors]. reply == nil ifTrue: [^ self]. cat := aClass whichCategoryIncludesSelector: reply. messageCatIndex := self messageCategoryList indexOf: cat. self messageCategoryListIndex: messageCatIndex. messageIndex := (self messageList indexOf: reply). self messageListIndex: messageIndex! ! !Browser methodsFor: 'class functions' stamp: 'nk 2/14/2004 15:09'! hierarchy "Display the inheritance hierarchy of the receiver's selected class." classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. self messageCategoryListIndex: 0. self editSelection: #hierarchy. self changed: #editComment. self contentsChanged. ^ self! ! !Browser methodsFor: 'class functions' stamp: 'nk 2/14/2004 15:07'! makeNewSubclass self selectedClassOrMetaClass ifNil: [^ self]. self okToChange ifFalse: [^ self]. self editSelection: #newClass. self contentsChanged! ! !Browser methodsFor: 'class functions' stamp: 'nk 2/14/2004 15:09'! plusButtonHit "Cycle among definition, comment, and hierachy" editSelection == #editComment ifTrue: [self hierarchy. ^ self]. editSelection == #hierarchy ifTrue: [self editSelection: #editClass. classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. self changed: #editComment. self contentsChanged. ^ self]. self editComment! ! !Browser methodsFor: 'class functions' stamp: 'sw 3/5/2001 18:04'! removeClass "If the user confirms the wish to delete the class, do so" super removeClass ifTrue: [self classListIndex: 0]! ! !Browser methodsFor: 'class functions' stamp: 'DamienCassou 9/29/2009 09:05'! renameClass | oldName newName obs | classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. oldName := self selectedClass name. newName := self request: 'Please type new class name' initialAnswer: oldName. newName isEmptyOrNil ifTrue: [^ self]. "Cancel returns ''" newName := newName asSymbol. newName = oldName ifTrue: [^ self]. (Smalltalk includesKey: newName) ifTrue: [^ self error: newName , ' already exists']. self selectedClass rename: newName. self changed: #classList. self classListIndex: ((systemOrganizer listAtCategoryNamed: self selectedSystemCategoryName) indexOf: newName). obs := self systemNavigation allCallsOn: (Smalltalk associationAt: newName). obs isEmpty ifFalse: [self systemNavigation browseMessageList: obs name: 'Obsolete References to ' , oldName autoSelect: oldName]! ! !Browser methodsFor: 'class functions' stamp: 'md 7/29/2005 15:59'! shiftedClassListMenu: aMenu "Set up the menu to apply to the receiver's class list when the shift key is down" ^ aMenu addList: #( - ('unsent methods' browseUnusedMethods 'browse all methods defined by this class that have no senders') ('unreferenced inst vars' showUnreferencedInstVars 'show a list of all instance variables that are not referenced in methods') ('unreferenced class vars' showUnreferencedClassVars 'show a list of all class variables that are not referenced in methods') ('subclass template' makeNewSubclass 'put a template into the code pane for defining of a subclass of this class') - ('sample instance' makeSampleInstance 'give me a sample instance of this class, if possible') ('inspect instances' inspectInstances 'open an inspector on all the extant instances of this class') ('inspect subinstances' inspectSubInstances 'open an inspector on all the extant instances of this class and of all of its subclasses') - ('add all meths to current chgs' addAllMethodsToCurrentChangeSet 'place all the methods defined by this class into the current change set') ('create inst var accessors' createInstVarAccessors 'compile instance-variable access methods for any instance variables that do not yet have them') - ('more...' offerUnshiftedClassListMenu 'return to the standard class-list menu'))! ! !Browser methodsFor: 'class list'! classList "Answer an array of the class names of the selected category. Answer an empty array if no selection exists." systemCategoryListIndex = 0 ifTrue: [^Array new] ifFalse: [^systemOrganizer listAtCategoryNumber: systemCategoryListIndex]! ! !Browser methodsFor: 'class list'! classListIndex "Answer the index of the current class selection." ^classListIndex! ! !Browser methodsFor: 'class list' stamp: 'sd 11/20/2005 21:26'! classListIndex: anInteger "Set anInteger to be the index of the current class selection." | className | classListIndex := anInteger. self setClassOrganizer. messageCategoryListIndex := 0. messageListIndex := 0. self classCommentIndicated ifTrue: [] ifFalse: [self editSelection: (anInteger = 0 ifTrue: [metaClassIndicated | (systemCategoryListIndex == 0) ifTrue: [#none] ifFalse: [#newClass]] ifFalse: [#editClass])]. contents := nil. self selectedClass isNil ifFalse: [className := self selectedClass name. (RecentClasses includes: className) ifTrue: [RecentClasses remove: className]. RecentClasses addFirst: className. RecentClasses size > 16 ifTrue: [RecentClasses removeLast]]. self changed: #classSelectionChanged. self changed: #classCommentText. self changed: #classListIndex. "update my selection" self changed: #messageCategoryList. self changed: #messageList. self changed: #relabel. self contentsChanged! ! !Browser methodsFor: 'class list' stamp: 'sd 11/20/2005 21:26'! classListSingleton | name | name := self selectedClassName. ^ name ifNil: [Array new] ifNotNil: [Array with: name]! ! !Browser methodsFor: 'class list' stamp: 'alain.plantec 2/6/2009 16:34'! recent "Let the user select from a list of recently visited classes. 11/96 stp. 12/96 di: use class name, not classes themselves. : dont fall into debugger in empty case" | className class recentList | recentList := RecentClasses select: [:n | Smalltalk includesKey: n]. recentList size == 0 ifTrue: [^ Beeper beep]. className := UIManager default chooseFrom: recentList values: recentList. className isNil ifTrue: [^ self]. class := Smalltalk at: className. self selectCategoryForClass: class. self classListIndex: (self classList indexOf: class name)! ! !Browser methodsFor: 'class list' stamp: 'sr 10/29/1999 20:28'! selectClass: classNotMeta self classListIndex: (self classList indexOf: classNotMeta name)! ! !Browser methodsFor: 'class list' stamp: 'sd 11/20/2005 21:26'! selectedClass "Answer the class that is currently selected. Answer nil if no selection exists." | name envt | (name := self selectedClassName) ifNil: [^ nil]. (envt := self selectedEnvironment) ifNil: [^ nil]. ^ envt at: name! ! !Browser methodsFor: 'class list' stamp: 'sd 11/20/2005 21:26'! selectedClassName | aClassList | "Answer the name of the current class. Answer nil if no selection exists." (classListIndex = 0 or: [classListIndex > (aClassList := self classList) size]) ifTrue: [^ nil]. ^ aClassList at: classListIndex! ! !Browser methodsFor: 'class list'! toggleClassListIndex: anInteger "If anInteger is the current class index, deselect it. Else make it the current class selection." self classListIndex: (classListIndex = anInteger ifTrue: [0] ifFalse: [anInteger])! ! !Browser methodsFor: 'code pane' stamp: 'rr 7/10/2006 11:48'! codePaneMenu: aMenu shifted: shifted ServiceGui browser: self codePaneMenu: aMenu. ServiceGui onlyServices ifTrue: [^ aMenu]. super codePaneMenu: aMenu shifted: shifted. ^ aMenu! ! !Browser methodsFor: 'code pane' stamp: 'sd 11/20/2005 21:26'! compileMessage: aText notifying: aController "Compile the code that was accepted by the user, placing the compiled method into an appropriate message category. Return true if the compilation succeeded, else false." | fallBackCategoryIndex fallBackMethodIndex originalSelectorName result | self selectedMessageCategoryName ifNil: [ self selectOriginalCategoryForCurrentMethod ifFalse:["Select the '--all--' category" self messageCategoryListIndex: 1]]. self selectedMessageCategoryName asSymbol = ClassOrganizer allCategory ifTrue: [ "User tried to save a method while the ALL category was selected" fallBackCategoryIndex := messageCategoryListIndex. fallBackMethodIndex := messageListIndex. editSelection == #newMessage ifTrue: [ "Select the 'as yet unclassified' category" messageCategoryListIndex := 0. (result := self defineMessageFrom: aText notifying: aController) ifNil: ["Compilation failure: reselect the original category & method" messageCategoryListIndex := fallBackCategoryIndex. messageListIndex := fallBackMethodIndex] ifNotNil: [self setSelector: result]] ifFalse: [originalSelectorName := self selectedMessageName. self setOriginalCategoryIndexForCurrentMethod. messageListIndex := fallBackMethodIndex := self messageList indexOf: originalSelectorName. (result := self defineMessageFrom: aText notifying: aController) ifNotNil: [self setSelector: result] ifNil: [ "Compilation failure: reselect the original category & method" messageCategoryListIndex := fallBackCategoryIndex. messageListIndex := fallBackMethodIndex. ^ result notNil]]. self changed: #messageCategoryList. ^ result notNil] ifFalse: [ "User tried to save a method while the ALL category was NOT selected" ^ (self defineMessageFrom: aText notifying: aController) notNil]! ! !Browser methodsFor: 'code pane' stamp: 'sw 5/18/2001 20:55'! showBytecodes "Show or hide the bytecodes of the selected method -- an older protocol now mostly not relevant." self toggleShowingByteCodes! ! !Browser methodsFor: 'construction' stamp: 'sd 11/20/2005 21:26'! addLowerPanesTo: window at: nominalFractions with: editString | commentPane | super addLowerPanesTo: window at: nominalFractions with: editString. commentPane := self buildMorphicCommentPane. window addMorph: commentPane fullFrame: (LayoutFrame fractions: (0@0.75 corner: 1@1)). self changed: #editSelection.! ! !Browser methodsFor: 'copying' stamp: 'sd 11/20/2005 21:26'! veryDeepInner: deepCopier "Copy all of my instance variables. Some need to be not copied at all, but shared. See DeepCopier class comment." super veryDeepInner: deepCopier. "systemOrganizer := systemOrganizer. clone has the old value. we share it" "classOrganizer := classOrganizer clone has the old value. we share it" "metaClassOrganizer := metaClassOrganizer clone has the old value. we share it" systemCategoryListIndex := systemCategoryListIndex veryDeepCopyWith: deepCopier. classListIndex := classListIndex veryDeepCopyWith: deepCopier. messageCategoryListIndex := messageCategoryListIndex veryDeepCopyWith: deepCopier. messageListIndex := messageListIndex veryDeepCopyWith: deepCopier. editSelection := editSelection veryDeepCopyWith: deepCopier. metaClassIndicated := metaClassIndicated veryDeepCopyWith: deepCopier. ! ! !Browser methodsFor: 'drag and drop' stamp: 'nk 6/12/2004 17:43'! acceptDroppingMorph: transferMorph event: evt inMorph: dstListMorph "Here we are fetching informations from the dropped transferMorph and performing the correct action for this drop." | srcType success srcBrowser | success := false. srcType := transferMorph dragTransferType. srcBrowser := transferMorph source model. srcType == #messageList ifTrue: [ | srcClass srcSelector srcCategory | srcClass := transferMorph passenger key. srcSelector := transferMorph passenger value. srcCategory := srcBrowser selectedMessageCategoryName. srcCategory ifNil: [srcCategory := srcClass organization categoryOfElement: srcSelector]. success := self acceptMethod: srcSelector messageCategory: srcCategory class: srcClass atListMorph: dstListMorph internal: self == srcBrowser copy: transferMorph shouldCopy]. srcType == #classList ifTrue: [success := self changeCategoryForClass: transferMorph passenger srcSystemCategory: srcBrowser selectedSystemCategoryName atListMorph: dstListMorph internal: self == srcBrowser copy: transferMorph shouldCopy]. ^ success! ! !Browser methodsFor: 'drag and drop' stamp: 'sd 11/20/2005 21:26'! acceptMethod: methodSel dstMessageCategory: dstMessageCategorySel srcMessageCategory: srcMessageCategorySel dstClass: dstClass dstClassOrMeta: dstClassOrMeta srcClassOrMeta: srcClassOrMeta internal: internal copySemantic: copyFlag | success hierarchyChange higher checkForOverwrite | (success := dstClassOrMeta ~~ nil) ifFalse: [^false]. checkForOverwrite := dstClassOrMeta selectors includes: methodSel. hierarchyChange := (higher := srcClassOrMeta inheritsFrom: dstClassOrMeta) | (dstClassOrMeta inheritsFrom: srcClassOrMeta). success := (checkForOverwrite not or: [self overwriteDialogHierarchyChange: hierarchyChange higher: higher sourceClassName: srcClassOrMeta name destinationClassName: dstClassOrMeta name methodSelector: methodSel]) and: [self message: methodSel compileInClass: dstClassOrMeta fromClass: srcClassOrMeta dstMessageCategory: dstMessageCategorySel srcMessageCategory: srcMessageCategorySel internal: internal copySemantic: copyFlag]. ^ success! ! !Browser methodsFor: 'drag and drop' stamp: 'al 4/24/2004 11:50'! acceptMethod: methodSel messageCategory: srcMessageCategorySel class: srcClassOrMeta atListMorph: dstListMorph internal: internal copy: copyFlag | success dstClassOrMeta dstClass dstMessageCategorySel | dstClass := self dstClassDstListMorph: dstListMorph. dstClassOrMeta := dstClass ifNotNil: [self metaClassIndicated ifTrue: [dstClass classSide] ifFalse: [dstClass]]. dstMessageCategorySel := self dstMessageCategoryDstListMorph: dstListMorph. success := (dstClassOrMeta notNil and: [dstClassOrMeta == srcClassOrMeta]) ifTrue: ["one class" self changeMessageCategoryForMethod: methodSel dstMessageCategory: dstMessageCategorySel srcMessageCategory: srcMessageCategorySel insideClassOrMeta: dstClassOrMeta internal: internal copySemantic: copyFlag] ifFalse: ["different classes" self acceptMethod: methodSel dstMessageCategory: dstMessageCategorySel srcMessageCategory: srcMessageCategorySel dstClass: dstClass dstClassOrMeta: dstClassOrMeta srcClassOrMeta: srcClassOrMeta internal: internal copySemantic: copyFlag]. ^ success! ! !Browser methodsFor: 'drag and drop' stamp: 'sd 11/20/2005 21:26'! changeCategoryForClass: class srcSystemCategory: srcSystemCategorySel atListMorph: dstListMorph internal: internal copy: copyFlag "only move semantic" | newClassCategory success | self flag: #stringSymbolProblem. success := copyFlag not ifFalse: [^ false]. newClassCategory := self dstCategoryDstListMorph: dstListMorph. (success := newClassCategory notNil & (newClassCategory ~= class category)) ifTrue: [class category: newClassCategory. self changed: #classList. internal ifFalse: [self selectClass: class]]. ^ success! ! !Browser methodsFor: 'drag and drop' stamp: 'nk 4/22/2004 18:00'! changeMessageCategoryForMethod: methodSel dstMessageCategory: dstMessageCategorySel srcMessageCategory: srcMessageCategorySel insideClassOrMeta: classOrMeta internal: internal copySemantic: copyFlag "Recategorize the method named by methodSel. If the dstMessageCategorySel is the allCategory, then recategorize it from its parents." | success messageCategorySel | copyFlag ifTrue: [^ false]. "only move semantic" messageCategorySel := dstMessageCategorySel ifNil: [srcMessageCategorySel]. (success := messageCategorySel notNil and: [messageCategorySel ~= srcMessageCategorySel]) ifTrue: [success := messageCategorySel == ClassOrganizer allCategory ifTrue: [self recategorizeMethodSelector: methodSel] ifFalse: [(classOrMeta organization categories includes: messageCategorySel) and: [classOrMeta organization classify: methodSel under: messageCategorySel suppressIfDefault: false. true]]]. success ifTrue: [self changed: #messageList. internal ifFalse: [self setSelector: methodSel]]. ^ success! ! !Browser methodsFor: 'drag and drop' stamp: 'sd 11/20/2005 21:26'! dragPassengerFor: item inMorph: dragSource | transferType smn | (dragSource isKindOf: PluggableListMorph) ifFalse: [^nil]. transferType := self dragTransferTypeForMorph: dragSource. transferType == #classList ifTrue: [^self selectedClass]. transferType == #messageList ifFalse: [ ^nil ]. smn := self selectedMessageName ifNil: [ ^nil ]. (MessageSet isPseudoSelector: smn) ifTrue: [ ^nil ]. ^ self selectedClassOrMetaClass -> smn. ! ! !Browser methodsFor: 'drag and drop' stamp: 'panda 4/28/2000 16:18'! dragTransferTypeForMorph: dragSource ^(dragSource isKindOf: PluggableListMorph) ifTrue: [dragSource getListSelector]! ! !Browser methodsFor: 'drag and drop' stamp: 'ls 6/22/2001 23:21'! dstCategoryDstListMorph: dstListMorph ^(dstListMorph getListSelector == #systemCategoryList) ifTrue: [dstListMorph potentialDropItem ] ifFalse: [self selectedSystemCategoryName]! ! !Browser methodsFor: 'drag and drop' stamp: 'sd 11/20/2005 21:26'! dstClassDstListMorph: dstListMorph | dropItem | ^(dstListMorph getListSelector == #classList) ifTrue: [(dropItem := dstListMorph potentialDropItem) ifNotNil: [Smalltalk at: dropItem withBlanksCondensed asSymbol]] ifFalse: [dstListMorph model selectedClass]! ! !Browser methodsFor: 'drag and drop' stamp: 'sd 11/20/2005 21:26'! dstMessageCategoryDstListMorph: dstListMorph | dropItem | ^dstListMorph getListSelector == #messageCategoryList ifTrue: [dropItem := dstListMorph potentialDropItem. dropItem ifNotNil: [dropItem asSymbol]] ifFalse: [self selectedMessageCategoryName ifNil: [ Categorizer default ]]! ! !Browser methodsFor: 'drag and drop' stamp: 'sd 11/20/2005 21:26'! message: messageSel compileInClass: dstClassOrMeta fromClass: srcClassOrMeta dstMessageCategory: dstMessageCategorySel srcMessageCategory: srcMessageCategorySel internal: internal copySemantic: copyFlag | source messageCategorySel tm success oldOrNoMethod newMethod | source := srcClassOrMeta sourceCodeAt: messageSel. messageCategorySel := dstMessageCategorySel ifNil: [srcMessageCategorySel]. self selectClass: dstClassOrMeta theNonMetaClass. (self messageCategoryList includes: messageCategorySel) ifFalse: ["create message category" self classOrMetaClassOrganizer addCategory: messageCategorySel]. self selectMessageCategoryNamed: messageCategorySel. tm := self codeTextMorph. tm setText: source. tm setSelection: (0 to: 0). tm hasUnacceptedEdits: true. oldOrNoMethod := srcClassOrMeta compiledMethodAt: messageSel ifAbsent: []. tm accept. "compilation successful?" newMethod := dstClassOrMeta compiledMethodAt: messageSel ifAbsent: []. success := newMethod ~~ nil & (newMethod ~~ oldOrNoMethod). " success ifFalse: [TransferMorph allInstances do: [:e | e delete]]. " success ifTrue: [copyFlag not ifTrue: ["remove old method in move semantic if new exists" srcClassOrMeta removeSelector: messageSel].internal ifTrue: [self selectClass: srcClassOrMeta] ifFalse: [self selectClass: dstClassOrMeta]. self setSelector: messageSel]. ^ success! ! !Browser methodsFor: 'drag and drop' stamp: 'alain.plantec 2/6/2009 16:33'! overwriteDialogHierarchyChange: hierarchyChange higher: higherFlag sourceClassName: srcClassName destinationClassName: dstClassName methodSelector: methodSelector | lf | lf := Character cr asString. ^ UIManager default confirm: 'There is a conflict.' translated, ' Overwrite' translated, (hierarchyChange ifTrue: [higherFlag ifTrue: [' superclass' translated] ifFalse: [' subclass' translated]] ifFalse: ['']) , ' method' translated, lf , dstClassName , '>>' , methodSelector , lf , 'by ' translated, (hierarchyChange ifTrue: ['moving' translated] ifFalse: ['copying' translated]) , ' method' translated, lf , srcClassName name , '>>' , methodSelector , ' ?'. ! ! !Browser methodsFor: 'drag and drop' stamp: 'sd 11/20/2005 21:26'! wantsDroppedMorph: transferMorph event: anEvent inMorph: destinationLM "We are only interested in TransferMorphs as wrappers for informations. If their content is really interesting for us, will determined later in >>acceptDroppingMorph:event:." | srcType dstType | "only want drops on lists (not, for example, on pluggable texts)" (destinationLM isKindOf: PluggableListMorph) ifFalse: [^ false]. srcType := transferMorph dragTransferType. dstType := destinationLM getListSelector. (srcType == #messageList and: [dstType == #messageCategoryList or: [dstType == #classList]]) ifTrue: [^true]. (srcType == #classList and: [dstType == #systemCategoryList]) ifTrue: [^true]. " [ srcLS == #messageList ifTrue: [^ dstLS == #messageList | (dstLS == #messageCategoryList) | (dstLS == #classList)]. srcLS == #classList ifTrue: [^ dstLS == #classList | (dstLS == #systemCategoryList)]]. " ^ false! ! !Browser methodsFor: 'initialization' stamp: 'md 2/24/2006 15:24'! addAListPane: aListPane to: window at: nominalFractions plus: verticalOffset | row switchHeight divider | row := AlignmentMorph newColumn hResizing: #spaceFill; vResizing: #spaceFill; layoutInset: 1; borderWidth: 1; layoutPolicy: ProportionalLayout new. switchHeight := 25. self addMorphicSwitchesTo: row at: ( LayoutFrame fractions: (0@1 corner: 1@1) offsets: (0@(1-switchHeight) corner: 0@0) ). divider := BorderedSubpaneDividerMorph forTopEdge. divider extent: 4@4; color: Color transparent; borderColor: #raised; borderWidth: 0. row addMorph: divider fullFrame: ( LayoutFrame fractions: (0@1 corner: 1@1) offsets: (0@switchHeight negated corner: 0@(1-switchHeight)) ). row addMorph: aListPane fullFrame: ( LayoutFrame fractions: (0@0 corner: 1@1) offsets: (0@0 corner: 0@(switchHeight negated)) ). window addMorph: row fullFrame: ( LayoutFrame fractions: nominalFractions offsets: (0@verticalOffset corner: 0@0) ). row on: #mouseEnter send: #paneTransition: to: window. row on: #mouseLeave send: #paneTransition: to: window. ! ! !Browser methodsFor: 'initialization' stamp: 'RAA 1/10/2001 11:46'! addClassAndSwitchesTo: window at: nominalFractions plus: verticalOffset ^self addAListPane: self buildMorphicClassList to: window at: nominalFractions plus: verticalOffset ! ! !Browser methodsFor: 'initialization' stamp: 'rr 6/21/2005 13:24'! addMorphicSwitchesTo: window at: aLayoutFrame window addMorph: self buildMorphicSwitches fullFrame: aLayoutFrame. ! ! !Browser methodsFor: 'initialization' stamp: 'rww 8/18/2002 09:31'! browseSelectionInPlace "In place code - incomplete" " self systemCategoryListIndex: (self systemCategoryList indexOf: self selectedClass category). self classListIndex: (self classList indexOf: self selectedClass name)" self spawnHierarchy.! ! !Browser methodsFor: 'initialization'! browserWindowActivated "Called when a window whose model is the receiver is reactivated, giving the receiver an opportunity to take steps if it wishes. The default is to do nothing. 8/5/96 sw"! ! !Browser methodsFor: 'initialization' stamp: 'alain.plantec 5/15/2009 09:36'! buildMorphicClassList | myClassList | (myClassList := PluggableListMorph new) on: self list: #classList selected: #classListIndex changeSelected: #classListIndex: menu: #classListMenu:shifted: keystroke: #classListKey:from:. myClassList borderWidth: 0. myClassList enableDragNDrop: true. myClassList doubleClickSelector: #browseSelectionInPlace. "For doubleClick to work best disable autoDeselect" myClassList autoDeselect: false . ^myClassList ! ! !Browser methodsFor: 'initialization' stamp: 'alain.plantec 5/15/2009 09:36'! buildMorphicMessageCatList | myMessageCatList | (myMessageCatList := PluggableMessageCategoryListMorph new) on: self list: #messageCategoryList selected: #messageCategoryListIndex changeSelected: #messageCategoryListIndex: menu: #messageCategoryMenu: keystroke: #arrowKey:from: getRawListSelector: #rawMessageCategoryList. myMessageCatList enableDragNDrop: true. ^myMessageCatList ! ! !Browser methodsFor: 'initialization' stamp: 'alain.plantec 5/15/2009 09:36'! buildMorphicMessageList "Build a morphic message list, with #messageList as its list-getter" | aListMorph | (aListMorph := PluggableListMorph new) on: self list: #messageList selected: #messageListIndex changeSelected: #messageListIndex: menu: #messageListMenu:shifted: keystroke: #messageListKey:from:. aListMorph enableDragNDrop: true. aListMorph menuTitleSelector: #messageListSelectorTitle. ^aListMorph ! ! !Browser methodsFor: 'initialization' stamp: 'alain.plantec 5/15/2009 09:36'! buildMorphicSystemCatList | dragNDropFlag myCatList | dragNDropFlag := true. (myCatList := PluggableListMorph new) on: self list: #systemCategoryList selected: #systemCategoryListIndex changeSelected: #systemCategoryListIndex: menu: #systemCategoryMenu: keystroke: #systemCatListKey:from:. myCatList enableDragNDrop: dragNDropFlag. ^myCatList ! ! !Browser methodsFor: 'initialization' stamp: 'sw 1/13/2000 16:45'! defaultBrowserTitle ^ 'System Browser'! ! !Browser methodsFor: 'initialization' stamp: 'ar 1/31/2001 20:56'! highlightClassList: list with: morphList! ! !Browser methodsFor: 'initialization' stamp: 'ar 1/31/2001 20:56'! highlightMessageCategoryList: list with: morphList! ! !Browser methodsFor: 'initialization' stamp: 'ar 1/31/2001 20:56'! highlightSystemCategoryList: list with: morphList! ! !Browser methodsFor: 'initialization' stamp: 'AdrianLienhard 8/26/2009 21:07'! labelString ^self selectedClass ifNil: [ self defaultBrowserTitle ] ifNotNil: [ self selectedClass printString ]. ! ! !Browser methodsFor: 'initialization' stamp: 'sw 9/22/1999 17:13'! methodCategoryChanged self changed: #messageCategoryList. self changed: #messageList. self changed: #annotation. self messageListIndex: 0! ! !Browser methodsFor: 'initialization' stamp: 'marcus.denker 11/26/2008 14:24'! openAsMorphClassEditing: editString "Create a pluggable version a Browser on just a single class." | window dragNDropFlag hSepFrac switchHeight mySingletonClassList | window := (SystemWindow labelled: 'later') model: self. dragNDropFlag := true. hSepFrac := 0.3. switchHeight := 25. mySingletonClassList := PluggableListMorph on: self list: #classListSingleton selected: #indexIsOne changeSelected: #indexIsOne: menu: #classListMenu:shifted: keystroke: #classListKey:from:. mySingletonClassList enableDragNDrop: dragNDropFlag. self addLowerPanesTo: window at: (0@hSepFrac corner: 1@1) with: editString. window addMorph: mySingletonClassList fullFrame: ( LayoutFrame fractions: (0@0 corner: 0.5@0) offsets: (0@0 corner: 0@switchHeight) ). self addMorphicSwitchesTo: window at: ( LayoutFrame fractions: (0.5@0 corner: 1.0@0) offsets: (0@0 corner: 0@switchHeight) ). window addMorph: self buildMorphicMessageCatList fullFrame: ( LayoutFrame fractions: (0@0 corner: 0.5@hSepFrac) offsets: (0@switchHeight corner: 0@0) ). window addMorph: self buildMorphicMessageList fullFrame: ( LayoutFrame fractions: (0.5@0 corner: 1.0@hSepFrac) offsets: (0@switchHeight corner: 0@0) ). window setUpdatablePanesFrom: #(messageCategoryList messageList). ^ window ! ! !Browser methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:26'! openAsMorphEditing: editString "Create a pluggable version of all the morphs for a Browser in Morphic" | window hSepFrac | hSepFrac := 0.4. window := (SystemWindow labelled: 'later') model: self. "The method SystemWindow>>addMorph:fullFrame: checks scrollBarsOnRight, then adds the morph at the back if true, otherwise it is added in front. But flopout hScrollbars need the lowerpanes to be behind the upper ones in the draw order. Hence the value of scrollBarsOnRight affects the order in which the lowerpanes are added. " Preferences scrollBarsOnRight ifFalse: [self addLowerPanesTo: window at: (0@hSepFrac corner: 1@1) with: editString]. window addMorph: self buildMorphicSystemCatList frame: (0@0 corner: 0.25@hSepFrac). self addClassAndSwitchesTo: window at: (0.25@0 corner: 0.5@hSepFrac) plus: 0. window addMorph: self buildMorphicMessageCatList frame: (0.5@0 extent: 0.25@hSepFrac). window addMorph: self buildMorphicMessageList frame: (0.75@0 extent: 0.25@hSepFrac). Preferences scrollBarsOnRight ifTrue: [self addLowerPanesTo: window at: (0@hSepFrac corner: 1@1) with: editString]. window setUpdatablePanesFrom: #(systemCategoryList classList messageCategoryList messageList). ^ window ! ! !Browser methodsFor: 'initialization' stamp: 'marcus.denker 11/26/2008 14:24'! openAsMorphMessageEditing: editString "Create a pluggable version a Browser that shows just one message" | window mySingletonMessageList verticalOffset nominalFractions | window := (SystemWindow labelled: 'later') model: self. mySingletonMessageList := PluggableListMorph on: self list: #messageListSingleton selected: #indexIsOne changeSelected: #indexIsOne: menu: #messageListMenu:shifted: keystroke: #messageListKey:from:. mySingletonMessageList enableDragNDrop: true. verticalOffset := 25. nominalFractions := 0@0 corner: 1@0. window addMorph: mySingletonMessageList fullFrame: ( LayoutFrame fractions: nominalFractions offsets: (0@0 corner: 0@verticalOffset) ). verticalOffset := self addOptionalAnnotationsTo: window at: nominalFractions plus: verticalOffset. verticalOffset := self addOptionalButtonsTo: window at: nominalFractions plus: verticalOffset. window addMorph: (self buildMorphicCodePaneWith: editString) fullFrame: ( LayoutFrame fractions: (0@0 corner: 1@1) offsets: (0@verticalOffset corner: 0@0) ). ^ window! ! !Browser methodsFor: 'initialization' stamp: 'marcus.denker 11/26/2008 14:24'! openAsMorphMsgCatEditing: editString "Create a pluggable version a Browser on just a message category." | window hSepFrac | window := (SystemWindow labelled: 'later') model: self. hSepFrac := 0.3. window addMorph: ((PluggableListMorph on: self list: #messageCatListSingleton selected: #indexIsOne changeSelected: #indexIsOne: menu: #messageCategoryMenu:) enableDragNDrop: true) fullFrame: ( LayoutFrame fractions: (0@0 corner: 1@0) offsets: (0@0 corner: 0@25) ). window addMorph: self buildMorphicMessageList fullFrame: ( LayoutFrame fractions: (0@0 corner: 1@hSepFrac) offsets: (0@25 corner: 0@0) ). self addLowerPanesTo: window at: (0@hSepFrac corner: 1@1) with: editString. window setUpdatablePanesFrom: #(messageCatListSingleton messageList). ^ window! ! !Browser methodsFor: 'initialization' stamp: 'marcus.denker 11/26/2008 14:24'! openAsMorphSysCatEditing: editString "Create a pluggable version of all the views for a Browser, including views and controllers." | window hSepFrac switchHeight mySingletonList nextOffsets | window := (SystemWindow labelled: 'later') model: self. hSepFrac := 0.30. switchHeight := 25. mySingletonList := PluggableListMorph on: self list: #systemCategorySingleton selected: #indexIsOne changeSelected: #indexIsOne: menu: #systemCatSingletonMenu: keystroke: #systemCatSingletonKey:from:. mySingletonList enableDragNDrop: true. mySingletonList hideScrollBarsIndefinitely. window addMorph: mySingletonList fullFrame: ( LayoutFrame fractions: (0@0 corner: 1@0) offsets: (0@0 corner: 0@switchHeight) ). self addClassAndSwitchesTo: window at: (0@0 corner: 0.3333@hSepFrac) plus: switchHeight. nextOffsets := 0@switchHeight corner: 0@0. window addMorph: self buildMorphicMessageCatList fullFrame: ( LayoutFrame fractions: (0.3333@0 corner: 0.6666@hSepFrac) offsets: nextOffsets ). window addMorph: self buildMorphicMessageList fullFrame: ( LayoutFrame fractions: (0.6666@0 corner: 1@hSepFrac) offsets: nextOffsets ). self addLowerPanesTo: window at: (0@hSepFrac corner: 1@1) with: editString. window setUpdatablePanesFrom: #( classList messageCategoryList messageList). ^ window! ! !Browser methodsFor: 'initialization' stamp: 'alain.plantec 6/10/2008 18:33'! openEditString: aString "Create a pluggable version of all the views for a Browser, including views and controllers." ^ self openAsMorphEditing: aString! ! !Browser methodsFor: 'initialization' stamp: 'alain.plantec 6/10/2008 18:34'! openMessageCatEditString: aString "Create a pluggable version of the views for a Browser that just shows one message category." ^ self openAsMorphMsgCatEditing: aString! ! !Browser methodsFor: 'initialization' stamp: 'alain.plantec 5/30/2008 10:08'! openMessageEditString: aString "Create a pluggable version of the views for a Browser that just shows one message." ^ self openAsMorphMessageEditing: aString! ! !Browser methodsFor: 'initialization' stamp: 'alain.plantec 5/30/2008 10:13'! openOnClassWithEditString: aString "Create a pluggable version of all the views for a Browser, including views and controllers." ^ self openAsMorphClassEditing: aString. ! ! !Browser methodsFor: 'initialization' stamp: 'alain.plantec 5/30/2008 10:16'! openSystemCatEditString: aString "Create a pluggable version of all the views for a Browser, including views and controllers. The top list view is of the currently selected system class category--a single item list." ^ self openAsMorphSysCatEditing: aString! ! !Browser methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:26'! setClass: aBehavior selector: aSymbol "Set the state of a new, uninitialized Browser." | isMeta aClass messageCatIndex | aBehavior ifNil: [^ self]. (aBehavior isKindOf: Metaclass) ifTrue: [ isMeta := true. aClass := aBehavior soleInstance] ifFalse: [ isMeta := false. aClass := aBehavior]. self selectCategoryForClass: aClass. self classListIndex: ( (systemOrganizer listAtCategoryNamed: self selectedSystemCategoryName) indexOf: aClass name). self metaClassIndicated: isMeta. aSymbol ifNil: [^ self]. messageCatIndex := aBehavior organization numberOfCategoryOfElement: aSymbol. self messageCategoryListIndex: (messageCatIndex > 0 ifTrue: [messageCatIndex + 1] ifFalse: [0]). messageCatIndex = 0 ifTrue: [^ self]. self messageListIndex: ( (aBehavior organization listAtCategoryNumber: messageCatIndex) indexOf: aSymbol).! ! !Browser methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:26'! setSelector: aSymbol "Make the receiver point at the given selector, in the currently chosen class" | aClass messageCatIndex | aSymbol ifNil: [^ self]. (aClass := self selectedClassOrMetaClass) ifNil: [^ self]. messageCatIndex := aClass organization numberOfCategoryOfElement: aSymbol. self messageCategoryListIndex: messageCatIndex + 1. messageCatIndex = 0 ifTrue: [^ self]. self messageListIndex: ((aClass organization listAtCategoryNumber: messageCatIndex) indexOf: aSymbol)! ! !Browser methodsFor: 'initialization' stamp: 'sw 11/8/1999 13:36'! systemCatSingletonKey: aChar from: aView ^ self messageListKey: aChar from: aView! ! !Browser methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:26'! systemOrganizer: aSystemOrganizer "Initialize the receiver as a perspective on the system organizer, aSystemOrganizer. Typically there is only one--the system variable SystemOrganization." contents := nil. systemOrganizer := aSystemOrganizer. systemCategoryListIndex := 0. classListIndex := 0. messageCategoryListIndex := 0. messageListIndex := 0. metaClassIndicated := false. self setClassOrganizer. self editSelection: #none.! ! !Browser methodsFor: 'message category functions' stamp: 'DamienCassou 9/29/2009 09:04'! addCategory "Present a choice of categories or prompt for a new category name and add it before the current selection, or at the end if no current selection" | labels reject lines cats menuIndex oldIndex newName | self okToChange ifFalse: [^ self]. classListIndex = 0 ifTrue: [^ self]. labels := OrderedCollection with: 'new...'. reject := Set new. reject addAll: self selectedClassOrMetaClass organization categories; add: ClassOrganizer nullCategory; add: ClassOrganizer default. lines := OrderedCollection new. self selectedClassOrMetaClass allSuperclasses do: [:cls | cls = Object ifFalse: [ cats := cls organization categories reject: [:cat | reject includes: cat]. cats isEmpty ifFalse: [ lines add: labels size. labels addAll: cats asSortedCollection. reject addAll: cats]]]. newName := (labels size = 1 or: [ menuIndex := (UIManager default chooseFrom: labels lines: lines title: 'Add Category'). menuIndex = 0 ifTrue: [^ self]. menuIndex = 1]) ifTrue: [ self request: 'Please type new category name' initialAnswer: 'category name'] ifFalse: [ labels at: menuIndex]. oldIndex := messageCategoryListIndex. newName isEmptyOrNil ifTrue: [^ self] ifFalse: [newName := newName asSymbol]. self classOrMetaClassOrganizer addCategory: newName before: (messageCategoryListIndex = 0 ifTrue: [nil] ifFalse: [self selectedMessageCategoryName]). self changed: #messageCategoryList. self messageCategoryListIndex: (oldIndex = 0 ifTrue: [self classOrMetaClassOrganizer categories size + 1] ifFalse: [oldIndex]). self changed: #messageCategoryList. ! ! !Browser methodsFor: 'message category functions' stamp: 'NS 4/7/2004 22:47'! alphabetizeMessageCategories classListIndex = 0 ifTrue: [^ false]. self okToChange ifFalse: [^ false]. self classOrMetaClassOrganizer sortCategories. self clearUserEditFlag. self editClass. self classListIndex: classListIndex. ^ true! ! !Browser methodsFor: 'message category functions'! buildMessageCategoryBrowser "Create and schedule a message category browser for the currently selected message category." self buildMessageCategoryBrowserEditString: nil! ! !Browser methodsFor: 'message category functions' stamp: 'sd 11/20/2005 21:26'! buildMessageCategoryBrowserEditString: aString "Create and schedule a message category browser for the currently selected message category. The initial text view contains the characters in aString." "wod 6/24/1998: set newBrowser classListIndex so that it works whether the receiver is a standard or a Hierarchy Browser." | newBrowser | messageCategoryListIndex ~= 0 ifTrue: [newBrowser := Browser new. newBrowser systemCategoryListIndex: systemCategoryListIndex. newBrowser classListIndex: (newBrowser classList indexOf: self selectedClassName). newBrowser metaClassIndicated: metaClassIndicated. newBrowser messageCategoryListIndex: messageCategoryListIndex. newBrowser messageListIndex: messageListIndex. self class openBrowserView: (newBrowser openMessageCatEditString: aString) label: 'Message Category Browser (' , newBrowser selectedClassOrMetaClassName , ')']! ! !Browser methodsFor: 'message category functions' stamp: 'sw 10/8/2001 14:10'! canShowMultipleMessageCategories "Answer whether the receiver is capable of showing multiple message categories" ^ true! ! !Browser methodsFor: 'message category functions' stamp: 'sd 11/20/2005 21:26'! categoryOfCurrentMethod "Determine the method category associated with the receiver at the current moment, or nil if none" | aCategory | ^ super categoryOfCurrentMethod ifNil: [(aCategory := self messageCategoryListSelection) == ClassOrganizer allCategory ifTrue: [nil] ifFalse: [aCategory]]! ! !Browser methodsFor: 'message category functions' stamp: 'NS 4/7/2004 22:56'! changeMessageCategories: aString "The characters in aString represent an edited version of the the message categories for the selected class. Update this information in the system and inform any dependents that the categories have been changed. This message is invoked because the user had issued the categories command and edited the message categories. Then the user issued the accept command." self classOrMetaClassOrganizer changeFromString: aString. self clearUserEditFlag. self editClass. self classListIndex: classListIndex. ^ true! ! !Browser methodsFor: 'message category functions' stamp: 'nk 2/14/2004 15:06'! editMessageCategories "Indicate to the receiver and its dependents that the message categories of the selected class have been changed." self okToChange ifFalse: [^ self]. classListIndex ~= 0 ifTrue: [self messageCategoryListIndex: 0. self editSelection: #editMessageCategories. self changed: #editMessageCategories. self contentsChanged]! ! !Browser methodsFor: 'message category functions' stamp: 'tk 4/2/98 13:53'! fileOutMessageCategories "Print a description of the selected message category of the selected class onto an external file." Cursor write showWhile: [messageCategoryListIndex ~= 0 ifTrue: [self selectedClassOrMetaClass fileOutCategory: self selectedMessageCategoryName]]! ! !Browser methodsFor: 'message category functions' stamp: 'marcus.denker 10/20/2008 20:53'! messageCategoryMenu: aMenu ServiceGui browser: self messageCategoryMenu: aMenu. ServiceGui onlyServices ifTrue: [^aMenu]. ^ aMenu labels: 'browse fileOut reorganize alphabetize remove empty categories categorize all uncategorized new category... rename... remove' lines: #(3 8) selections: #(buildMessageCategoryBrowser fileOutMessageCategories editMessageCategories alphabetizeMessageCategories removeEmptyCategories categorizeAllUncategorizedMethods addCategory renameCategory removeMessageCategory) ! ! !Browser methodsFor: 'message category functions' stamp: 'nk 4/23/2004 09:18'! removeEmptyCategories self okToChange ifFalse: [^ self]. self selectedClassOrMetaClass organization removeEmptyCategories. self changed: #messageCategoryList ! ! !Browser methodsFor: 'message category functions' stamp: 'sd 11/20/2005 21:26'! removeMessageCategory "If a message category is selected, create a Confirmer so the user can verify that the currently selected message category should be removed from the system. If so, remove it." | messageCategoryName | messageCategoryListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. messageCategoryName := self selectedMessageCategoryName. (self messageList size = 0 or: [self confirm: 'Are you sure you want to remove this method category and all its methods?']) ifTrue: [self selectedClassOrMetaClass removeCategory: messageCategoryName. self messageCategoryListIndex: 0. self changed: #classSelectionChanged]. self changed: #messageCategoryList. ! ! !Browser methodsFor: 'message category functions' stamp: 'DamienCassou 9/29/2009 09:05'! renameCategory "Prompt for a new category name and add it before the current selection, or at the end if no current selection" | oldIndex oldName newName | classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. (oldIndex := messageCategoryListIndex) = 0 ifTrue: [^ self]. oldName := self selectedMessageCategoryName. newName := self request: 'Please type new category name' initialAnswer: oldName. newName isEmptyOrNil ifTrue: [^ self] ifFalse: [newName := newName asSymbol]. newName = oldName ifTrue: [^ self]. self classOrMetaClassOrganizer renameCategory: oldName toBe: newName. self classListIndex: classListIndex. self messageCategoryListIndex: oldIndex. self changed: #messageCategoryList. ! ! !Browser methodsFor: 'message category functions' stamp: 'sd 11/20/2005 21:26'! showHomeCategory "Show the home category of the selected method. This is only really useful if one is in a tool that supports the showing of categories. Thus, it's good in browsers and hierarchy browsers but not in message-list browsers" | aSelector | self okToChange ifTrue: [(aSelector := self selectedMessageName) ifNotNil: [self selectOriginalCategoryForCurrentMethod. self selectedMessageName: aSelector]]! ! !Browser methodsFor: 'message category list' stamp: 'sd 11/20/2005 21:26'! categorizeAllUncategorizedMethods "Categorize methods by looking in parent classes for a method category." | organizer organizers | organizer := self classOrMetaClassOrganizer. organizers := self selectedClassOrMetaClass withAllSuperclasses collect: [:ea | ea organization]. (organizer listAtCategoryNamed: ClassOrganizer default) do: [:sel | | found | found := (organizers collect: [ :org | org categoryOfElement: sel]) detect: [:ea | ea ~= ClassOrganizer default and: [ ea ~= nil]] ifNone: []. found ifNotNil: [organizer classify: sel under: found]]. self changed: #messageCategoryList! ! !Browser methodsFor: 'message category list' stamp: 'sd 11/20/2005 21:26'! messageCatListSingleton | name | name := self selectedMessageCategoryName. ^ name ifNil: [Array new] ifNotNil: [Array with: name]! ! !Browser methodsFor: 'message category list' stamp: 'ccn 3/22/1999 17:56'! messageCategoryList "Answer the selected category of messages." classListIndex = 0 ifTrue: [^ Array new] ifFalse: [^ (Array with: ClassOrganizer allCategory), self classOrMetaClassOrganizer categories]! ! !Browser methodsFor: 'message category list'! messageCategoryListIndex "Answer the index of the selected message category." ^messageCategoryListIndex! ! !Browser methodsFor: 'message category list' stamp: 'sd 11/20/2005 21:26'! messageCategoryListIndex: anInteger "Set the selected message category to be the one indexed by anInteger." messageCategoryListIndex := anInteger. messageListIndex := 0. self changed: #messageCategorySelectionChanged. self changed: #messageCategoryListIndex. "update my selection" self changed: #messageList. self editSelection: (anInteger > 0 ifTrue: [#newMessage] ifFalse: [self classListIndex > 0 ifTrue: [#editClass] ifFalse: [#newClass]]). contents := nil. self contentsChanged.! ! !Browser methodsFor: 'message category list' stamp: 'ccn 3/24/1999 11:02'! messageCategoryListSelection "Return the selected category name or nil." ^ ((self messageCategoryList size = 0 or: [self messageCategoryListIndex = 0]) or: [self messageCategoryList size < self messageCategoryListIndex]) ifTrue: [nil] ifFalse: [self messageCategoryList at: (self messageCategoryListIndex max: 1)]! ! !Browser methodsFor: 'message category list' stamp: 'sw 10/16/1999 22:56'! rawMessageCategoryList ^ classListIndex = 0 ifTrue: [Array new] ifFalse: [self classOrMetaClassOrganizer categories]! ! !Browser methodsFor: 'message category list' stamp: 'nk 4/22/2004 17:59'! recategorizeMethodSelector: sel "Categorize method named sel by looking in parent classes for a method category. Answer true if recategorized." | thisCat | self selectedClassOrMetaClass allSuperclasses do: [:ea | thisCat := ea organization categoryOfElement: sel. (thisCat ~= ClassOrganizer default and: [thisCat notNil]) ifTrue: [self classOrMetaClassOrganizer classify: sel under: thisCat. self changed: #messageCategoryList. ^ true]]. ^ false! ! !Browser methodsFor: 'message category list' stamp: 'nk 6/13/2004 06:20'! selectMessageCategoryNamed: aSymbol "Given aSymbol, select the category with that name. Do nothing if aSymbol doesn't exist." self messageCategoryListIndex: (self messageCategoryList indexOf: aSymbol ifAbsent: [ 1])! ! !Browser methodsFor: 'message category list' stamp: 'sd 11/20/2005 21:26'! selectOriginalCategoryForCurrentMethod "private - Select the message category for the current method. Note: This should only be called when somebody tries to save a method that they are modifying while ALL is selected. Returns: true on success, false on failure." | aSymbol selectorName | aSymbol := self categoryOfCurrentMethod. selectorName := self selectedMessageName. (aSymbol notNil and: [aSymbol ~= ClassOrganizer allCategory]) ifTrue: [messageCategoryListIndex := (self messageCategoryList indexOf: aSymbol). messageListIndex := (self messageList indexOf: selectorName). self changed: #messageCategorySelectionChanged. self changed: #messageCategoryListIndex. "update my selection" self changed: #messageList. self changed: #messageListIndex. ^ true]. ^ false! ! !Browser methodsFor: 'message category list'! selectedMessageCategoryName "Answer the name of the selected message category, if any. Answer nil otherwise." messageCategoryListIndex = 0 ifTrue: [^nil]. ^self messageCategoryList at: messageCategoryListIndex! ! !Browser methodsFor: 'message category list' stamp: 'sd 11/20/2005 21:26'! setOriginalCategoryIndexForCurrentMethod "private - Set the message category index for the currently selected method. Note: This should only be called when somebody tries to save a method that they are modifying while ALL is selected." messageCategoryListIndex := self messageCategoryList indexOf: self categoryOfCurrentMethod ! ! !Browser methodsFor: 'message functions' stamp: 'sw 1/11/2001 07:22'! addExtraShiftedItemsTo: aMenu "The shifted selector-list menu is being built; some menu items are appropriate only for certain kinds of browsers, and this gives a hook for them to be added as approrpiate. If any is added here, a line should be added first -- browse reimplementors of this message for examples." ! ! !Browser methodsFor: 'message functions'! buildMessageBrowser "Create and schedule a message browser on the currently selected message. Do nothing if no message is selected. The initial text view contains nothing." self buildMessageBrowserEditString: nil! ! !Browser methodsFor: 'message functions' stamp: 'sd 1/5/2002 21:11'! buildMessageBrowserEditString: aString "Create and schedule a message browser for the receiver in which the argument, aString, contains characters to be edited in the text view." messageListIndex = 0 ifTrue: [^ self]. ^ self class openMessageBrowserForClass: self selectedClassOrMetaClass selector: self selectedMessageName editString: aString! ! !Browser methodsFor: 'message functions' stamp: 'sd 11/20/2005 21:26'! defineMessage: aString notifying: aController "Compile the expressions in aString. Notify aController if a syntax error occurs. Install the compiled method in the selected class classified under the currently selected message category name. Answer true if compilation succeeds, false otherwise." | selectedMessageName selector category oldMessageList | selectedMessageName := self selectedMessageName. oldMessageList := self messageList. contents := nil. selector := self selectedClassOrMetaClass compile: aString classified: (category := self selectedMessageCategoryName) notifying: aController. selector == nil ifTrue: [^ false]. contents := aString copy. selector ~~ selectedMessageName ifTrue: [category = ClassOrganizer nullCategory ifTrue: [self changed: #classSelectionChanged. self changed: #classList. self messageCategoryListIndex: 1]. self setClassOrganizer. "In case organization not cached" (oldMessageList includes: selector) ifFalse: [self changed: #messageList]. self messageListIndex: (self messageList indexOf: selector)]. ^ true! ! !Browser methodsFor: 'message functions' stamp: 'lr 7/3/2009 20:59'! defineMessageFrom: aString notifying: aController "Compile the expressions in aString. Notify aController if a syntax error occurs. Install the compiled method in the selected class classified under the currently selected message category name. Answer the selector obtained if compilation succeeds, nil otherwise." | selectedMessageName selector category oldMessageList | selectedMessageName := self selectedMessageName. oldMessageList := self messageList. contents := nil. selector := self selectedClassOrMetaClass compile: aString classified: (category := self selectedMessageCategoryName) notifying: aController. selector == nil ifTrue: [^ nil]. contents := aString copy. selector ~~ selectedMessageName ifTrue: [category = ClassOrganizer nullCategory ifTrue: [self changed: #classSelectionChanged. self changed: #classList. self messageCategoryListIndex: 1]. self setClassOrganizer. "In case organization not cached" (oldMessageList includes: selector) ifFalse: [self changed: #messageList]. self messageListIndex: (self messageList indexOf: selector)]. ^ selector! ! !Browser methodsFor: 'message functions' stamp: 'al 4/24/2004 12:48'! inspectInstances "Inspect all instances of the selected class. 1/26/96 sw" | myClass | ((myClass := self selectedClassOrMetaClass) isNil or: [myClass isTrait]) ifFalse: [myClass theNonMetaClass inspectAllInstances] ! ! !Browser methodsFor: 'message functions' stamp: 'al 4/24/2004 12:48'! inspectSubInstances "Inspect all instances of the selected class and all its subclasses 1/26/96 sw" | aClass | ((aClass := self selectedClassOrMetaClass) isNil or: [aClass isTrait]) ifFalse: [ aClass := aClass theNonMetaClass. aClass inspectSubInstances]. ! ! !Browser methodsFor: 'message functions' stamp: 'marcus.denker 9/20/2008 20:27'! messageListMenu: aMenu shifted: shifted "Answer the message-list menu" ServiceGui browser: self messageListMenu: aMenu. ServiceGui onlyServices ifTrue: [^ aMenu]. shifted ifTrue: [^ self shiftedMessageListMenu: aMenu]. aMenu addList: #( ('what to show...' offerWhatToShowMenu) ('toggle break on entry' toggleBreakOnEntry) - ('browse full (b)' browseMethodFull) ('browse hierarchy (h)' classHierarchy) ('browse method (O)' openSingleMessageBrowser) ('browse protocol (p)' browseFullProtocol) - ('fileOut' fileOutMessage) - ('senders of... (n)' browseSendersOfMessages) ('implementors of... (m)' browseMessages) ('inheritance (i)' methodHierarchy) ('versions (v)' browseVersions) - ('inst var refs...' browseInstVarRefs) ('inst var defs...' browseInstVarDefs) ('class var refs...' browseClassVarRefs) ('class variables' browseClassVariables) ('class refs (N)' browseClassRefs) - ('remove method (x)' removeMessage) - ('more...' shiftedYellowButtonActivity)). ^ aMenu! ! !Browser methodsFor: 'message functions' stamp: 'al 4/24/2004 11:49'! removeMessage "If a message is selected, create a Confirmer so the user can verify that the currently selected message should be removed from the system. If so, remove it. If the Preference 'confirmMethodRemoves' is set to false, the confirmer is bypassed." | messageName confirmation | messageListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. messageName := self selectedMessageName. confirmation := self systemNavigation confirmRemovalOf: messageName on: self selectedClassOrMetaClass. confirmation == 3 ifTrue: [^ self]. (self selectedClassOrMetaClass includesLocalSelector: messageName) ifTrue: [self selectedClassOrMetaClass removeSelector: messageName] ifFalse: [self removeNonLocalSelector: messageName]. self messageListIndex: 0. self changed: #messageList. self setClassOrganizer. "In case organization not cached" confirmation == 2 ifTrue: [self systemNavigation browseAllCallsOn: messageName]! ! !Browser methodsFor: 'message functions' stamp: 'tk 4/2/98 17:03'! removeMessageFromBrowser "Our list speaks the truth and can't have arbitrary things removed" ^ self changed: #flash! ! !Browser methodsFor: 'message functions' stamp: 'stephane.ducasse 10/26/2008 14:39'! shiftedMessageListMenu: aMenu "Fill aMenu with the items appropriate when the shift key is held down" aMenu addStayUpItem. aMenu addList: #( ('toggle diffing (D)' toggleDiffing) ('implementors of sent messages' browseAllMessages) - ('local senders of...' browseLocalSendersOfMessages) ('local implementors of...' browseLocalImplementors) - ('spawn sub-protocol' spawnProtocol) ('spawn full protocol' spawnFullProtocol) - ('sample instance' makeSampleInstance) ('inspect instances' inspectInstances) ('inspect subinstances' inspectSubInstances)). self addExtraShiftedItemsTo: aMenu. aMenu addList: #( - ('change category...' changeCategory)). self canShowMultipleMessageCategories ifTrue: [aMenu addList: #(('show category (C)' showHomeCategory))]. aMenu addList: #( - ('change sets with this method' findMethodInChangeSets) ('revert to previous version' revertToPreviousVersion) ('remove from current change set' removeFromCurrentChanges) ('revert & remove from changes' revertAndForget) ('add to current change set' adoptMessageInCurrentChangeset) ('copy up or copy down...' copyUpOrCopyDown) - ('more...' unshiftedYellowButtonActivity)). ^ aMenu ! ! !Browser methodsFor: 'message list' stamp: 'adrian-lienhard 5/18/2009 21:10'! messageList "Answer an Array of the message selectors of the currently selected message category, provided that the messageCategoryListIndex is in proper range. Otherwise, answer an empty Array If messageCategoryListIndex is found to be larger than the number of categories (it happens!!), it is reset to zero." | sel | (sel := self messageCategoryListSelection) ifNil: [ ^ self classOrMetaClassOrganizer ifNil: [Array new] ifNotNil: [self classOrMetaClassOrganizer allMethodSelectors] ]. ^ sel = ClassOrganizer allCategory ifTrue: [ self classOrMetaClassOrganizer ifNil: [Array new] ifNotNil: [self classOrMetaClassOrganizer allMethodSelectors]] ifFalse: [ (self classOrMetaClassOrganizer listAtCategoryNumber: messageCategoryListIndex - 1) ifNil: [messageCategoryListIndex := 0. Array new]]! ! !Browser methodsFor: 'message list'! messageListIndex "Answer the index of the selected message selector into the currently selected message category." ^messageListIndex! ! !Browser methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! messageListIndex: anInteger "Set the selected message selector to be the one indexed by anInteger." messageListIndex := anInteger. self editSelection: (anInteger > 0 ifTrue: [#editMessage] ifFalse: [self messageCategoryListIndex > 0 ifTrue: [#newMessage] ifFalse: [self classListIndex > 0 ifTrue: [#editClass] ifFalse: [#newClass]]]). contents := nil. self changed: #messageListIndex. "update my selection" self contentsChanged. self decorateButtons.! ! !Browser methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! messageListSingleton | name | name := self selectedMessageName. ^ name ifNil: [Array new] ifNotNil: [Array with: name]! ! !Browser methodsFor: 'message list' stamp: 'sw 12/1/2000 11:17'! reformulateList "If the receiver has a way of reformulating its message list, here is a chance for it to do so" super reformulateList. self messageListIndex: 0! ! !Browser methodsFor: 'message list' stamp: 'md 2/20/2006 15:01'! selectedMessage "Answer a copy of the source code for the selected message." | class selector method | contents == nil ifFalse: [^ contents copy]. self showingDecompile ifTrue: [^ self decompiledSourceIntoContents]. class := self selectedClassOrMetaClass. selector := self selectedMessageName. method := class compiledMethodAt: selector ifAbsent: [^ '']. "method deleted while in another project" currentCompiledMethod := method. ^ contents := (self showingDocumentation ifFalse: [ self sourceStringPrettifiedAndDiffed ] ifTrue: [ self commentContents ]) copy asText makeSelectorBoldIn: class! ! !Browser methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! selectedMessageName "Answer the message selector of the currently selected message, if any. Answer nil otherwise." | aList | messageListIndex = 0 ifTrue: [^ nil]. ^ (aList := self messageList) size >= messageListIndex ifTrue: [aList at: messageListIndex] ifFalse: [nil]! ! !Browser methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! selectedMessageName: aSelector "Make the given selector be the selected message name" | anIndex | anIndex := self messageList indexOf: aSelector. anIndex > 0 ifTrue: [self messageListIndex: anIndex]! ! !Browser methodsFor: 'message list'! toggleMessageListIndex: anInteger "If the currently selected message index is anInteger, deselect the message selector. Otherwise select the message selector whose index is anInteger." self messageListIndex: (messageListIndex = anInteger ifTrue: [0] ifFalse: [anInteger])! ! !Browser methodsFor: 'metaclass' stamp: 'di 1/14/98 12:25'! classCommentIndicated "Answer true iff we're viewing the class comment." ^ editSelection == #editComment ! ! !Browser methodsFor: 'metaclass' stamp: 'mir 9/25/2008 14:56'! classMessagesIndicated "Answer whether the messages to be presented should come from the metaclass." ^ self metaClassIndicated and: [self classCommentIndicated not]! ! !Browser methodsFor: 'metaclass'! classOrMetaClassOrganizer "Answer the class organizer for the metaclass or class, depending on which (instance or class) is indicated." self metaClassIndicated ifTrue: [^metaClassOrganizer] ifFalse: [^classOrganizer]! ! !Browser methodsFor: 'metaclass'! indicateClassMessages "Indicate that the message selection should come from the metaclass messages." self metaClassIndicated: true! ! !Browser methodsFor: 'metaclass'! indicateInstanceMessages "Indicate that the message selection should come from the class (instance) messages." self metaClassIndicated: false! ! !Browser methodsFor: 'metaclass' stamp: 'di 1/14/98 13:20'! instanceMessagesIndicated "Answer whether the messages to be presented should come from the class." ^metaClassIndicated not and: [self classCommentIndicated not]! ! !Browser methodsFor: 'metaclass' stamp: 'sr 6/21/2000 17:23'! metaClassIndicated "Answer the boolean flag that indicates which of the method dictionaries, class or metaclass." ^ metaClassIndicated! ! !Browser methodsFor: 'metaclass' stamp: 'sd 11/20/2005 21:26'! metaClassIndicated: trueOrFalse "Indicate whether browsing instance or class messages." metaClassIndicated := trueOrFalse. self setClassOrganizer. systemCategoryListIndex > 0 ifTrue: [self editSelection: (classListIndex = 0 ifTrue: [metaClassIndicated ifTrue: [#none] ifFalse: [#newClass]] ifFalse: [#editClass])]. messageCategoryListIndex := 0. messageListIndex := 0. contents := nil. self changed: #classSelectionChanged. self changed: #messageCategoryList. self changed: #messageList. self changed: #contents. self changed: #annotation. self decorateButtons ! ! !Browser methodsFor: 'metaclass' stamp: 'al 4/24/2004 11:47'! selectedClassOrMetaClass "Answer the selected class/trait or metaclass/classTrait." | cls | ^self metaClassIndicated ifTrue: [(cls := self selectedClass) ifNil: [nil] ifNotNil: [cls classSide]] ifFalse: [self selectedClass]! ! !Browser methodsFor: 'metaclass'! selectedClassOrMetaClassName "Answer the selected class name or metaclass name." ^self selectedClassOrMetaClass name! ! !Browser methodsFor: 'metaclass' stamp: 'md 2/18/2006 16:31'! setClassOrganizer "Install whatever organization is appropriate" | theClass | classOrganizer := nil. metaClassOrganizer := nil. classListIndex = 0 ifTrue: [^ self]. theClass := self selectedClass ifNil: [ ^self ]. classOrganizer := theClass organization. metaClassOrganizer := theClass classSide organization.! ! !Browser methodsFor: 'system category functions' stamp: 'DamienCassou 9/29/2009 09:04'! addSystemCategory "Prompt for a new category name and add it before the current selection, or at the end if no current selection" | oldIndex newName | self okToChange ifFalse: [^ self]. oldIndex := systemCategoryListIndex. newName := self request: 'Please type new category name' initialAnswer: 'Category-Name'. newName isEmptyOrNil ifTrue: [^ self] ifFalse: [newName := newName asSymbol]. systemOrganizer addCategory: newName before: (systemCategoryListIndex = 0 ifTrue: [nil] ifFalse: [self selectedSystemCategoryName]). self systemCategoryListIndex: (oldIndex = 0 ifTrue: [self systemCategoryList size] ifFalse: [oldIndex]). self changed: #systemCategoryList.! ! !Browser methodsFor: 'system category functions' stamp: 'brp 8/4/2003 21:38'! alphabetizeSystemCategories self okToChange ifFalse: [^ false]. systemOrganizer sortCategories. self systemCategoryListIndex: 0. self changed: #systemCategoryList. ! ! !Browser methodsFor: 'system category functions'! buildSystemCategoryBrowser "Create and schedule a new system category browser." self buildSystemCategoryBrowserEditString: nil! ! !Browser methodsFor: 'system category functions' stamp: 'sd 11/20/2005 21:26'! buildSystemCategoryBrowserEditString: aString "Create and schedule a new system category browser with initial textual contents set to aString." | newBrowser | systemCategoryListIndex > 0 ifTrue: [newBrowser := self class new. newBrowser systemCategoryListIndex: systemCategoryListIndex. newBrowser setClass: self selectedClassOrMetaClass selector: self selectedMessageName. self class openBrowserView: (newBrowser openSystemCatEditString: aString) label: 'Classes in category ', newBrowser selectedSystemCategoryName]! ! !Browser methodsFor: 'system category functions' stamp: 'di 4/12/98 13:21'! changeSystemCategories: aString "Update the class categories by parsing the argument aString." systemOrganizer changeFromString: aString. self changed: #systemCategoryList. ^ true! ! !Browser methodsFor: 'system category functions' stamp: 'tk 4/2/98 13:43'! classNotFound self changed: #flash.! ! !Browser methodsFor: 'system category functions' stamp: 'nk 2/14/2004 15:09'! editSystemCategories "Retrieve the description of the class categories of the system organizer." self okToChange ifFalse: [^ self]. self systemCategoryListIndex: 0. self editSelection: #editSystemCategories. self changed: #editSystemCategories. self contentsChanged! ! !Browser methodsFor: 'system category functions' stamp: 'tk 3/31/98 07:52'! fileOutSystemCategory "Print a description of each class in the selected category onto a file whose name is the category name followed by .st." systemCategoryListIndex ~= 0 ifTrue: [systemOrganizer fileOutCategory: self selectedSystemCategoryName]! ! !Browser methodsFor: 'system category functions' stamp: 'DamienCassou 9/23/2009 08:32'! findClass "Search for a class by name." | pattern foundClassOrTrait | self okToChange ifFalse: [^ self classNotFound]. pattern := UIManager default request: 'Class name or fragment?'. pattern isEmptyOrNil ifTrue: [^ self classNotFound]. foundClassOrTrait := SystemNavigation default classFromPattern: pattern withCaption: ''. foundClassOrTrait ifNil: [^ self classNotFound]. self selectCategoryForClass: foundClassOrTrait. self selectClass: foundClassOrTrait. ! ! !Browser methodsFor: 'system category functions' stamp: 'sw 11/8/1999 10:04'! potentialClassNames "Answer the names of all the classes that could be viewed in this browser. This hook is provided so that HierarchyBrowsers can indicate their restricted subset. For generic Browsers, the entire list of classes known to Smalltalk is provided, though of course that really only is accurate in the case of full system browsers." ^ Smalltalk classNames! ! !Browser methodsFor: 'system category functions' stamp: 'di 4/12/98 13:55'! removeSystemCategory "If a class category is selected, create a Confirmer so the user can verify that the currently selected class category and all of its classes should be removed from the system. If so, remove it." systemCategoryListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. (self classList size = 0 or: [self confirm: 'Are you sure you want to remove this system category and all its classes?']) ifTrue: [systemOrganizer removeSystemCategory: self selectedSystemCategoryName. self systemCategoryListIndex: 0. self changed: #systemCategoryList]! ! !Browser methodsFor: 'system category functions' stamp: 'DamienCassou 9/29/2009 09:05'! renameSystemCategory "Prompt for a new category name and add it before the current selection, or at the end if no current selection" | oldIndex oldName newName | (oldIndex := systemCategoryListIndex) = 0 ifTrue: [^ self]. "no selection" self okToChange ifFalse: [^ self]. oldName := self selectedSystemCategoryName. newName := self request: 'Please type new category name' initialAnswer: oldName. newName isEmptyOrNil ifTrue: [^ self] ifFalse: [newName := newName asSymbol]. oldName = newName ifTrue: [^ self]. systemOrganizer renameCategory: oldName toBe: newName. self systemCategoryListIndex: oldIndex. self changed: #systemCategoryList.! ! !Browser methodsFor: 'system category functions' stamp: 'marcus.denker 10/20/2008 21:22'! systemCatSingletonMenu: aMenu ^ aMenu labels: 'browse fileOut update rename... remove' lines: #(2 4) selections: #(buildSystemCategoryBrowser fileOutSystemCategory updateSystemCategories renameSystemCategory removeSystemCategory) ! ! !Browser methodsFor: 'system category functions' stamp: 'marcus.denker 10/20/2008 21:23'! systemCategoryMenu: aMenu ServiceGui browser: self classCategoryMenu: aMenu. ServiceGui onlyServices ifTrue: [^aMenu]. ^ aMenu labels: 'find class... (f) recent classes... (r) browse fileOut reorganize alphabetize update add category... rename... remove' lines: #(2 4 6 8) selections: #(findClass recent buildSystemCategoryBrowser fileOutSystemCategory editSystemCategories alphabetizeSystemCategories updateSystemCategories addSystemCategory renameSystemCategory removeSystemCategory )! ! !Browser methodsFor: 'system category functions' stamp: 'di 4/12/98 13:17'! updateSystemCategories "The class categories were changed in another browser. The receiver must reorganize its lists based on these changes." self okToChange ifFalse: [^ self]. self changed: #systemCategoryList! ! !Browser methodsFor: 'system category list' stamp: 'tk 5/4/1998 15:46'! indexIsOne "When used as a singleton list, index is always one" ^ 1! ! !Browser methodsFor: 'system category list' stamp: 'tk 5/4/1998 15:46'! indexIsOne: value "When used as a singleton list, can't change it" ^ self! ! !Browser methodsFor: 'system category list' stamp: 'stp 01/13/2000 12:25'! selectCategoryForClass: theClass self systemCategoryListIndex: (self systemCategoryList indexOf: theClass category) ! ! !Browser methodsFor: 'system category list' stamp: 'md 3/3/2006 11:02'! selectedEnvironment "Answer the name of the selected system category or nil." systemCategoryListIndex = 0 ifTrue: [^nil]. ^ Smalltalk! ! !Browser methodsFor: 'system category list'! selectedSystemCategoryName "Answer the name of the selected system category or nil." systemCategoryListIndex = 0 ifTrue: [^nil]. ^self systemCategoryList at: systemCategoryListIndex! ! !Browser methodsFor: 'system category list'! systemCategoryList "Answer the class categories modelled by the receiver." ^systemOrganizer categories! ! !Browser methodsFor: 'system category list'! systemCategoryListIndex "Answer the index of the selected class category." ^systemCategoryListIndex! ! !Browser methodsFor: 'system category list' stamp: 'sd 11/20/2005 21:26'! systemCategoryListIndex: anInteger "Set the selected system category index to be anInteger. Update all other selections to be deselected." systemCategoryListIndex := anInteger. classListIndex := 0. messageCategoryListIndex := 0. messageListIndex := 0. self editSelection: ( anInteger = 0 ifTrue: [#none] ifFalse: [#newClass]). metaClassIndicated := false. self setClassOrganizer. contents := nil. self changed: #systemCategorySelectionChanged. self changed: #systemCategoryListIndex. "update my selection" self changed: #classList. self changed: #messageCategoryList. self changed: #messageList. self changed: #relabel. self contentsChanged! ! !Browser methodsFor: 'system category list' stamp: 'sd 11/20/2005 21:26'! systemCategorySingleton | cat | cat := self selectedSystemCategoryName. ^ cat ifNil: [Array new] ifNotNil: [Array with: cat]! ! !Browser methodsFor: 'system category list'! toggleSystemCategoryListIndex: anInteger "If anInteger is the current system category index, deselect it. Else make it the current system category selection." self systemCategoryListIndex: (systemCategoryListIndex = anInteger ifTrue: [0] ifFalse: [anInteger])! ! !Browser methodsFor: 'toolbuilder' stamp: 'ar 2/12/2005 14:19'! buildWith: builder "Create the ui for the browser" | windowSpec listSpec textSpec buttonSpec panelSpec max | windowSpec := builder pluggableWindowSpec new. windowSpec model: self. windowSpec label: 'System Browser'. windowSpec children: OrderedCollection new. max := self wantsOptionalButtons ifTrue:[0.43] ifFalse:[0.5]. listSpec := builder pluggableListSpec new. listSpec model: self; list: #systemCategoryList; getIndex: #systemCategoryListIndex; setIndex: #systemCategoryListIndex:; menu: #systemCategoryMenu:; keyPress: #systemCatListKey:from:; frame: (0@0 corner: 0.25@max). windowSpec children add: listSpec. listSpec := builder pluggableListSpec new. listSpec model: self; list: #classList; getIndex: #classListIndex; setIndex: #classListIndex:; menu: #classListMenu:; keyPress: #classListKey:from:; frame: (0.25@0 corner: 0.5@(max-0.1)). windowSpec children add: listSpec. panelSpec := builder pluggablePanelSpec new. panelSpec frame: (0.25@(max-0.1) corner: 0.5@max). panelSpec children: OrderedCollection new. windowSpec children addLast: panelSpec. buttonSpec := builder pluggableButtonSpec new. buttonSpec model: self; label: 'instance'; state: #instanceMessagesIndicated; action: #indicateInstanceMessages; frame: (0@0 corner: 0.4@1). panelSpec children addLast: buttonSpec. buttonSpec := builder pluggableButtonSpec new. buttonSpec model: self; label: '?'; state: #classCommentIndicated; action: #plusButtonHit; frame: (0.4@0 corner: 0.6@1). panelSpec children addLast: buttonSpec. buttonSpec := builder pluggableButtonSpec new. buttonSpec model: self; label: 'class'; state: #classMessagesIndicated; action: #indicateClassMessages; frame: (0.6@0 corner: 1@1). panelSpec children addLast: buttonSpec. listSpec := builder pluggableListSpec new. listSpec model: self; list: #messageCategoryList; getIndex: #messageCategoryListIndex; setIndex: #messageCategoryListIndex:; menu: #messageCategoryMenu:; keyPress: #arrowKey:from:; frame: (0.5@0 corner: 0.75@max). windowSpec children add: listSpec. listSpec := builder pluggableListSpec new. listSpec model: self; list: #messageList; getIndex: #messageListIndex; setIndex: #messageListIndex:; menu: #messageListMenu:shifted:; keyPress: #messageListKey:from:; frame: (0.75@0 corner: 1@max). windowSpec children add: listSpec. self wantsOptionalButtons ifTrue:[ panelSpec := self buildOptionalButtonsWith: builder. panelSpec frame: (0@0.43 corner: 1@0.5). windowSpec children add: panelSpec. ]. textSpec := builder pluggableTextSpec new. textSpec model: self; getText: #contents; setText: #contents:notifying:; selection: #contentsSelection; menu: #codePaneMenu:shifted:; frame: (0@0.5corner: 1@1). windowSpec children add: textSpec. ^builder build: windowSpec! ! !Browser methodsFor: 'traits' stamp: 'al 1/9/2006 18:29'! addSpecialMenu: aMenu aMenu addList: #( - ('new class' newClass) ('new trait' newTrait) -). self selectedClass notNil ifTrue: [ aMenu addList: #( ('add trait' addTrait) -) ]. aMenu addList: #(-). ^ aMenu! ! !Browser methodsFor: 'traits' stamp: 'al 1/9/2006 18:26'! addTrait | input trait | input := UIManager default request: 'add trait'. input isEmptyOrNil ifFalse: [ trait := Smalltalk classNamed: input. (trait isNil or: [trait isTrait not]) ifTrue: [ ^self inform: 'Input invalid. ' , input , ' does not exist or is not a trait']. self selectedClass addToComposition: trait. self contentsChanged]. ! ! !Browser methodsFor: 'traits' stamp: 'md 3/3/2006 10:58'! defineTrait: defString notifying: aController | defTokens keywdIx envt oldTrait newTraitName trait | oldTrait := self selectedClassOrMetaClass. defTokens := defString findTokens: Character separators. keywdIx := defTokens findFirst: [:x | x = 'category']. envt := self selectedEnvironment. keywdIx := defTokens findFirst: [:x | x = 'named:']. newTraitName := (defTokens at: keywdIx+1) copyWithoutAll: '#()'. ((oldTrait isNil or: [oldTrait baseTrait name asString ~= newTraitName]) and: [envt includesKey: newTraitName asSymbol]) ifTrue: ["Attempting to define new class/trait over existing one when not looking at the original one in this browser..." (self confirm: ((newTraitName , ' is an existing class/trait in this system. Redefining it might cause serious problems. Is this really what you want to do?') asText makeBoldFrom: 1 to: newTraitName size)) ifFalse: [^ false]]. trait := Compiler evaluate: defString notifying: aController logged: true. ^(trait isKindOf: TraitBehavior) ifTrue: [ self changed: #classList. self classListIndex: (self classList indexOf: trait baseTrait name). self clearUserEditFlag; editClass. true] ifFalse: [ false ] ! ! !Browser methodsFor: 'traits' stamp: 'al 4/24/2004 11:48'! newClass (self selectedClassOrMetaClass notNil and: [self selectedClassOrMetaClass isTrait]) ifTrue: [self classListIndex: 0]. self editClass. editSelection := #newClass. self contentsChanged! ! !Browser methodsFor: 'traits' stamp: 'al 4/24/2004 11:48'! newTrait self classListIndex: 0. self editClass. editSelection := #newTrait. self contentsChanged! ! !Browser methodsFor: 'traits' stamp: 'al 4/24/2004 11:49'! removeNonLocalSelector: aSymbol | traits isAlias | traits := self selectedClassOrMetaClass traitsProvidingSelector: aSymbol. isAlias := self selectedClassOrMetaClass isLocalAliasSelector: aSymbol. isAlias ifTrue: [ self assert: traits size = 1. self selectedClassOrMetaClass removeAlias: aSymbol of: traits first] ifFalse: [ traits do: [:each | self selectedClassOrMetaClass addExclusionOf: aSymbol to: each ]] ! ! !Browser methodsFor: 'user interface' stamp: 'hpt 9/30/2004 20:51'! addModelItemsToWindowMenu: aMenu "Add model-related items to the window menu" super addModelItemsToWindowMenu: aMenu. SystemBrowser addRegistryMenuItemsTo: aMenu inAccountOf: self.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Browser class instanceVariableNames: ''! !Browser class methodsFor: 'initialization' stamp: 'hpt 8/5/2004 19:41'! initialize "Browser initialize" RecentClasses := OrderedCollection new. self registerInFlapsRegistry; registerInAppRegistry ! ! !Browser class methodsFor: 'initialization' stamp: 'hpt 8/5/2004 19:41'! registerInAppRegistry "Register the receiver in the SystemBrowser AppRegistry" SystemBrowser register: self.! ! !Browser class methodsFor: 'initialization' stamp: 'asm 4/10/2003 12:32'! registerInFlapsRegistry "Register the receiver in the system's flaps registry" self environment at: #Flaps ifPresent: [:cl | cl registerQuad: #(#Browser #prototypicalToolWindow 'Browser' 'A Browser is a tool that allows you to view all the code of all the classes in the system' ) forFlapNamed: 'Tools']! ! !Browser class methodsFor: 'initialization' stamp: 'hpt 8/5/2004 19:42'! unload "Unload the receiver from global registries" self environment at: #Flaps ifPresent: [:cl | cl unregisterQuadsWithReceiver: self]. SystemBrowser unregister: self.! ! !Browser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:27'! fullOnClass: aClass "Open a new full browser set to class." | brow | brow := self new. brow setClass: aClass selector: nil. ^ self openBrowserView: (brow openEditString: nil) label: 'System Browser'! ! !Browser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! fullOnClass: aClass selector: aSelector "Open a new full browser set to class." | brow classToUse | classToUse := SystemBrowser default. brow := classToUse new. brow setClass: aClass selector: aSelector. ^ classToUse openBrowserView: (brow openEditString: nil) label: brow labelString! ! !Browser class methodsFor: 'instance creation' stamp: 'di 10/18/1999 22:03'! new ^super new systemOrganizer: SystemOrganization! ! !Browser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! newOnCategory: aCategory "Browse the system category of the given name. 7/13/96 sw" "Browser newOnCategory: 'Interface-Browser'" | newBrowser catList | newBrowser := self new. catList := newBrowser systemCategoryList. newBrowser systemCategoryListIndex: (catList indexOf: aCategory asSymbol ifAbsent: [^ self inform: 'No such category']). ^ self openBrowserView: (newBrowser openSystemCatEditString: nil) label: 'Classes in category ', aCategory ! ! !Browser class methodsFor: 'instance creation' stamp: 'tk 4/18/1998 16:28'! newOnClass: aClass "Open a new class browser on this class." ^ self newOnClass: aClass label: 'Class Browser: ', aClass name! ! !Browser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! newOnClass: aClass label: aLabel "Open a new class browser on this class." | newBrowser | newBrowser := self new. newBrowser setClass: aClass selector: nil. ^ self openBrowserView: (newBrowser openOnClassWithEditString: nil) label: aLabel ! ! !Browser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! newOnClass: aClass selector: aSymbol "Open a new class browser on this class." | newBrowser | newBrowser := self new. newBrowser setClass: aClass selector: aSymbol. ^ self openBrowserView: (newBrowser openOnClassWithEditString: nil) label: 'Class Browser: ', aClass name ! ! !Browser class methodsFor: 'instance creation' stamp: 'md 3/10/2006 21:46'! open ^self openBrowser ! ! !Browser class methodsFor: 'instance creation' stamp: 'jcg 10/29/2003 23:11'! openBrowser "Create and schedule a BrowserView with default browser label. The view consists of five subviews, starting with the list view of system categories of SystemOrganization. The initial text view part is empty." | br | br := self new. ^ self openBrowserView: (br openEditString: nil) label: br defaultBrowserTitle. ! ! !Browser class methodsFor: 'instance creation' stamp: 'alain.plantec 6/19/2008 09:43'! openBrowserView: aBrowserView label: aString "Schedule aBrowserView, labelling the view aString." (aBrowserView setLabel: aString) openInWorld. ^ aBrowserView model ! ! !Browser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! openMessageBrowserForClass: aBehavior selector: aSymbol editString: aString "Create and schedule a message browser for the class, aBehavior, in which the argument, aString, contains characters to be edited in the text view. These characters are the source code for the message selector aSymbol." | newBrowser | (newBrowser := self new) setClass: aBehavior selector: aSymbol. ^ self openBrowserView: (newBrowser openMessageEditString: aString) label: newBrowser selectedClassOrMetaClassName , ' ' , newBrowser selectedMessageName ! ! !Browser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! prototypicalToolWindow "Answer an example of myself seen in a tool window, for the benefit of parts-launching tools" | aWindow | aWindow := self new openAsMorphEditing: nil. aWindow setLabel: 'System Browser'; applyModelExtent. ^ aWindow! ! !Browser class methodsFor: 'instance creation' stamp: 'nk 6/2/2004 12:55'! systemOrganizer: anOrganizer ^(super new) systemOrganizer: anOrganizer; yourself! ! !Browser class methodsFor: 'window color' stamp: 'sw 2/26/2002 13:46'! windowColorSpecification "Answer a WindowColorSpec object that declares my preference" ^ WindowColorSpec classSymbol: self name wording: 'Browser' brightColor: #lightGreen pastelColor: #paleGreen helpMessage: 'The standard "system browser" tool that allows you to browse through all the code in the system'! ! PluggableTextMorph subclass: #BrowserCommentTextMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tools-Browser'! !BrowserCommentTextMorph commentStamp: '' prior: 0! I am a PluggableTextMorph that knows enough to make myself invisible when necessary.! !BrowserCommentTextMorph methodsFor: 'accessing' stamp: 'nk 2/15/2004 14:12'! lowerPane "Answer the AlignmentMorph that I live beneath" ^self valueOfProperty: #browserLowerPane! ! !BrowserCommentTextMorph methodsFor: 'accessing' stamp: 'nk 2/15/2004 14:07'! window ^self owner ifNil: [ self valueOfProperty: #browserWindow ].! ! !BrowserCommentTextMorph methodsFor: 'displaying' stamp: 'nk 2/15/2004 13:41'! hideOrShowPane (self model editSelection == #editClass) ifTrue: [ self showPane ] ifFalse: [ self hidePane ]! ! !BrowserCommentTextMorph methodsFor: 'displaying' stamp: 'marcus.denker 11/10/2008 10:04'! hidePane "Fixed to not keep doing the splitters. If we are hiden don't hide again!!" | win | self owner ifNotNil: [ win := self window ifNil: [^self]. self window ifNotNil: [:window | window removePaneSplitters]. self lowerPane ifNotNil: [:lp | lp layoutFrame bottomFraction: self layoutFrame bottomFraction. lp layoutFrame bottomOffset: SystemWindow borderWidth negated]. self delete. win updatePanesFromSubmorphs. win addPaneSplitters]! ! !BrowserCommentTextMorph methodsFor: 'displaying' stamp: 'marcus.denker 11/10/2008 10:04'! showPane "Fixed to not keep doing the splitters. If we are showing don't show again!!" | win | self owner ifNil: [ win := self window ifNil: [ ^self ]. win addMorph: self fullFrame: self layoutFrame. win updatePanesFromSubmorphs. self lowerPane ifNotNil: [ :lp | lp layoutFrame bottomFraction: self layoutFrame topFraction ]. win addPaneSplitters]! ! !BrowserCommentTextMorph methodsFor: 'updating' stamp: 'stephane.ducasse 10/9/2008 18:50'! noteNewOwner: win "Dirty fix for when the 'lower pane' hasn't been reset to the bottom at the time the receiver is added" super noteNewOwner: win. self setProperty: #browserWindow toValue: win. win ifNil: [ ^self ]. win setProperty: #browserClassCommentPane toValue: self. self setProperty: #browserLowerPane toValue: (win submorphThat: [ :m | m isAlignmentMorph and: [ m layoutFrame bottomFraction = 1 or: [ m layoutFrame bottomFraction = self layoutFrame topFraction]]] ifNone: []). ! ! !BrowserCommentTextMorph methodsFor: 'updating' stamp: 'nk 2/15/2004 13:42'! update: anAspect super update: anAspect. anAspect == #editSelection ifFalse: [ ^self ]. self hideOrShowPane! ! ServiceProvider subclass: #BrowserProvider instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Services-Base-Providers'! !BrowserProvider commentStamp: 'rr 7/10/2006 15:17' prior: 0! I define the default categories of services dealing with browsing: - the class category menu (service identifier: browserClassCategoryMenu) - the class menu (browserClassMenu) - the method category menu (browserMethodCategoryMenu) - the browser method menu (browserMethodMenu) - the browser button bar (browserButtonBar) - the browser code pane/selection menu (browserCodePaneMenu)! !BrowserProvider methodsFor: 'saved preferences'! browserClassMenushortcut ^ #(#'Shortcut for browserClassMenu:' '' 1000 )! ! !BrowserProvider methodsFor: 'saved preferences'! browserMethodMenushortcut ^ #(#'Shortcut for browserMethodMenu:' '' 1000 )! ! !BrowserProvider methodsFor: 'services' stamp: 'rr 10/23/2005 14:42'! browser ^ ServiceCategory text: 'Browser' button: 'browser' description: 'The browser menus'! ! !BrowserProvider methodsFor: 'services' stamp: 'rr 1/9/2006 18:59'! browserButtonBar ^ ServiceCategory text:'button bar' button:'button' description:'the browser button bar'! ! !BrowserProvider methodsFor: 'services' stamp: 'rr 1/9/2006 19:00'! browserClassCategoryMenu ^ ServiceCategory text:'Class Category' button:'class cat' description:'The browser class category menu'! ! !BrowserProvider methodsFor: 'services' stamp: 'rr 1/9/2006 19:00'! browserClassMenu ^ ServiceCategory text:'Class' button:'class' description:'The browser class menu'! ! !BrowserProvider methodsFor: 'services' stamp: 'rr 1/9/2006 19:01'! browserCodePaneMenu ^ ServiceCategory text: 'Code Pane' button: 'pane' description: 'The browser code pane menu'! ! !BrowserProvider methodsFor: 'services' stamp: 'rr 1/9/2006 19:00'! browserMethodCategoryMenu ^ ServiceCategory text:'Method Category' button:'method cat' description:'The browser method menu'! ! !BrowserProvider methodsFor: 'services' stamp: 'rr 1/9/2006 19:01'! browserMethodMenu ^ ServiceCategory text:'Method' button:'method' description:'The browser method menu'! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BrowserProvider class instanceVariableNames: ''! !BrowserProvider class methodsFor: 'initialization' stamp: 'rr 1/10/2006 12:53'! initialize ServiceRegistry current buildProvider: self new! ! TextRequestor subclass: #BrowserRequestor instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Services-Base-Requestors'! !BrowserRequestor commentStamp: 'rr 7/10/2006 15:24' prior: 0! I am a requestor specialized to fetch information in a Browser. I can ask a browser its selected class and selected method for example. If the RB is installed too, I can also fetch ast nodes in the browser's selected method. I am the default requestor for CodeHolder and it's subclasses. To be integrated with services, alternative browsers, such as the OmniBrowser and Whisker should define a specialized requestor subclassing this one. A few core messages would need to be redefined, such as getClass, getMessage ... to be adapted to the browser's data structures. Only a few of them have to be overridden, the majority of the requests rely on a few base ones.! !BrowserRequestor methodsFor: 'initialization' stamp: 'rr 8/27/2005 15:52'! browser: b self model: b! ! !BrowserRequestor methodsFor: 'requests' stamp: 'gvc 9/26/2008 15:14'! getArgumentPermutation "Answer the argument permutation map. No support for changing argument count." ^(1 to: (self getBrowser selectedMessageName ifNil: [^nil]) numArgs) asArray! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 8/27/2005 15:43'! getBrowser ^ self getModel! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 8/27/2005 15:51'! getClass ^ self getBrowser selectedClassOrMetaClass! ! !BrowserRequestor methodsFor: 'requests' stamp: 'alain.plantec 2/6/2009 15:18'! getInitializingExpressionForTheNewParameter ^ UIManager default request: 'Enter default parameter code' translated initialAnswer: '42'! ! !BrowserRequestor methodsFor: 'requests' stamp: 'alain.plantec 2/6/2009 15:18'! getNewSelectorName ^ UIManager default request: 'Enter the new selector name' translated initialAnswer: self getSelector! ! !BrowserRequestor methodsFor: 'requests' stamp: 'alain.plantec 2/6/2009 15:18'! getNewVariableName ^ UIManager default request: 'Enter the new variable name' translated initialAnswer: 'foo'! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 8/4/2005 14:41'! getPackage self getSelector ifNil: [ ^ PackageInfo named:( self getClass ifNil: [self getSystemCategory] ifNotNilDo: [:c | c category copyUpTo: $-])]. ^ PackageOrganizer default packageOfMethod: (MethodReference class: self getClass selector: self getSelector) ifNone: [PackageInfo named: (self getClass category copyUpTo: $-)] ! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 5/31/2004 22:10'! getPackageForCategory "answers a packageinfo for the current class category" ^ PackageInfo named: self getClass theNonMetaClass category! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 5/31/2004 22:10'! getPackageForCategoryName "answers a packageinfo for the current class category" ^ self getPackageForCategory packageName! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 5/31/2004 22:10'! getPackageName ^ self getPackage packageName! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 1/9/2006 19:27'! getPackageProvider | provs classes | provs := ServiceProvider registeredProviders. classes := self getPackage classes. ^ classes detect: [:e | provs includes: e] ifNone: [ServiceProvider newProviderFor: self getPackageName]! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 8/27/2005 15:52'! getSelection self getBrowser selectedInterval ifEmpty: [^super getSelection]. ^ self getBrowser selectedInterval! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 1/9/2006 11:58'! getSelector | s | s := self getBrowser selectedMessageName. ^ s ifNil: [super getSelector] ifNotNil: [s]! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 10/11/2005 15:06'! getSelectorCollection self caption: 'enter selector list'. ^ self getSymbolCollection ! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 8/27/2005 15:51'! getSelectorName ^ self getBrowser selectedMessageName! ! !BrowserRequestor methodsFor: 'requests' stamp: 'rr 8/27/2005 15:51'! getSystemCategory ^ self getBrowser selectedSystemCategoryName ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BrowserRequestor class instanceVariableNames: ''! GenericUrl subclass: #BrowserUrl instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Network-Url'! !BrowserUrl commentStamp: '' prior: 0! URLs that instruct a browser to do something.! !BrowserUrl methodsFor: 'downloading' stamp: 'ls 8/4/1998 20:42'! hasContents ^true! ! WidgetStub subclass: #ButtonStub instanceVariableNames: 'enabled' classVariableNames: '' poolDictionaries: '' category: 'ToolBuilder-SUnit'! !ButtonStub methodsFor: 'events' stamp: 'cwp 4/22/2005 22:01'! eventAccessors ^ #(label color state enabled)! ! !ButtonStub methodsFor: 'simulating' stamp: 'stephaneducasse 2/3/2006 22:32'! click | action | action := spec action. action isSymbol ifTrue: [self model perform: action] ifFalse: [action value]! ! !ButtonStub methodsFor: 'simulating' stamp: 'cwp 4/22/2005 22:44'! color ^ self model perform: spec color! ! !ButtonStub methodsFor: 'simulating' stamp: 'cwp 7/14/2006 11:09'! isEnabled enabled ifNil: [enabled := spec model perform: spec enabled]. ^ enabled! ! ArrayedCollection variableByteSubclass: #ByteArray instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Collections-Arrayed'! !ByteArray commentStamp: '' prior: 0! I represent an ArrayedCollection whose elements are integers between 0 and 255. ! !ByteArray methodsFor: '*Network-Kernel' stamp: 'mir 6/17/2007 23:12'! asSocketAddress ^SocketAddress fromOldByteAddress: self! ! !ByteArray methodsFor: '*system-hashing-core' stamp: 'rww 4/11/2004 14:48'! asByteArrayOfSize: size " '34523' asByteArray asByteArrayOfSize: 100. ((( | repeats bytes | repeats := 1000000. bytes := '123456789123456789123456789123456789123456789123456789' asByteArray. [repeats timesRepeat: (bytes asByteArrayOfSize: 1024) ] timeToRun. )))" | bytes | size < self size ifTrue: [^ self error: 'bytearray bigger than ', size asString]. bytes := self asByteArray. ^ (ByteArray new: (size - bytes size)), bytes ! ! !ByteArray methodsFor: '*system-hashing-core' stamp: 'StephaneDucasse 10/17/2009 17:15'! bitXor: aByteArray | answer | answer := self copy. 1 to: (self size min: aByteArray size) do: [ :each | answer at: each put: ((self at: each) bitXor: (aByteArray at: each)) ]. ^ answer! ! !ByteArray methodsFor: '*system-hashing-core' stamp: 'cmm 2/21/2006 00:05'! destroy 1 to: self size do: [ : x | self at: x put: 0 ]! ! !ByteArray methodsFor: 'accessing' stamp: 'ar 4/12/2005 17:35'! asWideString ^ WideString fromByteArray: self. ! ! !ByteArray methodsFor: 'accessing' stamp: 'sma 4/22/2000 17:47'! atAllPut: value "Fill the receiver with the given value" super atAllPut: value! ! !ByteArray methodsFor: 'accessing' stamp: 'ar 12/5/1998 14:52'! byteAt: index ^self at: index! ! !ByteArray methodsFor: 'accessing' stamp: 'ar 12/5/1998 14:52'! byteAt: index put: value ^self at: index put: value! ! !ByteArray methodsFor: 'accessing' stamp: 'ar 3/3/2001 16:17'! byteSize ^self size! ! !ByteArray methodsFor: 'accessing' stamp: 'tk 3/13/2000 14:46'! bytesPerElement "Number of bytes in each item. This multiplied by (self size)*8 gives the number of bits stored." ^ 1! ! !ByteArray methodsFor: 'comparing' stamp: 'SqR 8/13/2002 10:52'! hash "#hash is implemented, because #= is implemented" ^self class hashBytes: self startingWith: self species hash! ! !ByteArray methodsFor: 'converting' stamp: 'sma 5/12/2000 17:35'! asByteArray ^ self! ! !ByteArray methodsFor: 'converting'! asString "Convert to a String with Characters for each byte. Fast code uses primitive that avoids character conversion" ^ (String new: self size) replaceFrom: 1 to: self size with: self! ! !ByteArray methodsFor: 'converting' stamp: 'MarianoMartinezPeck 8/16/2009 17:21'! hex | result stream | result := String new: self size * 2. stream := result writeStream. 1 to: self size do: [ :ix | |each| each := self at: ix. stream nextPut: ('0123456789ABCDEF' at: each // 16 + 1); nextPut: ('0123456789ABCDEF' at: each \\ 16 + 1)]. ^ result! ! !ByteArray methodsFor: 'platform independent access' stamp: 'jmb 12/3/2004 14:54'! doubleAt: index bigEndian: bool "Return a 64 bit float starting from the given byte index" | w1 w2 dbl | w1 := self unsignedLongAt: index bigEndian: bool. w2 := self unsignedLongAt: index + 4 bigEndian: bool. dbl := Float new: 2. bool ifTrue: [dbl basicAt: 1 put: w1. dbl basicAt: 2 put: w2] ifFalse: [dbl basicAt: 1 put: w2. dbl basicAt: 2 put: w1]. ^ dbl! ! !ByteArray methodsFor: 'platform independent access' stamp: 'jmb 12/3/2004 14:54'! doubleAt: index put: value bigEndian: bool "Store a 64 bit float starting from the given byte index" | w1 w2 | bool ifTrue: [w1 := value basicAt: 1. w2 := value basicAt: 2] ifFalse: [w1 := value basicAt: 2. w2 := value basicAt: 1]. self unsignedLongAt: index put: w1 bigEndian: bool. self unsignedLongAt: index + 4 put: w2 bigEndian: bool. ^ value! ! !ByteArray methodsFor: 'platform independent access' stamp: 'SergeStinckwich 2/19/2009 13:33'! floatAt: index bigEndian: boolean ^ Float fromIEEE32Bit: (self unsignedLongAt: index bigEndian: boolean)! ! !ByteArray methodsFor: 'platform independent access' stamp: 'ar 11/1/1998 20:44'! longAt: index bigEndian: aBool "Return a 32bit integer quantity starting from the given byte index" | b0 b1 b2 w h | aBool ifTrue:[ b0 := self at: index. b1 := self at: index+1. b2 := self at: index+2. w := self at: index+3. ] ifFalse:[ w := self at: index. b2 := self at: index+1. b1 := self at: index+2. b0 := self at: index+3. ]. "Minimize LargeInteger arithmetic" h := ((b0 bitAnd: 16r7F) - (b0 bitAnd: 16r80) bitShift: 8) + b1. b2 = 0 ifFalse:[w := (b2 bitShift: 8) + w]. h = 0 ifFalse:[w := (h bitShift: 16) + w]. ^w! ! !ByteArray methodsFor: 'platform independent access' stamp: 'ar 8/2/2003 19:29'! longAt: index put: value bigEndian: aBool "Return a 32bit integer quantity starting from the given byte index" | b0 b1 b2 b3 | b0 := value bitShift: -24. b0 := (b0 bitAnd: 16r7F) - (b0 bitAnd: 16r80). b0 < 0 ifTrue:[b0 := 256 + b0]. b1 := (value bitShift: -16) bitAnd: 255. b2 := (value bitShift: -8) bitAnd: 255. b3 := value bitAnd: 255. aBool ifTrue:[ self at: index put: b0. self at: index+1 put: b1. self at: index+2 put: b2. self at: index+3 put: b3. ] ifFalse:[ self at: index put: b3. self at: index+1 put: b2. self at: index+2 put: b1. self at: index+3 put: b0. ]. ^value! ! !ByteArray methodsFor: 'platform independent access' stamp: 'ar 11/1/1998 20:57'! shortAt: index bigEndian: aBool "Return a 16 bit integer quantity starting from the given byte index" | uShort | uShort := self unsignedShortAt: index bigEndian: aBool. ^(uShort bitAnd: 16r7FFF) - (uShort bitAnd: 16r8000)! ! !ByteArray methodsFor: 'platform independent access' stamp: 'ar 11/3/1998 14:20'! shortAt: index put: value bigEndian: aBool "Store a 16 bit integer quantity starting from the given byte index" self unsignedShortAt: index put: (value bitAnd: 16r7FFF) - (value bitAnd: -16r8000) bigEndian: aBool. ^value! ! !ByteArray methodsFor: 'platform independent access' stamp: 'ar 11/1/1998 20:49'! unsignedLongAt: index bigEndian: aBool "Return a 32bit unsigned integer quantity starting from the given byte index" | b0 b1 b2 w | aBool ifTrue:[ b0 := self at: index. b1 := self at: index+1. b2 := self at: index+2. w := self at: index+3. ] ifFalse:[ w := self at: index. b2 := self at: index+1. b1 := self at: index+2. b0 := self at: index+3. ]. "Minimize LargeInteger arithmetic" b2 = 0 ifFalse:[w := (b2 bitShift: 8) + w]. b1 = 0 ifFalse:[w := (b1 bitShift: 16) + w]. b0 = 0 ifFalse:[w := (b0 bitShift: 24) + w]. ^w! ! !ByteArray methodsFor: 'platform independent access' stamp: 'ar 11/1/1998 20:49'! unsignedLongAt: index put: value bigEndian: aBool "Store a 32bit unsigned integer quantity starting from the given byte index" | b0 b1 b2 b3 | b0 := value bitShift: -24. b1 := (value bitShift: -16) bitAnd: 255. b2 := (value bitShift: -8) bitAnd: 255. b3 := value bitAnd: 255. aBool ifTrue:[ self at: index put: b0. self at: index+1 put: b1. self at: index+2 put: b2. self at: index+3 put: b3. ] ifFalse:[ self at: index put: b3. self at: index+1 put: b2. self at: index+2 put: b1. self at: index+3 put: b0. ]. ^value! ! !ByteArray methodsFor: 'platform independent access' stamp: 'ar 11/1/1998 20:51'! unsignedShortAt: index bigEndian: aBool "Return a 16 bit unsigned integer quantity starting from the given byte index" ^aBool ifTrue:[((self at: index) bitShift: 8) + (self at: index+1)] ifFalse:[((self at: index+1) bitShift: 8) + (self at: index)].! ! !ByteArray methodsFor: 'platform independent access' stamp: 'ar 11/1/1998 20:53'! unsignedShortAt: index put: value bigEndian: aBool "Store a 16 bit unsigned integer quantity starting from the given byte index" aBool ifTrue:[ self at: index put: (value bitShift: -8). self at: index+1 put: (value bitAnd: 255). ] ifFalse:[ self at: index+1 put: (value bitShift: -8). self at: index put: (value bitAnd: 255). ]. ^value! ! !ByteArray methodsFor: 'printing' stamp: 'stephane.ducasse 2/1/2009 22:39'! printOn: aStream aStream nextPutAll: '#['. self do: [ :each | each printOn: aStream ] separatedBy: [ aStream nextPut: $ ]. aStream nextPut: $]! ! !ByteArray methodsFor: 'printing' stamp: 'stephane.ducasse 2/1/2009 22:40'! storeOn: aStream aStream nextPutAll: '#['. self do: [ :each | each storeOn: aStream ] separatedBy: [ aStream nextPut: $ ]. aStream nextPut: $]! ! !ByteArray methodsFor: 'testing' stamp: 'stephane.ducasse 2/1/2009 23:10'! isLiteral "so that #(1 #[1 2 3] 5) prints itself" ^ true! ! !ByteArray methodsFor: 'zip archive' stamp: 'nk 8/21/2004 15:23'! lastIndexOfPKSignature: aSignature "Answer the last index in me where aSignature (4 bytes long) occurs, or 0 if not found" | a b c d | a := aSignature first. b := aSignature second. c := aSignature third. d := aSignature fourth. (self size - 3) to: 1 by: -1 do: [ :i | (((self at: i) = a) and: [ ((self at: i + 1) = b) and: [ ((self at: i + 2) = c) and: [ ((self at: i + 3) = d) ]]]) ifTrue: [ ^i ] ]. ^0! ! !ByteArray methodsFor: 'private' stamp: 'ar 1/28/2000 17:45'! asByteArrayPointer "Return a ByteArray describing a pointer to the contents of the receiver." ^self shouldNotImplement! ! !ByteArray methodsFor: 'private'! defaultElement ^0! ! !ByteArray methodsFor: 'private'! replaceFrom: start to: stop with: replacement startingAt: repStart "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive." super replaceFrom: start to: stop with: replacement startingAt: repStart! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ByteArray class instanceVariableNames: ''! !ByteArray class methodsFor: 'byte based hash' stamp: 'SqR 8/21/2002 16:21'! hashBytes: aByteArray startingWith: speciesHash "Answer the hash of a byte-indexed collection, using speciesHash as the initial value. See SmallInteger>>hashMultiply. The primitive should be renamed at a suitable point in the future" | byteArraySize hash low | self var: #aHash declareC: 'int speciesHash'. self var: #aByteArray declareC: 'unsigned char *aByteArray'. byteArraySize := aByteArray size. hash := speciesHash bitAnd: 16rFFFFFFF. 1 to: byteArraySize do: [:pos | hash := hash + (aByteArray basicAt: pos). "Begin hashMultiply" low := hash bitAnd: 16383. hash := (16r260D * low + ((16r260D * (hash bitShift: -14) + (16r0065 * low) bitAnd: 16383) * 16384)) bitAnd: 16r0FFFFFFF. ]. ^ hash! ! TestCase subclass: #ByteArrayBugz instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Bugs'! !ByteArrayBugz methodsFor: 'as yet unclassified' stamp: 'ar 8/2/2003 19:28'! testByteArrayLongAt | ba value | ba := ByteArray new: 4. value := -1. self shouldnt:[ba longAt: 1 put: value bigEndian: true] raise: Error. self assert: (ba longAt: 1 bigEndian: true) = value. self shouldnt:[ba longAt: 1 put: value bigEndian: false] raise: Error. self assert: (ba longAt: 1 bigEndian: false) = value. ! ! TestCase subclass: #ByteArrayTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Arrayed'! !ByteArrayTest methodsFor: 'as yet unclassified' stamp: 'SergeStinckwich 2/19/2009 13:31'! testFourthByteArraysReturnTheCorrectValues self assert: [(#(16r3F 16r80 0 0) asByteArray floatAt:1 bigEndian: true) = 1.0]. self assert: [(#(16rC0 0 0 0) asByteArray floatAt:1 bigEndian: true) = -2.0]. ! ! String variableByteSubclass: #ByteString instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Collections-Strings'! !ByteString commentStamp: '' prior: 0! This class represents the array of 8 bit wide characters. ! !ByteString methodsFor: 'accessing' stamp: 'yo 8/26/2002 20:33'! at: index "Primitive. Answer the Character stored in the field of the receiver indexed by the argument. Fail if the index argument is not an Integer or is out of bounds. Essential. See Object documentation whatIsAPrimitive." ^ Character value: (super at: index)! ! !ByteString methodsFor: 'accessing' stamp: 'ar 4/12/2005 17:33'! at: index put: aCharacter "Primitive. Store the Character in the field of the receiver indicated by the index. Fail if the index is not an Integer or is out of bounds, or if the argument is not a Character. Essential. See Object documentation whatIsAPrimitive." aCharacter isCharacter ifFalse:[^self errorImproperStore]. aCharacter isOctetCharacter ifFalse:[ "Convert to WideString" self becomeForward: (WideString from: self). ^self at: index put: aCharacter. ]. index isInteger ifTrue: [self errorSubscriptBounds: index] ifFalse: [self errorNonIntegerIndex]! ! !ByteString methodsFor: 'accessing' stamp: 'ar 12/27/1999 13:44'! byteAt: index ^(self at: index) asciiValue! ! !ByteString methodsFor: 'accessing' stamp: 'ar 12/27/1999 13:44'! byteAt: index put: value self at: index put: value asCharacter. ^value! ! !ByteString methodsFor: 'accessing' stamp: 'ar 3/3/2001 16:17'! byteSize ^self size! ! !ByteString methodsFor: 'accessing' stamp: 'ar 4/12/2005 17:33'! replaceFrom: start to: stop with: replacement startingAt: repStart "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive." replacement class == WideString ifTrue: [ self becomeForward: (WideString from: self). ]. super replaceFrom: start to: stop with: replacement startingAt: repStart. ! ! !ByteString methodsFor: 'comparing' stamp: 'nice 3/23/2007 00:50'! beginsWith: prefix "Answer whether the receiver begins with the given prefix string. The comparison is case-sensitive." "IMPLEMENTATION NOTE: following algorithm is optimized in primitive only in case self and prefix are bytes like. Otherwise, if self is wide, then super outperforms, Otherwise, if prefix is wide, primitive is not correct" prefix class isBytes ifFalse: [^super beginsWith: prefix]. self size < prefix size ifTrue: [^ false]. ^ (self findSubstring: prefix in: self startingAt: 1 matchTable: CaseSensitiveOrder) = 1 ! ! !ByteString methodsFor: 'comparing' stamp: 'JMM 10/30/2006 15:58'! findSubstring: key in: body startingAt: start matchTable: matchTable key isWideString ifTrue: [^super findSubstring: key in: body startingAt: start matchTable: matchTable]. ^self findSubstringViaPrimitive: key in: body startingAt: start matchTable: matchTable! ! !ByteString methodsFor: 'comparing' stamp: 'JMM 10/30/2006 15:57'! findSubstringViaPrimitive: key in: body startingAt: start matchTable: matchTable "Answer the index in the string body at which the substring key first occurs, at or beyond start. The match is determined using matchTable, which can be used to effect, eg, case-insensitive matches. If no match is found, zero will be returned. The algorithm below is not optimum -- it is intended to be translated to C which will go so fast that it wont matter." | index | self var: #key declareC: 'unsigned char *key'. self var: #body declareC: 'unsigned char *body'. self var: #matchTable declareC: 'unsigned char *matchTable'. key size = 0 ifTrue: [^ 0]. start to: body size - key size + 1 do: [:startIndex | index := 1. [(matchTable at: (body at: startIndex+index-1) asciiValue + 1) = (matchTable at: (key at: index) asciiValue + 1)] whileTrue: [index = key size ifTrue: [^ startIndex]. index := index+1]]. ^ 0 " ' ' findSubstring: 'abc' in: 'abcdefabcd' startingAt: 1 matchTable: CaseSensitiveOrder 1 ' ' findSubstring: 'abc' in: 'abcdefabcd' startingAt: 2 matchTable: CaseSensitiveOrder 7 ' ' findSubstring: 'abc' in: 'abcdefabcd' startingAt: 8 matchTable: CaseSensitiveOrder 0 ' ' findSubstring: 'abc' in: 'abcdefABcd' startingAt: 2 matchTable: CaseSensitiveOrder 0 ' ' findSubstring: 'abc' in: 'abcdefABcd' startingAt: 2 matchTable: CaseInsensitiveOrder 7 "! ! !ByteString methodsFor: 'converting' stamp: 'ar 4/10/2005 17:20'! asByteArray | ba sz | sz := self byteSize. ba := ByteArray new: sz. ba replaceFrom: 1 to: sz with: self startingAt: 1. ^ba! ! !ByteString methodsFor: 'converting' stamp: 'yo 8/28/2002 16:52'! asOctetString ^ self. ! ! !ByteString methodsFor: 'converting' stamp: 'yo 11/11/2002 12:20'! convertFromCompoundText | readStream writeStream converter | readStream := self readStream. writeStream := String new writeStream. converter := CompoundTextConverter new. converter ifNil: [^ self]. [readStream atEnd] whileFalse: [ writeStream nextPut: (converter nextFromStream: readStream)]. ^ writeStream contents ! ! !ByteString methodsFor: 'converting' stamp: 'mir 7/20/2004 15:50'! convertFromSystemString | readStream writeStream converter | readStream := self readStream. writeStream := String new writeStream. converter := LanguageEnvironment defaultSystemConverter. converter ifNil: [^ self]. [readStream atEnd] whileFalse: [ writeStream nextPut: (converter nextFromStream: readStream)]. ^ writeStream contents ! ! !ByteString methodsFor: 'testing' stamp: 'ar 4/10/2005 18:04'! isByteString "Answer whether the receiver is a ByteString" ^true! ! !ByteString methodsFor: 'testing' stamp: 'ar 4/10/2005 17:28'! isOctetString "Answer whether the receiver can be represented as a byte string. This is different from asking whether the receiver *is* a ByteString (i.e., #isByteString)" ^ true. ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ByteString class instanceVariableNames: ''! !ByteString class methodsFor: 'primitives' stamp: 'yo 12/15/2005 13:44'! compare: string1 with: string2 collated: order "Return 1, 2 or 3, if string1 is <, =, or > string2, with the collating order of characters given by the order array." | len1 len2 c1 c2 | self var: #string1 declareC: 'unsigned char *string1'. self var: #string2 declareC: 'unsigned char *string2'. self var: #order declareC: 'unsigned char *order'. len1 := string1 size. len2 := string2 size. 1 to: (len1 min: len2) do: [:i | c1 := order at: (string1 basicAt: i) + 1. c2 := order at: (string2 basicAt: i) + 1. c1 = c2 ifFalse: [c1 < c2 ifTrue: [^ 1] ifFalse: [^ 3]]]. len1 = len2 ifTrue: [^ 2]. len1 < len2 ifTrue: [^ 1] ifFalse: [^ 3]. ! ! !ByteString class methodsFor: 'primitives' stamp: 'ar 2/3/2001 16:12'! findFirstInString: aString inSet: inclusionMap startingAt: start | i stringSize | self var: #aString declareC: 'unsigned char *aString'. self var: #inclusionMap declareC: 'char *inclusionMap'. inclusionMap size ~= 256 ifTrue: [ ^0 ]. i := start. stringSize := aString size. [ i <= stringSize and: [ (inclusionMap at: (aString at: i) asciiValue+1) = 0 ] ] whileTrue: [ i := i + 1 ]. i > stringSize ifTrue: [ ^0 ]. ^i! ! !ByteString class methodsFor: 'primitives' stamp: 'ar 2/3/2001 16:13'! indexOfAscii: anInteger inString: aString startingAt: start | stringSize | self var: #aCharacter declareC: 'int anInteger'. self var: #aString declareC: 'unsigned char *aString'. stringSize := aString size. start to: stringSize do: [:pos | (aString at: pos) asciiValue = anInteger ifTrue: [^ pos]]. ^ 0 ! ! !ByteString class methodsFor: 'primitives' stamp: 'ar 9/28/2001 04:35'! stringHash: aString initialHash: speciesHash | stringSize hash low | self var: #aHash declareC: 'int speciesHash'. self var: #aString declareC: 'unsigned char *aString'. stringSize := aString size. hash := speciesHash bitAnd: 16rFFFFFFF. 1 to: stringSize do: [:pos | hash := hash + (aString at: pos) asciiValue. "Begin hashMultiply" low := hash bitAnd: 16383. hash := (16r260D * low + ((16r260D * (hash bitShift: -14) + (16r0065 * low) bitAnd: 16383) * 16384)) bitAnd: 16r0FFFFFFF. ]. ^ hash! ! !ByteString class methodsFor: 'primitives' stamp: 'ar 2/3/2001 16:12'! translate: aString from: start to: stop table: table "translate the characters in the string by the given table, in place" self var: #table declareC: 'unsigned char *table'. self var: #aString declareC: 'unsigned char *aString'. start to: stop do: [ :i | aString at: i put: (table at: (aString at: i) asciiValue+1) ]! ! Symbol variableByteSubclass: #ByteSymbol instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Collections-Strings'! !ByteSymbol commentStamp: '' prior: 0! This class represents the symbols containing 8bit characters.! !ByteSymbol methodsFor: 'accessing' stamp: 'ar 4/10/2005 22:10'! at: index "Primitive. Answer the Character stored in the field of the receiver indexed by the argument. Fail if the index argument is not an Integer or is out of bounds. Essential. See Object documentation whatIsAPrimitive." ^ Character value: (super at: index)! ! !ByteSymbol methodsFor: 'accessing' stamp: 'ar 4/10/2005 22:10'! byteAt: index ^(self at: index) asciiValue! ! !ByteSymbol methodsFor: 'accessing' stamp: 'ar 4/10/2005 22:10'! byteAt: anInteger put: anObject "You cannot modify the receiver." self errorNoModification! ! !ByteSymbol methodsFor: 'accessing' stamp: 'ar 4/10/2005 22:11'! byteSize ^self size! ! !ByteSymbol methodsFor: 'accessing' stamp: 'ar 4/12/2005 17:51'! species "Answer the preferred class for reconstructing the receiver." ^ByteString ! ! !ByteSymbol methodsFor: 'comparing' stamp: 'nice 3/23/2007 00:50'! beginsWith: prefix "Answer whether the receiver begins with the given prefix string. The comparison is case-sensitive." "IMPLEMENTATION NOTE: following algorithm is optimized in primitive only in case self and prefix are bytes like. Otherwise, if self is wide, then super outperforms, Otherwise, if prefix is wide, primitive is not correct" prefix class isBytes ifFalse: [^super beginsWith: prefix]. self size < prefix size ifTrue: [^ false]. ^ (self findSubstring: prefix in: self startingAt: 1 matchTable: CaseSensitiveOrder) = 1 ! ! !ByteSymbol methodsFor: 'comparing' stamp: 'ar 4/10/2005 22:14'! findSubstring: key in: body startingAt: start matchTable: matchTable "Answer the index in the string body at which the substring key first occurs, at or beyond start. The match is determined using matchTable, which can be used to effect, eg, case-insensitive matches. If no match is found, zero will be returned." ^super findSubstring: key in: body startingAt: start matchTable: matchTable! ! !ByteSymbol methodsFor: 'converting' stamp: 'ar 4/10/2005 22:12'! asByteArray | ba sz | sz := self byteSize. ba := ByteArray new: sz. ba replaceFrom: 1 to: sz with: self startingAt: 1. ^ba! ! !ByteSymbol methodsFor: 'converting' stamp: 'ar 4/10/2005 22:12'! asOctetString ^ self! ! !ByteSymbol methodsFor: 'testing' stamp: 'ar 4/10/2005 22:14'! isByteString "Answer whether the receiver is a ByteString" ^true! ! !ByteSymbol methodsFor: 'testing' stamp: 'ar 4/10/2005 22:14'! isOctetString "Answer whether the receiver can be represented as a byte string. This is different from asking whether the receiver *is* a ByteString (i.e., #isByteString)" ^ true. ! ! !ByteSymbol methodsFor: 'private' stamp: 'ar 4/11/2005 00:08'! pvtAt: index put: aCharacter "Primitive. Store the Character in the field of the receiver indicated by the index. Fail if the index is not an Integer or is out of bounds, or if the argument is not a Character. Essential. See Object documentation whatIsAPrimitive." aCharacter isCharacter ifFalse:[^self errorImproperStore]. index isInteger ifTrue: [self errorSubscriptBounds: index] ifFalse: [self errorNonIntegerIndex]! ! !ByteSymbol methodsFor: 'private' stamp: 'ar 4/10/2005 23:02'! string: aString 1 to: aString size do: [:j | self pvtAt: j put: (aString at: j)]. ^self! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ByteSymbol class instanceVariableNames: ''! !ByteSymbol class methodsFor: 'primitives' stamp: 'ar 8/18/2005 13:46'! findFirstInString: aString inSet: inclusionMap startingAt: start ^ByteString findFirstInString: aString inSet: inclusionMap startingAt: start! ! !ByteSymbol class methodsFor: 'primitives' stamp: 'ar 8/18/2005 13:46'! indexOfAscii: anInteger inString: aString startingAt: start ^ByteString indexOfAscii: anInteger inString: aString startingAt: start! ! !ByteSymbol class methodsFor: 'primitives' stamp: 'ar 8/18/2005 13:46'! stringHash: aString initialHash: speciesHash ^ByteString stringHash: aString initialHash: speciesHash! ! !ByteSymbol class methodsFor: 'primitives' stamp: 'ar 8/18/2005 13:47'! translate: aString from: start to: stop table: table ^ByteString translate: aString from: start to: stop table: table! ! TextConverter subclass: #ByteTextConverter instanceVariableNames: '' classVariableNames: '' poolDictionaries: 'EventSensorConstants' category: 'Multilingual-TextConversion'! !ByteTextConverter commentStamp: 'michael.rueger 1/27/2009 18:00' prior: 0! A ByteTextConverter is the abstract class for text converters on single byte encodings.! !ByteTextConverter methodsFor: 'conversion' stamp: 'michael.rueger 2/5/2009 14:11'! byteToUnicode: char "Map from my byte based encoding to unicode. Due to the leading char encoding this is not strictly true, but hopefully at some point we can get rid of the leading char overhead." | value | value := char charCode. value < 128 ifTrue: [^ char]. value > 255 ifTrue: [^ char]. ^self class byteToUnicodeTable at: (value - 128 + 1)! ! !ByteTextConverter methodsFor: 'conversion' stamp: 'michael.rueger 2/5/2009 14:11'! nextFromStream: aStream "Read the next byte (we are only dealing with byte based encodings here) character from aStream and return the result converted to unicode." | byteOrChar | byteOrChar := aStream basicNext. aStream isBinary ifTrue: [^byteOrChar]. ^byteOrChar ifNotNil: [self byteToUnicode: byteOrChar]! ! !ByteTextConverter methodsFor: 'conversion' stamp: 'michael.rueger 2/5/2009 14:10'! nextPut: unicodeCharacter toStream: aStream "Write the unicode character to aStream." aStream isBinary ifTrue: [aStream basicNextPut: unicodeCharacter charCode] ifFalse: [aStream basicNextPut: (self unicodeToByte: unicodeCharacter)]! ! !ByteTextConverter methodsFor: 'conversion' stamp: 'michael.rueger 2/5/2009 14:10'! unicodeToByte: unicodeChar ^unicodeChar charCode < 128 ifTrue: [unicodeChar] ifFalse: [self class unicodeToByteTable at: unicodeChar charCode ifAbsent: [0 asCharacter]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ByteTextConverter class instanceVariableNames: 'byteToUnicode unicodeToByte'! !ByteTextConverter class methodsFor: 'accessing' stamp: 'michael.rueger 2/5/2009 14:10'! byteToUnicodeTable "Return the table mapping from my byte based encoding to unicode" ^byteToUnicode! ! !ByteTextConverter class methodsFor: 'accessing' stamp: 'michael.rueger 1/30/2009 11:01'! languageEnvironment self subclassResponsibility! ! !ByteTextConverter class methodsFor: 'accessing' stamp: 'michael.rueger 2/5/2009 14:10'! unicodeToByteTable "Return the table mapping from unicode to my byte based encoding" ^unicodeToByte! ! !ByteTextConverter class methodsFor: 'class initialization' stamp: 'michael.rueger 2/5/2009 14:06'! byteToUnicodeSpec "Sepcify a table mapping the entries 0x80 to 0xFF to their unicode counterparts by returning a 128 element array.. The entries 0x00 to 0x7F map to identical values so we don't need to specify them." self subclassResponsibility! ! !ByteTextConverter class methodsFor: 'class initialization' stamp: 'michael.rueger 1/27/2009 18:40'! initialize "ByteTextConverter initialize" self allSubclassesDo: [:subclass | subclass initializeTables]! ! !ByteTextConverter class methodsFor: 'class initialization' stamp: 'nice 7/26/2009 22:37'! initializeTables "Initialize the mappings to and from unicode." | byteToUnicodeSpec leadingChar | byteToUnicodeSpec := self byteToUnicodeSpec. leadingChar := self languageEnvironment leadingChar. byteToUnicode := byteToUnicodeSpec collect: [:charValue | Character leadingChar: leadingChar code: charValue]. unicodeToByte := Dictionary new. "Mind the offset because first 128 characters are not stored into byteToUnicodeSpec" byteToUnicodeSpec keysAndValuesDo: [:byteEntry :unicodeEntry | unicodeToByte at: unicodeEntry put: (127 + byteEntry) asCharacter]! ! TestCase subclass: #ByteTextConverterTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'MultilingualTests-TextConversion'! !ByteTextConverterTest methodsFor: 'testing' stamp: 'nice 7/26/2009 22:44'! testConversionToFrom "Non regresson test for http://code.google.com/p/pharo/issues/detail?id=986" self assert: (('äöü' convertToEncoding: 'mac-roman') convertFromEncoding: 'mac-roman') = 'äöü'! ! MethodNode subclass: #BytecodeAgnosticMethodNode instanceVariableNames: 'locationCounter localsPool' classVariableNames: '' poolDictionaries: '' category: 'Compiler-ParseNodes'! !BytecodeAgnosticMethodNode commentStamp: '' prior: 0! I am a version of MethodNode that is able to work with different BytecodeEncoders, and is hence able to generate methods using different bytecode sets.! ]style[(151)i! !BytecodeAgnosticMethodNode methodsFor: 'code generation (closures)' stamp: 'eem 5/29/2008 15:27'! addLocalsToPool: locals "" localsPool isNil ifTrue: [localsPool := IdentitySet new]. localsPool addAll: locals! ! !BytecodeAgnosticMethodNode methodsFor: 'code generation (closures)' stamp: 'eem 7/24/2008 10:04'! ensureClosureAnalysisDone block blockExtent ifNil: [temporaries := block analyseArguments: arguments temporaries: temporaries rootNode: self]! ! !BytecodeAgnosticMethodNode methodsFor: 'code generation (closures)' stamp: 'eem 5/20/2008 13:43'! locationCounter ^locationCounter! ! !BytecodeAgnosticMethodNode methodsFor: 'code generation (closures)' stamp: 'eem 5/30/2008 11:27'! noteBlockEntry: aBlock "Evaluate aBlock with the numbering for the block entry." locationCounter isNil ifTrue: [locationCounter := -1]. aBlock value: locationCounter + 1. locationCounter := locationCounter + 2! ! !BytecodeAgnosticMethodNode methodsFor: 'code generation (closures)' stamp: 'eem 6/2/2008 12:12'! noteBlockExit: aBlock "Evaluate aBlock with the numbering for the block exit." aBlock value: locationCounter + 1. locationCounter := locationCounter + 2! ! !BytecodeAgnosticMethodNode methodsFor: 'code generation (closures)' stamp: 'eem 5/29/2008 16:07'! referencedValuesWithinBlockExtent: anInterval ^(localsPool select: [:temp| temp isReferencedWithinBlockExtent: anInterval]) collect: [:temp| temp isRemote ifTrue: [temp remoteNode] ifFalse: [temp]]! ! !BytecodeAgnosticMethodNode methodsFor: 'code generation (new scheme)' stamp: 'eem 12/1/2008 13:48'! generate: trailer "The receiver is the root of a parse tree. Answer a CompiledMethod. The argument, trailer, is the reference to the source code that is stored with every CompiledMethod." | primErrNode blkSize nLits literals stack method | self generate: trailer ifQuick: [:m | m literalAt: 2 put: encoder associationForClass; properties: properties. ^m]. primErrNode := self primitiveErrorVariableName ifNotNil: [encoder fixTemp: self primitiveErrorVariableName]. encoder supportsClosureOpcodes ifTrue: [self ensureClosureAnalysisDone. encoder rootNode: self. "this is for BlockNode>>sizeCodeForClosureValue:"]. blkSize := (block sizeCodeForEvaluatedValue: encoder) + (primErrNode ifNil: [0] ifNotNil: [2 "We force store-long (129)"]). method := CompiledMethod newBytes: blkSize trailerBytes: trailer nArgs: arguments size nTemps: (encoder supportsClosureOpcodes ifTrue: [| locals | locals := arguments, temporaries, (primErrNode ifNil: [#()] ifNotNil: [{primErrNode}]). encoder noteBlockExtent: block blockExtent hasLocals: locals. locals size] ifFalse: [encoder maxTemp]) nStack: 0 nLits: (nLits := (literals := encoder allLiterals) size) primitive: primitive. nLits > 255 ifTrue: [^self error: 'Too many literals referenced']. 1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)]. encoder streamToMethod: method. stack := ParseStack new init. primErrNode ifNotNil: [primErrNode emitCodeForStore: stack encoder: encoder]. stack position: method numTemps. block emitCodeForEvaluatedValue: stack encoder: encoder. stack position ~= (method numTemps + 1) ifTrue: [^self error: 'Compiler stack discrepancy']. encoder methodStreamPosition ~= (method size - trailer size) ifTrue: [^self error: 'Compiler code size discrepancy']. method needsFrameSize: stack size - method numTemps. method properties: properties. ^method! ! !BytecodeAgnosticMethodNode methodsFor: 'debugger support' stamp: 'eem 6/5/2009 16:51'! blockExtentsToTempsMap "Answer a Dictionary of blockExtent to temp locations for the current method. This is used by the debugger to locate temp vars in contexts. A temp map entry is a pair of the temp's name and its index, where an index is either an integer for a normal temp or a pair of the index of the indirect temp vector containing the temp and the index of the temp in its indirect temp vector." ^encoder blockExtentsToTempsMap ifNil: [| methNode | methNode := encoder classEncoding parserClass new encoderClass: encoder class; parse: (sourceText ifNil: [self decompileString]) class: self methodClass. "As a side effect generate: creates data needed for the map." methNode generate: #(0 0 0 0). methNode encoder blockExtentsToTempsMap]! ! !BytecodeAgnosticMethodNode methodsFor: 'debugger support' stamp: 'eem 7/1/2009 13:45'! hasGeneratedMethod ^encoder hasGeneratedMethod! ! !BytecodeAgnosticMethodNode methodsFor: 'debugger support' stamp: 'eem 7/6/2009 09:46'! schematicTempNamesString "Answer the temp names for the current method node in a form that captures temp structure. The temps at each method and block scope level occur space-separated, with any indirect temps enclosed in parentheses. Each block level is enclosed in square brackets. e.g. 'method level temps (indirect temp)[block args and temps (indirect)]' This representation can be reconstituted into a blockExtentsToTempsMap by a CompiledMethod that has been copied with the schematicTempNamesString." encoder hasGeneratedMethod ifFalse: ["create the encoder's blockExtentsToLoals map, except if the method is quick in which case it has no temps." (self generate: #(0 0 0 0)) isQuick ifTrue: [^'']]. ^encoder schematicTempNamesString! ! !BytecodeAgnosticMethodNode methodsFor: 'printing' stamp: 'eem 7/24/2008 10:07'! printWithClosureAnalysisOn: aStream self ensureClosureAnalysisDone. super printWithClosureAnalysisOn: aStream! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! BytecodeAgnosticMethodNode class instanceVariableNames: ''! Encoder subclass: #BytecodeEncoder instanceVariableNames: 'stream position rootNode blockExtentsToLocals' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Kernel'! !BytecodeEncoder commentStamp: '' prior: 0! I am an abstract superclass for different bytecode set encoders. Subclasses inherit the literal management of Encoder and encapsulate the mapping of opcodes to specific bytecodes.! !BytecodeEncoder methodsFor: 'accessing' stamp: 'eem 5/29/2008 09:36'! methodNodeClass ^BytecodeAgnosticMethodNode! ! !BytecodeEncoder methodsFor: 'accessing' stamp: 'eem 5/14/2008 17:47'! methodStreamPosition ^stream position! ! !BytecodeEncoder methodsFor: 'accessing' stamp: 'eem 5/24/2008 11:56'! rootNode "^" ^rootNode! ! !BytecodeEncoder methodsFor: 'accessing' stamp: 'eem 5/24/2008 11:56'! rootNode: node "" rootNode := node! ! !BytecodeEncoder methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:52'! outOfRangeError: string index: index range: rangeStart to: rangeEnd "For now..." ^self error: thisContext sender method selector, ' ', string , ' index ', index printString , ' is out of range ', rangeStart printString, ' to ', rangeEnd printString! ! !BytecodeEncoder methodsFor: 'initialize-release' stamp: 'eem 7/24/2008 17:24'! streamToMethod: aCompiledMethod stream := WriteStream with: aCompiledMethod. stream position: aCompiledMethod initialPC - 1! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 7/27/2008 00:39'! nextPut: aByte "For sizing make the encoder its own stream and keep track of position with this version of nextPut:" position := position + 1! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 18:22'! sizeBranchPopFalse: distance ^self sizeOpcodeSelector: #genBranchPopFalse: withArguments: {distance}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 18:22'! sizeBranchPopTrue: distance ^self sizeOpcodeSelector: #genBranchPopTrue: withArguments: {distance}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:28'! sizeDup ^self sizeOpcodeSelector: #genDup withArguments: #()! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:40'! sizeJump: distance ^self sizeOpcodeSelector: #genJump: withArguments: {distance}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:40'! sizeJumpLong: distance ^self sizeOpcodeSelector: #genJumpLong: withArguments: {distance}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 7/27/2008 00:39'! sizeOpcodeSelector: genSelector withArguments: args stream := self. position := 0. self perform: genSelector withArguments: args. ^position! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:28'! sizePop ^self sizeOpcodeSelector: #genPop withArguments: #()! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/30/2008 16:46'! sizePushClosureCopyNumCopiedValues: numCopied numArgs: numArgs jumpSize: jumpSize ^self sizeOpcodeSelector: #genPushClosureCopyNumCopiedValues:numArgs:jumpSize: withArguments: {numCopied. numArgs. jumpSize}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/30/2008 16:36'! sizePushConsArray: numElements ^self sizeOpcodeSelector: #genPushConsArray: withArguments: {numElements}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 16:22'! sizePushInstVar: instVarIndex ^self sizeOpcodeSelector: #genPushInstVar: withArguments: {instVarIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 6/19/2008 08:54'! sizePushInstVarLong: instVarIndex ^self sizeOpcodeSelector: #genPushInstVarLong: withArguments: {instVarIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:43'! sizePushLiteral: literalIndex ^self sizeOpcodeSelector: #genPushLiteral: withArguments: {literalIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:43'! sizePushLiteralVar: literalIndex ^self sizeOpcodeSelector: #genPushLiteralVar: withArguments: {literalIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/24/2008 12:35'! sizePushNewArray: size ^self sizeOpcodeSelector: #genPushNewArray: withArguments: {size}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 16:21'! sizePushReceiver ^self sizeOpcodeSelector: #genPushReceiver withArguments: #()! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/24/2008 22:59'! sizePushRemoteTemp: tempIndex inVectorAt: tempVectorIndex ^self sizeOpcodeSelector: #genPushRemoteTemp:inVectorAt: withArguments: {tempIndex. tempVectorIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:37'! sizePushSpecialLiteral: specialLiteral ^self sizeOpcodeSelector: #genPushSpecialLiteral: withArguments: {specialLiteral}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:26'! sizePushTemp: tempIndex ^self sizeOpcodeSelector: #genPushTemp: withArguments: {tempIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:28'! sizePushThisContext ^self sizeOpcodeSelector: #genPushThisContext withArguments: #()! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/15/2008 09:07'! sizeReturnReceiver ^self sizeOpcodeSelector: #genReturnReceiver withArguments: #()! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:38'! sizeReturnSpecialLiteral: specialLiteral ^self sizeOpcodeSelector: #genReturnSpecialLiteral: withArguments: {specialLiteral}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:34'! sizeReturnTop ^self sizeOpcodeSelector: #genReturnTop withArguments: #()! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/15/2008 09:06'! sizeReturnTopToCaller ^self sizeOpcodeSelector: #genReturnTopToCaller withArguments: #()! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 16:11'! sizeSend: selectorLiteralIndex numArgs: nArgs ^self sizeOpcodeSelector: #genSend:numArgs: withArguments: {selectorLiteralIndex. nArgs}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 16:11'! sizeSendSuper: selectorLiteralIndex numArgs: nArgs ^self sizeOpcodeSelector: #genSendSuper:numArgs: withArguments: {selectorLiteralIndex. nArgs}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:44'! sizeStoreInstVar: instVarIndex ^self sizeOpcodeSelector: #genStoreInstVar: withArguments: {instVarIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 6/19/2008 08:54'! sizeStoreInstVarLong: instVarIndex ^self sizeOpcodeSelector: #genStoreInstVarLong: withArguments: {instVarIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:43'! sizeStoreLiteralVar: literalIndex ^self sizeOpcodeSelector: #genStoreLiteralVar: withArguments: {literalIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/15/2008 10:00'! sizeStorePopInstVar: instVarIndex ^self sizeOpcodeSelector: #genStorePopInstVar: withArguments: {instVarIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 6/19/2008 08:54'! sizeStorePopInstVarLong: instVarIndex ^self sizeOpcodeSelector: #genStorePopInstVarLong: withArguments: {instVarIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/15/2008 10:20'! sizeStorePopLiteralVar: literalIndex ^self sizeOpcodeSelector: #genStorePopLiteralVar: withArguments: {literalIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/24/2008 23:02'! sizeStorePopRemoteTemp: tempIndex inVectorAt: tempVectorIndex ^self sizeOpcodeSelector: #genStorePopRemoteTemp:inVectorAt: withArguments: {tempIndex. tempVectorIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:36'! sizeStorePopTemp: tempIndex ^self sizeOpcodeSelector: #genStorePopTemp: withArguments: {tempIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/24/2008 23:02'! sizeStoreRemoteTemp: tempIndex inVectorAt: tempVectorIndex ^self sizeOpcodeSelector: #genStoreRemoteTemp:inVectorAt: withArguments: {tempIndex. tempVectorIndex}! ! !BytecodeEncoder methodsFor: 'opcode sizing' stamp: 'eem 5/14/2008 17:45'! sizeStoreTemp: tempIndex ^self sizeOpcodeSelector: #genStoreTemp: withArguments: {tempIndex}! ! !BytecodeEncoder methodsFor: 'special literal encodings' stamp: 'eem 5/14/2008 16:02'! if: code isSpecialLiteralForPush: aBlock "If code is that of a special literal for push then evaluate aBlock with the special literal The special literals for push are nil true false -1 0 1 & 2 which have special encodings in the blue book bytecode set. Answer whether it was a special literal." ^(code between: LdTrue and: LdNil + 4) and: [aBlock value: (#(true false nil -1 0 1 2) at: code - LdSelf). true]! ! !BytecodeEncoder methodsFor: 'special literal encodings' stamp: 'eem 5/14/2008 17:49'! if: code isSpecialLiteralForReturn: aBlock "If code is that of a special literal for return then evaluate aBlock with the special literal. The special literals for return are nil true false which have special encodings in the blue book bytecode set. Answer whether it was a special literal." ^(code between: LdTrue and: LdNil) and: [aBlock value: (#(true false nil) at: code - LdSelf). true]! ! !BytecodeEncoder methodsFor: 'temps' stamp: 'eem 6/23/2008 10:55'! bindAndJuggle: name "This is used to insert a new temp and reorcder temps on editing. It doesn't really work for closure compilation since we have multiple locations for temps. Simply signal a reparse is necessary." ReparseAfterSourceEditing signal! ! !BytecodeEncoder methodsFor: 'temps' stamp: 'eem 9/8/2008 18:24'! bindBlockArg: name within: aBlockNode "Read the comment in the superclass's method. If we have closures we should check the argument count against the block, not the method. (Note that this isn't entirely adequate either since optimized blocks will slip through the cracks (their arguments (i.e. ifNotNil: [:expr|) are charged against their enclosing block, not themselves))." | nArgs | self supportsClosureOpcodes ifFalse: [^super bindBlockArg: name within: aBlockNode]. (nArgs := aBlockNode nArgsSlot) isNil ifTrue: [aBlockNode nArgsSlot: (nArgs := 0)]. nArgs >= 15 ifTrue: [^self notify: 'Too many arguments']. aBlockNode nArgsSlot: nArgs + 1. ^(self bindTemp: name) beBlockArg; nowHasDef; nowHasRef; yourself! ! !BytecodeEncoder methodsFor: 'temps' stamp: 'eem 5/30/2008 14:35'! bindBlockTemp: name within: aBlockNode "Read the comment in the superclass's bindBlockArg:within: method. If we have closures we should check the argument count against the block, not the method. (Note that this isn't entirely adequate either since optimized blocks will slip through the cracks (their arguments (i.e. ifNotNil: [:expr|) are charged against their enclosing block, not themselves))." | nArgs | self supportsClosureOpcodes ifFalse: [^super bindBlockTemp: name within: aBlockNode]. (nArgs := aBlockNode nArgsSlot) isNil ifTrue: [aBlockNode nArgsSlot: (nArgs := 0)]. nArgs >= (CompiledMethod fullFrameSize - 1) ifTrue: [^self notify: 'Too many temporaries']. aBlockNode nArgsSlot: nArgs + 1. ^self bindTemp: name! ! !BytecodeEncoder methodsFor: 'temps' stamp: 'eem 7/18/2008 07:33'! bindTemp: name "Declare a temporary; error not if a field or class variable or out-of-scope temp. Read the comment in Encoder>>bindBlockArg:within: and subclass implementations." self supportsClosureOpcodes ifFalse: [^super bindTemp: name]. scopeTable at: name ifPresent: [:node| "When non-interactive raise the error only if it is a duplicate" node isTemp ifTrue:[node scope >= 0 ifTrue: [^self notify:'Name is already defined']] ifFalse:[self warnAboutShadowed: name]]. ^self reallyBind: name! ! !BytecodeEncoder methodsFor: 'temps' stamp: 'eem 6/5/2009 16:51'! blockExtentsToTempsMap "Answer a Dictionary of blockExtent to temp locations for the current method. This is used by the debugger to locate temp vars in contexts. A temp map entry is a pair of the temp's name and its index, where an index is either an integer for a normal temp or a pair of the index of the indirect temp vector containing the temp and the index of the temp in its indirect temp vector." | blockExtentsToTempsMap | blockExtentsToLocals ifNil: [^nil]. blockExtentsToTempsMap := Dictionary new. blockExtentsToLocals keysAndValuesDo: [:blockExtent :locals| blockExtentsToTempsMap at: blockExtent put: (Array streamContents: [:stream| locals withIndexDo: [:local :index| local isIndirectTempVector ifTrue: [local remoteTemps withIndexDo: [:remoteLocal :innerIndex| stream nextPut: { remoteLocal key. { index. innerIndex } }]] ifFalse: [stream nextPut: { local key. index }]]])]. ^blockExtentsToTempsMap! ! !BytecodeEncoder methodsFor: 'temps' stamp: 'eem 6/3/2008 12:33'! noteBlockExtent: blockExtent hasLocals: tempNodes blockExtentsToLocals ifNil: [blockExtentsToLocals := Dictionary new]. blockExtentsToLocals at: blockExtent put: tempNodes asArray! ! !BytecodeEncoder methodsFor: 'testing' stamp: 'eem 6/29/2009 11:11'! hasGeneratedMethod ^blockExtentsToLocals notNil! ! !BytecodeEncoder methodsFor: 'testing' stamp: 'eem 7/17/2008 12:34'! supportsClosureOpcodes "Answer if the receiver supports the genPushNewArray:/genPushConsArray: genPushRemoteTemp:inVectorAt: genStoreRemoteTemp:inVectorAt: genStorePopRemoteTemp:inVectorAt: genPushClosureCopyCopiedValues:numArgs:jumpSize: opcodes" ^false! ! !BytecodeEncoder methodsFor: 'results' stamp: 'eem 6/5/2009 17:53'! printSchematicTempNamesOn: aStream blockExtents: blockExtents fromIndex: startIndex "Print the locals in the blockExtent startIndex, recursing to print any locals in nested blockExtents. Answer the index of the last blockExtent printed." | blockExtent subsequentIndex | blockExtent := blockExtents at: startIndex. blockExtent first > 0 ifTrue: [aStream nextPut: $[ ]. ((blockExtentsToLocals at: blockExtent) reject: [:local| local isRemote]) do: [:local| local isIndirectTempVector ifTrue: [aStream nextPut: $(. local remoteTemps do: [:remoteLocal| aStream nextPutAll: remoteLocal key] separatedBy: [aStream space]. aStream nextPut: $)] ifFalse: [aStream nextPutAll: local key]] separatedBy: [aStream space]. subsequentIndex := startIndex + 1. [subsequentIndex <= blockExtents size and: [(blockExtents at: subsequentIndex) last < blockExtent last]] whileTrue: [subsequentIndex := self printSchematicTempNamesOn: aStream blockExtents: blockExtents fromIndex: subsequentIndex]. blockExtent first > 0 ifTrue: [aStream nextPut: $] ]. ^subsequentIndex! ! !BytecodeEncoder methodsFor: 'results' stamp: 'eem 5/29/2009 09:11'! schematicTempNamesOn: aStream blockExtents: blockExtents fromIndex: startIndex "Print the locals in the blockExtent startIndex, recursing to print any locals in nested blockExtents. Answer the index of the last blockExtent printed." | blockExtent subsequentIndex | blockExtent := blockExtents at: startIndex. ((blockExtentsToLocals at: blockExtent) reject: [:local| local isRemote]) do: [:local| local isIndirectTempVector ifTrue: [local remoteTemps do: [:remoteLocal| aStream nextPut: remoteLocal key]] ifFalse: [aStream nextPut: local key]]. subsequentIndex := startIndex + 1. [subsequentIndex <= blockExtents size and: [(blockExtents at: subsequentIndex) last < blockExtent last]] whileTrue: [aStream nextPut: (Array streamContents: [:nestedTempStream| subsequentIndex := self schematicTempNamesOn: nestedTempStream blockExtents: blockExtents fromIndex: subsequentIndex])]. ^subsequentIndex! ! !BytecodeEncoder methodsFor: 'results' stamp: 'eem 6/29/2009 11:22'! schematicTempNamesString "Answer the temp names for the current method node in a form that captures temp structure. The temps at each method and block scope level occurr space-separated, with any indirect temps enclosed in parentheses. Each block level is enclosed in square brackets. e.g. 'method level temps (indirect temp)[block args and temps (indirect)]' This representation can be reconstituted into a blockExtentsToTempsMap by a CompiledMethod that has been copied with teh schematicTempNamesString." blockExtentsToLocals ifNil: [self error: 'blockExtentsToLocals uninitialized. method not yet generated?']. ^String streamContents: [:aStream| self printSchematicTempNamesOn: aStream blockExtents: (blockExtentsToLocals keys asSortedCollection: [:range1 :range2| range1 first <= range2 first]) fromIndex: 1]! ! EUCTextConverter subclass: #CNGBTextConverter instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Multilingual-TextConversion'! !CNGBTextConverter commentStamp: '' prior: 0! Text converter for Simplified Chinese variation of EUC. (Even though the name doesn't look so, it is what it is.)! !CNGBTextConverter methodsFor: 'private' stamp: 'yo 3/17/2004 00:41'! languageEnvironment ^ SimplifiedChineseEnvironment. ! ! !CNGBTextConverter methodsFor: 'private' stamp: 'yo 10/23/2002 14:42'! leadingChar ^ GB2312 leadingChar ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CNGBTextConverter class instanceVariableNames: ''! !CNGBTextConverter class methodsFor: 'utilities' stamp: 'yo 10/23/2002 14:42'! encodingNames ^ #('gb2312' ) copy ! ! ByteTextConverter subclass: #CP1250TextConverter instanceVariableNames: '' classVariableNames: 'FromTable' poolDictionaries: '' category: 'Multilingual-TextConversion'! !CP1250TextConverter commentStamp: '' prior: 0! Text converter for CP1250. Windows code page used in Eastern Europe.! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CP1250TextConverter class instanceVariableNames: ''! !CP1250TextConverter class methodsFor: 'accessing' stamp: 'pk 1/19/2005 14:35'! encodingNames ^ #('cp-1250') copy ! ! !CP1250TextConverter class methodsFor: 'accessing' stamp: 'michael.rueger 1/30/2009 11:02'! languageEnvironment ^Latin2Environment! ! !CP1250TextConverter class methodsFor: 'initialization' stamp: 'michael.rueger 2/5/2009 14:07'! byteToUnicodeSpec "Sepcify a table mapping the entries 0x80 to 0xFF to their unicode counterparts by returning a 128 element array.. The entries 0x00 to 0x7F map to identical values so we don't need to specify them." "http://en.wikipedia.org/wiki/Windows-1250" "http://www.microsoft.com/globaldev/reference/sbcs/1250.mspx" ^#( 16r20AC 16r0081 16r201A 16r083 16r201E 16r2026 16r2020 16r2021 16r0088 16r2030 16r0160 16r2039 16r015A 16r0164 16r017D 16r0179 16r0090 16r2018 16r2019 16r201C 16r201D 16r2022 16r2013 16r2014 16r0098 16r2122 16r0161 16r203A 16r015B 16r0165 16r017E 16r017A 16r00A0 16r02C7 16r02D8 16r0141 16r00A4 16r0104 16r00A6 16r00A7 16r00A8 16r00A9 16r015E 16r00AB 16r00AC 16r00AD 16r00AE 16r017B 16r00B0 16r00B1 16r02DB 16r0142 16r00B4 16r00B5 16r00B6 16r00B7 16r00B8 16r0105 16r015F 16r00BB 16r013D 16r02DD 16r013E 16r017C 16r0154 16r00C1 16r00C2 16r0102 16r00C4 16r0139 16r0106 16r00C7 16r010C 16r00C9 16r0118 16r00CB 16r011A 16r00CD 16r00CE 16r010E 16r0110 16r0143 16r0147 16r00D3 16r00D4 16r0150 16r00D6 16r00D7 16r0158 16r016E 16r00DA 16r0170 16r00DC 16r00DD 16r0162 16r00DF 16r0155 16r00E1 16r00E2 16r0103 16r00E4 16r013A 16r0107 16r00E7 16r010D 16r00E9 16r0119 16r00EB 16r011B 16r00ED 16r00EE 16r010F 16r0111 16r0144 16r0148 16r00F3 16r00F4 16r0151 16r00F6 16r00F7 16r0159 16r016F 16r00FA 16r0171 16r00FC 16r00FD 16r0163 16r02D9 )! ! ByteTextConverter subclass: #CP1253TextConverter instanceVariableNames: '' classVariableNames: 'FromTable' poolDictionaries: '' category: 'Multilingual-TextConversion'! !CP1253TextConverter commentStamp: '' prior: 0! Text converter for CP1253. Windows code page used for Greek.! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CP1253TextConverter class instanceVariableNames: ''! !CP1253TextConverter class methodsFor: 'accessing' stamp: 'michael.rueger 2/5/2009 14:07'! byteToUnicodeSpec "Sepcify a table mapping the entries 0x80 to 0xFF to their unicode counterparts by returning a 128 element array.. The entries 0x00 to 0x7F map to identical values so we don't need to specify them." "http://en.wikipedia.org/wiki/Windows-1253" "http://www.microsoft.com/globaldev/reference/sbcs/1253.mspx" ^#( 16r20AC 16r0081 16r201A 16r0192 16r201E 16r2026 16r2020 16r2021 16r0088 16r2030 16r008A 16r2039 16r008C 16r008D 16r008E 16r008F 16r0090 16r2018 16r2019 16r201C 16r201D 16r2022 16r2013 16r2014 16r0098 16r2122 16r009A 16r203A 16r009C 16r009D 16r009E 16r009F 16r00A0 16r0385 16r0386 16r00A3 16r00A4 16r00A5 16r00A6 16r00A7 16r00A8 16r00A9 16r00AA 16r00AB 16r00AC 16r00AD 16r00AE 16r2015 16r00B0 16r00B1 16r00B2 16r00B3 16r0384 16r00B5 16r00B6 16r00B7 16r0388 16r0389 16r038A 16r00BB 16r038C 16r00BD 16r038E 16r038F 16r0390 16r0391 16r0392 16r0393 16r0394 16r0395 16r0396 16r0397 16r0398 16r0399 16r039A 16r039B 16r039C 16r039D 16r039E 16r039F 16r03A0 16r03A1 16r00D2 16r03A3 16r03A4 16r03A5 16r03A6 16r03A7 16r03A8 16r03A9 16r03AA 16r03AB 16r03AC 16r03AD 16r03AE 16r03AF 16r03B0 16r03B1 16r03B2 16r03B3 16r03B4 16r03B5 16r03B6 16r03B7 16r03B8 16r03B9 16r03BA 16r03BB 16r03BC 16r03BD 16r03BE 16r03BF 16r03C0 16r03C1 16r03C2 16r03C3 16r03C4 16r03C5 16r03C6 16r03C7 16r03C8 16r03C9 16r03CA 16r03CB 16r03CC 16r03CD 16r03CE 16r00FF )! ! !CP1253TextConverter class methodsFor: 'accessing' stamp: 'yo 2/19/2004 10:11'! encodingNames ^ #('cp-1253') copy ! ! !CP1253TextConverter class methodsFor: 'accessing' stamp: 'michael.rueger 2/2/2009 18:49'! languageEnvironment ^GreekEnvironment! ! Model subclass: #CPUWatcher instanceVariableNames: 'tally watcher threshold' classVariableNames: 'CurrentCPUWatcher' poolDictionaries: '' category: 'Tools-Process Browser'! !CPUWatcher commentStamp: '' prior: 0! CPUWatcher implements a simple runaway process monitoring tool that will suspend a process that is taking up too much of Squeak's time and allow user interaction. By default it watches for a Process that is taking more than 80% of the time; this threshold can be changed. CPUWatcher can also be used to show cpu percentages for each process from within the ProcessBrowser. CPUWatcher startMonitoring. "process period 20 seconds, sample rate 100 msec" CPUWatcher current monitorProcessPeriod: 10 sampleRate: 20. CPUWatcher current threshold: 0.5. "change from 80% to 50%" CPUWatcher stopMonitoring. ! !CPUWatcher methodsFor: 'accessing' stamp: 'nk 3/14/2001 07:56'! isMonitoring ^watcher notNil! ! !CPUWatcher methodsFor: 'accessing' stamp: 'nk 3/8/2001 18:36'! tally ^tally copy! ! !CPUWatcher methodsFor: 'accessing' stamp: 'nk 3/8/2001 18:49'! threshold "What fraction of the time can a process be the active process before we stop it?" ^threshold! ! !CPUWatcher methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'! threshold: thresh "What fraction of the time can a process be the active process before we stop it?" threshold := (thresh max: 0.02) min: 1.0! ! !CPUWatcher methodsFor: 'accessing' stamp: 'nk 3/14/2001 08:26'! watcherProcess ^watcher! ! !CPUWatcher methodsFor: 'porcine capture' stamp: 'sd 11/20/2005 21:27'! catchThePig: aProcess | rules | "nickname, allow-stop, allow-debug" rules := ProcessBrowser nameAndRulesFor: aProcess. (ProcessBrowser isUIProcess: aProcess) ifTrue: [ "aProcess debugWithTitle: 'Interrupted from the CPUWatcher'." ] ifFalse: [ rules second ifFalse: [ ^self ]. ProcessBrowser suspendProcess: aProcess. self openWindowForSuspendedProcess: aProcess ] ! ! !CPUWatcher methodsFor: 'porcine capture' stamp: 'sd 11/20/2005 21:27'! findThePig "tally has been updated. Look at it to see if there is a bad process. This runs at a very high priority, so make it fast" | countAndProcess | countAndProcess := tally sortedCounts first. (countAndProcess key / tally size > self threshold) ifTrue: [ | proc | proc := countAndProcess value. proc == Processor backgroundProcess ifTrue: [ ^self ]. "idle process? OK" self catchThePig: proc ]. ! ! !CPUWatcher methodsFor: 'porcine capture' stamp: 'sd 11/20/2005 21:27'! openMorphicWindowForSuspendedProcess: aProcess | menu rules | menu := MenuMorph new. "nickname allow-stop allow-debug" rules := ProcessBrowser nameAndRulesFor: aProcess. menu add: 'Dismiss this menu' target: menu selector: #delete; addLine. menu add: 'Open Process Browser' target: ProcessBrowser selector: #open. menu add: 'Resume' target: self selector: #resumeProcess:fromMenu: argumentList: { aProcess . menu }. menu add: 'Terminate' target: self selector: #terminateProcess:fromMenu: argumentList: { aProcess . menu }. rules third ifTrue: [ menu add: 'Debug at a lower priority' target: self selector: #debugProcess:fromMenu: argumentList: { aProcess . menu }. ]. menu addTitle: aProcess identityHash asString, ' ', rules first, ' is taking too much time and has been suspended. What do you want to do with it?'. menu stayUp: true. menu popUpInWorld ! ! !CPUWatcher methodsFor: 'porcine capture' stamp: 'alain.plantec 5/30/2008 10:35'! openWindowForSuspendedProcess: aProcess WorldState addDeferredUIMessage: [ self openMorphicWindowForSuspendedProcess: aProcess ] ! ! !CPUWatcher methodsFor: 'process operations' stamp: 'sd 11/20/2005 21:27'! debugProcess: aProcess | uiPriority oldPriority | uiPriority := Processor activeProcess priority. aProcess priority >= uiPriority ifTrue: [ oldPriority := ProcessBrowser setProcess: aProcess toPriority: uiPriority - 1 ]. ProcessBrowser debugProcess: aProcess.! ! !CPUWatcher methodsFor: 'process operations' stamp: 'nk 3/8/2001 17:27'! debugProcess: aProcess fromMenu: aMenuMorph aMenuMorph delete. self debugProcess: aProcess.! ! !CPUWatcher methodsFor: 'process operations' stamp: 'nk 3/8/2001 17:21'! resumeProcess: aProcess fromMenu: aMenuMorph aMenuMorph delete. ProcessBrowser resumeProcess: aProcess.! ! !CPUWatcher methodsFor: 'process operations' stamp: 'nk 3/8/2001 17:24'! terminateProcess: aProcess fromMenu: aMenuMorph aMenuMorph delete. ProcessBrowser terminateProcess: aProcess.! ! !CPUWatcher methodsFor: 'startup-shutdown' stamp: 'sd 11/20/2005 21:27'! monitorProcessPeriod: secs sampleRate: msecs self stopMonitoring. watcher := [ [ | promise | promise := Processor tallyCPUUsageFor: secs every: msecs. tally := promise value. promise := nil. self findThePig. ] repeat ] forkAt: Processor highestPriority. Processor yield ! ! !CPUWatcher methodsFor: 'startup-shutdown' stamp: 'nk 3/14/2001 08:07'! startMonitoring self monitorProcessPeriod: 20 sampleRate: 100! ! !CPUWatcher methodsFor: 'startup-shutdown' stamp: 'sd 11/20/2005 21:27'! stopMonitoring watcher ifNotNil: [ ProcessBrowser terminateProcess: watcher. watcher := nil. ]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CPUWatcher class instanceVariableNames: ''! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'nk 3/8/2001 18:45'! current ^CurrentCPUWatcher ! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'nk 3/14/2001 08:28'! currentWatcherProcess ^CurrentCPUWatcher ifNotNil: [ CurrentCPUWatcher watcherProcess ] ! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'nk 3/8/2001 21:43'! dumpTallyOnTranscript self current ifNotNil: [ ProcessBrowser dumpTallyOnTranscript: self current tally ]! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'nk 6/18/2003 07:15'! initialize "CPUWatcher initialize" Smalltalk addToStartUpList: self. Smalltalk addToShutDownList: self.! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'nk 3/14/2001 08:06'! isMonitoring ^CurrentCPUWatcher notNil and: [ CurrentCPUWatcher isMonitoring ] ! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'nk 10/31/2001 10:50'! monitorPreferenceChanged Preferences cpuWatcherEnabled ifTrue: [ self startMonitoring ] ifFalse: [ self stopMonitoring ]! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'nk 6/18/2003 07:14'! shutDown self stopMonitoring.! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'nk 3/14/2001 08:17'! startMonitoring "CPUWatcher startMonitoring" ^self startMonitoringPeriod: 20 rate: 100 threshold: 0.8! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'sd 11/20/2005 21:28'! startMonitoringPeriod: pd rate: rt threshold: th "CPUWatcher startMonitoring" CurrentCPUWatcher ifNotNil: [ ^CurrentCPUWatcher startMonitoring. ]. CurrentCPUWatcher := (self new) monitorProcessPeriod: pd sampleRate: rt; threshold: th; yourself. ^CurrentCPUWatcher ! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'nk 6/18/2003 07:14'! startUp self monitorPreferenceChanged.! ! !CPUWatcher class methodsFor: 'as yet unclassified' stamp: 'sd 11/20/2005 21:28'! stopMonitoring "CPUWatcher stopMonitoring" CurrentCPUWatcher ifNotNil: [ CurrentCPUWatcher stopMonitoring. ]. CurrentCPUWatcher := nil. ! ! Error subclass: #CRCError instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Compression-Streams'! !CRCError methodsFor: 'as yet unclassified' stamp: 'nk 3/7/2004 15:56'! isResumable ^true! ! HTTPDownloadRequest subclass: #CachedHTTPDownloadRequest instanceVariableNames: 'cachedName' classVariableNames: '' poolDictionaries: '' category: 'System-Download'! !CachedHTTPDownloadRequest methodsFor: 'accessing' stamp: 'ar 12/14/1999 14:53'! cachedName ^cachedName! ! !CachedHTTPDownloadRequest methodsFor: 'accessing' stamp: 'ar 12/14/1999 14:53'! cachedName: aString cachedName := aString.! ! !CachedHTTPDownloadRequest methodsFor: 'accessing' stamp: 'ar 12/14/1999 15:00'! startRetrieval | fileStream | cachedName == nil ifTrue:[^super startRetrieval]. (FileDirectory default fileExists: cachedName) ifTrue:[ fileStream := FileStream concreteStream new open: cachedName forWrite: false. fileStream == nil ifFalse:[^self content: (MIMEDocument contentType: 'text/plain' content: fileStream contentsOfEntireFile)]. FileDirectory default deleteFileNamed: cachedName ifAbsent:[]]. super startRetrieval. "fetch from URL" "and cache in file dir" fileStream := FileStream concreteStream new open: cachedName forWrite: true. fileStream == nil ifFalse:[ fileStream nextPutAll: (content content). fileStream close].! ! CodeLoader subclass: #CachingCodeLoader instanceVariableNames: 'cacheDir' classVariableNames: '' poolDictionaries: '' category: 'System-Download'! !CachingCodeLoader methodsFor: 'accessing' stamp: 'mir 12/22/1999 14:10'! cacheDir ^cacheDir! ! !CachingCodeLoader methodsFor: 'accessing' stamp: 'mir 12/22/1999 14:10'! cacheDir: aString cacheDir := aString.! ! !CachingCodeLoader methodsFor: 'accessing' stamp: 'mir 12/22/1999 14:10'! localCache: stringArray | fd | fd := FileDirectory default. stringArray do:[:part| (fd directoryNames includes: part) ifFalse:[fd createDirectory: part]. fd := fd directoryNamed: part]. self cacheDir: (fd pathName copyWith: fd pathNameDelimiter).! ! !CachingCodeLoader methodsFor: 'accessing' stamp: 'mir 12/22/1999 14:10'! localCacheDir: aString self cacheDir: (FileDirectory default pathName, FileDirectory slash, aString, FileDirectory slash)! ! !CachingCodeLoader methodsFor: 'private' stamp: 'mir 12/22/1999 14:11'! createRequestFor: name in: aLoader | request | request := super createRequestFor: name in: aLoader. request cachedName: cacheDir, name. ^request! ! !CachingCodeLoader methodsFor: 'private' stamp: 'avi 4/30/2004 01:40'! httpRequestClass ^CachedHTTPDownloadRequest ! ! Morph subclass: #CachingMorph instanceVariableNames: 'damageRecorder cacheCanvas' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Basic'! !CachingMorph commentStamp: '' prior: 0! This morph can be used to cache the picture of a morph that takes a long time to draw. It should be used with judgement, however, since heavy use of caching can consume large amounts of memory.! !CachingMorph methodsFor: 'as yet unclassified' stamp: 'dgd 2/21/2003 23:03'! updateCacheCanvas: aCanvas "Update the cached image of the morphs being held by this hand." | myBnds rectList | myBnds := self fullBounds. (cacheCanvas isNil or: [cacheCanvas extent ~= myBnds extent]) ifTrue: [cacheCanvas := (aCanvas allocateForm: myBnds extent) getCanvas. cacheCanvas translateBy: myBnds origin negated during: [:tempCanvas | super fullDrawOn: tempCanvas]. ^self]. "incrementally update the cache canvas" rectList := damageRecorder invalidRectsFullBounds: (0 @ 0 extent: myBnds extent). damageRecorder reset. rectList do: [:r | cacheCanvas translateTo: myBnds origin negated clippingTo: r during: [:c | c fillColor: Color transparent. "clear to transparent" super fullDrawOn: c]]! ! !CachingMorph methodsFor: 'caching' stamp: 'jm 11/13/97 16:31'! releaseCachedState super releaseCachedState. cacheCanvas := nil. ! ! !CachingMorph methodsFor: 'change reporting' stamp: 'ar 11/12/2000 18:43'! invalidRect: damageRect from: aMorph "Record the given rectangle in the damage list." damageRecorder recordInvalidRect: (damageRect translateBy: self fullBounds origin negated). super invalidRect: damageRect from: aMorph! ! !CachingMorph methodsFor: 'drawing'! drawOn: aCanvas submorphs isEmpty ifTrue: [^ super drawOn: aCanvas]. ! ! !CachingMorph methodsFor: 'drawing' stamp: 'ar 12/30/2001 19:14'! fullDrawOn: aCanvas (aCanvas isVisible: self fullBounds) ifFalse:[^self]. self updateCacheCanvas: aCanvas. aCanvas cache: self fullBounds using: cacheCanvas form during:[:cachingCanvas| super fullDrawOn: cachingCanvas]. ! ! !CachingMorph methodsFor: 'drawing' stamp: 'ar 5/28/2000 17:12'! imageForm self updateCacheCanvas: Display getCanvas. ^ cacheCanvas form offset: self fullBounds topLeft ! ! !CachingMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:24'! defaultColor "answer the default color/fill style for the receiver" ^ Color veryLightGray! ! !CachingMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 21:48'! initialize "initialize the state of the receiver" super initialize. "" damageRecorder := DamageRecorder new! ! FileStreamException subclass: #CannotDeleteFileException instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! FlattenEncoder subclass: #Canvas instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'! !Canvas commentStamp: '' prior: 0! A canvas is a two-dimensional medium on which morphs are drawn in a device-independent manner. Canvases keep track of the origin and clipping rectangle, as well as the underlying drawing medium (such as a window, pixmap, or postscript script). Subclasses must implement (at least) the following methods: * Drawing: #fillOval:color:borderWidth:borderColor: #frameAndFillRectangle:fillColor:borderWidth:borderColor: #drawPolygon:color:borderWidth:borderColor: #image:at:sourceRect:rule: #stencil:at:sourceRect:rule: #line:to:width:color: #paragraph:bounds:color: #text:bounds:font:color: * Support #clipBy:during: #translateBy:during: #translateBy:clippingTo:during: #transformBy:clippingTo:during: ! !Canvas methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/21/2008 16:34'! fillRectangle: aRectangle basicFillStyle: aFillStyle "Fill the given rectangle with the given, non-composite, fill style Note: The default implementation does not recognize any enhanced fill styles." self fillRectangle: aRectangle color: aFillStyle asColor.! ! !Canvas methodsFor: '*Polymorph-Widgets' stamp: 'gvc 9/14/2006 14:33'! frameRectangle: aRectangle width: width colors: colors dashes: dashes "Draw a rectangle with the given width, colors and dash lengths." self frameRectangle: aRectangle width: width colors: colors dashes: dashes offset: self origin! ! !Canvas methodsFor: '*Polymorph-Widgets' stamp: 'gvc 9/18/2006 16:52'! frameRectangle: aRectangle width: width colors: colors dashes: dashes offset: offset "Draw a rectangle with the given width, colors and dash lengths. The offset specifies how the coordinate system is translated from the screen origin (infinite forms are 0@0 screen based)." |o s hf vf c r ds di d os l| width < 1 ifTrue: [^self]. dashes size < 2 ifTrue: [^self frameRectangle: aRectangle width: width color: colors first]. r := aRectangle. s := dashes sum * width. ds := dashes size. di := 1. d := (dashes at: di) * width. c := colors at: di. hf := Form extent: s @ 1 depth: 32. r height >= width ifTrue: [ o := r left + offset x \\ s. 0 to: s - 1 do: [:x | hf colorAt: x + o \\ s @ 0 put: c. d := d - 1. d = 0 ifTrue: [ di := di \\ ds + 1. d := (dashes at: di) * width. c := colors at: di]]. os := 0. l := r width truncateTo: width. self fillRectangle: (r topLeft + (os@0) extent: l@width) color: (InfiniteForm with: hf)]. vf := Form extent: 1 @ s depth: 32. r width >= width ifTrue: [ o := r top + offset y + width + (s - (r width \\ s)) \\ s. 0 to: s - 1 do: [:y | vf colorAt: 0 @ (y + o \\ s) put: c. d := d - 1. d = 0 ifTrue: [ di := di \\ ds + 1. d := (dashes at: di) * width. c := colors at: di]]. os := width - (r width \\ width). l := r height - os truncateTo: width. self fillRectangle: (r topRight + (width negated @ os) extent: width@l) color: (InfiniteForm with: vf)]. r height > width ifTrue: [ o := r right + offset x - (width * 2) + (r height \\ s) + (r width \\ s) \\ s. 0 to: s - 1 do: [:x | hf colorAt: o + s -1 - x \\ s @ 0 put: c. d := d - 1. d = 0 ifTrue: [ di := di \\ ds + 1. d := (dashes at: di) * width. c := colors at: di]]. os := width - (r width \\ width + (r height \\ width) \\ width). l := r width - os truncateTo: width. os := (r width - os) \\ width. self fillRectangle: (r bottomLeft + (os @ width negated) extent: l@width) color: (InfiniteForm with: hf)]. r width > width ifTrue: [ o := r top + offset y + (r height * 2 \\ s) + (r width * 2 \\ s) - (width * 3) \\ s. 0 to: s - 1 do: [:y | vf colorAt: 0 @ (o + s -1 - y \\ s) put: c. d := d - 1. d = 0 ifTrue: [ di := di \\ ds + 1. d := (dashes at: di) * width. c := colors at: di]]. l := r height - (2 * width) + os. os := width. self fillRectangle: (r topLeft + (0@os) extent: width@l) color: (InfiniteForm with: vf)]! ! !Canvas methodsFor: '*Polymorph-Widgets' stamp: 'gvc 6/17/2006 10:42'! line: pt1 to: pt2 width: width colors: colors dashes: dashes startingOffset: startingOffset "Draw a line using the given width, colors and dash lengths. Dash lengths are considered as multiples of width." |dist deltaBig segmentOffset phase segmentLength startPoint distDone endPoint segLens lens l ep| width = 0 ifTrue: [^startingOffset]. dist := pt1 dist: pt2. dist = 0 ifTrue: [^startingOffset]. (dashes allSatisfy: [:d | d = 0]) ifTrue: [^startingOffset]. deltaBig := pt2 - pt1. segLens := dashes collect: [:d | d * width]. "Figure out what phase we are in and how far, given startingOffset." segmentOffset := startingOffset \\ segLens sum. lens := segLens readStream. l := 0. [lens atEnd or: [segmentOffset <= (l := l + lens next)]] whileFalse: []. segmentLength := lens atEnd ifTrue: [phase := segLens size. segLens sum - segmentOffset] ifFalse: [phase := lens position. (segLens first: phase) sum - segmentOffset.]. startPoint := pt1. distDone := 0.0. segmentLength < (segLens at: phase) ifTrue: [startPoint := startPoint + (deltaBig * segmentLength / dist). distDone := distDone + segmentLength. phase := phase \\ segLens size + 1. segmentLength := (segLens at: phase)]. [distDone < dist] whileTrue: [segmentLength := segmentLength min: dist - distDone. endPoint := startPoint + (deltaBig * segmentLength / dist). ep := startPoint + (deltaBig * (segmentLength - width max: 0) / dist). self line: startPoint truncated to: ep truncated width: width color: (colors at: phase). distDone := distDone + segmentLength. phase := phase \\ segLens size + 1. startPoint := endPoint. segmentLength := segLens at: phase]. ^startingOffset + distDone! ! !Canvas methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 9/6/2007 15:18'! drawMorph: aMorph "Changed to improve performance. Have seen a 30% improvement." (aMorph fullBounds intersects: self clipRect) ifFalse: [^self]. self draw: aMorph! ! !Canvas methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 3/21/2008 16:35'! fillRectangle: aRectangle fillStyle: aFillStyle "Fill the given rectangle. Double-dispatched via the fill style." aFillStyle fillRectangle: aRectangle on: self! ! !Canvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 14:07'! clipRect "Return the currently active clipping rectangle" ^self subclassResponsibility! ! !Canvas methodsFor: 'accessing' stamp: 'ar 2/12/2000 18:17'! contentsOfArea: aRectangle "Return the contents of the given area" ^self contentsOfArea: aRectangle into: (Form extent: aRectangle extent depth: self depth)! ! !Canvas methodsFor: 'accessing' stamp: 'ar 2/12/2000 18:17'! contentsOfArea: aRectangle into: aForm "Return the contents of the given area" ^self subclassResponsibility! ! !Canvas methodsFor: 'accessing'! depth ^ Display depth ! ! !Canvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 14:15'! extent "Return the physical extent of the output device" ^self subclassResponsibility! ! !Canvas methodsFor: 'accessing' stamp: 'jm 6/2/1998 06:39'! form ^ Display ! ! !Canvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 14:11'! origin "Return the current origin for drawing operations" ^self subclassResponsibility! ! !Canvas methodsFor: 'accessing' stamp: 'ar 2/17/2000 01:46'! shadowColor "Return the current override color or nil if no such color exists" ^nil! ! !Canvas methodsFor: 'accessing' stamp: 'ar 2/17/2000 01:46'! shadowColor: aColor "Set a shadow color. If set this color overrides any client-supplied color."! ! !Canvas methodsFor: 'converting' stamp: 'ar 8/8/2001 14:22'! asAlphaBlendingCanvas: alpha ^(AlphaBlendingCanvas on: self) alpha: alpha! ! !Canvas methodsFor: 'converting' stamp: 'ar 6/24/1999 17:46'! asShadowDrawingCanvas ^self asShadowDrawingCanvas: (Color black alpha: 0.5).! ! !Canvas methodsFor: 'converting' stamp: 'ar 8/8/2001 14:14'! asShadowDrawingCanvas: aColor ^(ShadowDrawingCanvas on: self) shadowColor: aColor! ! !Canvas methodsFor: 'copying' stamp: 'jm 8/2/97 13:54'! copy ^ self clone ! ! !Canvas methodsFor: 'copying' stamp: 'ls 3/20/2000 21:24'! copyClipRect: newClipRect ^ ClippingCanvas canvas: self clipRect: newClipRect ! ! !Canvas methodsFor: 'drawing' stamp: 'ar 6/17/1999 01:18'! fillColor: aColor "Fill the receiver with the given color. Note: This method should be named differently since it is intended to fill the background and thus fills even if the color is transparent" ^self fillRectangle: self clipRect color: (aColor alpha: 1.0).! ! !Canvas methodsFor: 'drawing' stamp: 'ar 6/17/1999 01:30'! line: pt1 to: pt2 brushForm: brush "Obsolete - will be removed in the future"! ! !Canvas methodsFor: 'drawing' stamp: 'jm 8/2/97 13:54'! line: pt1 to: pt2 color: c self line: pt1 to: pt2 width: 1 color: c. ! ! !Canvas methodsFor: 'drawing' stamp: 'ar 6/17/1999 01:31'! line: pt1 to: pt2 width: w color: c "Draw a line using the given width and color" ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing' stamp: 'aoy 2/15/2003 21:41'! line: pt1 to: pt2 width: width color: color1 dashLength: s1 secondColor: color2 secondDashLength: s2 startingOffset: startingOffset "Draw a line using the given width, colors and dash lengths. Originally written by Stephan Rudlof; tweaked by Dan Ingalls to use startingOffset for sliding offset as in 'ants' animations. Returns the sum of the starting offset and the length of this line." | dist deltaBig colors nextPhase segmentOffset phase segmentLength startPoint distDone endPoint segLens | dist := pt1 dist: pt2. dist = 0 ifTrue: [^startingOffset]. s1 = 0 & (s2 = 0) ifTrue: [^startingOffset]. deltaBig := pt2 - pt1. colors := { color1. color2}. segLens := { s1 asFloat. s2 asFloat}. nextPhase := { 2. 1}. "Figure out what phase we are in and how far, given startingOffset." segmentOffset := startingOffset \\ (s1 + s2). segmentLength := segmentOffset < s1 ifTrue: [phase := 1. s1 - segmentOffset] ifFalse: [phase := 2. s1 + s2 - segmentOffset]. startPoint := pt1. distDone := 0.0. [distDone < dist] whileTrue: [segmentLength := segmentLength min: dist - distDone. endPoint := startPoint + (deltaBig * segmentLength / dist). self line: startPoint truncated to: endPoint truncated width: width color: (colors at: phase). distDone := distDone + segmentLength. phase := nextPhase at: phase. startPoint := endPoint. segmentLength := segLens at: phase]. ^startingOffset + dist! ! !Canvas methodsFor: 'drawing' stamp: 'sr 4/27/2000 03:31'! line: pt1 to: pt2 width: w1 color: c1 stepWidth: s1 secondWidth: w2 secondColor: c2 secondStepWidth: s2 "Draw a line using the given width, colors and steps; both steps can have different stepWidths (firstStep, secondStep), draw widths and colors." | bigSteps offsetPoint dist p1p2Vec deltaBig delta1 delta2 lastPoint bigStep | s1 = 0 & (s2 = 0) ifTrue: [^ self]. dist := pt1 dist: pt2. dist = 0 ifTrue: [^ self]. bigStep := s1 + s2. bigSteps := dist / bigStep. p1p2Vec := pt2 - pt1. deltaBig := p1p2Vec / bigSteps. delta1 := deltaBig * (s1 / bigStep). delta2 := deltaBig * (s2 / bigStep). dist <= s1 ifTrue: [self line: pt1 rounded to: pt2 rounded width: w1 color: c1. ^ self]. 0 to: bigSteps truncated - 1 do: [:bigStepIx | self line: (pt1 + (offsetPoint := deltaBig * bigStepIx)) rounded to: (pt1 + (offsetPoint := offsetPoint + delta1)) rounded width: w1 color: c1. self line: (pt1 + offsetPoint) rounded to: (pt1 + (offsetPoint + delta2)) rounded width: w2 color: c2]. "if there was no loop, offsetPoint is nil" lastPoint := pt1 + ((offsetPoint ifNil: [0 @ 0]) + delta2). (lastPoint dist: pt2) <= s1 ifTrue: [self line: lastPoint rounded to: pt2 rounded width: w1 color: c1] ifFalse: [self line: lastPoint rounded to: (lastPoint + delta1) rounded width: w1 color: c1. self line: (lastPoint + delta1) rounded to: pt2 width: w1 color: c2]! ! !Canvas methodsFor: 'drawing' stamp: 'ar 6/17/1999 01:31'! paragraph: paragraph bounds: bounds color: c "Draw the given paragraph" ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing' stamp: 'ar 6/17/1999 01:32'! point: p color: c "Obsolete - will be removed in the future"! ! !Canvas methodsFor: 'drawing' stamp: 'ar 2/5/1999 18:28'! render: anObject "Do some 3D operations with the object if possible"! ! !Canvas methodsFor: 'drawing-general' stamp: 'ar 5/29/1999 05:14'! draw: anObject ^anObject drawOn: self! ! !Canvas methodsFor: 'drawing-general'! fullDraw: anObject ^anObject fullDrawOn: self! ! !Canvas methodsFor: 'drawing-general' stamp: 'ar 12/30/2001 15:23'! fullDrawMorph: aMorph self fullDraw: aMorph! ! !Canvas methodsFor: 'drawing-general' stamp: 'ar 12/30/2001 18:47'! roundCornersOf: aMorph during: aBlock ^self roundCornersOf: aMorph in: aMorph bounds during: aBlock! ! !Canvas methodsFor: 'drawing-general' stamp: 'ar 12/30/2001 18:47'! roundCornersOf: aMorph in: bounds during: aBlock ^aBlock value! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 2/16/2000 23:45'! drawImage: aForm at: aPoint "Draw the given Form, which is assumed to be a Form or ColorForm" self drawImage: aForm at: aPoint sourceRect: aForm boundingBox! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 2/17/2000 01:47'! drawImage: aForm at: aPoint sourceRect: sourceRect "Draw the given form." self shadowColor ifNotNil:[ ^self fillRectangle: ((aForm boundingBox intersect: sourceRect) translateBy: aPoint) color: self shadowColor]. ^self image: aForm at: aPoint sourceRect: sourceRect rule: Form over! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 2/16/2000 23:48'! paintImage: aForm at: aPoint "Draw the given Form, which is assumed to be a Form or ColorForm following the convention that zero is the transparent pixel value." self paintImage: aForm at: aPoint sourceRect: aForm boundingBox ! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 2/17/2000 01:48'! paintImage: aForm at: aPoint sourceRect: sourceRect "Draw the given Form, which is assumed to be a Form or ColorForm following the convention that zero is the transparent pixel value." self shadowColor ifNotNil:[ ^self stencil: aForm at: aPoint sourceRect: sourceRect color: self shadowColor]. ^self image: aForm at: aPoint sourceRect: sourceRect rule: Form paint! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 6/25/1999 12:17'! stencil: stencilForm at: aPoint color: aColor "Flood this canvas with aColor wherever stencilForm has non-zero pixels" ^self stencil: stencilForm at: aPoint sourceRect: stencilForm boundingBox color: aColor! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 6/25/1999 12:17'! stencil: stencilForm at: aPoint sourceRect: sourceRect color: aColor "Flood this canvas with aColor wherever stencilForm has non-zero pixels" ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 2/17/2000 14:05'! translucentImage: aForm at: aPoint "Draw a translucent image using the best available way of representing translucency." self translucentImage: aForm at: aPoint sourceRect: aForm boundingBox! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 2/10/2004 17:19'! translucentImage: aForm at: aPoint sourceRect: sourceRect "Draw a translucent image using the best available way of representing translucency. Note: This will be fixed in the future." self shadowColor ifNotNil:[ ^self stencil: aForm at: aPoint sourceRect: sourceRect color: self shadowColor]. (self depth < 32 or:[aForm isTranslucent not]) ifTrue:[^self paintImage: aForm at: aPoint sourceRect: sourceRect]. self image: aForm at: aPoint sourceRect: sourceRect rule: Form blend! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 12/28/2001 23:44'! warpImage: aForm transform: aTransform "Warp the given form using aTransform" ^self warpImage: aForm transform: aTransform at: 0@0! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 12/28/2001 23:54'! warpImage: aForm transform: aTransform at: extraOffset "Warp the given form using aTransform. TODO: Use transform to figure out appropriate cell size" ^self warpImage: aForm transform: aTransform at: extraOffset sourceRect: aForm boundingBox cellSize: 1! ! !Canvas methodsFor: 'drawing-images' stamp: 'ar 12/29/2001 00:20'! warpImage: aForm transform: aTransform at: extraOffset sourceRect: sourceRect cellSize: cellSize "Warp the given using the appropriate transform and offset." ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing-obsolete' stamp: 'ar 2/12/2000 18:10'! image: aForm at: aPoint "Note: This protocol is deprecated. Use #paintImage: instead." self image: aForm at: aPoint sourceRect: aForm boundingBox rule: Form paint. ! ! !Canvas methodsFor: 'drawing-obsolete' stamp: 'ar 2/12/2000 18:11'! image: aForm at: aPoint rule: combinationRule "Note: This protocol is deprecated. Use one of the explicit image drawing messages (#paintImage, #drawImage) instead." self image: aForm at: aPoint sourceRect: aForm boundingBox rule: combinationRule. ! ! !Canvas methodsFor: 'drawing-obsolete' stamp: 'ar 2/12/2000 18:11'! imageWithOpaqueWhite: aForm at: aPoint "Note: This protocol is deprecated. Use #drawImage: instead" self image: aForm at: aPoint sourceRect: (0@0 extent: aForm extent) rule: Form over. ! ! !Canvas methodsFor: 'drawing-ovals' stamp: 'ar 6/18/1999 08:45'! fillOval: r color: c self fillOval: r color: c borderWidth: 0 borderColor: Color transparent. ! ! !Canvas methodsFor: 'drawing-ovals' stamp: 'ar 6/18/1999 08:45'! fillOval: r color: c borderWidth: borderWidth borderColor: borderColor "Fill the given oval." ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing-ovals' stamp: 'ar 6/18/1999 08:51'! fillOval: aRectangle fillStyle: aFillStyle "Fill the given oval." ^self fillOval: aRectangle fillStyle: aFillStyle borderWidth: 0 borderColor: Color transparent! ! !Canvas methodsFor: 'drawing-ovals' stamp: 'ar 6/18/1999 08:50'! fillOval: aRectangle fillStyle: aFillStyle borderWidth: bw borderColor: bc "Fill the given oval. Note: The default implementation does not recognize any enhanced fill styles" self fillOval: aRectangle color: aFillStyle asColor borderWidth: bw borderColor: bc! ! !Canvas methodsFor: 'drawing-ovals' stamp: 'ar 6/18/1999 08:45'! frameOval: r color: c self fillOval: r color: Color transparent borderWidth: 1 borderColor: c. ! ! !Canvas methodsFor: 'drawing-ovals' stamp: 'ar 6/18/1999 08:45'! frameOval: r width: w color: c self fillOval: r color: Color transparent borderWidth: w borderColor: c. ! ! !Canvas methodsFor: 'drawing-polygons' stamp: 'ar 6/18/1999 08:56'! drawPolygon: vertices color: aColor borderWidth: bw borderColor: bc "Draw the given polygon." ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing-polygons' stamp: 'ar 6/25/1999 12:18'! drawPolygon: vertices fillStyle: aFillStyle "Fill the given polygon." self drawPolygon: vertices fillStyle: aFillStyle borderWidth: 0 borderColor: Color transparent! ! !Canvas methodsFor: 'drawing-polygons' stamp: 'ar 6/18/1999 08:58'! drawPolygon: vertices fillStyle: aFillStyle borderWidth: bw borderColor: bc "Fill the given polygon. Note: The default implementation does not recognize any enhanced fill styles" self drawPolygon: vertices color: aFillStyle asColor borderWidth: bw borderColor: bc! ! !Canvas methodsFor: 'drawing-rectangles' stamp: 'ar 6/18/1999 07:32'! fillRectangle: r color: c "Fill the rectangle using the given color" ^self frameAndFillRectangle: r fillColor: c borderWidth: 0 borderColor: Color transparent! ! !Canvas methodsFor: 'drawing-rectangles' stamp: 'ar 8/25/2001 17:27'! fillRectangle: aRectangle fillStyle: aFillStyle borderStyle: aBorderStyle "Fill the given rectangle." self fillRectangle: (aRectangle insetBy: aBorderStyle width) fillStyle: aFillStyle. aBorderStyle frameRectangle: aRectangle on: self! ! !Canvas methodsFor: 'drawing-rectangles' stamp: 'ar 6/18/1999 07:32'! frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth borderColor: borderColor "Draw the rectangle using the given attributes" ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing-rectangles' stamp: 'RAA 8/14/2000 14:22'! frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth topLeftColor: topLeftColor bottomRightColor: bottomRightColor "Draw the rectangle using the given attributes. Note: This is a *very* simple implementation" | bw pt | self frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth borderColor: bottomRightColor. bottomRightColor = topLeftColor ifFalse: [ bw := borderWidth asPoint. pt := r topLeft + (bw // 2). self line: pt to: pt + ((r extent x - bw x)@0) width: borderWidth color: topLeftColor. self line: pt to: pt + (0@(r extent y - bw y)) width: borderWidth color: topLeftColor. ].! ! !Canvas methodsFor: 'drawing-rectangles' stamp: 'ar 6/18/1999 07:33'! frameRectangle: r color: c self frameRectangle: r width: 1 color: c. ! ! !Canvas methodsFor: 'drawing-rectangles' stamp: 'marcus.denker 8/15/2008 17:43'! frameRectangle: r width: w color: c "Draw a frame around the given rectangle" ^self frameAndFillRectangle: r fillColor: Color transparent borderWidth: w borderColor: c! ! !Canvas methodsFor: 'drawing-support' stamp: 'gm 2/22/2003 14:53'! cache: aRectangle using: aCache during: aBlock "Cache the execution of aBlock by the given cache. Note: At some point we may want to actually *create* the cache here; for now we're only using it." (aCache notNil and: [(aCache isForm) and: [aCache extent = aRectangle extent]]) ifTrue: [^self paintImage: aCache at: aRectangle origin]. aBlock value: self! ! !Canvas methodsFor: 'drawing-support' stamp: 'ar 6/17/1999 02:53'! clipBy: aRectangle during: aBlock "Set a clipping rectangle active only during the execution of aBlock. Note: In the future we may want to have more general clip shapes - not just rectangles" ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing-support' stamp: 'ar 6/17/1999 01:43'! preserveStateDuring: aBlock "Preserve the full canvas state during the execution of aBlock" ^aBlock value: self copy! ! !Canvas methodsFor: 'drawing-support' stamp: 'di 10/16/1999 16:02'! transformBy: aDisplayTransform clippingTo: aClipRect during: aBlock "Transform the receiver by the given display transformation during the execution of aBlock. The given clip rectangle defines the *global* (e.g., outer) rectangle against which the receiver should clip (which would be equivalent to 'self clipRect: aClipRect; transformBy: aDisplayTransform')." ^ self transformBy: aDisplayTransform clippingTo: aClipRect during: aBlock smoothing: 1 ! ! !Canvas methodsFor: 'drawing-support' stamp: 'di 10/16/1999 15:56'! transformBy: aDisplayTransform clippingTo: aClipRect during: aBlock smoothing: cellSize "Transform the receiver by the given display transformation during the execution of aBlock. The given clip rectangle defines the *global* (e.g., outer) rectangle against which the receiver should clip (which would be equivalent to 'self clipRect: aClipRect; transformBy: aDisplayTransform')." ^ self subclassResponsibility! ! !Canvas methodsFor: 'drawing-support' stamp: 'ar 6/17/1999 03:00'! translateBy: delta during: aBlock "Set a translation only during the execution of aBlock." ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing-support' stamp: 'ar 6/22/1999 14:08'! translateTo: newOrigin clippingTo: aRectangle during: aBlock "Set a new origin and clipping rectangle only during the execution of aBlock." self translateBy: newOrigin - self origin clippingTo: (aRectangle translateBy: self origin negated) during: aBlock! ! !Canvas methodsFor: 'drawing-text' stamp: 'ar 12/30/2001 20:35'! drawString: s at: pt ^ self drawString: s from: 1 to: s size at: pt font: nil color: Color black! ! !Canvas methodsFor: 'drawing-text' stamp: 'ar 12/31/2001 02:25'! drawString: s at: pt font: aFont color: aColor ^ self drawString: s from: 1 to: s size at: pt font: aFont color: aColor! ! !Canvas methodsFor: 'drawing-text' stamp: 'ar 12/30/2001 20:36'! drawString: s from: firstIndex to: lastIndex at: pt font: font color: aColor self drawString: s from: firstIndex to: lastIndex in: (pt extent: 10000@10000) font: font color: aColor! ! !Canvas methodsFor: 'drawing-text' stamp: 'tween 3/10/2009 08:07'! drawString: s from: firstIndex to: lastIndex at: pt font: font color: aColor underline: underline underlineColor: uc strikethrough: strikethrough strikethroughColor: sc self drawString: s from: firstIndex to: lastIndex in: (pt extent: 10000@10000) font: font color: aColor underline: underline underlineColor: uc strikethrough: strikethrough strikethroughColor: sc! ! !Canvas methodsFor: 'drawing-text' stamp: 'ar 12/30/2001 20:37'! drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: c ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing-text' stamp: 'tween 3/10/2009 07:42'! drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: c underline: underline underlineColor: uc strikethrough: strikethrough strikethroughColor: sc ^self subclassResponsibility! ! !Canvas methodsFor: 'drawing-text' stamp: 'ar 12/31/2001 02:39'! drawString: s in: boundsRect ^self drawString: s from: 1 to: s size in: boundsRect font: nil color: Color black! ! !Canvas methodsFor: 'drawing-text' stamp: 'ar 12/31/2001 02:13'! drawString: s in: boundsRect font: fontOrNil color: c ^self drawString: s from: 1 to: s size in: boundsRect font: fontOrNil color: c! ! !Canvas methodsFor: 'drawing-text' stamp: 'tween 3/10/2009 08:12'! drawString: s in: boundsRect font: fontOrNil color: c underline: underline underlineColor: uc strikethrough: strikethrough strikethroughColor: sc ^self drawString: s from: 1 to: s size in: boundsRect font: fontOrNil color: c underline: underline underlineColor: uc strikethrough: strikethrough strikethroughColor: sc! ! !Canvas methodsFor: 'drawing-text' stamp: 'ar 12/31/2001 02:40'! text: s at: pt font: fontOrNil color: c "OBSOLETE" ^ self drawString: s at: pt font: fontOrNil color: c! ! !Canvas methodsFor: 'drawing-text' stamp: 'ar 12/31/2001 02:40'! text: s bounds: boundsRect font: fontOrNil color: c "OBSOLETE" ^self drawString: s in: boundsRect font: fontOrNil color: c! ! !Canvas methodsFor: 'initialization' stamp: 'ar 5/27/2000 21:50'! finish "If there are any pending operations on the receiver complete them. Do not return before all modifications have taken effect." ^self flush! ! !Canvas methodsFor: 'initialization' stamp: 'ar 2/9/1999 06:29'! flush! ! !Canvas methodsFor: 'initialization' stamp: 'di 9/22/1999 19:21'! reset "Reset the canvas." super initWithTarget:self class defaultTarget. ! ! !Canvas methodsFor: 'nebraska/embeddedworlds' stamp: 'RAA 12/5/2000 18:28'! transform2By: aDisplayTransform clippingTo: aClipRect during: aBlock smoothing: cellSize "an attempt to use #displayInterpolatedOn: instead of WarpBlt." | patchRect subCanvas pureRect biggerPatch biggerClip interForm | self flag: #bob. "added to Canvas in hopes it will work for Nebraska" (aDisplayTransform isPureTranslation) ifTrue: [ ^aBlock value: (self copyOffset: aDisplayTransform offset negated truncated clipRect: aClipRect) ]. "Prepare an appropriate warp from patch to aClipRect" pureRect := (aDisplayTransform globalBoundsToLocal: aClipRect). patchRect := pureRect rounded. patchRect area = 0 ifTrue: [^self]. "oh, well!!" biggerPatch := patchRect expandBy: 1. biggerClip := (aDisplayTransform localBoundsToGlobal: biggerPatch) rounded. "Render the submorphs visible in the clipping rectangle, as patchForm" subCanvas := FormCanvas extent: biggerPatch extent depth: self depth. self isShadowDrawing ifTrue: [ subCanvas shadowColor: self shadowColor ]. "this biggerPatch/biggerClip is an attempt to improve positioning of the final image in high magnification conditions. Since we cannot grab fractional pixels from the source, take one extra and then take just the part we need from the expanded form" subCanvas translateBy: biggerPatch topLeft negated rounded during: [ :offsetCanvas | aBlock value: offsetCanvas]. interForm := Form extent: biggerClip extent depth: self depth. subCanvas form displayInterpolatedIn: interForm boundingBox on: interForm. self drawImage: interForm at: aClipRect origin sourceRect: (aClipRect origin - biggerClip origin extent: aClipRect extent) ! ! !Canvas methodsFor: 'other'! flushDisplay " Dummy ."! ! !Canvas methodsFor: 'other'! forceToScreen:rect " dummy " ! ! !Canvas methodsFor: 'other'! translateBy:aPoint clippingTo:aRect during:aBlock ^aBlock value:(self copyOffset:aPoint clipRect:aRect).! ! !Canvas methodsFor: 'testing' stamp: 'di 8/12/2000 15:04'! doesRoundedCorners ^ true! ! !Canvas methodsFor: 'testing' stamp: 'ar 11/13/1998 13:19'! isBalloonCanvas ^false! ! !Canvas methodsFor: 'testing' stamp: 'nk 1/1/2004 21:09'! isPostscriptCanvas ^false! ! !Canvas methodsFor: 'testing' stamp: 'ar 6/22/1999 19:03'! isShadowDrawing ^false! ! !Canvas methodsFor: 'testing' stamp: 'ar 6/22/1999 14:10'! isVisible: aRectangle "Return true if the given rectangle is (partially) visible" ^self clipRect intersects: aRectangle ! ! !Canvas methodsFor: 'testing' stamp: 'di 9/24/2000 16:10'! seesNothingOutside: aRectangle "Return true if this canvas will not touch anything outside aRectangle" ^ aRectangle containsRect: self clipRect ! ! !Canvas methodsFor: 'private' stamp: 'ar 2/12/2000 18:12'! image: aForm at: aPoint sourceRect: sourceRect rule: rule "Note: The public use of this protocol is deprecated. It will become private. Nobody in the outside world must assume that a thing like a combination rule has any specific effect." ^self subclassResponsibility! ! !Canvas methodsFor: 'private' stamp: 'ar 8/8/2001 14:21'! image: aForm at: aPoint sourceRect: sourceRect rule: rule alpha: sourceAlpha "Privately used for blending forms w/ constant alpha. Fall back to simpler case by defaul." ^self image: aForm at: aPoint sourceRect: sourceRect rule: rule! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Canvas class instanceVariableNames: ''! !Canvas class methodsFor: 'configuring'! filterSelector ^#drawOnCanvas:.! ! ParseNode subclass: #CascadeNode instanceVariableNames: 'receiver messages' classVariableNames: '' poolDictionaries: '' category: 'Compiler-ParseNodes'! !CascadeNode commentStamp: '' prior: 0! The first message has the common receiver, the rest have receiver == nil, which signifies cascading.! !CascadeNode methodsFor: 'accessing' stamp: 'eem 9/10/2008 15:15'! messages ^messages! ! !CascadeNode methodsFor: 'accessing' stamp: 'tk 10/22/2000 16:55'! receiver ^receiver! ! !CascadeNode methodsFor: 'code generation'! emitForValue: stack on: aStream receiver emitForValue: stack on: aStream. 1 to: messages size - 1 do: [:i | aStream nextPut: Dup. stack push: 1. (messages at: i) emitForValue: stack on: aStream. aStream nextPut: Pop. stack pop: 1]. messages last emitForValue: stack on: aStream! ! !CascadeNode methodsFor: 'code generation'! sizeForValue: encoder | size | size := (receiver sizeForValue: encoder) + (messages size - 1 * 2). messages do: [:aMessage | size := size + (aMessage sizeForValue: encoder)]. ^size! ! !CascadeNode methodsFor: 'code generation (closures)' stamp: 'eem 5/19/2008 20:26'! analyseTempsWithin: scopeBlock "" rootNode: rootNode "" assignmentPools: assignmentPools "" { receiver }, messages do: [:node| node analyseTempsWithin: scopeBlock rootNode: rootNode assignmentPools: assignmentPools]! ! !CascadeNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/15/2008 09:41'! emitCodeForValue: stack encoder: encoder receiver emitCodeForValue: stack encoder: encoder. 1 to: messages size - 1 do: [:i | encoder genDup. stack push: 1. (messages at: i) emitCodeForValue: stack encoder: encoder. encoder genPop. stack pop: 1]. messages last emitCodeForValue: stack encoder: encoder! ! !CascadeNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/15/2008 09:39'! sizeCodeForValue: encoder | size | size := (receiver sizeCodeForValue: encoder) + (messages size - 1 * (encoder sizeDup + encoder sizePop)). messages do: [:aMessage | size := size + (aMessage sizeCodeForValue: encoder)]. ^size! ! !CascadeNode methodsFor: 'initialize-release'! receiver: receivingObject messages: msgs " Transcript show: 'abc'; cr; show: 'def' " receiver := receivingObject. messages := msgs! ! !CascadeNode methodsFor: 'printing'! printOn: aStream indent: level self printOn: aStream indent: level precedence: 0! ! !CascadeNode methodsFor: 'printing' stamp: 'di 4/25/2000 19:17'! printOn: aStream indent: level precedence: p p > 0 ifTrue: [aStream nextPut: $(]. messages first printReceiver: receiver on: aStream indent: level. 1 to: messages size do: [:i | (messages at: i) printOn: aStream indent: level. i < messages size ifTrue: [aStream nextPut: $;. messages first precedence >= 2 ifTrue: [aStream crtab: level + 1]]]. p > 0 ifTrue: [aStream nextPut: $)]! ! !CascadeNode methodsFor: 'printing' stamp: 'eem 6/2/2008 11:47'! printWithClosureAnalysisOn: aStream indent: level self printWithClosureAnalysisOn: aStream indent: level precedence: 0! ! !CascadeNode methodsFor: 'printing' stamp: 'eem 6/2/2008 11:47'! printWithClosureAnalysisOn: aStream indent: level precedence: p p > 0 ifTrue: [aStream nextPut: $(]. messages first printWithClosureAnalysisReceiver: receiver on: aStream indent: level. 1 to: messages size do: [:i | (messages at: i) printWithClosureAnalysisOn: aStream indent: level. i < messages size ifTrue: [aStream nextPut: $;. messages first precedence >= 2 ifTrue: [aStream crtab: level + 1]]]. p > 0 ifTrue: [aStream nextPut: $)]! ! !CascadeNode methodsFor: 'visiting' stamp: 'eem 9/10/2008 15:16'! accept: aVisitor aVisitor visitCascadeNode: self! ! Object subclass: #Categorizer instanceVariableNames: 'categoryArray categoryStops elementArray' classVariableNames: 'Default NullCategory' poolDictionaries: '' category: 'Kernel-Classes'! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! addCategory: newCategory ^ self addCategory: newCategory before: nil ! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! addCategory: catString before: nextCategory "Add a new category named heading. If default category exists and is empty, remove it. If nextCategory is nil, then add the new one at the end, otherwise, insert it before nextCategory." | index newCategory | newCategory := catString asSymbol. (categoryArray indexOf: newCategory) > 0 ifTrue: [^self]. "heading already exists, so done" index := categoryArray indexOf: nextCategory ifAbsent: [categoryArray size + 1]. categoryArray := categoryArray copyReplaceFrom: index to: index-1 with: (Array with: newCategory). categoryStops := categoryStops copyReplaceFrom: index to: index-1 with: (Array with: (index = 1 ifTrue: [0] ifFalse: [categoryStops at: index-1])). "remove empty default category" (newCategory ~= Default and: [(self listAtCategoryNamed: Default) isEmpty]) ifTrue: [self removeCategory: Default]! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! allMethodSelectors "give a list of all method selectors." ^ elementArray copy sort! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 10:29'! categories "Answer an Array of categories (names)." categoryArray isNil ifTrue: [^ nil]. (categoryArray size = 1 and: [categoryArray first = Default & (elementArray size = 0)]) ifTrue: [^Array with: NullCategory]. ^categoryArray! ! !Categorizer methodsFor: 'accessing' stamp: 'mtf 1/19/2009 15:00'! categories: anArray "Reorder my categories to be in order of the argument, anArray. If the resulting organization does not include all elements, then give an error." | newCategories newStops newElements catName list runningTotal | anArray size < 2 ifTrue: [ ^ self ]. newCategories := Array new: anArray size. newStops := Array new: anArray size. newElements := Array new: 0. runningTotal := 0. 1 to: anArray size do: [:i | catName := (anArray at: i) asSymbol. list := self listAtCategoryNamed: catName. newElements := newElements, list. newCategories at: i put: catName. newStops at: i put: (runningTotal := runningTotal + list size)]. elementArray do: [:element | "check to be sure all elements are included" (newElements includes: element) ifFalse: [^self error: 'New categories must match old ones']]. "Everything is good, now update my three arrays." categoryArray := newCategories. categoryStops := newStops. elementArray := newElements! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! categoryOfElement: element "Answer the category associated with the argument, element." | index | index := self numberOfCategoryOfElement: element. index = 0 ifTrue: [^nil] ifFalse: [^categoryArray at: index]! ! !Categorizer methodsFor: 'accessing' stamp: 'PeterHugossonMiller 9/3/2009 00:16'! changeFromCategorySpecs: categorySpecs "Tokens is an array of categorySpecs as scanned from a browser 'reorganize' pane, or built up by some other process, such as a scan of an environment." | oldElements newElements newCategories newStops currentStop temp ii cc catSpec | oldElements := elementArray asSet. newCategories := Array new: categorySpecs size. newStops := Array new: categorySpecs size. currentStop := 0. newElements := (Array new: 16) writeStream. 1 to: categorySpecs size do: [:i | | selectors | catSpec := categorySpecs at: i. newCategories at: i put: catSpec first asSymbol. selectors := catSpec allButFirst collect: [:each | each isSymbol ifTrue: [each] ifFalse: [each printString asSymbol]]. selectors asSortedCollection do: [:elem | (oldElements remove: elem ifAbsent: [nil]) notNil ifTrue: [newElements nextPut: elem. currentStop := currentStop+1]]. newStops at: i put: currentStop]. "Ignore extra elements but don't lose any existing elements!!" oldElements := oldElements collect: [:elem | Array with: (self categoryOfElement: elem) with: elem]. newElements := newElements contents. categoryArray := newCategories. (cc := categoryArray asSet) size = categoryArray size ifFalse: ["has duplicate element" temp := categoryArray asOrderedCollection. temp removeAll: categoryArray asSet asOrderedCollection. temp do: [:dup | | tmp | tmp := dup. ii := categoryArray indexOf: tmp. [tmp := (tmp,' #2') asSymbol. cc includes: tmp] whileTrue. cc add: tmp. categoryArray at: ii put: tmp]]. categoryStops := newStops. elementArray := newElements. oldElements do: [:pair | self classify: pair last under: pair first].! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! changeFromString: aString "Parse the argument, aString, and make this be the receiver's structure." | categorySpecs | categorySpecs := Scanner new scanTokens: aString. "If nothing was scanned and I had no elements before, then default me" (categorySpecs isEmpty and: [elementArray isEmpty]) ifTrue: [^ self setDefaultList: Array new]. ^ self changeFromCategorySpecs: categorySpecs! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! classify: element under: heading self classify: element under: heading suppressIfDefault: true! ! !Categorizer methodsFor: 'accessing' stamp: 'al 11/28/2005 22:05'! classify: element under: heading suppressIfDefault: aBoolean "Store the argument, element, in the category named heading. If aBoolean is true, then invoke special logic such that the classification is NOT done if the new heading is the Default and the element already had a non-Default classification -- useful for filein" | catName catIndex elemIndex realHeading | ((heading = NullCategory) or: [heading == nil]) ifTrue: [realHeading := Default] ifFalse: [realHeading := heading asSymbol]. (catName := self categoryOfElement: element) = realHeading ifTrue: [^ self]. "done if already under that category" catName ~~ nil ifTrue: [(aBoolean and: [realHeading = Default]) ifTrue: [^ self]. "return if non-Default category already assigned in memory" self basicRemoveElement: element]. "remove if in another category" (categoryArray indexOf: realHeading) = 0 ifTrue: [self addCategory: realHeading]. catIndex := categoryArray indexOf: realHeading. elemIndex := catIndex > 1 ifTrue: [categoryStops at: catIndex - 1] ifFalse: [0]. [(elemIndex := elemIndex + 1) <= (categoryStops at: catIndex) and: [element >= (elementArray at: elemIndex)]] whileTrue. "elemIndex is now the index for inserting the element. Do the insertion before it." elementArray := elementArray copyReplaceFrom: elemIndex to: elemIndex-1 with: (Array with: element). "add one to stops for this and later categories" catIndex to: categoryArray size do: [:i | categoryStops at: i put: (categoryStops at: i) + 1]. ((categoryArray includes: Default) and: [(self listAtCategoryNamed: Default) size = 0]) ifTrue: [self removeCategory: Default]. self assertInvariant.! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! classifyAll: aCollection under: heading aCollection do: [:element | self classify: element under: heading]! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 10:20'! elementCategoryDict | dict firstIndex lastIndex | elementArray isNil ifTrue: [^ nil]. dict := Dictionary new: elementArray size. 1to: categoryStops size do: [:cat | firstIndex := self firstIndexOfCategoryNumber: cat. lastIndex := self lastIndexOfCategoryNumber: cat. firstIndex to: lastIndex do: [:el | dict at: (elementArray at: el) put: (categoryArray at: cat)]. ]. ^ dict.! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/15/2004 12:33'! isEmptyCategoryNamed: categoryName | i | i := categoryArray indexOf: categoryName ifAbsent: [^false]. ^self isEmptyCategoryNumber: i! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/15/2004 12:33'! isEmptyCategoryNumber: anInteger | firstIndex lastIndex | (anInteger < 1 or: [anInteger > categoryStops size]) ifTrue: [^ true]. firstIndex := self firstIndexOfCategoryNumber: anInteger. lastIndex := self lastIndexOfCategoryNumber: anInteger. ^ firstIndex > lastIndex! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! listAtCategoryNamed: categoryName "Answer the array of elements associated with the name, categoryName." | i | i := categoryArray indexOf: categoryName ifAbsent: [^Array new]. ^self listAtCategoryNumber: i! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/6/2004 13:51'! listAtCategoryNumber: anInteger "Answer the array of elements stored at the position indexed by anInteger. Answer nil if anInteger is larger than the number of categories." | firstIndex lastIndex | (anInteger < 1 or: [anInteger > categoryStops size]) ifTrue: [^ nil]. firstIndex := self firstIndexOfCategoryNumber: anInteger. lastIndex := self lastIndexOfCategoryNumber: anInteger. ^elementArray copyFrom: firstIndex to: lastIndex! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! numberOfCategoryOfElement: element "Answer the index of the category with which the argument, element, is associated." | categoryIndex elementIndex | categoryIndex := 1. elementIndex := 0. [(elementIndex := elementIndex + 1) <= elementArray size] whileTrue: ["point to correct category" [elementIndex > (categoryStops at: categoryIndex)] whileTrue: [categoryIndex := categoryIndex + 1]. "see if this is element" element = (elementArray at: elementIndex) ifTrue: [^categoryIndex]]. ^0! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! removeCategory: cat "Remove the category named, cat. Create an error notificiation if the category has any elements in it." | index lastStop | index := categoryArray indexOf: cat ifAbsent: [^self]. lastStop := index = 1 ifTrue: [0] ifFalse: [categoryStops at: index - 1]. (categoryStops at: index) - lastStop > 0 ifTrue: [^self error: 'cannot remove non-empty category']. categoryArray := categoryArray copyReplaceFrom: index to: index with: Array new. categoryStops := categoryStops copyReplaceFrom: index to: index with: Array new. categoryArray size = 0 ifTrue: [categoryArray := Array with: Default. categoryStops := Array with: 0] ! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/12/2004 20:50'! removeElement: element ^ self basicRemoveElement: element! ! !Categorizer methodsFor: 'accessing' stamp: 'PeterHugossonMiller 9/3/2009 00:16'! removeEmptyCategories "Remove empty categories." | categoryIndex currentStop keptCategories keptStops | keptCategories := (Array new: 16) writeStream. keptStops := (Array new: 16) writeStream. currentStop := categoryIndex := 0. [(categoryIndex := categoryIndex + 1) <= categoryArray size] whileTrue: [(categoryStops at: categoryIndex) > currentStop ifTrue: [keptCategories nextPut: (categoryArray at: categoryIndex). keptStops nextPut: (currentStop := categoryStops at: categoryIndex)]]. categoryArray := keptCategories contents. categoryStops := keptStops contents. categoryArray size = 0 ifTrue: [categoryArray := Array with: Default. categoryStops := Array with: 0] "ClassOrganizer allInstancesDo: [:co | co removeEmptyCategories]."! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! renameCategory: oldCatString toBe: newCatString "Rename a category. No action if new name already exists, or if old name does not exist." | index oldCategory newCategory | oldCategory := oldCatString asSymbol. newCategory := newCatString asSymbol. (categoryArray indexOf: newCategory) > 0 ifTrue: [^ self]. "new name exists, so no action" (index := categoryArray indexOf: oldCategory) = 0 ifTrue: [^ self]. "old name not found, so no action" categoryArray := categoryArray copy. "need to change identity so smart list update will notice the change" categoryArray at: index put: newCategory! ! !Categorizer methodsFor: 'accessing' stamp: 'NS 4/5/2004 17:44'! sortCategories | privateCategories publicCategories newCategories | privateCategories := self categories select: [:one | (one findString: 'private' startingAt: 1 caseSensitive: false) = 1]. publicCategories := self categories copyWithoutAll: privateCategories. newCategories := publicCategories asSortedCollection asOrderedCollection addAll: privateCategories asSortedCollection; asArray. self categories: newCategories! ! !Categorizer methodsFor: 'fileIn/Out' stamp: 'NS 4/5/2004 17:44'! scanFrom: aStream "Reads in the organization from the next chunk on aStream. Categories or elements not found in the definition are not affected. New elements are ignored." self changeFromString: aStream nextChunk. aStream skipStyleChunk.! ! !Categorizer methodsFor: 'printing' stamp: 'NS 4/5/2004 17:44'! printOn: aStream "Refer to the comment in Object|printOn:." | elementIndex | elementIndex := 1. 1 to: categoryArray size do: [:i | aStream nextPut: $(. (categoryArray at: i) asString printOn: aStream. [elementIndex <= (categoryStops at: i)] whileTrue: [aStream space; nextPutAll: (elementArray at: elementIndex). elementIndex := elementIndex + 1]. aStream nextPut: $); cr]! ! !Categorizer methodsFor: 'printing' stamp: 'NS 4/5/2004 17:44'! printOnStream: aStream "Refer to the comment in Object|printOn:." | elementIndex | elementIndex := 1. 1 to: categoryArray size do: [:i | aStream print: '('; write:(categoryArray at:i). " is the asString redundant? " [elementIndex <= (categoryStops at: i)] whileTrue: [aStream print:' '; write:(elementArray at: elementIndex). elementIndex := elementIndex + 1]. aStream print:')'. aStream cr]! ! !Categorizer methodsFor: 'printing' stamp: 'lr 6/22/2005 08:12'! printString ^ String streamContents: [ :stream | self printOn: stream ].! ! !Categorizer methodsFor: 'private' stamp: 'dvf 8/11/2005 22:38'! assertInvariant self assert: (elementArray size = categoryStops last)! ! !Categorizer methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 00:15'! basicRemoveElement: element "Remove the selector, element, from all categories." | categoryIndex elementIndex nextStop newElements | categoryIndex := 1. elementIndex := 0. nextStop := 0. "nextStop keeps track of the stops in the new element array" newElements := (Array new: elementArray size) writeStream. [(elementIndex := elementIndex + 1) <= elementArray size] whileTrue: [[elementIndex > (categoryStops at: categoryIndex)] whileTrue: [categoryStops at: categoryIndex put: nextStop. categoryIndex := categoryIndex + 1]. (elementArray at: elementIndex) = element ifFalse: [nextStop := nextStop + 1. newElements nextPut: (elementArray at: elementIndex)]]. [categoryIndex <= categoryStops size] whileTrue: [categoryStops at: categoryIndex put: nextStop. categoryIndex := categoryIndex + 1]. elementArray := newElements contents. self assertInvariant.! ! !Categorizer methodsFor: 'private' stamp: 'NS 4/5/2004 17:44'! elementArray ^ elementArray! ! !Categorizer methodsFor: 'private' stamp: 'NS 4/6/2004 13:51'! firstIndexOfCategoryNumber: anInteger anInteger < 1 ifTrue: [^ nil]. ^ (anInteger > 1 ifTrue: [(categoryStops at: anInteger - 1) + 1] ifFalse: [1]).! ! !Categorizer methodsFor: 'private' stamp: 'NS 4/6/2004 13:52'! lastIndexOfCategoryNumber: anInteger anInteger > categoryStops size ifTrue: [^ nil]. ^ categoryStops at: anInteger! ! !Categorizer methodsFor: 'private' stamp: 'NS 4/5/2004 17:50'! setDefaultList: aSortedCollection categoryArray := Array with: Default. categoryStops := Array with: aSortedCollection size. elementArray := aSortedCollection asArray! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Categorizer class instanceVariableNames: ''! !Categorizer class methodsFor: 'class initialization' stamp: 'eem 1/7/2009 16:04'! allCategory "Return a symbol that represents the virtual all methods category." ^#'-- all --'! ! !Categorizer class methodsFor: 'class initialization' stamp: 'NS 4/5/2004 17:44'! default ^ Default! ! !Categorizer class methodsFor: 'class initialization' stamp: 'NS 4/6/2004 11:48'! initialize " self initialize " Default := 'as yet unclassified' asSymbol. NullCategory := 'no messages' asSymbol.! ! !Categorizer class methodsFor: 'class initialization' stamp: 'NS 4/5/2004 17:44'! nullCategory ^ NullCategory! ! !Categorizer class methodsFor: 'documentation' stamp: 'NS 4/5/2004 17:44'! documentation "Instances consist of an Array of category names (categoryArray), each of which refers to an Array of elements (elementArray). This association is made through an Array of stop indices (categoryStops), each of which is the index in elementArray of the last element (if any) of the corresponding category. For example: categories := Array with: 'firstCat' with: 'secondCat' with: 'thirdCat'. stops := Array with: 1 with: 4 with: 4. elements := Array with: #a with: #b with: #c with: #d. This means that category firstCat has only #a, secondCat has #b, #c, and #d, and thirdCat has no elements. This means that stops at: stops size must be the same as elements size." ! ! !Categorizer class methodsFor: 'housekeeping' stamp: 'NS 4/6/2004 11:48'! sortAllCategories self allSubInstances do: [:x | x sortCategories]! ! !Categorizer class methodsFor: 'instance creation' stamp: 'NS 4/5/2004 17:44'! defaultList: aSortedCollection "Answer an instance of me with initial elements from the argument, aSortedCollection." ^self new setDefaultList: aSortedCollection! ! SystemChangeTestRoot subclass: #ChangeHooksTest instanceVariableNames: 'previousChangeSet testsChangeSet capturedEvents generatedTestClass generatedTestClassX createdMethodName createdMethod doItExpression' classVariableNames: '' poolDictionaries: '' category: 'Tests-SystemChangeNotification'! !ChangeHooksTest commentStamp: 'rw 4/5/2006 17:14' prior: 0! This class implements unit tests to verify that when the system changes, notification messages are sent around correctly. Therefore the test messages make a system change, after registering to receive an event ater the change occured. In this event (sent immediately after the change), the actual assertions take place. Note that the system changes are *really* made to the system, but in a change set that is created in the setUp method, while the previous one is restored in the tearDown method.! !ChangeHooksTest methodsFor: 'events-classes' stamp: 'rw 4/5/2006 17:15'! classCommentedEvent: event self addSingleEvent: event. self assert: generatedTestClass comment = self commentStringForTesting. self checkEvent: event kind: #Commented item: generatedTestClass itemKind: AbstractEvent classKind! ! !ChangeHooksTest methodsFor: 'events-classes' stamp: 'rw 4/5/2006 17:15'! classCreationEvent: event | classCreated | self addSingleEvent: event. classCreated := Smalltalk classNamed: self newlyCreatedClassName. self assert: classCreated notNil. self assert: ((Smalltalk organization listAtCategoryNamed: #'System-Change Notification') includes: self newlyCreatedClassName). self checkEvent: event kind: #Added item: classCreated itemKind: AbstractEvent classKind! ! !ChangeHooksTest methodsFor: 'events-classes' stamp: 'rw 4/5/2006 17:15'! classRecategorizedEvent: event self addSingleEvent: event. self checkEvent: event kind: #Recategorized item: generatedTestClass itemKind: AbstractEvent classKind. self assert: event oldCategory = #'System-Change Notification'! ! !ChangeHooksTest methodsFor: 'events-classes' stamp: 'rw 4/5/2006 17:15'! classRedefinitionEvent: event self addSingleEvent: event. self checkEvent: event kind: #Modified item: generatedTestClass itemKind: AbstractEvent classKind.! ! !ChangeHooksTest methodsFor: 'events-classes' stamp: 'rw 4/5/2006 17:16'! classRemovalEvent: event "This event used to be sent efter the class was removed. This was changed, and therefore this test is useless currently." self addSingleEvent: event. self assert: (Smalltalk classNamed: self generatedTestClassName) isNil. self checkEvent: event kind: #Removed item: self generatedTestClassName itemKind: AbstractEvent classKind! ! !ChangeHooksTest methodsFor: 'events-classes' stamp: 'rw 4/5/2006 17:16'! classRenameEvent: event | renamedClass | self addSingleEvent: event. renamedClass := Smalltalk classNamed: self renamedTestClassName. self assert: renamedClass notNil. self assert: (Smalltalk classNamed: self generatedTestClassName) isNil. self checkEvent: event kind: #Renamed item: renamedClass itemKind: AbstractEvent classKind. self assert: event oldName = self generatedTestClassName! ! !ChangeHooksTest methodsFor: 'events-classes' stamp: 'rw 4/5/2006 17:16'! classSuperChangedEvent: event self addSingleEvent: event. self checkEvent: event kind: #Modified item: generatedTestClass itemKind: AbstractEvent classKind. self assert: generatedTestClass superclass = Model! ! !ChangeHooksTest methodsFor: 'events-expression' stamp: 'rw 4/5/2006 17:16'! methodDoItEvent1: event self addSingleEvent: event. self checkEvent: event kind: #DoIt item: doItExpression itemKind: AbstractEvent expressionKind. self assert: event context isNil.! ! !ChangeHooksTest methodsFor: 'events-general' stamp: 'rw 8/1/2003 17:11'! rememberEvent: event capturedEvents add: event! ! !ChangeHooksTest methodsFor: 'events-general' stamp: 'rw 8/1/2003 16:41'! shouldNotBeCalledEvent: anEvent "This event should not be called, so fail the test." self assert: false! ! !ChangeHooksTest methodsFor: 'events-instance variables' stamp: 'rw 4/5/2006 17:16'! instanceVariableCreationEvent: event self addSingleEvent: event. self assert: event isModified. self assert: event item = generatedTestClass. self assert: event itemKind = AbstractEvent classKind. self assert: event areInstVarsModified. self deny: event isSuperclassModified. self deny: event areClassVarsModified. self deny: event areSharedPoolsModified. ! ! !ChangeHooksTest methodsFor: 'events-instance variables' stamp: 'rw 4/5/2006 17:18'! instanceVariableRemovedEvent: event self addSingleEvent: event. self assert: event isModified. self assert: event item = generatedTestClassX. self assert: event itemKind = AbstractEvent classKind. self assert: event areInstVarsModified. self deny: event isSuperclassModified. self deny: event areClassVarsModified. self deny: event areSharedPoolsModified. ! ! !ChangeHooksTest methodsFor: 'events-methods' stamp: 'rw 4/5/2006 17:18'! methodCreationEvent1: event | methodCreated | self addSingleEvent: event. self shouldnt: [methodCreated := generatedTestClass >> createdMethodName] raise: Error. self checkEvent: event kind: #Added item: methodCreated itemKind: AbstractEvent methodKind! ! !ChangeHooksTest methodsFor: 'events-methods' stamp: 'rw 4/5/2006 17:18'! methodCreationEvent2: event | methodCreated | self addSingleEvent: event. self shouldnt: [methodCreated := generatedTestClass >> createdMethodName] raise: Error. self checkEvent: event kind: #Added item: methodCreated itemKind: AbstractEvent methodKind! ! !ChangeHooksTest methodsFor: 'events-methods' stamp: 'rw 4/5/2006 17:18'! methodRecategorizationEvent: event | methodCreated | self addSingleEvent: event. self shouldnt: [methodCreated := generatedTestClass >> createdMethodName] raise: Error. self assert: ((generatedTestClass organization categoryOfElement: createdMethodName) = #newCategory). self assert: event oldCategory = #testing. self checkEvent: event kind: #Recategorized item: methodCreated itemKind: AbstractEvent methodKind.! ! !ChangeHooksTest methodsFor: 'events-methods' stamp: 'rw 4/5/2006 17:18'! methodRemovedEvent1: event self addSingleEvent: event. self should: [generatedTestClass >> createdMethodName] raise: Error. self checkEvent: event kind: #Removed item: createdMethod itemKind: AbstractEvent methodKind. event itemClass = generatedTestClass. event itemMethod = createdMethodName. self assert: ((generatedTestClass organization categoryOfElement: createdMethodName) isNil).! ! !ChangeHooksTest methodsFor: 'events-methods' stamp: 'rw 4/5/2006 17:18'! methodRemovedEvent2: event self methodRemovedEvent1: event! ! !ChangeHooksTest methodsFor: 'running' stamp: 'rw 4/4/2006 22:59'! setUp previousChangeSet := ChangeSet current. testsChangeSet := ChangeSet new. ChangeSet newChanges: testsChangeSet. capturedEvents := OrderedCollection new. self generateTestClass. self generateTestClassX. super setUp! ! !ChangeHooksTest methodsFor: 'running' stamp: 'rw 4/5/2006 17:23'! tearDown super tearDown. self removeGeneratedTestClasses. ChangeSet newChanges: previousChangeSet. ChangeSorter removeChangeSet: testsChangeSet. previousChangeSet := nil. testsChangeSet := nil. ! ! !ChangeHooksTest methodsFor: 'testing-classes' stamp: 'rw 4/5/2006 17:19'! testClassCommentedEvent self systemChangeNotifier notify: self ofAllSystemChangesUsing: #classCommentedEvent:. generatedTestClass comment: self commentStringForTesting. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-classes' stamp: 'rw 4/5/2006 17:19'! testClassCreationEvent self systemChangeNotifier notify: self ofAllSystemChangesUsing: #classCreationEvent:. Object subclass: self newlyCreatedClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-classes' stamp: 'rw 4/5/2006 17:19'! testClassRecategorizedEvent1 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #classRecategorizedEvent:. Object subclass: generatedTestClass name instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Collections-Abstract'. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-classes' stamp: 'rw 4/5/2006 17:19'! testClassRecategorizedEvent2 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #classRecategorizedEvent:. generatedTestClass category: 'Collections-Abstract'. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-classes' stamp: 'rw 4/5/2006 17:19'! testClassRedefinition self systemChangeNotifier notify: self ofAllSystemChangesUsing: #classRedefinitionEvent:. self generateTestClass! ! !ChangeHooksTest methodsFor: 'testing-classes' stamp: 'rw 4/5/2006 17:20'! testClassRemovalEvent "This event used to be sent efter the class was removed. This was changed, and therefore this test is useless currently." "Keep it, since I really want to check with the responsible for the ChangeSet, and it is very likely this will be reintroduced afterwards!!" " | createdClass | createdClass := self compileUniqueClass. self systemChangeNotifier notify: self ofAllSystemChangesUsing: #classRemovalEvent:. createdClass removeFromSystem. self checkForOnlySingleEvent "! ! !ChangeHooksTest methodsFor: 'testing-classes' stamp: 'rw 4/5/2006 17:20'! testClassRenamedEvent self systemChangeNotifier notify: self ofAllSystemChangesUsing: #classRenameEvent:. generatedTestClass rename: self renamedTestClassName. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-classes' stamp: 'rw 4/5/2006 17:20'! testClassSuperChangedEvent self systemChangeNotifier notify: self ofAllSystemChangesUsing: #classSuperChangedEvent:. Model subclass: generatedTestClass name instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-expression' stamp: 'rw 4/5/2006 17:20'! testDoItEvent1 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #methodDoItEvent1:. doItExpression := '1 + 2'. Compiler evaluate: doItExpression logged: true. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-expression' stamp: 'rw 4/5/2006 17:20'! testDoItEvent2 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #shouldNotBeCalledEvent:. doItExpression := '1 + 2'. Compiler evaluate: doItExpression logged: false.! ! !ChangeHooksTest methodsFor: 'testing-instance variables' stamp: 'rw 4/5/2006 17:20'! testInstanceVariableCreationEvent1 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #instanceVariableCreationEvent:. Object subclass: self generatedTestClassName instanceVariableNames: 'x' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-instance variables' stamp: 'rw 4/5/2006 17:17'! testInstanceVariableCreationEvent2 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #instanceVariableCreationEvent:. generatedTestClass addInstVarName: 'x'. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-instance variables' stamp: 'rw 4/5/2006 17:18'! testInstanceVariableRemovedEvent1 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #instanceVariableRemovedEvent:. Object subclass: generatedTestClassX name instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-instance variables' stamp: 'rw 4/5/2006 17:17'! testInstanceVariableRemovedEvent2 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #instanceVariableRemovedEvent:. generatedTestClassX removeInstVarName: 'x'. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-instance variables' stamp: 'rw 4/5/2006 17:21'! testInstanceVariableRenamedSilently self systemChangeNotifier notify: self ofAllSystemChangesUsing: #shouldNotBeCalledEvent:. generatedTestClassX renameSilentlyInstVar: 'x' to: 'y'! ! !ChangeHooksTest methodsFor: 'testing-methods' stamp: 'rw 4/5/2006 17:21'! testMethodCreationEvent1 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #methodCreationEvent1:. createdMethodName := #testCreation. generatedTestClass compile: createdMethodName , ' ^1'. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-methods' stamp: 'rw 4/5/2006 17:21'! testMethodCreationEvent2 self systemChangeNotifier notify: self ofAllSystemChangesUsing: #methodCreationEvent2:. createdMethodName := #testCreation. generatedTestClass compile: createdMethodName , ' ^1' classified: #testing. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-methods' stamp: 'rw 4/5/2006 17:21'! testMethodRecategorizationEvent createdMethodName := #testCreation. generatedTestClass compile: createdMethodName , ' ^1' classified: #testing. self systemChangeNotifier notify: self ofAllSystemChangesUsing: #methodRecategorizationEvent:. generatedTestClass organization classify: createdMethodName under: #newCategory suppressIfDefault: false. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-methods' stamp: 'rw 4/5/2006 17:21'! testMethodRemovedEvent1 createdMethodName := #testCreation. generatedTestClass compile: createdMethodName , ' ^1'. createdMethod := generatedTestClass >> createdMethodName. self systemChangeNotifier notify: self ofAllSystemChangesUsing: #methodRemovedEvent1:. generatedTestClass removeSelector: createdMethodName. self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'testing-methods' stamp: 'rw 4/5/2006 17:21'! testMethodRemovedEvent2 createdMethodName := #testCreation. generatedTestClass compile: createdMethodName , ' ^1'. createdMethod := generatedTestClass >> createdMethodName. self systemChangeNotifier notify: self ofAllSystemChangesUsing: #methodRemovedEvent2:. Smalltalk removeSelector: (Array with: generatedTestClass name with: createdMethodName). self checkForOnlySingleEvent! ! !ChangeHooksTest methodsFor: 'private' stamp: 'rw 8/1/2003 17:03'! addSingleEvent: anEvent capturedEvents isEmpty ifFalse: [self assert: false]. capturedEvents add: anEvent! ! !ChangeHooksTest methodsFor: 'private' stamp: 'rw 7/11/2003 09:55'! checkEvent: anEvent kind: changeKind item: item itemKind: itemKind self assert: (anEvent perform: ('is' , changeKind) asSymbol). self assert: anEvent item = item. self assert: anEvent itemKind = itemKind! ! !ChangeHooksTest methodsFor: 'private' stamp: 'rw 8/1/2003 17:01'! checkForOnlySingleEvent self assert: capturedEvents size = 1! ! !ChangeHooksTest methodsFor: 'private' stamp: 'rw 7/2/2003 18:07'! commentStringForTesting ^'Added this comment as part of the unit test in SystemChangeTest>>testClassCommentedBasicEvents. You should never see this, unless you are debugging the system somewhere in between the tests.'! ! !ChangeHooksTest methodsFor: 'private' stamp: 'rw 4/5/2006 17:22'! removeGeneratedTestClasses "Remove all classes that were possibly generated during testing." | possiblyToRemove | possiblyToRemove := OrderedCollection with: self generatedTestClassName with: self generatedTestClassNameX with: self renamedTestClassName with: self newlyCreatedClassName. possiblyToRemove do: [:name | (Smalltalk hasClassNamed: name) ifTrue: [(Smalltalk at: name) removeFromSystemUnlogged]]! ! !ChangeHooksTest methodsFor: 'private-generation' stamp: 'rw 4/4/2006 21:41'! generateTestClass generatedTestClass := Object subclass: self generatedTestClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'.! ! !ChangeHooksTest methodsFor: 'private-generation' stamp: 'rw 4/4/2006 21:41'! generateTestClassX generatedTestClassX := Object subclass: self generatedTestClassNameX instanceVariableNames: 'x' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'.! ! !ChangeHooksTest methodsFor: 'private-generation' stamp: 'rw 4/4/2006 22:10'! generatedTestClassName ^#'AutoGeneratedClassForTestingSystemChanges'! ! !ChangeHooksTest methodsFor: 'private-generation' stamp: 'rw 4/4/2006 22:10'! generatedTestClassNameX ^#'AutoGeneratedClassXForTestingSystemChanges'! ! !ChangeHooksTest methodsFor: 'private-generation' stamp: 'rw 4/4/2006 22:18'! newlyCreatedClassName ^#'AutoGeneratedClassWhileTestingSystemChanges'! ! !ChangeHooksTest methodsFor: 'private-generation' stamp: 'rw 4/4/2006 22:10'! renamedTestClassName ^#'AutoRenamedClassForTestingSystemChanges'! ! CodeHolder subclass: #ChangeList instanceVariableNames: 'changeList list listIndex listSelections file lostMethodPointer showsVersions' classVariableNames: '' poolDictionaries: '' category: 'Tools-Changes'! !ChangeList commentStamp: '' prior: 0! A ChangeList represents a list of changed methods that reside on a file in fileOut format. The classes and methods in my list are not necessarily in this image!! Used as the model for both Version Lists and Changed Methods (in Screen Menu, Changes...). Note that the two kinds of window have different controller classes!!!! It holds three lists: changeList - a list of ChangeRecords list - a list of one-line printable headers listSelections - a list of Booleans (true = selected, false = not selected) multiple OK. listIndex Items that are removed (removeDoits, remove an item) are removed from all three lists. Most recently clicked item is the one showing in the bottom pane.! !ChangeList methodsFor: '*Polymorph-Tools-Diff-override' stamp: 'gvc 9/2/2008 15:47'! compareToCurrentVersion "If the current selection corresponds to a method in the system, then spawn a window showing the diffs as text" | change class s1 s2 | listIndex = 0 ifTrue: [^ self]. change := changeList at: listIndex. ((class := change methodClass) notNil and: [class includesSelector: change methodSelector]) ifTrue: [s1 := (class sourceCodeAt: change methodSelector) asString. s2 := change string. s1 = s2 ifTrue: [^ self inform: 'Exact Match']. (DiffMorph from: s2 to: s1 contextClass: class) openInWindowLabeled: 'Comparison to Current Version'] ifFalse: [self flash]! ! !ChangeList methodsFor: '*monticello' stamp: 'stephaneducasse 2/4/2006 20:47'! changeTo: changeSubset | newList newChangeList | newChangeList := OrderedCollection new. newList := OrderedCollection new. 1 to: changeList size do: [:i | (changeSubset includes: (changeList at: i)) ifTrue: [newChangeList add: (changeList at: i). newList add: (list at: i)]]. newChangeList size < changeList size ifTrue: [changeList := newChangeList. list := newList. listIndex := 0. listSelections := Array new: list size withAll: false]. self changed: #list ! ! !ChangeList methodsFor: 'accessing'! changeList ^ changeList! ! !ChangeList methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:26'! changes: changeRecords file: aFile file := aFile. changeList := OrderedCollection new. list := OrderedCollection new. listIndex := 0. changeRecords do: [:each | (each respondsTo: #methodClass) ifFalse: [self addItem: ChangeRecord new text: each asString] ifTrue: [self addItem: each text: ('method: ' , each methodClass name , (each isMetaClassChange ifTrue: [' class '] ifFalse: [' ']) , each methodSelector , '; ' , each stamp)]]. listSelections := Array new: list size withAll: false! ! !ChangeList methodsFor: 'accessing' stamp: 'ls 5/12/1999 07:55'! currentChange "return the current change being viewed, or nil if none" listIndex = 0 ifTrue: [ ^nil ]. ^changeList at: listIndex! ! !ChangeList methodsFor: 'accessing'! file ^file! ! !ChangeList methodsFor: 'accessing' stamp: 'TPR 11/28/1998 17:38'! listHasSingleEntry "does the list of changes have only a single item?" ^list size = 1! ! !ChangeList methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:26'! listSelections listSelections ifNil: [ list ifNotNil: [ listSelections := Array new: list size withAll: false]]. ^ listSelections! ! !ChangeList methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:26'! setLostMethodPointer: sourcePointer lostMethodPointer := sourcePointer! ! !ChangeList methodsFor: 'accessing' stamp: 'sw 10/19/1999 15:11'! showsVersions ^ false! ! !ChangeList methodsFor: 'initialization-release' stamp: 'sd 11/20/2005 21:26'! addItem: item text: text | cr | cr := Character cr. changeList addLast: item. list addLast: (text collect: [:x | x = cr ifTrue: [$/] ifFalse: [x]])! ! !ChangeList methodsFor: 'initialization-release' stamp: 'sw 1/7/2000 12:42'! changeListButtonSpecs ^#( ('select all' selectAll 'select all entries') ('deselect all' deselectAll 'deselect all entries') ('select conflicts' selectAllConflicts 'select all methods that occur in any change set') ('file in selections' fileInSelections 'file in all selected entries') )! ! !ChangeList methodsFor: 'initialization-release' stamp: 'sd 11/20/2005 21:26'! initialize "Initialize a blank ChangeList. Set the contentsSymbol to reflect whether diffs will initally be shown or not" contentsSymbol := Preferences diffsInChangeList ifTrue: [self defaultDiffsSymbol] ifFalse: [#source]. changeList := OrderedCollection new. list := OrderedCollection new. listIndex := 0. super initialize! ! !ChangeList methodsFor: 'initialization-release' stamp: 'sd 11/20/2005 21:26'! openAsMorphName: labelString multiSelect: multiSelect "Open a morphic view for the messageSet, whose label is labelString. The listView may be either single or multiple selection type" | window listHeight listPane | listHeight := 0.4. window := (SystemWindow labelled: labelString) model: self. listPane := multiSelect ifTrue: [PluggableListMorphOfMany on: self list: #list primarySelection: #listIndex changePrimarySelection: #toggleListIndex: listSelection: #listSelectionAt: changeListSelection: #listSelectionAt:put: menu: (self showsVersions ifTrue: [#versionsMenu:] ifFalse: [#changeListMenu:])] ifFalse: [PluggableListMorph on: self list: #list selected: #listIndex changeSelected: #toggleListIndex: menu: (self showsVersions ifTrue: [#versionsMenu:] ifFalse: [#changeListMenu:])]. listPane keystrokeActionSelector: #changeListKey:from:. window addMorph: listPane frame: (0 @ 0 extent: 1 @ listHeight). self addLowerPanesTo: window at: (0 @ listHeight corner: 1 @ 1) with: nil. ^ window openInWorld! ! !ChangeList methodsFor: 'initialization-release' stamp: 'nice 4/16/2009 09:39'! optionalButtonRow "Answer a row of buttons to occur in a tool pane" | aRow | aRow := AlignmentMorph newRow. aRow hResizing: #spaceFill. aRow clipSubmorphs: true. aRow layoutInset: 2@2; cellInset: 3. aRow wrapCentering: #center; cellPositioning: #leftCenter. self changeListButtonSpecs do: [:triplet | | aButton | aButton := PluggableButtonMorph on: self getState: nil action: triplet second. aButton hResizing: #spaceFill; vResizing: #spaceFill; label: triplet first asString; askBeforeChanging: true; onColor: Color white offColor: Color white. aRow addMorphBack: aButton. aButton setBalloonText: triplet third]. aRow addMorphBack: self regularDiffButton. self wantsPrettyDiffOption ifTrue: [aRow addMorphBack: self prettyDiffButton]. ^ aRow! ! !ChangeList methodsFor: 'initialization-release' stamp: 'sw 8/15/2002 22:34'! wantsPrettyDiffOption "Answer whether pretty-diffs are meaningful for this tool" ^ true! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! browseAllVersionsOfSelections "Opens a Versions browser on all the currently selected methods, showing each alongside all of their historical versions." | oldSelection aList | oldSelection := self listIndex. aList := OrderedCollection new. Cursor read showWhile: [ 1 to: changeList size do: [:i | (listSelections at: i) ifTrue: [ listIndex := i. self browseVersions. aList add: i. ]]]. listIndex := oldSelection. aList size == 0 ifTrue: [^ self inform: 'no selected methods have in-memory counterparts']. ! ! !ChangeList methodsFor: 'menu actions' stamp: 'eem 6/11/2008 16:45'! browseCurrentVersionsOfSelections "Opens a message-list browser on the current in-memory versions of all methods that are currently seleted" | aList | aList := OrderedCollection new. Cursor read showWhile: [ 1 to: changeList size do: [:i | (listSelections at: i) ifTrue: [ | aClass aChange | aChange := changeList at: i. (aChange type = #method and: [(aClass := aChange methodClass) notNil and: [aClass includesSelector: aChange methodSelector]]) ifTrue: [ aList add: ( MethodReference new setStandardClass: aClass methodSymbol: aChange methodSelector ) ]]]]. aList size == 0 ifTrue: [^ self inform: 'no selected methods have in-memory counterparts']. MessageSet openMessageList: aList name: 'Current versions of selected methods in ', file localName! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! browseVersions | change class browser | listIndex = 0 ifTrue: [^ nil ]. change := changeList at: listIndex. ((class := change methodClass) notNil and: [class includesSelector: change methodSelector]) ifFalse: [ ^nil ]. browser := super browseVersions. browser ifNotNil: [ browser addedChangeRecord: change ]. ^browser! ! !ChangeList methodsFor: 'menu actions' stamp: 'nk 6/2/2006 08:03'! buildMorphicCodePaneWith: editString | codePane | codePane := AcceptableCleanTextMorph on: self text: #contents accept: #contents: readSelection: #contentsSelection menu: #codePaneMenu:shifted:. codePane font: Preferences standardCodeFont. editString ifNotNil: [ codePane editString: editString. codePane hasUnacceptedEdits: true ]. ^codePane ! ! !ChangeList methodsFor: 'menu actions' stamp: 'sw 1/25/2001 07:22'! changeListKey: aChar from: view "Respond to a Command key in the list pane." aChar == $D ifTrue: [^ self toggleDiffing]. aChar == $a ifTrue: [^ self selectAll]. ^ self arrowKey: aChar from: view! ! !ChangeList methodsFor: 'menu actions' stamp: 'alain.plantec 5/30/2008 10:39'! changeListMenu: aMenu "Fill aMenu up so that it comprises the primary changelist-browser menu" aMenu addTitle: 'change list'. aMenu addStayUpItemSpecial. aMenu addList: #( ('fileIn selections' fileInSelections 'import the selected items into the image') ('fileOut selections... ' fileOutSelections 'create a new file containing the selected items') - ('compare to current' compareToCurrentVersion 'open a separate window which shows the text differences between the on-file version and the in-image version.' ) ('toggle diffing (D)' toggleDiffing 'start or stop showing diffs in the code pane.') - ('select conflicts with any changeset' selectAllConflicts 'select methods in the file which also occur in any change-set in the system') ('select conflicts with current changeset' selectConflicts 'select methods in the file which also occur in the current change-set') ('select conflicts with...' selectConflictsWith 'allows you to designate a file or change-set against which to check for code conflicts.') - ('select unchanged methods' selectUnchangedMethods 'select methods in the file whose in-image versions are the same as their in-file counterparts' ) ('select new methods' selectNewMethods 'select methods in the file that do not current occur in the image') ('select methods for this class' selectMethodsForThisClass 'select all methods in the file that belong to the currently-selected class') - ('select all (a)' selectAll 'select all the items in the list') ('deselect all' deselectAll 'deselect all the items in the list') ('invert selections' invertSelections 'select every item that is not currently selected, and deselect every item that *is* currently selected') - ('browse all versions of single selection' browseVersions 'open a version browser showing the versions of the currently selected method') ('browse all versions of selections' browseAllVersionsOfSelections 'open a version browser showing all the versions of all the selected methods') ('browse current versions of selections' browseCurrentVersionsOfSelections 'open a message-list browser showing the current (in-image) counterparts of the selected methods') ('destroy current methods of selections' destroyCurrentCodeOfSelections 'remove (*destroy*) the in-image counterparts of all selected methods') - ('remove doIts' removeDoIts 'remove all items that are doIts rather than methods') ('remove older versions' removeOlderMethodVersions 'remove all but the most recent versions of methods in the list') ('remove up-to-date versions' removeExistingMethodVersions 'remove all items whose code is the same as the counterpart in-image code') ('remove selected items' removeSelections 'remove the selected items from the change-list') ('remove unselected items' removeNonSelections 'remove all the items not currently selected from the change-list')). ^ aMenu ! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! deselectAll "Deselect all items in the list pane, and clear the code pane" listIndex := 0. listSelections atAllPut: false. self changed: #allSelections. self contentsChanged! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! destroyCurrentCodeOfSelections "Actually remove from the system any in-memory methods with class and selector identical to items current selected. This may seem rather arcane but believe me it has its great uses, when trying to split out code. To use effectively, first file out a change set that you wish to split off. Then open a ChangeList browser on that fileout. Now look through the methods, and select any of them which you want to remove completely from the system, then issue this command. For those methods where you have made changes to pre-existing versions, of course, you won't want to remove them from the system, so use this mechanism with care!!" | aClass aChange aList | aList := OrderedCollection new. 1 to: changeList size do: [:index | (listSelections at: index) ifTrue: [aChange := changeList at: index. (aChange type = #method and: [(aClass := aChange methodClass) notNil and: [aClass includesSelector: aChange methodSelector]]) ifTrue: [aList add: {aClass. aChange methodSelector}]]]. aList size > 0 ifTrue: [(self confirm: 'Warning!! This will actually remove ', aList size printString, ' method(s) from the system!!') ifFalse: [^ self]]. aList do: [:aPair | Transcript cr; show: 'Removed: ', aPair first printString, '.', aPair second. aPair first removeSelector: aPair second]! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! fileInSelections | any | any := false. listSelections with: changeList do: [:selected :item | selected ifTrue: [any := true. item fileIn]]. any ifFalse: [self inform: 'nothing selected, so nothing done']! ! !ChangeList methodsFor: 'menu actions' stamp: 'PeterHugossonMiller 9/3/2009 00:17'! fileOutSelections | fileName internalStream | fileName := UIManager default request: 'Enter the base of file name' initialAnswer: 'Filename'. internalStream := (String new: 1000) writeStream. internalStream header; timeStamp. listSelections with: changeList do: [:selected :item | selected ifTrue: [item fileOutOn: internalStream]]. FileStream writeSourceCodeFrom: internalStream baseName: fileName isSt: true ! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! invertSelections "Invert the selectedness of each item in the changelist" listSelections := listSelections collect: [ :ea | ea not]. listIndex := 0. self changed: #allSelections. self contentsChanged! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! removeDoIts "Remove doits from the receiver, other than initializes. 1/26/96 sw" | newChangeList newList | newChangeList := OrderedCollection new. newList := OrderedCollection new. changeList with: list do: [:chRec :str | (chRec type ~~ #doIt or: [str endsWith: 'initialize']) ifTrue: [newChangeList add: chRec. newList add: str]]. newChangeList size < changeList size ifTrue: [changeList := newChangeList. list := newList. listIndex := 0. listSelections := Array new: list size withAll: false]. self changed: #list. ! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! removeExistingMethodVersions "Remove all up to date version of entries from the receiver" | newChangeList newList str keep cls sel | newChangeList := OrderedCollection new. newList := OrderedCollection new. changeList with: list do:[:chRec :strNstamp | keep := true. (cls := chRec methodClass) ifNotNil:[ str := chRec string. sel := cls parserClass new parseSelector: str. keep := (cls sourceCodeAt: sel ifAbsent:['']) asString ~= str. ]. keep ifTrue:[ newChangeList add: chRec. newList add: strNstamp]]. newChangeList size < changeList size ifTrue: [changeList := newChangeList. list := newList. listIndex := 0. listSelections := Array new: list size withAll: false]. self changed: #list! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! removeNonSelections "Remove the unselected items from the receiver." | newChangeList newList | newChangeList := OrderedCollection new. newList := OrderedCollection new. 1 to: changeList size do: [:i | (listSelections at: i) ifTrue: [newChangeList add: (changeList at: i). newList add: (list at: i)]]. newChangeList size == 0 ifTrue: [^ self inform: 'That would remove everything. Why would you want to do that?']. newChangeList size < changeList size ifTrue: [changeList := newChangeList. list := newList. listIndex := 0. listSelections := Array new: list size withAll: false]. self changed: #list ! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! removeOlderMethodVersions "Remove older versions of entries from the receiver." | newChangeList newList found str | newChangeList := OrderedCollection new. newList := OrderedCollection new. found := OrderedCollection new. changeList reverseWith: list do: [:chRec :strNstamp | str := strNstamp copyUpTo: $;. (found includes: str) ifFalse: [found add: str. newChangeList add: chRec. newList add: strNstamp]]. newChangeList size < changeList size ifTrue: [changeList := newChangeList reversed. list := newList reversed. listIndex := 0. listSelections := Array new: list size withAll: false]. self changed: #list! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! removeSelections "Remove the selected items from the receiver. 9/18/96 sw" | newChangeList newList | newChangeList := OrderedCollection new. newList := OrderedCollection new. 1 to: changeList size do: [:i | (listSelections at: i) ifFalse: [newChangeList add: (changeList at: i). newList add: (list at: i)]]. newChangeList size < changeList size ifTrue: [changeList := newChangeList. list := newList. listIndex := 0. listSelections := Array new: list size withAll: false]. self changed: #list ! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! selectAll listIndex := 0. listSelections atAllPut: true. self changed: #allSelections! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! selectAllConflicts "Selects all method definitions in the receiver which are also in any existing change set in the system. This makes no statement about whether the content of the methods differ, only whether there is a change represented." | aClass aChange | Cursor read showWhile: [1 to: changeList size do: [:i | aChange := changeList at: i. listSelections at: i put: (aChange type = #method and: [(aClass := aChange methodClass) notNil and: [ChangeSorter doesAnyChangeSetHaveClass: aClass andSelector: aChange methodSelector]])]]. self changed: #allSelections! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! selectConflicts "Selects all method definitions for which there is ALSO an entry in changes" | change class | Cursor read showWhile: [1 to: changeList size do: [:i | change := changeList at: i. listSelections at: i put: (change type = #method and: [(class := change methodClass) notNil and: [(ChangeSet current atSelector: change methodSelector class: class) ~~ #none]])]]. self changed: #allSelections! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! selectConflicts: changeSetOrList "Selects all method definitions for which there is ALSO an entry in the specified changeSet or changList" | change class systemChanges | Cursor read showWhile: [(changeSetOrList isKindOf: ChangeSet) ifTrue: [ 1 to: changeList size do: [:i | change := changeList at: i. listSelections at: i put: (change type = #method and: [(class := change methodClass) notNil and: [(changeSetOrList atSelector: change methodSelector class: class) ~~ #none]])]] ifFalse: ["a ChangeList" 1 to: changeList size do: [:i | change := changeList at: i. listSelections at: i put: (change type = #method and: [(class := change methodClass) notNil and: [changeSetOrList list includes: (list at: i)]])]] ]. self changed: #allSelections! ! !ChangeList methodsFor: 'menu actions' stamp: 'PeterHugossonMiller 9/3/2009 00:17'! selectConflictsWith "Selects all method definitions for which there is ALSO an entry in the specified changeSet or changList chosen by the user. 4/11/96 tk" | aStream all index | aStream := (String new: 200) writeStream. (all := ChangeSorter allChangeSets copy) do: [:sel | aStream nextPutAll: (sel name contractTo: 40); cr]. ChangeList allSubInstancesDo: [:sel | aStream nextPutAll: (sel file name); cr. all addLast: sel]. aStream skip: -1. index := (UIManager default chooseFrom: (aStream contents substrings)). index > 0 ifTrue: [ self selectConflicts: (all at: index)]. ! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! selectMethodsForThisClass | name | self currentChange ifNil: [ ^self ]. name := self currentChange methodClassName. name ifNil: [ ^self ]. ^self selectSuchThat: [ :change | change methodClassName = name ].! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! selectNewMethods "Selects all method definitions for which there is no counterpart method in the current image" | change class | Cursor read showWhile: [1 to: changeList size do: [:i | change := changeList at: i. listSelections at: i put: ((change type = #method and: [((class := change methodClass) isNil) or: [(class includesSelector: change methodSelector) not]]))]]. self changed: #allSelections! ! !ChangeList methodsFor: 'menu actions' stamp: 'DamienCassou 9/23/2009 08:33'! selectSuchThat "query the user for a selection criterio. By Lex Spoon. NB: the UI for invoking this from a changelist browser is currently commented out; to reenfranchise it, you'll need to mild editing to ChangeList method #changeListMenu:" | code block | code := UIManager default request: 'selection criteria for a change named aChangeRecord?\For instance, ''aChangeRecord category = ''System-Network''''' withCRs. code isEmptyOrNil ifTrue: [^ self ]. block := Compiler evaluate: '[:aChangeRecord | ', code, ']'. self selectSuchThat: block! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! selectSuchThat: aBlock "select all changes for which block returns true" listSelections := changeList collect: [ :change | aBlock value: change ]. self changed: #allSelections! ! !ChangeList methodsFor: 'menu actions' stamp: 'sd 11/20/2005 21:26'! selectUnchangedMethods "Selects all method definitions for which there is already a method in the current image, whose source is exactly the same. 9/18/96 sw" | change class | Cursor read showWhile: [1 to: changeList size do: [:i | change := changeList at: i. listSelections at: i put: ((change type = #method and: [(class := change methodClass) notNil]) and: [(class includesSelector: change methodSelector) and: [change string withBlanksCondensed = (class sourceCodeAt: change methodSelector) asString withBlanksCondensed ]])]]. self changed: #allSelections! ! !ChangeList methodsFor: 'scanning' stamp: 'sd 11/20/2005 21:26'! scanCategory "Scan anything that involves more than one chunk; method name is historical only" | itemPosition item tokens stamp isComment anIndex | itemPosition := file position. item := file nextChunk. isComment := (item includesSubString: 'commentStamp:'). (isComment or: [item includesSubString: 'methodsFor:']) ifFalse: ["Maybe a preamble, but not one we recognize; bail out with the preamble trick" ^ self addItem: (ChangeRecord new file: file position: itemPosition type: #preamble) text: ('preamble: ' , item contractTo: 50)]. tokens := Scanner new scanTokens: item. tokens size >= 3 ifTrue: [stamp := ''. anIndex := tokens indexOf: #stamp: ifAbsent: [nil]. anIndex ifNotNil: [stamp := tokens at: (anIndex + 1)]. tokens second == #methodsFor: ifTrue: [^ self scanCategory: tokens third class: tokens first meta: false stamp: stamp]. tokens third == #methodsFor: ifTrue: [^ self scanCategory: tokens fourth class: tokens first meta: true stamp: stamp]]. tokens second == #commentStamp: ifTrue: [stamp := tokens third. self addItem: (ChangeRecord new file: file position: file position type: #classComment class: tokens first category: nil meta: false stamp: stamp) text: 'class comment for ' , tokens first, (stamp isEmpty ifTrue: [''] ifFalse: ['; ' , stamp]). file nextChunk. ^ file skipStyleChunk]! ! !ChangeList methodsFor: 'scanning' stamp: 'md 2/21/2006 09:42'! scanCategory: category class: class meta: meta stamp: stamp | itemPosition method | [itemPosition := file position. method := file nextChunk. file skipStyleChunk. method size > 0] "done when double terminators" whileTrue: [self addItem: (ChangeRecord new file: file position: itemPosition type: #method class: class category: category meta: meta stamp: stamp) text: 'method: ' , class , (meta ifTrue: [' class '] ifFalse: [' ']) , (self class parserClass new parseSelector: method) , (stamp isEmpty ifTrue: [''] ifFalse: ['; ' , stamp])]! ! !ChangeList methodsFor: 'scanning' stamp: 'sd 11/20/2005 21:26'! scanFile: aFile from: startPosition to: stopPosition | itemPosition item prevChar | file := aFile. changeList := OrderedCollection new. list := OrderedCollection new. listIndex := 0. file position: startPosition. 'Scanning ', aFile localName, '...' displayProgressAt: Sensor cursorPoint from: startPosition to: stopPosition during: [:bar | [file position < stopPosition] whileTrue: [bar value: file position. [file atEnd not and: [file peek isSeparator]] whileTrue: [prevChar := file next]. (file peekFor: $!!) ifTrue: [(prevChar = Character cr or: [prevChar = Character lf]) ifTrue: [self scanCategory]] ifFalse: [itemPosition := file position. item := file nextChunk. file skipStyleChunk. item size > 0 ifTrue: [self addItem: (ChangeRecord new file: file position: itemPosition type: #doIt) text: 'do it: ' , (item contractTo: 50)]]]]. listSelections := Array new: list size withAll: false! ! !ChangeList methodsFor: 'toolbuilder' stamp: 'ar 2/12/2005 13:50'! buildWith: builder ^self buildWith: builder multiSelect: true! ! !ChangeList methodsFor: 'toolbuilder' stamp: 'ar 2/12/2005 14:46'! buildWith: builder multiSelect: multiSelect "Open a morphic view for the messageSet, whose label is labelString. The listView may be either single or multiple selection type" | windowSpec max listSpec panelSpec textSpec | windowSpec := builder pluggableWindowSpec new. windowSpec model: self. windowSpec label: 'System Browser'. windowSpec children: OrderedCollection new. max := self wantsOptionalButtons ifTrue:[0.33] ifFalse:[0.4]. multiSelect ifTrue:[ listSpec := builder pluggableMultiSelectionListSpec new. listSpec getSelectionList: #listSelectionAt:. listSpec setSelectionList: #listSelectionAt:put:. ] ifFalse:[ listSpec := builder pluggableListSpec new. ]. listSpec model: self; list: #list; getIndex: #listIndex; setIndex: #toggleListIndex:; menu: (self showsVersions ifTrue: [#versionsMenu:] ifFalse: [#changeListMenu:]); keyPress: #changeListKey:from:; frame: (0@0 corner: 1@max). windowSpec children add: listSpec. self wantsOptionalButtons ifTrue:[ panelSpec := self buildOptionalButtonsWith: builder. panelSpec frame: (0@0.33 corner: 1@0.4). windowSpec children add: panelSpec. ]. textSpec := builder pluggableTextSpec new. textSpec model: self; getText: #contents; setText: #contents:; selection: #contentsSelection; menu: #codePaneMenu:shifted:; frame: (0@0.4corner: 1@1). windowSpec children add: textSpec. ^builder build: windowSpec! ! !ChangeList methodsFor: 'viewing access' stamp: 'sd 11/20/2005 21:26'! annotation "Answer the string to be shown in an annotation pane. Make plain that the annotation is associated with the current in-image version of the code, not of the selected disk-based version, and if the corresponding method is missing from the in-image version, mention that fact." | annot aChange aClass | annot := super annotation. annot asString = '------' ifTrue: [^ annot]. ^ ((aChange := self currentChange) notNil and: [aChange methodSelector notNil]) ifFalse: [annot] ifTrue: [((aClass := aChange methodClass) isNil or: [(aClass includesSelector: aChange methodSelector) not]) ifTrue: [aChange methodClassName, ' >> ', aChange methodSelector, ' is not present in the current image.'] ifFalse: ['current version: ', annot]]! ! !ChangeList methodsFor: 'viewing access' stamp: 'sw 9/5/2001 13:52'! contents "Answer the contents string, obeying diffing directives if needed" ^ self showingAnyKindOfDiffs ifFalse: [self undiffedContents] ifTrue: [self showsVersions ifTrue: [self diffedVersionContents] ifFalse: [self contentsDiffedFromCurrent]]! ! !ChangeList methodsFor: 'viewing access' stamp: 'tk 4/10/1998 09:25'! contents: aString listIndex = 0 ifTrue: [self changed: #flash. ^ false]. lostMethodPointer ifNotNil: [^ self restoreDeletedMethod]. self okToChange "means not dirty" ifFalse: ["is dirty" self inform: 'This is a view of a method on a file.\Please cancel your changes. You may\accept, but only when the method is untouched.' withCRs. ^ false]. "Can't accept changes here. Method text must be unchanged!!" (changeList at: listIndex) fileIn. ^ true! ! !ChangeList methodsFor: 'viewing access' stamp: 'sd 11/20/2005 21:26'! contentsDiffedFromCurrent "Answer the contents diffed forward from current (in-memory) method version" | aChange aClass | listIndex = 0 ifTrue: [^ '']. aChange := changeList at: listIndex. ^ ((aChange type == #method and: [(aClass := aChange methodClass) notNil]) and: [aClass includesSelector: aChange methodSelector]) ifTrue: [Utilities methodDiffFor: aChange text class: aClass selector: aChange methodSelector prettyDiffs: self showingPrettyDiffs] ifFalse: [(changeList at: listIndex) text]! ! !ChangeList methodsFor: 'viewing access' stamp: 'sw 11/13/2001 09:12'! contentsSymbolQuints "Answer a list of quintuplets representing information on the alternative views available in the code pane" ^ self sourceAndDiffsQuintsOnly! ! !ChangeList methodsFor: 'viewing access' stamp: 'sd 11/20/2005 21:26'! diffedVersionContents "Answer diffed version contents, maybe pretty maybe not" | change class earlier later | (listIndex = 0 or: [changeList size < listIndex]) ifTrue: [^ '']. change := changeList at: listIndex. later := change text. class := change methodClass. (listIndex == changeList size or: [class == nil]) ifTrue: [^ later]. earlier := (changeList at: listIndex + 1) text. ^ TextDiffBuilder buildDisplayPatchFrom: earlier to: later inClass: class prettyDiffs: self showingPrettyDiffs! ! !ChangeList methodsFor: 'viewing access'! list ^ list! ! !ChangeList methodsFor: 'viewing access'! listIndex ^ listIndex! ! !ChangeList methodsFor: 'viewing access'! listSelectionAt: index ^ listSelections at: index! ! !ChangeList methodsFor: 'viewing access' stamp: 'di 1/13/1999 14:59'! listSelectionAt: index put: value ^ listSelections at: index put: value! ! !ChangeList methodsFor: 'viewing access' stamp: 'sd 11/20/2005 21:26'! restoreDeletedMethod "If lostMethodPointer is not nil, then this is a version browser for a method that has been removed. In this case we want to establish a sourceCode link to prior versions. We do this by installing a dummy method with the correct source code pointer prior to installing this version." | dummyMethod class selector | dummyMethod := CompiledMethod toReturnSelf setSourcePointer: lostMethodPointer. class := (changeList at: listIndex) methodClass. selector := (changeList at: listIndex) methodSelector. class addSelectorSilently: selector withMethod: dummyMethod. (changeList at: listIndex) fileIn. "IF for some reason, the dummy remains, remove it, but (N.B.!!) we might not get control back if the compile (fileIn above) fails." (class compiledMethodAt: selector) == dummyMethod ifTrue: [class basicRemoveSelector: selector]. ^ true! ! !ChangeList methodsFor: 'viewing access' stamp: 'nk 2/26/2004 13:50'! selectedClass ^(self selectedClassOrMetaClass ifNil: [ ^nil ]) theNonMetaClass ! ! !ChangeList methodsFor: 'viewing access' stamp: 'sd 11/20/2005 21:26'! selectedClassOrMetaClass | c | ^ (c := self currentChange) ifNotNil: [c methodClass]! ! !ChangeList methodsFor: 'viewing access' stamp: 'sd 11/20/2005 21:26'! selectedMessageName | c | ^ (c := self currentChange) ifNotNil: [c methodSelector]! ! !ChangeList methodsFor: 'viewing access' stamp: 'sd 11/20/2005 21:26'! toggleListIndex: newListIndex listIndex ~= 0 ifTrue: [listSelections at: listIndex put: false]. newListIndex ~= 0 ifTrue: [listSelections at: newListIndex put: true]. listIndex := newListIndex. self changed: #listIndex. self contentsChanged! ! !ChangeList methodsFor: 'viewing access' stamp: 'sw 1/25/1999 14:45'! undiffedContents ^ listIndex = 0 ifTrue: [''] ifFalse: [(changeList at: listIndex) text]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ChangeList class instanceVariableNames: ''! !ChangeList class methodsFor: '*monticello' stamp: 'ar 8/6/2009 18:46'! recentLogOn: origChangesFile startingFrom: initialPos "Prompt with a menu of how far back to go when browsing a changes file." | end banners positions pos chunk i changesFile | changesFile := origChangesFile readOnlyCopy. banners := OrderedCollection new. positions := OrderedCollection new. end := changesFile size. pos := initialPos. [pos = 0 or: [banners size > 20]] whileFalse: [changesFile position: pos. chunk := changesFile nextChunk. i := chunk indexOfSubCollection: 'priorSource: ' startingAt: 1. i > 0 ifTrue: [positions addLast: pos. banners addLast: (chunk copyFrom: 5 to: i - 2). pos := Number readFrom: (chunk copyFrom: i + 13 to: chunk size)] ifFalse: [pos := 0]]. changesFile close. banners size == 0 ifTrue: [^self recent: end on: origChangesFile]. pos := UIManager default chooseFrom: banners values: positions title: 'Browse as far back as...'. pos == nil ifTrue: [^ self]. ^self recent: end - pos on: origChangesFile! ! !ChangeList class methodsFor: '*monticello' stamp: 'stephaneducasse 2/4/2006 20:47'! recent: charCount on: origChangesFile "Opens a changeList on the end of the specified changes log file" | changeList end changesFile | changesFile := origChangesFile readOnlyCopy. end := changesFile size. Cursor read showWhile: [changeList := self new scanFile: changesFile from: (0 max: end - charCount) to: end]. changesFile close. ^changeList! ! !ChangeList class methodsFor: 'filein/out' stamp: 'md 10/22/2003 16:13'! browseChangesFile: fullName "Browse the selected file in fileIn format." fullName ifNotNil: [ChangeList browseStream: (FileStream readOnlyFileNamed: fullName)] ifNil: [Beeper beep]! ! !ChangeList class methodsFor: 'filein/out' stamp: 'tak 3/16/2005 11:46'! browseCompressedChangesFile: fullName "Browse the selected file in fileIn format." | zipped unzipped stream | fullName ifNil: [^Beeper beep]. stream := FileStream readOnlyFileNamed: fullName. [stream converter: Latin1TextConverter new. zipped := GZipReadStream on: stream. unzipped := zipped contents asString] ensure: [stream close]. stream := (MultiByteBinaryOrTextStream with: unzipped) reset. ChangeList browseStream: stream! ! !ChangeList class methodsFor: 'filein/out' stamp: 'sd 11/20/2005 21:28'! fileReaderServicesForFile: fullName suffix: suffix | services | services := OrderedCollection new. (FileStream isSourceFileSuffix: suffix) | (suffix = '*') ifTrue: [ services add: self serviceBrowseChangeFile ]. (suffix = 'changes') | (suffix = '*') ifTrue: [ services add: self serviceBrowseDotChangesFile ]. (fullName asLowercase endsWith: '.cs.gz') | (suffix = '*') ifTrue: [ services add: self serviceBrowseCompressedChangeFile ]. ^services! ! !ChangeList class methodsFor: 'filein/out' stamp: 'nk 4/29/2004 10:35'! serviceBrowseChangeFile "Answer a service for opening a changelist browser on a file" ^ (SimpleServiceEntry provider: self label: 'changelist browser' selector: #browseStream: description: 'open a changelist tool on this file' buttonLabel: 'changes') argumentGetter: [ :fileList | fileList readOnlyStream ]! ! !ChangeList class methodsFor: 'filein/out' stamp: 'nk 12/13/2002 12:03'! serviceBrowseCompressedChangeFile "Answer a service for opening a changelist browser on a file" ^ SimpleServiceEntry provider: self label: 'changelist browser' selector: #browseCompressedChangesFile: description: 'open a changelist tool on this file' buttonLabel: 'changes'! ! !ChangeList class methodsFor: 'filein/out' stamp: 'sw 7/4/2002 18:37'! serviceBrowseDotChangesFile "Answer a service for opening a changelist browser on the tail end of a .changes file" ^ SimpleServiceEntry provider: self label: 'recent changes in file' selector: #browseRecentLogOnPath: description: 'open a changelist tool on recent changes in file' buttonLabel: 'recent changes'! ! !ChangeList class methodsFor: 'filein/out' stamp: 'nk 12/13/2002 12:04'! services "Answer potential file services associated with this class" ^ { self serviceBrowseChangeFile. self serviceBrowseDotChangesFile. self serviceBrowseCompressedChangeFile }! ! !ChangeList class methodsFor: 'initialization' stamp: 'GabrielOmarCotelli 6/4/2009 20:38'! unload FileServices unregisterFileReader: self ! ! !ChangeList class methodsFor: 'initialize-release' stamp: 'GabrielOmarCotelli 6/4/2009 20:38'! initialize FileServices registerFileReader: self! ! !ChangeList class methodsFor: 'instance creation' stamp: 'alain.plantec 5/30/2008 10:41'! open: aChangeList name: aString multiSelect: multiSelect "Create a standard system view for the messageSet, whose label is aString. The listView may be either single or multiple selection type" ^ self openAsMorph: aChangeList name: aString multiSelect: multiSelect. ! ! !ChangeList class methodsFor: 'instance creation' stamp: 'RAA 1/11/2001 08:20'! openAsMorph: aChangeList name: labelString multiSelect: multiSelect "Open a morphic view for the messageSet, whose label is labelString. The listView may be either single or multiple selection type" ^aChangeList openAsMorphName: labelString multiSelect: multiSelect ! ! !ChangeList class methodsFor: 'public access' stamp: 'di 1/18/2001 15:30'! browseFile: fileName "ChangeList browseFile: 'AutoDeclareFix.st'" "Opens a changeList on the file named fileName" ^ self browseStream: (FileStream readOnlyFileNamed: fileName)! ! !ChangeList class methodsFor: 'public access' stamp: 'tak 9/25/2008 16:25'! browseRecent: charCount "ChangeList browseRecent: 5000" "Opens a changeList on the end of the changes log file" "The core was moved to browserRecent:on:." ^ self browseRecent: charCount on: (SourceFiles at: 2) ! ! !ChangeList class methodsFor: 'public access' stamp: 'sd 11/20/2005 21:28'! browseRecent: charCount on: origChangesFile "Opens a changeList on the end of the specified changes log file" | changeList end changesFile | changesFile := origChangesFile readOnlyCopy. changesFile setConverterForCode. end := changesFile size. Cursor read showWhile: [changeList := self new scanFile: changesFile from: (0 max: end - charCount) to: end]. changesFile close. self open: changeList name: 'Recent changes' multiSelect: true! ! !ChangeList class methodsFor: 'public access' stamp: 'sd 11/16/2003 14:10'! browseRecentLog "ChangeList browseRecentLog" "Prompt with a menu of how far back to go to browse the current image's changes log file" ^ self browseRecentLogOn: (SourceFiles at: 2) startingFrom: SmalltalkImage current lastQuitLogPosition! ! !ChangeList class methodsFor: 'public access' stamp: 'sd 11/20/2005 21:28'! browseRecentLogOn: origChangesFile "figure out where the last snapshot or quit was, then browse the recent entries." | end done block pos chunk changesFile positions prevBlock | changesFile := origChangesFile readOnlyCopy. positions := SortedCollection new. end := changesFile size. prevBlock := end. block := end - 1024 max: 0. done := false. [done or: [positions size > 0]] whileFalse: [changesFile position: block. "ignore first fragment" changesFile nextChunk. [changesFile position < prevBlock] whileTrue: [pos := changesFile position. chunk := changesFile nextChunk. ((chunk indexOfSubCollection: '----' startingAt: 1) = 1) ifTrue: [ ({ '----QUIT'. '----SNAPSHOT' } anySatisfy: [ :str | chunk beginsWith: str ]) ifTrue: [positions add: pos]]]. block = 0 ifTrue: [done := true] ifFalse: [prevBlock := block. block := block - 1024 max: 0]]. changesFile close. positions isEmpty ifTrue: [self inform: 'File ' , changesFile name , ' does not appear to be a changes file'] ifFalse: [self browseRecentLogOn: origChangesFile startingFrom: positions last]! ! !ChangeList class methodsFor: 'public access' stamp: 'alain.plantec 2/6/2009 16:37'! browseRecentLogOn: origChangesFile startingFrom: initialPos "Prompt with a menu of how far back to go when browsing a changes file." | end banners positions pos chunk i changesFile | changesFile := origChangesFile readOnlyCopy. banners := OrderedCollection new. positions := OrderedCollection new. end := changesFile size. changesFile setConverterForCode. pos := initialPos. [pos = 0 or: [banners size > 20]] whileFalse: [changesFile position: pos. chunk := changesFile nextChunk. i := chunk indexOfSubCollection: 'priorSource: ' startingAt: 1. i > 0 ifTrue: [positions addLast: pos. banners addLast: (chunk copyFrom: 5 to: i - 2). pos := Number readFrom: (chunk copyFrom: i + 13 to: chunk size)] ifFalse: [pos := 0]]. changesFile close. banners size == 0 ifTrue: [^ self inform: 'this image has never been saved since changes were compressed' translated]. pos := UIManager default chooseFrom: banners values: positions title: 'Browse as far back as...' translated. pos isNil ifTrue: [^ self]. self browseRecent: end - pos on: origChangesFile! ! !ChangeList class methodsFor: 'public access' stamp: 'nb 6/17/2003 12:25'! browseRecentLogOnPath: fullName "figure out where the last snapshot or quit was, then browse the recent entries." fullName ifNotNil: [self browseRecentLogOn: (FileStream readOnlyFileNamed: fullName)] ifNil: [Beeper beep] ! ! !ChangeList class methodsFor: 'public access' stamp: 'sd 11/20/2005 21:28'! browseStream: changesFile "Opens a changeList on a fileStream" | changeList charCount | changesFile readOnly. changesFile setConverterForCode. charCount := changesFile size. charCount > 1000000 ifTrue: [(self confirm: 'The file ', changesFile name , ' is really long (' , charCount printString , ' characters). Would you prefer to view only the last million characters?') ifTrue: [charCount := 1000000]]. "changesFile setEncoderForSourceCodeNamed: changesFile name." Cursor read showWhile: [changeList := self new scanFile: changesFile from: changesFile size-charCount to: changesFile size]. changesFile close. self open: changeList name: changesFile localName , ' log' multiSelect: true! ! !ChangeList class methodsFor: 'public access' stamp: 'alain.plantec 2/6/2009 16:38'! getRecentLocatorWithPrompt: aPrompt "Prompt with a menu of how far back to go. Return nil if user backs out. Otherwise return the number of characters back from the end of the .changes file the user wishes to include" "ChangeList getRecentPosition" | end changesFile banners positions pos chunk i | changesFile := (SourceFiles at: 2) readOnlyCopy. banners := OrderedCollection new. positions := OrderedCollection new. end := changesFile size. pos := SmalltalkImage current lastQuitLogPosition. [pos = 0 or: [banners size > 20]] whileFalse: [changesFile position: pos. chunk := changesFile nextChunk. i := chunk indexOfSubCollection: 'priorSource: ' startingAt: 1. i > 0 ifTrue: [positions addLast: pos. banners addLast: (chunk copyFrom: 5 to: i-2). pos := Number readFrom: (chunk copyFrom: i+13 to: chunk size)] ifFalse: [pos := 0]]. changesFile close. pos := UIManager default chooseFrom: banners values: positions title: aPrompt. pos ifNil: [^ nil]. ^ end - pos! ! !ChangeList class methodsFor: 'window color' stamp: 'sw 2/26/2002 14:07'! windowColorSpecification "Answer a WindowColorSpec object that declares my preference" ^ WindowColorSpec classSymbol: self name wording: 'Change List' brightColor: #lightBlue pastelColor: #paleBlue helpMessage: 'A tool that presents a list of all the changes found in an external file.'! ! ChangeList subclass: #ChangeListForProjects instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tools-Changes'! !ChangeListForProjects commentStamp: '' prior: 0! A ChangeList that looks at the changes in a revokable project. This class has no users at present.! !ChangeListForProjects methodsFor: 'contents' stamp: 'sw 9/5/2001 15:25'! contents ^ self showingAnyKindOfDiffs ifFalse: [self undiffedContents] ifTrue: [self currentDiffedFromContents] "Current is writing over one in list. Show how I would change it"! ! !ChangeListForProjects methodsFor: 'contents' stamp: 'sd 11/20/2005 21:26'! currentDiffedFromContents "Answer the current in-memory method diffed from the current contents" | aChange aClass | listIndex = 0 ifTrue: [^ '']. aChange := changeList at: listIndex. ^ ((aChange type == #method and: [(aClass := aChange methodClass) notNil]) and: [aClass includesSelector: aChange methodSelector]) ifTrue: [TextDiffBuilder buildDisplayPatchFrom: aChange text to: (aClass sourceCodeAt: aChange methodSelector) inClass: aClass prettyDiffs: self showingPrettyDiffs] ifFalse: [(changeList at: listIndex) text]! ! Object subclass: #ChangeRecord instanceVariableNames: 'file position type class category meta stamp' classVariableNames: '' poolDictionaries: '' category: 'System-Changes'! !ChangeRecord commentStamp: '' prior: 0! A ChangeRecord represents a change recorded on a file in fileOut format. It includes a type (more needs to be done here), and additional information for certain types such as method defs which need class and category.! !ChangeRecord methodsFor: '*monticello' stamp: 'avi 9/14/2004 14:27'! asMethodDefinition ^ MCMethodDefinition className: class classIsMeta: meta selector: self methodSelector category: category timeStamp: stamp source: self string! ! !ChangeRecord methodsFor: 'access'! category ^category! ! !ChangeRecord methodsFor: 'access' stamp: 'sumim 9/1/2003 18:27'! fileIndex ^ (SourceFiles collect: [ :sf | sf name]) indexOf: file name ifAbsent: [^ nil]. ! ! !ChangeRecord methodsFor: 'access' stamp: 'nk 1/7/2004 10:28'! fileName ^(file ifNotNil: [ file name ]) ifNil: [ '' ]! ! !ChangeRecord methodsFor: 'access' stamp: 'sw 10/20/2002 02:53'! fileOutOn: aFileStream "File the receiver out on the given file stream" | aString | type == #method ifTrue: [aFileStream nextPut: $!!. aString := class asString , (meta ifTrue: [' class methodsFor: '] ifFalse: [' methodsFor: ']) , category asString printString. stamp ifNotNil: [aString := aString, ' stamp: ''', stamp, '''']. aFileStream nextChunkPut: aString. aFileStream cr]. type == #preamble ifTrue: [aFileStream nextPut: $!!]. type == #classComment ifTrue: [aFileStream nextPut: $!!. aFileStream nextChunkPut: class asString, ' commentStamp: ', stamp storeString. aFileStream cr]. aFileStream nextChunkPut: self string. type == #method ifTrue: [aFileStream nextChunkPut: ' ']. aFileStream cr! ! !ChangeRecord methodsFor: 'access' stamp: 'tk 6/24/1999 15:27'! headerFor: selector ^ ' ' , class , (meta ifTrue: [' class '] ifFalse: [' ']) , selector , (stamp isEmpty ifTrue: [''] ifFalse: ['; ' , stamp])! ! !ChangeRecord methodsFor: 'access'! isMetaClassChange ^meta! ! !ChangeRecord methodsFor: 'access'! methodClass | methodClass | type == #method ifFalse: [^ nil]. (Smalltalk includesKey: class asSymbol) ifFalse: [^ nil]. methodClass := Smalltalk at: class asSymbol. meta ifTrue: [^ methodClass class] ifFalse: [^ methodClass]! ! !ChangeRecord methodsFor: 'access'! methodClassName ^class! ! !ChangeRecord methodsFor: 'access' stamp: 'eem 1/28/2009 16:40'! methodSelector ^type == #method ifTrue: [(Smalltalk at: class ifAbsent: [Object]) parserClass new parseSelector: self string]! ! !ChangeRecord methodsFor: 'access' stamp: 'ar 7/15/2005 22:57'! originalChangeSetForSelector: methodSelector "Returns the original changeset which contained this method version. If it is contained in the .sources file, return #sources. If it is in neither (e.g. its changeset was deleted), return nil. (The selector is passed in purely as an optimization.)" | likelyChangeSets originalChangeSet | (file localName findTokens: '.') last = 'sources' ifTrue: [^ #sources]. likelyChangeSets := ChangeSet allChangeSets select: [:cs | (cs atSelector: methodSelector class: self methodClass) ~~ #none]. originalChangeSet := likelyChangeSets detect: [:cs | cs containsMethodAtPosition: position] ifNone: [nil]. ^ originalChangeSet "(still need to check for sources file)"! ! !ChangeRecord methodsFor: 'access' stamp: 'sumim 9/2/2003 14:07'! position ^ position! ! !ChangeRecord methodsFor: 'access' stamp: 'sumim 9/2/2003 13:33'! prior | currFile preamble prevPos tokens prevFileIndex | currFile := file readOnlyCopy. currFile position: (0 max: position - 150). [currFile position < (position - 1)] whileTrue: [preamble := currFile nextChunk]. currFile close. prevPos := nil. (preamble findString: 'methodsFor:' startingAt: 1) > 0 ifTrue: [tokens := Scanner new scanTokens: preamble] ifFalse: [tokens := Array new]. ((tokens size between: 7 and: 8) and: [(tokens at: tokens size - 5) == #methodsFor:]) ifTrue: [ (tokens at: tokens size - 3) == #stamp: ifTrue: [ prevPos := tokens last. prevFileIndex := SourceFiles fileIndexFromSourcePointer: prevPos. prevPos := SourceFiles filePositionFromSourcePointer: prevPos] ifFalse: [ prevPos := tokens at: tokens size - 2. prevFileIndex := tokens last]. (prevPos = 0 or: [prevFileIndex = 0]) ifTrue: [prevPos := nil]]. prevPos ifNil: [^ nil]. ^ {prevFileIndex. prevPos. SourceFiles sourcePointerFromFileIndex: prevFileIndex andPosition: prevPos}! ! !ChangeRecord methodsFor: 'access' stamp: 'tk 6/21/1999 20:34'! readStamp "Get the time stamp of this method off the file" | item tokens anIndex | stamp := ''. file ifNil: [^ stamp]. file position: position. item := file nextChunk. tokens := Scanner new scanTokens: item. tokens size < 3 ifTrue: [^ stamp]. anIndex := tokens indexOf: #stamp: ifAbsent: [^ stamp]. ^ stamp := tokens at: (anIndex + 1). ! ! !ChangeRecord methodsFor: 'access' stamp: '6/6/97 08:56 dhhi'! stamp ^ stamp! ! !ChangeRecord methodsFor: 'access' stamp: 'tk 9/7/2000 15:09'! stamp: threePartString stamp := threePartString! ! !ChangeRecord methodsFor: 'access' stamp: 'di 1/13/98 16:57'! string | string | file openReadOnly. file position: position. string := file nextChunk. file close. ^ string! ! !ChangeRecord methodsFor: 'access' stamp: 'tk 6/23/1999 08:20'! text | text | ^ file ifNil: [''] ifNotNil: [ file openReadOnly. file position: position. text := file nextChunkText. file close. text]! ! !ChangeRecord methodsFor: 'access' stamp: 'nk 11/25/2003 09:44'! timeStamp "Answer a TimeStamp that corresponds to my (text) stamp" | tokens date time | tokens := self stamp findTokens: Character separators. ^ tokens size > 2 ifTrue: [[date := Date fromString: (tokens at: tokens size - 1). time := Time fromString: tokens last. TimeStamp date: date time: time] on: Error do: [:ex | ex return: (TimeStamp fromSeconds: 0)]] ifFalse: [TimeStamp fromSeconds: 0]! ! !ChangeRecord methodsFor: 'access'! type ^ type! ! !ChangeRecord methodsFor: 'initialization' stamp: 'tk 6/24/1999 14:51'! class: clsName category: cat method: method sourceFiles: fileArray "This should be enough to find all the information for a method, or method deletion" file := fileArray at: method fileIndex. position := method filePosition. type := #method. class := clsName copyUpTo: $ . "the non-meta part of a class name" category := cat. meta := clsName endsWith: ' class'. self readStamp.! ! !ChangeRecord methodsFor: 'initialization'! file: f position: p type: t file := f. position := p. type := t! ! !ChangeRecord methodsFor: 'initialization' stamp: '6/6/97 08:48 dhhi'! file: f position: p type: t class: c category: cat meta: m stamp: s self file: f position: p type: t. class := c. category := cat. meta := m. stamp := s! ! !ChangeRecord methodsFor: 'initialization' stamp: 'nk 11/26/2002 12:07'! fileIn "File the receiver in. If I represent a method or a class-comment, file the method in and make a note of it in the recent-submissions list; if I represent a do-it, then, well, do it." | methodClass s aSelector | Cursor read showWhile: [(methodClass := self methodClass) notNil ifTrue: [methodClass compile: self text classified: category withStamp: stamp notifying: nil. (aSelector := self methodSelector) ifNotNil: [Utilities noteMethodSubmission: aSelector forClass: methodClass]]. (type == #doIt) ifTrue: [((s := self string) beginsWith: '----') ifFalse: [Compiler evaluate: s]]. (type == #classComment) ifTrue: [ | cls | (cls := Smalltalk at: class asSymbol) comment: self text stamp: stamp. Utilities noteMethodSubmission: #Comment forClass: cls ]]! ! Object subclass: #ChangeSet instanceVariableNames: 'name preamble postscript revertable isolationSet isolatedProject changeRecords structures superclasses' classVariableNames: 'AllChangeSets PreviousSet' poolDictionaries: '' category: 'System-Changes'! !ChangeSet commentStamp: '' prior: 0! ChangeSets keep track of the changes made to a system, so they can be written on a file as source code (a "fileOut"). Every project has an associated changeSet. For simple projects, a different changeSet may be designated to capture changes at any time. This implementation of ChangeSet is capable of remembering and manipulating methods for which the classes are not present in the system. However at the present time, this capability is not used in normal rearranging and fileOuts, but only for invoking and revoking associated with isolation layers. For isolated projects (see Project class comment), the changeSet binding is semi-permanent. Every project exists in an isolation layer defined by its closest enclosing parent (or itself) that is isolated. If a project is not isolated, then changes reported to its designated changeSet must also be reported to the permanent changeSet for that layer, designated in the isolated project. This ensures that that outer project will be able to revert all changes upon exit. Note that only certain changes may be reverted. Classes may not be added, removed, renamed or reshaped except in the layer in which they are defined because these operations on non-local classes are not revertable. If a Squeak Project is established as being isolated, then its associated changeSet will be declared to be revertable. In this case all changes stored can be reverted. The changeSet associated with an isolated project is tied to that project, and cannot be edited in a changeSorter. ------ name - a String used to name the changeSet, and thus any associated project or fileOut. preamble and postscript: two strings that serve as prefix (useful for documentation) and suffix (useful for doits) to the fileout of the changeSet. revertable - a Boolean If this variable is true, then all of the changes recorded by this changeSet can be reverted. isolationSet - a ChangeSet or nil The isolationSet is the designated changeSet for an isolation layer. If this changeSet is an isolationSet, then this variable will be nil. If not, then it points to the isolationSet for this layer, and all changes reported here will also be reported to the isolationSet. isolatedProject - a Project or nil If this is an isolationSet, then this variable points to the project with which it is associated. changeRecords - Dictionary {class name -> a ClassChangeRecord}. These classChangeRecords (qv) remember all of the system changes. structures - Dictionary {#Rectangle -> #( 'origin' 'corner')}. Of the names of the instances variables before any changes for all classes in classChanges, and all of their superclasses. In the same format used in SmartRefStream. Inst var names are strings. superclasses - Dictionary {#Rectangle -> #Object}. Of all classes in classChanges, and all of their superclasses. Structures and superclasses save the instance variable names of this class and all of its superclasses. Later we can tell how it changed and write a conversion method. The conversion method is used when old format objects are brought in from the disk from ImageSegment files (.extSeg) or SmartRefStream files (.obj .morph .bo .sp). NOTE: It should be fairly simple, by adding a bit more information to the classChangeRecords, to reconstruct the information now stored in 'structures' and 'superclasses'. This would be a welcome simplification. ! !ChangeSet methodsFor: 'accessing' stamp: 'BJP 4/24/2001 00:23'! author | author | self assurePreambleExists. author := self preambleString lineNumber: 3. author := author copyFrom: 8 to: author size. "Strip the 'Author:' prefix. Ugly ugly." ^author withBlanksTrimmed. ! ! !ChangeSet methodsFor: 'accessing' stamp: 'di 4/1/2000 12:00'! classRemoves ^ changeRecords keys select: [:className | (changeRecords at: className) isClassRemoval]! ! !ChangeSet methodsFor: 'accessing' stamp: 'ar 7/16/2005 18:59'! editPostscript "edit the receiver's postscript, in a separate window. " self assurePostscriptExists. UIManager default edit: self postscript label: 'Postscript for ChangeSet named ', name accept:[:aString| self postscript: aString].! ! !ChangeSet methodsFor: 'accessing' stamp: 'sw 6/29/1999 14:44'! hasPostscript ^ postscript notNil! ! !ChangeSet methodsFor: 'accessing' stamp: 'di 4/1/2000 12:00'! methodChanges | methodChangeDict changeTypes | methodChangeDict := Dictionary new. changeRecords associationsDo: [:assn | changeTypes := assn value methodChangeTypes. changeTypes isEmpty ifFalse: [methodChangeDict at: assn key put: changeTypes]]. ^ methodChangeDict! ! !ChangeSet methodsFor: 'accessing' stamp: 'di 3/29/2000 16:22'! methodInfoFromRemoval: classAndSelector ^ (self changeRecorderFor: classAndSelector first) infoFromRemoval: classAndSelector last! ! !ChangeSet methodsFor: 'accessing'! name "The name of this changeSet. 2/7/96 sw: If name is nil, we've got garbage. Help to identify." ^ name == nil ifTrue: [''] ifFalse: [name]! ! !ChangeSet methodsFor: 'accessing'! name: anObject name := anObject! ! !ChangeSet methodsFor: 'accessing' stamp: 'ar 7/16/2005 18:04'! postscriptHasDependents ^false! ! !ChangeSet methodsFor: 'accessing'! printOn: aStream "2/7/96 sw: provide the receiver's name in the printout" super printOn: aStream. aStream nextPutAll: ' named ', self name! ! !ChangeSet methodsFor: 'accessing' stamp: 'MPW 1/1/1901 22:02'! printOnStream: aStream "2/7/96 sw: provide the receiver's name in the printout" super printOnStream: aStream. aStream print: ' named ', self name! ! !ChangeSet methodsFor: 'accessing' stamp: 'sw 6/29/1999 14:48'! removePostscript postscript := nil! ! !ChangeSet methodsFor: 'accessing' stamp: 'tk 6/8/1999 22:25'! structures ^structures! ! !ChangeSet methodsFor: 'accessing' stamp: 'tk 6/8/1999 22:25'! superclasses ^superclasses! ! !ChangeSet methodsFor: 'change logging' stamp: 'di 3/29/2000 13:10'! addClass: class "Include indication that a new class was created." class wantsChangeSetLogging ifFalse: [^ self]. isolationSet ifNotNil: ["If there is an isolation layer above me, inform it as well." isolationSet addClass: class]. self atClass: class add: #new. self atClass: class add: #change. self addCoherency: class name! ! !ChangeSet methodsFor: 'change logging' stamp: 'NS 1/19/2004 18:30'! changeClass: class from: oldClass "Remember that a class definition has been changed. Record the original structure, so that a conversion method can be built." class wantsChangeSetLogging ifFalse: [^ self]. isolationSet ifNotNil: ["If there is an isolation layer above me, inform it as well." isolationSet changeClass: class from: oldClass]. class isMeta ifFalse: [self atClass: class add: #change] "normal" ifTrue: [((self classChangeAt: class theNonMetaClass name) includes: #add) ifTrue: [self atClass: class add: #add] "When a class is defined, the metaclass is not recorded, even though it was added. A further change is really just part of the original add." ifFalse: [self atClass: class add: #change]]. self addCoherency: class name. (self changeRecorderFor: class) notePriorDefinition: oldClass. self noteClassStructure: oldClass! ! !ChangeSet methodsFor: 'change logging' stamp: 'rw 10/17/2006 22:26'! event: anEvent "Hook for SystemChangeNotifier" anEvent itemKind = SystemChangeNotifier classKind ifTrue: [ anEvent isRemoved ifTrue: [self noteRemovalOf: anEvent item]. anEvent isAdded ifTrue: [self addClass: anEvent item]. anEvent isModified ifTrue: [anEvent anyChanges ifTrue: [self changeClass: anEvent item from: anEvent oldItem]]. anEvent isCommented ifTrue: [self commentClass: anEvent item]. anEvent isRenamed ifTrue: [self renameClass: anEvent item from: anEvent oldName to: anEvent newName]. anEvent isReorganized ifTrue: [self reorganizeClass: anEvent item]. anEvent isRecategorized ifTrue: [self changeClass: anEvent item from: anEvent item]. ]. anEvent itemKind = SystemChangeNotifier methodKind ifTrue: [ anEvent isAdded ifTrue: [self noteNewMethod: anEvent item forClass: anEvent itemClass selector: anEvent itemSelector priorMethod: nil]. anEvent isModified ifTrue: [self noteNewMethod: anEvent item forClass: anEvent itemClass selector: anEvent itemSelector priorMethod: anEvent oldItem]. anEvent isRemoved ifTrue: [self removeSelector: anEvent itemSelector class: anEvent itemClass priorMethod: anEvent item lastMethodInfo: {anEvent item sourcePointer. anEvent itemProtocol}]. anEvent isRecategorized ifTrue: [self reorganizeClass: anEvent itemClass]. ].! ! !ChangeSet methodsFor: 'change logging' stamp: 'di 3/29/2000 11:08'! noteNewMethod: newMethod forClass: class selector: selector priorMethod: methodOrNil class wantsChangeSetLogging ifFalse: [^ self]. isolationSet ifNotNil: ["If there is an isolation layer above me, inform it as well." isolationSet noteNewMethod: newMethod forClass: class selector: selector priorMethod: methodOrNil]. (self changeRecorderFor: class) noteNewMethod: newMethod selector: selector priorMethod: methodOrNil ! ! !ChangeSet methodsFor: 'change logging' stamp: 'di 3/29/2000 12:29'! removeSelector: selector class: class priorMethod: priorMethod lastMethodInfo: info "Include indication that a method has been forgotten. info is a pair of the source code pointer and message category for the method that was removed." class wantsChangeSetLogging ifFalse: [^ self]. isolationSet ifNotNil: ["If there is an isolation layer above me, inform it as well." isolationSet removeSelector: selector class: class priorMethod: priorMethod lastMethodInfo: info]. (self changeRecorderFor: class) noteRemoveSelector: selector priorMethod: priorMethod lastMethodInfo: info ! ! !ChangeSet methodsFor: 'change logging' stamp: 'rw 10/19/2006 17:52'! renameClass: class from: oldName to: newName "Include indication that a class has been renamed." | recorder oldMetaClassName newMetaClassName | isolationSet ifNotNil: ["If there is an isolation layer above me, inform it as well." isolationSet renameClass: class as: newName]. (recorder := self changeRecorderFor: oldName) noteChangeType: #rename; noteNewName: newName asSymbol. "store under new name (metaclass too)" changeRecords at: newName put: recorder. changeRecords removeKey: oldName. self noteClassStructure: class. newMetaClassName := newName, ' class'. oldMetaClassName := oldName, ' class'. recorder := changeRecords at: oldMetaClassName ifAbsent: [^ nil]. changeRecords at: newMetaClassName put: recorder. changeRecords removeKey: oldMetaClassName. recorder noteNewName: newMetaClassName! ! !ChangeSet methodsFor: 'class changes' stamp: 'di 4/1/2000 12:00'! changedClassNames "Answer a OrderedCollection of the names of changed or edited classes. DOES include removed classes. Sort alphabetically." ^ changeRecords keysSortedSafely ! ! !ChangeSet methodsFor: 'class changes' stamp: 'di 3/23/2000 08:12'! changedClasses "Answer an OrderedCollection of changed or edited classes. Does not include removed classes. Sort alphabetically by name." "Much faster to sort names first, then convert back to classes. Because metaclasses reconstruct their name at every comparison in the sorted collection. 8/91 sw chgd to filter out non-existent classes (triggered by problems with class-renames" ^ self changedClassNames collect: [:className | Smalltalk classNamed: className] thenSelect: [:aClass | aClass notNil]! ! !ChangeSet methodsFor: 'class changes' stamp: 'di 4/1/2000 12:00'! classChangeAt: className "Return what we know about class changes to this class." ^ (changeRecords at: className ifAbsent: [^ Set new]) allChangeTypes! ! !ChangeSet methodsFor: 'class changes' stamp: 'NS 1/26/2004 09:46'! commentClass: class "Include indication that a class comment has been changed." class wantsChangeSetLogging ifFalse: [^ self]. self atClass: class add: #comment! ! !ChangeSet methodsFor: 'class changes' stamp: 'nk 6/26/2002 12:30'! containsClass: aClass ^ self changedClasses includes: aClass! ! !ChangeSet methodsFor: 'class changes' stamp: 'PeterHugossonMiller 9/3/2009 00:18'! fatDefForClass: class | newDef oldDef oldStrm newStrm outStrm oldVars newVars addedVars | class isBehavior ifFalse: [ ^ class definition ]. newDef := class definition. oldDef := (self changeRecorderFor: class) priorDefinition. oldDef ifNil: [ ^ newDef ]. oldDef = newDef ifTrue: [ ^ newDef ]. oldStrm := oldDef readStream. newStrm := newDef readStream. outStrm := (String new: newDef size * 2) writeStream. "Merge inst vars from old and new defs..." oldStrm upToAll: 'instanceVariableNames'; upTo: $'. outStrm nextPutAll: (newStrm upToAll: 'instanceVariableNames'); nextPutAll: 'instanceVariableNames:'. newStrm peek = $: ifTrue: [ newStrm next ]. "may or may not be there, but already written" outStrm nextPutAll: (newStrm upTo: $'); nextPut: $'. oldVars := (oldStrm upTo: $') findTokens: Character separators. newVars := (newStrm upTo: $') findTokens: Character separators. addedVars := oldVars asSet addAll: newVars; removeAll: oldVars; asOrderedCollection. oldVars , addedVars do: [ :var | outStrm nextPutAll: var; space ]. outStrm nextPut: $'. class isMeta ifFalse: [ "Merge class vars from old and new defs..." oldStrm upToAll: 'classVariableNames:'; upTo: $'. outStrm nextPutAll: (newStrm upToAll: 'classVariableNames:'); nextPutAll: 'classVariableNames:'; nextPutAll: (newStrm upTo: $'); nextPut: $'. oldVars := (oldStrm upTo: $') findTokens: Character separators. newVars := (newStrm upTo: $') findTokens: Character separators. addedVars := oldVars asSet addAll: newVars; removeAll: oldVars; asOrderedCollection. oldVars , addedVars do: [ :var | outStrm nextPutAll: var; space ]. outStrm nextPut: $' ]. outStrm nextPutAll: newStrm upToEnd. ^ outStrm contents! ! !ChangeSet methodsFor: 'class changes' stamp: 'tk 6/9/1999 19:54'! noteClassForgotten: className "Remove from structures if class is not a superclass of some other one we are remembering" structures ifNil: [^ self]. Smalltalk at: className ifPresent: [:cls | cls subclasses do: [:sub | (structures includesKey: sub) ifTrue: [ ^ self]]]. "No delete" structures removeKey: className ifAbsent: [].! ! !ChangeSet methodsFor: 'class changes' stamp: 'dvf 9/27/2005 19:05'! noteClassStructure: aClass "Save the instance variable names of this class and all of its superclasses. Later we can tell how it changed and write a conversion method. The conversion method is used when old format objects are brought in from the disk from ImageSegment files (.extSeg) or SmartRefStream files (.obj .morph .bo .sp)." | clsName | aClass isBehavior ifFalse: [^ self]. structures ifNil: [structures := Dictionary new. superclasses := Dictionary new]. clsName := (aClass name asLowercase beginsWith: 'anobsolete') ifTrue: [(aClass name copyFrom: 11 to: aClass name size) asSymbol] ifFalse: [aClass name]. (structures includesKey: clsName) ifFalse: [ structures at: clsName put: ((Array with: aClass classVersion), (aClass allInstVarNames)). superclasses at: clsName put: aClass superclass name]. "up the superclass chain" aClass superclass ifNotNil: [self noteClassStructure: aClass superclass]. ! ! !ChangeSet methodsFor: 'class changes' stamp: 'NS 1/19/2004 17:49'! noteRemovalOf: class "The class is about to be removed from the system. Adjust the receiver to reflect that fact." class wantsChangeSetLogging ifFalse: [^ self]. (self changeRecorderFor: class) noteChangeType: #remove fromClass: class. changeRecords removeKey: class class name ifAbsent: [].! ! !ChangeSet methodsFor: 'class changes'! reorganizeClass: class "Include indication that a class was reorganized." self atClass: class add: #reorganize! ! !ChangeSet methodsFor: 'class changes' stamp: 'di 5/16/2000 09:03'! trimHistory "Drop non-essential history: methods added and then removed, as well as rename and reorganization of newly-added classes." changeRecords do: [:chgRecord | chgRecord trimHistory]! ! !ChangeSet methodsFor: 'converting' stamp: 'RAA 12/20/2000 16:02'! convertApril2000: varDict using: smartRefStrm | cls info selector pair classChanges methodChanges methodRemoves classRemoves | "These variables are automatically stored into the new instance: ('name' 'preamble' 'postscript' 'structures' 'superclasses' ). This method is for additional changes. It initializes the isolation variables, and then duplicates the logic fo assimilateAllChangesFoundIn:." revertable := false. isolationSet := nil. isolatedProject := nil. changeRecords := Dictionary new. classChanges := varDict at: 'classChanges'. classChanges keysDo: [:className | (cls := Smalltalk classNamed: className) ifNotNil: [info := classChanges at: className ifAbsent: [Set new]. info do: [:each | self atClass: cls add: each]]]. methodChanges := varDict at: 'methodChanges'. methodRemoves := varDict at: 'methodRemoves'. methodChanges keysDo: [:className | (cls := Smalltalk classNamed: className) ifNotNil: [info := methodChanges at: className ifAbsent: [Dictionary new]. info associationsDo: [:assoc | selector := assoc key. (assoc value == #remove or: [assoc value == #addedThenRemoved]) ifTrue: [assoc value == #addedThenRemoved ifTrue: [self atSelector: selector class: cls put: #add]. pair := methodRemoves at: {cls name. selector} ifAbsent: [nil] . self removeSelector: selector class: cls priorMethod: nil lastMethodInfo: pair] ifFalse: [self atSelector: selector class: cls put: assoc value]]]]. classRemoves := varDict at: 'classRemoves'. classRemoves do: [:className | self noteRemovalOf: className]. ! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/15/2005 21:53'! askAddedInstVars: classList | pairList pairClasses index pls newStruct oldStruct | "Ask the author whether these newly added inst vars need to be non-nil" pairList := OrderedCollection new. pairClasses := OrderedCollection new. "Class version numbers: If it must change, something big happened. Do need a conversion method then. Ignore them here." classList do: [:cls | newStruct := (cls allInstVarNames). oldStruct := (structures at: cls name ifAbsent: [#(0), newStruct]) allButFirst. newStruct do: [:instVarName | (oldStruct includes: instVarName) ifFalse: [ pairList add: cls name, ' ', instVarName. pairClasses add: cls]]]. pairList isEmpty ifTrue: [^ #()]. [index := UIManager default chooseFrom: pairList, #('all of these need a non-nil value' 'all of these are OK with a nil value') title: 'These instance variables were added. When an old project comes in, newly added instance variables will have the value nil. Click on items to remove them from the list. Click on any for which nil is an OK value.'. (index <= (pls := pairList size)) & (index > 0) ifTrue: [ pairList removeAt: index. pairClasses removeAt: index]. index = (pls + 2) ifTrue: ["all are OK" ^ #()]. pairList isEmpty | (index = (pls + 1)) "all need conversion, exit"] whileFalse. ^ pairClasses asSet asArray "non redundant"! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/15/2005 21:54'! askRemovedInstVars: classList | pairList pairClasses index pls newStruct oldStruct | "Ask the author whether these newly removed inst vars need to have their info saved" pairList := OrderedCollection new. pairClasses := OrderedCollection new. "Class version numbers: If it must change, something big happened. Do need a conversion method then. Ignore them here." classList do: [:cls | newStruct := (cls allInstVarNames). oldStruct := (structures at: cls name ifAbsent: [#(0), newStruct]) allButFirst. oldStruct do: [:instVarName | (newStruct includes: instVarName) ifFalse: [ pairList add: cls name, ' ', instVarName. pairClasses add: cls]]]. pairList isEmpty ifTrue: [^ #()]. [index := UIManager default chooseFrom: pairList, #('all of these need a conversion method' 'all of these have old values that can be erased') title: 'These instance variables were removed. When an old project comes in, instance variables that have been removed will lose their contents. Click on items to remove them from the list. Click on any whose value is unimportant and need not be saved.'. (index <= (pls := pairList size)) & (index > 0) ifTrue: [ pairList removeAt: index. pairClasses removeAt: index]. index = (pls + 2) ifTrue: ["all are OK" ^ #()]. pairList isEmpty | (index = (pls + 1)) "all need conversion, exit"] whileFalse. ^ pairClasses asSet asArray "non redundant"! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/15/2005 21:51'! askRenames: renamed addTo: msgSet using: smart | list rec ans oldStruct newStruct | "Go through the renamed classes. Ask the user if it could be in a project. Add a method in SmartRefStream, and a conversion method in the new class." list := OrderedCollection new. renamed do: [:cls | rec := changeRecords at: cls name. rec priorName ifNotNil: [ ans := UIManager default chooseFrom: #('Yes, write code to convert those instances' 'No, no instances are in projects') title: 'You renamed class ', rec priorName, ' to be ', rec thisName, '.\Could an instance of ', rec priorName, ' be in a project on someone''s disk?'. ans = 1 ifTrue: [ oldStruct := structures at: rec priorName ifAbsent: [nil]. newStruct := (Array with: cls classVersion), (cls allInstVarNames). oldStruct ifNotNil: [ smart writeConversionMethodIn: cls fromInstVars: oldStruct to: newStruct renamedFrom: rec priorName. smart writeClassRename: cls name was: rec priorName. list add: cls name, ' convertToCurrentVersion:refStream:']] ifFalse: [structures removeKey: rec priorName ifAbsent: []]]]. list isEmpty ifTrue: [^ msgSet]. msgSet messageList ifNil: [msgSet initializeMessageList: list] ifNotNil: [list do: [:item | msgSet addItem: item]]. ^ msgSet! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:05'! assurePostscriptExists "Make sure there is a StringHolder holding the postscript. " "NOTE: FileIn recognizes the postscript by the line with Postscript: on it" postscript == nil ifTrue: [postscript := '"Postscript: Leave the line above, and replace the rest of this comment by a useful one. Executable statements should follow this comment, and should be separated by periods, with no exclamation points (!!). Be sure to put any further comments in double-quotes, like this one." ']! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:02'! assurePreambleExists "Make sure there is a StringHolder holding the preamble; if it's found to have reverted to empty contents, put up the template" (preamble isEmptyOrNil) ifTrue: [preamble := self preambleTemplate]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'PeterHugossonMiller 9/3/2009 00:20'! buildMessageForMailOutWithUser: userName "prepare the message" | message compressBuffer compressStream data compressedStream compressTarget | message := MailMessage empty. message setField: 'from' toString: userName. message setField: 'to' toString: 'Pharo-project@lists.gforge.inria.fr'. message setField: 'subject' toString: self chooseSubjectPrefixForEmail , name. message body: (MIMEDocument contentType: 'text/plain' content: (String streamContents: [ :str | str nextPutAll: 'from preamble:'; cr; cr. self fileOutPreambleOn: str ])). "Prepare the gzipped data" data := String new writeStream. data header; timeStamp. self fileOutPreambleOn: data. self fileOutOn: data. self fileOutPostscriptOn: data. data trailer. data := data contents readStream. compressBuffer := ByteArray new: 1000. compressStream := GZipWriteStream on: (compressTarget := (ByteArray new: 1000) writeStream). [ data atEnd ] whileFalse: [ compressStream nextPutAll: (data nextInto: compressBuffer) ]. compressStream close. compressedStream := compressTarget contents asString readStream. message addAttachmentFrom: compressedStream withName: name , '.cs.gz'. ^ message! ! !ChangeSet methodsFor: 'filein/out' stamp: 'MiguelCoba 7/25/2009 02:16'! checkForAlienAuthorship "Check to see if there are any methods in the receiver that have author full name other than that of the current author, and open a browser on all found" | aList fullName | (fullName := Author fullNamePerSe) ifNil: [^ self inform: 'No author full name set in this image']. (aList := self methodsWithInitialsOtherThan: fullName) size > 0 ifFalse: [^ self inform: 'All methods in "', self name, '" have authoring stamps which start with "', fullName, '"'] ifTrue: [self systemNavigation browseMessageList: aList name: 'methods in "', self name, '" whose authoring stamps do not start with "', fullName, '"']! ! !ChangeSet methodsFor: 'filein/out' stamp: 'MiguelCoba 7/25/2009 02:17'! checkForAnyAlienAuthorship "Check to see if there are any versions of any methods in the receiver that have author full name other than that of the current author, and open a browser on all found" | aList fullName | (fullName := Author fullNamePerSe) ifNil: [^ self inform: 'No author full name set in this image']. (aList := self methodsWithAnyInitialsOtherThan: fullName) size > 0 ifFalse: [^ self inform: 'All versions of all methods in "', self name, '" have authoring stamps which start with "', fullName, '"'] ifTrue: [self systemNavigation browseMessageList: aList name: 'methods in "', self name, '" with any authoring stamps not starting with "', fullName, '"']! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/17/2005 11:13'! checkForConversionMethods "See if any conversion methods are needed" | oldStruct newStruct tell choice list need sel smart restore renamed listAdd listDrop msgSet rec nn | Preferences conversionMethodsAtFileOut ifFalse: [^ self]. "Check preference" structures ifNil: [^ self]. list := OrderedCollection new. renamed := OrderedCollection new. self changedClasses do: [:class | need := (self atClass: class includes: #new) not. need ifTrue: ["Renamed classes." (self atClass: class includes: #rename) ifTrue: [ rec := changeRecords at: class name. rec priorName ifNotNil: [ (structures includesKey: rec priorName) ifTrue: [ renamed add: class. need := false]]]]. need ifTrue: [need := (self atClass: class includes: #change)]. need ifTrue: [oldStruct := structures at: class name ifAbsent: [need := false. #()]]. need ifTrue: [ newStruct := (Array with: class classVersion), (class allInstVarNames). need := (oldStruct ~= newStruct)]. need ifTrue: [sel := #convertToCurrentVersion:refStream:. (#(add change) includes: (self atSelector: sel class: class)) ifFalse: [ list add: class]]. ]. list isEmpty & renamed isEmpty ifTrue: [^ self]. "Ask user if want to do this" tell := 'If there might be instances of ', (list asArray, renamed asArray) printString, '\in a project (.pr file) on someone''s disk, \please ask to write a conversion method.\' withCRs, 'After you edit the conversion method, you''ll need to fileOut again.\' withCRs, 'The preference conversionMethodsAtFileOut in category "fileout" controls this feature.'. choice := UIManager default chooseFrom: 'Write a conversion method by editing a prototype These classes are not used in any object file. fileOut my changes now. I''m too busy. fileOut my changes now. Don''t ever ask again. fileOut my changes now.' withCRs title: tell. choice = 4 ifTrue: [Preferences disable: #conversionMethodsAtFileOut]. choice = 2 ifTrue: ["Don't consider this class again in the changeSet" list do: [:cls | structures removeKey: cls name ifAbsent: []]. renamed do: [:cls | nn := (changeRecords at: cls name) priorName. structures removeKey: nn ifAbsent: []]]. choice ~= 1 ifTrue: [^ self]. "exit if choice 2,3,4" listAdd := self askAddedInstVars: list. "Go through each inst var that was added" listDrop := self askRemovedInstVars: list. "Go through each inst var that was removed" list := (listAdd, listDrop) asSet asArray. smart := SmartRefStream on: (RWBinaryOrTextStream on: '12345'). smart structures: structures. smart superclasses: superclasses. (restore := self class current) == self ifFalse: [ self class newChanges: self]. "if not current one" msgSet := smart conversionMethodsFor: list. "each new method is added to self (a changeSet). Then filed out with the rest." self askRenames: renamed addTo: msgSet using: smart. "renamed classes, add 2 methods" restore == self ifFalse: [self class newChanges: restore]. msgSet isEmpty ifTrue: [^ self]. self inform: 'Remember to fileOut again after modifying these methods.'. ToolSet browseMessageSet: msgSet name: 'Conversion methods for ', self name autoSelect: false.! ! !ChangeSet methodsFor: 'filein/out' stamp: 'di 3/26/2000 10:06'! checkForSlips "Return a collection of method refs with possible debugging code in them." | slips method | slips := OrderedCollection new. self changedClasses do: [:aClass | (self methodChangesAtClass: aClass name) associationsDo: [:mAssoc | (#(remove addedThenRemoved) includes: mAssoc value) ifFalse: [method := aClass compiledMethodAt: mAssoc key ifAbsent: [nil]. method ifNotNil: [method hasReportableSlip ifTrue: [slips add: aClass name , ' ' , mAssoc key]]]]]. ^ slips! ! !ChangeSet methodsFor: 'filein/out' stamp: 'sd 4/16/2003 09:16'! checkForUnclassifiedMethods "Open a message list browser on all methods in the current change set that have not been categorized," | aList | (aList := self methodsWithoutClassifications) size > 0 ifFalse: [^ self inform: 'All methods in "', self name, '" are categorized.'] ifTrue: [self systemNavigation browseMessageList: aList name: 'methods in "', self name, '" which have not been categorized']! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/17/2005 10:48'! checkForUncommentedClasses "Check to see if any classes involved in this change set do not have class comments. Open up a browser showing all such classes." | aList | aList := self changedClasses select: [:aClass | aClass theNonMetaClass organization classComment isEmptyOrNil] thenCollect: [:aClass | aClass theNonMetaClass name]. aList size > 0 ifFalse: [^ self inform: 'All classes involved in this change set have class comments'] ifTrue: [ToolSet openClassListBrowser: aList asSet asSortedArray title: 'Classes in Change Set ', self name, ': classes that lack class comments']! ! !ChangeSet methodsFor: 'filein/out' stamp: 'sd 4/16/2003 09:16'! checkForUncommentedMethods | aList | "Check to see if there are any methods in the receiver that have no comments, and open a browser on all found" (aList := self methodsWithoutComments) size > 0 ifFalse: [^ self inform: 'All methods in "', self name, '" have comments'] ifTrue: [self systemNavigation browseMessageList: aList name: 'methods in "', self name, '" that lack comments']! ! !ChangeSet methodsFor: 'filein/out' stamp: 'stephane.ducasse 10/12/2008 21:02'! checkForUnsentMessages "Check the change set for unsent messages, and if any are found, open up a message-list browser on them" | nameLine allChangedSelectors augList unsent | nameLine := '"' , self name , '"'. allChangedSelectors := Set new. (augList := self changedMessageListAugmented) do: [:each | each isValid ifTrue: [allChangedSelectors add: each methodSymbol]]. unsent := self systemNavigation allUnsentMessagesIn: allChangedSelectors. unsent size = 0 ifTrue: [^ self inform: 'There are no unsent messages in change set ' , nameLine]. self systemNavigation browseMessageList: (augList select: [:each | unsent includes: each methodSymbol]) name: 'Unsent messages in ' , nameLine! ! !ChangeSet methodsFor: 'filein/out' stamp: 'rbb 2/18/2005 14:21'! chooseSubjectPrefixForEmail | subjectIndex | subjectIndex := (UIManager default chooseFrom: #('Bug fix [FIX]' 'Enhancement [ENH]' 'Goodie [GOODIE]' 'Test suite [TEST]' 'None of the above (will not be archived)') title: 'What type of change set\are you submitting to the list?' withCRs). ^ #('[CS] ' '[FIX] ' '[ENH] ' '[GOODIE] ' '[TEST] ' '[CS] ') at: subjectIndex + 1! ! !ChangeSet methodsFor: 'filein/out' stamp: 'nk 10/15/2003 09:55'! defaultChangeSetDirectory ^self class defaultChangeSetDirectory! ! !ChangeSet methodsFor: 'filein/out' stamp: 'PeterHugossonMiller 9/3/2009 00:51'! fileOut "File out the receiver, to a file whose name is a function of the change-set name and a unique numeric tag." | slips nameToUse internalStream | self checkForConversionMethods. ChangeSet promptForDefaultChangeSetDirectoryIfNecessary. nameToUse := self defaultChangeSetDirectory nextNameFor: self name extension: FileStream cs. nameToUse := self defaultChangeSetDirectory fullNameFor: nameToUse. Cursor write showWhile: [ internalStream := (String new: 10000) writeStream. internalStream header; timeStamp. self fileOutPreambleOn: internalStream. self fileOutOn: internalStream. self fileOutPostscriptOn: internalStream. internalStream trailer. FileStream writeSourceCodeFrom: internalStream baseName: (nameToUse copyFrom: 1 to: nameToUse size - 3) isSt: false. ]. Preferences checkForSlips ifFalse: [^ self]. slips := self checkForSlips. (slips size > 0 and: [self confirm: 'Methods in this fileOut have halts or references to the Transcript or other ''slips'' in them. Would you like to browse them?' translated]) ifTrue: [self systemNavigation browseMessageList: slips name: 'Possible slips in ' , name]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'di 3/28/2000 09:35'! fileOutChangesFor: class on: stream "Write out all the method changes for this class." | changes | changes := Set new. (self methodChangesAtClass: class name) associationsDo: [:mAssoc | (mAssoc value = #remove or: [mAssoc value = #addedThenRemoved]) ifFalse: [changes add: mAssoc key]]. changes isEmpty ifFalse: [class fileOutChangedMessages: changes on: stream. stream cr]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'dvf 9/27/2005 19:04'! fileOutOn: stream "Write out all the changes the receiver knows about" | classList traits classes traitList list | (self isEmpty and: [stream isKindOf: FileStream]) ifTrue: [self inform: 'Warning: no changes to file out']. traits := self changedClasses reject: [:each | each isBehavior]. classes := self changedClasses select: [:each | each isBehavior]. traitList := self class traitsOrder: traits asOrderedCollection. classList := self class superclassOrder: classes asOrderedCollection. list := OrderedCollection new addAll: traitList; addAll: classList; yourself. "First put out rename, max classDef and comment changes." list do: [:aClass | self fileOutClassDefinition: aClass on: stream]. "Then put out all the method changes" list do: [:aClass | self fileOutChangesFor: aClass on: stream]. "Finally put out removals, final class defs and reorganization if any" list reverseDo: [:aClass | self fileOutPSFor: aClass on: stream]. self classRemoves asSortedCollection do: [:aClassName | stream nextChunkPut: 'Smalltalk removeClassNamed: #', aClassName; cr].! ! !ChangeSet methodsFor: 'filein/out' stamp: 'al 7/22/2008 21:35'! fileOutPSFor: class on: stream "Write out removals and initialization for this class." | dict changeType classRecord currentDef | classRecord := changeRecords at: class name ifAbsent: [^ self]. dict := classRecord methodChangeTypes. dict keysSortedSafely do: [:key | changeType := dict at: key. (#(remove addedThenRemoved) includes: changeType) ifTrue: [stream nextChunkPut: class name, ' removeSelector: ', key storeString; cr] ifFalse: [(key = #initialize and: [class isMeta]) ifTrue: [stream nextChunkPut: class soleInstance name, ' initialize'; cr]]]. ((classRecord includesChangeType: #change) and: [(currentDef := class definition) ~= (self fatDefForClass: class)]) ifTrue: [stream nextChunkPut: currentDef; cr ]. (classRecord includesChangeType: #reorganize) ifTrue: [class fileOutOrganizationOn: stream. stream cr]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'di 3/29/1999 13:35'! fileOutPostscriptOn: stream "If the receiver has a postscript, put it out onto the stream. " | aString | aString := self postscriptString. (aString ~~ nil and: [aString size > 0]) ifTrue: [stream nextChunkPut: aString "surroundedBySingleQuotes". stream cr; cr]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'di 3/29/1999 14:58'! fileOutPreambleOn: stream "If the receiver has a preamble, put it out onto the stream. " | aString | aString := self preambleString. (aString ~~ nil and: [aString size > 0]) ifTrue: [stream nextChunkPut: aString "surroundedBySingleQuotes". stream cr; cr]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'rbb 2/18/2005 14:16'! lookForSlips "Scan the receiver for changes that the user may regard as slips to be remedied" | slips nameLine msg | nameLine := ' "', self name, '" '. (slips := self checkForSlips) size == 0 ifTrue: [^ self inform: 'No slips detected in change set', nameLine]. msg := slips size == 1 ifTrue: [ 'One method in change set', nameLine, 'has a halt, reference to the Transcript, and/or some other ''slip'' in it. Would you like to browse it? ?'] ifFalse: [ slips size printString, ' methods in change set', nameLine, 'have halts or references to the Transcript or other ''slips'' in them. Would you like to browse them?']. (UIManager default chooseFrom: #('Ignore' 'Browse slips') title: msg) = 2 ifTrue: [self systemNavigation browseMessageList: slips name: 'Possible slips in ', name]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'sd 4/16/2003 09:16'! mailOut "Email a compressed version of this changeset to the squeak-dev list, so that it can be shared with everyone. (You will be able to edit the email before it is sent.)" | userName message slips | userName := MailSender userName. self checkForConversionMethods. Cursor write showWhile: [message := self buildMessageForMailOutWithUser: userName]. MailSender sendMessage: message. Preferences suppressCheckForSlips ifTrue: [^ self]. slips := self checkForSlips. (slips size > 0 and: [self confirm: 'Methods in this fileOut have halts or references to the Transcript or other ''slips'' in them. Would you like to browse them?']) ifTrue: [self systemNavigation browseMessageList: slips name: 'Possible slips in ' , name] ! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/15/2005 21:27'! objectForDataStream: refStrm "I am about to be written on an object file. Write a path to me in the other system instead." refStrm projectChangeSet == self ifTrue: [^ self]. "try to write reference for me" ^ DiskProxy global: #ChangeSet selector: #existingOrNewChangeSetNamed: args: (Array with: self name) "=== refStrm replace: self with: nil. ^ nil ===" ! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:03'! postscript "Answer the string representing the postscript. " ^postscript ifNotNil:[postscript isString ifTrue:[postscript] ifFalse:[postscript contents asString]]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:03'! postscript: aString "Answer the string representing the postscript. " postscript := aString! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:03'! postscriptString "Answer the string representing the postscript. " ^self postscript! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:03'! postscriptString: aString "Establish aString as the new contents of the postscript. " self postscript: aString! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 17:55'! preamble "Answer the string representing the preamble" ^preamble ifNotNil:[preamble isString ifTrue:[preamble] ifFalse:[preamble contents asString]]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:00'! preamble: aString "Establish aString as the new contents of the preamble. " preamble := aString! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:00'! preambleString "Answer the string representing the preamble" ^self preamble! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:00'! preambleString: aString "Establish aString as the new contents of the preamble. " self preamble: aString.! ! !ChangeSet methodsFor: 'filein/out' stamp: 'nk 7/2/2003 10:47'! preambleTemplate "Answer a string that will form the default contents for a change set's preamble. Just a first stab at what the content should be." ^ String streamContents: [:strm | strm nextPutAll: '"Change Set:'. "NOTE: fileIn recognizes preambles by this string." strm tab;tab; nextPutAll: self name. strm cr; nextPutAll: 'Date:'; tab; tab; tab; nextPutAll: Date today printString. strm cr; nextPutAll: 'Author:'; tab; tab; tab; nextPutAll: Preferences defaultAuthorName. strm cr; cr; nextPutAll: '"'] "ChangeSet current preambleTemplate"! ! !ChangeSet methodsFor: 'filein/out' stamp: 'ar 7/16/2005 18:02'! setPreambleToSay: aString "Make aString become the preamble of this change set" self preamble: aString! ! !ChangeSet methodsFor: 'filein/out' stamp: 'di 9/24/1999 12:33'! summaryString "Answer the string summarizing this changeSet" ^ self summaryStringDelta: 0 " To summarize all recent changeSets on a file... (FileStream newFileNamed: 'Summaries.txt') nextPutAll: (String streamContents: [:s | (ChangeSorter changeSetsNamedSuchThat: [:name | name first isDigit and: [name initialIntegerOrNil >= 948]]) do: [:cs | s nextPutAll: cs summaryString; cr]]); close To list all changeSets with a certain string in the preamble... (FileStream newFileNamed: 'MyUpdates.txt') nextPutAll: (String streamContents: [:s | ChangeSorter gatherChangeSetRevertables do: [:cs | (cs preambleString notNil and: [cs preambleString includesSubString: 'Author Name']) ifTrue: [s nextPutAll: cs summaryString; cr]]]); close "! ! !ChangeSet methodsFor: 'filein/out' stamp: 'dc 5/30/2008 10:17'! summaryStringDelta: delta "Answer the string summarizing this changeSet" | ps s2 date author line intName | ^ String streamContents: [ :s | intName := self name splitInteger. intName first isNumber ifTrue: [ s nextPutAll: (intName first + delta) printString , intName last ] ifFalse: [ s nextPutAll: intName first "weird convention of splitInteger" ]. (ps := self preambleString) ifNil: [ s cr ] ifNotNil: [ s2 := ps readStream. s2 match: 'Date:'; skipSeparators. date := s2 upTo: Character cr. s2 match: 'Author:'; skipSeparators. author := s2 upTo: Character cr. s nextPutAll: ' -- '; nextPutAll: author; nextPutAll: ' -- '; nextPutAll: date; cr. [ s2 atEnd ] whileFalse: [ line := s2 upTo: Character cr. (line isEmpty or: [ line = '"' ]) ifFalse: [ s nextPutAll: line; cr ] ] ] ]! ! !ChangeSet methodsFor: 'filein/out' stamp: 'sd 1/16/2004 21:31'! verboseFileOut "File out the receiver, to a file whose name is a function of the change-set name and either of the date & time or chosen to have a unique numeric tag, depending on the preference 'changeSetVersionNumbers'" ChangeSet current fileOut. Transcript cr; show: 'Changes filed out ', Date dateAndTimeNow printString! ! !ChangeSet methodsFor: 'initialization' stamp: 'di 3/29/2000 20:42'! beIsolationSetFor: aProject self isEmpty ifFalse: [self error: 'Must be empty at the start.']. isolatedProject := aProject. revertable := true.! ! !ChangeSet methodsFor: 'initialization' stamp: 'di 4/1/2000 12:00'! clear "Reset the receiver to be empty. " changeRecords := Dictionary new. preamble := nil. postscript := nil! ! !ChangeSet methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:44'! initialize "Initialize the receiver to be empty." super initialize. name ifNil: [^ self error: 'All changeSets must be registered, as in ChangeSorter newChangeSet']. revertable := false. self clear. ! ! !ChangeSet methodsFor: 'initialization'! isMoribund "Answer whether the receiver is obsolete and about to die; part of an effort to get such guys cleared out from the change sorter. 2/7/96 sw" ^ name == nil ! ! !ChangeSet methodsFor: 'initialization' stamp: 'sw 3/6/1999 09:31'! veryDeepCopyWith: deepCopier "Return self; this is NOT the way to launch new change sets!! Having this method here allows Change Sorters to be in parts bins"! ! !ChangeSet methodsFor: 'initialization' stamp: 'di 3/23/2000 12:14'! wither "The receiver is to be clobbered. Clear it out. 2/7/96 sw" self clear. name := nil! ! !ChangeSet methodsFor: 'initialization' stamp: 'di 9/21/2000 15:29'! zapHistory "Much stronger than trimHistory, but it should still leave the changeSet in good shape. Must not be done on revertable changeSets ChangeSet allInstancesDo: [:cs | cs zapHistory]." revertable ifTrue: [^ self]. "No can do" changeRecords do: [:chgRecord | chgRecord zapHistory]! ! !ChangeSet methodsFor: 'isolation layers' stamp: 'di 4/1/2000 09:25'! compileAll: newClass from: oldClass "If I have changes for this class, recompile them" (changeRecords at: newClass ifAbsent: [^ self]) compileAll: newClass from: oldClass ! ! !ChangeSet methodsFor: 'isolation layers' stamp: 'di 3/29/2000 14:47'! invoke "Do the first part of the invoke operation -- no particular hurry." changeRecords do: [:changeRecord | changeRecord invokePhase1]. "Complete the invoke process -- this must be very simple." "Replace method dicts for any method changes." changeRecords do: [:changeRecord | changeRecord invokePhase2]. Behavior flushCache. ! ! !ChangeSet methodsFor: 'isolation layers' stamp: 'di 4/13/2000 12:47'! isolatedProject "Return the isolated project for which I am the changeSet." ^ isolatedProject! ! !ChangeSet methodsFor: 'isolation layers' stamp: 'di 3/29/2000 13:59'! isolationSet: setOrNil setOrNil == self ifTrue: [isolationSet := nil] "Means this IS the isolation set" ifFalse: [isolationSet := setOrNil]! ! !ChangeSet methodsFor: 'isolation layers' stamp: 'di 3/29/2000 14:47'! revoke "Do the first part of the revoke operation -- this must be very simple." "Replace original method dicts if there are method changes." changeRecords do: [:changeRecord | changeRecord revokePhase1]. Behavior flushCache. "Complete the revoke process -- no particular hurry." changeRecords do: [:changeRecord | changeRecord revokePhase2]. ! ! !ChangeSet methodsFor: 'isolation layers' stamp: 'di 3/23/2000 12:00'! uninstall self halt. ! ! !ChangeSet methodsFor: 'method changes' stamp: 'sw 12/28/2000 18:08'! adoptSelector: aSelector forClass: aClass "Adopt the given selector/class combination as a change in the receiver" self noteNewMethod: (aClass methodDictionary at: aSelector) forClass: aClass selector: aSelector priorMethod: nil! ! !ChangeSet methodsFor: 'method changes' stamp: 'md 8/27/2005 16:37'! atSelector: selector class: class put: changeType selector isDoIt ifTrue: [^ self]. (self changeRecorderFor: class) atSelector: selector put: changeType. ! ! !ChangeSet methodsFor: 'method changes' stamp: 'sw 6/26/2001 12:15'! changedMessageList "Used by a message set browser to access the list view information." | messageList classNameInFull classNameInParts | messageList := OrderedCollection new. changeRecords associationsDo: [:clAssoc | classNameInFull := clAssoc key asString. classNameInParts := classNameInFull findTokens: ' '. (clAssoc value allChangeTypes includes: #comment) ifTrue: [messageList add: (MethodReference new setClassSymbol: classNameInParts first asSymbol classIsMeta: false methodSymbol: #Comment stringVersion: classNameInFull, ' Comment')]. clAssoc value methodChangeTypes associationsDo: [:mAssoc | (#(remove addedThenRemoved) includes: mAssoc value) ifFalse: [messageList add: (MethodReference new setClassSymbol: classNameInParts first asSymbol classIsMeta: classNameInParts size > 1 methodSymbol: mAssoc key stringVersion: classNameInFull, ' ' , mAssoc key)]]]. ^ messageList asSortedArray! ! !ChangeSet methodsFor: 'method changes' stamp: 'tk 6/7/1999 18:57'! changedMessageListAugmented "Even added classes have all messages in changedMessageList." ^ self changedMessageList asArray! ! !ChangeSet methodsFor: 'method changes' stamp: 'sw 4/19/2001 19:45'! hasAnyChangeForSelector: aSelector "Answer whether the receiver has any change under the given selector, whether it be add, change, or remove, for any class" changeRecords do: [:aRecord | (aRecord changedSelectors includes: aSelector) ifTrue: [^ true]]. ^ false! ! !ChangeSet methodsFor: 'method changes' stamp: 'RAA 5/28/2001 12:05'! messageListForChangesWhich: aBlock ifNone: ifEmptyBlock | answer | answer := self changedMessageListAugmented select: [ :each | aBlock value: each actualClass value: each methodSymbol ]. answer isEmpty ifTrue: [^ifEmptyBlock value]. ^answer ! ! !ChangeSet methodsFor: 'method changes' stamp: 'di 4/1/2000 12:00'! methodChangesAtClass: className "Return an old-style dictionary of method change types." ^(changeRecords at: className ifAbsent: [^ Dictionary new]) methodChangeTypes! ! !ChangeSet methodsFor: 'method changes' stamp: 'di 4/4/2000 11:14'! removeSelectorChanges: selector class: class "Remove all memory of changes associated with the argument, selector, in this class." | chgRecord | (chgRecord := changeRecords at: class name ifAbsent: [^ self]) removeSelector: selector. chgRecord hasNoChanges ifTrue: [changeRecords removeKey: class name]! ! !ChangeSet methodsFor: 'method changes' stamp: 'SqR 6/13/2000 19:16'! selectorsInClass: aClassName "Used by a ChangeSorter to access the list methods." ^ (changeRecords at: aClassName ifAbsent: [^#()]) changedSelectors! ! !ChangeSet methodsFor: 'moving changes' stamp: 'di 4/4/2000 09:37'! absorbClass: className from: otherChangeSet "Absorb into the receiver all the changes found in the class in the other change set. *** Classes renamed in otherChangeSet may have problems" | cls | (self changeRecorderFor: className) assimilateAllChangesIn: (otherChangeSet changeRecorderFor: className). (cls := Smalltalk classNamed: className) ifNotNil: [self absorbStructureOfClass: cls from: otherChangeSet]. ! ! !ChangeSet methodsFor: 'moving changes' stamp: 'di 3/23/2000 11:52'! absorbMethod: selector class: aClass from: aChangeSet "Absorb into the receiver all the changes for the method in the class in the other change set." | info | info := aChangeSet methodChanges at: aClass name ifAbsent: [Dictionary new]. self atSelector: selector class: aClass put: (info at: selector). ! ! !ChangeSet methodsFor: 'moving changes' stamp: 'sw 1/30/2001 15:41'! absorbStructureOfClass: aClass from: otherChangeSet "Absorb into the receiver all the structure and superclass info in the other change set. Used to write conversion methods." | sup next | otherChangeSet structures ifNil: [^ self]. (otherChangeSet structures includesKey: aClass name) ifFalse: [^ self]. structures ifNil: [structures := Dictionary new. superclasses := Dictionary new]. sup := aClass name. [(structures includesKey: sup) ifTrue: ["use what is here" true] ifFalse: [self flag: #noteToDan. "sw 1/30/2001 13:57 emergency workaround -- a case arose where the otherChangeSet's structures did not have the key, and it gummed up the works." (otherChangeSet structures includesKey: sup) ifTrue: [structures at: sup put: (otherChangeSet structures at: sup)]. next := otherChangeSet superclasses at: sup. superclasses at: sup put: next. (sup := next) = 'nil'] ] whileFalse. ! ! !ChangeSet methodsFor: 'moving changes' stamp: 'di 4/4/2000 11:21'! assimilateAllChangesFoundIn: otherChangeSet "Make all changes in otherChangeSet take effect on self as if they happened just now." otherChangeSet changedClassNames do: [:className | self absorbClass: className from: otherChangeSet] ! ! !ChangeSet methodsFor: 'moving changes' stamp: 'ar 7/16/2005 18:59'! editPreamble "edit the receiver's preamble, in a separate window. " self assurePreambleExists. UIManager default edit: self preamble label: 'Preamble for ChangeSet named ', name accept:[:aString| self preamble: aString]! ! !ChangeSet methodsFor: 'moving changes' stamp: 'di 4/4/2000 11:49'! expungeEmptyClassChangeEntries changeRecords keysAndValuesRemove: [:className :classRecord | classRecord hasNoChanges]! ! !ChangeSet methodsFor: 'moving changes' stamp: 'di 4/4/2000 12:40'! forgetAllChangesFoundIn: otherChangeSet "Remove from the receiver all method changes found in aChangeSet. The intention is facilitate the process of factoring a large set of changes into disjoint change sets. To use: in a change sorter, copy over all the changes you want into some new change set, then use the subtract-other-side feature to subtract those changes from the larger change set, and continue in this manner." otherChangeSet == self ifTrue: [^ self]. otherChangeSet changedClassNames do: [:className | self forgetChangesForClass: className in: otherChangeSet]. self expungeEmptyClassChangeEntries. " Old code... aChangeSet changedClassNames do: [:className | (cls := Smalltalk classNamed: className) ~~ nil ifTrue: [itsMethodChanges := aChangeSet methodChanges at: className ifAbsent: [Dictionary new]. itsMethodChanges associationsDo: [:assoc | self forgetChange: assoc value forSelector: assoc key class: cls]. myClassChange := self classChangeAt: className. myClassChange size > 0 ifTrue: [(aChangeSet classChangeAt: className) do: [:aChange | myClassChange remove: aChange ifAbsent: []]]. self noteClassForgotten: className]]. aChangeSet classRemoves do: [:className | (recorder := changeRecords at: className ifAbsent: []) ifNotNil: [recorder forgetClassRemoval]]. self expungeEmptyClassChangeEntries " ! ! !ChangeSet methodsFor: 'moving changes' stamp: 'di 4/4/2000 12:04'! forgetChangesForClass: className in: otherChangeSet "See forgetAllChangesFoundIn:. Used in culling changeSets." (self changeRecorderFor: className) forgetChangesIn: (otherChangeSet changeRecorderFor: className). self noteClassForgotten: className ! ! !ChangeSet methodsFor: 'moving changes' stamp: 'sw 3/5/1999 19:27'! hasPreamble ^ preamble notNil! ! !ChangeSet methodsFor: 'moving changes' stamp: 'nk 3/30/2002 09:13'! methodsWithAnyInitialsOtherThan: myInits "Return a collection of method refs whose author appears to be different from the given one, even historically" | slips method aTimeStamp | slips := Set new. self changedClasses do: [:aClass | (self methodChangesAtClass: aClass name) associationsDo: [ :mAssoc | (#(remove addedThenRemoved) includes: mAssoc value) ifFalse: [method := aClass compiledMethodAt: mAssoc key ifAbsent: [nil]. method ifNotNil: [ (aClass changeRecordsAt: mAssoc key) do: [ :chg | aTimeStamp := chg stamp. (aTimeStamp notNil and: [(aTimeStamp beginsWith: myInits) not]) ifTrue: [slips add: aClass name , ' ' , mAssoc key]]]]]]. ^ slips! ! !ChangeSet methodsFor: 'moving changes' stamp: 'nk 7/2/2003 10:47'! methodsWithInitialsOtherThan: myInits "Return a collection of method refs whose author appears to be different from the given one" | slips method aTimeStamp | slips := OrderedCollection new. self changedClasses do: [:aClass | (self methodChangesAtClass: aClass name) associationsDo: [:mAssoc | (#(remove addedThenRemoved) includes: mAssoc value) ifFalse: [method := aClass compiledMethodAt: mAssoc key ifAbsent: [nil]. method ifNotNil: [((aTimeStamp := Utilities timeStampForMethod: method) notNil and: [(aTimeStamp beginsWith: myInits) not]) ifTrue: [slips add: aClass name , ' ' , mAssoc key]]]]]. ^ slips "Smalltalk browseMessageList: (ChangeSet current methodsWithInitialsOtherThan: 'sw') name: 'authoring problems'"! ! !ChangeSet methodsFor: 'moving changes' stamp: 'nk 7/2/2003 10:47'! methodsWithoutComments "Return a collection representing methods in the receiver which have no precode comments" | slips | slips := OrderedCollection new. self changedClasses do: [:aClass | (self methodChangesAtClass: aClass name) associationsDo: [:mAssoc | (#(remove addedThenRemoved) includes: mAssoc value) ifFalse: [(aClass selectors includes: mAssoc key) ifTrue: [(aClass firstPrecodeCommentFor: mAssoc key) isEmptyOrNil ifTrue: [slips add: aClass name , ' ' , mAssoc key]]]]]. ^ slips "Smalltalk browseMessageList: (ChangeSet current methodsWithoutComments) name: 'methods lacking comments'"! ! !ChangeSet methodsFor: 'moving changes' stamp: 'di 4/1/2000 12:00'! removeClassAndMetaClassChanges: class "Remove all memory of changes associated with this class and its metaclass. 7/18/96 sw" changeRecords removeKey: class name ifAbsent: []. changeRecords removeKey: class class name ifAbsent: []. ! ! !ChangeSet methodsFor: 'moving changes' stamp: 'yo 8/30/2002 13:59'! removeClassChanges: class "Remove all memory of changes associated with this class" | cname | (class isString) ifTrue: [ cname := class ] ifFalse: [ cname := class name ]. changeRecords removeKey: cname ifAbsent: []. self noteClassForgotten: cname.! ! !ChangeSet methodsFor: 'moving changes' stamp: 'sw 3/5/1999 19:32'! removePreamble preamble := nil! ! !ChangeSet methodsFor: 'testing' stamp: 'sw 8/10/2002 22:21'! containsMethodAtPosition: aFilePosition "Answer whether the receiver contains the method logged at the given file position" "class: aClassSymbol" "(need class parameter to speed up?)" "<- dew 9/6/2001" changeRecords values do: [:classChangeRecord | classChangeRecord methodChanges values do: [:methodChangeRecord | | changeType | changeType := methodChangeRecord changeType. ((changeType == #add or: [changeType == #change]) and: [methodChangeRecord currentMethod notNil and: [methodChangeRecord currentMethod filePosition = aFilePosition]]) ifTrue: [^ true]]]. ^ false! ! !ChangeSet methodsFor: 'testing' stamp: 'RAA 10/19/2000 13:17'! isEmpty "Answer whether the receiver contains any elements." changeRecords ifNil: [^true]. ^ changeRecords isEmpty ! ! !ChangeSet methodsFor: 'testing' stamp: 'nk 7/2/2003 10:47'! methodsWithoutClassifications "Return a collection representing methods in the receiver which have not been categorized" | slips notClassified aSelector | notClassified := {'as yet unclassified' asSymbol. #all}. slips := OrderedCollection new. self changedClasses do: [:aClass | (self methodChangesAtClass: aClass name) associationsDo: [:mAssoc | (aClass selectors includes: (aSelector := mAssoc key)) ifTrue: [(notClassified includes: (aClass organization categoryOfElement: aSelector)) ifTrue: [slips add: aClass name , ' ' , aSelector]]]]. ^ slips "Smalltalk browseMessageList: (ChangeSet current methodsWithoutClassifications) name: 'unclassified methods'"! ! !ChangeSet methodsFor: 'testing' stamp: 'sw 8/3/1998 16:25'! okayToRemove ^ self okayToRemoveInforming: true! ! !ChangeSet methodsFor: 'testing' stamp: 'stephane.ducasse 7/10/2009 16:44'! okayToRemoveInforming: aBoolean "Answer whether it is okay to remove the receiver. If aBoolean is true, inform the receiver if it is not okay" | aName | aName := self name. self == self class current ifTrue: [aBoolean ifTrue: [self inform: 'Cannot remove "', aName, '" because it is the current change set.']. ^ false]. ^ true ! ! !ChangeSet methodsFor: 'private' stamp: 'di 3/23/2000 08:37'! addCoherency: className "SqR!! 19980923: If I recreate the class then don't remove it" (self changeRecorderFor: className) checkCoherence. " classRemoves remove: className ifAbsent: []. (classChanges includesKey: className) ifTrue: [(classChanges at: className) remove: #remove ifAbsent: []] "! ! !ChangeSet methodsFor: 'private' stamp: 'di 3/28/2000 14:40'! atClass: class add: changeType (self changeRecorderFor: class) noteChangeType: changeType fromClass: class! ! !ChangeSet methodsFor: 'private' stamp: 'di 4/1/2000 12:00'! atClass: class includes: changeType ^(changeRecords at: class name ifAbsent: [^false]) includesChangeType: changeType! ! !ChangeSet methodsFor: 'private' stamp: 'di 4/1/2000 12:00'! atSelector: selector class: class ^ (changeRecords at: class name ifAbsent: [^ #none]) atSelector: selector ifAbsent: [^ #none]! ! !ChangeSet methodsFor: 'private'! changed: anAspectSymbol with: aParameter "Allow objects to depend on the ChangeSet class instead of a particular instance of ChangeSet (which may be switched using projects)." ChangeSet changed: anAspectSymbol with: aParameter. super changed: anAspectSymbol with: aParameter! ! !ChangeSet methodsFor: 'private' stamp: 'yo 8/30/2002 13:59'! changeRecorderFor: class | cname | (class isString) ifTrue: [ cname := class ] ifFalse: [ cname := class name ]. "Later this will init the changeRecords so according to whether they should be revertable." ^ changeRecords at: cname ifAbsent: [^ changeRecords at: cname put: (ClassChangeRecord new initFor: cname revertable: revertable)]! ! !ChangeSet methodsFor: 'private' stamp: 'al 7/22/2008 21:36'! fileOutClassDefinition: class on: stream "Write out class definition for the given class on the given stream, if the class definition was added or changed." (self atClass: class includes: #rename) ifTrue: [stream nextChunkPut: 'Smalltalk renameClassNamed: #', (self oldNameFor: class), ' as: #', class name; cr]. (self atClass: class includes: #change) ifTrue: [ "fat definition only needed for changes" stream nextChunkPut: (self fatDefForClass: class); cr. DeepCopier new checkClass: class. "If veryDeepCopy weakly copies some inst vars in this class, warn author when new ones are added." ] ifFalse: [ (self atClass: class includes: #add) ifTrue: [ "use current definition for add" stream nextChunkPut: class definition; cr. DeepCopier new checkClass: class. "If veryDeepCopy weakly copies some inst vars in this class, warn author when new ones are added." ]. ]. (self atClass: class includes: #comment) ifTrue: [class theNonMetaClass organization putCommentOnFile: stream numbered: 0 moveSource: false forClass: class theNonMetaClass. stream cr]. ! ! !ChangeSet methodsFor: 'private' stamp: 'di 4/1/2000 12:00'! oldNameFor: class ^ (changeRecords at: class name) priorName! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ChangeSet class instanceVariableNames: 'current'! !ChangeSet class methodsFor: 'current changeset' stamp: 'ar 7/17/2005 10:48'! browseChangedMessages "Create and schedule a message browser on each method that has been changed." current isEmpty ifTrue: [^ self inform: 'There are no changed messages in the current change set.']. ToolSet openChangedMessageSet: current.! ! !ChangeSet class methodsFor: 'current changeset' stamp: 'wiz 9/19/2006 03:21'! current "return the current changeset assure first that we have a named changeset. To cure mantis #4535. " current isMoribund ifTrue: [(ChangeSet newChanges: (ChangeSet assuredChangeSetNamed: 'Unnamed'))] . ^ current! ! !ChangeSet class methodsFor: 'current changeset' stamp: 'em 3/31/2005 11:48'! currentChangeSetString "ChangeSet current currentChangeSetString" ^ 'Current Change Set: ' translated, self current name! ! !ChangeSet class methodsFor: 'current changeset' stamp: 'NS 1/16/2004 14:49'! newChanges: aChangeSet "Set the system ChangeSet to be the argument, aChangeSet. Tell the current project that aChangeSet is now its change set. When called from Project enter:, the setChangeSet: call is redundant but harmless; when called from code that changes the current-change-set from within a project, it's vital" SystemChangeNotifier uniqueInstance noMoreNotificationsFor: current. current isolationSet: nil. current := aChangeSet. SystemChangeNotifier uniqueInstance notify: aChangeSet ofAllSystemChangesUsing: #event:. Smalltalk currentProjectDo: [:proj | proj setChangeSet: aChangeSet. aChangeSet isolationSet: proj isolationSet]! ! !ChangeSet class methodsFor: 'current changeset' stamp: 'sd 5/22/2003 22:18'! noChanges "Initialize the system ChangeSet." current initialize! ! !ChangeSet class methodsFor: 'current changeset' stamp: 'sd 9/8/2006 21:05'! resetCurrentToNewUnnamedChangeSet current := self new. self newChanges: current ! ! !ChangeSet class methodsFor: 'defaults' stamp: 'nk 7/18/2004 16:13'! defaultChangeSetDirectory "Answer the directory in which to store ChangeSets. Answer the default directory if the preferred directory doesn't exist." | dir directoryName | directoryName := Preferences parameterAt: #defaultChangeSetDirectoryName ifAbsentPut: ['']. dir := directoryName isEmptyOrNil ifTrue: [ FileDirectory default ] ifFalse: [ FileDirectory default directoryNamed: directoryName ]. dir exists ifTrue: [^ dir]. ^ FileDirectory default! ! !ChangeSet class methodsFor: 'defaults' stamp: 'nk 3/24/2004 15:52'! defaultChangeSetDirectory: dirOrName "Set the Preference for storing change sets to the given directory or name (possibly relative). Rewrite directory names below the default directory as relative names. If dirOrName is an empty string, use the default directory." "ChangeSet defaultChangeSetDirectory: 'changeSets'" | dirName defaultFullName | dirName := dirOrName isString ifTrue: [FileDirectory default fullNameFor: dirOrName] ifFalse: [dirOrName fullName]. defaultFullName := FileDirectory default fullName. dirName = defaultFullName ifTrue: [dirName := ''] ifFalse: [(dirName beginsWith: defaultFullName , FileDirectory slash) ifTrue: [dirName := dirName copyFrom: defaultFullName size + 2 to: dirName size]]. Preferences setParameter: #defaultChangeSetDirectoryName to: dirName! ! !ChangeSet class methodsFor: 'defaults' stamp: 'dgd 9/6/2003 19:56'! defaultName ^ self uniqueNameLike: 'Unnamed' translated! ! !ChangeSet class methodsFor: 'defaults' stamp: 'alain.plantec 2/8/2009 18:54'! promptForDefaultChangeSetDirectoryIfNecessary "Check the Preference (if any), and prompt the user to change it if necessary. The default if the Preference is unset is the current directory. Answer the directory." "ChangeSet promptForDefaultChangeSetDirectoryIfNecessary" | choice directoryName dir message | directoryName := Preferences parameterAt: #defaultChangeSetDirectoryName ifAbsentPut: ['']. [dir := FileDirectory default directoryNamed: directoryName. dir exists] whileFalse: [message := 'The preferred change set directory' translated , ' (''{1}'') ' , 'does not exist.' translated , ' ' , 'Create it or use the default directory' translated , ' ({2})?' format: {directoryName. FileDirectory default pathName}. choice := UIManager default chooseFrom: (#('Create directory' 'Use default directory and forget preference' 'Choose another directory' ) collect: [:ea | ea translated]) message: message. choice = 1 ifTrue: [dir assureExistence]. choice = 3 ifTrue: [dir := UIManager default chooseDirectory. directoryName := dir ifNil: [''] ifNotNil: [dir pathName]]]. self defaultChangeSetDirectory: directoryName. ^ dir! ! !ChangeSet class methodsFor: 'defaults' stamp: 'ar 7/15/2005 21:24'! uniqueNameLike: aString | try | (self named: aString) ifNil: [^ aString]. 1 to: 999999 do: [:i | try := aString , i printString. (self named: try) ifNil: [^ try]]! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:20'! allChangeSetNames ^ self allChangeSets collect: [:c | c name]! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:10'! allChangeSets "Return the list of all current ChangeSets" ^ AllChangeSets! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:22'! allChangeSetsWithClass: class selector: selector class ifNil: [^ #()]. ^ self allChangeSets select: [:cs | (cs atSelector: selector class: class) ~~ #none]! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:17'! allChangeSets: aCollection "Return the list of all current ChangeSets" AllChangeSets := aCollection.! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:14'! basicNewChangeSet: newName | newSet | newName ifNil: [^ nil]. (self named: newName) ifNotNil: [self inform: 'Sorry that name is already used'. ^ nil]. newSet := self basicNewNamed: newName. AllChangeSets add: newSet. ^ newSet! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:11'! changeSetsNamedSuchThat: nameBlock "(ChangeSet changeSetsNamedSuchThat: [:name | name first isDigit and: [name initialInteger >= 373]]) do: [:cs | AllChangeSets remove: cs wither]" ^ AllChangeSets select: [:aChangeSet | nameBlock value: aChangeSet name]! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:26'! changeSet: aChangeSet containsClass: aClass | theClass | theClass := Smalltalk classNamed: aClass. theClass ifNil: [^ false]. ^ aChangeSet containsClass: theClass! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:26'! deleteChangeSetsNumberedLowerThan: anInteger "Delete all changes sets whose names start with integers smaller than anInteger" self removeChangeSetsNamedSuchThat: [:aName | aName first isDigit and: [aName initialIntegerOrNil < anInteger]]. "ChangeSet deleteChangeSetsNumberedLowerThan: (ChangeSorterPlus highestNumberedChangeSet name initialIntegerOrNil - 500)" ! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:24'! existingOrNewChangeSetNamed: aName | newSet | ^(self named: aName) ifNil: [ newSet := self basicNewNamed: aName. AllChangeSets add: newSet. newSet ]! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:12'! gatherChangeSets "ChangeSet gatherChangeSets" "Collect any change sets created in other projects" | allChangeSets obsolete | allChangeSets := AllChangeSets asSet. ChangeSet allSubInstances do: [:each | (allChangeSets includes: each) == (obsolete := each isMoribund) ifTrue:[ obsolete ifTrue: ["Was included and is obsolete." AllChangeSets remove: each] ifFalse: ["Was not included and is not obsolete." AllChangeSets add: each]]]. ^ AllChangeSets! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:20'! highestNumberedChangeSet "ChangeSorter highestNumberedChangeSet" | aList | aList := (self allChangeSetNames select: [:aString | aString startsWithDigit] thenCollect: [:aString | aString initialIntegerOrNil]). ^ (aList size > 0) ifTrue: [aList max] ifFalse: [nil] ! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:29'! mostRecentChangeSetWithChangeForClass: class selector: selector | hits | hits := self allChangeSets select: [:cs | (cs atSelector: selector class: class) ~~ #none]. hits isEmpty ifTrue: [^ 'not in any change set']. ^ 'recent cs: ', hits last name! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:11'! named: aName "Return the change set of the given name, or nil if none found. 1/22/96 sw" ^ AllChangeSets detect: [:aChangeSet | aChangeSet name = aName] ifNone: [nil]! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:13'! promoteToTop: aChangeSet "Make aChangeSet the first in the list from now on" AllChangeSets remove: aChangeSet ifAbsent: [^ self]. AllChangeSets add: aChangeSet! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:26'! removeChangeSetsNamedSuchThat: nameBlock (self changeSetsNamedSuchThat: nameBlock) do: [:cs | self removeChangeSet: cs]! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:13'! removeChangeSet: aChangeSet "Remove the given changeSet. Caller must assure that it's cool to do this" AllChangeSets remove: aChangeSet ifAbsent: []. aChangeSet wither ! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:26'! removeEmptyUnnamedChangeSets "Remove all change sets that are empty, whose names start with Unnamed, and which are not nailed down by belonging to a Project." "ChangeSorter removeEmptyUnnamedChangeSets" | toGo | (toGo := (self changeSetsNamedSuchThat: [:csName | csName beginsWith: 'Unnamed']) select: [:cs | cs isEmpty and: [cs okayToRemoveInforming: false]]) do: [:cs | self removeChangeSet: cs]. self inform: toGo size printString, ' change set(s) removed.'! ! !ChangeSet class methodsFor: 'enumerating' stamp: 'ar 7/15/2005 21:13'! secondaryChangeSet "Answer a likely change set to use as the second initial one in a Dual Change Sorter. " AllChangeSets size = 1 ifTrue: [^ AllChangeSets first]. AllChangeSets last == ChangeSet current ifTrue: [^ AllChangeSets at: (AllChangeSets size - 1)] ifFalse: [^ AllChangeSets last]! ! !ChangeSet class methodsFor: 'file list services' stamp: 'ar 7/15/2005 21:36'! fileReaderServicesForFile: fullName suffix: suffix ^ (FileStream isSourceFileSuffix: suffix) ifTrue: [ self services] ifFalse: [#()]! ! !ChangeSet class methodsFor: 'file list services' stamp: 'ar 7/15/2005 21:35'! serviceFileIntoNewChangeSet "Answer a service for installing a file into a new change set" ^ SimpleServiceEntry provider: self label: 'install into new change set' selector: #fileIntoNewChangeSet: description: 'install the file as a body of code in the image: create a new change set and file-in the selected file into it' buttonLabel: 'install'! ! !ChangeSet class methodsFor: 'file list services' stamp: 'ar 7/15/2005 21:36'! services ^ Array with: self serviceFileIntoNewChangeSet! ! !ChangeSet class methodsFor: 'filein/out' stamp: 'SqR 11/14/2000 11:36'! doWeFileOut: aClass given: aSet cache: cache | aClassAllSuperclasses aClassSoleInstanceAllSuperclasses | aClassAllSuperclasses := cache at: aClass ifAbsent: [cache at: aClass put: aClass allSuperclasses asArray]. (aSet includesAnyOf: aClassAllSuperclasses) ifTrue: [^false]. aClass isMeta ifFalse: [^true]. (aSet includes: aClass soleInstance) ifTrue: [^false]. aClassSoleInstanceAllSuperclasses := cache at: aClass soleInstance ifAbsent: [cache at: aClass soleInstance put: aClass soleInstance allSuperclasses asArray]. (aSet includesAnyOf: aClassSoleInstanceAllSuperclasses) ifTrue: [^false]. ^true! ! !ChangeSet class methodsFor: 'filein/out' stamp: 'marcus.denker 9/14/2008 21:10'! superclassOrder: classes "Arrange the classes in the collection, classes, in superclass order so the classes can be properly filed in. Do it in sets instead of ordered collections. SqR 4/12/2000 22:04" | all list aClass inclusionSet aClassIndex cache | list := classes copy. "list is indexable" inclusionSet := list asSet. cache := Dictionary new. all := OrderedCollection new: list size. list size timesRepeat: [ aClassIndex := list findFirst: [:one | one notNil and: [self doWeFileOut: one given: inclusionSet cache: cache]]. aClass := list at: aClassIndex. all addLast: aClass. inclusionSet remove: aClass. list at: aClassIndex put: nil ]. ^all! ! !ChangeSet class methodsFor: 'filein/out' stamp: 'al 7/18/2004 18:45'! traitsOrder: aCollection "Answer an OrderedCollection. The traits are ordered so they can be filed in." | traits | traits := aCollection asSortedCollection: [:t1 :t2 | (t1 isBaseTrait and: [t1 classTrait == t2]) or: [ (t2 traitComposition allTraits includes: t1) or: [ (t1 traitComposition allTraits includes: t2) not]]]. ^traits asArray! ! !ChangeSet class methodsFor: 'initialization' stamp: 'ar 7/15/2005 21:12'! initialize "ChangeSet initialize" AllChangeSets == nil ifTrue: [AllChangeSets := OrderedCollection new]. self gatherChangeSets. FileServices registerFileReader: self. ! ! !ChangeSet class methodsFor: 'instance creation' stamp: 'di 4/6/2001 09:43'! basicNewNamed: aName ^ (self basicNew name: aName) initialize! ! !ChangeSet class methodsFor: 'instance creation' stamp: 'ar 7/16/2005 15:17'! new "All current changeSets must be registered in the AllChangeSets collection. Due to a quirk of history, this is maintained as class variable of ChangeSorter." ^ self basicNewChangeSet: ChangeSet defaultName! ! !ChangeSet class methodsFor: 'scanning' stamp: 'ar 7/16/2005 19:22'! getRecentLocatorWithPrompt: aPrompt "Prompt with a menu of how far back to go. Return nil if user backs out. Otherwise return the number of characters back from the end of the .changes file the user wishes to include" "ChangeList getRecentPosition" | end changesFile banners positions pos chunk i | changesFile := (SourceFiles at: 2) readOnlyCopy. banners := OrderedCollection new. positions := OrderedCollection new. end := changesFile size. pos := SmalltalkImage current lastQuitLogPosition. [pos = 0 or: [banners size > 20]] whileFalse: [changesFile position: pos. chunk := changesFile nextChunk. i := chunk indexOfSubCollection: 'priorSource: ' startingAt: 1. i > 0 ifTrue: [positions addLast: pos. banners addLast: (chunk copyFrom: 5 to: i-2). pos := Number readFrom: (chunk copyFrom: i+13 to: chunk size)] ifFalse: [pos := 0]]. changesFile close. pos := UIManager default chooseFrom: banners values: positions title: aPrompt. pos == nil ifTrue: [^ nil]. ^ end - pos! ! !ChangeSet class methodsFor: 'scanning' stamp: 'ar 7/16/2005 15:12'! scanCategory: file "Scan anything that involves more than one chunk; method name is historical only" | itemPosition item tokens stamp isComment anIndex | itemPosition := file position. item := file nextChunk. isComment := (item includesSubString: 'commentStamp:'). (isComment or: [item includesSubString: 'methodsFor:']) ifFalse: ["Maybe a preamble, but not one we recognize; bail out with the preamble trick" ^{(ChangeRecord new file: file position: itemPosition type: #preamble)}]. tokens := Scanner new scanTokens: item. tokens size >= 3 ifTrue: [stamp := ''. anIndex := tokens indexOf: #stamp: ifAbsent: [nil]. anIndex ifNotNil: [stamp := tokens at: (anIndex + 1)]. tokens second == #methodsFor: ifTrue: [^ self scanFile: file category: tokens third class: tokens first meta: false stamp: stamp]. tokens third == #methodsFor: ifTrue: [^ self scanFile: file category: tokens fourth class: tokens first meta: true stamp: stamp]]. tokens second == #commentStamp: ifTrue: [stamp := tokens third. item := (ChangeRecord new file: file position: file position type: #classComment class: tokens first category: nil meta: false stamp: stamp). file nextChunk. file skipStyleChunk. ^Array with: item]. ^#()! ! !ChangeSet class methodsFor: 'scanning' stamp: 'ar 7/16/2005 15:11'! scanFile: file category: cat class: class meta: meta stamp: stamp | itemPosition method items | items := OrderedCollection new. [itemPosition := file position. method := file nextChunk. file skipStyleChunk. method size > 0] whileTrue:[ items add: (ChangeRecord new file: file position: itemPosition type: #method class: class category: cat meta: meta stamp: stamp)]. ^items! ! !ChangeSet class methodsFor: 'scanning' stamp: 'ar 7/16/2005 15:14'! scanFile: file from: startPosition to: stopPosition | itemPosition item prevChar changeList | changeList := OrderedCollection new. file position: startPosition. 'Scanning ', file localName, '...' displayProgressAt: Sensor cursorPoint from: startPosition to: stopPosition during: [:bar | [file position < stopPosition] whileTrue:[ bar value: file position. [file atEnd not and: [file peek isSeparator]] whileTrue: [prevChar := file next]. (file peekFor: $!!) ifTrue:[ (prevChar = Character cr or: [prevChar = Character lf]) ifTrue: [changeList addAll: (self scanCategory: file)]. ] ifFalse:[ itemPosition := file position. item := file nextChunk. file skipStyleChunk. item size > 0 ifTrue:[ changeList add: (ChangeRecord new file: file position: itemPosition type: #doIt). ]. ]. ]]. ^changeList! ! !ChangeSet class methodsFor: 'scanning' stamp: 'ar 7/16/2005 20:19'! scanVersionsOf: method class: class meta: meta category: cat selector: selector | position prevPos prevFileIndex preamble tokens sourceFilesCopy stamp changeList file | changeList := OrderedCollection new. position := method filePosition. sourceFilesCopy := SourceFiles collect:[:x | x ifNotNil:[x readOnlyCopy]]. method fileIndex == 0 ifTrue: [^ nil]. file := sourceFilesCopy at: method fileIndex. [position notNil & file notNil] whileTrue:[ file position: (0 max: position-150). "Skip back to before the preamble" preamble := method getPreambleFrom: file at: (0 max: position - 3). "Preamble is likely a linked method preamble, if we're in a changes file (not the sources file). Try to parse it for prior source position and file index" prevPos := nil. stamp := ''. (preamble findString: 'methodsFor:' startingAt: 1) > 0 ifTrue: [tokens := Scanner new scanTokens: preamble] ifFalse: [tokens := Array new "ie cant be back ref"]. ((tokens size between: 7 and: 8) and: [(tokens at: tokens size-5) = #methodsFor:]) ifTrue:[ (tokens at: tokens size-3) = #stamp: ifTrue:[ "New format gives change stamp and unified prior pointer" stamp := tokens at: tokens size-2. prevPos := tokens last. prevFileIndex := sourceFilesCopy fileIndexFromSourcePointer: prevPos. prevPos := sourceFilesCopy filePositionFromSourcePointer: prevPos. ] ifFalse: ["Old format gives no stamp; prior pointer in two parts" prevPos := tokens at: tokens size-2. prevFileIndex := tokens last. ]. (prevPos = 0 or: [prevFileIndex = 0]) ifTrue: [prevPos := nil] ]. ((tokens size between: 5 and: 6) and: [(tokens at: tokens size-3) = #methodsFor:]) ifTrue:[ (tokens at: tokens size-1) = #stamp: ifTrue: [ "New format gives change stamp and unified prior pointer" stamp := tokens at: tokens size. ] ]. changeList add: (ChangeRecord new file: file position: position type: #method class: class name category: cat meta: meta stamp: stamp). position := prevPos. prevPos notNil ifTrue:[file := sourceFilesCopy at: prevFileIndex]. ]. sourceFilesCopy do: [:x | x ifNotNil:[x close]]. ^changeList! ! !ChangeSet class methodsFor: 'services' stamp: 'ar 7/15/2005 21:30'! assuredChangeSetNamed: aName "Answer a change set of the given name. If one already exists, answer that, else create a new one and answer it." | existing | ^ (existing := self named: aName) ifNotNil: [existing] ifNil: [self basicNewChangeSet: aName]! ! !ChangeSet class methodsFor: 'services' stamp: 'ar 7/15/2005 21:28'! buildAggregateChangeSet "Establish a change-set named Aggregate which bears the union of all the changes in all the existing change-sets in the system (other than any pre-existing Aggregate). This can be useful when wishing to discover potential conflicts between a disk-resident change-set and an image. Formerly very useful, now some of its unique contributions have been overtaken by new features" | aggregateChangeSet | aggregateChangeSet := self existingOrNewChangeSetNamed: 'Aggregate'. aggregateChangeSet clear. self allChangeSets do: [:aChangeSet | aChangeSet == aggregateChangeSet ifFalse: [aggregateChangeSet assimilateAllChangesFoundIn: aChangeSet]] "ChangeSet buildAggregateChangeSet" ! ! !ChangeSet class methodsFor: 'services' stamp: 'ar 7/15/2005 21:37'! countOfChangeSetsWithClass: aClass andSelector: aSelector "Answer how many change sets record a change for the given class and selector" ^ (self allChangeSetsWithClass: aClass selector: aSelector) size! ! !ChangeSet class methodsFor: 'services' stamp: 'ar 7/15/2005 21:38'! doesAnyChangeSetHaveClass: aClass andSelector: aSelector "Answer whether any known change set bears a change for the given class and selector" ^ (self countOfChangeSetsWithClass: aClass andSelector: aSelector) > 0! ! !ChangeSet class methodsFor: 'services' stamp: 'jf 11/1/2008 13:29'! fileIntoNewChangeSet: fullName "File in all of the contents of the currently selected file, if any, into a new change set." | fn ff | fullName ifNil: [^ Beeper beep]. [ff := FileStream readOnlyFileNamed: (fn := GZipReadStream uncompressedFileName: fullName). ChangeSet newChangesFromStream: ff named: (FileDirectory localNameFor: fn)] ensure: [ff ifNotNil: [ff close]]! ! !ChangeSet class methodsFor: 'services' stamp: 'ar 7/15/2005 21:37'! fileOutChangeSetsNamed: nameList "File out the list of change sets whose names are provided" "ChangeSorter fileOutChangeSetsNamed: #('New Changes' 'miscTidies-sw')" | notFound aChangeSet infoString empty | notFound := OrderedCollection new. empty := OrderedCollection new. nameList do: [:aName | (aChangeSet := self named: aName) ifNotNil: [aChangeSet isEmpty ifTrue: [empty add: aName] ifFalse: [aChangeSet fileOut]] ifNil: [notFound add: aName]]. infoString := (nameList size - notFound size) printString, ' change set(s) filed out'. notFound size > 0 ifTrue: [infoString := infoString, ' ', notFound size printString, ' change set(s) not found:'. notFound do: [:aName | infoString := infoString, ' ', aName]]. empty size > 0 ifTrue: [infoString := infoString, ' ', empty size printString, ' change set(s) were empty:'. empty do: [:aName | infoString := infoString, ' ', aName]]. self inform: infoString! ! !ChangeSet class methodsFor: 'services' stamp: 'ar 7/15/2005 21:31'! newChangeSet "Prompt the user for a name, and establish a new change set of that name (if ok), making it the current changeset. Return nil of not ok, else return the actual changeset." | newName newSet | newName := UIManager default request: 'Please name the new change set:' initialAnswer: ChangeSet defaultName. newName isEmptyOrNil ifTrue: [^ nil]. newSet := self basicNewChangeSet: newName. newSet ifNotNil: [self newChanges: newSet]. ^ newSet! ! !ChangeSet class methodsFor: 'services' stamp: 'MiguelCoba 7/25/2009 02:00'! newChangeSet: aName "Makes a new change set called aName, add author full name to try to ensure a unique change set name." | newName | newName := aName , FileDirectory dot , Author fullName. ^ self basicNewChangeSet: newName! ! !ChangeSet class methodsFor: 'services' stamp: 'ar 7/15/2005 21:33'! newChangesFromStream: aStream named: aName "File in the code from the stream into a new change set whose name is derived from aName. Leave the 'current change set' unchanged. Return the new change set or nil on failure." | oldChanges newName newSet newStream | oldChanges := ChangeSet current. PreviousSet := oldChanges name. "so a Bumper update can find it" newName := aName sansPeriodSuffix. newSet := self basicNewChangeSet: newName. [newSet ifNotNil:[ (aStream respondsTo: #converter:) ifFalse: [ newStream := MultiByteBinaryOrTextStream with: (aStream contentsOfEntireFile). newStream reset. ] ifTrue: [ newStream := aStream. ]. self newChanges: newSet. newStream setConverterForCode. newStream fileInAnnouncing: 'Loading ', newName, '...'. Transcript cr; show: 'File ', aName, ' successfully filed in to change set ', newName]. aStream close] ensure: [self newChanges: oldChanges]. PreviousSet := nil. ^ newSet! ! ChangeSorter subclass: #ChangeSetBrowser instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tools-Changes'! !ChangeSetBrowser commentStamp: '' prior: 0! A tool allowing you to browse the methods of a single change set.! !ChangeSetBrowser methodsFor: 'initialization' stamp: 'alain.plantec 5/30/2008 10:45'! addModelItemsToWindowMenu: aMenu "Add model-related items to the given window menu" | oldTarget | oldTarget := aMenu defaultTarget. aMenu defaultTarget: self. aMenu addLine. aMenu add: 'rename change set' action: #rename. aMenu add: 'make changes go to me' action: #newCurrent. aMenu addLine. aMenu add: 'file out' action: #fileOut. aMenu add: 'browse methods' action: #browseChangeSet. aMenu addLine. myChangeSet hasPreamble ifTrue: [aMenu add: 'edit preamble' action: #addPreamble. aMenu add: 'remove preamble' action: #removePreamble] ifFalse: [aMenu add: 'add preamble' action: #addPreamble]. myChangeSet hasPostscript ifTrue: [aMenu add: 'edit postscript...' action: #editPostscript. aMenu add: 'remove postscript' action: #removePostscript] ifFalse: [aMenu add: 'add postscript...' action: #editPostscript]. aMenu addLine. aMenu add: 'destroy change set' action: #remove. aMenu addLine. aMenu addLine. aMenu add: 'what to show...' target: self action: #offerWhatToShowMenu. aMenu addLine. aMenu add: 'more...' action: #offerShiftedChangeSetMenu. aMenu defaultTarget: oldTarget. ^ aMenu! ! !ChangeSetBrowser methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:26'! openAsMorphIn: window rect: rect "Add a set of changeSetBrowser views to the given top view offset by the given amount" | aHeight | contents := ''. aHeight := 0.25. self addDependent: window. "so it will get changed: #relabel" window addMorph: (PluggableListMorphByItem on: self list: #classList selected: #currentClassName changeSelected: #currentClassName: menu: #classListMenu:shifted: keystroke: #classListKey:from:) frame: (((0.0@0 extent: 0.5 @ aHeight) scaleBy: rect extent) translateBy: rect origin). window addMorph: (PluggableListMorphByItem on: self list: #messageList selected: #currentSelector changeSelected: #currentSelector: menu: #messageMenu:shifted: keystroke: #messageListKey:from:) frame: (((0.5@0 extent: 0.5 @ aHeight) scaleBy: rect extent) translateBy: rect origin). self addLowerPanesTo: window at: (((0@aHeight corner: 1@1) scaleBy: rect extent) translateBy: rect origin) with: nil! ! !ChangeSetBrowser methodsFor: 'initialization' stamp: 'sw 3/14/2001 10:03'! wantsAnnotationPane "This kind of browser always wants annotation panes, so answer true" ^ true! ! !ChangeSetBrowser methodsFor: 'initialization' stamp: 'sw 3/9/2001 15:02'! wantsOptionalButtons "Sure, why not?" ^ true! ! !ChangeSetBrowser methodsFor: 'menu' stamp: 'sw 3/12/2001 14:07'! offerUnshiftedChangeSetMenu "The user chose 'more' from the shifted window menu; go back to the regular window menu" self containingWindow ifNotNil: [self containingWindow offerWindowMenu] ! ! !ChangeSetBrowser methodsFor: 'menu' stamp: 'MiguelCoba 7/25/2009 02:06'! shiftedChangeSetMenu: aMenu "Set up aMenu to hold items relating to the change-set-list pane when the shift key is down" aMenu title: 'Change set (shifted)'. aMenu addStayUpItemSpecial. aMenu add: 'conflicts with other change sets' action: #browseMethodConflicts. aMenu balloonTextForLastItem: 'Browse all methods that occur both in this change set and in at least one other change set.'. aMenu addLine. aMenu add: 'check for slips' action: #lookForSlips. aMenu balloonTextForLastItem: 'Check this change set for halts and references to Transcript.'. aMenu add: 'check for unsent messages' action: #checkForUnsentMessages. aMenu balloonTextForLastItem: 'Check this change set for messages that are not sent anywhere in the system'. aMenu add: 'check for uncommented methods' action: #checkForUncommentedMethods. aMenu balloonTextForLastItem: 'Check this change set for methods that do not have comments'. aMenu add: 'check for uncommented classes' action: #checkForUncommentedClasses. aMenu balloonTextForLastItem: 'Check for classes with code in this changeset which lack class comments'. Author fullNamePerSe isEmptyOrNil ifFalse: [aMenu add: 'check for other authors' action: #checkForAlienAuthorship. aMenu balloonTextForLastItem: 'Check this change set for methods whose current authoring stamp does not start with "', Author fullName, '"'. aMenu add: 'check for any other authors' action: #checkForAnyAlienAuthorship. aMenu balloonTextForLastItem: 'Check this change set for methods any of whose previous authoring stamps do not start with "', Author fullName, '"']. aMenu add: 'check for uncategorized methods' action: #checkForUnclassifiedMethods. aMenu balloonTextForLastItem: 'Check to see if any methods in the selected change set have not yet been assigned to a category. If any are found, open a browser on them.'. aMenu addLine. aMenu add: 'inspect change set' action: #inspectChangeSet. aMenu balloonTextForLastItem: 'Open an inspector on this change set. (There are some details in a change set which you don''t see in a change sorter.)'. aMenu add: 'update' action: #update. aMenu balloonTextForLastItem: 'Update the display for this change set. (This is done automatically when you activate this window, so is seldom needed.)'. aMenu add: 'trim history' action: #trimHistory. aMenu balloonTextForLastItem: ' Drops any methods added and then removed, as well as renaming and reorganization of newly-added classes. NOTE: can cause confusion if later filed in over an earlier version of these changes'. aMenu add: 'clear this change set' action: #clearChangeSet. aMenu balloonTextForLastItem: 'Reset this change set to a pristine state where it holds no information. CAUTION: this is destructive and irreversible!!'. aMenu add: 'uninstall this change set' action: #uninstallChangeSet. aMenu balloonTextForLastItem: 'Attempt to uninstall this change set. CAUTION: this may not work completely and is irreversible!!'. aMenu addLine. aMenu add: 'more...' action: #offerUnshiftedChangeSetMenu. aMenu balloonTextForLastItem: 'Takes you back to the primary change-set menu.'. ^ aMenu! ! ElementCategory subclass: #ChangeSetCategory instanceVariableNames: 'membershipSelector' classVariableNames: '' poolDictionaries: '' category: 'Tools-Changes'! !ChangeSetCategory commentStamp: '' prior: 0! A ChangeSetCategory represents a list of change sets to be shown in a ChangeSorter. It computes whether a given change set is in the list by sending its membershipSelector to ChangeSorter (i.e. the class object) with the change set as message argument.! !ChangeSetCategory methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:26'! membershipSelector: aSelector "Set the membershipSelector" membershipSelector := aSelector! ! !ChangeSetCategory methodsFor: 'miscellaneous' stamp: 'sd 5/23/2003 14:25'! defaultChangeSetToShow "Answer the name of a change-set to show" ^ ChangeSet current! ! !ChangeSetCategory methodsFor: 'miscellaneous' stamp: 'sd 11/20/2005 21:26'! reconstituteList "Clear out the receiver's elements and rebuild them" | newMembers | "First determine newMembers and check if they have not changed..." newMembers := ChangeSorter allChangeSets select: [:aChangeSet | ChangeSorter perform: membershipSelector with: aChangeSet]. (newMembers collect: [:cs | cs name]) = keysInOrder ifTrue: [^ self "all current"]. "Things have changed. Need to recompute the whole category" self clear. newMembers do: [:aChangeSet | self fasterElementAt: aChangeSet name asSymbol put: aChangeSet] ! ! !ChangeSetCategory methodsFor: 'queries' stamp: 'sw 4/11/2001 16:11'! acceptsManualAdditions "Answer whether the user is allowed manually to manipulate the contents of the change-set-category." ^ false! ! !ChangeSetCategory methodsFor: 'queries' stamp: 'sd 11/20/2005 21:26'! changeSetList "Answer the list of change-set names in the category" | aChangeSet | self reconstituteList. keysInOrder size == 0 ifTrue: ["don't tolerate emptiness, because ChangeSorters gag when they have no change-set selected" aChangeSet := ChangeSorter assuredChangeSetNamed: 'New Changes'. self elementAt: aChangeSet name put: aChangeSet]. ^ keysInOrder reversed! ! !ChangeSetCategory methodsFor: 'queries' stamp: 'sw 4/5/2001 17:26'! hasChangeForClassName: aClassName selector: aSelector otherThanIn: excludedChangeSet "Answer whether any change set in this category, other than the excluded one, has a change marked for the given class and selector" self elementsInOrder do: [:aChangeSet | (aChangeSet ~~ excludedChangeSet and: [((aChangeSet methodChangesAtClass: aClassName) includesKey: aSelector)]) ifTrue: [^ true]]. ^ false! ! !ChangeSetCategory methodsFor: 'queries' stamp: 'sw 3/30/2001 14:04'! includesChangeSet: aChangeSet "Answer whether the receiver includes aChangeSet in its retrieval list" ^ ChangeSorter perform: membershipSelector with: aChangeSet! ! !ChangeSetCategory methodsFor: 'services' stamp: 'sd 11/20/2005 21:26'! fileOutAllChangeSets "File out all the nonempty change sets in the current category, suppressing the checks for slips that might otherwise ensue. Obtain user confirmation before undertaking this possibly prodigious task." | aList | aList := self elementsInOrder select: [:aChangeSet | aChangeSet isEmpty not]. aList size == 0 ifTrue: [^ self inform: 'sorry, all the change sets in this category are empty']. (self confirm: 'This will result in filing out ', aList size printString, ' change set(s) Are you certain you want to do this?') ifFalse: [^ self]. Preferences setFlag: #checkForSlips toValue: false during: [ChangeSorter fileOutChangeSetsNamed: (aList collect: [:m | m name]) asSortedArray]! ! !ChangeSetCategory methodsFor: 'services' stamp: 'alain.plantec 5/30/2008 10:48'! fillAggregateChangeSet "Create a change-set named Aggregate and pour into it all the changes in all the change-sets of the currently-selected category" | aggChangeSet | aggChangeSet := ChangeSorter assuredChangeSetNamed: #Aggregate. aggChangeSet clear. aggChangeSet setPreambleToSay: '"Change Set: Aggregate Created at ', Time now printString, ' on ', Date today printString, ' by combining all the changes in all the change sets in the category ', categoryName printString, '"'. (self elementsInOrder copyWithout: aggChangeSet) do: [:aChangeSet | aggChangeSet assimilateAllChangesFoundIn: aChangeSet]. SystemWindow wakeUpTopWindowUponStartup ! ! ChangeSetCategory subclass: #ChangeSetCategoryWithParameters instanceVariableNames: 'parameters' classVariableNames: '' poolDictionaries: '' category: 'Tools-Changes'! !ChangeSetCategoryWithParameters methodsFor: 'as yet unclassified' stamp: 'nk 6/26/2002 12:34'! acceptsManualAdditions "Answer whether the user is allowed manually to manipulate the contents of the change-set-category." ^ true! ! !ChangeSetCategoryWithParameters methodsFor: 'as yet unclassified' stamp: 'nk 6/26/2002 12:43'! addChangeSet: aChangeSet self inform: 'sorry, you can''t do that'! ! !ChangeSetCategoryWithParameters methodsFor: 'as yet unclassified' stamp: 'nk 6/26/2002 12:08'! includesChangeSet: aChangeSet "Answer whether the receiver includes aChangeSet in its retrieval list" ^ ChangeSorter perform: membershipSelector withArguments: { aChangeSet } , parameters! ! !ChangeSetCategoryWithParameters methodsFor: 'as yet unclassified' stamp: 'sd 11/20/2005 21:26'! parameters: anArray parameters := anArray! ! !ChangeSetCategoryWithParameters methodsFor: 'as yet unclassified' stamp: 'sd 11/20/2005 21:26'! reconstituteList "Clear out the receiver's elements and rebuild them" | newMembers | "First determine newMembers and check if they have not changed..." newMembers := ChangeSorter allChangeSets select: [:aChangeSet | ChangeSorter perform: membershipSelector withArguments: { aChangeSet }, parameters]. (newMembers collect: [:cs | cs name]) = keysInOrder ifTrue: [^ self "all current"]. "Things have changed. Need to recompute the whole category" self clear. newMembers do: [:aChangeSet | self fasterElementAt: aChangeSet name asSymbol put: aChangeSet]! ! TestCase subclass: #ChangeSetClassChangesTest instanceVariableNames: 'saveCurrentChangeSet addedChangeSetAccessor' classVariableNames: '' poolDictionaries: '' category: 'Tests-Bugs'! !ChangeSetClassChangesTest commentStamp: 'dtl 2/19/2005 13:21' prior: 0! Class category changes are not being properly added to the default changeset in Squeak 3.7. This test case will pass in Squeak 3.6, and fail in Squeak 3.[7-9]. ! !ChangeSetClassChangesTest methodsFor: 'running' stamp: 'marcus.denker 11/10/2008 10:04'! tearDown (Smalltalk classNamed: #JunkClass) ifNotNil: [:c | c removeFromSystem: true]. SystemOrganization removeCategory: #'DeleteMe-1'. SystemOrganization removeCategory: #'DeleteMe-2'. ChangeSet current removeClassChanges: 'JunkClass' ! ! !ChangeSetClassChangesTest methodsFor: 'support' stamp: 'dtl 2/19/2005 13:08'! isDefinition: firstString equivalentTo: secondString "When a class definition is reconstructed with #fatDefForClass, it may contain extra trailing space characters in parts of the definition. This is probably a minor bug, but it should be overlooked for purposes of testing the change set update mechanism. The expedient here is to just remove spaces before comparing the definition strings." ^ firstString notNil and: [(firstString copyReplaceAll: ' ''' with: '''') = (secondString copyReplaceAll: ' ''' with: '''')]! ! !ChangeSetClassChangesTest methodsFor: 'testing' stamp: 'stephaneducasse 2/3/2006 22:39'! testAddInstanceVariable "Adding an instance variable to the class should result in a change record being added to the current change set." | saveClassDefinition | "Define a class and save its definition" Object subclass: #JunkClass instanceVariableNames: 'zzz' classVariableNames: '' poolDictionaries: '' category: 'DeleteMe-1'. saveClassDefinition := (Smalltalk classNamed: #JunkClass) definition. self assert: (self isDefinition: saveClassDefinition equivalentTo: (ChangeSet current fatDefForClass: (Smalltalk classNamed: #JunkClass))). "Redefine the class, adding one instance variable" Object subclass: #JunkClass instanceVariableNames: 'zzz aaa' classVariableNames: '' poolDictionaries: '' category: 'DeleteMe-1'. "Assert that the class definition has changed" self deny: (self isDefinition: (Smalltalk classNamed: #JunkClass) definition equivalentTo: saveClassDefinition). self deny: (self isDefinition: saveClassDefinition equivalentTo: (ChangeSet current fatDefForClass: (Smalltalk classNamed: #JunkClass))). self assert: (self isDefinition: (Smalltalk classNamed: #JunkClass) definition equivalentTo: (ChangeSet current fatDefForClass: (Smalltalk classNamed: #JunkClass))). "Assert that the change has been recorded in the current change set" self assert: (self isDefinition: (ChangeSet current changeRecorderFor: (Smalltalk classNamed: #JunkClass)) priorDefinition equivalentTo: saveClassDefinition). ! ! !ChangeSetClassChangesTest methodsFor: 'testing' stamp: 'dtl 2/19/2005 11:55'! testAddInstanceVariableAddsNewChangeRecord "Changing the class category for a class should result in a change record being updated in the current change set." "At the start of this test, JunkClass should not exist, and there should be no change records pertaining to it in the change set." self deny: (Smalltalk hasClassNamed: 'JunkClass'). self assert: (ChangeSet current changeRecorderFor: (Smalltalk classNamed: #JunkClass)) thisName = 'nil'. "Remove bogus change records created as side effect of preceding assert" ChangeSet current removeClassChanges: 'nil'. "Define a class and save its definition" Object subclass: #JunkClass instanceVariableNames: 'zzz' classVariableNames: '' poolDictionaries: '' category: 'DeleteMe-1'. "Forget about JunkClass in the change set" ChangeSet current removeClassChanges: 'JunkClass'. "Redefine the class, adding one instance variable" Object subclass: #JunkClass instanceVariableNames: 'zzz aaa' classVariableNames: '' poolDictionaries: '' category: 'DeleteMe-1'. "A change record should now exist in the change set" self assert: (self isDefinition: (ChangeSet current changeRecorderFor: (Smalltalk classNamed: #JunkClass)) priorDefinition equivalentTo: 'Object subclass: #JunkClass instanceVariableNames: ''zzz '' classVariableNames: '''' poolDictionaries: '''' category: ''DeleteMe-1''') ! ! !ChangeSetClassChangesTest methodsFor: 'testing' stamp: 'stephaneducasse 2/3/2006 22:39'! testChangeClassCategory "Changing the class category for a class should result in a change record being added to the current change set." | saveClassDefinition | "Define a class and save its definition" Object subclass: #JunkClass instanceVariableNames: 'zzz' classVariableNames: '' poolDictionaries: '' category: 'DeleteMe-1'. saveClassDefinition := (Smalltalk classNamed: #JunkClass) definition. self assert: saveClassDefinition = (ChangeSet current fatDefForClass: (Smalltalk classNamed: #JunkClass)). "Redefine the class, changing only the class category" Object subclass: #JunkClass instanceVariableNames: 'zzz' classVariableNames: '' poolDictionaries: '' category: 'DeleteMe-2'. "Assert that the class definition has changed" self deny: (self isDefinition: (Smalltalk classNamed: #JunkClass) definition equivalentTo: saveClassDefinition). self deny: (self isDefinition: saveClassDefinition equivalentTo: (ChangeSet current fatDefForClass: (Smalltalk classNamed: #JunkClass))). self assert: (self isDefinition: (Smalltalk classNamed: #JunkClass) definition equivalentTo: (ChangeSet current fatDefForClass: (Smalltalk classNamed: #JunkClass))). "Assert that the change has been recorded in the current change set" self assert: (self isDefinition: (ChangeSet current changeRecorderFor: (Smalltalk classNamed: #JunkClass)) priorDefinition equivalentTo: 'Object subclass: #JunkClass instanceVariableNames: ''zzz '' classVariableNames: '''' poolDictionaries: '''' category: ''DeleteMe-2''')! ! !ChangeSetClassChangesTest methodsFor: 'testing' stamp: 'dtl 2/19/2005 12:01'! testChangeClassCategoryAddsNewChangeRecord "Changing the class category for a class should result in a change record being updated in the current change set." "At the start of this test, JunkClass should not exist, and there should be no change records pertaining to it in the change set." self deny: (Smalltalk hasClassNamed: 'JunkClass'). self assert: (ChangeSet current changeRecorderFor: (Smalltalk classNamed: #JunkClass)) thisName = 'nil'. "Remove bogus change records created as side effect of preceding assert" ChangeSet current removeClassChanges: 'nil'. "Define a class and save its definition" Object subclass: #JunkClass instanceVariableNames: 'zzz' classVariableNames: '' poolDictionaries: '' category: 'DeleteMe-1'. "Forget about JunkClass in the change set" ChangeSet current removeClassChanges: 'JunkClass'. "Redefine the class, changing only the class category" Object subclass: #JunkClass instanceVariableNames: 'zzz' classVariableNames: '' poolDictionaries: '' category: 'DeleteMe-2'. "A change record should now exist in the change set" self assert: (self isDefinition: (ChangeSet current changeRecorderFor: (Smalltalk classNamed: #JunkClass)) priorDefinition equivalentTo: 'Object subclass: #JunkClass instanceVariableNames: ''zzz '' classVariableNames: '''' poolDictionaries: '''' category: ''DeleteMe-2''')! ! !ChangeSetClassChangesTest methodsFor: 'testing' stamp: 'wiz 8/13/2006 17:55'! testInitialChangeSet "Run this to assure the initial changeset is named. Checks bug found in 3.9 7052." "self new testInitialChangeSet" "self run: #testInitialChangeSet" self deny: (ChangeSet current printString = 'a ChangeSet named ') . ^true! ! CodeHolder subclass: #ChangeSorter instanceVariableNames: 'parent myChangeSet currentClassName currentSelector priorChangeSetList changeSetCategory' classVariableNames: '' poolDictionaries: '' category: 'Tools-Changes'! !ChangeSorter commentStamp: '' prior: 0! I display a ChangeSet. Two of me are in a DualChangeSorter.! !ChangeSorter methodsFor: 'access' stamp: 'tk 4/29/1998 08:22'! changeSet ^ myChangeSet! ! !ChangeSorter methodsFor: 'access' stamp: 'sw 3/29/2001 14:45'! changeSetCategory "Answer the current changeSetCategory object that governs which change sets are shown in this ChangeSorter" ^ changeSetCategory ifNil: [self setDefaultChangeSetCategory]! ! !ChangeSorter methodsFor: 'access' stamp: 'sw 1/27/2000 11:19'! changeSetCurrentlyDisplayed ^ myChangeSet! ! !ChangeSorter methodsFor: 'access' stamp: 'tk 4/30/1998 13:37'! label ^ self labelString! ! !ChangeSorter methodsFor: 'access' stamp: 'sd 5/23/2003 14:25'! labelString "The label for my entire window. The large button that displays my name is gotten via mainButtonName" ^ String streamContents: [:aStream | aStream nextPutAll: (ChangeSet current == myChangeSet ifTrue: ['Changes go to "', myChangeSet name, '"'] ifFalse: ['ChangeSet: ', myChangeSet name]). (self changeSetCategory categoryName ~~ #All) ifTrue: [aStream nextPutAll: ' - ', self parenthesizedCategoryName]]! ! !ChangeSorter methodsFor: 'access' stamp: 'sma 11/11/2000 23:28'! modelWakeUp "A window with me as model is being entered. Make sure I am up-to-date with the changeSets." self canDiscardEdits ifTrue: [self update]! ! !ChangeSorter methodsFor: 'access' stamp: 'sd 11/20/2005 21:26'! myChangeSet: anObject myChangeSet := anObject! ! !ChangeSorter methodsFor: 'access' stamp: 'tk 4/24/1998 08:42'! parent ^ parent! ! !ChangeSorter methodsFor: 'access' stamp: 'sd 11/20/2005 21:26'! parent: anObject parent := anObject! ! !ChangeSorter methodsFor: 'access' stamp: 'sw 3/29/2001 22:51'! parenthesizedCategoryName "Answer my category name in parentheses" ^ ' (', self changeSetCategory categoryName, ')'! ! !ChangeSorter methodsFor: 'access' stamp: 'sd 11/20/2005 21:26'! showChangeSet: chgSet myChangeSet == chgSet ifFalse: [ myChangeSet := chgSet. currentClassName := nil. currentSelector := nil]. self changed: #relabel. self changed: #currentCngSet. "new -- list of sets" self changed: #mainButtonName. "old, button" self changed: #classList. self changed: #messageList. self setContents. self contentsChanged.! ! !ChangeSorter methodsFor: 'access' stamp: 'pk 10/17/2006 09:37'! showChangeSetNamed: aName self showChangeSet: (ChangesOrganizer changeSetNamed: aName) ! ! !ChangeSorter methodsFor: 'annotation' stamp: 'sw 2/22/2001 10:35'! addPriorVersionsCountForSelector: aSelector ofClass: aClass to: aStream "Add an annotation detailing the prior versions count. Specially handled here for the case of a selector no longer in the system, whose prior version is pointed to by the lost-method pointer in the change held on to by the changeset" (aClass includesSelector: aSelector) ifTrue: [^ super addPriorVersionsCountForSelector: aSelector ofClass: aClass to: aStream]. aStream nextPutAll: ((myChangeSet methodInfoFromRemoval: {aClass name. aSelector}) ifNil: ['no prior versions'] ifNotNil: ['version(s) retrievable here']), self annotationSeparator! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:36'! browseMethodConflicts "Check to see if any other change set also holds changes to any methods in the selected change set; if so, open a browser on all such." | aList | aList := myChangeSet messageListForChangesWhich: [ :aClass :aSelector | (ChangesOrganizer allChangeSetsWithClass: aClass selector: aSelector) size > 1 ] ifNone: [^ self inform: 'No other change set has changes for any method in this change set.']. MessageSet openMessageList: aList name: 'Methods in "', myChangeSet name, '" that are also in other change sets (', aList size printString, ')' ! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:48'! changeSetCategories ^ ChangesOrganizer changeSetCategories! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:48'! chooseChangeSetCategoryInMorphic "Present the user with a list of change-set-categories and let her choose one. In this morphic variant, we include balloon help" | aMenu | aMenu := MenuMorph new defaultTarget: self. aMenu title: 'Choose the category of change sets to show in this Change Sorter (red = current choice)'. self changeSetCategories elementsInOrder do: [:aCategory | aMenu add: aCategory categoryName target: self selector: #showChangeSetCategory: argument: aCategory. aCategory == changeSetCategory ifTrue: [aMenu lastItem color: Color red]. aMenu balloonTextForLastItem: aCategory documentation]. aMenu popUpInWorld! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:36'! chooseCngSet "Present the user with an alphabetical list of change set names, and let her choose one" | changeSetsSortedAlphabetically chosen | self okToChange ifFalse: [^ self]. changeSetsSortedAlphabetically := self changeSetList asSortedCollection: [:a :b | a asLowercase withoutLeadingDigits < b asLowercase withoutLeadingDigits]. chosen := (SelectionMenu selections: changeSetsSortedAlphabetically) startUp. chosen ifNil: [^ self]. self showChangeSet: (ChangesOrganizer changeSetNamed: chosen)! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:49'! makeNewCategory "Create a new, static change-set category, which will be populated entirely by change sets that have been manually placed in it" | catName aCategory | catName := UIManager default request: 'Please give the new category a name' initialAnswer: ''. catName isEmptyOrNil ifTrue: [^ self]. catName := catName asSymbol. (self changeSetCategories includesKey: catName) ifTrue: [^ self inform: 'Sorry, there is already a category of that name']. aCategory := StaticChangeSetCategory new categoryName: catName. self changeSetCategories elementAt: catName put: aCategory. aCategory addChangeSet: myChangeSet. self showChangeSetCategory: aCategory! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:49'! makeNewCategoryShowingClassChanges "Create a new, static change-set category, which will be populated entirely by change sets that have been manually placed in it" | catName aCategory clsName | clsName := self selectedClass ifNotNil: [self selectedClass name ] ifNil: ['']. clsName := UIManager default request: 'Which class?' initialAnswer: clsName. clsName isEmptyOrNil ifTrue: [^ self]. catName := ('Changes to ', clsName) asSymbol. (self changeSetCategories includesKey: catName) ifTrue: [^ self inform: 'Sorry, there is already a category of that name']. aCategory := ChangeSetCategoryWithParameters new categoryName: catName. aCategory membershipSelector: #changeSet:containsClass: ; parameters: { clsName }. self changeSetCategories elementAt: catName put: aCategory. aCategory reconstituteList. self showChangeSetCategory: aCategory! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:49'! removeCategory "Remove the current category" | itsName | self changeSetCategory acceptsManualAdditions ifFalse: [^ self inform: 'sorry, you can only remove manually-added categories.']. (self confirm: 'Really remove the change-set-category named ', (itsName := changeSetCategory categoryName), '?') ifFalse: [^ self]. self changeSetCategories removeElementAt: itsName. self setDefaultChangeSetCategory. self update! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:36'! removePrompting: doPrompt "Completely destroy my change set. Check if it's OK first, and if doPrompt is true, get the user to confirm his intentions first." | message aName changeSetNumber msg | aName := myChangeSet name. myChangeSet okayToRemove ifFalse: [^ self]. "forms current changes for some project" (myChangeSet isEmpty or: [doPrompt not]) ifFalse: [message := 'Are you certain that you want to remove (destroy) the change set named "', aName, '" ?'. (self confirm: message) ifFalse: [^ self]]. doPrompt ifTrue: [msg := myChangeSet hasPreamble ifTrue: [myChangeSet hasPostscript ifTrue: ['a preamble and a postscript'] ifFalse: ['a preamble']] ifFalse: [myChangeSet hasPostscript ifTrue: ['a postscript'] ifFalse: ['']]. msg isEmpty ifFalse: [(self confirm: 'Caution!! This change set has ', msg, ' which will be lost if you destroy the change set. Do you really want to go ahead with this?') ifFalse: [^ self]]]. "Go ahead and remove the change set" changeSetNumber := myChangeSet name initialIntegerOrNil. changeSetNumber ifNotNil: [SystemVersion current unregisterUpdate: changeSetNumber]. ChangesOrganizer removeChangeSet: myChangeSet. self showChangeSet: ChangeSet current.! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:49'! renameCategory "Obtain a new name for the category and, if acceptable, apply it" | catName oldName | self changeSetCategory acceptsManualAdditions ifFalse: [^ self inform: 'sorry, you can only rename manually-added categories.']. catName := UIManager default request: 'Please give the new category a name' initialAnswer: (oldName := changeSetCategory categoryName). catName isEmptyOrNil ifTrue: [^ self]. (catName := catName asSymbol) = oldName ifTrue: [^ self inform: 'no change.']. (self changeSetCategories includesKey: catName) ifTrue: [^ self inform: 'Sorry, there is already a category of that name']. changeSetCategory categoryName: catName. self changeSetCategories removeElementAt: oldName. self changeSetCategories elementAt: catName put: changeSetCategory. self update! ! !ChangeSorter methodsFor: 'changeSet menu' stamp: 'pk 10/17/2006 09:37'! showChangeSetCategory: aChangeSetCategory "Show the given change-set category" changeSetCategory := aChangeSetCategory. self changed: #changeSetList. (self changeSetList includes: myChangeSet name) ifFalse: [self showChangeSet: (ChangesOrganizer changeSetNamed: self changeSetList first)]. self changed: #relabel! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! addPreamble myChangeSet assurePreambleExists. self okToChange ifTrue: [currentClassName := nil. currentSelector := nil. self showChangeSet: myChangeSet]! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! addToCategoryOpposite "Add the current change set to the category viewed on the opposite side, if it's of the sort to accept things like that" | categoryOpposite | categoryOpposite := (parent other: self) changeSetCategory. categoryOpposite acceptsManualAdditions ifTrue: [categoryOpposite addChangeSet: myChangeSet. categoryOpposite reconstituteList. self update] ifFalse: [self inform: 'sorry, this command only makes sense if the category showing on the opposite side is a static category whose members are manually maintained']! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'tk 4/24/1998 13:27'! browseChangeSet "Open a message list browser on the new and changed methods in the current change set" ChangedMessageSet openFor: myChangeSet ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 8/12/2002 17:29'! categorySubmenu: aMenu shifted: shiftedIgnored "Fill aMenu with less-frequently-needed category items" aMenu title: 'Change set category'. aMenu addStayUpItem. aMenu addList: #( ('make a new category...' makeNewCategory 'Creates a new change-set-category (you will be asked to supply a name) which will start out its life with this change set in it') ('make a new category with class...' makeNewCategoryShowingClassChanges 'Creates a new change-set-category that includes change sets that change a particular class (you will be asked to supply a name)') ('rename this category' renameCategory 'Rename this change-set category. Only applies when the current category being shown is a manually-maintained, user-defined category, such as you can create for yourself by choosing "make a new category..." from this same menu.') ('remove this category' removeCategory 'Remove this change-set category. Only applies when the current category being shown is a manually-maintained, user-defined category, such as you can create for yourself by choosing "make a new category..." from this same menu.') ('show categories of this changeset' showCategoriesOfChangeSet 'Show a list of all the change-set categories that contain this change-set; if the you choose one of the categories from this pop-up, that category will be installed in this change sorter') -). parent ifNotNil: [aMenu addList: #( ('add change set to category opposite' addToCategoryOpposite 'Adds this change set to the category on the other side of the change sorter. Only applies if the category shown on the opposite side is a manually-maintained, user-defined category, such as you can create for yourself by choosing "make a new category..." from this same menu.'))]. aMenu addList: #( ('remove change set from this category' removeFromCategory 'Removes this change set from the current category. Only applies when the current category being shown is a manually-maintained, user-defined category, such as you can create for yourself by choosing "make a new category..." from this same menu.') - ('file out category''s change sets' fileOutAllChangeSets 'File out every change set in this category that has anything in it. The usual checks for slips are suppressed when this command is done.') ('set recent-updates marker' setRecentUpdatesMarker 'Allows you to specify a number that will demarcate which updates are considered "recent" and which are not. This will govern which updates are included in the RecentUpdates category in a change sorter') ('fill aggregate change set' fillAggregateChangeSet 'Creates a change-set named Aggregate into which all the changes in all the change sets in this category will be copied.') - ('back to main menu' offerUnshiftedChangeSetMenu 'Takes you back to the shifted change-set menu.') ('back to shifted menu' offerShiftedChangeSetMenu 'Takes you back to the primary change-set menu.')). ^ aMenu! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 3/30/2001 00:00'! changeSetList "Answer a list of ChangeSet names to be shown in the change sorter." ^ self changeSetCategory changeSetList! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 7/17/2002 11:37'! changeSetListKey: aChar from: view "Respond to a Command key. I am a model with a listView that has a list of changeSets." aChar == $b ifTrue: [^ self browseChangeSet]. aChar == $B ifTrue: [^ self openChangeSetBrowser]. aChar == $c ifTrue: [^ self copyAllToOther]. aChar == $D ifTrue: [^ self toggleDiffing]. aChar == $f ifTrue: [^ self findCngSet]. aChar == $m ifTrue: [^ self newCurrent]. aChar == $n ifTrue: [^ self newSet]. aChar == $o ifTrue: [^ self fileOut]. aChar == $p ifTrue: [^ self addPreamble]. aChar == $r ifTrue: [^ self rename]. aChar == $s ifTrue: [^ self chooseChangeSetCategory]. aChar == $x ifTrue: [^ self remove]. aChar == $- ifTrue: [^ self subtractOtherSide]. ^ self messageListKey: aChar from: view! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'alain.plantec 5/30/2008 10:56'! changeSetMenu: aMenu shifted: isShifted "Set up aMenu to hold commands for the change-set-list pane. This could be for a single or double changeSorter" isShifted ifTrue: [^ self shiftedChangeSetMenu: aMenu]. aMenu title: 'Change Set'. aMenu addStayUpItemSpecial. aMenu add: 'make changes go to me (m)' action: #newCurrent. aMenu addLine. aMenu add: 'new change set... (n)' action: #newSet. aMenu add: 'find...(f)' action: #findCngSet. aMenu add: 'show category... (s)' action: #chooseChangeSetCategory. aMenu balloonTextForLastItem: 'Lets you choose which change sets should be listed in this change sorter'. aMenu add: 'select change set...' action: #chooseCngSet. aMenu addLine. aMenu add: 'rename change set (r)' action: #rename. aMenu add: 'file out (o)' action: #fileOut. aMenu add: 'mail to list' action: #mailOut. aMenu add: 'browse methods (b)' action: #browseChangeSet. aMenu add: 'browse change set (B)' action: #openChangeSetBrowser. aMenu addLine. parent ifNotNil: [aMenu add: 'copy all to other side (c)' action: #copyAllToOther. aMenu add: 'submerge into other side' action: #submergeIntoOtherSide. aMenu add: 'subtract other side (-)' action: #subtractOtherSide. aMenu addLine]. myChangeSet hasPreamble ifTrue: [aMenu add: 'edit preamble (p)' action: #addPreamble. aMenu add: 'remove preamble' action: #removePreamble] ifFalse: [aMenu add: 'add preamble (p)' action: #addPreamble]. myChangeSet hasPostscript ifTrue: [aMenu add: 'edit postscript...' action: #editPostscript. aMenu add: 'remove postscript' action: #removePostscript] ifFalse: [aMenu add: 'add postscript...' action: #editPostscript]. aMenu addLine. aMenu add: 'category functions...' action: #offerCategorySubmenu. aMenu balloonTextForLastItem: 'Various commands relating to change-set-categories'. aMenu addLine. aMenu add: 'destroy change set (x)' action: #remove. aMenu addLine. aMenu add: 'more...' action: #offerShiftedChangeSetMenu. ^ aMenu! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 10/30/2000 10:48'! checkForAlienAuthorship "Open a message list browser on all uncommented methods in the current change set that have alien authorship" myChangeSet checkForAlienAuthorship ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'nk 3/30/2002 08:56'! checkForAnyAlienAuthorship "Open a message list browser on all uncommented methods in the current change set that have alien authorship, even historically" myChangeSet checkForAnyAlienAuthorship ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 3/29/2001 12:47'! checkForUnclassifiedMethods "Open a message list browser on all methods in the current change set that have not been categorized" myChangeSet checkForUnclassifiedMethods ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 7/18/2002 17:58'! checkForUncommentedClasses "Open a class list browser on classes in the change set that lack class comments" myChangeSet checkForUncommentedClasses! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 10/30/2000 10:39'! checkForUncommentedMethods "Open a message list browser on all uncommented methods in the current change set" myChangeSet checkForUncommentedMethods ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 10/27/1999 14:20'! checkForUnsentMessages "Open a message list browser on all unsent messages in the current change set" myChangeSet checkForUnsentMessages ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 7/8/1999 13:36'! checkThatSidesDiffer: escapeBlock "If the change sets on both sides of the dual sorter are the same, put up an error message and escape via escapeBlock, else proceed happily" (myChangeSet == (parent other: self) changeSet) ifTrue: [self inform: 'This command requires that the change sets selected on the two sides of the change sorter *not* be the same.'. ^ escapeBlock value] ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'alain.plantec 5/30/2008 11:01'! chooseChangeSetCategory "Present the user with a list of change-set-categories and let her choose one" self okToChange ifFalse: [^ self]. ^ self chooseChangeSetCategoryInMorphic ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! clearChangeSet "Clear out the current change set, after getting a confirmation." | message | self okToChange ifFalse: [^ self]. myChangeSet isEmpty ifFalse: [message := 'Are you certain that you want to\forget all the changes in this set?' withCRs. (self confirm: message) ifFalse: [^ self]]. myChangeSet clear. self changed: #classList. self changed: #messageList. self setContents. self contentsChanged. ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! copyAllToOther "Copy this entire change set into the one on the other side" | companionSorter | self checkThatSidesDiffer: [^ self]. (companionSorter := parent other: self) changeSetCurrentlyDisplayed assimilateAllChangesFoundIn: myChangeSet. companionSorter changed: #classList. "Later the changeSet itself will notice..." companionSorter changed: #messageList! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'tk 6/5/1998 06:47'! currentCngSet ^ myChangeSet name! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'tk 4/28/1998 08:06'! editPostscript "Allow the user to edit the receiver's change-set's postscript -- in a separate window" myChangeSet editPostscript! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'tk 4/28/1998 08:06'! editPreamble "Allow the user to edit the receiver's change-set's preamble -- in a separate window." myChangeSet editPreamble! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'nk 1/4/2004 17:07'! fileIntoNewChangeSet "Obtain a file designation from the user, and file its contents into a new change set whose name is a function of the filename. Show the new set and leave the current changeSet unaltered." | aNewChangeSet stream | self okToChange ifFalse: [^ self]. ChangeSet promptForDefaultChangeSetDirectoryIfNecessary. stream := StandardFileMenu oldFileStreamFrom: ChangeSet defaultChangeSetDirectory. stream ifNil: [^ self]. aNewChangeSet := self class newChangesFromStream: stream named: (FileDirectory localNameFor: stream name). aNewChangeSet ifNotNil: [self showChangeSet: aNewChangeSet]! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'tk 6/10/1999 12:44'! fileOut "File out the current change set." myChangeSet fileOut. parent modelWakeUp. "notice object conversion methods created" ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 3/30/2001 00:57'! fileOutAllChangeSets "File out all nonempty change sets in the current category, probably" self changeSetCategory fileOutAllChangeSets! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 3/30/2001 01:26'! fillAggregateChangeSet "Create a change-set named Aggregate and pour into it all the changes in all the change-sets of the currently-selected category" self changeSetCategory fillAggregateChangeSet! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'DamienCassou 9/23/2009 08:33'! findCngSet "Search for a changeSet by name. Pop up a menu of all changeSets whose name contains the string entered by the user. If only one matches, then the pop-up menu is bypassed" | index pattern candidates nameList | self okToChange ifFalse: [^ self]. pattern := UIManager default request: 'ChangeSet name or fragment?'. pattern isEmptyOrNil ifTrue: [^ self]. nameList := self changeSetList asSet. candidates := ChangeSet allChangeSets select: [:c | (nameList includes: c name) and: [c name includesSubstring: pattern caseSensitive: false]]. candidates size = 0 ifTrue: [^ Beeper beep]. candidates size = 1 ifTrue: [^ self showChangeSet: candidates first]. index := UIManager default chooseFrom: (candidates collect: [:each | each name]). index = 0 ifFalse: [self showChangeSet: (candidates at: index)]. ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 1/10/1999 01:01'! inspectChangeSet "Open a message list browser on the new and changed methods in the current change set" myChangeSet inspectWithLabel: 'Change set: ', myChangeSet name ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 2/17/1999 11:05'! lookForSlips "Open a message list browser on the new and changed methods in the current change set" myChangeSet lookForSlips ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'dvf 5/13/2000 05:08'! mailOut "Create a mail with a gzipped attachment holding out the current change set. " myChangeSet mailOut. parent modelWakeUp! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'tk 4/24/1998 13:10'! mainButtonName ^ myChangeSet name! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! methodConflictsWithOppositeCategory "Check to see if ANY change set on the other side shares any methods with the selected change set; if so, open a browser on all such." | aList otherCategory | otherCategory := (parent other: self) changeSetCategory. aList := myChangeSet messageListForChangesWhich: [ :aClass :aSelector | aClass notNil and: [otherCategory hasChangeForClassName: aClass name selector: aSelector otherThanIn: myChangeSet] ] ifNone: [^ self inform: 'There are no methods that appear both in this change set and in any change set (other than this one) on the other side.']. MessageSet openMessageList: aList name: 'Methods in "', myChangeSet name, '" also in some other change set in category ', otherCategory categoryName,' (', aList size printString, ')' ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! methodConflictsWithOtherSide "Check to see if the change set on the other side shares any methods with the selected change set; if so, open a browser on all such." | aList other | self checkThatSidesDiffer: [^ self]. other := (parent other: self) changeSet. aList := myChangeSet messageListForChangesWhich: [ :aClass :aSelector | aClass notNil and: [(other methodChangesAtClass: aClass name) includesKey: aSelector] ] ifNone: [^ self inform: 'There are no methods that appear both in this change set and in the one on the other side.']. MessageSet openMessageList: aList name: 'Methods in "', myChangeSet name, '" that are also in ', other name,' (', aList size printString, ')' ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 5/23/2003 15:15'! newCurrent "make my change set be the current one that changes go into" ChangeSet newChanges: myChangeSet. self update. "Because list of changes in a category may thus have changed" self changed: #relabel.! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! newSet "Create a new changeSet and show it., making it the current one. Reject name if already in use." | aSet | self okToChange ifFalse: [^ self]. aSet := self class newChangeSet. aSet ifNotNil: [self changeSetCategory acceptsManualAdditions ifTrue: [changeSetCategory addChangeSet: aSet]. self update. (changeSetCategory includesChangeSet: aSet) ifTrue: [self showChangeSet: aSet]. self changed: #relabel]! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 4/11/2001 17:41'! offerCategorySubmenu "Offer a menu of category-related items" self offerMenuFrom: #categorySubmenu:shifted: shifted: false! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 2/27/2001 21:55'! offerShiftedChangeSetMenu "Offer the shifted version of the change set menu" self offerMenuFrom: #changeSetMenu:shifted: shifted: true! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 3/6/2001 14:41'! offerUnshiftedChangeSetMenu "Offer the unshifted version of the change set menu" self offerMenuFrom: #changeSetMenu:shifted: shifted: false! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'alain.plantec 5/30/2008 11:10'! openChangeSetBrowser "Open a ChangeSet browser on the current change set" (ChangeSetBrowser new myChangeSet: myChangeSet) openAsMorph! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 12/13/2003 18:14'! promoteToTopChangeSet "Move the selected change-set to the top of the list" self class promoteToTop: myChangeSet. (parent ifNil: [self]) modelWakeUp! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'di 6/14/1998 12:00'! remove "Completely destroy my change set. Check if it's OK first" self okToChange ifFalse: [^ self]. self removePrompting: true. self update! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'DamienCassou 9/29/2009 09:07'! removeContainedInClassCategories | matchExpression | myChangeSet removePreamble. matchExpression := UIManager default request: 'Enter class category name (wildcard is ok)' initialAnswer: 'System-*'. matchExpression ifNil: [^ self]. (Smalltalk organization categories select: [:each | matchExpression match: each]) do: [:eachCat | | classNames | classNames := Smalltalk organization listAtCategoryNamed: eachCat. classNames do: [:eachClassName | myChangeSet removeClassChanges: eachClassName. myChangeSet removeClassChanges: eachClassName , ' class']. self showChangeSet: myChangeSet]! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! removeFromCategory "Add the current change set to the category viewed on the opposite side, if it's of the sort to accept things like that" | aCategory | (aCategory := self changeSetCategory) acceptsManualAdditions ifTrue: [aCategory removeElementAt: myChangeSet name. aCategory reconstituteList. self update] ifFalse: [self inform: 'sorry, this command only makes sense for static categories whose members are manually maintained']! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 6/29/1999 20:53'! removePostscript (myChangeSet hasPostscript and: [myChangeSet postscriptHasDependents]) ifTrue: [^ self inform: 'Cannot remove the postscript right now because there is at least one window open on that postscript. Close that window and try again.']. myChangeSet removePostscript. self showChangeSet: myChangeSet! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 3/5/1999 19:32'! removePreamble myChangeSet removePreamble. self showChangeSet: myChangeSet! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'DamienCassou 9/29/2009 09:08'! rename "Store a new name string into the selected ChangeSet. reject duplicate name; allow user to back out" | newName | newName := UIManager default request: 'New name for this change set' initialAnswer: myChangeSet name. (newName = myChangeSet name or: [newName isEmptyOrNil]) ifTrue: [^ Beeper beep]. (self class changeSetNamed: newName) ifNotNil: [^ Utilities inform: 'Sorry that name is already used']. myChangeSet name: newName. self update. self changed: #mainButtonName. self changed: #relabel.! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 3/5/2001 11:03'! reorderChangeSets "apply a standard reordering -- let the class handle this" ^ self class reorderChangeSets! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'alain.plantec 2/6/2009 15:19'! setRecentUpdatesMarker "Allow the user to change the recent-updates marker" | result | result := UIManager default request: ('Enter the lowest change-set number that you wish to consider "recent"?' translated, ' (note: highest change-set number in this image at this time is ' translated, ChangeSet highestNumberedChangeSet asString, ')') initialAnswer: self class recentUpdateMarker asString. (result notNil and: [result startsWithDigit]) ifTrue: [self class recentUpdateMarker: result asInteger. SystemWindow wakeUpTopWindowUponStartup]! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'MiguelCoba 7/25/2009 02:06'! shiftedChangeSetMenu: aMenu "Set up aMenu to hold items relating to the change-set-list pane when the shift key is down" aMenu title: 'Change set (shifted)'. aMenu addStayUpItemSpecial. "CONFLICTS SECTION" aMenu add: 'conflicts with other change sets' action: #browseMethodConflicts. aMenu balloonTextForLastItem: 'Browse all methods that occur both in this change set and in at least one other change set.'. parent ifNotNil: [aMenu add: 'conflicts with change set opposite' action: #methodConflictsWithOtherSide. aMenu balloonTextForLastItem: 'Browse all methods that occur both in this change set and in the one on the opposite side of the change sorter.'. aMenu add: 'conflicts with category opposite' action: #methodConflictsWithOppositeCategory. aMenu balloonTextForLastItem: 'Browse all methods that occur both in this change set and in ANY change set in the category list on the opposite side of this change sorter, other of course than this change set itself. (Caution -- this could be VERY slow)']. aMenu addLine. "CHECKS SECTION" aMenu add: 'check for slips' action: #lookForSlips. aMenu balloonTextForLastItem: 'Check this change set for halts and references to Transcript.'. aMenu add: 'check for unsent messages' action: #checkForUnsentMessages. aMenu balloonTextForLastItem: 'Check this change set for messages that are not sent anywhere in the system'. aMenu add: 'check for uncommented methods' action: #checkForUncommentedMethods. aMenu balloonTextForLastItem: 'Check this change set for methods that do not have comments'. aMenu add: 'check for uncommented classes' action: #checkForUncommentedClasses. aMenu balloonTextForLastItem: 'Check for classes with code in this changeset which lack class comments'. Author fullNamePerSe isEmptyOrNil ifFalse: [aMenu add: 'check for other authors' action: #checkForAlienAuthorship. aMenu balloonTextForLastItem: 'Check this change set for methods whose current authoring stamp does not start with "', Author fullName, '"'. aMenu add: 'check for any other authors' action: #checkForAnyAlienAuthorship. aMenu balloonTextForLastItem: 'Check this change set for methods any of whose authoring stamps do not start with "', Author fullName, '"']. aMenu add: 'check for uncategorized methods' action: #checkForUnclassifiedMethods. aMenu balloonTextForLastItem: 'Check to see if any methods in the selected change set have not yet been assigned to a category. If any are found, open a browser on them.'. aMenu addLine. aMenu add: 'inspect change set' action: #inspectChangeSet. aMenu balloonTextForLastItem: 'Open an inspector on this change set. (There are some details in a change set which you don''t see in a change sorter.)'. aMenu add: 'update' action: #update. aMenu balloonTextForLastItem: 'Update the display for this change set. (This is done automatically when you activate this window, so is seldom needed.)'. aMenu add: 'promote to top of list' action: #promoteToTopChangeSet. aMenu balloonTextForLastItem: 'Make this change set appear first in change-set lists in all change sorters.'. aMenu add: 'trim history' action: #trimHistory. aMenu balloonTextForLastItem: ' Drops any methods added and then removed, as well as renaming and reorganization of newly-added classes. NOTE: can cause confusion if later filed in over an earlier version of these changes'. aMenu add: 'remove contained in class categories...' action: #removeContainedInClassCategories. aMenu balloonTextForLastItem: ' Drops any changes in given class categories'. aMenu add: 'clear this change set' action: #clearChangeSet. aMenu balloonTextForLastItem: 'Reset this change set to a pristine state where it holds no information. CAUTION: this is destructive and irreversible!!'. aMenu add: 'uninstall this change set' action: #uninstallChangeSet. aMenu balloonTextForLastItem: 'Attempt to uninstall this change set. CAUTION: this may not work completely and is irreversible!!'. aMenu addLine. aMenu add: 'file into new...' action: #fileIntoNewChangeSet. aMenu balloonTextForLastItem: 'Load a fileout from disk and place its changes into a new change set (seldom needed -- much better to do this from a file-list browser these days.)'. aMenu add: 'reorder all change sets' action: #reorderChangeSets. aMenu balloonTextForLastItem: 'Applies a standard reordering of all change-sets in the system -- at the bottom will come the sets that come with the release; next will come all the numbered updates; finally, at the top, will come all other change sets'. aMenu addLine. aMenu add: 'more...' action: #offerUnshiftedChangeSetMenu. aMenu balloonTextForLastItem: 'Takes you back to the primary change-set menu.'. ^ aMenu! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'pk 10/23/2008 18:13'! showCategoriesOfChangeSet "Show a list of all the categories in which the selected change-set occurs at the moment. Install the one the user chooses, if any." | aMenu | aMenu := MenuMorph new defaultTarget: self. aMenu title: 'Categories which contain change set "' , myChangeSet name , '"'. self changeSetCategories elementsInOrder do: [:aCategory | (aCategory includesChangeSet: myChangeSet) ifTrue: [aMenu add: aCategory categoryName target: self selector: #showChangeSetCategory: argument: aCategory. aCategory == changeSetCategory ifTrue: [aMenu lastItem color: Color red]]. aMenu balloonTextForLastItem: aCategory documentation]. aMenu popUpInWorld! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! submergeIntoOtherSide "Copy the contents of the receiver to the other side, then remove the receiver -- all after checking that all is well." | other message nextToView i all | self checkThatSidesDiffer: [^ self]. self okToChange ifFalse: [^ self]. other := (parent other: self) changeSet. other == myChangeSet ifTrue: [^ self inform: 'Both sides are the same!!']. myChangeSet isEmpty ifTrue: [^ self inform: 'Nothing to copy. To remove, simply choose "remove".']. myChangeSet okayToRemove ifFalse: [^ self]. message := 'Please confirm: copy all changes in "', myChangeSet name, '" into "', other name, '" and then destroy the change set named "', myChangeSet name, '"?'. (self confirm: message) ifFalse: [^ self]. (myChangeSet hasPreamble or: [myChangeSet hasPostscript]) ifTrue: [(self confirm: 'Caution!! This change set has a preamble or a postscript or both. If you submerge it into the other side, these will be lost. Do you really want to go ahead with this?') ifFalse: [^ self]]. other assimilateAllChangesFoundIn: myChangeSet. all := ChangeSet allChangeSets. nextToView := ((all includes: myChangeSet) and: [(i := all indexOf: myChangeSet) < all size]) ifTrue: [all at: i+1] ifFalse: [other]. self removePrompting: false. self showChangeSet: nextToView. parent modelWakeUp. ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sw 7/8/1999 12:32'! subtractOtherSide "Subtract the changes found on the other side from the requesting side." self checkThatSidesDiffer: [^ self]. myChangeSet forgetAllChangesFoundIn: ((parent other: self) changeSet). self showChangeSet: myChangeSet! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'di 5/12/2000 15:03'! trimHistory "Drop non-essential history (rename, reorg, method removals) from newly-added classes." myChangeSet trimHistory ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'di 3/8/2000 14:18'! uninstallChangeSet "Attempt to uninstall the current change set, after confirmation." self okToChange ifFalse: [^ self]. (self confirm: 'Uninstalling a changeSet is unreliable at best. It will only work if the changeSet consists only of single changes, additions and removals of methods, and if no subsequent changes have been to any of them. No changes to classes will be undone. The changeSet will be cleared after uninstallation. Do you still wish to attempt to uninstall this changeSet?') ifFalse: [^ self]. myChangeSet uninstall. self changed: #relabel. self changed: #classList. self changed: #messageList. self setContents. self contentsChanged. ! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'di 6/21/1998 13:02'! update "recompute all of my panes" self updateIfNecessary. parent ifNotNil: [(parent other: self) updateIfNecessary]! ! !ChangeSorter methodsFor: 'changeset menu' stamp: 'sd 11/20/2005 21:26'! updateIfNecessary "Recompute all of my panes." | newList | self okToChange ifFalse: [^ self]. myChangeSet ifNil: [^ self]. "Has been known to happen though shouldn't" (myChangeSet isMoribund or: [(changeSetCategory notNil and: [changeSetCategory includesChangeSet: myChangeSet]) not]) ifTrue: [self changed: #changeSetList. ^ self showChangeSet: self changeSetCategory defaultChangeSetToShow]. newList := self changeSetList. (priorChangeSetList == nil or: [priorChangeSetList ~= newList]) ifTrue: [priorChangeSetList := newList. self changed: #changeSetList]. self showChangeSet: myChangeSet! ! !ChangeSorter methodsFor: 'class list' stamp: 'sw 3/29/2001 15:19'! classList "Computed. View should try to preserve selections, even though index changes" ^ myChangeSet ifNotNil: [myChangeSet changedClassNames] ifNil: [OrderedCollection new] ! ! !ChangeSorter methodsFor: 'class list' stamp: 'sw 3/5/2001 18:24'! classListKey: aChar from: view "Respond to a Command key in the class-list pane." aChar == $x ifTrue: [^ self removeClass]. aChar == $d ifTrue: [^ self forgetClass]. ^ self messageListKey: aChar from: view "picks up b,h,p"! ! !ChangeSorter methodsFor: 'class list' stamp: 'dc 7/18/2008 11:41'! classListMenu: aMenu shifted: shifted "Fill aMenu with items appropriate for the class list" aMenu title: 'class list'. aMenu addStayUpItemSpecial. (parent notNil and: [shifted not]) ifTrue: [aMenu addList: #( "These two only apply to dual change sorters" ('copy class chgs to other side' copyClassToOther) ('move class chgs to other side' moveClassToOther))]. aMenu addList: (shifted ifFalse: [#( - ('delete class from change set (d)' forgetClass) ('remove class from system (x)' removeClass) - ('browse full (b)' browseMethodFull) ('browse hierarchy (h)' spawnHierarchy) ('browse protocol (p)' browseFullProtocol) - ('fileOut' fileOutClass) - ('inst var refs...' browseInstVarRefs) ('inst var defs...' browseInstVarDefs) ('class var refs...' browseClassVarRefs) ('class vars' browseClassVariables) ('class refs (N)' browseClassRefs) - ('more...' offerShiftedClassListMenu))] ifTrue: [#( - ('unsent methods' browseUnusedMethods) ('unreferenced inst vars' showUnreferencedInstVars) ('unreferenced class vars' showUnreferencedClassVars) - ('sample instance' makeSampleInstance) ('inspect instances' inspectInstances) ('inspect subinstances' inspectSubInstances) - ('more...' offerUnshiftedClassListMenu ))]). ^ aMenu! ! !ChangeSorter methodsFor: 'class list' stamp: 'sw 2/26/2001 12:00'! classMenu: aMenu "Set up aMenu for the class-list. Retained for backward compatibility with old change sorters in image segments" ^ self classListMenu: aMenu shifted: false! ! !ChangeSorter methodsFor: 'class list' stamp: 'sw 3/6/2001 12:40'! classMenu: aMenu shifted: shifted "Fill aMenu with items appropriate for the class list. Retained for bkwd compatibility" ^ self classListMenu: aMenu shifted: shifted! ! !ChangeSorter methodsFor: 'class list' stamp: 'sd 11/20/2005 21:26'! copyClassToOther "Place these changes in the other changeSet also" | otherSorter otherChangeSet | self checkThatSidesDiffer: [^ self]. self okToChange ifFalse: [^ Beeper beep]. currentClassName ifNil: [^ Beeper beep]. otherSorter := parent other: self. otherChangeSet := otherSorter changeSet. otherChangeSet absorbClass: self selectedClassOrMetaClass name from: myChangeSet. otherSorter showChangeSet: otherChangeSet.! ! !ChangeSorter methodsFor: 'class list' stamp: 'tk 4/24/1998 09:14'! currentClassName ^ currentClassName! ! !ChangeSorter methodsFor: 'class list' stamp: 'sd 11/20/2005 21:26'! currentClassName: aString currentClassName := aString. currentSelector := nil. "fix by wod" self changed: #currentClassName. self changed: #messageList. self setContents. self contentsChanged.! ! !ChangeSorter methodsFor: 'class list' stamp: 'sd 11/20/2005 21:26'! fileOutClass "this is a hack!!!! makes a new change set, called the class name, adds author initials to try to make a unique change set name, files it out and removes it. kfr 16 june 2000" | aSet | "File out the selected class set." aSet := self class newChangeSet: currentClassName. aSet absorbClass: self selectedClassOrMetaClass name from: myChangeSet. aSet fileOut. self class removeChangeSet: aSet. parent modelWakeUp. "notice object conversion methods created" ! ! !ChangeSorter methodsFor: 'class list' stamp: 'sd 11/20/2005 21:26'! forgetClass "Remove all mention of this class from the changeSet" self okToChange ifFalse: [^ self]. currentClassName ifNotNil: [ myChangeSet removeClassChanges: currentClassName. currentClassName := nil. currentSelector := nil. self showChangeSet: myChangeSet]. ! ! !ChangeSorter methodsFor: 'class list' stamp: 'sw 3/5/2001 18:30'! messageListKey: aChar from: view "Respond to a Command key in the message-list pane." aChar == $d ifTrue: [^ self forget]. super messageListKey: aChar from: view! ! !ChangeSorter methodsFor: 'class list' stamp: 'nb 6/17/2003 12:25'! moveClassToOther "Place class changes in the other changeSet and remove them from this one" self checkThatSidesDiffer: [^ self]. (self okToChange and: [currentClassName notNil]) ifFalse: [^ Beeper beep]. self copyClassToOther. self forgetClass! ! !ChangeSorter methodsFor: 'class list' stamp: 'sd 11/20/2005 21:26'! selectedClass "Answer the currently-selected class. If there is no selection, or if the selection refers to a class no longer extant, return nil" | c | ^ currentClassName ifNotNil: [(c := self selectedClassOrMetaClass) ifNotNil: [c theNonMetaClass]]! ! !ChangeSorter methodsFor: 'code pane' stamp: 'sd 11/20/2005 21:26'! contents: aString notifying: aController "Compile the code in aString. Notify aController of any syntax errors. Create an error if the category of the selected message is unknown. Answer false if the compilation fails. Otherwise, if the compilation created a new method, deselect the current selection. Then answer true." | category selector class oldSelector | (class := self selectedClassOrMetaClass) ifNil: [(myChangeSet preambleString == nil or: [aString size == 0]) ifTrue: [ ^ false]. (aString count: [:char | char == $"]) odd ifTrue: [self inform: 'unmatched double quotes in preamble'] ifFalse: [(Scanner new scanTokens: aString) size > 0 ifTrue: [ self inform: 'Part of the preamble is not within double-quotes. To put a double-quote inside a comment, type two double-quotes in a row. (Ignore this warning if you are including a doIt in the preamble.)']]. myChangeSet preambleString: aString. self currentSelector: nil. "forces update with no 'unsubmitted chgs' feedback" ^ true]. oldSelector := self selectedMessageName. category := class organization categoryOfElement: oldSelector. selector := class compile: aString classified: category notifying: aController. selector ifNil: [^ false]. (self messageList includes: selector) ifTrue: [self currentSelector: selector] ifFalse: [self currentSelector: oldSelector]. self update. ^ true! ! !ChangeSorter methodsFor: 'code pane' stamp: 'PeterHugossonMiller 9/3/2009 00:52'! setContents "return the source code that shows in the bottom pane" | sel class strm changeType | self clearUserEditFlag. currentClassName ifNil: [^ contents := myChangeSet preambleString ifNil: ['']]. class := self selectedClassOrMetaClass. (sel := currentSelector) == nil ifTrue: [strm := (String new: 100) writeStream. (myChangeSet classChangeAt: currentClassName) do: [:each | each = #remove ifTrue: [strm nextPutAll: 'Entire class was removed.'; cr]. each = #addedThenRemoved ifTrue: [strm nextPutAll: 'Class was added then removed.']. each = #rename ifTrue: [strm nextPutAll: 'Class name was changed.'; cr]. each = #add ifTrue: [strm nextPutAll: 'Class definition was added.'; cr]. each = #change ifTrue: [strm nextPutAll: 'Class definition was changed.'; cr]. each = #reorganize ifTrue: [strm nextPutAll: 'Class organization was changed.'; cr]. each = #comment ifTrue: [strm nextPutAll: 'New class comment.'; cr]]. ^ contents := strm contents] ifFalse: [changeType := myChangeSet atSelector: (sel := sel asSymbol) class: class. changeType == #remove ifTrue: [^ contents := 'Method has been removed (see versions)']. changeType == #addedThenRemoved ifTrue: [^ contents := 'Added then removed (see versions)']. class ifNil: [^ contents := 'Method was added, but cannot be found!!']. (class includesSelector: sel) ifFalse: [^ contents := 'Method was added, but cannot be found!!']. contents := class sourceCodeAt: sel. (#(#prettyPrint #prettyDiffs ) includes: contentsSymbol) ifTrue: [contents := class prettyPrinterClass format: contents in: class notifying: nil]. self showingAnyKindOfDiffs ifTrue: [contents := self diffFromPriorSourceFor: contents]. ^ contents := contents asText makeSelectorBoldIn: class]! ! !ChangeSorter methodsFor: 'code pane' stamp: 'sw 11/13/2001 07:34'! toggleDiffing "Toggle whether diffs should be shown in the code pane" self okToChange ifTrue: [super toggleDiffing. self changed: #contents. self update] ! ! !ChangeSorter methodsFor: 'code pane' stamp: 'JW 2/2/2001 21:41'! wantsOptionalButtons "No optional buttons for ChangeSorter" ^false! ! !ChangeSorter methodsFor: 'creation' stamp: 'sd 11/20/2005 21:26'! morphicWindow "ChangeSorter new openAsMorph" | window | myChangeSet ifNil: [self myChangeSet: ChangeSet current]. window := (SystemWindow labelled: self labelString) model: self. self openAsMorphIn: window rect: (0@0 extent: 1@1). ^ window ! ! !ChangeSorter methodsFor: 'creation' stamp: 'alain.plantec 5/30/2008 11:08'! open "ChangeSorter new open" ^ self openAsMorph! ! !ChangeSorter methodsFor: 'creation' stamp: 'sw 3/6/1999 09:34'! openAsMorph "ChangeSorter new openAsMorph" ^ self morphicWindow openInWorld. ! ! !ChangeSorter methodsFor: 'creation' stamp: 'sd 11/20/2005 21:26'! openAsMorphIn: window rect: rect "Add a set of change sorter views to the given top view offset by the given amount. To create a single change sorter, call this once with an offset of 0@0. To create a dual change sorter, call it twice with offsets of 0@0 and 0.5@0." | csListHeight msgListHeight csMsgListHeight | contents := ''. csListHeight := 0.25. msgListHeight := 0.25. csMsgListHeight := csListHeight + msgListHeight. self addDependent: window. "so it will get changed: #relabel" "The method SystemWindow>>addMorph:fullFrame: checks scrollBarsOnRight, then adds the morph at the back if true, otherwise it is added in front. But flopout hScrollbars needs the crrentSelector pane to be behind the upper ones in the draw order. Hence the value of scrollBarsOnRight affects the order in which the lowerpanes are added." Preferences scrollBarsOnRight ifFalse: [window addMorph: (PluggableListMorphByItem on: self list: #messageList selected: #currentSelector changeSelected: #currentSelector: menu: #messageMenu:shifted: keystroke: #messageListKey:from:) frame: (((0@csListHeight extent: 1@msgListHeight) scaleBy: rect extent) translateBy: rect origin)]. window addMorph: ((PluggableListMorphByItem on: self list: #changeSetList selected: #currentCngSet changeSelected: #showChangeSetNamed: menu: #changeSetMenu:shifted: keystroke: #changeSetListKey:from:) autoDeselect: false) frame: (((0@0 extent: 0.5@csListHeight) scaleBy: rect extent) translateBy: rect origin). window addMorph: (PluggableListMorphByItem on: self list: #classList selected: #currentClassName changeSelected: #currentClassName: menu: #classListMenu:shifted: keystroke: #classListKey:from:) frame: (((0.5@0 extent: 0.5@csListHeight) scaleBy: rect extent) translateBy: rect origin). Preferences scrollBarsOnRight ifTrue: [window addMorph: (PluggableListMorphByItem on: self list: #messageList selected: #currentSelector changeSelected: #currentSelector: menu: #messageMenu:shifted: keystroke: #messageListKey:from:) frame: (((0@csListHeight extent: 1@msgListHeight) scaleBy: rect extent) translateBy: rect origin)]. self addLowerPanesTo: window at: (((0@csMsgListHeight corner: 1@1) scaleBy: rect extent) translateBy: rect origin) with: nil. ! ! !ChangeSorter methodsFor: 'creation' stamp: 'sd 11/20/2005 21:26'! setDefaultChangeSetCategory "Set a default ChangeSetCategory for the receiver, and answer it" ^ changeSetCategory := self class changeSetCategoryNamed: #All! ! !ChangeSorter methodsFor: 'creation' stamp: 'sd 11/20/2005 21:26'! veryDeepFixupWith: deepCopier super veryDeepFixupWith: deepCopier. parent := deepCopier references at: parent ifAbsent: [parent]. self updateIfNecessary! ! !ChangeSorter methodsFor: 'creation' stamp: 'sd 11/20/2005 21:26'! veryDeepInner: deepCopier "Copy all of my instance variables. Some need to be not copied at all, but shared." super veryDeepInner: deepCopier. "parent := parent. Weakly copied" "myChangeSet := myChangeSet. Weakly copied" currentClassName := currentClassName veryDeepCopyWith: deepCopier. "currentSelector := currentSelector. Symbol" priorChangeSetList := priorChangeSetList veryDeepCopyWith: deepCopier. changeSetCategory := changeSetCategory. ! ! !ChangeSorter methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! browseVersions "Create and schedule a changelist browser on the versions of the selected message." | class selector method category pair sourcePointer | (selector := self selectedMessageName) ifNil: [^ self]. class := self selectedClassOrMetaClass. (class includesSelector: selector) ifTrue: [method := class compiledMethodAt: selector. category := class whichCategoryIncludesSelector: selector. sourcePointer := nil] ifFalse: [pair := myChangeSet methodInfoFromRemoval: {class name. selector}. pair ifNil: [^ nil]. sourcePointer := pair first. method := CompiledMethod toReturnSelf setSourcePointer: sourcePointer. category := pair last]. VersionsBrowser browseVersionsOf: method class: self selectedClass meta: class isMeta category: category selector: selector lostMethodPointer: sourcePointer. ! ! !ChangeSorter methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! copyMethodToOther "Place this change in the other changeSet also" | other cls sel | self checkThatSidesDiffer: [^ self]. currentSelector ifNotNil: [other := (parent other: self) changeSet. cls := self selectedClassOrMetaClass. sel := currentSelector asSymbol. other absorbMethod: sel class: cls from: myChangeSet. (parent other: self) showChangeSet: other] ! ! !ChangeSorter methodsFor: 'message list' stamp: 'tk 4/24/1998 09:15'! currentSelector ^ currentSelector! ! !ChangeSorter methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! currentSelector: messageName currentSelector := messageName. self changed: #currentSelector. self setContents. self contentsChanged.! ! !ChangeSorter methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! forget "Drop this method from the changeSet" self okToChange ifFalse: [^ self]. currentSelector ifNotNil: [ myChangeSet removeSelectorChanges: self selectedMessageName class: self selectedClassOrMetaClass. currentSelector := nil. self showChangeSet: myChangeSet]! ! !ChangeSorter methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! messageList | probe newSelectors | currentClassName ifNil: [^ #()]. probe := (currentClassName endsWith: ' class') ifTrue: [currentClassName] ifFalse: [currentClassName asSymbol]. newSelectors := myChangeSet selectorsInClass: probe. (newSelectors includes: currentSelector) ifFalse: [currentSelector := nil]. ^ newSelectors asSortedCollection ! ! !ChangeSorter methodsFor: 'message list' stamp: 'sw 3/9/2001 14:27'! messageListMenu: aMenu shifted: shifted "Fill aMenu with items appropriate for the message list; could be for a single or double changeSorter" ^ self messageMenu: aMenu shifted: shifted! ! !ChangeSorter methodsFor: 'message list' stamp: 'alain.plantec 5/30/2008 11:03'! messageMenu: aMenu shifted: shifted "Fill aMenu with items appropriate for the message list; could be for a single or double changeSorter" shifted ifTrue: [^ self shiftedMessageMenu: aMenu]. aMenu title: 'message list'. aMenu addStayUpItemSpecial. parent ifNotNil: [aMenu addList: #( ('copy method to other side' copyMethodToOther) ('move method to other side' moveMethodToOther))]. aMenu addList: #( ('delete method from changeSet (d)' forget) - ('remove method from system (x)' removeMessage) - ('browse full (b)' browseMethodFull) ('browse hierarchy (h)' spawnHierarchy) ('browse method (O)' openSingleMessageBrowser) ('browse protocol (p)' browseFullProtocol) - ('fileOut' fileOutMessage) - ('senders of... (n)' browseSendersOfMessages) ('implementors of... (m)' browseMessages) ('inheritance (i)' methodHierarchy) ('versions (v)' browseVersions) - ('more...' shiftedYellowButtonActivity)). ^ aMenu ! ! !ChangeSorter methodsFor: 'message list' stamp: 'nk 7/30/2004 17:58'! moveMethodToOther "Place this change in the other changeSet and remove it from this side" | other cls sel | self checkThatSidesDiffer: [^self]. self okToChange ifFalse: [^Beeper beep]. currentSelector ifNotNil: [other := (parent other: self) changeSet. other == myChangeSet ifTrue: [^Beeper beep]. cls := self selectedClassOrMetaClass. sel := currentSelector asSymbol. other absorbMethod: sel class: cls from: myChangeSet. (parent other: self) showChangeSet: other. self forget "removes the method from this side"]! ! !ChangeSorter methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! removeFromCurrentChanges "Redisplay after removal in case we are viewing the current changeSet" super removeFromCurrentChanges. currentSelector := nil. self showChangeSet: myChangeSet! ! !ChangeSorter methodsFor: 'message list' stamp: 'sd 11/20/2005 21:26'! removeMessage "Remove the selected msg from the system. Real work done by the parent, a ChangeSorter" | confirmation sel | self okToChange ifFalse: [^ self]. currentSelector ifNotNil: [confirmation := self systemNavigation confirmRemovalOf: (sel := self selectedMessageName) on: self selectedClassOrMetaClass. confirmation == 3 ifTrue: [^ self]. self selectedClassOrMetaClass removeSelector: sel. self update. confirmation == 2 ifTrue: [self systemNavigation browseAllCallsOn: sel]]! ! !ChangeSorter methodsFor: 'message list' stamp: 'jm 5/4/1998 07:32'! selectedMessageName currentSelector ifNil: [^ nil]. ^ currentSelector asSymbol! ! !ChangeSorter methodsFor: 'message list' stamp: 'marcus.denker 9/20/2008 20:19'! shiftedMessageMenu: aMenu "Arm the menu so that it holds items appropriate to the message-list while the shift key is down. Answer the menu." ^ aMenu addList: #( - ('toggle diffing (D)' toggleDiffing) ('implementors of sent messages' browseAllMessages) ('change category...' changeCategory) - ('sample instance' makeSampleInstance) ('inspect instances' inspectInstances) ('inspect subinstances' inspectSubInstances) - ('change sets with this method' findMethodInChangeSets) ('revert to previous version' revertToPreviousVersion) ('revert & remove from changes' revertAndForget) - ('more...' unshiftedYellowButtonActivity))! ! !ChangeSorter methodsFor: 'toolbuilder' stamp: 'ar 2/11/2005 20:32'! buildWith: builder " MorphicUIBuilder open: ChangeSorter. " | windowSpec | windowSpec := builder pluggableWindowSpec new. windowSpec label: 'Change Sorter'. windowSpec model: self. windowSpec children: OrderedCollection new. self buildWith: builder in: windowSpec rect: (0@0 extent: 1@1). ^builder build: windowSpec! ! !ChangeSorter methodsFor: 'toolbuilder' stamp: 'sd 11/20/2005 21:26'! buildWith: builder in: window rect: rect | csListHeight msgListHeight csMsgListHeight listSpec textSpec | contents := ''. csListHeight := 0.25. msgListHeight := 0.25. csMsgListHeight := csListHeight + msgListHeight. listSpec := builder pluggableListSpec new. listSpec model: self; list: #changeSetList; getSelected: #currentCngSet; setSelected: #showChangeSetNamed:; menu: #changeSetMenu:shifted:; keyPress: #changeSetListKey:from:; autoDeselect: false; frame: (((0@0 extent: 0.5@csListHeight) scaleBy: rect extent) translateBy: rect origin). window children add: listSpec. listSpec := builder pluggableListSpec new. listSpec model: self; list: #classList; getSelected: #currentClassName; setSelected: #currentClassName:; menu: #classListMenu:shifted:; keyPress: #classListKey:from:; frame: (((0.5@0 extent: 0.5@csListHeight) scaleBy: rect extent) translateBy: rect origin). window children add: listSpec. listSpec := builder pluggableListSpec new. listSpec model: self; list: #messageList; getSelected: #currentSelector; setSelected: #currentSelector:; menu: #messageMenu:shifted:; keyPress: #messageListKey:from:; frame: (((0@csListHeight extent: 1@msgListHeight) scaleBy: rect extent) translateBy: rect origin). window children add: listSpec. textSpec := builder pluggableTextSpec new. textSpec model: self; getText: #contents; setText: #contents:notifying:; selection: #contentsSelection; menu: #codePaneMenu:shifted:; frame: (((0@csMsgListHeight corner: 1@1) scaleBy: rect extent) translateBy: rect origin). window children add: textSpec. ^window! ! !ChangeSorter methodsFor: 'traits' stamp: 'al 7/18/2004 11:44'! selectedClassOrMetaClass "Careful, the class may have been removed!!" | cName tName | currentClassName ifNil: [^ nil]. (currentClassName endsWith: ' class') ifTrue: [cName := (currentClassName copyFrom: 1 to: currentClassName size-6) asSymbol. ^ (Smalltalk at: cName ifAbsent: [^nil]) class]. (currentClassName endsWith: ' classTrait') ifTrue: [tName := (currentClassName copyFrom: 1 to: currentClassName size-11) asSymbol. ^ (Smalltalk at: tName ifAbsent: [^nil]) classTrait]. cName := currentClassName asSymbol. ^ Smalltalk at: cName ifAbsent: [nil]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ChangeSorter class instanceVariableNames: ''! !ChangeSorter class methodsFor: 'browse' stamp: 'sd 11/20/2005 21:28'! browseChangeSetsWithClass: class selector: selector "Put up a menu comprising a list of change sets that hold changes for the given class and selector. If the user selects one, open a single change-sorter onto it" | hits index | hits := self allChangeSets select: [:cs | (cs atSelector: selector class: class) ~~ #none]. hits isEmpty ifTrue: [^ self inform: class name, '.', selector , ' is not in any change set']. index := hits size == 1 ifTrue: [1] ifFalse: [(UIManager default chooseFrom: (hits collect: [:cs | cs name]) lines: #())]. index = 0 ifTrue: [^ self]. (ChangeSorter new myChangeSet: (hits at: index)) open. ! ! !ChangeSorter class methodsFor: 'browse' stamp: 'sd 11/20/2005 21:28'! browseChangeSetsWithSelector: aSelector "Put up a list of all change sets that contain an addition, deletion, or change of any method with the given selector" | hits index | hits := self allChangeSets select: [:cs | cs hasAnyChangeForSelector: aSelector]. hits isEmpty ifTrue: [^ self inform: aSelector , ' is not in any change set']. index := hits size == 1 ifTrue: [1] ifFalse: [(UIManager default chooseFrom: (hits collect: [:cs | cs name]) lines: #())]. index = 0 ifTrue: [^ self]. (ChangeSetBrowser new myChangeSet: (hits at: index)) open "ChangeSorter browseChangeSetsWithSelector: #clearPenTrails" ! ! !ChangeSorter class methodsFor: 'class initialization' stamp: 'pk 10/17/2006 09:10'! initialize "ChangeSorter initialize" FileList registerFileReader: self. self registerInFlapsRegistry. ! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 08:59'! allChangeSetNames ^ ChangesOrganizer allChangeSetNames! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:00'! allChangeSets ^ ChangesOrganizer allChangeSets! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:12'! allChangeSetsWithClass: class selector: selector ^ ChangesOrganizer allChangeSetsWithClass: class selector: selector! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:19'! assuredChangeSetNamed: aName ^ ChangesOrganizer assuredChangeSetNamed: aName! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:01'! basicNewChangeSet: newName ^ ChangesOrganizer basicNewChangeSet: newName! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:03'! belongsInAdditions: aChangeSet ^ ChangesOrganizer belongsInAdditions: aChangeSet! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:03'! belongsInAll: aChangeSet ^ ChangesOrganizer belongsInAll: aChangeSet! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:03'! belongsInMyInitials: aChangeSet ^ ChangesOrganizer belongsInMyInitials: aChangeSet! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:04'! belongsInNumbered: aChangeSet ^ ChangesOrganizer belongsInNumbered: aChangeSet! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:06'! belongsInProjectsInRelease: aChangeSet ^ ChangesOrganizer belongsInProjectsInRelease: aChangeSet! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:06'! belongsInRecentUpdates: aChangeSet ^ ChangesOrganizer belongsInRecentUpdates: aChangeSet! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:20'! buildAggregateChangeSet ^ ChangesOrganizer buildAggregateChangeSet ! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:12'! changeSet: aChangeSet containsClass: aClass ^ ChangesOrganizer changeSet: aChangeSet containsClass: aClass! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:07'! changeSetCategoryNamed: aName ^ ChangesOrganizer changeSetCategoryNamed: aName! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:12'! changeSetNamed: aName ^ ChangesOrganizer changeSetNamed: aName! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:07'! changeSetNamesInReleaseImage ^ ChangesOrganizer changeSetNamesInReleaseImage! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:08'! changeSetNamesInThreeOh ^ ChangesOrganizer changeSetNamesInThreeOh! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:12'! changeSetsNamedSuchThat: nameBlock ^ ChangesOrganizer changeSetsNamedSuchThat: nameBlock! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:20'! countOfChangeSetsWithClass: aClass andSelector: aSelector ^ ChangesOrganizer countOfChangeSetsWithClass: aClass andSelector: aSelector! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:16'! deleteChangeSetsNumberedLowerThan: anInteger ^ ChangesOrganizer deleteChangeSetsNumberedLowerThan: anInteger! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:21'! doesAnyChangeSetHaveClass: aClass andSelector: aSelector ^ ChangesOrganizer doesAnyChangeSetHaveClass: aClass andSelector: aSelector! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:13'! existingOrNewChangeSetNamed: aName ^ ChangesOrganizer existingOrNewChangeSetNamed: aName! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:23'! fileOutChangeSetsNamed: nameList ^ ChangesOrganizer fileOutChangeSetsNamed: nameList! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:13'! gatherChangeSets ^ ChangesOrganizer gatherChangeSets! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:13'! highestNumberedChangeSet ^ ChangesOrganizer highestNumberedChangeSet ! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:10'! initializeChangeSetCategories ^ ChangesOrganizer initializeChangeSetCategories! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:13'! mostRecentChangeSetWithChangeForClass: class selector: selector ^ ChangesOrganizer mostRecentChangeSetWithChangeForClass: class selector: selector! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:01'! newChangeSet ^ ChangesOrganizer newChangeSet! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:02'! newChangeSet: aName ^ ChangesOrganizer newChangeSet: aName! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:02'! newChangesFromStream: aStream named: aName ^ ChangesOrganizer newChangesFromStream: aStream named: aName! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:14'! promoteToTop: aChangeSet ^ ChangesOrganizer promoteToTop: aChangeSet! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:21'! recentUpdateMarker ^ ChangesOrganizer recentUpdateMarker! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:22'! recentUpdateMarker: aNumber ^ ChangesOrganizer recentUpdateMarker: aNumber! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:16'! removeChangeSet: aChangeSet ^ ChangesOrganizer removeChangeSet: aChangeSet! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:17'! removeChangeSetsNamedSuchThat: nameBlock ^ ChangesOrganizer removeChangeSetsNamedSuchThat: nameBlock! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:17'! removeEmptyUnnamedChangeSets ^ ChangesOrganizer removeEmptyUnnamedChangeSets! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:22'! reorderChangeSets ^ ChangesOrganizer reorderChangeSets! ! !ChangeSorter class methodsFor: 'deprecated' stamp: 'pk 10/17/2006 09:22'! secondaryChangeSet ^ ChangesOrganizer secondaryChangeSet! ! !ChangeSorter class methodsFor: 'initialization' stamp: 'asm 4/10/2003 12:42'! registerInFlapsRegistry "Register the receiver in the system's flaps registry" self environment at: #Flaps ifPresent: [:cl | cl registerQuad: #(ChangeSorter prototypicalToolWindow 'Change Set' 'A tool that allows you to view and manipulate all the code changes in a single change set') forFlapNamed: 'Tools']! ! !ChangeSorter class methodsFor: 'initialization' stamp: 'ar 9/27/2005 19:56'! unload "Unload the receiver from global registries" self environment at: #FileList ifPresent: [:cl | cl unregisterFileReader: self]. self environment at: #Flaps ifPresent: [:cl | cl unregisterQuadsWithReceiver: self] ! ! !ChangeSorter class methodsFor: 'services' stamp: 'sw 6/13/2001 00:56'! prototypicalToolWindow "Answer a window representing a prototypical instance of the receiver" ^ self new morphicWindow applyModelExtent! ! !ChangeSorter class methodsFor: 'window color' stamp: 'sw 2/26/2002 14:09'! windowColorSpecification "Answer a WindowColorSpec object that declares my preference" ^ WindowColorSpec classSymbol: self name wording: 'Change Sorter' brightColor: #lightBlue pastelColor: #paleBlue helpMessage: 'A tool that lets you see the code for one change set at a time.'! ! MessageSet subclass: #ChangedMessageSet instanceVariableNames: 'changeSet' classVariableNames: '' poolDictionaries: '' category: 'Tools-Browser'! !ChangedMessageSet commentStamp: '' prior: 0! A ChangedMessageSet is a message set associated with a change-set; it bears an entry for every method added or changed in the change set, as well as for every class-comment of which the change-set bears a note.! !ChangedMessageSet methodsFor: 'acceptance' stamp: 'md 2/20/2006 18:42'! contents: aString notifying: aController "Accept the string as new source for the current method, and make certain the annotation pane gets invalidated" | existingSelector existingClass superResult newSelector | existingSelector := self selectedMessageName. existingClass := self selectedClassOrMetaClass. superResult := super contents: aString notifying: aController. superResult ifTrue: "succeeded" [newSelector := existingClass parserClass new parseSelector: aString. newSelector ~= existingSelector ifTrue: "Selector changed -- maybe an addition" [self reformulateList. self changed: #messageList. self messageList doWithIndex: [:aMethodReference :anIndex | (aMethodReference actualClass == existingClass and: [aMethodReference methodSymbol == newSelector]) ifTrue: [self messageListIndex: anIndex]]]]. ^ superResult! ! !ChangedMessageSet methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:26'! changeSet: aChangeSet changeSet := aChangeSet! ! !ChangedMessageSet methodsFor: 'message list' stamp: 'sw 1/28/2001 20:59'! growable "Answer whether the receiver can be changed by manual additions & deletions" ^ false! ! !ChangedMessageSet methodsFor: 'reformulation' stamp: 'sw 6/26/2001 11:20'! reformulateList "Reformulate the message list of the receiver" self initializeMessageList: (changeSet changedMessageListAugmented select: [:each | each isValid]) ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ChangedMessageSet class instanceVariableNames: ''! !ChangedMessageSet class methodsFor: 'as yet unclassified' stamp: 'sd 11/20/2005 21:28'! openFor: aChangeSet "Open up a ChangedMessageSet browser on the given change set; this is a conventional message-list browser whose message-list consists of all the methods in aChangeSet. After any method submission, the message list is refigured, making it plausibly dynamic" | messageSet | messageSet := aChangeSet changedMessageListAugmented select: [ :each | each isValid]. self openMessageList: messageSet name: 'Methods in Change Set ', aChangeSet name autoSelect: nil changeSet: aChangeSet! ! !ChangedMessageSet class methodsFor: 'as yet unclassified' stamp: 'alain.plantec 5/30/2008 11:20'! openMessageList: messageList name: labelString autoSelect: autoSelectString changeSet: aChangeSet | messageSet | messageSet := self messageList: messageList. messageSet changeSet: aChangeSet. messageSet autoSelectString: autoSelectString. self openAsMorph: messageSet name: labelString! ! Object subclass: #ChangesOrganizer instanceVariableNames: '' classVariableNames: 'ChangeSetCategories ChangeSetNamesInRelease RecentUpdateMarker' poolDictionaries: '' category: 'System-Changes'! !ChangesOrganizer commentStamp: 'pk 10/17/2006 09:25' prior: 0! Changes organizer! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ChangesOrganizer class instanceVariableNames: ''! !ChangesOrganizer class methodsFor: 'adding' stamp: 'pk 2/6/2006 09:49'! basicNewChangeSet: newName ^ChangeSet basicNewChangeSet: newName! ! !ChangesOrganizer class methodsFor: 'adding' stamp: 'pk 2/6/2006 09:49'! newChangeSet "Prompt the user for a name, and establish a new change set of that name (if ok), making it the current changeset. Return nil of not ok, else return the actual changeset." | newName newSet | newName := UIManager default request: 'Please name the new change set:' initialAnswer: ChangeSet defaultName. newName isEmptyOrNil ifTrue: [^ nil]. newSet := self basicNewChangeSet: newName. newSet ifNotNil: [ChangeSet newChanges: newSet]. ^ newSet! ! !ChangesOrganizer class methodsFor: 'adding' stamp: 'MiguelCoba 7/25/2009 02:01'! newChangeSet: aName "Makes a new change set called aName, add author full name to try to ensure a unique change set name." | newName | newName := aName , FileDirectory dot , Author fullName. ^ self basicNewChangeSet: newName! ! !ChangesOrganizer class methodsFor: 'adding' stamp: 'pk 2/6/2006 09:49'! newChangesFromStream: aStream named: aName ^ChangeSet newChangesFromStream: aStream named: aName ! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'pk 2/6/2006 09:49'! belongsInAdditions: aChangeSet "Answer whether a change set belongs in the Additions category, which is fed by all change sets that are neither numbered nor in the initial release" ^ (((self belongsInProjectsInRelease: aChangeSet) or: [self belongsInNumbered: aChangeSet])) not! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'pk 2/6/2006 09:49'! belongsInAll: aChangeSet "Answer whether a change set belongs in the All category" ^ true ! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'MiguelCoba 7/25/2009 02:01'! belongsInMyInitials: aChangeSet "Answer whether a change set belongs in the MyInitials category. " ^ aChangeSet name endsWith: ('-', Author fullName)! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'pk 10/17/2006 09:04'! belongsInNumbered: aChangeSet "Answer whether a change set belongs in the Numbered category. " ^ aChangeSet name startsWithDigit! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'pk 2/6/2006 09:49'! belongsInProjectsInRelease: aChangeSet "Answer whether a change set belongs in the ProjectsInRelease category. You can hand-tweak this to suit your working style. This just covers the space of project names in the 2.9, 3.0, and 3.1a systems" | aString | ^ ((aString := aChangeSet name) beginsWith: 'Play With Me') or: [self changeSetNamesInReleaseImage includes: aString]! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'pk 2/6/2006 09:49'! belongsInRecentUpdates: aChangeSet "Answer whether a change set belongs in the RecentUpdates category." ^ aChangeSet name startsWithDigit and: [aChangeSet name asInteger >= self recentUpdateMarker]! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'pk 2/6/2006 09:49'! changeSetCategoryNamed: aName "Answer the changeSetCategory of the given name, or nil if none" ^ ChangeSetCategories elementAt: aName asSymbol ! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'pk 2/6/2006 09:49'! changeSetNamesInReleaseImage "Answer a list of names of project change sets that come pre-shipped in the latest sytem release. On the brink of shipping a new release, call 'ChangeSorter noteChangeSetsInRelease' " ^ ChangeSetNamesInRelease ifNil: [ChangeSetNamesInRelease := self changeSetNamesInThreeOh]! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'pk 2/6/2006 09:49'! changeSetNamesInThreeOh "Hard-coded: answer a list of names of project change sets that came pre-shipped in Squeak 3.0" ^ #('The Worlds of Squeak' 'Fun with Morphic' 'Games' 'Fun With Music' 'Building with Squeak' 'Squeak and the Internet' 'Squeak in 3D' 'More About Sound' ) ! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'pk 10/23/2008 16:41'! initialization "Initialize the class variables" ChangeSetCategories ifNil: [self initializeChangeSetCategories]. RecentUpdateMarker := 0.! ! !ChangesOrganizer class methodsFor: 'class initialization' stamp: 'stephane.ducasse 7/10/2009 16:46'! initializeChangeSetCategories "Initialize the set of change-set categories" "ChangesOrganizer initializeChangeSetCategories" | aCategory | ChangeSetCategories := ElementCategory new categoryName: #ChangeSetCategories. aCategory := ChangeSetCategory new categoryName: #All. aCategory membershipSelector: #belongsInAll:. aCategory documentation: 'All change sets known to the system'. ChangeSetCategories addCategoryItem: aCategory. aCategory := ChangeSetCategory new categoryName: #Additions. aCategory membershipSelector: #belongsInAdditions:. aCategory documentation: 'All unnumbered change sets except those representing projects in the system as initially released.'. ChangeSetCategories addCategoryItem: aCategory. aCategory := ChangeSetCategory new categoryName: #MyInitials. aCategory membershipSelector: #belongsInMyInitials:. aCategory documentation: 'All change sets whose names end with the current author''s initials.'. ChangeSetCategories addCategoryItem: aCategory. aCategory := ChangeSetCategory new categoryName: #Numbered. aCategory membershipSelector: #belongsInNumbered:. aCategory documentation: 'All change sets whose names start with a digit -- normally these will be the official updates to the system.'. ChangeSetCategories addCategoryItem: aCategory. aCategory := ChangeSetCategory new categoryName: #RecentUpdates. aCategory membershipSelector: #belongsInRecentUpdates:. aCategory documentation: 'Updates whose numbers are at or beyond the number I have designated as the earliest one to qualify as Recent'. ChangeSetCategories addCategoryItem: aCategory. ChangeSetCategories elementsInOrder do: [:anElem | anElem reconstituteList] ! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 2/6/2006 09:49'! allChangeSetNames ^ self allChangeSets collect: [:c | c name]! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 2/6/2006 09:49'! allChangeSets "Return the list of all current ChangeSets" ^ChangeSet allChangeSets! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 2/6/2006 09:49'! allChangeSetsWithClass: class selector: selector class ifNil: [^ #()]. ^ self allChangeSets select: [:cs | (cs atSelector: selector class: class) ~~ #none]! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 2/6/2006 09:49'! changeSet: aChangeSet containsClass: aClass | theClass | theClass := Smalltalk classNamed: aClass. theClass ifNil: [^ false]. ^ aChangeSet containsClass: theClass! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 2/6/2006 09:49'! changeSetNamed: aName "Return the change set of the given name, or nil if none found. 1/22/96 sw" ^ChangeSet named: aName! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 2/6/2006 09:49'! changeSetsNamedSuchThat: nameBlock ^ChangeSet changeSetsNamedSuchThat: nameBlock! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 2/6/2006 09:49'! existingOrNewChangeSetNamed: aName ^ChangeSet existingOrNewChangeSetNamed: aName! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 10/23/2008 16:30'! gatherChangeSets "ChangesOrganizer gatherChangeSets" ^ ChangeSet gatherChangeSets! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 10/23/2008 16:28'! highestNumberedChangeSet "ChangesOrganizer highestNumberedChangeSet" | aList | aList := (ChangeSet allChangeSetNames select: [:aString | aString startsWithDigit] thenCollect: [:aString | aString initialIntegerOrNil]). ^ (aList size > 0) ifTrue: [aList max] ifFalse: [nil] ! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 2/6/2006 09:49'! mostRecentChangeSetWithChangeForClass: class selector: selector | hits | hits := self allChangeSets select: [:cs | (cs atSelector: selector class: class) ~~ #none]. hits isEmpty ifTrue: [^ 'not in any change set']. ^ 'recent cs: ', hits last name! ! !ChangesOrganizer class methodsFor: 'enumerating' stamp: 'pk 2/6/2006 09:49'! promoteToTop: aChangeSet "Make aChangeSet the first in the list from now on" ^ChangeSet promoteToTop: aChangeSet! ! !ChangesOrganizer class methodsFor: 'removing' stamp: 'pk 2/6/2006 09:49'! deleteChangeSetsNumberedLowerThan: anInteger "Delete all changes sets whose names start with integers smaller than anInteger" self removeChangeSetsNamedSuchThat: [:aName | aName first isDigit and: [aName initialIntegerOrNil < anInteger]]. "ChangesOrganizer deleteChangeSetsNumberedLowerThan: (ChangeSorter highestNumberedChangeSet name initialIntegerOrNil - 500)" ! ! !ChangesOrganizer class methodsFor: 'removing' stamp: 'pk 2/6/2006 09:49'! removeChangeSet: aChangeSet "Remove the given changeSet. Caller must assure that it's cool to do this" ^ChangeSet removeChangeSet: aChangeSet! ! !ChangesOrganizer class methodsFor: 'removing' stamp: 'pk 2/6/2006 09:49'! removeChangeSetsNamedSuchThat: nameBlock (self changeSetsNamedSuchThat: nameBlock) do: [:cs | self removeChangeSet: cs]! ! !ChangesOrganizer class methodsFor: 'removing' stamp: 'pk 10/23/2008 15:57'! removeEmptyUnnamedChangeSets "Remove all change sets that are empty, whose names start with Unnamed, and which are not nailed down by belonging to a Project." "ChangesOrganizer removeEmptyUnnamedChangeSets" | toGo | (toGo := (self changeSetsNamedSuchThat: [:csName | csName beginsWith: 'Unnamed']) select: [:cs | cs isEmpty and: [cs okayToRemoveInforming: false]]) do: [:cs | self removeChangeSet: cs]. self inform: toGo size printString, ' change set(s) removed.'! ! !ChangesOrganizer class methodsFor: 'services' stamp: 'pk 2/6/2006 09:49'! assuredChangeSetNamed: aName "Answer a change set of the given name. If one already exists, answer that, else create a new one and answer it." | existing | ^ (existing := self changeSetNamed: aName) ifNotNil: [existing] ifNil: [self basicNewChangeSet: aName]! ! !ChangesOrganizer class methodsFor: 'services' stamp: 'pk 10/23/2008 16:29'! buildAggregateChangeSet "Establish a change-set named Aggregate which bears the union of all the changes in all the existing change-sets in the system (other than any pre-existing Aggregate). This can be useful when wishing to discover potential conflicts between a disk-resident change-set and an image. Formerly very useful, now some of its unique contributions have been overtaken by new features" | aggregateChangeSet | aggregateChangeSet := self existingOrNewChangeSetNamed: 'Aggregate'. aggregateChangeSet clear. self allChangeSets do: [:aChangeSet | aChangeSet == aggregateChangeSet ifFalse: [aggregateChangeSet assimilateAllChangesFoundIn: aChangeSet]] "ChangesOrganizer buildAggregateChangeSet" ! ! !ChangesOrganizer class methodsFor: 'services' stamp: 'pk 2/6/2006 09:49'! countOfChangeSetsWithClass: aClass andSelector: aSelector "Answer how many change sets record a change for the given class and selector" ^ (self allChangeSetsWithClass: aClass selector: aSelector) size! ! !ChangesOrganizer class methodsFor: 'services' stamp: 'pk 2/6/2006 09:49'! doesAnyChangeSetHaveClass: aClass andSelector: aSelector "Answer whether any known change set bears a change for the given class and selector" ^ (self countOfChangeSetsWithClass: aClass andSelector: aSelector) > 0! ! !ChangesOrganizer class methodsFor: 'services' stamp: 'pk 2/6/2006 09:49'! recentUpdateMarker "Answer the number representing the threshold of what counts as 'recent' for an update number. This allow you to use the RecentUpdates category in a ChangeSorter to advantage" ^ RecentUpdateMarker ifNil: [RecentUpdateMarker := 0]! ! !ChangesOrganizer class methodsFor: 'services' stamp: 'pk 2/6/2006 09:49'! recentUpdateMarker: aNumber "Set the recent update marker as indicated" ^ RecentUpdateMarker := aNumber! ! !ChangesOrganizer class methodsFor: 'services' stamp: 'hfm 9/30/2009 04:03'! reorderChangeSets "Change the order of the change sets to something more convenient: First come the project changesets that come with the release. These are mostly empty. Next come all numbered updates. Next come all remaining changesets In a ChangeSorter, they will appear in the reversed order." "ChangesOrganizer reorderChangeSets" | newHead newMid newTail | newHead := OrderedCollection new. newMid := OrderedCollection new. newTail := OrderedCollection new. ChangeSet allChangeSets do: [:aChangeSet | (self belongsInProjectsInRelease: aChangeSet) ifTrue: [newHead add: aChangeSet] ifFalse: [(self belongsInNumbered: aChangeSet) ifTrue: [newMid add: aChangeSet] ifFalse: [newTail add: aChangeSet]]]. ChangeSet allChangeSets: newHead, newMid, newTail. SystemWindow wakeUpTopWindowUponStartup! ! !ChangesOrganizer class methodsFor: 'services' stamp: 'pk 2/6/2006 09:49'! secondaryChangeSet ^ChangeSet secondaryChangeSet! ! !ChangesOrganizer class methodsFor: 'utilities' stamp: 'pk 10/23/2008 16:28'! fileOutChangeSetsNamed: nameList "File out the list of change sets whose names are provided" "ChangesOrganizer fileOutChangeSetsNamed: #('New Changes' 'miscTidies-sw')" | notFound aChangeSet infoString empty | notFound := OrderedCollection new. empty := OrderedCollection new. nameList do: [:aName | (aChangeSet := self changeSetNamed: aName) ifNotNil: [aChangeSet isEmpty ifTrue: [empty add: aName] ifFalse: [aChangeSet fileOut]] ifNil: [notFound add: aName]]. infoString := (nameList size - notFound size) printString, ' change set(s) filed out'. notFound size > 0 ifTrue: [infoString := infoString, ' ', notFound size printString, ' change set(s) not found:'. notFound do: [:aName | infoString := infoString, ' ', aName]]. empty size > 0 ifTrue: [infoString := infoString, ' ', empty size printString, ' change set(s) were empty:'. empty do: [:aName | infoString := infoString, ' ', aName]]. self inform: infoString! ! Magnitude subclass: #Character instanceVariableNames: 'value' classVariableNames: 'CharacterTable ClassificationTable LetterBits LowercaseBit UppercaseBit' poolDictionaries: '' category: 'Collections-Strings'! !Character commentStamp: 'ar 4/9/2005 22:35' prior: 0! I represent a character by storing its associated Unicode. The first 256 characters are created uniquely, so that all instances of latin1 characters ($R, for example) are identical. The code point is based on Unicode. Since Unicode is 21-bit wide character set, we have several bits available for other information. As the Unicode Standard states, a Unicode code point doesn't carry the language information. This is going to be a problem with the languages so called CJK (Chinese, Japanese, Korean. Or often CJKV including Vietnamese). Since the characters of those languages are unified and given the same code point, it is impossible to display a bare Unicode code point in an inspector or such tools. To utilize the extra available bits, we use them for identifying the languages. Since the old implementation uses the bits to identify the character encoding, the bits are sometimes called "encoding tag" or neutrally "leading char", but the bits rigidly denotes the concept of languages. The other languages can have the language tag if you like. This will help to break the large default font (font set) into separately loadable chunk of fonts. However, it is open to the each native speakers and writers to decide how to define the character equality, since the same Unicode code point may have different language tag thus simple #= comparison may return false. I represent a character by storing its associated ASCII code (extended to 256 codes). My instances are created uniquely, so that all instances of a character ($R, for example) are identical.! !Character methodsFor: '*packageinfo-base' stamp: 'ab 5/31/2003 17:15'! escapeEntities #($< '<' $> '>' $& '&') pairsDo: [:k :v | self = k ifTrue: [^ v]]. ^ String with: self! ! !Character methodsFor: '*splitjoin' stamp: 'onierstrasz 4/10/2009 22:51'! join: aSequenceableCollection ^ self asString join: aSequenceableCollection ! ! !Character methodsFor: '*vb-regex' stamp: 'avi 11/30/2003 13:31'! isAlphabetic ^ self isLetter! ! !Character methodsFor: 'accessing'! asciiValue "Answer the value of the receiver that represents its ascii encoding." ^value! ! !Character methodsFor: 'accessing' stamp: 'yo 12/29/2002 10:11'! charCode ^ (value bitAnd: 16r3FFFFF). ! ! !Character methodsFor: 'accessing' stamp: 'GabrielOmarCotelli 5/25/2009 16:04'! codePoint ^value! ! !Character methodsFor: 'accessing' stamp: 'yo 12/1/2003 19:30'! digitValue "Answer 0-9 if the receiver is $0-$9, 10-35 if it is $A-$Z, and < 0 otherwise. This is used to parse literal numbers of radix 2-36." ^ (EncodedCharSet charsetAt: self leadingChar) digitValue: self. ! ! !Character methodsFor: 'accessing' stamp: 'yo 12/29/2002 10:14'! leadingChar ^ (value bitAnd: (16r3FC00000)) bitShift: -22. ! ! !Character methodsFor: 'comparing' stamp: 'md 8/2/2005 18:21'! sameAs: aCharacter "Answer whether the receiver is equal to aCharacter, ignoring case" ^ (self asLowercase = aCharacter asLowercase) ! ! !Character methodsFor: 'comparing'! < aCharacter "Answer true if the receiver's value < aCharacter's value." ^self asciiValue < aCharacter asciiValue! ! !Character methodsFor: 'comparing' stamp: 'ar 4/9/2005 21:48'! = aCharacter "Primitive. Answer true if the receiver and the argument are the same object (have the same object pointer) and false otherwise. Optional. See Object documentation whatIsAPrimitive." ^ self == aCharacter or:[ aCharacter isCharacter and: [self asciiValue = aCharacter asciiValue]]! ! !Character methodsFor: 'comparing'! > aCharacter "Answer true if the receiver's value > aCharacter's value." ^self asciiValue > aCharacter asciiValue! ! !Character methodsFor: 'comparing'! hash "Hash is reimplemented because = is implemented." ^value! ! !Character methodsFor: 'converting'! asCharacter "Answer the receiver itself." ^self! ! !Character methodsFor: 'converting' stamp: 'ls 9/5/1998 01:18'! asIRCLowercase "convert to lowercase, using IRC's rules" self == $[ ifTrue: [ ^ ${ ]. self == $] ifTrue: [ ^ $} ]. self == $\ ifTrue: [ ^ $| ]. ^self asLowercase! ! !Character methodsFor: 'converting'! asInteger "Answer the value of the receiver." ^value! ! !Character methodsFor: 'converting' stamp: 'yo 8/16/2004 11:35'! asLowercase "If the receiver is uppercase, answer its matching lowercase Character." "A tentative implementation. Eventually this should consult the Unicode table." | v | v := self charCode. (((8r101 <= v and: [v <= 8r132]) or: [16rC0 <= v and: [v <= 16rD6]]) or: [16rD8 <= v and: [v <= 16rDE]]) ifTrue: [^ Character value: value + 8r40] ifFalse: [^ self]! ! !Character methodsFor: 'converting' stamp: 'sma 3/11/2000 17:21'! asString ^ String with: self! ! !Character methodsFor: 'converting' stamp: 'raa 5/26/2001 09:54'! asSymbol "Answer a Symbol consisting of the receiver as the only element." ^Symbol internCharacter: self! ! !Character methodsFor: 'converting' stamp: 'tk 9/4/2000 12:05'! asText ^ self asString asText! ! !Character methodsFor: 'converting' stamp: 'ar 4/9/2005 21:51'! asUnicode | table charset v | self leadingChar = 0 ifTrue: [^ value]. charset := EncodedCharSet charsetAt: self leadingChar. charset isCharset ifFalse: [^ self charCode]. table := charset ucsTable. table isNil ifTrue: [^ 16rFFFD]. v := table at: self charCode + 1. v = -1 ifTrue: [^ 16rFFFD]. ^ v. ! ! !Character methodsFor: 'converting' stamp: 'yo 8/16/2004 11:34'! asUppercase "If the receiver is lowercase, answer its matching uppercase Character." "A tentative implementation. Eventually this should consult the Unicode table." | v | v := self charCode. (((8r141 <= v and: [v <= 8r172]) or: [16rE0 <= v and: [v <= 16rF6]]) or: [16rF8 <= v and: [v <= 16rFE]]) ifTrue: [^ Character value: value - 8r40] ifFalse: [^ self] ! ! !Character methodsFor: 'converting' stamp: 'yo 8/11/2003 21:18'! basicSqueakToIso | asciiValue | value < 128 ifTrue: [^ self]. value > 255 ifTrue: [^ self]. asciiValue := #(196 197 199 201 209 214 220 225 224 226 228 227 229 231 233 232 234 235 237 236 238 239 241 243 242 244 246 245 250 249 251 252 134 176 162 163 167 149 182 223 174 169 153 180 168 128 198 216 129 177 138 141 165 181 142 143 144 154 157 170 186 158 230 248 191 161 172 166 131 173 178 171 187 133 160 192 195 213 140 156 150 151 147 148 145 146 247 179 253 159 185 164 139 155 188 189 135 183 130 132 137 194 202 193 203 200 205 206 207 204 211 212 190 210 218 219 217 208 136 152 175 215 221 222 184 240 254 255 256 ) at: self asciiValue - 127. ^ Character value: asciiValue. ! ! !Character methodsFor: 'converting' stamp: 'michael.rueger 2/5/2009 17:02'! macRomanToUnicode "Convert the receiver from MacRoman Unicode." ^MacRomanTextConverter new unicodeToByte: self! ! !Character methodsFor: 'converting'! to: other "Answer with a collection in ascii order -- $a to: $z" ^ (self asciiValue to: other asciiValue) collect: [:ascii | Character value: ascii]! ! !Character methodsFor: 'converting' stamp: 'michael.rueger 2/5/2009 17:01'! unicodeToMacRoman "Convert the receiver from Unicode to MacRoman encoding." ^MacRomanTextConverter new byteToUnicode: self! ! !Character methodsFor: 'copying' stamp: 'tk 12/9/2000 11:46'! clone "Answer with the receiver, because Characters are unique."! ! !Character methodsFor: 'copying'! copy "Answer with the receiver because Characters are unique."! ! !Character methodsFor: 'copying'! deepCopy "Answer with the receiver because Characters are unique."! ! !Character methodsFor: 'copying' stamp: 'tk 1/7/1999 16:50'! veryDeepCopyWith: deepCopier "Return self. I can't be copied."! ! !Character methodsFor: 'object filein' stamp: 'tk 1/17/2000 11:27'! comeFullyUpOnReload: smartRefStream "Use existing an Character. Don't use the new copy." ^ self class value: value! ! !Character methodsFor: 'object filein' stamp: 'tk 2/16/2001 14:52'! objectForDataStream: refStrm "I am being collected for inclusion in a segment. Do not include Characters!! Let them be in outPointers." refStrm insideASegment ifFalse: ["Normal use" ^ self] ifTrue: ["recording objects to go into an ImageSegment" "remove it from references. Do not trace." refStrm references removeKey: self ifAbsent: []. ^ nil] ! ! !Character methodsFor: 'printing' stamp: 'ar 4/9/2005 21:53'! hex ^value hex! ! !Character methodsFor: 'printing'! isLiteral ^true! ! !Character methodsFor: 'printing' stamp: 'lr 11/21/2005 17:40'! printOn: aStream | name | value > 32 ifTrue: [ aStream nextPut: $$; nextPut: self ] ifFalse: [ name := self class constantNameFor: self. name notNil ifTrue: [ aStream nextPutAll: self class name; space; nextPutAll: name ] ifFalse: [ aStream nextPutAll: self class name; nextPutAll: ' value: '; print: value ] ].! ! !Character methodsFor: 'printing' stamp: 'MPW 1/1/1901 22:04'! printOnStream: aStream aStream print:'$', (String with:self).! ! !Character methodsFor: 'printing' stamp: 'ar 4/9/2005 22:30'! storeBinaryOn: aStream "Store the receiver on a binary (file) stream" value < 256 ifTrue:[aStream basicNextPut: self] ifFalse:[Stream nextInt32Put: value].! ! !Character methodsFor: 'printing' stamp: 'lr 1/3/2007 19:30'! storeOn: aStream "Common character literals are preceded by '$', however special need to be encoded differently: for some this might be done by using one of the shortcut constructor methods for the rest we have to create them by ascii-value." | name | (value between: 33 and: 255) ifTrue: [ aStream nextPut: $$; nextPut: self ] ifFalse: [ name := self class constantNameFor: self. name notNil ifTrue: [ aStream nextPutAll: self class name; space; nextPutAll: name ] ifFalse: [ aStream nextPut: $(; nextPutAll: self class name; nextPutAll: ' value: '; print: value; nextPut: $) ] ].! ! !Character methodsFor: 'testing' stamp: 'yo 8/5/2003 16:57'! canBeGlobalVarInitial ^ (EncodedCharSet charsetAt: self leadingChar) canBeGlobalVarInitial: self. ! ! !Character methodsFor: 'testing' stamp: 'yo 8/5/2003 16:58'! canBeNonGlobalVarInitial ^ (EncodedCharSet charsetAt: self leadingChar) canBeNonGlobalVarInitial: self. ! ! !Character methodsFor: 'testing'! isAlphaNumeric "Answer whether the receiver is a letter or a digit." ^self isLetter or: [self isDigit]! ! !Character methodsFor: 'testing' stamp: 'yo 8/28/2002 13:42'! isCharacter ^ true. ! ! !Character methodsFor: 'testing' stamp: 'yo 8/5/2003 16:43'! isDigit ^ (EncodedCharSet charsetAt: self leadingChar) isDigit: self. ! ! !Character methodsFor: 'testing' stamp: 'yo 8/5/2003 16:43'! isLetter ^ (EncodedCharSet charsetAt: self leadingChar) isLetter: self. ! ! !Character methodsFor: 'testing' stamp: 'yo 8/5/2003 16:43'! isLowercase ^ (EncodedCharSet charsetAt: self leadingChar) isLowercase: self. ! ! !Character methodsFor: 'testing' stamp: 'yo 8/27/2002 15:18'! isOctetCharacter ^ value < 256. ! ! !Character methodsFor: 'testing' stamp: 'yo 7/29/2005 15:21'! isSafeForHTTP "whether a character is 'safe', or needs to be escaped when used, eg, in a URL" "[GG] See http://www.faqs.org/rfcs/rfc1738.html. ~ is unsafe and has been removed" ^ self charCode < 128 and: [self isAlphaNumeric or: ['.-_' includes: (Character value: self charCode)]]! ! !Character methodsFor: 'testing'! isSeparator "Answer whether the receiver is one of the separator characters--space, cr, tab, line feed, or form feed." value = 32 ifTrue: [^true]. "space" value = 13 ifTrue: [^true]. "cr" value = 9 ifTrue: [^true]. "tab" value = 10 ifTrue: [^true]. "line feed" value = 12 ifTrue: [^true]. "form feed" ^false! ! !Character methodsFor: 'testing' stamp: 'di 4/3/1999 00:38'! isSpecial "Answer whether the receiver is one of the special characters" ^'+-/\*~<>=@,%|&?!!' includes: self! ! !Character methodsFor: 'testing' stamp: 'ar 4/12/2005 14:09'! isTraditionalDomestic "Yoshiki's note about #isUnicode says: [This method] is for the backward compatibility when we had domestic traditional encodings for CJK languages. To support loading the projects in traditional domestic encodings (From Nihongo4), and load some changesets. Once we decided to get rid of classes like JISX0208 from the EncodedCharSet table, the need for isUnicode will not be necessary. I (Andreas) decided to change the name from isUnicode to #isTraditionalDomestic since I found isUnicode to be horribly confusing (how could the character *not* be Unicode after all?). But still, we should remove this method in due time." ^ ((EncodedCharSet charsetAt: self leadingChar) isKindOf: LanguageEnvironment class) not! ! !Character methodsFor: 'testing' stamp: 'yo 8/5/2003 16:43'! isUppercase ^ (EncodedCharSet charsetAt: self leadingChar) isUppercase: self. ! ! !Character methodsFor: 'testing'! isVowel "Answer whether the receiver is one of the vowels, AEIOU, in upper or lower case." ^'AEIOU' includes: self asUppercase! ! !Character methodsFor: 'testing'! tokenish "Answer whether the receiver is a valid token-character--letter, digit, or colon." ^self isLetter or: [self isDigit or: [self = $:]]! ! !Character methodsFor: 'private' stamp: 'ar 4/9/2005 22:18'! setValue: newValue value ifNotNil:[^self error:'Characters are immutable']. value := newValue.! ! !Character methodsFor: '*Multilingual' stamp: 'pmm 9/12/2009 20:39'! asUnicodeChar "Answer a copy of the receiver with Unicode as the leadingChar" ^ Unicode charFromUnicode: self asUnicode! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Character class instanceVariableNames: ''! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:20'! arrowDown ^ self value: 31! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:20'! arrowLeft ^ self value: 28! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:20'! arrowRight ^ self value: 29! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:20'! arrowUp ^ self value: 30! ! !Character class methodsFor: 'accessing untypeable characters'! backspace "Answer the Character representing a backspace." ^self value: 8! ! !Character class methodsFor: 'accessing untypeable characters'! cr "Answer the Character representing a carriage return." ^self value: 13! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:19'! delete ^ self value: 127! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:21'! end ^ self value: 4! ! !Character class methodsFor: 'accessing untypeable characters'! enter "Answer the Character representing enter." ^self value: 3! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'ls 9/2/1999 08:06'! escape "Answer the ASCII ESC character" ^self value: 27! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'sma 3/15/2000 22:33'! euro "The Euro currency sign, that E with two dashes. The key code is a wild guess" ^ Character value: 219! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:21'! home ^ self value: 1! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:19'! insert ^ self value: 5! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'ls 9/8/1998 22:15'! lf "Answer the Character representing a linefeed." ^self value: 10! ! !Character class methodsFor: 'accessing untypeable characters'! linefeed "Answer the Character representing a linefeed." ^self value: 10! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'wiz 4/9/2006 20:30'! nbsp "non-breakable space. Latin1 encoding common usage." ^ Character value: 160! ! !Character class methodsFor: 'accessing untypeable characters'! newPage "Answer the Character representing a form feed." ^self value: 12! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:20'! pageDown ^ self value: 12! ! !Character class methodsFor: 'accessing untypeable characters' stamp: 'NS 7/11/2000 09:21'! pageUp ^ self value: 11! ! !Character class methodsFor: 'accessing untypeable characters'! space "Answer the Character representing a space." ^self value: 32! ! !Character class methodsFor: 'accessing untypeable characters'! tab "Answer the Character representing a tab." ^self value: 9! ! !Character class methodsFor: 'constants' stamp: 'rhi 9/8/2000 14:57'! alphabet "($a to: $z) as: String" ^ 'abcdefghijklmnopqrstuvwxyz' copy! ! !Character class methodsFor: 'constants'! characterTable "Answer the class variable in which unique Characters are stored." ^CharacterTable! ! !Character class methodsFor: 'initialization' stamp: 'yo 10/4/2003 16:03'! initialize "Create the table of unique Characters." " self initializeClassificationTable"! ! !Character class methodsFor: 'initialization' stamp: 'dgd 8/24/2003 15:10'! initializeClassificationTable " Initialize the classification table. The classification table is a compact encoding of upper and lower cases of characters with - bits 0-7: The lower case value of this character. - bits 8-15: The upper case value of this character. - bit 16: lowercase bit (e.g., isLowercase == true) - bit 17: uppercase bit (e.g., isUppercase == true) " | ch1 ch2 | LowercaseBit := 1 bitShift: 16. UppercaseBit := 1 bitShift: 17. "Initialize the letter bits (e.g., isLetter == true)" LetterBits := LowercaseBit bitOr: UppercaseBit. ClassificationTable := Array new: 256. "Initialize the defaults (neither lower nor upper case)" 0 to: 255 do:[:i| ClassificationTable at: i+1 put: (i bitShift: 8) + i. ]. "Initialize character pairs (upper-lower case)" #( "Basic roman" ($A $a) ($B $b) ($C $c) ($D $d) ($E $e) ($F $f) ($G $g) ($H $h) ($I $i) ($J $j) ($K $k) ($L $l) ($M $m) ($N $n) ($O $o) ($P $p) ($Q $q) ($R $r) ($S $s) ($T $t) ($U $u) ($V $v) ($W $w) ($X $x) ($Y $y) ($Z $z) "International" ($Ä $ä) ($Å $å) ($Ç $ç) ($É $é) ($Ñ $ñ) ($Ö $ö) ($Ü $ü) ($À $à) ($à $ã) ($Õ $õ) ($Œ $œ) ($Æ $æ) "International - Spanish" ($Á $á) ($Í $í) ($Ó $ó) ($Ú $ú) "International - PLEASE CHECK" ($È $è) ($Ì $ì) ($Ò $ò) ($Ù $ù) ($Ë $ë) ($Ï $ï) ($ $â) ($Ê $ê) ($Î $î) ($Ô $ô) ($Û $û) ) do:[:pair| ch1 := pair first asciiValue. ch2 := pair last asciiValue. ClassificationTable at: ch1+1 put: (ch1 bitShift: 8) + ch2 + UppercaseBit. ClassificationTable at: ch2+1 put: (ch1 bitShift: 8) + ch2 + LowercaseBit. ]. "Initialize a few others for which we only have lower case versions." #($ß $Ø $ø $ÿ) do:[:char| ch1 := char asciiValue. ClassificationTable at: ch1+1 put: (ch1 bitShift: 8) + ch1 + LowercaseBit. ]. ! ! !Character class methodsFor: 'instance creation' stamp: 'ar 4/9/2005 22:36'! allByteCharacters "Answer all the characters that can be encoded in a byte" ^ (0 to: 255) collect: [:v | Character value: v] ! ! !Character class methodsFor: 'instance creation' stamp: 'ar 4/9/2005 22:37'! allCharacters "This name is obsolete since only the characters that will fit in a byte can be queried" ^self allByteCharacters ! ! !Character class methodsFor: 'instance creation' stamp: 'GabrielOmarCotelli 5/25/2009 16:03'! codePoint: anInteger "Just for ANSI Compliance" ^self value: anInteger ! ! !Character class methodsFor: 'instance creation'! digitValue: x "Answer the Character whose digit value is x. For example, answer $9 for x=9, $0 for x=0, $A for x=10, $Z for x=35." | index | index := x asInteger. ^CharacterTable at: (index < 10 ifTrue: [48 + index] ifFalse: [55 + index]) + 1! ! !Character class methodsFor: 'instance creation' stamp: 'ar 4/9/2005 22:24'! leadingChar: leadChar code: code code >= 16r400000 ifTrue: [ self error: 'code is out of range'. ]. leadChar >= 256 ifTrue: [ self error: 'lead is out of range'. ]. ^self value: (leadChar bitShift: 22) + code.! ! !Character class methodsFor: 'instance creation'! new "Creating new characters is not allowed." self error: 'cannot create new characters'! ! !Character class methodsFor: 'instance creation'! separators ^ #(32 "space" 13 "cr" 9 "tab" 10 "line feed" 12 "form feed") collect: [:v | Character value: v] ! ! !Character class methodsFor: 'instance creation' stamp: 'GabrielOmarCotelli 5/29/2009 23:42'! value: anInteger "Answer the Character whose value is anInteger." anInteger negative ifTrue:[self error: 'Characters expects a positive value.']. anInteger > 255 ifTrue: [^self basicNew setValue: anInteger]. ^ CharacterTable at: anInteger + 1. ! ! !Character class methodsFor: 'private' stamp: 'lr 11/21/2005 17:24'! constantNameFor: aCharacter ^ self constantNames detect: [ :each | (self perform: each) = aCharacter ] ifNone: [ nil ].! ! !Character class methodsFor: 'private' stamp: 'gvc 6/21/2007 11:52'! constantNames "Added the rest of them!!" ^#(backspace cr delete escape lf newPage space tab arrowDown arrowLeft arrowRight arrowUp enter end home insert nbsp pageDown pageUp).! ! Rectangle subclass: #CharacterBlock instanceVariableNames: 'stringIndex text textLine' classVariableNames: '' poolDictionaries: 'TextConstants' category: 'Graphics-Text'! !CharacterBlock commentStamp: '' prior: 0! My instances contain information about displayed characters. They are used to return the results of methods: Paragraph characterBlockAtPoint: aPoint and Paragraph characterBlockForIndex: stringIndex. Any recomposition or movement of a Paragraph can make the instance obsolete.! !CharacterBlock methodsFor: 'accessing' stamp: 'di 6/7/2000 17:33'! copy "Overridden because Rectangle does a deepCopy, which goes nuts with the text" ^ self clone! ! !CharacterBlock methodsFor: 'accessing'! stringIndex "Answer the position of the receiver in the string it indexes." ^stringIndex! ! !CharacterBlock methodsFor: 'accessing' stamp: 'di 12/2/97 14:33'! textLine ^ textLine! ! !CharacterBlock methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! textLine: aLine textLine := aLine! ! !CharacterBlock methodsFor: 'comparing'! < aCharacterBlock "Answer whether the string index of the receiver precedes that of aCharacterBlock." ^stringIndex < aCharacterBlock stringIndex! ! !CharacterBlock methodsFor: 'comparing'! <= aCharacterBlock "Answer whether the string index of the receiver does not come after that of aCharacterBlock." ^(self > aCharacterBlock) not! ! !CharacterBlock methodsFor: 'comparing'! = aCharacterBlock self species = aCharacterBlock species ifTrue: [^stringIndex = aCharacterBlock stringIndex] ifFalse: [^false]! ! !CharacterBlock methodsFor: 'comparing'! > aCharacterBlock "Answer whether the string index of the receiver comes after that of aCharacterBlock." ^aCharacterBlock < self! ! !CharacterBlock methodsFor: 'comparing'! >= aCharacterBlock "Answer whether the string index of the receiver does not precede that of aCharacterBlock." ^(self < aCharacterBlock) not! ! !CharacterBlock methodsFor: 'comparing' stamp: 'th 9/17/2002 11:54'! max: aCharacterBlock aCharacterBlock ifNil:[^self]. ^aCharacterBlock > self ifTrue:[ aCharacterBlock] ifFalse:[self].! ! !CharacterBlock methodsFor: 'comparing' stamp: 'th 9/17/2002 11:54'! min: aCharacterBlock aCharacterBlock ifNil:[^self]. ^aCharacterBlock < self ifTrue:[ aCharacterBlock] ifFalse:[self].! ! !CharacterBlock methodsFor: 'printing' stamp: 'di 12/2/97 19:15'! printOn: aStream aStream nextPutAll: 'a CharacterBlock with index '. stringIndex printOn: aStream. (text ~~ nil and: [text size> 0 and: [stringIndex between: 1 and: text size]]) ifTrue: [aStream nextPutAll: ' and character '. (text at: stringIndex) printOn: aStream]. aStream nextPutAll: ' and rectangle '. super printOn: aStream. textLine ifNotNil: [aStream cr; nextPutAll: ' in '. textLine printOn: aStream]. ! ! !CharacterBlock methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! moveBy: aPoint "Change the corner positions of the receiver so that its area translates by the amount defined by the argument, aPoint." origin := origin + aPoint. corner := corner + aPoint! ! !CharacterBlock methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! stringIndex: anInteger text: aText topLeft: topLeft extent: extent stringIndex := anInteger. text := aText. super setOrigin: topLeft corner: topLeft + extent! ! CharacterScanner subclass: #CharacterBlockScanner instanceVariableNames: 'characterPoint characterIndex lastCharacter lastCharacterExtent lastSpaceOrTabExtent nextLeftMargin specialWidth' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Text'! !CharacterBlockScanner commentStamp: '' prior: 0! My instances are used to scan text to compute the CharacterBlock for a character specified by its index in the text or its proximity to the cursor location.! !CharacterBlockScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 12:49'! crossedX "Text display has wrapping. The scanner just found a character past the x location of the cursor. We know that the cursor is pointing at a character or before one." | leadingTab currentX | characterIndex == nil ifFalse: [ "If the last character of the last line is a space, and it crosses the right margin, then locating the character block after it is impossible without this hack." characterIndex > text size ifTrue: [ lastIndex := characterIndex. characterPoint := (nextLeftMargin ifNil: [leftMargin]) @ (destY + line lineHeight). ^true]]. characterPoint x <= (destX + (lastCharacterExtent x // 2)) ifTrue: [lastCharacter := (text at: lastIndex). characterPoint := destX @ destY. ^true]. lastIndex >= line last ifTrue: [lastCharacter := (text at: line last). characterPoint := destX @ destY. ^true]. "Pointing past middle of a character, return the next character." lastIndex := lastIndex + 1. lastCharacter := text at: lastIndex. currentX := destX + lastCharacterExtent x + kern. self lastCharacterExtentSetX: (font widthOf: lastCharacter). characterPoint := currentX @ destY. lastCharacter = Space ifFalse: [^ true]. "Yukky if next character is space or tab." alignment = Justified ifTrue: [self lastCharacterExtentSetX: (lastCharacterExtent x + (line justifiedPadFor: (spaceCount + 1) font: font)). ^ true]. true ifTrue: [^ true]. "NOTE: I find no value to the following code, and so have defeated it - DI" "See tabForDisplay for illumination on the following awfulness." leadingTab := true. line first to: lastIndex - 1 do: [:index | (text at: index) ~= Tab ifTrue: [leadingTab := false]]. (alignment ~= Justified or: [leadingTab]) ifTrue: [self lastCharacterExtentSetX: (textStyle nextTabXFrom: currentX leftMargin: leftMargin rightMargin: rightMargin) - currentX] ifFalse: [self lastCharacterExtentSetX: (((currentX + (textStyle tabWidth - (line justifiedTabDeltaFor: spaceCount))) - currentX) max: 0)]. ^ true! ! !CharacterBlockScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 12:50'! paddedSpace "When the line is justified, the spaces will not be the same as the font's space character. A padding of extra space must be considered in trying to find which character the cursor is pointing at. Answer whether the scanning has crossed the cursor." | pad | pad := 0. spaceCount := spaceCount + 1. pad := line justifiedPadFor: spaceCount font: font. lastSpaceOrTabExtent := lastCharacterExtent copy. self lastSpaceOrTabExtentSetX: spaceWidth + pad. (destX + lastSpaceOrTabExtent x) >= characterPoint x ifTrue: [lastCharacterExtent := lastSpaceOrTabExtent copy. ^self crossedX]. lastIndex := lastIndex + 1. destX := destX + lastSpaceOrTabExtent x. ^ false ! ! !CharacterBlockScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! characterBlockAtPoint: aPoint in: aParagraph "Answer a CharacterBlock for character in aParagraph at point aPoint. It is assumed that aPoint has been transformed into coordinates appropriate to the text's destination form rectangle and the composition rectangle." self initializeFromParagraph: aParagraph clippedBy: aParagraph clippingRectangle. characterPoint := aPoint. ^ self buildCharacterBlockIn: aParagraph! ! !CharacterBlockScanner methodsFor: 'scanning' stamp: 'nk 11/22/2004 14:32'! characterBlockAtPoint: aPoint index: index in: textLine "This method is the Morphic characterBlock finder. It combines MVC's characterBlockAtPoint:, -ForIndex:, and buildCharcterBlock:in:" | runLength lineStop done stopCondition | line := textLine. rightMargin := line rightMargin. lastIndex := line first. self setStopConditions. "also sets font" characterIndex := index. " == nil means scanning for point" characterPoint := aPoint. (characterPoint isNil or: [characterPoint y > line bottom]) ifTrue: [characterPoint := line bottomRight]. (text isEmpty or: [(characterPoint y < line top or: [characterPoint x < line left]) or: [characterIndex notNil and: [characterIndex < line first]]]) ifTrue: [^ (CharacterBlock new stringIndex: line first text: text topLeft: line leftMargin@line top extent: 0 @ textStyle lineGrid) textLine: line]. destX := leftMargin := line leftMarginForAlignment: alignment. destY := line top. runLength := text runLengthFor: line first. characterIndex ifNotNil: [lineStop := characterIndex "scanning for index"] ifNil: [lineStop := line last "scanning for point"]. runStopIndex := lastIndex + (runLength - 1) min: lineStop. lastCharacterExtent := 0 @ line lineHeight. spaceCount := 0. done := false. [done] whileFalse: [stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex in: text string rightX: characterPoint x stopConditions: stopConditions kern: kern. "see setStopConditions for stopping conditions for character block operations." self lastCharacterExtentSetX: (specialWidth ifNil: [font widthOf: (text at: lastIndex)] ifNotNil: [specialWidth]). (self perform: stopCondition) ifTrue: [characterIndex ifNil: [ "Result for characterBlockAtPoint: " (stopCondition ~~ #cr and: [ lastIndex == line last and: [ aPoint x > ((characterPoint x) + (lastCharacterExtent x / 2)) ]]) ifTrue: [ "Correct for right half of last character in line" ^ (CharacterBlock new stringIndex: lastIndex + 1 text: text topLeft: characterPoint + (lastCharacterExtent x @ 0) + (font descentKern @ 0) extent: 0 @ lastCharacterExtent y) textLine: line ]. ^ (CharacterBlock new stringIndex: lastIndex text: text topLeft: characterPoint + (font descentKern @ 0) extent: lastCharacterExtent - (font baseKern @ 0)) textLine: line] ifNotNil: ["Result for characterBlockForIndex: " ^ (CharacterBlock new stringIndex: characterIndex text: text topLeft: characterPoint + ((font descentKern) - kern @ 0) extent: lastCharacterExtent) textLine: line]]]! ! !CharacterBlockScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! characterBlockForIndex: targetIndex in: aParagraph "Answer a CharacterBlock for character in aParagraph at targetIndex. The coordinates in the CharacterBlock will be appropriate to the intersection of the destination form rectangle and the composition rectangle." self initializeFromParagraph: aParagraph clippedBy: aParagraph clippingRectangle. characterIndex := targetIndex. characterPoint := aParagraph rightMarginForDisplay @ (aParagraph topAtLineIndex: (aParagraph lineIndexOfCharacterIndex: characterIndex)). ^ self buildCharacterBlockIn: aParagraph! ! !CharacterBlockScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! indentationLevel: anInteger super indentationLevel: anInteger. nextLeftMargin := leftMargin. indentationLevel timesRepeat: [ nextLeftMargin := textStyle nextTabXFrom: nextLeftMargin leftMargin: leftMargin rightMargin: rightMargin ]! ! !CharacterBlockScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! placeEmbeddedObject: anchoredMorph "Workaround: The following should really use #textAnchorType" anchoredMorph relativeTextAnchorPosition ifNotNil: [ ^ true ]. (super placeEmbeddedObject: anchoredMorph) ifFalse: [ ^ false ]. specialWidth := anchoredMorph width. ^ true! ! !CharacterBlockScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! cr "Answer a CharacterBlock that specifies the current location of the mouse relative to a carriage return stop condition that has just been encountered. The ParagraphEditor convention is to denote selections by CharacterBlocks, sometimes including the carriage return (cursor is at the end) and sometimes not (cursor is in the middle of the text)." ((characterIndex ~= nil and: [ characterIndex > text size ]) or: [ line last = text size and: [ destY + line lineHeight < characterPoint y ] ]) ifTrue: [ "When off end of string, give data for next character" destY := destY + line lineHeight. lastCharacter := nil. characterPoint := (nextLeftMargin ifNil: [ leftMargin ]) @ destY. lastIndex := lastIndex + 1. self lastCharacterExtentSetX: 0. ^ true ]. lastCharacter := CR. characterPoint := destX @ destY. self lastCharacterExtentSetX: rightMargin - destX. ^ true! ! !CharacterBlockScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! endOfRun "Before arriving at the cursor location, the selection has encountered an end of run. Answer false if the selection continues, true otherwise. Set up indexes for building the appropriate CharacterBlock." | runLength lineStop | (((characterIndex ~~ nil and: [ runStopIndex < characterIndex and: [ runStopIndex < text size ] ]) or: [ characterIndex == nil and: [ lastIndex < line last ] ]) or: [ lastIndex < line last and: [ (text at: lastIndex) leadingChar ~= (text at: lastIndex + 1) leadingChar and: [ lastIndex ~= characterIndex ] ] ]) ifTrue: [ "We're really at the end of a real run." runLength := text runLengthFor: (lastIndex := lastIndex + 1). characterIndex ~~ nil ifTrue: [ lineStop := characterIndex "scanning for index" ] ifFalse: [ lineStop := line last "scanning for point" ]. (runStopIndex := lastIndex + (runLength - 1)) > lineStop ifTrue: [ runStopIndex := lineStop ]. self setStopConditions. ^ false ]. lastCharacter := text at: lastIndex. characterPoint := destX @ destY. ((lastCharacter = Space and: [ alignment = Justified ]) or: [ lastCharacter = Tab and: [ lastSpaceOrTabExtent notNil ] ]) ifTrue: [ lastCharacterExtent := lastSpaceOrTabExtent ]. characterIndex ~~ nil ifTrue: [ "If scanning for an index and we've stopped on that index, then we back destX off by the width of the character stopped on (it will be pointing at the right side of the character) and return" runStopIndex = characterIndex ifTrue: [ self characterPointSetX: destX - lastCharacterExtent x. ^ true ]. "Otherwise the requested index was greater than the length of the string. Return string size + 1 as index, indicate further that off the string by setting character to nil and the extent to 0." lastIndex := lastIndex + 1. lastCharacter := nil. self lastCharacterExtentSetX: 0. ^ true ]. "Scanning for a point and either off the end of the line or off the end of the string." runStopIndex = text size ifTrue: [ "off end of string" lastIndex := lastIndex + 1. lastCharacter := nil. self lastCharacterExtentSetX: 0. ^ true ]. "just off end of line without crossing x" lastIndex := lastIndex + 1. ^ true! ! !CharacterBlockScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! setFont specialWidth := nil. super setFont! ! !CharacterBlockScanner methodsFor: 'stop conditions' stamp: 'ar 10/18/2004 14:30'! setStopConditions "Set the font and the stop conditions for the current run." self setFont. self setConditionArray: (alignment = Justified ifTrue: [#paddedSpace]). ! ! !CharacterBlockScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! tab | currentX | currentX := (alignment == Justified and: [ self leadingTab not ]) ifTrue: [ "imbedded tabs in justified text are weird" destX + (textStyle tabWidth - (line justifiedTabDeltaFor: spaceCount)) max: destX ] ifFalse: [ textStyle nextTabXFrom: destX leftMargin: leftMargin rightMargin: rightMargin ]. lastSpaceOrTabExtent := lastCharacterExtent copy. self lastSpaceOrTabExtentSetX: (currentX - destX max: 0). currentX >= characterPoint x ifTrue: [ lastCharacterExtent := lastSpaceOrTabExtent copy. ^ self crossedX ]. destX := currentX. lastIndex := lastIndex + 1. ^ false! ! !CharacterBlockScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! buildCharacterBlockIn: para "handle nullText" | lineIndex runLength lineStop done stopCondition | (para numberOfLines = 0 or: [ text size = 0 ]) ifTrue: [ ^ CharacterBlock new stringIndex: 1 text: para text topLeft: (para leftMarginForDisplayForLine: 1 alignment: (alignment ifNil: [ "like being off end of string" textStyle alignment ])) @ para compositionRectangle top extent: 0 @ textStyle lineGrid ]. "find the line" lineIndex := para lineIndexOfTop: characterPoint y. destY := para topAtLineIndex: lineIndex. line := para lines at: lineIndex. lastIndex := line first. rightMargin := para rightMarginForDisplay. self setStopConditions. " also loads the font and loads all emphasis attributes " (lineIndex = para numberOfLines and: [ destY + line lineHeight < characterPoint y ]) ifTrue: [ "if beyond lastLine, force search to last character" self characterPointSetX: rightMargin ] ifFalse: [ characterPoint y < para compositionRectangle top ifTrue: [ "force search to first line" characterPoint := para compositionRectangle topLeft ]. characterPoint x > rightMargin ifTrue: [ self characterPointSetX: rightMargin ] ]. destX := leftMargin := para leftMarginForDisplayForLine: lineIndex alignment: (alignment ifNil: [ textStyle alignment ]). nextLeftMargin := para leftMarginForDisplayForLine: lineIndex + 1 alignment: (alignment ifNil: [ textStyle alignment ]). lastIndex := line first. self setStopConditions. "also sets font" runLength := text runLengthFor: line first. characterIndex == nil ifTrue: [ lineStop := line last "characterBlockAtPoint" ] ifFalse: [ lineStop := characterIndex "characterBlockForIndex" ]. (runStopIndex := lastIndex + (runLength - 1)) > lineStop ifTrue: [ runStopIndex := lineStop ]. lastCharacterExtent := 0 @ line lineHeight. spaceCount := 0. done := false. self handleIndentation. [ done ] whileFalse: [ stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex in: text string rightX: characterPoint x stopConditions: stopConditions kern: kern. "see setStopConditions for stopping conditions for character block operations." self lastCharacterExtentSetX: (font widthOf: (text at: lastIndex)). (self perform: stopCondition) ifTrue: [ characterIndex == nil ifTrue: [ "characterBlockAtPoint" ^ CharacterBlock new stringIndex: lastIndex text: text topLeft: characterPoint + (font descentKern @ 0) extent: lastCharacterExtent ] ifFalse: [ "characterBlockForIndex" ^ CharacterBlock new stringIndex: lastIndex text: text topLeft: characterPoint + ((font descentKern - kern) @ 0) extent: lastCharacterExtent ] ] ]! ! !CharacterBlockScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! characterPointSetX: xVal characterPoint := xVal @ characterPoint y! ! !CharacterBlockScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! lastCharacterExtentSetX: xVal lastCharacterExtent := xVal @ lastCharacterExtent y! ! !CharacterBlockScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! lastSpaceOrTabExtentSetX: xVal lastSpaceOrTabExtent := xVal @ lastSpaceOrTabExtent y! ! Object subclass: #CharacterScanner instanceVariableNames: 'destX lastIndex xTable destY stopConditions text textStyle alignment leftMargin rightMargin font line runStopIndex spaceCount spaceWidth emphasisCode kern indentationLevel wantsColumnBreaks pendingKernX' classVariableNames: 'DefaultStopConditions NilCondition PaddedSpaceCondition SpaceCondition' poolDictionaries: 'TextConstants' category: 'Graphics-Text'! !CharacterScanner commentStamp: '' prior: 0! My instances hold the state associated with scanning text. My subclasses scan characters for specified purposes, such as computing a CharacterBlock or placing characters into Forms.! !CharacterScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 09:53'! basicScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta "Primitive. This is the inner loop of text display--but see scanCharactersFrom: to:rightX: which would get the string, stopConditions and displaying from the instance. March through source String from startIndex to stopIndex. If any character is flagged with a non-nil entry in stops, then return the corresponding value. Determine width of each character from xTable, indexed by map. If dextX would exceed rightX, then return stops at: 258. Advance destX by the width of the character. If stopIndex has been reached, then return stops at: 257. Optional. See Object documentation whatIsAPrimitive." | ascii nextDestX char floatDestX widthAndKernedWidth nextChar atEndOfRun | lastIndex := startIndex. floatDestX := destX. widthAndKernedWidth := Array new: 2. atEndOfRun := false. [lastIndex <= stopIndex] whileTrue: [char := (sourceString at: lastIndex). ascii := char asciiValue + 1. (stops at: ascii) == nil ifFalse: [^stops at: ascii]. "Note: The following is querying the font about the width since the primitive may have failed due to a non-trivial mapping of characters to glyphs or a non-existing xTable." nextChar := (lastIndex + 1 <= stopIndex) ifTrue:[sourceString at: lastIndex + 1] ifFalse:[ atEndOfRun := true. "if there is a next char in sourceString, then get the kern and store it in pendingKernX" lastIndex + 1 <= sourceString size ifTrue:[sourceString at: lastIndex + 1] ifFalse:[ nil]]. font widthAndKernedWidthOfLeft: char right: nextChar into: widthAndKernedWidth. nextDestX := floatDestX + (widthAndKernedWidth at: 1). nextDestX > rightX ifTrue: [^stops at: CrossedX]. floatDestX := floatDestX + kernDelta + (widthAndKernedWidth at: 2). atEndOfRun ifTrue:[ pendingKernX := (widthAndKernedWidth at: 2) - (widthAndKernedWidth at: 1). floatDestX := floatDestX - pendingKernX]. destX := floatDestX. lastIndex := lastIndex + 1]. lastIndex := stopIndex. ^stops at: EndOfRun! ! !CharacterScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 11:16'! columnBreak pendingKernX := 0. ^true! ! !CharacterScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 09:59'! setFont | priorFont | "Set the font and other emphasis." priorFont := font. text == nil ifFalse:[ emphasisCode := 0. kern := 0. indentationLevel := 0. alignment := textStyle alignment. font := nil. (text attributesAt: lastIndex forStyle: textStyle) do: [:att | att emphasizeScanner: self]]. font == nil ifTrue: [self setFont: textStyle defaultFontIndex]. font := font emphasized: emphasisCode. priorFont ifNotNil: [ font = priorFont ifTrue:[ "font is the same, perhaps the color has changed? We still want kerning between chars of the same font, but of different color. So add any pending kern to destX" destX := destX + (pendingKernX ifNil:[0])]. destX := destX + priorFont descentKern]. pendingKernX := 0. "clear any pending kern so there is no danger of it being added twice" destX := destX - font descentKern. "NOTE: next statement should be removed when clipping works" leftMargin ifNotNil: [destX := destX max: leftMargin]. kern := kern - font baseKern. "Install various parameters from the font." spaceWidth := font widthOf: Space. xTable := font xTable. stopConditions := DefaultStopConditions.! ! !CharacterScanner methodsFor: 'initialize' stamp: 'alain.plantec 5/28/2009 09:44'! initialize super initialize. destX := destY := leftMargin := 0.! ! !CharacterScanner methodsFor: 'initialize' stamp: 'lr 7/4/2009 10:42'! initializeStringMeasurer stopConditions := Array new: 258. stopConditions at: CrossedX put: #crossedX. stopConditions at: EndOfRun put: #endOfRun! ! !CharacterScanner methodsFor: 'initialize' stamp: 'lr 7/4/2009 10:42'! wantsColumnBreaks: aBoolean wantsColumnBreaks := aBoolean! ! !CharacterScanner methodsFor: 'scanner methods' stamp: 'yo 12/18/2002 12:32'! isBreakableAtIndex: index ^ (EncodedCharSet at: ((text at: index) leadingChar + 1)) isBreakableAt: index in: text. ! ! !CharacterScanner methodsFor: 'scanner methods' stamp: 'lr 7/4/2009 10:42'! scanJapaneseCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta | ascii encoding f nextDestX maxAscii startEncoding | lastIndex := startIndex. lastIndex > stopIndex ifTrue: [ lastIndex := stopIndex. ^ stops at: EndOfRun ]. startEncoding := (sourceString at: startIndex) leadingChar. font ifNil: [ font := (TextConstants at: #DefaultMultiStyle) fontArray at: 1 ]. ((font isMemberOf: StrikeFontSet) or: [ font isKindOf: TTCFontSet ]) ifTrue: [ maxAscii := font maxAsciiFor: startEncoding. f := font fontArray at: startEncoding + 1. "xTable _ f xTable. maxAscii _ xTable size - 2." spaceWidth := f widthOf: Space ] ifFalse: [ maxAscii := font maxAscii ]. [ lastIndex <= stopIndex ] whileTrue: [ encoding := (sourceString at: lastIndex) leadingChar. encoding ~= startEncoding ifTrue: [ lastIndex := lastIndex - 1. ^ stops at: EndOfRun ]. ascii := (sourceString at: lastIndex) charCode. ascii > maxAscii ifTrue: [ ascii := maxAscii ]. (encoding = 0 and: [ (stopConditions at: ascii + 1) ~~ nil ]) ifTrue: [ ^ stops at: ascii + 1 ]. nextDestX := destX + (font widthOf: (sourceString at: lastIndex)). nextDestX > rightX ifTrue: [ ^ stops at: CrossedX ]. destX := nextDestX + kernDelta. "destX printString displayAt: 0@(lastIndex*20)." lastIndex := lastIndex + 1 ]. lastIndex := stopIndex. ^ stops at: EndOfRun! ! !CharacterScanner methodsFor: 'scanner methods' stamp: 'lr 7/4/2009 10:42'! scanMultiCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta | ascii encoding f nextDestX maxAscii startEncoding | lastIndex := startIndex. lastIndex > stopIndex ifTrue: [ lastIndex := stopIndex. ^ stops at: EndOfRun ]. startEncoding := (sourceString at: startIndex) leadingChar. font ifNil: [ font := (TextConstants at: #DefaultMultiStyle) fontArray at: 1 ]. ((font isMemberOf: StrikeFontSet) or: [ font isKindOf: TTCFontSet ]) ifTrue: [ maxAscii := font maxAsciiFor: startEncoding. f := font fontArray at: startEncoding + 1. spaceWidth := f widthOf: Space ] ifFalse: [ maxAscii := font maxAscii ]. [ lastIndex <= stopIndex ] whileTrue: [ encoding := (sourceString at: lastIndex) leadingChar. encoding ~= startEncoding ifTrue: [ lastIndex := lastIndex - 1. ^ stops at: EndOfRun ]. ascii := (sourceString at: lastIndex) charCode. ascii > maxAscii ifTrue: [ ascii := maxAscii ]. (encoding = 0 and: [ (stopConditions at: ascii + 1) ~~ nil ]) ifTrue: [ ^ stops at: ascii + 1 ]. nextDestX := destX + (font widthOf: (sourceString at: lastIndex)). nextDestX > rightX ifTrue: [ ^ stops at: CrossedX ]. destX := nextDestX + kernDelta. "destX printString displayAt: 0@(lastIndex*20)." lastIndex := lastIndex + 1 ]. lastIndex := stopIndex. ^ stops at: EndOfRun! ! !CharacterScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! embeddedObject | savedIndex | savedIndex := lastIndex. text attributesAt: lastIndex do: [ :attr | attr anchoredMorph ifNotNil: [ "Following may look strange but logic gets reversed. If the morph fits on this line we're not done (return false for true) and if the morph won't fit we're done (return true for false)" (self placeEmbeddedObject: attr anchoredMorph) ifFalse: [ ^ true ] ] ]. lastIndex := savedIndex + 1. "for multiple(!!) embedded morphs" ^ false! ! !CharacterScanner methodsFor: 'scanning' stamp: 'hmm 7/15/2000 22:40'! handleIndentation self indentationLevel timesRepeat: [ self plainTab]! ! !CharacterScanner methodsFor: 'scanning' stamp: 'ar 5/17/2000 18:20'! indentationLevel "return the number of tabs that are currently being placed at the beginning of each line" ^indentationLevel ifNil:[0]! ! !CharacterScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! indentationLevel: anInteger "set the number of tabs to put at the beginning of each line" indentationLevel := anInteger! ! !CharacterScanner methodsFor: 'scanning' stamp: 'ar 1/8/2000 14:23'! leadingTab "return true if only tabs lie to the left" line first to: lastIndex do: [:i | (text at: i) == Tab ifFalse: [^ false]]. ^ true! ! !CharacterScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! measureString: aString inFont: aFont from: startIndex to: stopIndex "WARNING: In order to use this method the receiver has to be set up using #initializeStringMeasurer" destX := destY := lastIndex := 0. xTable := aFont xTable. self scanCharactersFrom: startIndex to: stopIndex in: aString rightX: 999999 stopConditions: stopConditions kern: 0. ^ destX! ! !CharacterScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! placeEmbeddedObject: anchoredMorph "Place the anchoredMorph or return false if it cannot be placed. In any event, advance destX by its width." "Workaround: The following should really use #textAnchorType" | w | anchoredMorph relativeTextAnchorPosition ifNotNil: [ ^ true ]. destX := destX + (w := anchoredMorph width). (destX > rightMargin and: [ leftMargin + w <= rightMargin ]) ifTrue: [ "Won't fit, but would on next line" ^ false ]. lastIndex := lastIndex + 1. self setFont. "Force recalculation of emphasis for next run" ^ true! ! !CharacterScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! plainTab "This is the basic method of adjusting destX for a tab." destX := (alignment == Justified and: [ self leadingTab not ]) ifTrue: [ "embedded tabs in justified text are weird" destX + (textStyle tabWidth - (line justifiedTabDeltaFor: spaceCount)) max: destX ] ifFalse: [ textStyle nextTabXFrom: destX leftMargin: leftMargin rightMargin: rightMargin ]! ! !CharacterScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! scanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta | startEncoding selector | sourceString isByteString ifTrue: [ ^ self basicScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta ]. sourceString isWideString ifTrue: [ startIndex > stopIndex ifTrue: [ lastIndex := stopIndex. ^ stops at: EndOfRun ]. startEncoding := (sourceString at: startIndex) leadingChar. selector := (EncodedCharSet charsetAt: startEncoding) scanSelector. ^ self perform: selector withArguments: (Array with: startIndex with: stopIndex with: sourceString with: rightX with: stopConditions with: kernDelta) ]. ^ stops at: EndOfRun! ! !CharacterScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! addEmphasis: code "Set the bold-ital-under-strike emphasis." emphasisCode := emphasisCode bitOr: code! ! !CharacterScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! addKern: kernDelta "Set the current kern amount." kern := kern + kernDelta! ! !CharacterScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! initializeFromParagraph: aParagraph clippedBy: clippingRectangle text := aParagraph text. textStyle := aParagraph textStyle! ! !CharacterScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setActualFont: aFont "Set the basal font to an isolated font reference." font := aFont! ! !CharacterScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setAlignment: style alignment := style! ! !CharacterScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setConditionArray: aSymbol aSymbol == #paddedSpace ifTrue: [ ^ stopConditions := PaddedSpaceCondition copy ]. aSymbol == #space ifTrue: [ ^ stopConditions := SpaceCondition copy ]. aSymbol == nil ifTrue: [ ^ stopConditions := NilCondition copy ]. self error: 'undefined stopcondition for space character'! ! !CharacterScanner methodsFor: 'private' stamp: 'ar 1/8/2000 14:28'! setFont: fontNumber "Set the font by number from the textStyle." self setActualFont: (textStyle fontAt: fontNumber)! ! !CharacterScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! text: t textStyle: ts text := t. textStyle := ts! ! !CharacterScanner methodsFor: 'private' stamp: 'ar 1/8/2000 14:28'! textColor: ignored "Overridden in DisplayScanner"! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CharacterScanner class instanceVariableNames: ''! !CharacterScanner class methodsFor: 'initialization' stamp: 'lr 7/4/2009 10:42'! initialize " CharacterScanner initialize " | a | a := Array new: 258. a at: 1 + 1 put: #embeddedObject. a at: Tab asciiValue + 1 put: #tab. a at: CR asciiValue + 1 put: #cr. a at: EndOfRun put: #endOfRun. a at: CrossedX put: #crossedX. NilCondition := a copy. DefaultStopConditions := a copy. PaddedSpaceCondition := a copy. PaddedSpaceCondition at: Space asciiValue + 1 put: #paddedSpace. SpaceCondition := a copy. SpaceCondition at: Space asciiValue + 1 put: #space! ! Collection subclass: #CharacterSet instanceVariableNames: 'map' classVariableNames: '' poolDictionaries: '' category: 'Collections-Support'! !CharacterSet commentStamp: '' prior: 0! A set of characters. Lookups for inclusion are very fast.! !CharacterSet methodsFor: 'collection ops' stamp: 'nice 5/9/2006 23:20'! add: aCharacter "I automatically become a WideCharacterSet if you add a wide character to myself" aCharacter asciiValue >= 256 ifTrue: [| wide | wide := WideCharacterSet new. wide addAll: self. wide add: aCharacter. self become: wide. ^aCharacter]. map at: aCharacter asciiValue + 1 put: 1. ^aCharacter! ! !CharacterSet methodsFor: 'collection ops' stamp: 'ar 4/9/2005 22:37'! do: aBlock "evaluate aBlock with each character in the set" Character allByteCharacters do: [ :c | (self includes: c) ifTrue: [ aBlock value: c ] ] ! ! !CharacterSet methodsFor: 'collection ops' stamp: 'nice 5/9/2006 23:09'! includes: aCharacter aCharacter asciiValue >= 256 ifTrue: ["Guard against wide characters" ^false]. ^(map at: aCharacter asciiValue + 1) > 0! ! !CharacterSet methodsFor: 'collection ops' stamp: 'nice 5/9/2006 23:20'! remove: aCharacter aCharacter asciiValue >= 256 ifFalse: ["Guard against wide characters" map at: aCharacter asciiValue + 1 put: 0]. ^aCharacter! ! !CharacterSet methodsFor: 'collection ops' stamp: 'nice 5/9/2006 23:02'! size ^map sum! ! !CharacterSet methodsFor: 'comparison' stamp: 'tk 7/5/2001 21:58'! = anObject ^self species == anObject species and: [ self byteArrayMap = anObject byteArrayMap ]! ! !CharacterSet methodsFor: 'comparison' stamp: 'ls 8/17/1998 20:46'! hash ^self byteArrayMap hash! ! !CharacterSet methodsFor: 'comparison' stamp: 'tk 7/5/2001 21:57'! species ^CharacterSet! ! !CharacterSet methodsFor: 'conversion' stamp: 'nice 3/23/2007 02:28'! byteComplement "return a character set containing precisely the single byte characters the receiver does not" | set | set := CharacterSet allCharacters. self do: [ :c | set remove: c ]. ^set! ! !CharacterSet methodsFor: 'conversion' stamp: 'nice 11/20/2007 00:19'! complement "return a character set containing precisely the characters the receiver does not" ^CharacterSetComplement of: self copy! ! !CharacterSet methodsFor: 'copying' stamp: 'nice 11/20/2007 00:40'! postCopy map := map copy! ! !CharacterSet methodsFor: 'testing' stamp: 'nice 5/9/2006 23:23'! hasWideCharacters ^false! ! !CharacterSet methodsFor: 'private' stamp: 'ls 8/17/1998 20:35'! byteArrayMap "return a ByteArray mapping each ascii value to a 1 if that ascii value is in the set, and a 0 if it isn't. Intended for use by primitives only" ^map! ! !CharacterSet methodsFor: 'private' stamp: 'alain.plantec 5/28/2009 09:44'! initialize super initialize. map := ByteArray new: 256 withAll: 0.! ! !CharacterSet methodsFor: 'private' stamp: 'nice 5/9/2006 23:22'! wideCharacterMap "used for comparing with WideCharacterSet" | wide | wide := WideCharacterSet new. wide addAll: self. ^wide wideCharacterMap! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CharacterSet class instanceVariableNames: ''! !CharacterSet class methodsFor: 'instance creation' stamp: 'ls 8/17/1998 20:42'! allCharacters "return a set containing all characters" | set | set := self empty. 0 to: 255 do: [ :ascii | set add: (Character value: ascii) ]. ^set! ! !CharacterSet class methodsFor: 'instance creation' stamp: 'nk 8/3/2004 06:54'! empty "return an empty set of characters" ^self new! ! !CharacterSet class methodsFor: 'instance creation' stamp: 'ls 1/3/1999 12:52'! newFrom: aCollection | newCollection | newCollection := self new. newCollection addAll: aCollection. ^newCollection! ! !CharacterSet class methodsFor: 'instance creation' stamp: 'ls 8/18/1998 00:40'! nonSeparators "return a set containing everything but the whitespace characters" ^self separators complement! ! !CharacterSet class methodsFor: 'instance creation' stamp: 'ls 8/18/1998 00:40'! separators "return a set containing just the whitespace characters" | set | set := self empty. set addAll: Character separators. ^set! ! Collection subclass: #CharacterSetComplement instanceVariableNames: 'absent byteArrayMapCache' classVariableNames: '' poolDictionaries: '' category: 'Collections-Support'! !CharacterSetComplement commentStamp: 'nice 8/31/2008 14:53' prior: 0! CharacterSetComplement is a space efficient implementation of (CharacterSet complement) taking care of WideCharacter (code > 255) However, it will maintain a byteArrayMap for character <= 255 in a cache keeping instance variables: absent contains character that are not in the set (i.e. my complement) byteArrayMapCache cache this information because it has to be used in tight loops where efficiency matters! !CharacterSetComplement methodsFor: 'collection ops' stamp: 'nice 8/31/2008 14:56'! add: aCharacter "a character is present if not absent, so adding a character is removing it from the absent" (absent includes: aCharacter) ifTrue: [byteArrayMapCache := nil. absent remove: aCharacter]. ^ aCharacter! ! !CharacterSetComplement methodsFor: 'collection ops' stamp: 'nice 3/23/2007 02:11'! do: aBlock "evaluate aBlock with each character in the set. don't do it, there are too many..." self shouldNotImplement! ! !CharacterSetComplement methodsFor: 'collection ops' stamp: 'nice 3/23/2007 02:07'! includes: aCharacter ^(absent includes: aCharacter) not! ! !CharacterSetComplement methodsFor: 'collection ops' stamp: 'nice 3/23/2007 02:15'! reject: aBlock "Implementation note: rejecting present is selecting absent" ^(absent select: aBlock) complement! ! !CharacterSetComplement methodsFor: 'collection ops' stamp: 'nice 8/31/2008 14:54'! remove: aCharacter "This means aCharacter is now absent from myself. It must be added to my absent." byteArrayMapCache := nil. ^absent add: aCharacter! ! !CharacterSetComplement methodsFor: 'collection ops' stamp: 'nice 1/10/2009 00:50'! removeAll | newSet | newSet := CharacterSet new. self become: newSet! ! !CharacterSetComplement methodsFor: 'collection ops' stamp: 'nice 3/23/2007 02:15'! select: aBlock "Implementation note: selecting present is rejecting absent" ^(absent reject: aBlock) complement! ! !CharacterSetComplement methodsFor: 'collection ops' stamp: 'nice 3/23/2007 02:10'! size "Is this 2**32-absent size ?" ^self shouldNotImplement! ! !CharacterSetComplement methodsFor: 'comparing' stamp: 'nice 3/23/2007 02:19'! = anObject "Implementation note: we do not test if equal to a WideCharacterSet, because it is unlikely that WideCharacterSet is as complete as self" ^self class == anObject class and: [ absent = anObject complement ]! ! !CharacterSetComplement methodsFor: 'comparing' stamp: 'marcus.denker 8/11/2008 20:45'! hash ^absent hash bitXor: self class hash! ! !CharacterSetComplement methodsFor: 'converting' stamp: 'nice 3/23/2007 02:08'! complement "return a character set containing precisely the characters the receiver does not" ^absent copy! ! !CharacterSetComplement methodsFor: 'copying' stamp: 'nice 11/20/2007 01:08'! postCopy absent := absent copy! ! !CharacterSetComplement methodsFor: 'initialization' stamp: 'nice 8/31/2008 14:56'! complement: aCharacterSet "initialize with the complement" byteArrayMapCache := nil. absent := aCharacterSet. ! ! !CharacterSetComplement methodsFor: 'printing' stamp: 'nice 11/19/2007 23:54'! printOn: aStream "Print a description of the complement rather than self. Rationale: self would be too long to print." aStream nextPut: $(. absent printOn: aStream. aStream nextPut: $); space; nextPutAll: #complement.! ! !CharacterSetComplement methodsFor: 'printing' stamp: 'nice 11/19/2007 23:55'! storeOn: aStream "Store a description of the elements of the complement rather than self." aStream nextPut: $(. absent storeOn: aStream. aStream nextPut: $); space; nextPutAll: #complement.! ! !CharacterSetComplement methodsFor: 'testing' stamp: 'nice 3/23/2007 02:12'! hasWideCharacters "This is a guess that absent is not holding each and every possible wideCharacter..." ^true! ! !CharacterSetComplement methodsFor: 'private' stamp: 'nice 8/31/2008 14:28'! byteArrayMap "return a ByteArray mapping each ascii value to a 1 if that ascii value is in the set, and a 0 if it isn't. Intended for use by primitives only" ^byteArrayMapCache ifNil: [byteArrayMapCache := absent byteArrayMap collect: [:i | 1 - i]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CharacterSetComplement class instanceVariableNames: ''! !CharacterSetComplement class methodsFor: 'instance creation' stamp: 'nice 3/23/2007 02:25'! of: aCharacterSet "answer the complement of aCharacterSet" ^ super new complement: aCharacterSet! ! TestCase subclass: #CharacterSetTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Support'! !CharacterSetTest commentStamp: 'nice 11/20/2007 00:35' prior: 0! CharacterSetTest holds tests for CharacterSet! !CharacterSetTest methodsFor: 'testing' stamp: 'nice 11/20/2007 00:38'! testCopy | theOriginal theCopy | theOriginal := CharacterSet newFrom: 'abc'. theCopy := theOriginal copy. theCopy remove: $a. ^self should: [theOriginal includes: $a] description: 'Changing the copy should not change the original'.! ! ClassTestCase subclass: #CharacterTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Text'! !CharacterTest commentStamp: '' prior: 0! This is the unit test for the class Character. Unit tests are a good way to exercise the functionality of your system in a repeatable and automatic manner. They are therefore recommended if you plan to release anything. For more information, see: - http://www.c2.com/cgi/wiki?UnitTest - http://minnow.cc.gatech.edu/squeak/1547 - the sunit class category! !CharacterTest methodsFor: 'testing - class methods' stamp: 'GabrielOmarCotelli 5/25/2009 16:02'! testCodePoint self assert: (Character codePoint: $a codePoint) = $a. self assert: (Character codePoint: 97) codePoint = 97.! ! !CharacterTest methodsFor: 'testing - class methods' stamp: 'GabrielOmarCotelli 5/29/2009 23:43'! testInstanceCreation self should: [ Character value: -1] raise: Error. self shouldnt: [Character value: 0] raise: Error. self shouldnt: [Character value: 256] raise: Error! ! !CharacterTest methodsFor: 'testing - class methods' stamp: 'sd 6/5/2005 09:25'! testNew self should: [Character new] raise: Error.! ! !CharacterTest methodsFor: 'testing-printing' stamp: 'stephane.ducasse 5/25/2008 15:47'! testHex self assert: $a hex = '61'. self assert: Character space hex = '20'! ! !CharacterTest methodsFor: 'testing-printing' stamp: 'lr 11/21/2005 17:41'! testPrintString self assert: $a printString = '$a'. self assert: $5 printString = '$5'. self assert: $@ printString = '$@'. self assert: Character cr printString = 'Character cr'. self assert: Character lf printString = 'Character lf'. self assert: Character space printString = 'Character space'. self assert: (Character value: 0) printString = 'Character value: 0'. self assert: (Character value: 17) printString = 'Character value: 17'.! ! !CharacterTest methodsFor: 'testing-printing' stamp: 'lr 11/21/2005 17:41'! testPrintStringAll Character allCharacters do: [ :each | self assert: (self class compilerClass evaluate: each printString) = each ].! ! !CharacterTest methodsFor: 'testing-printing' stamp: 'lr 11/21/2005 17:22'! testStoreString self assert: $a storeString = '$a'. self assert: $5 storeString = '$5'. self assert: $@ storeString = '$@'. self assert: Character cr storeString = 'Character cr'. self assert: Character lf storeString = 'Character lf'. self assert: Character space storeString = 'Character space'. self assert: (Character value: 0) storeString = '(Character value: 0)'. self assert: (Character value: 17) storeString = '(Character value: 17)'.! ! !CharacterTest methodsFor: 'testing-printing' stamp: 'lr 11/21/2005 17:24'! testStoreStringAll Character allCharacters do: [ :each | self assert: (self class compilerClass evaluate: each storeString) = each ].! ! ThreePhaseButtonMorph subclass: #CheckboxButtonMorph uses: TEnableOnHaloMenu instanceVariableNames: 'repressedImage enabled isRadioButton' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !CheckboxButtonMorph commentStamp: 'gvc 5/23/2007 12:19' prior: 0! Checkbox/radio - button only.! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 12/8/2008 19:17'! adoptPaneColor: paneColor "Pass on to the border too." super adoptPaneColor: paneColor. paneColor ifNil: [^self]. self fillStyle: self fillStyleToUse. self borderStyle: self borderStyleToUse. self cornerStyle: (self isRadioButton ifTrue: [self theme radioButtonCornerStyleFor: self] ifFalse: [self theme checkboxCornerStyleFor: self])! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 8/27/2009 11:54'! borderStyle: newStyle "Use narrowest image dimension." | newExtent | self borderStyle = newStyle ifTrue: [^self]. super borderStyle: newStyle. newExtent := 2 * newStyle width + image extent min asPoint. bounds extent = newExtent ifFalse: [self extent: newExtent]! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 11/5/2007 15:34'! borderWidth: bw "Use narrowest image dimension." | newExtent | super borderWidth: bw. newExtent := 2 * bw + image extent min asPoint. bounds extent = newExtent ifFalse: [super extent: newExtent]! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 16:04'! enabled "Answer the value of enabled" ^ enabled! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 7/30/2009 14:11'! enabled: anObject "Set the value of enabled" enabled = anObject ifTrue: [^self]. enabled := anObject. self changed: #enabled. self adoptPaneColor: self paneColor; changed! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 11/5/2007 15:28'! image: anImage "Fixed to take account of border width. Use narrowest dimanesion of image to allow a little flexibility." image := anImage depth = 1 ifTrue: [ColorForm mappingWhiteToTransparentFrom: anImage] ifFalse: [anImage]. self extent: 2 * self borderWidth + image extent min asPoint. self changed! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 10/25/2007 17:34'! isRadioButton "Answer the value of isRadioButton" ^ isRadioButton! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 10/25/2007 17:34'! isRadioButton: anObject "Set the value of isRadioButton" isRadioButton := anObject! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 15:17'! repressedImage "Answer the value of repressedImage" ^ repressedImage! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 15:18'! repressedImage: anObject "Set the value of repressedImage. This is shown when pressed after being off." repressedImage := anObject. self invalidRect: self bounds! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 10/25/2006 17:46'! selected "Answer the state taking account of the intermediate states." ^self state == #repressed or: [self state == #on]! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 18:00'! selected: aBoolean "Set the state taking account of the intermediate states." (self state == #pressed or: [self state == #repressed]) ifTrue: [self state: (aBoolean ifTrue: [#repressed] ifFalse: [#pressed])] ifFalse: [self state: (aBoolean ifTrue: [#on] ifFalse: [#off])]! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 16:41'! state "Answer the state." ^state! ! !CheckboxButtonMorph methodsFor: 'accessing' stamp: 'gvc 2/29/2008 21:53'! state: newState "Change the image and invalidate the rect." newState == state ifTrue: [^ self]. state := newState. self adoptPaneColor: self paneColor; changed! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified'! addToggleItemsToHaloMenu: aCustomMenu "Add toggle-items to the halo menu" super addToggleItemsToHaloMenu: aCustomMenu. aCustomMenu addUpdating: #enabledString target: self action: #toggleEnabled! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/8/2008 19:16'! beCheckbox "Change the images and square the border to be a checkbox." self isRadioButton: false; onImage: self theme checkboxMarkerForm; cornerStyle: (self theme checkboxCornerStyleFor: self); borderStyle: self borderStyleToUse! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/8/2008 19:16'! beRadioButton "Change the images and round the border to be a radio button." self isRadioButton: true; onImage: self theme radioButtonMarkerForm; cornerStyle: (self theme radioButtonCornerStyleFor: self); borderStyle: self borderStyleToUse! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/29/2008 22:05'! borderStyleToUse "Answer the borderStyle that should be used for the receiver." ^self isRadioButton ifTrue: [self radioBorderStyleToUse] ifFalse: [self checkboxBorderStyleToUse]! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/29/2008 22:05'! checkboxBorderStyleToUse "Answer the borderStyle that should be used for the receiver when it is a checkbox." ^self selected ifTrue: [self enabled ifTrue: [self theme checkboxButtonSelectedBorderStyleFor: self] ifFalse: [self theme checkboxButtonSelectedDisabledBorderStyleFor: self]] ifFalse: [self enabled ifTrue: [self theme checkboxButtonNormalBorderStyleFor: self] ifFalse: [self theme checkboxButtonDisabledBorderStyleFor: self]]! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/29/2008 22:04'! checkboxFillStyleToUse "Answer the fillStyle that should be used for the receiver when it is a checkbox." ^self selected ifTrue: [self enabled ifTrue: [self theme checkboxButtonSelectedFillStyleFor: self] ifFalse: [self theme checkboxButtonSelectedDisabledFillStyleFor: self]] ifFalse: [self enabled ifTrue: [self theme checkboxButtonNormalFillStyleFor: self] ifFalse: [self theme checkboxButtonDisabledFillStyleFor: self]]! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/23/2007 11:38'! colorToUse "Answer the color we should use." ^self paneColor! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/2/2007 14:16'! disable "Disable the receiver." self enabled: false! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/2/2007 14:16'! enable "Enable the receiver." self enabled: true! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified'! enabledString "Answer the string to be shown in a menu to represent the 'enabled' status" ^ (self enabled ifTrue: [''] ifFalse: ['']), 'enabled' translated! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/29/2008 21:56'! fillStyleToUse "Answer the fillStyle that should be used for the receiver." ^self isRadioButton ifTrue: [self radioFillStyleToUse] ifFalse: [self checkboxFillStyleToUse]! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/23/2007 11:46'! imageToUse "Answer the image we should use." ^state caseOf: { [#off] -> [self offImage]. [#pressed] -> [self pressedImage]. [#on] -> [self onImage]. [#repressed] -> [self repressedImage ifNil: [self onImage]]} otherwise: []! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/29/2008 22:04'! radioBorderStyleToUse "Answer the borderStyle that should be used for the receiver when it is a radio button." ^self selected ifTrue: [self enabled ifTrue: [self theme radioButtonSelectedBorderStyleFor: self] ifFalse: [self theme radioButtonSelectedDisabledBorderStyleFor: self]] ifFalse: [self enabled ifTrue: [self theme radioButtonNormalBorderStyleFor: self] ifFalse: [self theme radioButtonDisabledBorderStyleFor: self]]! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/29/2008 21:58'! radioFillStyleToUse "Answer the fillStyle that should be used for the receiver when it is a radio button." ^self selected ifTrue: [self enabled ifTrue: [self theme radioButtonSelectedFillStyleFor: self] ifFalse: [self theme radioButtonSelectedDisabledFillStyleFor: self]] ifFalse: [self enabled ifTrue: [self theme radioButtonNormalFillStyleFor: self] ifFalse: [self theme radioButtonDisabledFillStyleFor: self]]! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/8/2008 19:17'! themeChanged "Update the on image." self onImage: (self isRadioButton ifTrue: [self theme radioButtonMarkerForm] ifFalse: [self theme checkboxMarkerForm]). self adoptPaneColor: self paneColor. super themeChanged! ! !CheckboxButtonMorph methodsFor: 'as yet unclassified'! toggleEnabled "Toggle the enabled state." self enabled: self enabled not! ! !CheckboxButtonMorph methodsFor: 'drawing' stamp: 'gvc 5/23/2007 11:48'! drawOn: aCanvas "Draw the image for the current state." |img| aCanvas fillRectangle: self bounds fillStyle: self fillStyle borderStyle: self borderStyle. img := self imageToUse. img ifNotNil: [ aCanvas translucentImage: img at: self innerBounds center - (img extent // 2)]. (self state == #pressed or: [self state == #repressed]) ifTrue: [ aCanvas fillRectangle: self innerBounds fillStyle: (self paneColor alpha: 0.3)]. self enabled ifFalse: [aCanvas fillRectangle: self innerBounds fillStyle: (self paneColor alpha: 0.4)]! ! !CheckboxButtonMorph methodsFor: 'event handling' stamp: 'gvc 9/18/2006 13:40'! mouseDown: evt "Handle the transitions." self enabled ifFalse: [^self perform: #mouseDown: withArguments: {evt} inSuperclass: Morph]. self isOn ifTrue: [self state: #repressed] ifFalse: [self state: #pressed]. actWhen == #buttonDown ifTrue: [self doButtonAction]. self mouseStillDown: evt.! ! !CheckboxButtonMorph methodsFor: 'event handling' stamp: 'gvc 8/17/2006 16:34'! mouseMove: evt "Check for straying." self enabled ifFalse: [^self perform: #mouseMove: withArguments: {evt} inSuperclass: Morph]. (self containsPoint: evt cursorPoint) ifTrue: [state == #on ifTrue: [self state: #repressed]. state == #off ifTrue: [self state: #pressed]. self perform: #mouseMove: withArguments: {evt} inSuperclass: Morph] "Allow on:send:to: to set the response to events other than actWhen" ifFalse: [state == #repressed ifTrue: [self state: #on]. state == #pressed ifTrue: [self state: #off]]. ! ! !CheckboxButtonMorph methodsFor: 'event handling' stamp: 'gvc 8/17/2006 16:35'! mouseUp: evt "Allow on:send:to: to set the response to events other than actWhen" self enabled ifFalse: [^self perform: #mouseUp: withArguments: {evt} inSuperclass: Morph]. actWhen == #buttonUp ifFalse: [^self perform: #mouseUp: withArguments: {evt} inSuperclass: Morph]. (self containsPoint: evt cursorPoint) ifTrue: [state == #repressed ifTrue: [self state: #off] ifFalse: [self state: #on]. self doButtonAction: evt] ifFalse: [target ifNotNil: [target mouseUpBalk: evt]]. ^self perform: #mouseDown: withArguments: {evt} inSuperclass: Morph! ! !CheckboxButtonMorph methodsFor: 'initialization' stamp: 'gvc 10/25/2007 17:36'! initialize "Initialize the receiver." super initialize. self isRadioButton: false; enabled: true; onImage: self theme checkboxMarkerForm; fillStyle: self fillStyleToUse; borderStyle: self borderStyleToUse! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CheckboxButtonMorph class uses: TEnableOnHaloMenu classTrait instanceVariableNames: ''! !CheckboxButtonMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 5/22/2007 15:21'! checkBox "Answer a button pre-initialized with checkbox images." ^self new beCheckbox! ! !CheckboxButtonMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 5/22/2007 15:21'! radioButton "Answer a button pre-initialized with radio button images." ^self new beRadioButton! ! MorphicModel subclass: #CheckboxMorph uses: TEnableOnHaloMenu instanceVariableNames: 'buttonMorph labelMorph setStateSelector getStateSelector enabled getEnabledSelector' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !CheckboxMorph commentStamp: 'gvc 5/18/2007 13:47' prior: 0! Checkbox with box button and label with enablement support.! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 14:49'! buttonMorph "Answer the value of buttonMorph" ^ buttonMorph! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/2/2007 16:11'! buttonMorph: aMorph "Set the value of buttonMorph" buttonMorph ifNotNil: [ self removeDependent: buttonMorph. buttonMorph delete]. buttonMorph := aMorph. self addDependent: aMorph; addMorphFront: aMorph! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 14:49'! enabled "Answer the value of enabled" ^ enabled! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/2/2007 16:06'! enabled: aBoolean "Set the value of enabled" enabled := aBoolean. self labelMorph ifNotNilDo: [:m | (m respondsTo: #enabled:) ifTrue: [ m enabled: aBoolean]]. self buttonMorph ifNotNilDo: [:m | m enabled: aBoolean]. self changed: #enabled! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 9/8/2006 14:58'! font "Answer the label font" ^self labelMorph font! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 9/8/2006 14:58'! font: aFont "Set the label font" self labelMorph font: aFont! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 15:05'! getEnabledSelector "Answer the value of getEnabledSelector" ^ getEnabledSelector! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 18:01'! getEnabledSelector: anObject "Set the value of getEnabledSelector" getEnabledSelector := anObject. self updateEnabled! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 14:49'! getStateSelector "Answer the value of getStateSelector" ^ getStateSelector! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 18:02'! getStateSelector: anObject "Set the value of getStateSelector" getStateSelector := anObject. self updateSelection! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/2/2007 16:14'! label "Answer the contents of the label morph." ^(self labelMorph ifNil: [^'']) contents! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/2/2007 16:13'! label: aString "Set the contents of the label morph." self labelMorph contents: aString. self labelMorph: self newLabel! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 14:49'! labelMorph "Answer the value of labelMorph" ^ labelMorph! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/2/2007 16:09'! labelMorph: aMorph "Set the value of labelMorph" labelMorph ifNotNil: [labelMorph delete]. labelMorph := aMorph. self addMorphBack: aMorph! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 15:00'! setStateSelector "Answer the value of setStateSelector" ^ setStateSelector! ! !CheckboxMorph methodsFor: 'accessing' stamp: 'gvc 8/17/2006 15:00'! setStateSelector: anObject "Set the value of setStateSelector" setStateSelector := anObject! ! !CheckboxMorph methodsFor: 'as yet unclassified'! addToggleItemsToHaloMenu: aCustomMenu "Add toggle-items to the halo menu" super addToggleItemsToHaloMenu: aCustomMenu. aCustomMenu addUpdating: #enabledString target: self action: #toggleEnabled! ! !CheckboxMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/22/2007 15:38'! beCheckbox "Change the button to be a checkbox." self buttonMorph beCheckbox! ! !CheckboxMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/22/2007 15:38'! beRadioButton "Change the button to be a radio button." self buttonMorph beRadioButton! ! !CheckboxMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/2/2007 11:38'! disable "Disable the receiver." self enabled: false! ! !CheckboxMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/2/2007 11:38'! enable "Enable the receiver." self enabled: true! ! !CheckboxMorph methodsFor: 'as yet unclassified'! enabledString "Answer the string to be shown in a menu to represent the 'enabled' status" ^ (self enabled ifTrue: [''] ifFalse: ['']), 'enabled' translated! ! !CheckboxMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/17/2006 15:14'! isSelected "Answer whether the receiver is selected." self model ifNil: [^false]. ^self model perform: (self getStateSelector ifNil: [^false])! ! !CheckboxMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/17/2006 18:03'! newButtonMorph "Answer a new button morph" ^CheckboxButtonMorph new target: self; actionSelector: #toggleSelected; vResizing: #shrinkWrap; hResizing: #shrinkWrap! ! !CheckboxMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/2/2007 16:13'! newLabel "Answer a new label morph" ^self theme checkboxLabelFor: self! ! !CheckboxMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/2/2007 16:14'! newLabelMorph "Answer a new label morph" ^self theme checkboxLabelFor: self! ! !CheckboxMorph methodsFor: 'as yet unclassified'! toggleEnabled "Toggle the enabled state." self enabled: self enabled not! ! !CheckboxMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/25/2006 14:35'! toggleSelected "Toggle the selection state." self enabled ifFalse: [^self]. self model ifNil: [^self]. (self setStateSelector ifNil: [^self]) numArgs = 0 ifTrue: [self model perform: self setStateSelector]. self setStateSelector numArgs = 1 ifTrue: [ self model perform: self setStateSelector with: self isSelected not]. self updateSelection ! ! !CheckboxMorph methodsFor: 'drawing' stamp: 'gvc 5/22/2007 16:04'! drawSubmorphsOn: aCanvas "Display submorphs back to front. Draw the focus here since we are using inset bounds for the focus rectangle." super drawSubmorphsOn: aCanvas. self hasKeyboardFocus ifTrue: [self drawKeyboardFocusOn: aCanvas]! ! !CheckboxMorph methodsFor: 'event handling' stamp: 'gvc 1/16/2007 15:20'! handlesKeyboard: evt "Yes, we do it here." ^true! ! !CheckboxMorph methodsFor: 'event handling' stamp: 'gvc 5/22/2007 16:11'! keyStroke: event "Process keys navigation and space to toggle." (self navigationKey: event) ifTrue: [^self]. event keyCharacter = Character space ifTrue: [self toggleSelected]! ! !CheckboxMorph methodsFor: 'event handling' stamp: 'gvc 9/6/2007 14:37'! keyboardFocusChange: aBoolean "The message is sent to a morph when its keyboard focus changes. Update for focus feedback." self focusChanged! ! !CheckboxMorph methodsFor: 'focus handling' stamp: 'gvc 1/11/2007 12:28'! takesKeyboardFocus "Answer whether the receiver can normally take keyboard focus." ^true! ! !CheckboxMorph methodsFor: 'initialization' stamp: 'gvc 8/2/2007 16:11'! initialize "Initialize the receiver." super initialize. self borderWidth: 2; "space for focus" borderColor: Color transparent; enabled: true; changeTableLayout; listDirection: #leftToRight; wrapCentering: #center; cellInset: 8; buttonMorph: self newButtonMorph; labelMorph: self newLabelMorph; on: #mouseDown send: #updateButton: to: self; on: #mouseMove send: #updateButton: to: self; on: #mouseUp send: #updateButton: to: self! ! !CheckboxMorph methodsFor: 'initialization' stamp: 'gvc 8/17/2006 18:01'! on: anObject selected: getSelectionSel changeSelected: setSelectionSel "Set the receiver to the given model parameterized by the given message selectors." self model: anObject; getStateSelector: getSelectionSel; setStateSelector: setSelectionSel; updateSelection! ! !CheckboxMorph methodsFor: 'updating' stamp: 'gvc 8/17/2006 17:58'! update: aSymbol "Refer to the comment in View|update:." aSymbol == self getStateSelector ifTrue: [self updateSelection. ^ self]. aSymbol == self getEnabledSelector ifTrue: [self updateEnabled. ^ self]! ! !CheckboxMorph methodsFor: 'updating' stamp: 'gvc 8/17/2006 18:06'! updateButton: evt "Update the button due to mouse activity in the receiver." self enabled ifFalse: [^self]. evt isMouseDown ifTrue: [ self buttonMorph state == #on ifTrue: [^self buttonMorph state: #repressed]. self buttonMorph state == #off ifTrue: [^self buttonMorph state: #pressed]]. evt isMouseUp ifTrue: [ self buttonMorph state == #repressed ifTrue: [ ^self buttonMorph state: #off; doButtonAction]. self buttonMorph state == #pressed ifTrue: [ ^self buttonMorph state: #on; doButtonAction]]. evt isMove ifTrue: [ (self containsPoint: evt cursorPoint) ifTrue: [self buttonMorph state == #on ifTrue: [^self buttonMorph state: #repressed]. self buttonMorph state == #off ifTrue: [^self buttonMorph state: #pressed]] ifFalse: [self buttonMorph state == #repressed ifTrue: [^self buttonMorph state: #on]. self buttonMorph state == #pressed ifTrue: [^self buttonMorph state: #off]]]! ! !CheckboxMorph methodsFor: 'updating' stamp: 'gvc 9/8/2009 13:25'! updateEnabled "Update the enablement state." self model ifNotNil: [ self getEnabledSelector ifNotNil: [ self enabled: (self model perform: self getEnabledSelector)]]! ! !CheckboxMorph methodsFor: 'updating' stamp: 'gvc 8/17/2006 17:58'! updateSelection "Update the selection state." self buttonMorph ifNotNilDo: [:m | m selected: self isSelected]. self changed: #isSelected! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CheckboxMorph class uses: TEnableOnHaloMenu classTrait instanceVariableNames: ''! !CheckboxMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 8/17/2006 16:50'! on: anObject selected: getSelectionSel changeSelected: setSelectionSel "Answer a new instance of the receiver on the given model using the given selectors as the interface." ^self new on: anObject selected: getSelectionSel changeSelected: setSelectionSel! ! MessageDialogWindow subclass: #ChooseDropListDialogWindow instanceVariableNames: 'listMorph list' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !ChooseDropListDialogWindow commentStamp: 'gvc 5/18/2007 13:46' prior: 0! Message dialog containing a drop list for selection of an item.! !ChooseDropListDialogWindow methodsFor: 'accessing' stamp: 'gvc 1/12/2007 14:15'! list "Answer the value of list" ^ list! ! !ChooseDropListDialogWindow methodsFor: 'accessing' stamp: 'gvc 1/12/2007 15:21'! list: anObject "Set the value of list" list := anObject. self changed: #list; changed: #selectionIndex! ! !ChooseDropListDialogWindow methodsFor: 'accessing' stamp: 'gvc 1/12/2007 14:17'! listMorph "Answer the value of listMorph" ^ listMorph! ! !ChooseDropListDialogWindow methodsFor: 'accessing' stamp: 'gvc 1/12/2007 14:17'! listMorph: anObject "Set the value of listMorph" listMorph := anObject! ! !ChooseDropListDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/18/2007 10:27'! icon "Answer an icon for the receiver." ^self theme questionIcon! ! !ChooseDropListDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/12/2007 14:35'! initialize "Initialize the receiver." self list: #(). super initialize! ! !ChooseDropListDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/29/2007 13:32'! newContentMorph "Answer a new content morph." self iconMorph: self newIconMorph. self textMorph: self newTextMorph. self listMorph: self newListMorph. ^self newGroupboxForAll: { self newRow: {self iconMorph. self textMorph}. self listMorph}! ! !ChooseDropListDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/12/2007 14:17'! newListMorph "Answer a new drop-list morph." ^self newDropListFor: self list: #list getSelected: #selectionIndex setSelected: nil getEnabled: nil help: nil! ! !ChooseDropListDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/12/2007 14:22'! selectedItem "Answer the selected list item or nil if cancelled." ^self cancelled ifFalse: [self listMorph selectedItem]! ! !ChooseDropListDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/12/2007 14:15'! selectionIndex "Answer the initial selection index for the list." ^self list ifEmpty: [0] ifNotEmpty: [1]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ChooseDropListDialogWindow class instanceVariableNames: ''! !ChooseDropListDialogWindow class methodsFor: 'as yet unclassified' stamp: 'gvc 5/22/2007 11:50'! taskbarIcon "Answer the icon for the receiver in a task bar." ^self theme smallQuestionIcon! ! SharedPool subclass: #ChronologyConstants instanceVariableNames: '' classVariableNames: 'DayNames DaysInMonth MonthNames NanosInMillisecond NanosInSecond SecondsInDay SecondsInHour SecondsInMinute SqueakEpoch' poolDictionaries: '' category: 'Kernel-Chronology'! !ChronologyConstants commentStamp: 'brp 3/12/2004 14:34' prior: 0! ChronologyConstants is a SharedPool for the constants used by the Kernel-Chronology classes.! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ChronologyConstants class instanceVariableNames: ''! !ChronologyConstants class methodsFor: 'class initialization' stamp: 'brp 9/25/2003 10:49'! initialize "ChronologyConstants initialize" SqueakEpoch := 2415386. "Julian day number of 1 Jan 1901" SecondsInDay := 86400. SecondsInHour := 3600. SecondsInMinute := 60. NanosInSecond := 10 raisedTo: 9. NanosInMillisecond := 10 raisedTo: 6. DayNames := #(Sunday Monday Tuesday Wednesday Thursday Friday Saturday). MonthNames := #(January February March April May June July August September October November December). DaysInMonth := #(31 28 31 30 31 30 31 31 30 31 30 31). ! ! Arc subclass: #Circle instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ST80-Paths'! !Circle commentStamp: '' prior: 0! I represent a full circle. I am made from four Arcs.! !Circle methodsFor: 'display box access'! computeBoundingBox ^center - radius + form offset extent: form extent + (radius * 2) asPoint! ! !Circle methodsFor: 'displaying'! displayOn: aDisplayMedium at: aPoint clippingBox: clipRect rule: anInteger fillColor: aForm 1 to: 4 do: [:i | super quadrant: i. super displayOn: aDisplayMedium at: aPoint clippingBox: clipRect rule: anInteger fillColor: aForm]! ! !Circle methodsFor: 'displaying'! displayOn: aDisplayMedium transformation: aTransformation clippingBox: clipRect rule: anInteger fillColor: aForm 1 to: 4 do: [:i | super quadrant: i. super displayOn: aDisplayMedium transformation: aTransformation clippingBox: clipRect rule: anInteger fillColor: aForm]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Circle class instanceVariableNames: ''! !Circle class methodsFor: 'examples'! exampleOne "Click any button somewhere on the screen. The point will be the center of the circcle of radius 150." | aCircle aForm | aForm := Form extent: 1@30. aForm fillBlack. aCircle := Circle new. aCircle form: aForm. aCircle radius: 150. aCircle center: Sensor waitButton. aCircle displayOn: Display "Circle exampleOne"! ! !Circle class methodsFor: 'examples'! exampleTwo "Designate a rectangular area that should be used as the brush for displaying the circle. Click any button at a point on the screen which will be the center location for the circle. The curve will be displayed with a long black form." | aCircle aForm | aForm := Form fromUser. aCircle := Circle new. aCircle form: aForm. aCircle radius: 150. aCircle center: Sensor waitButton. aCircle displayOn: Display at: 0 @ 0 rule: Form reverse "Circle exampleTwo"! ! EllipseMorph subclass: #CircleMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Basic'! !CircleMorph commentStamp: '' prior: 0! I am a specialization of EllipseMorph that knows enough to remain circular. ! !CircleMorph methodsFor: 'geometry' stamp: 'nk 7/1/2002 07:01'! bounds: aRectangle | size | size := aRectangle width min: aRectangle height. super bounds: (Rectangle origin: aRectangle origin extent: size @ size).! ! !CircleMorph methodsFor: 'geometry' stamp: 'nk 7/1/2002 16:39'! extent: aPoint | size oldRotationCenter | oldRotationCenter := self rotationCenter. size := aPoint x min: aPoint y. super extent: size @ size. self rotationCenter: oldRotationCenter.! ! !CircleMorph methodsFor: 'geometry' stamp: 'nk 7/1/2002 08:49'! transformedBy: aTransform aTransform isIdentity ifTrue:[^self]. ^self center: (aTransform localPointToGlobal: self center). ! ! !CircleMorph methodsFor: 'geometry etoy' stamp: 'nk 7/1/2002 07:12'! heading: newHeading "Set the receiver's heading (in eToy terms). Note that circles never use flex shells." self rotationDegrees: newHeading.! ! !CircleMorph methodsFor: 'geometry etoy' stamp: 'nk 7/1/2002 07:31'! referencePosition "Return the current reference position of the receiver" ^ self valueOfProperty: #referencePosition ifAbsent: [ self center ] ! ! !CircleMorph methodsFor: 'geometry etoy' stamp: 'nk 7/1/2002 11:16'! rotationCenter "Return the rotation center of the receiver. The rotation center defines the relative offset inside the receiver's bounds for locating the reference position." | refPos | refPos := self referencePosition. ^ (refPos - self bounds origin) / self bounds extent asFloatPoint! ! !CircleMorph methodsFor: 'geometry etoy' stamp: 'nk 7/1/2002 13:48'! rotationCenter: aPointOrNil "Set the new rotation center of the receiver. The rotation center defines the relative offset inside the receiver's bounds for locating the reference position." | newRef box | aPointOrNil isNil ifTrue: [self removeProperty: #referencePosition. self removeProperty: #originalCenter. self removeProperty: #originalAngle. ] ifFalse: [ box := self bounds. newRef := box origin + (aPointOrNil * box extent). self setRotationCenterFrom: newRef ]. ! ! !CircleMorph methodsFor: 'menus' stamp: 'nk 7/1/2002 11:30'! setRotationCenterFrom: aPoint "Called by halo rotation code. Circles store their referencePosition." self setProperty: #referencePosition toValue: aPoint. self setProperty: #originalCenter toValue: self center. self setProperty: #originalAngle toValue: self heading.! ! !CircleMorph methodsFor: 'parts bin' stamp: 'alain.plantec 5/28/2009 09:46'! initialize super initialize. self extent: 40@40; color: Color green lighter; yourself! ! !CircleMorph methodsFor: 'parts bin' stamp: 'nk 7/1/2002 16:42'! initializeToStandAlone ^super initializeToStandAlone extent: 40@40; color: Color green lighter; yourself! ! !CircleMorph methodsFor: 'rotate scale and flex' stamp: 'nk 7/1/2002 07:04'! addFlexShellIfNecessary "When scaling or rotating from a halo, I can do this without a flex shell" ^ self ! ! !CircleMorph methodsFor: 'rotate scale and flex' stamp: 'nk 7/1/2002 16:29'! privateMoveBy: delta self setProperty: #referencePosition toValue: self referencePosition + delta. self setProperty: #originalCenter toValue: (self valueOfProperty: #originalCenter ifAbsent: [ self center ]) + delta. super privateMoveBy: delta. ! ! !CircleMorph methodsFor: 'rotate scale and flex' stamp: 'nk 7/1/2002 07:28'! rotationDegrees ^ self forwardDirection! ! !CircleMorph methodsFor: 'rotate scale and flex' stamp: 'nk 7/1/2002 15:52'! rotationDegrees: degrees | ref newPos flex origAngle origCenter | ref := self referencePosition. origAngle := self valueOfProperty: #originalAngle ifAbsentPut: [ self heading ]. origCenter := self valueOfProperty: #originalCenter ifAbsentPut: [ self center ]. flex := (MorphicTransform offset: ref negated) withAngle: (degrees - origAngle) degreesToRadians. newPos := (flex transform: origCenter) - flex offset. self position: (self position + newPos - self center) asIntegerPoint. self setProperty: #referencePosition toValue: ref. self setProperty: #originalAngle toValue: origAngle. self setProperty: #originalCenter toValue: origCenter. self forwardDirection: degrees. self changed. ! ! TestCase subclass: #CircleMorphBugs instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Bugs'! !CircleMorphBugs methodsFor: 'as yet unclassified' stamp: 'wiz 4/18/2007 00:57'! testCircleInstance "" "self run: #testCircleInstance" | circ | self assert: (circ := CircleMorph initializedInstance) extent = circ extent x asPoint ! ! MorphTest subclass: #CircleMorphTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'MorphicTests-Basic'! !CircleMorphTest commentStamp: 'tlk 5/21/2006 14:16' prior: 0! A CircleMorphTest is a subclass of MorphTest. It was first implemented when removing some unused and broken functionality. My fixtures are morph, a CircleMorph and world. ! !CircleMorphTest methodsFor: 'initialization' stamp: 'tlk 5/21/2006 14:17'! setUp morph := CircleMorph new! ! ClassDescription subclass: #Class uses: TBehaviorCategorization instanceVariableNames: 'subclasses name classPool sharedPools environment category traitComposition localSelectors' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Classes'! !Class commentStamp: '' prior: 0! I add a number of facilities to those in ClassDescription: A set of all my subclasses (defined in ClassDescription, but only used here and below) A name by which I can be found in a SystemDictionary A classPool for class variables shared between this class and its metaclass A list of sharedPools which probably should be supplanted by some better mechanism. 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. The slot 'subclasses' is a redundant structure. It is never used during execution, but is used by the development system to simplify or speed certain operations. ! !Class methodsFor: '*monticello' stamp: 'al 3/26/2006 21:31'! asClassDefinition ^ MCClassDefinition name: self name superclassName: self superclass name traitComposition: self traitCompositionString classTraitComposition: self class traitCompositionString category: self category instVarNames: self instVarNames classVarNames: self classVarNames poolDictionaryNames: self poolDictionaryNames classInstVarNames: self class instVarNames type: self typeOfClass comment: self organization classComment asString commentStamp: self organization commentStamp ! ! !Class methodsFor: '*monticello' stamp: 'avi 3/10/2004 13:32'! classDefinitions ^ Array with: self asClassDefinition! ! !Class methodsFor: '*monticello' stamp: 'ab 4/14/2003 22:30'! poolDictionaryNames ^ self sharedPools collect: [:ea | self environment keyAtIdentityValue: ea]! ! !Class methodsFor: 'accessing' stamp: 'al 3/18/2006 13:23'! basicCategory ^category! ! !Class methodsFor: 'accessing' stamp: 'al 3/18/2006 13:23'! basicCategory: aSymbol category := aSymbol! ! !Class methodsFor: 'accessing' stamp: 'al 3/25/2006 13:16'! basicLocalSelectors "Direct accessor for the instance variable localSelectors. Since localSelectors is lazily initialized, this may return nil, which means that all selectors are local." ^ localSelectors! ! !Class methodsFor: 'accessing' stamp: 'al 3/25/2006 13:16'! basicLocalSelectors: aSetOrNil localSelectors := aSetOrNil! ! !Class methodsFor: 'accessing'! classPool "Answer the dictionary of class variables." classPool == nil ifTrue: [^Dictionary new] ifFalse: [^classPool]! ! !Class methodsFor: 'accessing' stamp: 'BG 8/11/2002 20:53'! classPoolFrom: aClass "share the classPool with aClass." classPool := aClass classPool! ! !Class methodsFor: 'accessing' stamp: 'al 9/3/2004 13:37'! classPool: aDictionary classPool := aDictionary! ! !Class methodsFor: 'accessing' stamp: 'al 3/25/2006 12:38'! hasTraitComposition ^traitComposition notNil! ! !Class methodsFor: 'accessing'! name "Answer the name of the receiver." name == nil ifTrue: [^super name] ifFalse: [^name]! ! !Class methodsFor: 'accessing' stamp: 'al 3/25/2006 12:35'! traitComposition traitComposition ifNil: [traitComposition := TraitComposition new]. ^traitComposition! ! !Class methodsFor: 'accessing' stamp: 'al 3/25/2006 12:37'! traitComposition: aTraitComposition traitComposition := aTraitComposition! ! !Class methodsFor: 'accessing class hierarchy' stamp: 'tk 10/17/1999 13:31'! addSubclass: aSubclass "Make the argument, aSubclass, be one of the subclasses of the receiver. Create an error notification if the argument's superclass is not the receiver." aSubclass superclass ~~ self ifTrue: [^self error: aSubclass name , ' is not my subclass']. subclasses == nil ifTrue: [subclasses := Array with: aSubclass. ^self]. subclasses do:[:cl| cl == aSubclass ifTrue:[^self]]. "Already my subclass" subclasses := subclasses copyWith: aSubclass.! ! !Class methodsFor: 'accessing class hierarchy' stamp: 'ar 7/14/1999 10:54'! removeSubclass: aSubclass "If the argument, aSubclass, is one of the receiver's subclasses, remove it." subclasses == nil ifFalse: [subclasses := subclasses copyWithout: aSubclass. subclasses isEmpty ifTrue: [subclasses := nil]]. ! ! !Class methodsFor: 'accessing class hierarchy' stamp: 'ar 7/14/1999 11:00'! subclasses "Answer a Set containing the receiver's subclasses." ^subclasses == nil ifTrue: [#()] ifFalse: [subclasses copy]! ! !Class methodsFor: 'accessing class hierarchy' stamp: 'tk 8/18/1999 17:42'! subclassesDoGently: aBlock "Evaluate the argument, aBlock, for each of the receiver's immediate subclasses." subclasses == nil ifFalse: [subclasses do: aBlock]! ! !Class methodsFor: 'accessing class hierarchy' stamp: 'ar 7/14/1999 11:00'! subclassesDo: aBlock "Evaluate the argument, aBlock, for each of the receiver's immediate subclasses." subclasses == nil ifFalse:[subclasses do: aBlock]! ! !Class methodsFor: 'class name' stamp: 'sw 12/1/2000 20:39'! externalName "Answer a name by which the receiver can be known." ^ name! ! !Class methodsFor: 'class name' stamp: 'sw 12/18/2000 15:50'! nameForViewer "Answer the name to be shown in the header of a viewer looking at the receiver" ^ self name ifNil: ['Unnamed class']! ! !Class methodsFor: 'class name' stamp: 'rw 10/7/2006 08:30'! rename: aString "The new name of the receiver is the argument, aString." | oldName newName | (newName := aString asSymbol) = (oldName := self name) ifTrue: [^ self]. (self environment includesKey: newName) ifTrue: [^ self error: newName , ' already exists']. (Undeclared includesKey: newName) ifTrue: [self inform: 'There are references to, ' , aString printString , ' from Undeclared. Check them after this change.']. name := newName. self environment renameClass: self from: oldName! ! !Class methodsFor: 'class variables' stamp: 'dvf 9/27/2005 17:32'! addClassVarName: aString "Add the argument, aString, as a class variable of the receiver. Signal an error if the first character of aString is not capitalized, or if it is already a variable named in the class." | symbol oldState | oldState := self copy. aString first canBeGlobalVarInitial ifFalse: [^self error: aString, ' class variable name should be capitalized; proceed to include anyway.']. symbol := aString asSymbol. self withAllSubclasses do: [:subclass | (subclass bindingOf: symbol) ifNotNil:[ ^ self error: aString , ' is already used as a variable name in class ' , subclass name]]. classPool == nil ifTrue: [classPool := Dictionary new]. (classPool includesKey: symbol) ifFalse: ["Pick up any refs in Undeclared" classPool declare: symbol from: Undeclared. SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: oldState to: self]! ! !Class methodsFor: 'class variables' stamp: 'al 9/3/2004 14:25'! allClassVarNames "Answer a Set of the names of the receiver's class variables, including those defined in the superclasses of the receiver." | aSet | self superclass == nil ifTrue: [^self classVarNames] "This is the keys so it is a new Set." ifFalse: [aSet := self superclass allClassVarNames. aSet addAll: self classVarNames. ^aSet]! ! !Class methodsFor: 'class variables' stamp: 'al 9/3/2004 14:25'! classVarNames "Answer a Set of the names of the class variables defined in the receiver." ^self classPool keys! ! !Class methodsFor: 'class variables' stamp: 'tk 3/15/98 20:19'! ensureClassPool classPool ifNil: [classPool := Dictionary new].! ! !Class methodsFor: 'class variables' stamp: 'bf 1/12/2006 10:44'! removeClassVarName: aString "Remove the class variable whose name is the argument, aString, from the names defined in the receiver, a class. Create an error notification if aString is not a class variable or if it is still being used in the code of the class." | aSymbol | aSymbol := aString asSymbol. (classPool includesKey: aSymbol) ifFalse: [^self error: aString, ' is not a class variable']. self withAllSubclasses do:[:subclass | (Array with: subclass with: subclass class) do:[:classOrMeta | (classOrMeta whichSelectorsReferTo: (classPool associationAt: aSymbol)) isEmpty ifFalse: [ InMidstOfFileinNotification signal ifTrue: [ Transcript cr; show: self name, ' (' , aString , ' is Undeclared) '. ^Undeclared declare: aSymbol from: classPool]. (self confirm: (aString,' is still used in code of class ', classOrMeta name, '.\Is it okay to move it to Undeclared?') withCRs) ifTrue:[^Undeclared declare: aSymbol from: classPool] ifFalse:[^self]]]]. classPool removeKey: aSymbol. classPool isEmpty ifTrue: [classPool := nil]. ! ! !Class methodsFor: 'compiling' stamp: 'md 3/5/2006 23:47'! binding ^ Smalltalk associationAt: name ifAbsent: [nil -> self] ! ! !Class methodsFor: 'compiling' stamp: 'ar 5/17/2003 14:06'! bindingOf: varName "Answer the binding of some variable resolved in the scope of the receiver" | aSymbol binding | aSymbol := varName asSymbol. "First look in classVar dictionary." binding := self classPool bindingOf: aSymbol. binding ifNotNil:[^binding]. "Next look in shared pools." self sharedPools do:[:pool | binding := pool bindingOf: aSymbol. binding ifNotNil:[^binding]. ]. "Next look in declared environment." binding := self environment bindingOf: aSymbol. binding ifNotNil:[^binding]. "Finally look higher up the superclass chain and fail at the end." superclass == nil ifTrue: [^ nil] ifFalse: [^ superclass bindingOf: aSymbol]. ! ! !Class methodsFor: 'compiling' stamp: 'ar 5/17/2003 14:13'! canFindWithoutEnvironment: varName "This method is used for analysis of system structure -- see senders." "Look up varName, in the context of the receiver. Return true if it can be found without using the declared environment." "First look in classVar dictionary." (self classPool bindingOf: varName) ifNotNil:[^true]. "Next look in shared pools." self sharedPools do:[:pool | (pool bindingOf: varName) ifNotNil:[^true]. ]. "Finally look higher up the superclass chain and fail at the end." superclass == nil ifTrue: [^ false] ifFalse: [^ (superclass bindingOf: varName) notNil]. ! ! !Class methodsFor: 'compiling' stamp: 'ar 7/14/1999 04:56'! compileAll super compileAll. self class compileAll.! ! !Class methodsFor: 'compiling'! compileAllFrom: oldClass "Recompile all the methods in the receiver's method dictionary (not the subclasses). Also recompile the methods in the metaclass." super compileAllFrom: oldClass. self class compileAllFrom: oldClass class! ! !Class methodsFor: 'compiling' stamp: 'sd 3/28/2003 15:24'! possibleVariablesFor: misspelled continuedFrom: oldResults | results | results := misspelled correctAgainstDictionary: self classPool continuedFrom: oldResults. self sharedPools do: [:pool | results := misspelled correctAgainstDictionary: pool continuedFrom: results ]. superclass == nil ifTrue: [ ^ misspelled correctAgainstDictionary: self environment continuedFrom: results ] ifFalse: [ ^ superclass possibleVariablesFor: misspelled continuedFrom: results ]! ! !Class methodsFor: 'copying' stamp: 'di 2/17/2000 22:43'! copy | newClass | newClass := self class copy new superclass: superclass methodDict: self methodDict copy format: format name: name organization: self organization copy instVarNames: instanceVariables copy classPool: classPool copy sharedPools: sharedPools. Class instSize+1 to: self class instSize do: [:offset | newClass instVarAt: offset put: (self instVarAt: offset)]. ^ newClass! ! !Class methodsFor: 'copying' stamp: 'marcus.denker 8/19/2008 21:09'! duplicateClassWithNewName: aSymbol | copysName class newDefinition | copysName := aSymbol asSymbol. copysName = self name ifTrue: [^ self]. (Smalltalk includesKey: copysName) ifTrue: [^ self error: copysName , ' already exists']. newDefinition := self definition copyReplaceAll: '#' , self name asString with: '#' , copysName asString. class := Compiler evaluate: newDefinition logged: true. class class instanceVariableNames: self class instanceVariablesString. class copyAllCategoriesFrom: self. class class copyAllCategoriesFrom: self class. ^class! ! !Class methodsFor: 'fileIn/Out' stamp: 'PeterHugossonMiller 9/3/2009 00:53'! fileOut "Create a file whose name is the name of the receiver with '.st' as the extension, and file a description of the receiver onto it." | internalStream | internalStream := (String new: 100) writeStream. internalStream header; timeStamp. self hasSharedPools ifTrue: [ self shouldFileOutPools ifTrue: [self fileOutSharedPoolsOn: internalStream]]. self fileOutOn: internalStream moveSource: false toFile: 0. internalStream trailer. FileStream writeSourceCodeFrom: internalStream baseName: self name isSt: true! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:00'! fileOutInitializerOn: aStream ^self class fileOutInitializerOn: aStream! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:04'! fileOutOn: aFileStream moveSource: moveSource toFile: fileIndex "File a description of the receiver on aFileStream. If the boolean argument, moveSource, is true, then set the trailing bytes to the position of aFileStream and to fileIndex in order to indicate where to find the source code." ^self fileOutOn: aFileStream moveSource: moveSource toFile: fileIndex initializing: true! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:04'! fileOutOn: aFileStream moveSource: moveSource toFile: fileIndex initializing: aBool "File a description of the receiver on aFileStream. If the boolean argument, moveSource, is true, then set the trailing bytes to the position of aFileStream and to fileIndex in order to indicate where to find the source code." Transcript cr; show: self name. super fileOutOn: aFileStream moveSource: moveSource toFile: fileIndex. self class nonTrivial ifTrue: [aFileStream cr; nextPutAll: '"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!!'; cr; cr. self class fileOutOn: aFileStream moveSource: moveSource toFile: fileIndex initializing: aBool]! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:04'! fileOutPool: aPool onFileStream: aFileStream | aPoolName aValue | (aPool isKindOf: SharedPool class) ifTrue:[^self notify: 'we do not fileout SharedPool type shared pools for now']. aPoolName := self environment keyAtIdentityValue: aPool. Transcript cr; show: aPoolName. aFileStream nextPutAll: 'Transcript show: ''' , aPoolName , '''; cr!!'; cr. aFileStream nextPutAll: 'Smalltalk at: #' , aPoolName , ' put: Dictionary new!!'; cr. aPool keys asSortedCollection do: [ :aKey | aValue := aPool at: aKey. aFileStream nextPutAll: aPoolName , ' at: #''' , aKey asString , '''', ' put: '. (aValue isKindOf: Number) ifTrue: [aValue printOn: aFileStream] ifFalse: [aFileStream nextPutAll: '('. aValue printOn: aFileStream. aFileStream nextPutAll: ')']. aFileStream nextPutAll: '!!'; cr]. aFileStream cr! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:04'! fileOutSharedPoolsOn: aFileStream "file out the shared pools of this class after prompting the user about each pool" | poolsToFileOut | poolsToFileOut := self sharedPools select: [:aPool | (self shouldFileOutPool: (self environment keyAtIdentityValue: aPool))]. poolsToFileOut do: [:aPool | self fileOutPool: aPool onFileStream: aFileStream]. ! ! !Class methodsFor: 'fileIn/Out' stamp: 'md 4/30/2008 15:36'! hasSharedPools ^ self sharedPools notEmpty! ! !Class methodsFor: 'fileIn/Out' stamp: 'dvf 9/27/2005 17:36'! objectForDataStream: refStrm "I am about to be written on an object file. Write a reference to a class in Smalltalk instead." refStrm insideASegment ifFalse: ["Normal use" ^ DiskProxy global: self theNonMetaClass name selector: #withClassVersion: args: {self classVersion}] ifTrue: ["recording objects to go into an ImageSegment" self isSystemDefined ifFalse: [^ self]. "do trace Player classes" (refStrm rootObject includes: self) ifTrue: [^ self]. "is in roots, intensionally write out, ^ self" "A normal class. remove it from references. Do not trace." refStrm references removeKey: self ifAbsent: []. "already there" ^ nil] ! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:05'! reformatAll "Reformat all methods in this class. Leaves old code accessible to version browsing" super reformatAll. "me..." self class reformatAll "...and my metaclass"! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:05'! removeFromChanges "References to the receiver, a class, and its metaclass should no longer be included in the system ChangeSet. 7/18/96 sw: call removeClassAndMetaClassChanges:" ChangeSet current removeClassAndMetaClassChanges: self! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:05'! shouldFileOutPool: aPoolName "respond with true if the user wants to file out aPoolName" ^self confirm: ('FileOut the sharedPool ', aPoolName, '?')! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:05'! shouldFileOutPools "respond with true if the user wants to file out the shared pools" ^self confirm: 'FileOut selected sharedPools?'! ! !Class methodsFor: 'fileIn/Out' stamp: 'al 9/3/2004 14:05'! storeDataOn: aDataStream "I don't get stored. Use a DiskProxy" (aDataStream insideASegment and: [self isSystemDefined not]) ifTrue: [ ^ super storeDataOn: aDataStream]. "do trace me" self error: 'use a DiskProxy to store a Class'! ! !Class methodsFor: 'fileIn/Out' stamp: 'ar 4/10/2005 20:27'! withClassVersion: aVersion aVersion = self classVersion ifTrue:[^self]. ^self error: 'Invalid class version'! ! !Class methodsFor: 'initialize-release' stamp: 'Noury 10/26/2008 18:58'! declare: varString "Declare class variables common to all instances. Answer whether recompilation is advisable." | newVars conflicts | newVars := (Scanner new scanFieldNames: varString) collect: [:x | x asSymbol]. conflicts := false. classPool == nil ifFalse: [(classPool keys reject: [:x | newVars includes: x]) do: [:var | self removeClassVarName: var]]. (newVars reject: [:var | self classPool includesKey: var]) do: [:var | "adding" "check if new vars defined elsewhere" (self bindingOf: var) notNil ifTrue: [self error: var , ' is defined elsewhere'. conflicts := true]]. newVars size > 0 ifTrue: [classPool := self classPool. "in case it was nil" newVars do: [:var | classPool declare: var from: Undeclared]]. ^conflicts! ! !Class methodsFor: 'initialize-release' stamp: 'al 9/3/2004 14:07'! obsolete "Change the receiver and all of its subclasses to an obsolete class." self == Object ifTrue: [^self error: 'Object is NOT obsolete']. self setName: 'AnObsolete' , self name. Object class instSize + 1 to: self class instSize do: [:i | self instVarAt: i put: nil]. "Store nil over class instVars." self classPool: nil. self sharedPools: nil. self class obsolete. super obsolete.! ! !Class methodsFor: 'initialize-release' stamp: 'al 9/3/2004 13:35'! removeFromSystem "Forget the receiver from the Smalltalk global dictionary. Any existing instances will refer to an obsolete version of the receiver." self removeFromSystem: true.! ! !Class methodsFor: 'initialize-release' stamp: 'sd 4/24/2008 22:28'! removeFromSystem: logged "Forget the receiver from the Smalltalk global dictionary. Any existing instances will refer to an obsolete version of the receiver." "keep the class name and category for triggering the system change message. If we wait to long, then we get obsolete information which is not what we want." "tell class to deactivate and unload itself-- two separate events in the module system" self unload. self superclass ifNotNil: ["If we have no superclass there's nothing to be remembered" self superclass addObsoleteSubclass: self]. self environment forgetClass: self logged: logged. self obsolete.! ! !Class methodsFor: 'initialize-release' stamp: 'al 9/3/2004 13:36'! removeFromSystemUnlogged "Forget the receiver from the Smalltalk global dictionary. Any existing instances will refer to an obsolete version of the receiver. Do not log the removal either to the current change set nor to the system changes log" ^self removeFromSystem: false! ! !Class methodsFor: 'initialize-release' stamp: 'sd 3/28/2003 16:09'! sharing: poolString "Set up sharedPools. Answer whether recompilation is advisable." | oldPools found | oldPools := self sharedPools. sharedPools := OrderedCollection new. (Scanner new scanFieldNames: poolString) do: [:poolName | sharedPools add: (self environment at: poolName asSymbol ifAbsent:[ (self confirm: 'The pool dictionary ', poolName,' does not exist.', '\Do you want it automatically created?' withCRs) ifTrue:[self environment at: poolName asSymbol put: Dictionary new] ifFalse:[^self error: poolName,' does not exist']])]. sharedPools isEmpty ifTrue: [sharedPools := nil]. oldPools do: [:pool | found := false. self sharedPools do: [:p | p == pool ifTrue: [found := true]]. found ifFalse: [^ true "A pool got deleted"]]. ^ false! ! !Class methodsFor: 'initialize-release' stamp: 'NS 4/8/2004 10:55'! superclass: sup methodDict: md format: ft name: nm organization: org instVarNames: nilOrArray classPool: pool sharedPools: poolSet "Answer an instance of me, a new class, using the arguments of the message as the needed information. Must only be sent to a new instance; else we would need Object flushCache." superclass := sup. methodDict := md. format := ft. name := nm. instanceVariables := nilOrArray. classPool := pool. sharedPools := poolSet. self organization: org.! ! !Class methodsFor: 'initialize-release' stamp: 'ar 7/20/1999 11:23'! superclass: aClass methodDictionary: mDict format: fmt "Basic initialization of the receiver" super superclass: aClass methodDictionary: mDict format: fmt. subclasses := nil. "Important for moving down the subclasses field into Class" ! ! !Class methodsFor: 'initialize-release' stamp: 'al 9/3/2004 13:35'! unload "Sent when a the class is removed. Does nothing, but may be overridden by (class-side) subclasses." ! ! !Class methodsFor: 'instance variables' stamp: 'al 9/3/2004 14:25'! addInstVarName: aString "Add the argument, aString, as one of the receiver's instance variables." ^(ClassBuilder new) name: self name inEnvironment: self environment subclassOf: self superclass type: self typeOfClass instanceVariableNames: self instanceVariablesString, ' ', aString classVariableNames: self classVariablesString poolDictionaries: self sharedPoolsString category: self category ! ! !Class methodsFor: 'instance variables' stamp: 'al 9/3/2004 14:25'! 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]. ^(ClassBuilder new) name: self name inEnvironment: self environment subclassOf: self superclass type: self typeOfClass instanceVariableNames: newInstVarString classVariableNames: self classVariablesString poolDictionaries: self sharedPoolsString category: self category! ! !Class methodsFor: 'organization'! category "Answer the system organization category for the receiver. First check whether the category name stored in the ivar is still correct and only if this fails look it up (latter is much more expensive)" | result | self basicCategory ifNotNil: [ :symbol | ((SystemOrganization listAtCategoryNamed: symbol) includes: self name) ifTrue: [ ^symbol ] ]. self basicCategory: (result := SystemOrganization categoryOfElement: self name). ^result! ! !Class methodsFor: 'organization'! category: aString "Categorize the receiver under the system category, aString, removing it from any previous categorization." | oldCategory | oldCategory := self basicCategory. aString isString ifTrue: [ self basicCategory: aString asSymbol. SystemOrganization classify: self name under: self basicCategory ] ifFalse: [self errorCategoryName]. SystemChangeNotifier uniqueInstance class: self recategorizedFrom: oldCategory to: self basicCategory! ! !Class methodsFor: 'organization' stamp: 'di 11/16/1999 16:25'! environment environment == nil ifTrue: [^ super environment]. ^ environment! ! !Class methodsFor: 'organization' stamp: 'di 12/23/1999 11:42'! environment: anEnvironment environment := anEnvironment! ! !Class methodsFor: 'pool variables' stamp: 'tpr 5/30/2003 13:04'! addSharedPool: aSharedPool "Add the argument, aSharedPool, as one of the receiver's shared pools. Create an error if the shared pool is already one of the pools. This method will work with shared pools that are plain Dictionaries or thenewer SharedPool subclasses" (self sharedPools includes: aSharedPool) ifTrue: [^self error: 'This is already in my shared pool list']. sharedPools == nil ifTrue: [sharedPools := OrderedCollection with: aSharedPool] ifFalse: [sharedPools add: aSharedPool]! ! !Class methodsFor: 'pool variables' stamp: 'al 9/3/2004 14:25'! allSharedPools "Answer a Set of the pools the receiver shares, including those defined in the superclasses of the receiver." | aSet | ^self superclass == nil ifTrue: [self sharedPools copy] ifFalse: [aSet := self superclass allSharedPools. aSet addAll: self sharedPools. aSet]! ! !Class methodsFor: 'pool variables' stamp: 'tk 9/12/96'! removeSharedPool: aDictionary "Remove the pool dictionary, aDictionary, as one of the receiver's pool dictionaries. Create an error notification if the dictionary is not one of the pools. : Note that it removes the wrong one if there are two empty Dictionaries in the list." | satisfiedSet workingSet aSubclass | (self sharedPools includes: aDictionary) ifFalse: [^self error: 'the dictionary is not in my pool']. "first see if it is declared in a superclass in which case we can remove it." (self selectSuperclasses: [:class | class sharedPools includes: aDictionary]) isEmpty ifFalse: [sharedPools remove: aDictionary. sharedPools isEmpty ifTrue: [sharedPools := nil]. ^self]. "second get all the subclasses that reference aDictionary through me rather than a superclass that is one of my subclasses." workingSet := self subclasses asOrderedCollection. satisfiedSet := Set new. [workingSet isEmpty] whileFalse: [aSubclass := workingSet removeFirst. (aSubclass sharedPools includes: aDictionary) ifFalse: [satisfiedSet add: aSubclass. workingSet addAll: aSubclass subclasses]]. "for each of these, see if they refer to any of the variables in aDictionary because if they do, we can not remove the dictionary." satisfiedSet add: self. satisfiedSet do: [:sub | aDictionary associationsDo: [:aGlobal | (sub whichSelectorsReferTo: aGlobal) isEmpty ifFalse: [^self error: aGlobal key , ' is still used in code of class ' , sub name]]]. sharedPools remove: aDictionary. sharedPools isEmpty ifTrue: [sharedPools := nil]! ! !Class methodsFor: 'pool variables'! sharedPools "Answer a Set of the pool dictionaries declared in the receiver." sharedPools == nil ifTrue: [^OrderedCollection new] ifFalse: [^sharedPools]! ! !Class methodsFor: 'pool variables' stamp: 'al 9/3/2004 13:41'! sharedPools: aCollection sharedPools := aCollection! ! !Class methodsFor: 'self evaluating' stamp: 'sd 7/31/2005 21:46'! isSelfEvaluating ^ true! ! !Class methodsFor: 'subclass creation' stamp: 'StephaneDucasse 9/15/2009 09:46'! newSubclass | i className | i := 1. [className := (self name , i printString) asSymbol. self environment includesKey: className] whileTrue: [i := i + 1]. ^ self subclass: className instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Foo' "Point newSubclass new"! ! !Class methodsFor: 'subclass creation' stamp: 'AlexandreBergel 1/26/2009 10:22'! subclass: t ^ self subclass: t instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Unclassified' ! ! !Class methodsFor: 'subclass creation' stamp: 'AlexandreBergel 1/26/2009 10:22'! subclass: t instanceVariableNames: ins ^ self subclass: t instanceVariableNames: ins classVariableNames: '' poolDictionaries: '' category: 'Unclassified' ! ! !Class methodsFor: 'subclass creation' stamp: 'ar 7/15/1999 18:57'! subclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver)." ^(ClassBuilder new) superclass: self subclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat ! ! !Class methodsFor: 'subclass creation' stamp: 'al 7/19/2004 11:18'! subclass: t uses: aTraitCompositionOrArray instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat | newClass copyOfOldClass | copyOfOldClass := self copy. newClass := self subclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat. newClass setTraitComposition: aTraitCompositionOrArray asTraitComposition. SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: copyOfOldClass to: newClass. ^newClass! ! !Class methodsFor: 'subclass creation' stamp: 'ar 7/15/1999 18:57'! variableByteSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver) in which the subclass is to have indexable byte-sized nonpointer variables." ^(ClassBuilder new) superclass: self variableByteSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat ! ! !Class methodsFor: 'subclass creation' stamp: 'al 7/19/2004 11:18'! variableByteSubclass: t uses: aTraitCompositionOrArray instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver) in which the subclass is to have indexable byte-sized nonpointer variables." | newClass copyOfOldClass | copyOfOldClass := self copy. newClass := self variableByteSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat. newClass setTraitComposition: aTraitCompositionOrArray asTraitComposition. SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: copyOfOldClass to: newClass. ^newClass ! ! !Class methodsFor: 'subclass creation' stamp: 'ar 7/15/1999 18:56'! variableSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver) in which the subclass is to have indexable pointer variables." ^(ClassBuilder new) superclass: self variableSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat ! ! !Class methodsFor: 'subclass creation' stamp: 'al 7/19/2004 11:17'! variableSubclass: t uses: aTraitCompositionOrArray instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver) in which the subclass is to have indexable pointer variables." | newClass copyOfOldClass | copyOfOldClass := self copy. newClass := self variableSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat. newClass setTraitComposition: aTraitCompositionOrArray asTraitComposition. SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: copyOfOldClass to: newClass. ^newClass ! ! !Class methodsFor: 'subclass creation' stamp: 'ar 7/15/1999 18:56'! variableWordSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver) in which the subclass is to have indexable word-sized nonpointer variables." ^(ClassBuilder new) superclass: self variableWordSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat ! ! !Class methodsFor: 'subclass creation' stamp: 'al 7/19/2004 11:18'! variableWordSubclass: t uses: aTraitCompositionOrArray instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver) in which the subclass is to have indexable word-sized nonpointer variables." | newClass copyOfOldClass | copyOfOldClass := self copy. newClass := self variableWordSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat. newClass setTraitComposition: aTraitCompositionOrArray asTraitComposition. SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: copyOfOldClass to: newClass. ^newClass ! ! !Class methodsFor: 'subclass creation' stamp: 'tak 9/25/2008 15:00'! weakSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver) in which the subclass is to have weak indexable pointer variables." ^(ClassBuilder new) superclass: self weakSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat! ! !Class methodsFor: 'subclass creation' stamp: 'al 7/19/2004 11:18'! weakSubclass: t uses: aTraitCompositionOrArray instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver) in which the subclass is to have weak indexable pointer variables." | newClass copyOfOldClass | copyOfOldClass := self copy. newClass := self weakSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat. newClass setTraitComposition: aTraitCompositionOrArray asTraitComposition. SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: copyOfOldClass to: newClass. ^newClass ! ! !Class methodsFor: 'testing'! hasMethods "Answer a Boolean according to whether any methods are defined for the receiver (includes whether there are methods defined in the receiver's metaclass)." ^super hasMethods or: [self class hasMethods]! ! !Class methodsFor: 'testing' stamp: 'al 6/5/2006 13:13'! isObsolete "Return true if the receiver is obsolete." ^(self environment at: name ifAbsent: [nil]) ~~ self! ! !Class methodsFor: 'testing' stamp: 'tk 8/12/1999 15:47'! isSystemDefined "Answer true if the receiver is a system-defined class, and not a UniClass (an instance-specific lightweight class)" ^ self == self officialClass! ! !Class methodsFor: 'testing' stamp: 'tk 8/12/1999 15:49'! officialClass "I am not a UniClass. (See Player officialClass). Return the class you use to make new subclasses." ^ self! ! !Class methodsFor: 'traits' stamp: 'NS 4/12/2004 16:48'! applyChangesOfNewTraitCompositionReplacing: oldComposition "See Trait>>applyChangesOfNewTraitCompositionReplacing:" | changedSelectors | changedSelectors := super applyChangesOfNewTraitCompositionReplacing: oldComposition. self classSide noteNewBaseTraitCompositionApplied: self traitComposition. ^ changedSelectors! ! !Class methodsFor: 'private' stamp: 'ar 7/15/1999 15:37'! setName: aSymbol "Private - set the name of the class" name := aSymbol.! ! !Class methodsFor: 'private' stamp: 'sd 2/1/2004 15:18'! spaceUsed "Object spaceUsed" ^ super spaceUsed + self class spaceUsed! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Class class uses: TBehaviorCategorization classTrait instanceVariableNames: ''! !Class class methodsFor: 'fileIn/Out' stamp: 'PeterHugossonMiller 9/3/2009 00:53'! fileOutPool: aString "file out the global pool named aString" | internalStream | internalStream := (String new: 1000) writeStream. self new fileOutPool: (self environment at: aString asSymbol) onFileStream: internalStream. FileStream writeSourceCodeFrom: internalStream baseName: aString isSt: true.! ! !Class class methodsFor: 'inquiries' stamp: 'al 6/14/2008 09:50'! rootsOfTheWorld "return all classes that have a nil superclass" ^(Smalltalk select: [:each | each isBehavior and: [each superclass isNil]]) asOrderedCollection! ! !Class class methodsFor: 'instance creation' stamp: 'di 6/7/2000 22:01'! template: aSystemCategoryName "Answer an expression that can be edited and evaluated in order to define a new class." ^ self templateForSubclassOf: Object name category: aSystemCategoryName ! ! !Class class methodsFor: 'instance creation' stamp: 'eem 5/7/2008 12:06'! templateForSubclassOf: priorClassName category: systemCategoryName "Answer an expression that can be edited and evaluated in order to define a new class, given that the class previously looked at was as given" ^priorClassName asString, ' subclass: #NameOfSubclass instanceVariableNames: '''' classVariableNames: '''' poolDictionaries: '''' category: ''' , systemCategoryName asString , ''''! ! Object subclass: #ClassBuilder instanceVariableNames: 'environ classMap instVarMap progress maxClassIndex currentClassIndex' classVariableNames: 'QuietMode' poolDictionaries: '' category: 'Kernel-Classes'! !ClassBuilder commentStamp: 'ar 2/27/2003 22:55' prior: 0! Responsible for creating a new class or changing the format of an existing class (from a class definition in a browser or a fileIn). This includes validating the definition, computing the format of instances, creating or modifying the accompanying Metaclass, setting up the class and metaclass objects themselves, registering the class as a global, recompiling methods, modifying affected subclasses, mutating existing instances to the new format, and more. You typically only need to use or modify this class, or even know how it works, when making fundamental changes to how the Smalltalk system and language works. Implementation notes: ClassBuilder relies on the assumption that it can see ALL subclasses of some class. If there are any existing subclasses of some class, regardless of whether they have instances or not, regardless of whether they are considered obsolete or not, ClassBuilder MUST SEE THEM. ! !ClassBuilder methodsFor: 'class definition' stamp: 'adrian_lienhard 1/17/2009 14:06'! class: oldClass instanceVariableNames: instVarString unsafe: unsafe "This is the basic initialization message to change the definition of an existing Metaclass" | instVars newClass needNew copyOfOldClass copyOfOldTraitComposition copyOfOldClassTraitComposition | environ := oldClass environment. instVars := Scanner new scanFieldNames: instVarString. unsafe ifFalse:[ "Run validation checks so we know that we have a good chance for recompilation" (self validateInstvars: instVars from: oldClass forSuper: oldClass superclass) ifFalse:[^nil]. (self validateSubclassFormat: oldClass typeOfClass from: oldClass forSuper: oldClass superclass extra: instVars size) ifFalse:[^nil]]. "See if we need a new subclass or not" needNew := self needsSubclassOf: oldClass superclass type: oldClass typeOfClass instanceVariables: instVars from: oldClass. needNew ifNil:[^nil]. "some error" needNew ifFalse:[^oldClass]. "no new class needed" "Create the new class" copyOfOldClass := oldClass copy. oldClass hasTraitComposition ifTrue: [ copyOfOldTraitComposition := oldClass traitComposition copyTraitExpression ]. oldClass class hasTraitComposition ifTrue: [ copyOfOldClassTraitComposition := oldClass class traitComposition copyTraitExpression ]. newClass := self newSubclassOf: oldClass superclass type: oldClass typeOfClass instanceVariables: instVars from: oldClass. newClass := self recompile: false from: oldClass to: newClass mutate: false. "... set trait composition..." copyOfOldTraitComposition ifNotNil: [ newClass setTraitComposition: copyOfOldTraitComposition ]. copyOfOldClassTraitComposition ifNotNil: [ newClass class setTraitComposition: copyOfOldClassTraitComposition ]. self doneCompiling: newClass. SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: copyOfOldClass to: newClass. ^newClass! ! !ClassBuilder methodsFor: 'class definition' stamp: 'ar 8/29/1999 15:34'! name: className inEnvironment: env subclassOf: newSuper type: type instanceVariableNames: instVarString classVariableNames: classVarString poolDictionaries: poolString category: category "Define a new class in the given environment" ^self name: className inEnvironment: env subclassOf: newSuper type: type instanceVariableNames: instVarString classVariableNames: classVarString poolDictionaries: poolString category: category unsafe: false! ! !ClassBuilder methodsFor: 'class definition' stamp: 'adrian_lienhard 1/17/2009 14:06'! name: className inEnvironment: env subclassOf: newSuper type: type instanceVariableNames: instVarString classVariableNames: classVarString poolDictionaries: poolString category: category unsafe: unsafe "Define a new class in the given environment. If unsafe is true do not run any validation checks. This facility is provided to implement important system changes." | oldClass newClass organization instVars classVars force needNew oldCategory copyOfOldClass newCategory copyOfOldTraitComposition copyOfOldClassTraitComposition | environ := env. instVars := Scanner new scanFieldNames: instVarString. classVars := (Scanner new scanFieldNames: classVarString) collect: [:x | x asSymbol]. "Validate the proposed name" unsafe ifFalse:[(self validateClassName: className) ifFalse:[^nil]]. oldClass := env at: className ifAbsent:[nil]. oldClass isBehavior ifFalse: [oldClass := nil] "Already checked in #validateClassName:" ifTrue: [ copyOfOldClass := oldClass copy. copyOfOldClass superclass addSubclass: copyOfOldClass. copyOfOldClass ifNotNil: [ oldClass hasTraitComposition ifTrue: [ copyOfOldTraitComposition := oldClass traitComposition copyTraitExpression ]. oldClass class hasTraitComposition ifTrue: [ copyOfOldClassTraitComposition := oldClass class traitComposition copyTraitExpression ] ] ]. [unsafe ifFalse:[ "Run validation checks so we know that we have a good chance for recompilation" (self validateSuperclass: newSuper forSubclass: oldClass) ifFalse:[^nil]. (self validateInstvars: instVars from: oldClass forSuper: newSuper) ifFalse:[^nil]. (self validateClassvars: classVars from: oldClass forSuper: newSuper) ifFalse:[^nil]. (self validateSubclassFormat: type from: oldClass forSuper: newSuper extra: instVars size) ifFalse:[^nil]]. "See if we need a new subclass" needNew := self needsSubclassOf: newSuper type: type instanceVariables: instVars from: oldClass. needNew == nil ifTrue:[^nil]. "some error" (needNew and:[unsafe not]) ifTrue:[ "Make sure we don't redefine any dangerous classes" (self tooDangerousClasses includes: oldClass name) ifTrue:[ self error: oldClass name, ' cannot be changed'. ]. "Check if the receiver should not be redefined" (oldClass ~~ nil and:[oldClass shouldNotBeRedefined]) ifTrue:[ self notify: oldClass name asText allBold, ' should not be redefined. \Proceed to store over it.' withCRs]]. needNew ifTrue:[ "Create the new class" newClass := self newSubclassOf: newSuper type: type instanceVariables: instVars from: oldClass. newClass == nil ifTrue:[^nil]. "Some error" newClass setName: className. ] ifFalse:[ "Reuse the old class" newClass := oldClass. ]. "Install the class variables and pool dictionaries... " force := (newClass declare: classVarString) | (newClass sharing: poolString). "... classify ..." newCategory := category asSymbol. organization := environ ifNotNil:[environ organization]. oldClass isNil ifFalse: [oldCategory := (organization categoryOfElement: oldClass name) asSymbol]. organization classify: newClass name under: newCategory. newClass environment: environ. "... recompile ..." newClass := self recompile: force from: oldClass to: newClass mutate: false. "... export if not yet done ..." (environ at: newClass name ifAbsent:[nil]) == newClass ifFalse:[ environ at: newClass name put: newClass. Smalltalk flushClassNameCache. ]. "... set trait composition..." copyOfOldTraitComposition ifNotNil: [ newClass setTraitComposition: copyOfOldTraitComposition ]. copyOfOldClassTraitComposition ifNotNil: [ newClass class setTraitComposition: copyOfOldClassTraitComposition ]. newClass doneCompiling. "... notify interested clients ..." oldClass isNil ifTrue: [ SystemChangeNotifier uniqueInstance classAdded: newClass inCategory: newCategory. ^ newClass]. newCategory ~= oldCategory ifTrue: [SystemChangeNotifier uniqueInstance class: newClass recategorizedFrom: oldCategory to: category] ifFalse: [SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: copyOfOldClass to: newClass.]. ] ensure: [copyOfOldClass ifNotNil: [copyOfOldClass superclass removeSubclass: copyOfOldClass]. Behavior flushObsoleteSubclasses. ]. ^newClass! ! !ClassBuilder methodsFor: 'class definition' stamp: 'ar 9/22/2002 02:57'! needsSubclassOf: newSuper type: type instanceVariables: instVars from: oldClass "Answer whether we need a new subclass to conform to the requested changes" | newFormat | "Compute the format of the new class" newFormat := self computeFormat: type instSize: instVars size forSuper: newSuper ccIndex: (oldClass ifNil:[0] ifNotNil:[oldClass indexIfCompact]). newFormat == nil ifTrue:[^nil]. "Check if we really need a new subclass" oldClass ifNil:[^true]. "yes, it's a new class" newSuper == oldClass superclass ifFalse:[^true]. "yes, it's a superclass change" newFormat = oldClass format ifFalse:[^true]. "yes, it's a format change" instVars = oldClass instVarNames ifFalse:[^true]. "yes, it's an iVar change" ^false ! ! !ClassBuilder methodsFor: 'class definition' stamp: 'adrian_lienhard 1/17/2009 11:31'! newSubclassOf: newSuper type: type instanceVariables: instVars from: oldClass "Create a new subclass of the given superclass with the given specification." | newFormat newClass | "Compute the format of the new class" newFormat := self computeFormat: type instSize: instVars size forSuper: newSuper ccIndex: (oldClass ifNil:[0] ifNotNil:[oldClass indexIfCompact]). newFormat == nil ifTrue:[^nil]. (oldClass == nil or:[oldClass isMeta not]) ifTrue:[newClass := self privateNewSubclassOf: newSuper from: oldClass] ifFalse:[newClass := oldClass clone]. newClass superclass: newSuper methodDictionary: MethodDictionary new format: newFormat; setInstVarNames: instVars. oldClass ifNotNil:[ newClass organization: oldClass organization. "Recompile the new class" oldClass hasMethods ifTrue:[newClass compileAllFrom: oldClass]. self recordClass: oldClass replacedBy: newClass. ]. (oldClass == nil or:[oldClass isObsolete not]) ifTrue:[newSuper addSubclass: newClass] ifFalse:[newSuper addObsoleteSubclass: newClass]. ^newClass! ! !ClassBuilder methodsFor: 'class definition' stamp: 'NS 1/21/2004 09:53'! recompile: force from: oldClass to: newClass mutate: forceMutation "Do the necessary recompilation after changine oldClass to newClass. If required (e.g., when oldClass ~~ newClass) mutate oldClass to newClass and all its subclasses. If forceMutation is true force a mutation even if oldClass and newClass are the same." oldClass == nil ifTrue:[^ newClass]. (newClass == oldClass and:[force not and:[forceMutation not]]) ifTrue:[ ^newClass]. currentClassIndex := 0. maxClassIndex := oldClass withAllSubclasses size. (oldClass == newClass and:[forceMutation not]) ifTrue:[ "Recompile from newClass without mutating" self informUserDuring:[ newClass isSystemDefined ifFalse:[progress := nil]. newClass withAllSubclassesDo:[:cl| self showProgressFor: cl. cl compileAll]]. ^newClass]. "Recompile and mutate oldClass to newClass" self informUserDuring:[ newClass isSystemDefined ifFalse:[progress := nil]. self mutate: oldClass to: newClass. ]. ^oldClass "now mutated to newClass"! ! !ClassBuilder methodsFor: 'class definition' stamp: 'al 7/4/2009 16:55'! silentlyMoveInstVarNamed: instVarName from: srcClass to: dstClass after: prevInstVarName "Move the instvar from srcClass to dstClass. Do not perform any checks." | srcVars dstVars dstIndex newClass copyOfSrcClass copyOfDstClass copyOfOldTraitComposition copyOfOldClassTraitComposition | copyOfSrcClass := srcClass copy. copyOfDstClass := dstClass copy. srcVars := srcClass instVarNames copyWithout: instVarName. srcClass == dstClass ifTrue:[dstVars := srcVars] ifFalse:[dstVars := dstClass instVarNames]. dstIndex := dstVars indexOf: prevInstVarName. dstVars := (dstVars copyFrom: 1 to: dstIndex), (Array with: instVarName), (dstVars copyFrom: dstIndex+1 to: dstVars size). instVarMap at: srcClass name put: srcVars. instVarMap at: dstClass name put: dstVars. (srcClass inheritsFrom: dstClass) ifTrue:[ copyOfOldTraitComposition := copyOfOldClassTraitComposition := nil. dstClass hasTraitComposition ifTrue: [ copyOfOldTraitComposition := dstClass traitComposition copyTraitExpression ]. dstClass class hasTraitComposition ifTrue: [ copyOfOldClassTraitComposition := dstClass class traitComposition copyTraitExpression ]. newClass := self reshapeClass: dstClass toSuper: dstClass superclass. self recompile: false from: dstClass to: newClass mutate: true. copyOfOldTraitComposition ifNotNil: [ newClass setTraitComposition: copyOfOldTraitComposition ]. copyOfOldClassTraitComposition ifNotNil: [ newClass class setTraitComposition: copyOfOldClassTraitComposition ]. ] ifFalse:[ (dstClass inheritsFrom: srcClass) ifTrue:[ newClass := self reshapeClass: srcClass toSuper: srcClass superclass. self recompile: false from: srcClass to: newClass mutate: true. ] ifFalse:[ "Disjunct hierarchies" srcClass == dstClass ifFalse:[ newClass := self reshapeClass: dstClass toSuper: dstClass superclass. self recompile: false from: dstClass to: newClass mutate: true. ]. newClass := self reshapeClass: srcClass toSuper: srcClass superclass. self recompile: false from: srcClass to: newClass mutate: true. ]. ]. self doneCompiling: srcClass. self doneCompiling: dstClass. SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: copyOfSrcClass to: srcClass. SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: copyOfDstClass to: dstClass.! ! !ClassBuilder methodsFor: 'class format' stamp: 'eem 6/13/2008 10:03'! computeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex "Compute the new format for making oldClass a subclass of newSuper. Return the format or nil if there is any problem." | instSize isVar isWords isPointers isWeak | type == #compiledMethod ifTrue:[^CompiledMethod format]. instSize := newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]). instSize > 254 ifTrue:[ self error: 'Class has too many instance variables (', instSize printString,')'. ^nil]. type == #normal ifTrue:[isVar := isWeak := false. isWords := isPointers := true]. type == #bytes ifTrue:[isVar := true. isWords := isPointers := isWeak := false]. type == #words ifTrue:[isVar := isWords := true. isPointers := isWeak := false]. type == #variable ifTrue:[isVar := isPointers := isWords := true. isWeak := false]. type == #weak ifTrue:[isVar := isWeak := isWords := isPointers := true]. (isPointers not and:[instSize > 0]) ifTrue:[ self error:'A non-pointer class cannot have instance variables'. ^nil]. ^(self format: instSize variable: isVar words: isWords pointers: isPointers weak: isWeak) + (ccIndex bitShift: 11).! ! !ClassBuilder methodsFor: 'class format' stamp: 'ar 7/11/1999 06:39'! format: nInstVars variable: isVar words: isWords pointers: isPointers weak: isWeak "Compute the format for the given instance specfication." | cClass instSpec sizeHiBits fmt | self flag: #instSizeChange. " Smalltalk browseAllCallsOn: #instSizeChange. Smalltalk browseAllImplementorsOf: #fixedFieldsOf:. Smalltalk browseAllImplementorsOf: #instantiateClass:indexableSize:. " " NOTE: This code supports the backward-compatible extension to 8 bits of instSize. For now the format word is... <2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0> But when we revise the image format, it should become... <5 bits=cClass><4 bits=instSpec><8 bits=instSize><1 bit=0> " sizeHiBits := (nInstVars+1) // 64. cClass := 0. "for now" instSpec := isWeak ifTrue:[4] ifFalse:[isPointers ifTrue: [isVar ifTrue: [nInstVars>0 ifTrue: [3] ifFalse: [2]] ifFalse: [nInstVars>0 ifTrue: [1] ifFalse: [0]]] ifFalse: [isWords ifTrue: [6] ifFalse: [8]]]. fmt := sizeHiBits. fmt := (fmt bitShift: 5) + cClass. fmt := (fmt bitShift: 4) + instSpec. fmt := (fmt bitShift: 6) + ((nInstVars+1)\\64). "+1 since prim size field includes header" fmt := (fmt bitShift: 1). "This shift plus integer bit lets wordSize work like byteSize" ^fmt! ! !ClassBuilder methodsFor: 'class mutation' stamp: 'al 7/4/2009 16:52'! mutate: oldClass to: newClass "Mutate the old class and subclasses into newClass and subclasses. Note: This method is slightly different from: #mutate:toSuper: since here we are at the root of reshaping and have two distinct roots." | copyOfOldTraitComposition copyOfOldClassTraitComposition | self showProgressFor: oldClass. "Convert the subclasses" oldClass subclasses do: [:oldSubclass | | newSubclass | copyOfOldTraitComposition := copyOfOldClassTraitComposition := nil. oldSubclass hasTraitComposition ifTrue: [ copyOfOldTraitComposition := oldSubclass traitComposition copyTraitExpression ]. oldSubclass class hasTraitComposition ifTrue: [ copyOfOldClassTraitComposition := oldSubclass class traitComposition copyTraitExpression ]. newSubclass := self reshapeClass: oldSubclass toSuper: newClass. self mutate: oldSubclass to: newSubclass. copyOfOldTraitComposition ifNotNil: [ newSubclass setTraitComposition: copyOfOldTraitComposition ]. copyOfOldClassTraitComposition ifNotNil: [ newSubclass class setTraitComposition: copyOfOldClassTraitComposition ]. ]. "And any obsolete ones" oldClass obsoleteSubclasses do: [:oldSubclass | | newSubclass | oldSubclass ifNotNil: [ copyOfOldTraitComposition := copyOfOldClassTraitComposition := nil. oldSubclass hasTraitComposition ifTrue: [ copyOfOldTraitComposition := oldSubclass traitComposition copyTraitExpression ]. oldSubclass class hasTraitComposition ifTrue: [ copyOfOldClassTraitComposition := oldSubclass class traitComposition copyTraitExpression ]. newSubclass := self reshapeClass: oldSubclass toSuper: newClass. self mutate: oldSubclass to: newSubclass. copyOfOldTraitComposition ifNotNil: [ newSubclass setTraitComposition: copyOfOldTraitComposition ]. copyOfOldClassTraitComposition ifNotNil: [ newSubclass class setTraitComposition: copyOfOldClassTraitComposition ]. ]. ]. self update: oldClass to: newClass. ^newClass! ! !ClassBuilder methodsFor: 'class mutation' stamp: 'ar 9/22/2002 03:16'! reshapeClass: oldClass toSuper: newSuper "Reshape the given class to the new super class. Recompile all the methods in the newly created class. Answer the new class." | instVars | "ar 9/22/2002: The following is a left-over from some older code. I do *not* know why we uncompact oldClass here. If you do, then please let me know so I can put a comment here..." oldClass becomeUncompact. instVars := instVarMap at: oldClass name ifAbsent:[oldClass instVarNames]. ^self newSubclassOf: newSuper type: oldClass typeOfClass instanceVariables: instVars from: oldClass! ! !ClassBuilder methodsFor: 'class mutation' stamp: 'ar 2/27/2003 23:42'! update: oldClass to: newClass "Convert oldClass, all its instances and possibly its meta class into newClass, instances of newClass and possibly its meta class. The process is surprisingly simple in its implementation and surprisingly complex in its nuances and potentially bad side effects. We can rely on two assumptions (which are critical): #1: The method #updateInstancesFrom: will not create any lasting pointers to 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do a become of the old vs. the new instances and therefore it will not create pointers to *new* instances before the #become: which are *old* afterwards) #2: The non-preemptive execution of the critical piece of code guarantees that nobody can get a hold by 'other means' (such as process interruption and reflection) on the old instances. Given the above two, we know that after #updateInstancesFrom: there are no pointer to any old instances. After the forwarding become there will be no pointers to the old class or meta class either. Meaning that if we throw in a nice fat GC at the end of the critical block, everything will be gone (but see the comment right there). There's no need to worry. " | meta | meta := oldClass isMeta. "Note: Everything from here on will run without the ability to get interrupted to prevent any other process to create new instances of the old class." [ "Note: The following removal may look somewhat obscure and needs an explanation. When we mutate the class hierarchy we create new classes for any existing subclass. So it may look as if we don't have to remove the old class from its superclass. However, at the top of the hierarchy (the first class we reshape) that superclass itself is not newly created so therefore it will hold both the oldClass and newClass in its (obsolete or not) subclasses. Since the #become: below will transparently replace the pointers to oldClass with newClass the superclass would have newClass in its subclasses TWICE. With rather unclear effects if we consider that we may convert the meta-class hierarchy itself (which is derived from the non-meta class hierarchy). Due to this problem ALL classes are removed from their superclass just prior to converting them. Here, breaking the superclass/subclass invariant really doesn't matter since we will effectively remove the oldClass (become+GC) just a few lines below." oldClass superclass removeSubclass: oldClass. oldClass superclass removeObsoleteSubclass: oldClass. "Convert the instances of oldClass into instances of newClass" newClass updateInstancesFrom: oldClass. meta ifTrue:[oldClass becomeForward: newClass] ifFalse:[(Array with: oldClass with: oldClass class) elementsForwardIdentityTo: (Array with: newClass with: newClass class)]. Smalltalk garbageCollect. "Warning: Read this before you even think about removing the GC. Yes, it slows us down. Quite heavily if you have a large image. However, there's no good and simple alternative here, since unfortunately, #become: does change class pointers. What happens is that after the above become all of the instances of the old class will have a class pointer identifying them as instances of newClass. If we get our hands on any of these instances we will break immediately since their expected instance layout (that of its class, e.g., newClass) will not match their actual instance layout (that of oldClass). And getting your hands on any of those instances is really simple - just reshaping one class two times in rapid succession will do it. Reflection techniques, interrupts, etc. will only add to this problem. In the case of Metaclass things get even worse since when we recompile the entire class hierarchy we will recompile both, Metaclass and its instances (and some of its instances will have the old and some the new layout). The only easy solution to this problem would be to 'fix up' the class pointers of the old instances to point to the old class (using primitiveChangeClassTo:). But this won't work either - as we do a one-way become we would have to search the entire object memory for the oldClass and couldn't even clearly identify it unless we give it some 'special token' which sounds quite error-prone. If you really need to get rid of the GC here are some alternatives: On the image level, one could create a copy of the oldClass before becoming it into the new class and, after becoming it, 'fix up' the old instances. That would certainly work but it sounds quite complex, as we need to make sure we're not breaking any of the superclass/subclass meta/non-meta class variants. Alternatively, fix up #becomeForward on the VM-level to 'dump the source objects' of #become. This would be quite doable (just 'convert' them into a well known special class such as bitmap) yet it has problems if (accidentally or not) one of the objects in #become: appears on 'both sides of the fence' (right now, this will work ... in a way ... even though the consequences are unclear). Another alternative is to provide a dedicated primitive for this (instead of using it implicitly in become) which would allow us to dump all the existing instances right here. This is equivalent to a more general primitiveChangeClassTo: and might be worthwhile but it would likely have to keep in mind the differences between bits and pointer thingies etc. Since all of the alternatives seem rather complex and magical compared to a straight-forward GC it seems best to stick with the GC solution for now. If someone has a real need to fix this problem, that person will likely be motivated enough to check out the alternatives. Personally I'd probably go for #1 (copy the old class and remap the instances to it) since it's a solution that could be easily reverted from within the image if there's any problem with it." ] valueUnpreemptively. ! ! !ClassBuilder methodsFor: 'initialize' stamp: 'ar 3/3/2001 00:29'! doneCompiling: aClass "The receiver has finished modifying the class hierarchy. Do any necessary cleanup." aClass doneCompiling. Behavior flushObsoleteSubclasses.! ! !ClassBuilder methodsFor: 'initialize' stamp: 'alain.plantec 5/28/2009 09:47'! initialize super initialize. environ := Smalltalk. instVarMap := IdentityDictionary new.! ! !ClassBuilder methodsFor: 'public' stamp: 'ar 8/29/1999 15:38'! class: oldClass instanceVariableNames: instVarString "This is the basic initialization message to change the definition of an existing Metaclass" oldClass isMeta ifFalse:[^self error: oldClass name, 'is not a Metaclass']. ^self class: oldClass instanceVariableNames: instVarString unsafe: false! ! !ClassBuilder methodsFor: 'public' stamp: 'ar 7/19/1999 23:40'! moveInstVarNamed: instVarName from: srcClass to: dstClass after: prevInstVarName "Move the given instVar from srcClass to dstClass" (srcClass instVarNames includes: instVarName) ifFalse:[^self error: instVarName,' is not an instance variable of ', srcClass name]. (prevInstVarName isNil or:[dstClass instVarNames includes: prevInstVarName]) ifFalse:[^self error: prevInstVarName, 'is not an instance variable of', dstClass name]. (srcClass inheritsFrom: dstClass) ifTrue:[ "Move the instvar up the hierarchy." (self validateClass: srcClass forMoving: instVarName upTo: dstClass) ifFalse:[^false]. ]. (dstClass inheritsFrom: srcClass) ifTrue:[ "Move the instvar down the hierarchy" (self validateClass: srcClass forMoving: instVarName downTo: dstClass) ifFalse:[^false]. ]. ^self silentlyMoveInstVarNamed: instVarName from: srcClass to: dstClass after: prevInstVarName! ! !ClassBuilder methodsFor: 'public' stamp: 'ar 7/19/1999 23:29'! superclass: newSuper subclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class." ^self name: t inEnvironment: newSuper environment subclassOf: newSuper type: newSuper typeOfClass instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat! ! !ClassBuilder methodsFor: 'public' stamp: 'eem 6/13/2008 10:00'! superclass: aClass variableByteSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class in which the subclass is to have indexable byte-sized nonpointer variables." | oldClassOrNil actualType | (aClass instSize > 0) ifTrue: [^self error: 'cannot make a byte subclass of a class with named fields']. (aClass isVariable and: [aClass isWords]) ifTrue: [^self error: 'cannot make a byte subclass of a class with word fields']. (aClass isVariable and: [aClass isPointers]) ifTrue: [^self error: 'cannot make a byte subclass of a class with pointer fields']. oldClassOrNil := aClass environment at: t ifAbsent:[nil]. actualType := (oldClassOrNil notNil and: [oldClassOrNil typeOfClass == #compiledMethod]) ifTrue: [#compiledMethod] ifFalse: [#bytes]. ^self name: t inEnvironment: aClass environment subclassOf: aClass type: actualType instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat! ! !ClassBuilder methodsFor: 'public' stamp: 'ar 7/19/1999 23:29'! superclass: aClass variableSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class in which the subclass is to have indexable pointer variables." aClass isBits ifTrue: [^self error: 'cannot make a pointer subclass of a class with non-pointer fields']. ^self name: t inEnvironment: aClass environment subclassOf: aClass type: #variable instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat! ! !ClassBuilder methodsFor: 'public' stamp: 'ar 7/19/1999 23:30'! superclass: aClass variableWordSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class in which the subclass is to have indexable word-sized nonpointer variables." (aClass instSize > 0) ifTrue: [^self error: 'cannot make a word subclass of a class with named fields']. (aClass isVariable and: [aClass isBytes]) ifTrue: [^self error: 'cannot make a word subclass of a class with byte fields']. (aClass isVariable and: [aClass isPointers]) ifTrue: [^self error: 'cannot make a word subclass of a class with pointer fields']. ^self name: t inEnvironment: aClass environment subclassOf: aClass type: #words instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat! ! !ClassBuilder methodsFor: 'public' stamp: 'ar 7/19/1999 23:30'! superclass: aClass weakSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat "This is the standard initialization message for creating a new class as a subclass of an existing class (the receiver) in which the subclass is to have weak indexable pointer variables." aClass isBits ifTrue: [^self error: 'cannot make a pointer subclass of a class with non-pointer fields']. ^self name: t inEnvironment: aClass environment subclassOf: aClass type: #weak instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat! ! !ClassBuilder methodsFor: 'validation' stamp: 'ar 7/20/1999 00:41'! validateClass: srcClass forMoving: iv downTo: dstClass "Make sure that we don't have any accesses to the instVar left" srcClass withAllSubclassesDo:[:cls| (cls == dstClass or:[cls inheritsFrom: dstClass]) ifFalse:[ cls forgetDoIts. (cls whichSelectorsAccess: iv) isEmpty ifFalse:[ self notify: (iv printString asText allBold), ' is still used in ', cls name asText allBold,'. Proceed to move it to Undeclared'. ]. ]. ]. ^true! ! !ClassBuilder methodsFor: 'validation' stamp: 'ar 7/20/1999 00:39'! validateClass: srcClass forMoving: iv upTo: dstClass "Make sure we don't have this instvar already" dstClass withAllSubclassesDo:[:cls| (cls == srcClass or:[cls inheritsFrom: srcClass]) ifFalse:[ cls isPointers ifFalse:[ self error: dstClass name, ' cannot have instance variables'. ^false]. cls instSize >= 254 ifTrue:[ self error: cls name, ' has more than 254 instance variables'. ^false]. (cls instVarNames includes: iv) ifTrue:[ self notify: (iv printString asText allBold),' is defined in ', cls name asText allBold,' Proceed to move it up to ', dstClass name asText allBold,' as well'. instVarMap at: cls name put: (cls instVarNames copyWithout: iv)]. ]. ]. ^true! ! !ClassBuilder methodsFor: 'validation' stamp: 'yo 11/11/2002 10:22'! validateClassName: aString "Validate the new class name" aString first canBeGlobalVarInitial ifFalse:[ self error: 'Class names must be capitalized'. ^false]. environ at: aString ifPresent:[:old| (old isKindOf: Behavior) ifFalse:[ self notify: aString asText allBold, ' already exists!!\Proceed will store over it.' withCRs]]. ^true! ! !ClassBuilder methodsFor: 'validation' stamp: 'lr 7/3/2009 20:54'! validateClassvars: classVarArray from: oldClass forSuper: newSuper "Check if any of the classVars of oldClass conflict with the new superclass" | usedNames classVars temp | classVarArray isEmpty ifTrue:[^true]. "Okay" "Validate the class var names" usedNames := classVarArray asSet. usedNames size = classVarArray size ifFalse:[ classVarArray do:[:var| usedNames remove: var ifAbsent:[temp := var]]. self error: temp,' is multiply defined'. ^false]. (usedNames includesAnyOf: self reservedNames) ifTrue:[ self reservedNames do:[:var| (usedNames includes: var) ifTrue:[temp := var]]. self error: temp,' is a reserved name'. ^false]. newSuper == nil ifFalse:[ usedNames := newSuper allClassVarNames asSet. classVarArray do:[:iv| (usedNames includes: iv) ifTrue:[ newSuper withAllSuperclassesDo:[:cl| (cl classVarNames includes: iv) ifTrue:[temp := cl]]. self error: iv, ' is already defined in ', temp name. ^false]]]. classVars := classVarArray. oldClass == nil ifFalse:[ usedNames := Set new: 20. (oldClass allSubclasses reject: #isMeta) do: [:cl | usedNames addAll: cl classVarNames]. newSuper == nil ifFalse:[classVars := classVars, newSuper allClassVarNames asArray]. classVars do:[:iv| (usedNames includes: iv) ifTrue:[ self error: iv, ' is already defined in a subclass of ', oldClass name. ^false]]]. ^true! ! !ClassBuilder methodsFor: 'validation' stamp: 'lr 7/3/2009 20:54'! validateInstvars: instVarArray from: oldClass forSuper: newSuper "Check if any of the instVars of oldClass conflict with the new superclass" | instVars usedNames temp | instVarArray isEmpty ifTrue:[^true]. "Okay" newSuper allowsSubInstVars ifFalse: [ self error: newSuper printString, ' does not allow subclass inst vars. See allowsSubInstVars.'. ^ false]. "Validate the inst var names" usedNames := instVarArray asSet. usedNames size = instVarArray size ifFalse:[ instVarArray do:[:var| usedNames remove: var ifAbsent:[temp := var]]. self error: temp,' is multiply defined'. ^false]. (usedNames includesAnyOf: self reservedNames) ifTrue:[ self reservedNames do:[:var| (usedNames includes: var) ifTrue:[temp := var]]. self error: temp,' is a reserved name'. ^false]. newSuper == nil ifFalse:[ usedNames := newSuper allInstVarNames asSet. instVarArray do:[:iv| (usedNames includes: iv) ifTrue:[ newSuper withAllSuperclassesDo:[:cl| (cl instVarNames includes: iv) ifTrue:[temp := cl]]. self error: iv,' is already defined in ', temp name. ^false]]]. oldClass == nil ifFalse:[ usedNames := Set new: 20. oldClass allSubclassesDo:[:cl| usedNames addAll: cl instVarNames]. instVars := instVarArray. newSuper == nil ifFalse:[instVars := instVars, newSuper allInstVarNames]. instVars do:[:iv| (usedNames includes: iv) ifTrue:[ self error: iv, ' is already defined in a subclass of ', oldClass name. ^false]]]. ^true! ! !ClassBuilder methodsFor: 'validation' stamp: 'ar 7/13/2009 21:19'! validateSubclass: subclass canKeepLayoutFrom: oldClass forSubclassFormat: newType "Returns whether the immediate subclasses of oldClass can keep its layout" "Note: Squeak does not appear to model classFormat relationships.. so I'm putting some logic here. bkv 4/2/2003" "Only run this test for a real subclass - otherwise this prevents changing a class from #subclass: to #variableSubclass: etc." subclass = oldClass ifTrue:[^true]. "isWeak implies isVariant" (oldClass isVariable and: [ subclass isWeak ]) ifFalse: [ "In general we discourage format mis-matches" (subclass typeOfClass == newType) ifFalse: [ self error: subclass name,' cannot be recompiled'. ^ false ]]. ^ true! ! !ClassBuilder methodsFor: 'validation' stamp: 'bkv 4/2/2003 17:19'! validateSubclassFormat: newType from: oldClass forSuper: newSuper extra: newInstSize "Validate the # of instVars and the format of the subclasses" | deltaSize | oldClass == nil ifTrue: [^ true]. "No subclasses" "Compute the # of instvars needed for all subclasses" deltaSize := newInstSize. (oldClass notNil) ifTrue: [deltaSize := deltaSize - oldClass instVarNames size]. (newSuper notNil) ifTrue: [deltaSize := deltaSize + newSuper instSize]. (oldClass notNil and: [oldClass superclass notNil]) ifTrue: [deltaSize := deltaSize - oldClass superclass instSize]. (oldClass == nil) ifTrue: [ (deltaSize > 254) ifTrue: [ self error: 'More than 254 instance variables'. ^ false]. ^ true]. oldClass withAllSubclassesDo: [:sub | ( sub instSize + deltaSize > 254 ) ifTrue: [ self error: sub name,' has more than 254 instance variables'. ^ false]. "If we get this far, check whether the immediate subclasses of oldClass can keep its layout." (newType ~~ #normal) ifTrue: [ self validateSubclass: sub canKeepLayoutFrom: oldClass forSubclassFormat: newType ]]. ^ true! ! !ClassBuilder methodsFor: 'validation' stamp: 'ar 7/15/1999 13:50'! validateSuperclass: aSuperClass forSubclass: aClass "Check if it is okay to use aSuperClass as the superclass of aClass" aClass == nil ifTrue:["New class" (aSuperClass == nil or:[aSuperClass isBehavior and:[aSuperClass isMeta not]]) ifFalse:[self error: aSuperClass name,' is not a valid superclass'. ^false]. ^true]. aSuperClass == aClass superclass ifTrue:[^true]. "No change" (aClass isMeta) "Not permitted - meta class hierarchy is derived from class hierarchy" ifTrue:[^self error: aClass name, ' must inherit from ', aClass superclass name]. "Check for circular references" (aSuperClass ~~ nil and:[aSuperClass == aClass or:[aSuperClass inheritsFrom: aClass]]) ifTrue:[self error: aSuperClass name,' inherits from ', aClass name. ^false]. ^true! ! !ClassBuilder methodsFor: 'private' stamp: 'sd 3/28/2008 11:03'! informUserDuring: aBlock self class isSilent ifTrue: [ ^ aBlock value ]. UIManager default informUserDuring: [ :bar | progress := bar. aBlock value ]. progress := nil! ! !ClassBuilder methodsFor: 'private' stamp: 'ar 2/27/2003 22:56'! privateNewSubclassOf: newSuper "Create a new meta and non-meta subclass of newSuper" "WARNING: This method does not preserve the superclass/subclass invariant!!" | newSuperMeta newMeta | newSuperMeta := newSuper ifNil:[Class] ifNotNil:[newSuper class]. newMeta := Metaclass new. newMeta superclass: newSuperMeta methodDictionary: MethodDictionary new format: newSuperMeta format. ^newMeta new ! ! !ClassBuilder methodsFor: 'private' stamp: 'ar 2/27/2003 22:56'! privateNewSubclassOf: newSuper from: oldClass "Create a new meta and non-meta subclass of newSuper using oldClass as template" "WARNING: This method does not preserve the superclass/subclass invariant!!" | newSuperMeta oldMeta newMeta | oldClass ifNil:[^self privateNewSubclassOf: newSuper]. newSuperMeta := newSuper ifNil:[Class] ifNotNil:[newSuper class]. oldMeta := oldClass class. newMeta := oldMeta clone. newMeta superclass: newSuperMeta methodDictionary: MethodDictionary new format: (self computeFormat: oldMeta typeOfClass instSize: oldMeta instVarNames size forSuper: newSuperMeta ccIndex: 0); setInstVarNames: oldMeta instVarNames; organization: oldMeta organization. "Recompile the meta class" oldMeta hasMethods ifTrue:[newMeta compileAllFrom: oldMeta]. "Record the meta class change" self recordClass: oldMeta replacedBy: newMeta. "And create a new instance" ^newMeta adoptInstance: oldClass from: oldMeta! ! !ClassBuilder methodsFor: 'private' stamp: 'NS 1/27/2004 14:21'! recordClass: oldClass replacedBy: newClass "Keep the changes up to date when we're moving instVars around" (instVarMap includesKey: oldClass name) ifTrue:[ SystemChangeNotifier uniqueInstance classDefinitionChangedFrom: oldClass to: newClass. ].! ! !ClassBuilder methodsFor: 'private' stamp: 'gk 2/28/2005 16:35'! reservedNames "Return a list of names that must not be used for variables" ^#('self' 'super' 'thisContext' 'true' 'false' 'nil' self super thisContext #true #false #nil).! ! !ClassBuilder methodsFor: 'private' stamp: 'ar 3/5/2001 12:00'! showProgressFor: aClass "Announce that we're processing aClass" progress == nil ifTrue:[^self]. aClass isObsolete ifTrue:[^self]. currentClassIndex := currentClassIndex + 1. (aClass hasMethods and: [aClass wantsRecompilationProgressReported]) ifTrue: [progress value: ('Recompiling ', aClass name,' (', currentClassIndex printString,'/', maxClassIndex printString,')')]! ! !ClassBuilder methodsFor: 'private' stamp: 'eem 7/21/2008 14:16'! tooDangerousClasses "Return a list of class names which will not be modified in the public interface" ^#( "Object will break immediately" ProtoObject Object "Contexts and their superclasses" InstructionStream ContextPart BlockContext MethodContext BlockClosure "Superclasses of basic collections" Collection SequenceableCollection ArrayedCollection "Collections known to the VM" Array Bitmap String Symbol ByteArray CompiledMethod TranslatedMethod "Basic Numbers" Magnitude Number SmallInteger Float "Misc other" LookupKey Association Link Point Rectangle Behavior PositionableStream UndefinedObject ) ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassBuilder class instanceVariableNames: ''! !ClassBuilder class methodsFor: 'accessing' stamp: 'ar 7/15/1999 18:50'! beSilent: aBool "ClassDefiner beSilent: true" "ClassDefiner beSilent: false" QuietMode := aBool.! ! !ClassBuilder class methodsFor: 'accessing' stamp: 'ar 7/15/1999 18:53'! beSilentDuring: aBlock "Temporarily suppress information about what is going on" | wasSilent result | wasSilent := self isSilent. self beSilent: true. result := aBlock value. self beSilent: wasSilent. ^result! ! !ClassBuilder class methodsFor: 'accessing' stamp: 'ar 7/15/1999 18:48'! isSilent ^QuietMode == true! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'sd 3/28/2008 11:03'! checkClassHierarchyConsistency "Check the consistency of the class hierarchy. The class hierarchy is consistent if the following two logical equivalences hold for classes A and B: - B is obsolete and 'B superclass' yields A <--> 'A obsoleteSubclasses' contains B - B is not obsolete and 'B superclass' yields A <--> 'A subclasses' contains B" UIManager default informUserDuring: [ :bar | self checkClassHierarchyConsistency: bar ]! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'ar 4/23/2002 16:03'! checkClassHierarchyConsistency: informer "Check the consistency of the class hierarchy. The class hierarchy is consistent if the following two logical equivalences hold for classes A and B: - B is obsolete and 'B superclass' yields A <--> 'A obsoleteSubclasses' contains B - B is not obsolete and 'B superclass' yields A <--> 'A subclasses' contains B" | classes | Transcript cr; show: 'Start checking the class hierarchy...'. Smalltalk garbageCollect. classes := Metaclass allInstances. classes keysAndValuesDo: [:index :meta | informer value:'Validating class hierarchy ', (index * 100 // classes size) printString,'%'. meta allInstances do: [:each | self checkClassHierarchyConsistencyFor: each]. self checkClassHierarchyConsistencyFor: meta. ]. Transcript show: 'OK'.! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'NS 2/19/2002 11:48'! checkClassHierarchyConsistencyFor: aClassDescription "Check whether aClassDescription has a consistent superclass and consistent regular and obsolete subclasses" | mySuperclass | mySuperclass := aClassDescription superclass. (mySuperclass subclasses includes: aClassDescription) = aClassDescription isObsolete ifTrue: [self error: 'Something wrong!!']. mySuperclass ifNil: [^ self]. "Obsolete subclasses of nil cannot be stored" (mySuperclass obsoleteSubclasses includes: aClassDescription) = aClassDescription isObsolete ifFalse: [self error: 'Something wrong!!']. aClassDescription subclasses do: [:each | each isObsolete ifTrue: [self error: 'Something wrong!!']. each superclass == aClassDescription ifFalse: [self error: 'Something wrong!!'] ]. aClassDescription obsoleteSubclasses do: [:each | each isObsolete ifFalse: [self error: 'Something wrong!!']. each superclass == aClassDescription ifFalse: [self error: 'Something wrong!!'] ].! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'sd 3/28/2008 11:03'! cleanupAndCheckClassHierarchy "Makes the class hierarchy consistent and removes obsolete classes from the SystemDictionary. Afterwards it checks whether the hierarchy is really consistent." UIManager default informUserDuring: [ :bar | self cleanupAndCheckClassHierarchy: bar ]! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'ar 4/23/2002 15:58'! cleanupAndCheckClassHierarchy: informer "Makes the class hierarchy consistent and removes obsolete classes from the SystemDictionary. Afterwards it checks whether the hierarchy is really consistent." Transcript cr; show: '*** Before cleaning up ***'. self countReallyObsoleteClassesAndMetaclasses. self cleanupClassHierarchy: informer. self checkClassHierarchyConsistency: informer. Transcript cr; cr; show: '*** After cleaning up ***'. self countReallyObsoleteClassesAndMetaclasses.! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'sd 3/28/2008 11:03'! cleanupClassHierarchy "Makes the class hierarchy consistent and removes obsolete classes from the SystemDictionary." UIManager default informUserDuring: [ :bar | self cleanupClassHierarchy: bar ]! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'ar 4/23/2002 16:02'! cleanupClassHierarchy: informer "Makes the class hierarchy consistent and removes obsolete classes from the SystemDictionary." | classes | Transcript cr; show: 'Start fixing the class hierarchy and cleaning up...'. Smalltalk garbageCollect. classes := Metaclass allInstances. classes keysAndValuesDo: [:index :meta | informer value:'Fixing class hierarchy ', (index * 100 // classes size) printString,'%'. "Check classes before metaclasses (because Metaclass>>isObsolete checks whether the related class is obsolete)" meta allInstances do: [:each | self cleanupClassHierarchyFor: each]. self cleanupClassHierarchyFor: meta. ]. Transcript show: 'DONE'.! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'NS 5/8/2002 10:55'! cleanupClassHierarchyFor: aClassDescription | myName mySuperclass | mySuperclass := aClassDescription superclass. (self isReallyObsolete: aClassDescription) ifTrue: [ "Remove class >>>from SystemDictionary if it is obsolete" myName := aClassDescription name asString. Smalltalk keys asArray do: [:each | (each asString = myName and: [(Smalltalk at: each) == aClassDescription]) ifTrue: [Smalltalk removeKey: each]]. "Make class officially obsolete if it is not" (aClassDescription name asString beginsWith: 'AnObsolete') ifFalse: [aClassDescription obsolete]. aClassDescription isObsolete ifFalse: [self error: 'Something wrong!!']. "Add class to obsoleteSubclasses of its superclass" mySuperclass ifNil: [self error: 'Obsolete subclasses of nil cannot be stored']. (mySuperclass obsoleteSubclasses includes: aClassDescription) ifFalse: [mySuperclass addObsoleteSubclass: aClassDescription]. ] ifFalse:[ "check if superclass has aClassDescription in its obsolete subclasses" mySuperclass ifNil:[mySuperclass := Class]. "nil subclasses" mySuperclass removeObsoleteSubclass: aClassDescription. ]. "And remove its obsolete subclasses if not actual superclass" aClassDescription obsoleteSubclasses do:[:obs| obs superclass == aClassDescription ifFalse:[ aClassDescription removeObsoleteSubclass: obs]]. ! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'NS 2/19/2002 11:49'! countReallyObsoleteClassesAndMetaclasses "Counting really obsolete classes and metaclasses" | metaSize classSize | Smalltalk garbageCollect. metaSize := self reallyObsoleteMetaclasses size. Transcript cr; show: 'Really obsolete metaclasses: ', metaSize printString. classSize := self reallyObsoleteClasses size. Transcript cr; show: 'Really obsolete classes: ', classSize printString; cr. "Metaclasses must correspond to classes!!" metaSize ~= classSize ifTrue: [self error: 'Serious metalevel inconsistency!!!!'].! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'NS 2/19/2002 11:49'! isReallyObsolete: aClassDescription "Returns whether the argument class is *really* obsolete. (Due to a bug, the method isObsolete isObsolete does not always return the right answer" ^ aClassDescription isObsolete or: [(aClassDescription superclass subclasses includes: aClassDescription) not]! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'NS 2/15/2002 16:52'! reallyObsoleteClasses | obsoleteClasses | obsoleteClasses := OrderedCollection new. Metaclass allInstances do: [:meta | meta allInstances do: [:each | (self isReallyObsolete: each) ifTrue: [obsoleteClasses add: each]]]. ^ obsoleteClasses! ! !ClassBuilder class methodsFor: 'cleanup obsolete classes' stamp: 'NS 2/15/2002 16:52'! reallyObsoleteMetaclasses ^ Metaclass allInstances select: [:each | self isReallyObsolete: each].! ! TestCase subclass: #ClassBuilderChangeClassTypeTest instanceVariableNames: 'baseClass subClass' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Classes'! !ClassBuilderChangeClassTypeTest methodsFor: 'utilities' stamp: 'BG 1/5/2004 22:49'! baseClassName ^'TestClassForClassChangeTest'! ! !ClassBuilderChangeClassTypeTest methodsFor: 'utilities' stamp: 'BG 1/5/2004 22:51'! cleanup baseClass ifNotNil:[baseClass removeFromSystem].! ! TestCase subclass: #ClassBuilderFormatTests instanceVariableNames: 'baseClass subClass' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Classes'! !ClassBuilderFormatTests methodsFor: 'testing' stamp: 'ar 1/4/2004 20:21'! testByteVariableSubclass "Ensure that the invariants for superclass/subclass format are preserved" baseClass := Object variableByteSubclass: self baseClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'. [ self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error. self deny: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self assert: (subClass isBytes). subClass removeFromSystem. "pointer classes" self should:[self makeIVarsSubclassOf: baseClass] raise: Error. self should:[self makeVariableSubclassOf: baseClass] raise: Error. self should:[self makeWeakSubclassOf: baseClass] raise: Error. "bit classes" self shouldnt:[self makeByteVariableSubclassOf: baseClass] raise: Error. self deny: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self assert: (subClass isBytes). subClass removeFromSystem. self should:[self makeWordVariableSubclassOf: baseClass] raise: Error. ] ensure:[self cleanup].! ! !ClassBuilderFormatTests methodsFor: 'testing' stamp: 'ar 7/13/2009 21:18'! testChangeToVariableSubclass "Ensure that the invariants for superclass/subclass format are preserved" baseClass := Object subclass: self baseClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'. [ self shouldnt:[baseClass := Object variableSubclass: self baseClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'] raise: Error. ] ensure:[self cleanup].! ! !ClassBuilderFormatTests methodsFor: 'testing' stamp: 'ar 1/4/2004 20:20'! testSubclass "Ensure that the invariants for superclass/subclass format are preserved" baseClass := Object subclass: self baseClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'. [ self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self deny: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. "pointer classes" self shouldnt:[self makeIVarsSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self deny: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeVariableSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert:(subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeWeakSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert:(subClass isVariable). self assert:(subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. "bit classes" self shouldnt:[self makeByteVariableSubclassOf: baseClass] raise: Error. self deny: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self assert: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeWordVariableSubclassOf: baseClass] raise: Error. self deny: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. ] ensure:[self cleanup].! ! !ClassBuilderFormatTests methodsFor: 'testing' stamp: 'ar 1/4/2004 20:21'! testSubclassWithInstanceVariables "Ensure that the invariants for superclass/subclass format are preserved" baseClass := Object subclass: self baseClassName instanceVariableNames: 'var1 var2' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'. [ self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self deny: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. "pointer classes" self shouldnt:[self makeIVarsSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self deny: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeVariableSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeWeakSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self assert: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. "bit classes" self should:[self makeByteVariableSubclassOf: baseClass] raise: Error. self should:[self makeWordVariableSubclassOf: baseClass] raise: Error. ] ensure:[self cleanup].! ! !ClassBuilderFormatTests methodsFor: 'testing' stamp: 'ar 1/4/2004 20:20'! testVariableSubclass "Ensure that the invariants for superclass/subclass format are preserved" baseClass := Object variableSubclass: self baseClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'. [ "pointer classes" self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeIVarsSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeVariableSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeWeakSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self assert: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. "bit classes" self should:[self makeByteVariableSubclassOf: baseClass] raise: Error. self should:[self makeWordVariableSubclassOf: baseClass] raise: Error. ] ensure:[self cleanup].! ! !ClassBuilderFormatTests methodsFor: 'testing' stamp: 'ar 1/4/2004 20:20'! testWeakSubclass "Ensure that the invariants for superclass/subclass format are preserved" baseClass := Object weakSubclass: self baseClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'. [ "pointer classes" self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self assert: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeIVarsSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self assert: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeVariableSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. self shouldnt:[self makeWeakSubclassOf: baseClass] raise: Error. self assert: (subClass isPointers). self assert: (subClass isVariable). self assert: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. "bit classes" self should:[self makeByteVariableSubclassOf: baseClass] raise: Error. self should:[self makeWordVariableSubclassOf: baseClass] raise: Error. ] ensure:[self cleanup].! ! !ClassBuilderFormatTests methodsFor: 'testing' stamp: 'ar 1/4/2004 20:20'! testWordVariableSubclass "Ensure that the invariants for superclass/subclass format are preserved" baseClass := Object variableWordSubclass: self baseClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'. [ self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error. self deny: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. "pointer classes" self should:[self makeIVarsSubclassOf: baseClass] raise: Error. self should:[self makeVariableSubclassOf: baseClass] raise: Error. self should:[self makeWeakSubclassOf: baseClass] raise: Error. "bit classes" self should:[self makeByteVariableSubclassOf: baseClass] raise: Error. self shouldnt:[self makeWordVariableSubclassOf: baseClass] raise: Error. self deny: (subClass isPointers). self assert: (subClass isVariable). self deny: (subClass isWeak). self deny: (subClass isBytes). subClass removeFromSystem. ] ensure:[self cleanup].! ! !ClassBuilderFormatTests methodsFor: 'utilities' stamp: 'ar 1/4/2004 20:15'! baseClassName ^#DummyClassBuilderFormatTestSuperClass! ! !ClassBuilderFormatTests methodsFor: 'utilities' stamp: 'ar 1/4/2004 20:15'! cleanup subClass ifNotNil:[subClass removeFromSystem]. baseClass ifNotNil:[baseClass removeFromSystem].! ! !ClassBuilderFormatTests methodsFor: 'utilities' stamp: 'ar 1/4/2004 20:15'! makeByteVariableSubclassOf: aClass subClass := aClass variableByteSubclass: self subClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'! ! !ClassBuilderFormatTests methodsFor: 'utilities' stamp: 'ar 1/4/2004 20:15'! makeIVarsSubclassOf: aClass subClass := aClass subclass: self subClassName instanceVariableNames: 'var3 var4' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'! ! !ClassBuilderFormatTests methodsFor: 'utilities' stamp: 'ar 1/4/2004 20:15'! makeNormalSubclassOf: aClass subClass := aClass subclass: self subClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'! ! !ClassBuilderFormatTests methodsFor: 'utilities' stamp: 'ar 1/4/2004 20:15'! makeVariableSubclassOf: aClass subClass := aClass variableSubclass: self subClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'.! ! !ClassBuilderFormatTests methodsFor: 'utilities' stamp: 'ar 1/4/2004 20:16'! makeWeakSubclassOf: aClass subClass := aClass weakSubclass: self subClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'! ! !ClassBuilderFormatTests methodsFor: 'utilities' stamp: 'ar 1/4/2004 20:16'! makeWordVariableSubclassOf: aClass subClass := aClass variableWordSubclass: self subClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Tests-ClassBuilder'! ! !ClassBuilderFormatTests methodsFor: 'utilities' stamp: 'ar 1/4/2004 20:16'! subClassName ^#DummyClassBuilderFormatTestSubClass! ! Object subclass: #ClassCategoryReader instanceVariableNames: 'class category changeStamp' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Classes'! !ClassCategoryReader commentStamp: '' prior: 0! I represent a mechanism for retrieving class descriptions stored on a file.! !ClassCategoryReader methodsFor: 'fileIn/Out' stamp: 'al 11/28/2005 22:10'! scanFrom: aStream "File in methods from the stream, aStream." | methodText | [methodText := aStream nextChunkText. methodText size > 0] whileTrue: [class compile: methodText classified: category withStamp: changeStamp notifying: nil]! ! !ClassCategoryReader methodsFor: 'fileIn/Out' stamp: 'tk 1/27/2000 23:24'! scanFromNoCompile: aStream "Just move the source code for the methods from aStream." | methodText selector | [methodText := aStream nextChunkText. methodText size > 0] whileTrue: [(SourceFiles at: 2) ifNotNil: [ selector := class parserClass new parseSelector: methodText. (class compiledMethodAt: selector) putSource: methodText fromParseNode: nil class: class category: category withStamp: changeStamp inFile: 2 priorMethod: nil]]! ! !ClassCategoryReader methodsFor: 'fileIn/Out' stamp: 'RAA 6/22/2000 16:08'! scanFromNoCompile: aStream forSegment: anImageSegment ^self scanFromNoCompile: aStream "subclasses may care about the segment"! ! !ClassCategoryReader methodsFor: 'private' stamp: '6/5/97 di'! setClass: aClass category: aCategory ^ self setClass: aClass category: aCategory changeStamp: String new ! ! !ClassCategoryReader methodsFor: 'private' stamp: '6/5/97 di'! setClass: aClass category: aCategory changeStamp: aString class := aClass. category := aCategory. changeStamp := aString ! ! !ClassCategoryReader methodsFor: 'private' stamp: 'ajh 1/18/2002 01:14'! theClass ^ class! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassCategoryReader class instanceVariableNames: ''! Object subclass: #ClassChangeRecord instanceVariableNames: 'inForce revertable changeTypes thisDefinition priorDefinition thisName priorName thisOrganization priorOrganization thisComment priorComment thisMD priorMD methodChanges' classVariableNames: '' poolDictionaries: '' category: 'System-Changes'! !ClassChangeRecord commentStamp: '' prior: 0! A ClassChangeRecorder keeps track of most substantive changes premissible in a project, isolated or not. Structure: inForce a boolean Tells whether these changes are in effect. true for all changeSets in and above the current project. It should be sufficient only to record this for the changeSet as a whole, but this redundancy could help in error recovery. classIsLocal a boolean True if and only if this class is defined in this layer of the project structure. changeTypes an identitySet Summarizes which changes have been made in this class. Values include #comment, #reorganize, #rename, and the four more summarized below. thisName a string Retains the class name for this layer. priorName a string Preserves the prior name. thisComment a text Retains the class comment for this layer. priorComment a text Preserves the prior comment. thisOrganization a classOrganizer Retains the class organization for this layer. priorOrganization a classOrganizer Preserves the prior organization. thisMD a methodDictionary Used to prepare changes for nearly atomic invocation of this layer (see below). priorMD a methodDictionary Preserves the state of an altered class as it exists in the next outer layer of the project structure. methodChanges a dictionary of classChangeRecords Retains all the method changes for this layer. Four of the possible changeTypes are maintained in a mutually exclusive set, analogously to MethodChangeRecords. Here is a simple summary of the relationship between these four changeType symbols and the recording of prior state | prior == nil | prior not nil --------- |---------------------------- |-------------------- add | add | change --------- |---------------------------- |-------------------- remove | addedThenRemoved | remove A classChangeRecorder is notified of changes by the method noteMethodChange: . ClassChangeRecorders are designed to invoke a set of changes relative to the definition of a class in an prior layer. It is important that both invocation and revocation of these changes take place in a nearly atomic fashion so that interdependent changes will be adopted as a whole, and so that only one flush of the method cache should be necessary. A further reason for revocation to be simple is that it may be requested as an attempt to recover from an error in a project that is failing.! !ClassChangeRecord methodsFor: 'all changes' stamp: 'di 4/2/2000 21:39'! allChangeTypes | chgs | (priorName ~~ nil and: [changeTypes includes: #rename]) ifTrue: [(chgs := changeTypes copy) add: 'oldName: ' , priorName. ^ chgs]. ^ changeTypes! ! !ClassChangeRecord methodsFor: 'all changes' stamp: 'di 4/2/2000 21:59'! assimilateAllChangesIn: otherRecord | selector changeRecord changeType | otherRecord isClassRemoval ifTrue: [^ self noteChangeType: #remove]. otherRecord allChangeTypes do: [:chg | self noteChangeType: chg fromClass: self realClass]. otherRecord methodChanges associationsDo: [:assn | selector := assn key. changeRecord := assn value. changeType := changeRecord changeType. (changeType == #remove or: [changeType == #addedThenRemoved]) ifTrue: [changeType == #addedThenRemoved ifTrue: [self atSelector: selector put: #add]. self noteRemoveSelector: selector priorMethod: nil lastMethodInfo: changeRecord methodInfoFromRemoval] ifFalse: [self atSelector: selector put: changeType]]. ! ! !ClassChangeRecord methodsFor: 'all changes' stamp: 'di 3/28/2000 10:59'! hasNoChanges ^ changeTypes isEmpty and: [methodChanges isEmpty]! ! !ClassChangeRecord methodsFor: 'all changes' stamp: 'di 3/24/2000 09:36'! includesChangeType: changeType changeType == #new ifTrue: [^ changeTypes includes: #add]. "Backwd compat" ^ changeTypes includes: changeType! ! !ClassChangeRecord methodsFor: 'all changes' stamp: 'di 3/28/2000 15:14'! noteChangeType: changeSymbol ^ self noteChangeType: changeSymbol fromClass: nil! ! !ClassChangeRecord methodsFor: 'all changes' stamp: 'sw 4/3/2001 14:16'! noteChangeType: changeSymbol fromClass: class (changeSymbol = #new or: [changeSymbol = #add]) ifTrue: [changeTypes add: #add. changeTypes remove: #change ifAbsent: []. revertable := false. ^ self]. changeSymbol = #change ifTrue: [(changeTypes includes: #add) ifTrue: [^ self]. ^ changeTypes add: changeSymbol]. changeSymbol == #addedThenRemoved ifTrue: [^ self]. "An entire class was added but then removed" changeSymbol = #comment ifTrue: [^ changeTypes add: changeSymbol]. changeSymbol = #reorganize ifTrue: [^ changeTypes add: changeSymbol]. changeSymbol = #rename ifTrue: [^ changeTypes add: changeSymbol]. (changeSymbol beginsWith: 'oldName: ') ifTrue: ["Must only be used when assimilating other changeSets" (changeTypes includes: #add) ifTrue: [^ self]. priorName := changeSymbol copyFrom: 'oldName: ' size + 1 to: changeSymbol size. ^ changeTypes add: #rename]. changeSymbol = #remove ifTrue: [(changeTypes includes: #add) ifTrue: [changeTypes add: #addedThenRemoved] ifFalse: [changeTypes add: #remove]. ^ changeTypes removeAllFoundIn: #(add change comment reorganize)]. self error: 'Unrecognized changeType'! ! !ClassChangeRecord methodsFor: 'all changes' stamp: 'di 5/16/2000 08:43'! trimHistory "Drop non-essential history." "Forget methods added and later removed" methodChanges keysAndValuesRemove: [:sel :chgRecord | chgRecord changeType == #addedThenRemoved]. "Forget renaming and reorganization of newly-added classes." (changeTypes includes: #add) ifTrue: [changeTypes removeAllFoundIn: #(rename reorganize)]. ! ! !ClassChangeRecord methodsFor: 'definition' stamp: 'di 3/27/2000 22:06'! checkCoherence "If I recreate the class then don't remove it" (changeTypes includes: #remove) ifTrue: [changeTypes remove: #remove. changeTypes add: #change]. (changeTypes includes: #addedThenRemoved) ifTrue: [changeTypes remove: #addedThenRemoved. changeTypes add: #add]. ! ! !ClassChangeRecord methodsFor: 'definition' stamp: 'di 3/27/2000 22:08'! notePriorDefinition: oldClass oldClass ifNil: [^ self]. priorDefinition ifNil: [priorDefinition := oldClass definition]! ! !ClassChangeRecord methodsFor: 'definition' stamp: 'di 3/28/2000 09:12'! priorDefinition ^ priorDefinition! ! !ClassChangeRecord methodsFor: 'initialization' stamp: 'di 4/5/2000 08:11'! initFor: className revertable: isRevertable inForce := isRevertable. changeTypes := IdentitySet new. methodChanges := IdentityDictionary new. priorName := thisName := className. revertable := isRevertable and: [self realClass notNil]. revertable ifTrue: [priorMD := self realClass methodDict copy. priorOrganization := self realClass organization deepCopy]. ! ! !ClassChangeRecord methodsFor: 'initialization' stamp: 'di 9/21/2000 12:34'! zapHistory "Drop all recorded information not needed to simply keep track of what has been changed. Saves a lot of space." methodChanges do: [:r | r noteNewMethod: nil]. "Drop all refes to old methods" thisOrganization := nil. priorOrganization := nil. thisComment := nil. priorComment := nil. thisMD := nil. priorMD := nil.! ! !ClassChangeRecord methodsFor: 'isolation layers' stamp: 'eem 6/11/2008 16:51'! invokePhase1 | elements | revertable ifFalse: [^ self]. inForce ifTrue: [self error: 'Can invoke only when not in force.']. "Do the first part of the invoke operation -- no particular hurry." "Save the outer method dictionary for quick revert of method changes." priorMD := self realClass methodDict. "Prepare a methodDictionary for switcheroo." thisMD := self realClass methodDict copy. methodChanges associationsDo: [:assn | | selector changeRecord type | selector := assn key. changeRecord := assn value. type := changeRecord changeType. type = #remove ifTrue: [thisMD removeKey: selector]. type = #add ifTrue: [thisMD at: selector put: changeRecord currentMethod]. type = #change ifTrue: [thisMD at: selector put: changeRecord currentMethod]. ]. "Replace the original organization (and comment)." priorOrganization := self realClass organization. thisOrganization elementArray copy do: [:sel | (thisMD includesKey: sel) ifFalse: [thisOrganization removeElement: sel]]. #(DoIt DoItIn:) do: [:sel | thisMD removeKey: sel ifAbsent: []]. thisOrganization elementArray size = thisMD size ifFalse: [elements := thisOrganization elementArray asSet. thisMD keysDo: [:sel | (elements includes: sel) ifFalse: [thisOrganization classify: sel under: (priorOrganization categoryOfElement: sel)]]]. self realClass organization: thisOrganization. ! ! !ClassChangeRecord methodsFor: 'isolation layers' stamp: 'di 3/29/2000 14:50'! invokePhase2 revertable ifFalse: [^ self]. "Do the second part of the revert operation. This must be very simple." "Replace original method dicts if there are method changes." self realClass methodDictionary: thisMD. "zap. Must flush Cache in outer loop." inForce := true. ! ! !ClassChangeRecord methodsFor: 'isolation layers' stamp: 'di 3/30/2000 18:03'! realClass "Return the actual class (or meta), as determined from my name." thisName ifNil: [^ nil]. (thisName endsWith: ' class') ifTrue: [^ (Smalltalk at: (thisName copyFrom: 1 to: thisName size - 6) asSymbol ifAbsent: [^ nil]) class] ifFalse: [^ Smalltalk at: thisName ifAbsent: [^ nil]]! ! !ClassChangeRecord methodsFor: 'isolation layers' stamp: 'di 3/29/2000 14:50'! revokePhase1 revertable ifFalse: [^ self]. inForce ifFalse: [self error: 'Can revoke only when in force.']. "Do the first part of the revoke operation. This must be very simple." "Replace original method dict if there are method changes." self realClass methodDictionary: priorMD "zap. Must flush Cache in outer loop."! ! !ClassChangeRecord methodsFor: 'isolation layers' stamp: 'di 3/29/2000 14:50'! revokePhase2 revertable ifFalse: [^ self]. "Replace the original organization (and comment)." thisOrganization := self realClass organization. self realClass organization: priorOrganization. inForce := false. ! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'di 3/28/2000 10:38'! atSelector: selector ifAbsent: absentBlock ^ (methodChanges at: selector ifAbsent: absentBlock) changeType! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'di 3/28/2000 11:01'! atSelector: selector put: changeType (self findOrMakeMethodChangeAt: selector priorMethod: nil) noteChangeType: changeType! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'di 3/28/2000 10:07'! changedSelectors "Return a set of the changed or removed selectors." ^ methodChanges keys! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'eem 6/11/2008 16:50'! compileAll: newClass from: oldClass "Something about this class has changed. Locally retained methods must be recompiled. NOTE: You might think that if this changeSet is in force, then we can just note the new methods but a lower change set may override and be in force which would mean that only the overriding copies go recompiled. Just do it." methodChanges associationsDo: [:assn | | sel changeType changeRecord newMethod | sel := assn key. changeRecord := assn value. changeType := changeRecord changeType. (changeType == #add or: [changeType == #change]) ifTrue: [newMethod := newClass recompileNonResidentMethod: changeRecord currentMethod atSelector: sel from: oldClass. changeRecord noteNewMethod: newMethod]]! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'di 3/28/2000 11:01'! findOrMakeMethodChangeAt: selector priorMethod: priorMethod ^ methodChanges at: selector ifAbsent: [methodChanges at: selector put: (MethodChangeRecord new priorMethod: priorMethod)]! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'di 3/29/2000 16:26'! infoFromRemoval: selector ^ (methodChanges at: selector ifAbsent: [^ nil]) methodInfoFromRemoval ! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'eem 6/11/2008 16:53'! methodChangeTypes "Return an old-style dictionary of method change types." | dict | dict := IdentityDictionary new. methodChanges associationsDo: [:assn | | selector record | selector := assn key. record := assn value. dict at: selector put: record changeType]. ^ dict! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'di 4/1/2000 23:49'! methodChanges ^ methodChanges! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'di 3/28/2000 23:28'! noteNewMethod: newMethod selector: selector priorMethod: methodOrNil | methodChange | methodChange := self findOrMakeMethodChangeAt: selector priorMethod: methodOrNil. methodOrNil == nil ifTrue: [methodChange noteChangeType: #add] ifFalse: [methodChange noteChangeType: #change]. methodChange noteNewMethod: newMethod. ! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'di 3/23/2000 23:00'! noteRemoveSelector: selector priorMethod: priorMethod lastMethodInfo: infoOrNil | methodChange | methodChange := self findOrMakeMethodChangeAt: selector priorMethod: priorMethod. methodChange changeType == #add ifTrue: [methodChange noteChangeType: #addedThenRemoved] ifFalse: [methodChange noteChangeType: #remove]. infoOrNil ifNotNil: ["Save the source code pointer and category so can still browse old versions" methodChange noteMethodInfoFromRemoval: infoOrNil] ! ! !ClassChangeRecord methodsFor: 'method changes' stamp: 'sw 8/14/2002 11:11'! removeSelector: selector "Remove all memory of changes associated with the argument, selector, in this class." selector == #Comment ifTrue: [changeTypes remove: #comment ifAbsent: []] ifFalse: [methodChanges removeKey: selector ifAbsent: []]! ! !ClassChangeRecord methodsFor: 'removal' stamp: 'eem 6/11/2008 16:50'! forgetChangesIn: otherRecord "See forgetAllChangesFoundIn:. Used in culling changeSets." | cls otherMethodChanges | (cls := self realClass) == nil ifTrue: [^ self]. "We can do better now, though..." otherMethodChanges := otherRecord methodChangeTypes. otherMethodChanges associationsDo: [:assoc | | selector actionToSubtract | selector := assoc key. actionToSubtract := assoc value. (cls includesSelector: selector) ifTrue: [(#(add change) includes: actionToSubtract) ifTrue: [methodChanges removeKey: selector ifAbsent: []]] ifFalse: [(#(remove addedThenRemoved) includes: actionToSubtract) ifTrue: [methodChanges removeKey: selector ifAbsent: []]]]. changeTypes isEmpty ifFalse: [changeTypes removeAllFoundIn: otherRecord allChangeTypes. (changeTypes includes: #rename) ifFalse: [changeTypes removeAllSuchThat: [:x | x beginsWith: 'oldName: ']]]! ! !ClassChangeRecord methodsFor: 'removal' stamp: 'di 3/23/2000 12:27'! forgetClassRemoval self halt.! ! !ClassChangeRecord methodsFor: 'removal' stamp: 'di 4/1/2000 23:05'! isClassRemoval "NOTE: there are other removals with changeType #addedThenRemoved, but this message is used to write out removals in fileOut, and those cases should not be written out." ^ (changeTypes includes: #remove) or: [changeTypes includes: #removeClass]! ! !ClassChangeRecord methodsFor: 'rename' stamp: 'di 5/8/2000 20:39'! noteNewName: newName thisName := newName! ! !ClassChangeRecord methodsFor: 'rename' stamp: 'di 3/24/2000 09:38'! priorName ^ priorName! ! !ClassChangeRecord methodsFor: 'rename' stamp: 'tk 6/8/2001 09:11'! thisName ^ thisName! ! ClassCategoryReader subclass: #ClassCommentReader instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Classes'! !ClassCommentReader methodsFor: 'fileIn/Out' stamp: 'sw 7/31/2002 10:40'! scanFrom: aStream "File in the class comment from aStream. Not string-i-fied, just a text, exactly as it is in the browser. Move to changes file." class theNonMetaClass classComment: (aStream nextChunkText) stamp: changeStamp "Writes it on the disk and saves a RemoteString ref"! ! !ClassCommentReader methodsFor: 'fileIn/Out' stamp: 'tk 1/27/2000 22:56'! scanFromNoCompile: aStream "File in the class comment from aStream. Not string-i-fied, just a text, exactly as it is in the browser. Move to changes file." self scanFrom: aStream. "for comments, the same as usual"! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassCommentReader class instanceVariableNames: ''! !ClassCommentReader class methodsFor: 'instance creation' stamp: 'AndrewBlack 9/1/2009 06:42'! forClass: aClass ^ self new setClass: aClass category: #Comment ! ! VersionsBrowser subclass: #ClassCommentVersionsBrowser instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tools-Changes'! !ClassCommentVersionsBrowser commentStamp: 'asm 8/13/2002 23:20' prior: 0! A class-comment-versions-browser tool! !ClassCommentVersionsBrowser methodsFor: 'basic function' stamp: 'sd 11/20/2005 21:26'! diffedVersionContents "Answer diffed version contents, maybe pretty maybe not" | change class earlier later | (listIndex = 0 or: [changeList size < listIndex]) ifTrue: [^ '']. change := changeList at: listIndex. later := change text. class := self selectedClass. (listIndex == changeList size or: [class == nil]) ifTrue: [^ later]. earlier := (changeList at: listIndex + 1) text. ^ TextDiffBuilder buildDisplayPatchFrom: earlier to: later inClass: class prettyDiffs: self showingPrettyDiffs! ! !ClassCommentVersionsBrowser methodsFor: 'basic function' stamp: 'sd 11/20/2005 21:26'! reformulateList classOfMethod organization classComment ifNil: [^ self]. self scanVersionsOf: classOfMethod. self changed: #list. "for benefit of mvc" listIndex := 1. self changed: #listIndex. self contentsChanged! ! !ClassCommentVersionsBrowser methodsFor: 'basic function' stamp: 'sd 11/20/2005 21:26'! scanVersionsOf: class "Scan for all past versions of the class comment of the given class" | oldCommentRemoteStr sourceFilesCopy position prevPos stamp preamble tokens prevFileIndex | classOfMethod := class. oldCommentRemoteStr := class organization commentRemoteStr. currentCompiledMethod := oldCommentRemoteStr. selectorOfMethod := #Comment. changeList := OrderedCollection new. list := OrderedCollection new. listIndex := 0. oldCommentRemoteStr ifNil:[^ nil] ifNotNil: [oldCommentRemoteStr sourcePointer]. sourceFilesCopy := SourceFiles collect: [:x | x isNil ifTrue: [ nil ] ifFalse: [x readOnlyCopy]]. position := oldCommentRemoteStr position. file := sourceFilesCopy at: oldCommentRemoteStr sourceFileNumber. [position notNil & file notNil] whileTrue: [file position: (0 max: position-150). " Skip back to before the preamble" [file position < (position-1)] "then pick it up from the front" whileTrue: [preamble := file nextChunk]. prevPos := nil. stamp := ''. (preamble findString: 'commentStamp:' startingAt: 1) > 0 ifTrue: [tokens := Scanner new scanTokens: preamble. (tokens at: tokens size-3) = #commentStamp: ifTrue: ["New format gives change stamp and unified prior pointer" stamp := tokens at: tokens size-2. prevPos := tokens last. prevFileIndex := sourceFilesCopy fileIndexFromSourcePointer: prevPos. prevPos := sourceFilesCopy filePositionFromSourcePointer: prevPos]] ifFalse: ["The stamp get lost, maybe after a condenseChanges" stamp := '']. self addItem: (ChangeRecord new file: file position: position type: #classComment class: class name category: nil meta: class stamp: stamp) text: stamp , ' ' , class name , ' class comment'. prevPos = 0 ifTrue:[prevPos := nil]. position := prevPos. prevPos notNil ifTrue:[file := sourceFilesCopy at: prevFileIndex]]. sourceFilesCopy do: [:x | x notNil ifTrue: [x close]]. listSelections := Array new: list size withAll: false! ! !ClassCommentVersionsBrowser methodsFor: 'basic function' stamp: 'sd 11/20/2005 21:26'! updateListsAndCodeIn: aWindow | aComment | aComment := classOfMethod organization commentRemoteStr. aComment == currentCompiledMethod ifFalse: ["Do not attempt to formulate if there is no source pointer. It probably means it has been recompiled, but the source hasn't been written (as during a display of the 'save text simply?' confirmation)." aComment last ~= 0 ifTrue: [self reformulateList]]. ^ true ! ! !ClassCommentVersionsBrowser methodsFor: 'menu' stamp: 'sd 11/20/2005 21:26'! compareToCurrentVersion "If the current selection corresponds to a method in the system, then spawn a window showing the diffs as text" | change s1 s2 | listIndex = 0 ifTrue: [^ self]. change := changeList at: listIndex. s1 := classOfMethod organization classComment. s2 := change string. s1 = s2 ifTrue: [^ self inform: 'Exact Match']. (StringHolder new textContents: (TextDiffBuilder buildDisplayPatchFrom: s1 to: s2 inClass: classOfMethod prettyDiffs: self showingPrettyDiffs)) openLabel: 'Comparison to Current Version'! ! !ClassCommentVersionsBrowser methodsFor: 'menu' stamp: 'asm 8/13/2002 21:02'! offerVersionsHelp (StringHolder new contents: self versionsHelpString) openLabel: 'Class Comment Versions Browsers'! ! !ClassCommentVersionsBrowser methodsFor: 'menu' stamp: 'sd 11/20/2005 21:26'! openSingleMessageBrowser | mr | "Create and schedule a message list browser populated only by the currently selected message" mr := MethodReference new setStandardClass: self selectedClass methodSymbol: #Comment. self systemNavigation browseMessageList: (Array with: mr) name: mr asStringOrText autoSelect: nil! ! !ClassCommentVersionsBrowser methodsFor: 'menu' stamp: 'alain.plantec 5/30/2008 11:20'! versionsMenu: aMenu "Fill aMenu with menu items appropriate to the receiver" aMenu title: 'versions'. aMenu addStayUpItemSpecial. ^ aMenu addList: #( ('compare to current' compareToCurrentVersion 'compare selected version to the current version') ('revert to selected version' fileInSelections 'resubmit the selected version, so that it becomes the current version') ('remove from changes' removeMethodFromChanges 'remove this method from the current change set, if present') ('edit current method (O)' openSingleMessageBrowser 'open a single-message browser on the current version of this method') - ('toggle diffing (D)' toggleDiffing 'toggle whether or not diffs should be shown here') ('update list' reformulateList 'reformulate the list of versions, in case it somehow got out of synch with reality') - ('help...' offerVersionsHelp 'provide an explanation of the use of this tool')) ! ! !ClassCommentVersionsBrowser methodsFor: 'misc' stamp: 'sw 8/17/2002 21:57'! classCommentIndicated "Answer whether the receiver is pointed at a class comment" ^ true! ! !ClassCommentVersionsBrowser methodsFor: 'misc' stamp: 'sw 8/15/2002 22:38'! contentsSymbolQuints "Answer a list of quintuplets representing information on the alternative views available in the code pane" ^ #( (source togglePlainSource showingPlainSourceString 'source' 'the textual source code as writen') (showDiffs toggleRegularDiffing showingRegularDiffsString 'showDiffs' 'the textual source diffed from its prior version'))! ! !ClassCommentVersionsBrowser methodsFor: 'misc' stamp: 'sd 11/20/2005 21:26'! priorSourceOrNil "If the currently-selected method has a previous version, return its source, else return nil" | aClass aSelector changeRecords | (aClass := self selectedClass) ifNil: [^ nil]. (aSelector := self selectedMessageName) ifNil: [^ nil]. changeRecords := self class commentRecordsOf: self selectedClass. (changeRecords == nil or: [changeRecords size <= 1]) ifTrue: [^ nil]. ^ (changeRecords at: 2) string ! ! !ClassCommentVersionsBrowser methodsFor: 'misc' stamp: 'asm 8/13/2002 20:59'! selectedClass "Answer the class currently selected in the browser. In the case of a VersionsBrowser, the class and selector are always the same, regardless of which version is selected and indeed whether or not any entry is selected in the list pane" ^ classOfMethod! ! !ClassCommentVersionsBrowser methodsFor: 'misc' stamp: 'sw 8/15/2002 22:35'! wantsPrettyDiffOption "Answer whether pretty-diffs are meaningful for this tool" ^ false! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassCommentVersionsBrowser class instanceVariableNames: ''! !ClassCommentVersionsBrowser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! browseCommentOf: class | changeList | Cursor read showWhile: [changeList := self new scanVersionsOf: class. changeList ifNil: [^ self inform: 'No versions available']. self open: changeList name: 'Recent versions of ',class name,'''s comments' multiSelect: false ] ! ! !ClassCommentVersionsBrowser class methodsFor: 'utilities' stamp: 'sd 11/20/2005 21:28'! commentRecordsOf: aClass "Return a list of ChangeRecords for all versions of the method at selector. Source code can be retrieved by sending string to any one. Return nil if the method is absent." | aList | aList := self new scanVersionsOf: aClass. ^ aList ifNotNil: [aList changeList]! ! !ClassCommentVersionsBrowser class methodsFor: 'utilities' stamp: 'sd 11/20/2005 21:28'! timeStampFor: aSelector class: aClass reverseOrdinal: anInteger "Answer the time stamp corresponding to some version of the given method, nil if none. The reverseOrdinal parameter is interpreted as: 1 = current version; 2 = last-but-one version, etc." | aChangeList | aChangeList := self new scanVersionsOf: aClass. ^ aChangeList ifNil: [nil] ifNotNil: [aChangeList list size >= anInteger ifTrue: [(aChangeList changeList at: anInteger) stamp] ifFalse: [nil]]! ! !ClassCommentVersionsBrowser class methodsFor: 'window color' stamp: 'asm 8/13/2002 20:57'! windowColorSpecification "Answer a WindowColorSpec object that declares my preference" ^ WindowColorSpec classSymbol: self name wording: 'Class Comment Versions Browser' brightColor: #(0.769 0.653 1.0) pastelColor: #(0.819 0.753 1.0) helpMessage: 'A tool for viewing prior versions of a class comment.'! ! Behavior subclass: #ClassDescription uses: TClassAndTraitDescription instanceVariableNames: 'instanceVariables organization' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Classes'! !ClassDescription commentStamp: '' prior: 0! I add a number of facilities to basic Behaviors: Named instance variables Category organization for methods The notion of a name of this class (implemented as subclass responsibility) The maintenance of a ChangeSet, and logging changes on a file Most of the mechanism for fileOut. I am an abstract class, in particular, my facilities are intended for inheritance by two subclasses, Class and Metaclass. The slots 'organization' and 'methodDict' should ONLY be accessed by message in order for things to work during ImageSegment>>discoverActiveClasses (q.v.).! !ClassDescription methodsFor: '*system-support' stamp: 'dvf 8/23/2003 12:45'! allUnreferencedClassVariables "Answer a list of the names of all the receiver's unreferenced class vars, including those defined in superclasses" ^ self systemNavigation allUnreferencedClassVariablesOf: self! ! !ClassDescription methodsFor: 'accessing' stamp: 'sd 6/27/2003 23:57'! classVersion "Default. Any class may return a later version to inform readers that use ReferenceStream. 8/17/96 tk" "This method allows you to distinguish between class versions when the shape of the class hasn't changed (when there's no change in the instVar names). In the conversion methods you usually can tell by the inst var names what old version you have. In a few cases, though, the same inst var names were kept but their interpretation changed (like in the layoutFrame). By changing the class version when you keep the same instVars you can warn older and newer images that they have to convert." ^ 0! ! !ClassDescription methodsFor: 'accessing' stamp: 'NS 12/9/2003 15:12'! version "Allows polymoprhism with TraitDescription>>version" ^ self classVersion! ! !ClassDescription methodsFor: 'accessing class hierarchy' stamp: 'di 2/17/2000 22:36'! classesThatImplementAllOf: selectorSet "Return an array of any classes that implement all the messages in selectorSet." | found remaining | found := OrderedCollection new. selectorSet do: [:sel | (self methodDict includesKey: sel) ifTrue: [found add: sel]]. found isEmpty ifTrue: [^ self subclasses inject: Array new into: [:subsThatDo :sub | subsThatDo , (sub classesThatImplementAllOf: selectorSet)]] ifFalse: [remaining := selectorSet copyWithoutAll: found. remaining isEmpty ifTrue: [^ Array with: self]. ^ self subclasses inject: Array new into: [:subsThatDo :sub | subsThatDo , (sub classesThatImplementAllOf: remaining)]]! ! !ClassDescription methodsFor: 'accessing class hierarchy' stamp: 'dtl 8/26/2004 11:02'! commentInventory "Answer a string with a count of the classes with and without comments for all the classes in the package of which this class is a member." "Morph commentInventory" ^ SystemOrganization commentInventory: (self category copyUpTo: $-), '*'! ! !ClassDescription methodsFor: 'accessing class hierarchy' stamp: 'al 11/28/2005 11:51'! 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." | subclassNames | aStream crtab: level. aStream nextPutAll: self name. aStream space; print: self instVarNames. self == Class ifTrue: [aStream crtab: level + 1; nextPutAll: '[ ... all the Metaclasses ... ]'. ^self]. subclassNames := self subclasses asSortedCollection:[:c1 :c2| c1 name <= c2 name]. "Print subclasses in alphabetical order" subclassNames do: [:subclass | subclass printSubclassesOn: aStream level: level + 1]! ! !ClassDescription methodsFor: 'accessing class hierarchy' stamp: 'al 11/28/2005 11:52'! removeUninstantiatedSubclassesSilently "Remove the classes of any subclasses that have neither instances nor subclasses. Answer the number of bytes reclaimed" "Player removeUninstantiatedSubclassesSilently" | candidatesForRemoval oldFree | oldFree := self environment garbageCollect. candidatesForRemoval := self subclasses select: [:c | (c instanceCount = 0) and: [c subclasses size = 0]]. candidatesForRemoval do: [:c | c removeFromSystem]. ^ self environment garbageCollect - oldFree! ! !ClassDescription methodsFor: 'accessing class hierarchy' stamp: 'al 11/28/2005 11:52'! subclasses ^ Array new! ! !ClassDescription methodsFor: 'accessing class hierarchy' stamp: 'al 11/28/2005 11:52'! subclassesDo: aBlock "Evaluate the argument, aBlock, for each of the receiver's immediate subclasses." ^self subclasses do: aBlock! ! !ClassDescription methodsFor: 'accessing comment' stamp: 'PeterHugossonMiller 9/3/2009 00:54'! classCommentBlank | existingComment stream | existingComment := self theNonMetaClass organization classComment. existingComment isEmpty ifFalse: [^existingComment]. stream := (String new: 100) writeStream. stream nextPutAll: 'A'; nextPutAll: (self name first isVowel ifTrue: ['n '] ifFalse: [' ']); nextPutAll: self name; nextPutAll: ' is xxxxxxxxx.'; cr; cr; nextPutAll: 'Instance Variables'. self instVarNames asSortedCollection do: [:each | stream cr; tab; nextPutAll: each; nextPut: $:; tab; tab; nextPutAll: '']. stream cr. self instVarNames asSortedCollection do: [:each | stream cr; nextPutAll: each; cr; tab; nextPutAll: '- xxxxx'; cr]. ^stream contents! ! !ClassDescription methodsFor: 'accessing comment'! comment "Answer the receiver's comment. (If missing, supply a template) " | aString | aString := self instanceSide organization classComment. aString isEmpty ifFalse: [^ aString]. ^self classCommentBlank! ! !ClassDescription methodsFor: 'accessing comment'! comment: aStringOrText "Set the receiver's comment to be the argument, aStringOrText." self instanceSide classComment: aStringOrText.! ! !ClassDescription methodsFor: 'accessing comment'! comment: aStringOrText stamp: aStamp "Set the receiver's comment to be the argument, aStringOrText." self instanceSide classComment: aStringOrText stamp: aStamp.! ! !ClassDescription methodsFor: 'accessing comment'! hasComment "return whether this class truly has a comment other than the default" | org | org := self instanceSide organization. ^org classComment isEmptyOrNil not! ! !ClassDescription methodsFor: 'accessing method dictionary'! addAndClassifySelector: selector withMethod: compiledMethod inProtocol: category notifying: requestor | priorMethodOrNil oldProtocol newProtocol | priorMethodOrNil := self compiledMethodAt: selector ifAbsent: [nil]. self addSelectorSilently: selector withMethod: compiledMethod. oldProtocol := self organization categoryOfElement: selector. SystemChangeNotifier uniqueInstance doSilently: [self organization classify: selector under: category]. newProtocol := self organization categoryOfElement: selector. priorMethodOrNil isNil ifTrue: [SystemChangeNotifier uniqueInstance methodAdded: compiledMethod selector: selector inProtocol: category class: self requestor: requestor] ifFalse: [SystemChangeNotifier uniqueInstance methodChangedFrom: priorMethodOrNil to: compiledMethod selector: selector inClass: self oldProtocol: oldProtocol newProtocol: newProtocol requestor: requestor].! ! !ClassDescription methodsFor: 'accessing method dictionary'! addSelectorSilently: selector withMethod: compiledMethod super addSelectorSilently: selector withMethod: compiledMethod. self instanceSide noteAddedSelector: selector meta: self isMeta.! ! !ClassDescription methodsFor: 'accessing method dictionary'! addSelector: selector withMethod: compiledMethod notifying: requestor | priorMethodOrNil | priorMethodOrNil := self compiledMethodAt: selector ifAbsent: [nil]. self addSelectorSilently: selector withMethod: compiledMethod. priorMethodOrNil isNil ifTrue: [SystemChangeNotifier uniqueInstance methodAdded: compiledMethod selector: selector inClass: self requestor: requestor] ifFalse: [SystemChangeNotifier uniqueInstance methodChangedFrom: priorMethodOrNil to: compiledMethod selector: selector inClass: self requestor: requestor].! ! !ClassDescription methodsFor: 'accessing method dictionary' stamp: 'sw 1/5/2001 06:53'! allMethodCategoriesIntegratedThrough: mostGenericClass "Answer a list of all the method categories of the receiver and all its superclasses, up through mostGenericClass" | aColl | aColl := OrderedCollection new. self withAllSuperclasses do: [:aClass | (aClass includesBehavior: mostGenericClass) ifTrue: [aColl addAll: aClass organization categories]]. aColl remove: 'no messages' asSymbol ifAbsent: []. ^ (aColl asSet asSortedCollection: [:a :b | a asLowercase < b asLowercase]) asArray "ColorTileMorph allMethodCategoriesIntegratedThrough: TileMorph"! ! !ClassDescription methodsFor: 'accessing method dictionary' stamp: 'nice 3/22/2008 01:21'! allMethodsInCategory: aName "Answer a list of all the methods of the receiver and all its superclasses that are in the category named aName" | aColl | aColl := OrderedCollection new. self withAllSuperclasses do: [:aClass | aColl addAll: (aName = ClassOrganizer allCategory ifTrue: [aClass organization allMethodSelectors] ifFalse: [aClass organization listAtCategoryNamed: aName])]. ^ aColl asSet asSortedArray "TileMorph allMethodsInCategory: #initialization"! ! !ClassDescription methodsFor: 'accessing method dictionary' stamp: 'di 2/17/2000 22:17'! induceMDFault "Stache a copy of the methodDict in the organization slot (hack!!), and set the methodDict to nil. This will induce an MD fault on any message send. See: ClassDescription>>recoverFromMDFault and ImageSegment>>discoverActiveClasses." organization := Array with: methodDict with: organization. methodDict := nil. self flushCache! ! !ClassDescription methodsFor: 'accessing method dictionary' stamp: 'nice 3/22/2008 01:21'! methodsInCategory: aName "Answer a list of the methods of the receiver that are in category named aName" | aColl | aColl := Set withAll: (aName = ClassOrganizer allCategory ifTrue: [self organization allMethodSelectors] ifFalse: [self organization listAtCategoryNamed: aName]). ^ aColl asSortedArray "TileMorph methodsInCategory: #initialization"! ! !ClassDescription methodsFor: 'accessing method dictionary'! noteAddedSelector: aSelector meta: isMeta "A hook allowing some classes to react to adding of certain selectors"! ! !ClassDescription methodsFor: 'accessing method dictionary' stamp: 'di 3/7/2001 17:05'! recoverFromMDFault "This method handles methodDict faults to support, eg, discoverActiveClasses (qv)." (organization isMemberOf: Array) ifFalse: [^ self error: 'oops']. methodDict := organization first. organization := organization second. ! ! !ClassDescription methodsFor: 'accessing method dictionary' stamp: 'sd 3/28/2003 15:32'! recoverFromMDFaultWithTrace "This method handles emthodDict faults to support, eg, discoverActiveClasses (qv)." self recoverFromMDFault. self environment at: #MDFaultDict ifPresent: [:faultDict | faultDict at: self name put: (String streamContents: [:strm | (thisContext stackOfSize: 20) do: [:item | strm print: item; cr]])] "Execute the following statement to induce MD fault tracing. This means that, not only will all active classes be recorded but, after a test run, MDFaultDict will contain, for every class used, a stack trace showing how it came to be used. This statement should be executed just prior to any such text, in order to clear the traces. Smalltalk at: #MDFaultDict put: Dictionary new. "! ! !ClassDescription methodsFor: 'accessing method dictionary'! removeCategory: aString "Remove each of the messages categorized under aString in the method dictionary of the receiver. Then remove the category aString." | categoryName | categoryName := aString asSymbol. (self organization listAtCategoryNamed: categoryName) do: [:sel | self removeSelector: sel]. self organization removeCategory: categoryName! ! !ClassDescription methodsFor: 'accessing method dictionary'! removeSelector: selector "Remove the message whose selector is given from the method dictionary of the receiver, if it is there. Answer nil otherwise." | priorMethod priorProtocol | priorMethod := self compiledMethodAt: selector ifAbsent: [^ nil]. priorProtocol := self whichCategoryIncludesSelector: selector. super removeSelector: selector. SystemChangeNotifier uniqueInstance doSilently: [self updateOrganizationSelector: selector oldCategory: priorProtocol newCategory: nil]. SystemChangeNotifier uniqueInstance methodRemoved: priorMethod selector: selector inProtocol: priorProtocol class: self.! ! !ClassDescription methodsFor: 'accessing parallel hierarchy' stamp: 'NS 4/12/2004 15:03'! classSide ^self theMetaClass! ! !ClassDescription methodsFor: 'accessing parallel hierarchy' stamp: 'NS 4/12/2004 15:04'! instanceSide ^ self theNonMetaClass! ! !ClassDescription methodsFor: 'accessing parallel hierarchy'! isClassSide ^self == self classSide! ! !ClassDescription methodsFor: 'accessing parallel hierarchy'! isInstanceSide ^self isClassSide not! ! !ClassDescription methodsFor: 'accessing parallel hierarchy'! isMeta ^self isClassSide! ! !ClassDescription methodsFor: 'accessing parallel hierarchy' stamp: 'sd 6/27/2003 22:50'! theMetaClass "Sent to a class or metaclass, always return the metaclass" ^self class! ! !ClassDescription methodsFor: 'accessing parallel hierarchy'! theNonMetaClass "Sent to a class or metaclass, always return the class" ^self! ! !ClassDescription methodsFor: 'compiling'! acceptsLoggingOfCompilation "Answer whether the receiver's method submisions and class defintions should be logged to the changes file and to the current change set. The metaclass follows the rule of the class itself. 6/18/96 sw" "weird name is so that it will come lexically before #compile, so that a clean build can make it through. 7/7/96 sw" ^ true! ! !ClassDescription methodsFor: 'compiling'! compile: code classified: heading "Compile the argument, code, as source code in the context of the receiver and install the result in the receiver's method dictionary under the classification indicated by the second argument, heading. nil is to be notified if an error occurs. The argument code is either a string or an object that converts to a string or a PositionableStream on an object that converts to a string." ^self compile: code classified: heading notifying: nil! ! !ClassDescription methodsFor: 'compiling'! compile: text classified: category notifying: requestor | stamp | stamp := self acceptsLoggingOfCompilation ifTrue: [Utilities changeStamp] ifFalse: [nil]. ^ self compile: text classified: category withStamp: stamp notifying: requestor! ! !ClassDescription methodsFor: 'compiling'! compile: text classified: category withStamp: changeStamp notifying: requestor ^ self compile: text classified: category withStamp: changeStamp notifying: requestor logSource: self acceptsLoggingOfCompilation! ! !ClassDescription methodsFor: 'compiling'! compile: text classified: category withStamp: changeStamp notifying: requestor logSource: logSource | methodAndNode | methodAndNode := self compile: text asString classified: category notifying: requestor trailer: self defaultMethodTrailer ifFail: [^nil]. logSource ifTrue: [ self logMethodSource: text forMethodWithNode: methodAndNode inCategory: category withStamp: changeStamp notifying: requestor. ]. self addAndClassifySelector: methodAndNode selector withMethod: methodAndNode method inProtocol: category notifying: requestor. self instanceSide noteCompilationOf: methodAndNode selector meta: self isClassSide. ^ methodAndNode selector! ! !ClassDescription methodsFor: 'compiling'! compile: code notifying: requestor "Refer to the comment in Behavior|compile:notifying:." ^self compile: code classified: ClassOrganizer default notifying: requestor! ! !ClassDescription methodsFor: 'compiling'! compileSilently: code classified: category "Compile the code and classify the resulting method in the given category, leaving no trail in the system log, nor in any change set, nor in the 'recent submissions' list. This should only be used when you know for sure that the compilation will succeed." ^ self compileSilently: code classified: category notifying: nil.! ! !ClassDescription methodsFor: 'compiling'! compileSilently: code classified: category notifying: requestor "Compile the code and classify the resulting method in the given category, leaving no trail in the system log, nor in any change set, nor in the 'recent submissions' list. This should only be used when you know for sure that the compilation will succeed." ^ SystemChangeNotifier uniqueInstance doSilently: [self compile: code classified: category withStamp: nil notifying: requestor logSource: false].! ! !ClassDescription methodsFor: 'compiling'! doneCompiling "A ClassBuilder has finished the compilation of the receiver. This message is a notification for a class that needs to do some cleanup / reinitialization after it has been recompiled."! ! !ClassDescription methodsFor: 'compiling' stamp: 'eem 5/13/2008 09:48'! instVarNamesAndOffsetsDo: aBinaryBlock "This is part of the interface between the compiler and a class's instance or field names. The class should enumerate aBinaryBlock with the instance variable name strings and their integer offsets. The order is important. Names evaluated later will override the same names occurring earlier." | superInstSize | (superInstSize := superclass notNil ifTrue: [superclass instSize] ifFalse: [0]) > 0 ifTrue: [superclass instVarNamesAndOffsetsDo: aBinaryBlock]. 1 to: self instSize - superInstSize do: [:i| aBinaryBlock value: (instanceVariables at: i) value: i + superInstSize]! ! !ClassDescription methodsFor: 'compiling' stamp: 'al 11/28/2005 11:51'! moveInstVarNamed: instVarName to: anotherClass after: prevInstVarName "Move the given instance variable to another class." self == anotherClass ifFalse:[ self notify:'Warning:' asText allBold,' moving ', instVarName printString,' from ', self name,' to ', anotherClass name,' will not be recorded in the change set correctly. Proceed to do it anyways.']. ^(ClassBuilder new) moveInstVarNamed: instVarName from: self to: anotherClass after: prevInstVarName! ! !ClassDescription methodsFor: 'compiling'! noteCompilationOf: aSelector meta: isMeta "A hook allowing some classes to react to recompilation of certain selectors"! ! !ClassDescription methodsFor: 'compiling'! reformatAll "Reformat all methods in this class. Leaves old code accessible to version browsing" self selectorsDo: [:sel | self reformatMethodAt: sel]! ! !ClassDescription methodsFor: 'compiling' stamp: 'alain.plantec 5/18/2009 15:46'! reformatMethodAt: selector | newCodeString method | newCodeString := self prettyPrinterClass format: (self sourceCodeAt: selector) in: self notifying: nil. method := self compiledMethodAt: selector. method putSource: newCodeString fromParseNode: nil class: self category: (self organization categoryOfElement: selector) inFile: 2 priorMethod: method ! ! !ClassDescription methodsFor: 'compiling'! wantsChangeSetLogging "Answer whether code submitted for the receiver should be remembered by the changeSet mechanism. 7/12/96 sw" ^ true! ! !ClassDescription methodsFor: 'compiling'! wantsRecompilationProgressReported "Answer whether the receiver would like progress of its recompilation reported interactively to the user." ^ true! ! !ClassDescription methodsFor: 'copying'! copy: sel from: class "Install the method associated with the first argument, sel, a message selector, found in the method dictionary of the second argument, class, as one of the receiver's methods. Classify the message under -As yet not classified-." self copy: sel from: class classified: nil! ! !ClassDescription methodsFor: 'copying'! copy: sel from: class classified: cat "Install the method associated with the first arugment, sel, a message selector, found in the method dictionary of the second argument, class, as one of the receiver's methods. Classify the message under the third argument, cat." | code category | "Useful when modifying an existing class" code := class sourceMethodAt: sel. code == nil ifFalse: [cat == nil ifTrue: [category := class organization categoryOfElement: sel] ifFalse: [category := cat]. (self methodDict includesKey: sel) ifTrue: [code asString = (self sourceMethodAt: sel) asString ifFalse: [self error: self name , ' ' , sel , ' will be redefined if you proceed.']]. self compile: code classified: category]! ! !ClassDescription methodsFor: 'copying'! copyAll: selArray from: class "Install all the methods found in the method dictionary of the second argument, class, as the receiver's methods. Classify the messages under -As yet not classified-." self copyAll: selArray from: class classified: nil! ! !ClassDescription methodsFor: 'copying'! copyAll: selArray from: class classified: cat "Install all the methods found in the method dictionary of the second argument, class, as the receiver's methods. Classify the messages under the third argument, cat." selArray do: [:s | self copy: s from: class classified: cat]! ! !ClassDescription methodsFor: 'copying'! copyAllCategoriesFrom: aClass "Specify that the categories of messages for the receiver include all of those found in the class, aClass. Install each of the messages found in these categories into the method dictionary of the receiver, classified under the appropriate categories." aClass organization categories do: [:cat | self copyCategory: cat from: aClass]! ! !ClassDescription methodsFor: 'copying'! copyCategory: cat from: class "Specify that one of the categories of messages for the receiver is cat, as found in the class, class. Copy each message found in this category." self copyCategory: cat from: class classified: cat! ! !ClassDescription methodsFor: 'copying'! copyCategory: cat from: aClass classified: newCat "Specify that one of the categories of messages for the receiver is the third argument, newCat. Copy each message found in the category cat in class aClass into this new category." self copyAll: (aClass organization listAtCategoryNamed: cat) from: aClass classified: newCat! ! !ClassDescription methodsFor: 'copying'! copyMethodDictionaryFrom: donorClass "Copy the method dictionary of the donor class over to the receiver" self methodDict: donorClass copyOfMethodDictionary. self organization: donorClass organization deepCopy.! ! !ClassDescription methodsFor: 'deprecated' stamp: 'sd 4/26/2008 11:54'! commentFollows "Answer a ClassCommentReader who will scan in the comment." self deprecated: 'user classCommentReader instead'. ^ ClassCommentReader new setClass: self category: #Comment ! ! !ClassDescription methodsFor: 'fileIn/Out'! classComment: aString stamp: aStamp "Store the comment, aString or Text or RemoteString, associated with the class we are organizing. Empty string gets stored only if had a non-empty one before." | ptr header file oldCommentRemoteStr oldComment oldStamp | oldComment := self organization classComment. oldStamp := self organization commentStamp. (aString isKindOf: RemoteString) ifTrue: [SystemChangeNotifier uniqueInstance class: self oldComment: oldComment newComment: aString string oldStamp: oldStamp newStamp: aStamp. ^ self organization classComment: aString stamp: aStamp]. oldCommentRemoteStr := self organization commentRemoteStr. (aString size = 0) & (oldCommentRemoteStr isNil) ifTrue: [^ self organization classComment: nil]. "never had a class comment, no need to write empty string out" ptr := oldCommentRemoteStr ifNil: [0] ifNotNil: [oldCommentRemoteStr sourcePointer]. SourceFiles ifNotNil: [(file := SourceFiles at: 2) ifNotNil: [file setToEnd; cr; nextPut: $!!. "directly" "Should be saying (file command: 'H3') for HTML, but ignoring it here" header := String streamContents: [:strm | strm nextPutAll: self name; nextPutAll: ' commentStamp: '. aStamp storeOn: strm. strm nextPutAll: ' prior: '; nextPutAll: ptr printString]. file nextChunkPut: header]]. self organization classComment: (RemoteString newString: aString onFileNumber: 2) stamp: aStamp. SystemChangeNotifier uniqueInstance class: self oldComment: oldComment newComment: aString oldStamp: oldStamp newStamp: aStamp! ! !ClassDescription methodsFor: 'fileIn/Out' stamp: 'PeterHugossonMiller 9/3/2009 00:55'! definition "Answer a String that defines the receiver." | aStream | aStream := (String new: 300) writeStream. superclass == nil ifTrue: [aStream nextPutAll: 'ProtoObject'] ifFalse: [aStream nextPutAll: superclass name]. aStream nextPutAll: self kindOfSubclass; store: self name. (self hasTraitComposition and: [self traitComposition notEmpty]) ifTrue: [ aStream cr; tab; nextPutAll: 'uses: '; nextPutAll: self traitCompositionString]. aStream cr; tab; nextPutAll: 'instanceVariableNames: '; store: self instanceVariablesString. aStream cr; tab; nextPutAll: 'classVariableNames: '; store: self classVariablesString. aStream cr; tab; nextPutAll: 'poolDictionaries: '; store: self sharedPoolsString. aStream cr; tab; nextPutAll: 'category: '; store: (SystemOrganization categoryOfElement: self name) asString. superclass ifNil: [ aStream nextPutAll: '.'; cr. aStream nextPutAll: self name. aStream space; nextPutAll: 'superclass: nil'. ]. ^ aStream contents! ! !ClassDescription methodsFor: 'fileIn/Out'! fileOutCategory: aSymbol on: aFileStream moveSource: moveSource toFile: fileIndex "File a description of the receiver's category, aString, onto aFileStream. If moveSource, is true, then set the method source pointer to the new file position. Note when this method is called with moveSource=true, it is condensing the .sources file, and should only write one preamble per method category." | selectors | aFileStream cr. selectors := (aSymbol asString = ClassOrganizer allCategory) ifTrue: [ self organization allMethodSelectors ] ifFalse: [ self organization listAtCategoryNamed: aSymbol ]. "Overridden to preserve author stamps in sources file regardless" selectors do: [:sel | self printMethodChunk: sel withPreamble: true on: aFileStream moveSource: moveSource toFile: fileIndex]. ^ self! ! !ClassDescription methodsFor: 'fileIn/Out' stamp: 'bf 12/17/2005 00:04'! fileOutChangedMessages: aSet on: aFileStream moveSource: moveSource toFile: fileIndex "File a description of the messages of this class that have been changed (i.e., are entered into the argument, aSet) onto aFileStream. If moveSource, is true, then set the method source pointer to the new file position. Note when this method is called with moveSource=true, it is condensing the .changes file, and should only write a preamble for every method." | org sels | (org := self organization) categories do: [:cat | sels := (org listAtCategoryNamed: cat) select: [:sel | aSet includes: sel]. ((cat beginsWith: '*') and: [cat endsWith: '-override']) ifTrue: [ sels do: [:sel | self printMethodChunkHistorically: sel on: aFileStream moveSource: moveSource toFile: fileIndex]] ifFalse: [ sels do: [:sel | self printMethodChunk: sel withPreamble: true on: aFileStream moveSource: moveSource toFile: fileIndex]]]! ! !ClassDescription methodsFor: 'fileIn/Out' stamp: 'sumim 9/2/2003 14:36'! fileOutChangedMessagesHistorically: aSet on: aFileStream moveSource: moveSource toFile: fileIndex "File all historical description of the messages of this class that have been changed (i.e., are entered into the argument, aSet) onto aFileStream. If moveSource, is true, then set the method source pointer to the new file position. Note when this method is called with moveSource=true, it is condensing the .changes file, and should only write a preamble for every method." | org sels | (org := self organization) categories do: [:cat | sels := (org listAtCategoryNamed: cat) select: [:sel | aSet includes: sel]. sels do: [:sel | self printMethodChunkHistorically: sel on: aFileStream moveSource: moveSource toFile: fileIndex]]! ! !ClassDescription methodsFor: 'fileIn/Out'! moveChangesTo: newFile "Used in the process of condensing changes, this message requests that the source code of all methods of the receiver that have been changed should be moved to newFile." | changes | changes := self methodDict keys select: [:sel | (self compiledMethodAt: sel) fileIndex > 1 ]. self fileOutChangedMessages: changes on: newFile moveSource: true toFile: 2! ! !ClassDescription methodsFor: 'fileIn/Out' stamp: 'sumim 9/2/2003 14:37'! moveChangesWithVersionsTo: newFile "Used in the process of condensing changes, this message requests that the source code of all methods of the receiver that have been changed should be moved to newFile." | changes | changes := self methodDict keys select: [:sel | (self methodDict at: sel) fileIndex > 1]. self fileOutChangedMessagesHistorically: changes on: newFile moveSource: true toFile: 2! ! !ClassDescription methodsFor: 'fileIn/Out' stamp: 'md 2/20/2006 15:13'! printMethodChunkHistorically: selector on: outStream moveSource: moveSource toFile: fileIndex "Copy all source codes historically for the method associated with selector onto the fileStream. If moveSource true, then also set the source code pointer of the method." | preamble method newPos sourceFile endPos category changeList prior | category := self organization categoryOfElement: selector. preamble := self name , ' methodsFor: ', category asString printString. method := self methodDict at: selector. ((method fileIndex = 0 or: [(SourceFiles at: method fileIndex) == nil]) or: [method filePosition = 0]) ifTrue: [ outStream cr; nextPut: $!!; nextChunkPut: preamble; cr. outStream nextChunkPut: method decompileString. outStream nextChunkPut: ' '; cr] ifFalse: [ changeList := ChangeSet scanVersionsOf: method class: self meta: self isMeta category: category selector: selector. newPos := nil. sourceFile := SourceFiles at: method fileIndex. changeList reverseDo: [ :chgRec | chgRec fileIndex = fileIndex ifTrue: [ outStream copyPreamble: preamble from: sourceFile at: chgRec position. (prior := chgRec prior) ifNotNil: [ outStream position: outStream position - 2. outStream nextPutAll: ' prior: ', ( prior first = method fileIndex ifFalse: [prior third] ifTrue: [ SourceFiles sourcePointerFromFileIndex: method fileIndex andPosition: newPos]) printString. outStream nextPut: $!!; cr]. "Copy the method chunk" newPos := outStream position. outStream copyMethodChunkFrom: sourceFile at: chgRec position. sourceFile skipSeparators. "The following chunk may have ]style[" sourceFile peek == $] ifTrue: [ outStream cr; copyMethodChunkFrom: sourceFile]. outStream nextChunkPut: ' '; cr]]. moveSource ifTrue: [ endPos := outStream position. method checkOKToAdd: endPos - newPos at: newPos. method setSourcePosition: newPos inFile: fileIndex]]. ^ outStream! ! !ClassDescription methodsFor: 'filein/out'! classComment: aString "Store the comment, aString or Text or RemoteString, associated with the class we are orgainzing. Empty string gets stored only if had a non-empty one before." ^ self classComment: aString stamp: ''! ! !ClassDescription methodsFor: 'filein/out'! commentStamp: changeStamp self organization commentStamp: changeStamp. ^ self commentStamp: changeStamp prior: 0! ! !ClassDescription methodsFor: 'filein/out'! commentStamp: changeStamp prior: indexAndOffset "Prior source link ignored when filing in." ^ ClassCommentReader new setClass: self category: #Comment changeStamp: changeStamp! ! !ClassDescription methodsFor: 'filein/out' stamp: 'PeterHugossonMiller 9/3/2009 00:55'! fileOutCategory: catName | internalStream | internalStream := (String new: 1000) writeStream. internalStream header; timeStamp. self fileOutCategory: catName on: internalStream moveSource: false toFile: 0. internalStream trailer. ^ FileStream writeSourceCodeFrom: internalStream baseName: (self name , '-' , catName) isSt: true.! ! !ClassDescription methodsFor: 'filein/out'! fileOutChangedMessages: aSet on: aFileStream "File a description of the messages of the receiver that have been changed (i.e., are entered into the argument, aSet) onto aFileStream." self fileOutChangedMessages: aSet on: aFileStream moveSource: false toFile: 0! ! !ClassDescription methodsFor: 'filein/out' stamp: 'PeterHugossonMiller 9/3/2009 00:55'! fileOutMethod: selector "Write source code of a single method on a file. Make up a name for the file." | internalStream | (selector == #Comment) ifTrue: [^ self inform: 'Sorry, cannot file out class comment in isolation.']. (self includesSelector: selector) ifFalse: [^ self error: 'Selector ', selector asString, ' not found']. internalStream := (String new: 1000) writeStream. internalStream header; timeStamp. self printMethodChunk: selector withPreamble: true on: internalStream moveSource: false toFile: 0. FileStream writeSourceCodeFrom: internalStream baseName: (self name , '-' , (selector copyReplaceAll: ':' with: '')) isSt: true.! ! !ClassDescription methodsFor: 'filein/out'! fileOutOn: aFileStream "File a description of the receiver on aFileStream." self fileOutOn: aFileStream moveSource: false toFile: 0! ! !ClassDescription methodsFor: 'filein/out'! fileOutOn: aFileStream moveSource: moveSource toFile: fileIndex "File a description of the receiver on aFileStream. If the boolean argument, moveSource, is true, then set the trailing bytes to the position of aFileStream and to fileIndex in order to indicate where to find the source code." aFileStream nextChunkPut: self definition. self organization putCommentOnFile: aFileStream numbered: fileIndex moveSource: moveSource forClass: self. self organization categories do: [:heading | self fileOutCategory: heading on: aFileStream moveSource: moveSource toFile: fileIndex]! ! !ClassDescription methodsFor: 'filein/out'! fileOutOrganizationOn: aFileStream "File a description of the receiver's organization on aFileStream." aFileStream cr; nextPut: $!!. aFileStream nextChunkPut: self name, ' reorganize'; cr. aFileStream nextChunkPut: self organization printString; cr! ! !ClassDescription methodsFor: 'filein/out'! localMethods "returns the methods of classes including the ones of the traits that the class uses" ^ self methods select: [:each | self includesLocalSelector: each selector].! ! !ClassDescription methodsFor: 'filein/out'! methods "returns the methods of classes including the ones of the traits that the class uses" ^ self methodDict values ! ! !ClassDescription methodsFor: 'filein/out'! methodsFor: categoryName "Answer a ClassCategoryReader for compiling the messages in the category, categoryName, of the receiver." ^ ClassCategoryReader new setClass: self category: categoryName asSymbol "(False methodsFor: 'logical operations') inspect"! ! !ClassDescription methodsFor: 'filein/out'! methodsFor: aString priorSource: sourcePosition inFile: fileIndex "Prior source pointer ignored when filing in." ^ self methodsFor: aString! ! !ClassDescription methodsFor: 'filein/out'! methodsFor: categoryName stamp: changeStamp ^ self methodsFor: categoryName stamp: (Utilities fixStamp: changeStamp) prior: 0! ! !ClassDescription methodsFor: 'filein/out'! methodsFor: categoryName stamp: changeStamp prior: indexAndOffset "Prior source link ignored when filing in." ^ ClassCategoryReader new setClass: self category: categoryName asSymbol changeStamp: changeStamp "Most importantly, return the new ClassCategoryReader, so a fileIn will let it seize control. So method will be placed in the proper category. See the transfer of control where ReadWriteStream fileIn calls scanFrom:"! ! !ClassDescription methodsFor: 'filein/out'! printCategoryChunk: categoryName on: aFileStream ^ self printCategoryChunk: categoryName withStamp: '' on: aFileStream! ! !ClassDescription methodsFor: 'filein/out'! printCategoryChunk: category on: aFileStream priorMethod: priorMethod ^ self printCategoryChunk: category on: aFileStream withStamp: Utilities changeStamp priorMethod: priorMethod! ! !ClassDescription methodsFor: 'filein/out'! printCategoryChunk: category on: aFileStream withStamp: changeStamp priorMethod: priorMethod "Print a method category preamble. This must have a category name. It may have an author/date stamp, and it may have a prior source link. If it has a prior source link, it MUST have a stamp, even if it is empty." "The current design is that changeStamps and prior source links are preserved in the changes file. All fileOuts include changeStamps. Condensing sources, however, eliminates all stamps (and links, natch)." aFileStream cr; nextPut: $!!. aFileStream nextChunkPut: (String streamContents: [:strm | strm nextPutAll: self name; nextPutAll: ' methodsFor: '; print: category asString. (changeStamp ~~ nil and: [changeStamp size > 0 or: [priorMethod ~~ nil]]) ifTrue: [strm nextPutAll: ' stamp: '; print: changeStamp]. priorMethod ~~ nil ifTrue: [strm nextPutAll: ' prior: '; print: priorMethod sourcePointer]]). ! ! !ClassDescription methodsFor: 'filein/out'! printCategoryChunk: categoryName withStamp: changeStamp on: aFileStream ^ self printCategoryChunk: categoryName on: aFileStream withStamp: changeStamp priorMethod: nil! ! !ClassDescription methodsFor: 'filein/out'! printMethodChunk: selector withPreamble: doPreamble on: outStream moveSource: moveSource toFile: fileIndex "Copy the source code for the method associated with selector onto the fileStream. If moveSource true, then also set the source code pointer of the method." | preamble method oldPos newPos sourceFile endPos | doPreamble ifTrue: [preamble := self name , ' methodsFor: ' , (self organization categoryOfElement: selector) asString printString] ifFalse: [preamble := '']. method := self methodDict at: selector ifAbsent: [outStream nextPutAll: selector; cr. outStream tab; nextPutAll: '** ERROR!! THIS SCRIPT IS MISSING ** ' translated; cr; cr. outStream nextPutAll: ' '. ^ outStream]. ((method fileIndex = 0 or: [(SourceFiles at: method fileIndex) == nil]) or: [(oldPos := method filePosition) = 0]) ifTrue: ["The source code is not accessible. We must decompile..." preamble size > 0 ifTrue: [outStream cr; nextPut: $!!; nextChunkPut: preamble; cr]. outStream nextChunkPut: method decompileString] ifFalse: [sourceFile := SourceFiles at: method fileIndex. preamble size > 0 ifTrue: "Copy the preamble" [outStream copyPreamble: preamble from: sourceFile at: oldPos] ifFalse: [sourceFile position: oldPos]. "Copy the method chunk" newPos := outStream position. outStream copyMethodChunkFrom: sourceFile. sourceFile skipSeparators. "The following chunk may have ]style[" sourceFile peek == $] ifTrue: [ outStream cr; copyMethodChunkFrom: sourceFile]. moveSource ifTrue: "Set the new method source pointer" [endPos := outStream position. method checkOKToAdd: endPos - newPos at: newPos. method setSourcePosition: newPos inFile: fileIndex]]. preamble size > 0 ifTrue: [outStream nextChunkPut: ' ']. ^ outStream cr! ! !ClassDescription methodsFor: 'filein/out'! putClassCommentToCondensedChangesFile: aFileStream "Called when condensing changes. If the receiver has a class comment, and if that class comment does not reside in the .sources file, then write it to the given filestream, with the resulting RemoteString being reachable from the source file #2. Note that any existing backpointer into the .sources file is lost by this process -- a situation that maybe should be fixed someday." | header aStamp aCommentRemoteStr | self isMeta ifTrue: [^ self]. "bulletproofing only" ((aCommentRemoteStr := self organization commentRemoteStr) isNil or: [aCommentRemoteStr sourceFileNumber == 1]) ifTrue: [^ self]. aFileStream cr; nextPut: $!!. header := String streamContents: [:strm | strm nextPutAll: self name; nextPutAll: ' commentStamp: '. (aStamp := self organization commentStamp ifNil: ['']) storeOn: strm. strm nextPutAll: ' prior: 0']. aFileStream nextChunkPut: header. aFileStream cr. self organization classComment: (RemoteString newString: self organization classComment onFileNumber: 2 toFile: aFileStream) stamp: aStamp! ! !ClassDescription methodsFor: 'initialize-release' stamp: 'NS 4/8/2004 10:59'! forgetDoIts "get rid of old DoIt methods and bogus entries in the ClassOrganizer." SystemChangeNotifier uniqueInstance doSilently: [ self organization removeElement: #DoIt; removeElement: #DoItIn:. ]. super forgetDoIts.! ! !ClassDescription methodsFor: 'initialize-release' stamp: 'NS 4/8/2004 11:00'! obsolete "Make the receiver obsolete." superclass removeSubclass: self. self organization: nil. super obsolete.! ! !ClassDescription methodsFor: 'initialize-release' stamp: 'NS 4/8/2004 11:26'! superclass: aClass methodDictionary: mDict format: fmt "Basic initialization of the receiver" super superclass: aClass methodDictionary: mDict format: fmt. instanceVariables := nil. self organization: nil.! ! !ClassDescription methodsFor: 'initialize-release' stamp: 'ar 3/1/2001 23:25'! updateInstances: oldInstances from: oldClass isMeta: isMeta "Recreate any existing instances of the argument, oldClass, as instances of the receiver, which is a newly changed class. Permute variables as necessary. Return the array of old instances (none of which should be pointed to legally by anyone but the array)." "If there are any contexts having an old instance as receiver it might crash the system because the layout has changed, and the method only knows about the old layout." | map variable instSize newInstances | oldInstances isEmpty ifTrue:[^#()]. "no instances to convert" isMeta ifTrue: [ oldInstances size = 1 ifFalse:[^self error:'Metaclasses can only have one instance']. self soleInstance class == self ifTrue:[ ^self error:'Metaclasses can only have one instance']]. map := self instVarMappingFrom: oldClass. variable := self isVariable. instSize := self instSize. newInstances := Array new: oldInstances size. 1 to: oldInstances size do:[:i| newInstances at: i put: ( self newInstanceFrom: (oldInstances at: i) variable: variable size: instSize map: map)]. "Now perform a bulk mutation of old instances into new ones" oldInstances elementsExchangeIdentityWith: newInstances. ^newInstances "which are now old"! ! !ClassDescription methodsFor: 'initialize-release' stamp: 'ar 3/1/2001 20:48'! updateInstancesFrom: oldClass "Recreate any existing instances of the argument, oldClass, as instances of the receiver, which is a newly changed class. Permute variables as necessary. Return the array of old instances (none of which should be pointed to legally by anyone but the array)." "ar 7/15/1999: The updating below is possibly dangerous. If there are any contexts having an old instance as receiver it might crash the system if the new receiver in which the context is executed has a different layout. See bottom below for a simple example:" | oldInstances | oldInstances := oldClass allInstances asArray. oldInstances := self updateInstances: oldInstances from: oldClass isMeta: self isMeta. "Now fix up instances in segments that are out on the disk." ImageSegment allSubInstancesDo: [:seg | seg segUpdateInstancesOf: oldClass toBe: self isMeta: self isMeta]. ^oldInstances " | crashingBlock class | class := Object subclass: #CrashTestDummy instanceVariableNames: 'instVar' classVariableNames: '' poolDictionaries: '' category: 'Crash-Test'. class compile:'instVar: value instVar := value'. class compile:'crashingBlock ^[instVar]'. crashingBlock := (class new) instVar: 42; crashingBlock. Object subclass: #CrashTestDummy instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Crash-Test'. crashingBlock. crashingBlock value. " ! ! !ClassDescription methodsFor: 'instance variables'! addInstVarName: aString "Add the argument, aString, as one of the receiver's instance variables." self subclassResponsibility! ! !ClassDescription methodsFor: 'instance variables' stamp: 'al 11/28/2005 11:50'! allInstVarNamesEverywhere "Answer the set of inst var names used by the receiver, all superclasses, and all subclasses" | aList | aList := OrderedCollection new. (self allSuperclasses , self withAllSubclasses asOrderedCollection) do: [:cls | aList addAll: cls instVarNames]. ^ aList asSet "BorderedMorph allInstVarNamesEverywhere"! ! !ClassDescription methodsFor: 'instance variables' stamp: 'al 11/28/2005 11:50'! checkForInstVarsOK: instVarString "Return true if instVarString does no include any names used in a subclass" | instVarArray | instVarArray := Scanner new scanFieldNames: instVarString. self allSubclasses do: [:cl | cl instVarNames do: [:n | (instVarArray includes: n) ifTrue: [self error: n , ' is already used in ' , cl name. ^ false]]]. ^ true! ! !ClassDescription methodsFor: 'instance variables' stamp: 'PeterHugossonMiller 9/3/2009 00:54'! chooseClassVarName "Present the user with a list of class variable names and answer the one selected, or nil if none" | lines labelStream allVars index | lines := OrderedCollection new. allVars := OrderedCollection new. labelStream := (String new: 200) writeStream. self withAllSuperclasses reverseDo: [:class | | vars | vars := class classVarNames asSortedCollection. vars do: [:var | labelStream nextPutAll: var; cr. allVars add: var]. vars isEmpty ifFalse: [lines add: allVars size]]. labelStream contents isEmpty ifTrue: [^Beeper beep]. "handle nil superclass better" labelStream skip: -1 "cut last CR". index := (UIManager default chooseFrom: (labelStream contents substrings) lines: lines). index = 0 ifTrue: [^ nil]. ^ allVars at: index! ! !ClassDescription methodsFor: 'instance variables' stamp: 'al 11/28/2005 22:16'! chooseInstVarAlphabeticallyThenDo: aBlock | allVars index | "Put up a menu of all the instance variables in the receiver, presented in alphabetical order, and when the user chooses one, evaluate aBlock with the chosen variable as its parameter." allVars := self allInstVarNames asSortedArray. allVars isEmpty ifTrue: [^ self inform: 'There are no instance variables']. index := (UIManager default chooseFrom: allVars lines: #() title: 'Instance variables in ', self name). index = 0 ifTrue: [^ self]. aBlock value: (allVars at: index)! ! !ClassDescription methodsFor: 'instance variables' stamp: 'PeterHugossonMiller 9/3/2009 00:54'! chooseInstVarThenDo: aBlock "Put up a menu of all the instance variables in the receiver, and when the user chooses one, evaluate aBlock with the chosen variable as its parameter. If the list is 6 or larger, then offer an alphabetical formulation as an alternative. triggered by a 'show alphabetically' item at the top of the list." | lines labelStream allVars index count offerAlpha | (count := self allInstVarNames size) = 0 ifTrue: [^ self inform: 'There are no instance variables.']. allVars := OrderedCollection new. lines := OrderedCollection new. labelStream := (String new: 200) writeStream. (offerAlpha := count > 5) ifTrue: [lines add: 1. allVars add: 'show alphabetically'. labelStream nextPutAll: allVars first; cr]. self withAllSuperclasses reverseDo: [:class | | vars | vars := class instVarNames. vars do: [:var | labelStream nextPutAll: var; cr. allVars add: var]. vars isEmpty ifFalse: [lines add: allVars size]]. labelStream skip: -1 "cut last CR". (lines size > 0 and: [lines last = allVars size]) ifTrue: [lines removeLast]. "dispense with inelegant line beneath last item" index := (UIManager default chooseFrom: (labelStream contents subStrings: {Character cr}) lines: lines title: 'Instance variables in', self name). index = 0 ifTrue: [^ self]. (index = 1 and: [offerAlpha]) ifTrue: [^ self chooseInstVarAlphabeticallyThenDo: aBlock]. aBlock value: (allVars at: index)! ! !ClassDescription methodsFor: 'instance variables' stamp: 'al 11/28/2005 11:50'! classThatDefinesClassVariable: classVarName "Answer the class that defines the given class variable" (self classPool includesKey: classVarName asSymbol) ifTrue: [^ self]. ^self superclass ifNotNil: [self superclass classThatDefinesClassVariable: classVarName]! ! !ClassDescription methodsFor: 'instance variables' stamp: 'al 11/28/2005 11:50'! classThatDefinesInstanceVariable: instVarName (self instVarNames notNil and: [self instVarNames includes: instVarName asString]) ifTrue: [^ self]. ^self superclass ifNotNil: [self superclass classThatDefinesInstanceVariable: instVarName]! ! !ClassDescription methodsFor: 'instance variables'! forceNewFrom: anArray "Create a new instance of the class and fill its instance variables up with the array." | object max | object := self new. max := self instSize. anArray doWithIndex: [:each :index | index > max ifFalse: [object instVarAt: index put: each]]. ^ object! ! !ClassDescription methodsFor: 'instance variables'! instVarIndexFor: instVarName "Answer the index of the named instance variable." | index | index := instanceVariables == nil ifTrue: [0] ifFalse: [instanceVariables indexOf: instVarName]. index == 0 ifTrue: [^superclass == nil ifTrue: [0] ifFalse: [superclass instVarIndexFor: instVarName]]. ^superclass == nil ifTrue: [index] ifFalse: [index + superclass instSize]! ! !ClassDescription methodsFor: 'instance variables' stamp: 'eem 5/14/2008 13:15'! instVarIndexFor: instVarName ifAbsent: aBlock "Answer the index of the named instance variable." | index | index := instanceVariables == nil ifTrue: [0] ifFalse: [instanceVariables indexOf: instVarName ifAbsent: [0]]. index == 0 ifTrue: [^superclass == nil ifTrue: [aBlock value] ifFalse: [superclass instVarIndexFor: instVarName ifAbsent: aBlock]]. ^superclass == nil ifTrue: [index] ifFalse: [index + superclass instSize]! ! !ClassDescription methodsFor: 'instance variables'! instVarNameForIndex: index "Answer the named instance variable with index index or nil if none." | superInstSize | index > self instSize ifTrue: [^nil]. superInstSize := superclass isNil ifTrue: [0] ifFalse: [superclass instSize]. index > superInstSize ifTrue: [^instanceVariables at: index - superInstSize]. superclass isNil ifTrue: [^nil]. ^superclass instVarNameForIndex: index "(Object allSubclasses select: [:cls| cls instSize > cls superclass instSize and: [cls subclasses isEmpty and: [cls superclass instSize > 0]]]) collect: [:cls| (1 to: cls instSize) collect: [:i| cls instVarNameForIndex: i]]"! ! !ClassDescription methodsFor: 'instance variables'! instVarNames "Answer an Array of the receiver's instance variable names." instanceVariables == nil ifTrue: [^#()] ifFalse: [^instanceVariables]! ! !ClassDescription methodsFor: 'instance variables'! removeInstVarName: aString "Remove the argument, aString, as one of the receiver's instance variables. Create an error notification if the argument is not found." self subclassResponsibility! ! !ClassDescription methodsFor: 'instance variables' stamp: 'al 11/28/2005 11:52'! renameInstVar: oldName to: newName (self confirm: 'WARNING: Renaming of instance variables is subject to substitution ambiguities. Do you still wish to attempt it?') ifFalse: [self halt]. "...In other words, this does a dumb text search-and-replace, which might improperly alter, eg, a literal string. As long as the oldName is unique, everything should work jes' fine. - di" ^ self renameSilentlyInstVar: oldName to: newName! ! !ClassDescription methodsFor: 'instance variables' stamp: 'al 11/28/2005 11:52'! renameSilentlyInstVar: old to: new | i oldName newName | oldName := old asString. newName := new asString. (i := self instVarNames indexOf: oldName) = 0 ifTrue: [self error: oldName , ' is not defined in ', self name]. self allSuperclasses , self withAllSubclasses asOrderedCollection do: [:cls | (cls instVarNames includes: newName) ifTrue: [self error: newName , ' is already used in ', cls name]]. self instVarNames replaceFrom: i to: i with: (Array with: newName). self replaceSilently: oldName to: newName. "replace in text body of all methods"! ! !ClassDescription methodsFor: 'instance variables' stamp: 'al 11/28/2005 11:52'! replaceSilently: old to: new "text-replace any part of a method. Used for class and pool variables. Don't touch the header. Not guaranteed to work if name appears in odd circumstances" | oldCode newCode parser header body sels oldName newName | oldName := old asString. newName := new asString. self withAllSubclasses do: [:cls | sels := cls selectors. sels removeAllFoundIn: #(DoIt DoItIn:). sels do: [:sel | oldCode := cls sourceCodeAt: sel. "Don't make changes in the method header" (parser := cls parserClass new) parseSelector: oldCode. header := oldCode copyFrom: 1 to: (parser endOfLastToken min: oldCode size). body := header size > oldCode size ifTrue: [''] ifFalse: [oldCode copyFrom: header size+1 to: oldCode size]. newCode := header , (body copyReplaceTokens: oldName with: newName). newCode ~= oldCode ifTrue: [cls compile: newCode classified: (cls organization categoryOfElement: sel) notifying: nil]]. cls isMeta ifFalse: [oldCode := cls comment. newCode := oldCode copyReplaceTokens: oldName with: newName. newCode ~= oldCode ifTrue: [cls comment: newCode]]]! ! !ClassDescription methodsFor: 'organization'! methodReferencesInCategory: aCategoryName ^(self organization listAtCategoryNamed: aCategoryName) collect: [:ea | MethodReference new setClassSymbol: self theNonMetaClass name classIsMeta: self isMeta methodSymbol: ea stringVersion: ''] ! ! !ClassDescription methodsFor: 'organization' stamp: 'NS 4/8/2004 11:02'! organization "Answer the instance of ClassOrganizer that represents the organization of the messages of the receiver." organization ifNil: [self organization: (ClassOrganizer defaultList: self methodDict keys asSortedCollection asArray)]. (organization isMemberOf: Array) ifTrue: [self recoverFromMDFaultWithTrace]. "Making sure that subject is set correctly. It should not be necessary." organization ifNotNil: [organization setSubject: self]. ^ organization! ! !ClassDescription methodsFor: 'organization' stamp: 'NS 4/8/2004 11:04'! organization: aClassOrg "Install an instance of ClassOrganizer that represents the organization of the messages of the receiver." aClassOrg ifNotNil: [aClassOrg setSubject: self]. organization := aClassOrg! ! !ClassDescription methodsFor: 'organization'! reorganize "During fileIn, !!Rectangle reorganize!! allows Rectangle to seize control and treat the next chunk as its organization. See the transfer of control where ReadWriteStream fileIn calls scanFrom:" ^self organization! ! !ClassDescription methodsFor: 'organization'! whichCategoryIncludesSelector: aSelector "Answer the category of the argument, aSelector, in the organization of the receiver, or answer nil if the receiver does not inlcude this selector." (self includesSelector: aSelector) ifTrue: [^ self organization categoryOfElement: aSelector] ifFalse: [^nil]! ! !ClassDescription methodsFor: 'organization'! zapOrganization "Remove the organization of this class by message categories. This is typically done to save space in small systems. Classes and methods created or filed in subsequently will, nonetheless, be organized" self organization: nil. self isClassSide ifFalse: [self classSide zapOrganization]! ! !ClassDescription methodsFor: 'organization updating'! applyChangesOfNewTraitCompositionReplacing: oldComposition | changedSelectors | changedSelectors := super applyChangesOfNewTraitCompositionReplacing: oldComposition. self noteRecategorizedSelectors: changedSelectors oldComposition: oldComposition. ^ changedSelectors.! ! !ClassDescription methodsFor: 'organization updating'! noteRecategorizedSelectors: aCollection oldComposition: aTraitComposition | oldCategory newCategory | aCollection do: [:each | oldCategory := self organization categoryOfElement: each. newCategory := (self traitComposition methodDescriptionForSelector: each) effectiveMethodCategory. self noteRecategorizedSelector: each from: oldCategory to: newCategory]! ! !ClassDescription methodsFor: 'organization updating'! noteRecategorizedSelector: aSymbol from: oldCategoryOrNil to: newCategoryOrNil | changedCategories | changedCategories := self updateOrganizationSelector: aSymbol oldCategory: oldCategoryOrNil newCategory: newCategoryOrNil. changedCategories do: [:each | (self organization isEmptyCategoryNamed: each) ifTrue: [self organization removeCategory: each]]! ! !ClassDescription methodsFor: 'organization updating'! notifyOfRecategorizedSelector: element from: oldCategory to: newCategory SystemChangeNotifier uniqueInstance selector: element recategorizedFrom: oldCategory to: newCategory inClass: self! ! !ClassDescription methodsFor: 'organization updating'! updateOrganizationSelector: aSymbol oldCategory: oldCategoryOrNil newCategory: newCategoryOrNil | currentCategory effectiveCategory sel changedCategories composition | changedCategories := IdentitySet new. composition := self hasTraitComposition ifTrue: [self traitComposition] ifFalse: [TraitComposition new]. (composition methodDescriptionsForSelector: aSymbol) do: [:each | sel := each selector. (self includesLocalSelector: sel) ifFalse: [ currentCategory := self organization categoryOfElement: sel. effectiveCategory := each effectiveMethodCategoryCurrent: currentCategory new: newCategoryOrNil. effectiveCategory isNil ifTrue: [ currentCategory ifNotNil: [changedCategories add: currentCategory]. self organization removeElement: sel. ] ifFalse: [ ((currentCategory isNil or: [currentCategory == ClassOrganizer ambiguous or: [currentCategory == oldCategoryOrNil]]) and: [currentCategory ~~ effectiveCategory]) ifTrue: [ currentCategory ifNotNil: [changedCategories add: currentCategory]. self organization classify: sel under: effectiveCategory suppressIfDefault: false]]]]. ^ changedCategories! ! !ClassDescription methodsFor: 'printing' stamp: 'al 11/28/2005 11:51'! classVariablesString "Answer a string of my class variable names separated by spaces." ^String streamContents: [ :stream | self classPool keys asSortedCollection do: [ :each | stream nextPutAll: each ] separatedBy: [ stream space ] ]! ! !ClassDescription methodsFor: 'printing' stamp: 'al 11/28/2005 11:51'! instanceVariablesString "Answer a string of my instance variable names separated by spaces." ^String streamContents: [ :stream | self instVarNames do: [ :each | stream nextPutAll: each ] separatedBy: [ stream space ] ]! ! !ClassDescription methodsFor: 'printing'! printOn: aStream aStream nextPutAll: self name! ! !ClassDescription methodsFor: 'printing'! printOnStream: aStream aStream print: self name! ! !ClassDescription methodsFor: 'printing' stamp: 'eem 6/2/2008 11:47'! printWithClosureAnalysisOn: aStream aStream nextPutAll: self name! ! !ClassDescription methodsFor: 'printing' stamp: 'al 11/28/2005 11:52'! sharedPoolsString "Answer a string of my shared pool names separated by spaces." ^String streamContents: [ :stream | self sharedPools do: [ :each | stream nextPutAll: (self environment keyAtIdentityValue: each ifAbsent: [ 'private' ]) ] separatedBy: [ stream space ] ]! ! !ClassDescription methodsFor: 'printing'! storeOn: aStream "Classes and Metaclasses have global names." aStream nextPutAll: self name! ! !ClassDescription methodsFor: 'private'! errorCategoryName self error: 'Category name must be a String'! ! !ClassDescription methodsFor: 'private' stamp: 'al 11/28/2005 11:51'! instVarMappingFrom: oldClass "Return the mapping from instVars of oldClass to new class that is used for converting old instances of oldClass." | oldInstVarNames | oldInstVarNames := oldClass allInstVarNames. ^self allInstVarNames collect: [:instVarName | oldInstVarNames indexOf: instVarName].! ! !ClassDescription methodsFor: 'private' stamp: 'marcus.denker 8/25/2008 12:05'! linesOfCode "An approximate measure of lines of code. Includes comments, but excludes blank lines." | lines | lines := self localMethods inject: 0 into: [:sum :each | sum + each linesOfCode]. self isMeta ifTrue: [^ lines] ifFalse: [^ lines + self class linesOfCode]! ! !ClassDescription methodsFor: 'private' stamp: 'alain.plantec 5/18/2009 08:43'! logMethodSource: aText forMethodWithNode: aCompiledMethodWithNode inCategory: category withStamp: changeStamp notifying: requestor aCompiledMethodWithNode method putSource: aText fromParseNode: aCompiledMethodWithNode node class: self category: category withStamp: changeStamp inFile: 2 priorMethod: (self compiledMethodAt: aCompiledMethodWithNode selector ifAbsent: []) ! ! !ClassDescription methodsFor: 'private' stamp: 'ar 7/10/1999 11:17'! newInstanceFrom: oldInstance variable: variable size: instSize map: map "Create a new instance of the receiver based on the given old instance. The supplied map contains a mapping of the old instVar names into the receiver's instVars" | new | variable ifTrue: [new := self basicNew: oldInstance basicSize] ifFalse: [new := self basicNew]. 1 to: instSize do: [:offset | (map at: offset) > 0 ifTrue: [new instVarAt: offset put: (oldInstance instVarAt: (map at: offset))]]. variable ifTrue: [1 to: oldInstance basicSize do: [:offset | new basicAt: offset put: (oldInstance basicAt: offset)]]. ^new! ! !ClassDescription methodsFor: 'private' stamp: 'marcus.denker 8/24/2008 13:14'! numberOfMethods "cound all methods that are local (not comming from a trait)" | num | num := (self methods select: [:each | self includesLocalSelector: each selector]) size. self isMeta ifTrue: [^ num] ifFalse: [^ num + self class numberOfMethods] ! ! !ClassDescription methodsFor: 'private' stamp: 'ar 7/15/1999 17:04'! setInstVarNames: instVarArray "Private - for class initialization only" | required | required := self instSize. superclass notNil ifTrue:[required := required - superclass instSize]. instVarArray size = required ifFalse:[^self error: required printString, ' instvar names are required']. instVarArray isEmpty ifTrue:[instanceVariables := nil] ifFalse:[instanceVariables := instVarArray asArray].! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassDescription class uses: TClassAndTraitDescription classTrait instanceVariableNames: ''! ClassTestCase subclass: #ClassDescriptionTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Classes'! !ClassDescriptionTest commentStamp: '' prior: 0! This is the unit test for the class ClassDescription. Unit tests are a good way to exercise the functionality of your system in a repeatable and automatic manner. They are therefore recommended if you plan to release anything. For more information, see: - http://www.c2.com/cgi/wiki?UnitTest - http://minnow.cc.gatech.edu/squeak/1547 - the sunit class category! !ClassDescriptionTest methodsFor: 'tests' stamp: 'sd 5/10/2008 12:34'! testMethods self assert: Object methods = Object methodDict values. ! ! !ClassDescriptionTest methodsFor: 'tests' stamp: 'sd 6/5/2005 08:24'! testOrganization | aClassOrganizer | aClassOrganizer := ClassDescription organization. self assert: (aClassOrganizer isKindOf: ClassOrganizer).! ! TextDiffBuilder subclass: #ClassDiffBuilder instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-FilePackage'! !ClassDiffBuilder methodsFor: 'initialize' stamp: 'PeterHugossonMiller 9/3/2009 00:56'! split: aString | lines in out c | lines := OrderedCollection new. in := aString readStream. out := String new writeStream. [ in atEnd ] whileFalse: [ (c := in next) isSeparator ifTrue: [ out nextPut: c. lines add: out contents. out reset ] ifFalse: [ out nextPut: c ] ]. out position = 0 ifFalse: [ lines add: out contents ]. ^ lines! ! !ClassDiffBuilder methodsFor: 'printing' stamp: 'nk 4/24/2004 08:49'! printPatchSequence: ps on: aStream | type line | ps do: [:assoc | type := assoc key. line := assoc value. aStream withAttributes: (self attributesOf: type) do: [aStream nextPutAll: line]]! ! Object subclass: #ClassFactoryForTestCase instanceVariableNames: 'createdClasses' classVariableNames: '' poolDictionaries: '' category: 'SUnit-Extensions'! !ClassFactoryForTestCase methodsFor: 'accessing' stamp: 'Noury 10/26/2008 14:21'! createdClassNames ^self createdClasses collect: [:class| class name]! ! !ClassFactoryForTestCase methodsFor: 'accessing' stamp: 'Noury 10/26/2008 13:59'! createdClasses ^createdClasses! ! !ClassFactoryForTestCase methodsFor: 'accessing' stamp: 'Noury 10/26/2008 14:01'! createdClasses: classes createdClasses := classes asIdentitySet ! ! !ClassFactoryForTestCase methodsFor: 'accessing' stamp: 'Noury 10/26/2008 16:37'! defaultCategory ^ (self packageName , '-', self defaultCategoryPostfix) asSymbol! ! !ClassFactoryForTestCase methodsFor: 'accessing' stamp: 'Noury 10/26/2008 16:23'! defaultCategoryPostfix ^ #Default! ! !ClassFactoryForTestCase methodsFor: 'accessing' stamp: 'Noury 10/26/2008 16:20'! packageName ^#CategoryForTestToBeDeleted! ! !ClassFactoryForTestCase methodsFor: 'cleaning' stamp: 'Noury 10/26/2008 16:26'! cleanUp | createdClassNames | createdClassNames := self createdClassNames. self deleteClasses. self deletePackage. self cleanUpChangeSetForClassNames: createdClassNames! ! !ClassFactoryForTestCase methodsFor: 'cleaning' stamp: 'Noury 10/26/2008 14:20'! cleanUpChangeSetForClassNames: classeNames | changeSet | changeSet := ChangeSet current. classeNames do: [:name| changeSet removeClassChanges: name; removeClassChanges: name, ' class']. ! ! !ClassFactoryForTestCase methodsFor: 'cleaning' stamp: 'Noury 10/26/2008 12:47'! delete: aClass aClass isObsolete ifTrue: [^self]. aClass removeFromChanges. aClass removeFromSystemUnlogged ! ! !ClassFactoryForTestCase methodsFor: 'cleaning' stamp: 'Noury 10/26/2008 12:46'! deleteClasses self createdClasses do: [:class| self delete: class]! ! !ClassFactoryForTestCase methodsFor: 'cleaning' stamp: 'Noury 10/26/2008 16:33'! deletePackage | categoriesMatchString | categoriesMatchString := self packageName, '-*'. SystemOrganization removeCategoriesMatching: categoriesMatchString! ! !ClassFactoryForTestCase methodsFor: 'cleaning' stamp: 'Noury 10/26/2008 14:01'! initialize super initialize. self createdClasses: IdentitySet new! ! !ClassFactoryForTestCase methodsFor: 'creating' stamp: 'Noury 10/26/2008 14:55'! newClass ^self newSubclassOf: Object instanceVariableNames: '' classVariableNames: ''! ! !ClassFactoryForTestCase methodsFor: 'creating' stamp: 'Noury 10/26/2008 16:46'! newClassInCategory: category ^self newSubclassOf: Object instanceVariableNames: '' classVariableNames: '' category: category! ! !ClassFactoryForTestCase methodsFor: 'creating' stamp: 'Noury 10/26/2008 14:08'! newName | postFix | postFix := (self createdClasses size + 1) printString. ^#ClassForTestToBeDeleted, postFix! ! !ClassFactoryForTestCase methodsFor: 'creating' stamp: 'Noury 10/26/2008 16:25'! newSubclassOf: aClass instanceVariableNames: ivNamesString classVariableNames: classVarsString ^self newSubclassOf: aClass instanceVariableNames: ivNamesString classVariableNames: classVarsString category: self defaultCategoryPostfix! ! !ClassFactoryForTestCase methodsFor: 'creating' stamp: 'Noury 10/26/2008 16:36'! newSubclassOf: aClass instanceVariableNames: ivNamesString classVariableNames: classVarsString category: category | newClass | newClass := aClass subclass: self newName instanceVariableNames: ivNamesString classVariableNames: classVarsString poolDictionaries: '' category: (self packageName, '-', category) asSymbol. self createdClasses add: newClass. ^newClass! ! TestCase subclass: #ClassFactoryForTestCaseTest instanceVariableNames: 'factory' classVariableNames: '' poolDictionaries: '' category: 'SUnit-Tests'! !ClassFactoryForTestCaseTest methodsFor: 'setUp-tearDown' stamp: 'Noury 10/26/2008 12:19'! setUp super setUp. factory := ClassFactoryForTestCase new! ! !ClassFactoryForTestCaseTest methodsFor: 'setUp-tearDown' stamp: 'Noury 10/26/2008 14:53'! tearDown super tearDown. factory cleanUp! ! !ClassFactoryForTestCaseTest methodsFor: 'testing' stamp: 'Noury 10/26/2008 16:43'! testClassCreationInDifferentCategories | firstThreeClasses lastTwoClasses | 3 timesRepeat: [ factory newSubclassOf: Object instanceVariableNames: '' classVariableNames: '' category: #One]. firstThreeClasses := factory createdClasses copy. 2 timesRepeat: [ factory newSubclassOf: Object instanceVariableNames: '' classVariableNames: '' category: #Two]. lastTwoClasses := factory createdClasses copyWithoutAll: firstThreeClasses. self assert: (firstThreeClasses allSatisfy: [:class| class category = (factory packageName, '-', #One) asSymbol]). self assert: (lastTwoClasses allSatisfy: [:class| class category = (factory packageName, '-', #Two) asSymbol]).! ! !ClassFactoryForTestCaseTest methodsFor: 'testing' stamp: 'Noury 10/26/2008 16:42'! testClassFastCreationInDifferentCategories | firstThreeClasses lastTwoClasses | 3 timesRepeat: [ factory newClassInCategory: #One]. firstThreeClasses := factory createdClasses copy. 2 timesRepeat: [ factory newClassInCategory: #Two]. lastTwoClasses := factory createdClasses copyWithoutAll: firstThreeClasses. self assert: (firstThreeClasses allSatisfy: [:class| class category = (factory packageName, '-', #One) asSymbol]). self assert: (lastTwoClasses allSatisfy: [:class| class category = (factory packageName, '-', #Two) asSymbol]).! ! !ClassFactoryForTestCaseTest methodsFor: 'testing' stamp: 'Noury 10/26/2008 16:44'! testDefaultCategoryCleanUp | createdClassNames allClasses | 3 timesRepeat: [ factory newClass]. createdClassNames := factory createdClassNames. factory cleanUp. self assert: (factory createdClasses allSatisfy: [:class| class isObsolete]). allClasses := SystemNavigation new allClasses. self assert: (factory createdClasses noneSatisfy: [:class| allClasses includes: class]). self deny: (SystemOrganization categories includes: factory defaultCategory). self deny: (ChangeSet current changedClassNames includesAnyOf: createdClassNames) ! ! !ClassFactoryForTestCaseTest methodsFor: 'testing' stamp: 'Noury 10/26/2008 16:38'! testMultipleClassCreation 5 timesRepeat: [ factory newClass]. self assert: (SystemNavigation new allClasses includesAllOf: factory createdClasses). self assert: factory createdClassNames asSet size = 5. self assert: (SystemOrganization listAtCategoryNamed: factory defaultCategory) asSet = factory createdClassNames asSet! ! !ClassFactoryForTestCaseTest methodsFor: 'testing' stamp: 'Noury 10/26/2008 16:47'! testPackageCleanUp | createdClassNames allClasses | 3 timesRepeat: [ factory newClassInCategory: #One]. 2 timesRepeat: [ factory newClassInCategory: #Two]. createdClassNames := factory createdClassNames. factory cleanUp. self assert: (factory createdClasses allSatisfy: [:class| class isObsolete]). allClasses := SystemNavigation new allClasses. self assert: (factory createdClasses noneSatisfy: [:class| allClasses includes: class]). self assert: (SystemOrganization categoriesMatching: factory packageName, '*') isEmpty. self deny: (ChangeSet current changedClassNames includesAnyOf: createdClassNames) ! ! !ClassFactoryForTestCaseTest methodsFor: 'testing' stamp: 'Noury 10/26/2008 16:37'! testSingleClassCreation |class elementsInCategoryForTest | class := factory newSubclassOf: Object instanceVariableNames: 'a b c' classVariableNames: 'X Y'. self assert: (SystemNavigation new allClasses includes: class). elementsInCategoryForTest := SystemOrganization listAtCategoryNamed: factory defaultCategory. self assert: elementsInCategoryForTest = {class name}. self assert: class instVarNames = #(a b c). self assert: class classPool keys = #(X Y) asSet! ! !ClassFactoryForTestCaseTest methodsFor: 'testing' stamp: 'Noury 10/26/2008 16:37'! testSingleClassFastCreation |class elementsInCategoryForTest | class := factory newClass. self assert: (SystemNavigation new allClasses includes: class). elementsInCategoryForTest := SystemOrganization listAtCategoryNamed: factory defaultCategory. self assert: elementsInCategoryForTest = {class name}. self assert: class instVarNames isEmpty. self assert: class classPool isEmpty! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassFactoryForTestCaseTest class instanceVariableNames: ''! !ClassFactoryForTestCaseTest class methodsFor: 'history' stamp: 'simon.denier 11/22/2008 22:13'! lastStoredRun ^ ((Dictionary new) add: (#passed->((Set new) add: #testDefaultCategoryCleanUp; add: #testPackageCleanUp; add: #testSingleClassCreation; add: #testClassCreationInDifferentCategories; add: #testClassFastCreationInDifferentCategories; add: #testMultipleClassCreation; add: #testSingleClassFastCreation; yourself)); add: (#timeStamp->'22 November 2008 10:11:35 pm'); add: (#failures->((Set new))); add: (#errors->((Set new))); yourself)! ! HierarchyBrowser subclass: #ClassListBrowser instanceVariableNames: 'defaultTitle' classVariableNames: '' poolDictionaries: '' category: 'Tools-Browser'! !ClassListBrowser commentStamp: '' prior: 0! A ClassListBrowser displays the code for an arbitrary list of classes. ClassListBrowser example1. "all classes that have the string 'Pluggable' in their names" ClassListBrowser example2. "all classes whose names start with the letter S" ClassListBrowser example3. "all variable classes" ClassListBrowser example4. "all classes with more than 100 methods" ClassListBrowser example5. "all classes that lack class comments" ClassListBrowser example6. "all classes that have class instance variables" ClassListBrowser new initForClassesNamed: #(Browser Boolean) title: 'Browser and Boolean!!'. ! !ClassListBrowser methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:26'! initForClassesNamed: nameList title: aTitle "Initialize the receiver for the class-name-list and title provided" self systemOrganizer: SystemOrganization. metaClassIndicated := false. defaultTitle := aTitle. classList := nameList copy. self class openBrowserView: (self openSystemCatEditString: nil) label: aTitle "ClassListBrowser new initForClassesNamed: #(Browser CategoryViewer) title: 'Frogs'"! ! !ClassListBrowser methodsFor: 'title' stamp: 'sd 11/20/2005 21:26'! defaultTitle: aTitle "Set the browser's default title" defaultTitle := aTitle! ! !ClassListBrowser methodsFor: 'title' stamp: 'sw 7/18/2002 22:43'! labelString "Answer the label strilng to use on the browser" ^ defaultTitle ifNil: [super labelString]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassListBrowser class instanceVariableNames: ''! !ClassListBrowser class methodsFor: 'examples' stamp: 'sw 7/27/2002 16:01'! example1 "Put up a ClassListBrowser that shows all classes that have the string 'Pluggable' in their names" self browseClassesSatisfying: [:cl | cl name includesSubString: 'Pluggable'] title: 'Pluggables' "ClassListBrowser example1" ! ! !ClassListBrowser class methodsFor: 'examples' stamp: 'sd 4/17/2003 21:21'! example2 "Put up a ClassListBrowser that shows all classes whose names start with the letter S" self new initForClassesNamed: (self systemNavigation allClasses collect: [:c | c name] thenSelect: [:aName | aName first == $S]) title: 'All classes starting with S' "ClassListBrowser example2"! ! !ClassListBrowser class methodsFor: 'examples' stamp: 'sw 7/27/2002 16:03'! example3 "Put up a ClassListBrowser that shows all Variable classes" self browseClassesSatisfying: [:c | c isVariable] title: 'All Variable classes' "ClassListBrowser example3" ! ! !ClassListBrowser class methodsFor: 'examples' stamp: 'sw 7/27/2002 16:04'! example4 "Put up a ClassListBrowser that shows all classes implementing more than 100 methods" self browseClassesSatisfying: [:c | (c selectors size + c class selectors size) > 100] title: 'Classes with more than 100 methods' "ClassListBrowser example4" ! ! !ClassListBrowser class methodsFor: 'examples' stamp: 'sw 7/27/2002 14:32'! example5 "Put up a ClassListBrowser that shows all classes that lack class comments" self browseClassesSatisfying: [:c | c organization classComment isEmptyOrNil] title: 'Classes lacking class comments' "ClassListBrowser example5" ! ! !ClassListBrowser class methodsFor: 'examples' stamp: 'sw 7/27/2002 14:33'! example6 "Put up a ClassListBrowser that shows all classes that have class instance variables" self browseClassesSatisfying: [:c | c class instVarNames size > 0] title: 'Classes that define class-side instance variables' "ClassListBrowser example6"! ! !ClassListBrowser class methodsFor: 'instance creation' stamp: 'sd 4/17/2003 21:21'! browseClassesSatisfying: classBlock title: aTitle "Put up a ClassListBrowser showing all classes that satisfy the classBlock." self new initForClassesNamed: (self systemNavigation allClasses select: [:c | (classBlock value: c) == true] thenCollect: [:c | c name]) title: aTitle! ! BasicClassOrganizer subclass: #ClassOrganizer instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Classes'! !ClassOrganizer commentStamp: 'NS 4/6/2004 16:13' prior: 0! I represent method categorization information for classes. The handling of class comments has gone through a tortuous evolution. Grandfathered class comments (before late aug 98) have no time stamps, and historically, fileouts of class comments always substituted the timestamp reflecting the author and date/time at the moment of fileout; and historically any timestamps in a filed out class comment were dropped on the floor, with the author & time prevailing at the moment of filein being substituted. Such grandfathered comments now go out on fileouts with '' timestamp; class comments created after the 8/98 changes will have their correct timestamps preserved, though there is not yet a decent ui for reading those stamps other than filing out and looking at the file; nor is there yet any ui for browsing and recovering past versions of such comments. Everything in good time!!! !ClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 10:37'! addCategory: catString before: nextCategory | oldCategories | oldCategories := self categories copy. SystemChangeNotifier uniqueInstance doSilently: [ super addCategory: catString before: nextCategory]. self notifyOfChangedCategoriesFrom: oldCategories to: self categories.! ! !ClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/15/2004 12:28'! changeFromCategorySpecs: categorySpecs | oldDict oldCategories | oldDict := self elementCategoryDict. oldCategories := self categories copy. SystemChangeNotifier uniqueInstance doSilently: [ super changeFromCategorySpecs: categorySpecs]. self notifyOfChangedSelectorsOldDict: oldDict newDict: self elementCategoryDict. self notifyOfChangedCategoriesFrom: oldCategories to: self categories.! ! !ClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 10:37'! classify: element under: heading suppressIfDefault: aBoolean | oldCat newCat | oldCat := self categoryOfElement: element. SystemChangeNotifier uniqueInstance doSilently: [ super classify: element under: heading suppressIfDefault: aBoolean]. newCat := self categoryOfElement: element. self notifyOfChangedSelector: element from: oldCat to: newCat.! ! !ClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 10:37'! removeCategory: cat | oldCategories | oldCategories := self categories copy. SystemChangeNotifier uniqueInstance doSilently: [ super removeCategory: cat]. self notifyOfChangedCategoriesFrom: oldCategories to: self categories.! ! !ClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 10:37'! removeElement: element | oldCat | oldCat := self categoryOfElement: element. SystemChangeNotifier uniqueInstance doSilently: [ super removeElement: element]. self notifyOfChangedSelector: element from: oldCat to: (self categoryOfElement: element).! ! !ClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 10:38'! removeEmptyCategories | oldCategories | oldCategories := self categories copy. SystemChangeNotifier uniqueInstance doSilently: [ super removeEmptyCategories]. self notifyOfChangedCategoriesFrom: oldCategories to: self categories.! ! !ClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 10:38'! renameCategory: oldCatString toBe: newCatString | oldCat newCat oldElementsBefore oldElementsAfter | oldCat := oldCatString asSymbol. newCat := newCatString asSymbol. oldElementsBefore := self listAtCategoryNamed: oldCat. SystemChangeNotifier uniqueInstance doSilently: [ super renameCategory: oldCatString toBe: newCatString]. oldElementsAfter := (self listAtCategoryNamed: oldCat) asSet. oldElementsBefore do: [:each | (oldElementsAfter includes: each) ifFalse: [self notifyOfChangedSelector: each from: oldCat to: newCat]. ]. self notifyOfChangedCategoryFrom: oldCat to: newCat.! ! !ClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/12/2004 20:57'! setDefaultList: aSortedCollection | oldDict oldCategories | oldDict := self elementCategoryDict. oldCategories := self categories copy. SystemChangeNotifier uniqueInstance doSilently: [ super setDefaultList: aSortedCollection]. self notifyOfChangedSelectorsOldDict: oldDict newDict: self elementCategoryDict. self notifyOfChangedCategoriesFrom: oldCategories to: self categories.! ! !ClassOrganizer methodsFor: 'accessing' stamp: 'NS 4/7/2004 10:38'! sortCategories | oldCategories | oldCategories := self categories copy. SystemChangeNotifier uniqueInstance doSilently: [ super sortCategories]. self notifyOfChangedCategoriesFrom: oldCategories to: self categories.! ! !ClassOrganizer methodsFor: 'private' stamp: 'NS 4/7/2004 10:15'! notifyOfChangedCategoriesFrom: oldCollectionOrNil to: newCollectionOrNil (self hasSubject and: [oldCollectionOrNil ~= newCollectionOrNil]) ifTrue: [SystemChangeNotifier uniqueInstance classReorganized: self subject].! ! !ClassOrganizer methodsFor: 'private' stamp: 'NS 4/7/2004 23:02'! notifyOfChangedCategoryFrom: oldNameOrNil to: newNameOrNil (self hasSubject and: [oldNameOrNil ~= newNameOrNil]) ifTrue: [SystemChangeNotifier uniqueInstance classReorganized: self subject].! ! !ClassOrganizer methodsFor: 'private' stamp: 'NS 4/16/2004 10:47'! notifyOfChangedSelector: element from: oldCategory to: newCategory (self hasSubject and: [(oldCategory ~= newCategory)]) ifTrue: [ self subject notifyOfRecategorizedSelector: element from: oldCategory to: newCategory. ].! ! !ClassOrganizer methodsFor: 'private' stamp: 'eem 6/11/2008 17:00'! notifyOfChangedSelectorsOldDict: oldDictionaryOrNil newDict: newDictionaryOrNil (oldDictionaryOrNil isNil and: [newDictionaryOrNil isNil]) ifTrue: [^ self]. oldDictionaryOrNil isNil ifTrue: [ newDictionaryOrNil keysAndValuesDo: [:el :cat | self notifyOfChangedSelector: el from: nil to: cat]. ^ self. ]. newDictionaryOrNil isNil ifTrue: [ oldDictionaryOrNil keysAndValuesDo: [:el :cat | self notifyOfChangedSelector: el from: cat to: nil]. ^ self. ]. oldDictionaryOrNil keysAndValuesDo: [:el :cat | | newCat | newCat := newDictionaryOrNil at: el. self notifyOfChangedSelector: el from: cat to: newCat. ].! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassOrganizer class instanceVariableNames: ''! TestCase subclass: #ClassRenameFixTest instanceVariableNames: 'previousChangeSet testsChangeSet newClassName originalName' classVariableNames: '' poolDictionaries: '' category: 'Tests-Bugs'! !ClassRenameFixTest methodsFor: 'running' stamp: 'cmm 8/7/2005 18:20'! setUp previousChangeSet := ChangeSet current. testsChangeSet := ChangeSet new. ChangeSet newChanges: testsChangeSet. SystemChangeNotifier uniqueInstance notify: self ofSystemChangesOfItem: #class change: #Renamed using: #verifyRenameEvent:. super setUp! ! !ClassRenameFixTest methodsFor: 'running' stamp: 'cmm 8/7/2005 18:21'! tearDown self removeEverythingInSetFromSystem: testsChangeSet. ChangeSet newChanges: previousChangeSet. ChangeSorter removeChangeSet: testsChangeSet. previousChangeSet := nil. testsChangeSet := nil. SystemChangeNotifier uniqueInstance noMoreNotificationsFor: self. super tearDown.! ! !ClassRenameFixTest methodsFor: 'running' stamp: 'cmm 8/7/2005 19:04'! verifyRenameEvent: aRenamedEvent | renamedClass | self assert: aRenamedEvent isRenamed. renamedClass := aRenamedEvent item. self assert: (Smalltalk classNamed: newClassName) name = newClassName. self assert: renamedClass name = newClassName! ! !ClassRenameFixTest methodsFor: 'tests' stamp: 'cmm 8/7/2005 18:21'! renameClassUsing: aBlock | createdClass foundClasses | originalName := self newUniqueClassName. createdClass := Object subclass: originalName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ClassRenameFix-GeneradClass'. newClassName := self newUniqueClassName. aBlock value: createdClass value: newClassName. self assert: (Smalltalk classNamed: originalName) isNil. self assert: (Smalltalk classNamed: newClassName) notNil. foundClasses := Smalltalk organization listAtCategoryNamed: 'ClassRenameFix-GeneradClass'. self assert: (foundClasses notEmpty). self assert: (foundClasses includes: newClassName). self assert: (createdClass name = newClassName).! ! !ClassRenameFixTest methodsFor: 'tests' stamp: 'md 9/6/2005 18:30'! testRenameClassUsingClass "self run: #testRenameClassUsingClass" self renameClassUsing: [:class :newName | class rename: newName].! ! !ClassRenameFixTest methodsFor: 'private' stamp: 'md 9/6/2005 18:30'! newUniqueClassName "Return a class name that is not used in the system." "self new newClassName" | baseName newName | baseName := 'AutoGeneratedClassForTestingSystemChanges'. 1 to: 9999 do: [:number | newName := baseName , number printString. (Smalltalk hasClassNamed: newName) ifFalse: [^newName asSymbol]]. ^self error: 'Can no longer find a new and unique class name for the SystemChangeTest !!'! ! !ClassRenameFixTest methodsFor: 'private' stamp: 'md 9/6/2005 18:30'! removeEverythingInSetFromSystem: aChangeSet aChangeSet changedMessageList do: [:methodRef | methodRef actualClass removeSelector: methodRef methodSymbol]. aChangeSet changedClasses do: [:each | each isMeta ifFalse: [each removeFromSystemUnlogged]]! ! TestCase subclass: #ClassTest instanceVariableNames: 'className renamedName' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Classes'! !ClassTest methodsFor: 'setup' stamp: 'rw 10/7/2006 08:57'! deleteClass | cl | cl := Smalltalk at: className ifAbsent: [^self]. cl removeFromChanges; removeFromSystemUnlogged ! ! !ClassTest methodsFor: 'setup' stamp: 'rw 10/7/2006 08:57'! deleteRenamedClass | cl | cl := Smalltalk at: renamedName ifAbsent: [^self]. cl removeFromChanges; removeFromSystemUnlogged ! ! !ClassTest methodsFor: 'setup' stamp: 'rw 10/17/2006 22:05'! setUp className := #TUTU. renamedName := #RenamedTUTU. self deleteClass. self deleteRenamedClass. Object subclass: className instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Classes'! ! !ClassTest methodsFor: 'setup' stamp: 'rw 10/17/2006 22:08'! tearDown self deleteClass. self deleteRenamedClass! ! !ClassTest methodsFor: 'testing' stamp: 'md 1/5/2004 14:59'! testAddInstVarName "self run: #testAddInstVarName" | tutu | tutu := Smalltalk at: #TUTU. tutu addInstVarName: 'x'. self assert: (tutu instVarNames = #('x')). tutu addInstVarName: 'y'. self assert: (tutu instVarNames = #('x' 'y')) ! ! !ClassTest methodsFor: 'testing' stamp: 'rw 10/17/2006 22:13'! testRenaming "self debug: #testRenaming" "self run: #testRenaming" | oldName newMetaclassName class | oldName := className. newMetaclassName := (renamedName, #' class') asSymbol. class := Smalltalk at: oldName. class class compile: 'dummyMeth'. class rename: renamedName. self assert: class name = renamedName. self assert: (ChangeSet current changedClassNames includes: renamedName). self assert: (ChangeSet current changedClassNames includes: newMetaclassName). ! ! !ClassTest methodsFor: 'testing - access' stamp: 'sd 4/24/2008 22:11'! testHaSharedPools "self run: #testHaSharedPools" self deny: Point hasSharedPools. self assert: Date hasSharedPools! ! !ClassTest methodsFor: 'testing - class variables' stamp: 'marcus.denker 12/4/2008 11:12'! testClassVarNames self assert: (Object classVarNames includes: #DependentsFields). "A class and it's meta-class share the class variables" self assert: (Object classVarNames = Object class classVarNames).! ! !ClassTest methodsFor: 'testing - compiling' stamp: 'sd 6/5/2005 08:25'! testCompileAll self shouldnt: [ClassTest compileAll] raise: Error.! ! TestCase subclass: #ClassTestCase instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'SUnit-Utilities'! !ClassTestCase commentStamp: 'brp 7/26/2003 16:57' prior: 0! This class is intended for unit tests of individual classes and their metaclasses. It provides methods to determine the coverage of the unit tests. Subclasses are expected to re-implement #classesToBeTested and #selectorsToBeIgnored. They should also implement to confirm that all methods have been tested. #testCoverage super testCoverage. ! !ClassTestCase methodsFor: 'Coverage' stamp: 'apb 4/15/2006 11:50'! selectorsTested | literals | literals := Set new. self class selectorsAndMethodsDo: [ :s :m | (s beginsWith: 'test') ifTrue: [ literals addAll: (m messages)] ]. ^ literals asSortedArray! ! !ClassTestCase methodsFor: 'coverage' stamp: 'brp 7/27/2003 12:39'! classToBeTested self subclassResponsibility! ! !ClassTestCase methodsFor: 'coverage' stamp: 'brp 7/26/2003 16:35'! selectorsNotTested ^ self selectorsToBeTested difference: self selectorsTested. ! ! !ClassTestCase methodsFor: 'coverage' stamp: 'brp 7/26/2003 17:22'! selectorsToBeIgnored ^ #(#DoIt #DoItIn:)! ! !ClassTestCase methodsFor: 'coverage' stamp: 'brp 7/27/2003 12:40'! selectorsToBeTested ^ ( { self classToBeTested. self classToBeTested class } gather: [:c | c selectors]) difference: self selectorsToBeIgnored! ! !ClassTestCase methodsFor: 'tests' stamp: 'marcus.denker 7/29/2009 15:27'! testClassComment self should: [self targetClass organization hasComment].! ! !ClassTestCase methodsFor: 'tests' stamp: 'brp 12/14/2003 15:51'! testCoverage | untested | self class mustTestCoverage ifTrue: [ untested := self selectorsNotTested. self assert: untested isEmpty description: untested size asString, ' selectors are not covered' ]! ! !ClassTestCase methodsFor: 'tests' stamp: 'md 3/25/2003 23:07'! testNew self shouldnt: [self targetClass new] raise: Error.! ! !ClassTestCase methodsFor: 'tests' stamp: 'md 3/26/2003 17:24'! testUnCategorizedMethods | categories slips | categories := self categoriesForClass: self targetClass. slips := categories select: [:each | each = #'as yet unclassified']. self should: [slips isEmpty]. ! ! !ClassTestCase methodsFor: 'private' stamp: 'md 1/28/2004 11:32'! categoriesForClass: aClass ^ aClass organization allMethodSelectors collect: [:each | aClass organization categoryOfElement: each]. ! ! !ClassTestCase methodsFor: 'private' stamp: 'md 1/28/2004 11:28'! targetClass |className| className := self class name asText copyFrom: 0 to: self class name size - 4. ^ Smalltalk at: (className asString asSymbol). ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassTestCase class instanceVariableNames: ''! !ClassTestCase class methodsFor: 'testing' stamp: 'md 2/22/2006 14:21'! isAbstract "Override to true if a TestCase subclass is Abstract and should not have TestCase instances built from it" ^self name = #ClassTestCase ! ! !ClassTestCase class methodsFor: 'testing' stamp: 'brp 12/14/2003 15:50'! mustTestCoverage ^ false! ! TraitDescription subclass: #ClassTrait uses: TApplyingOnClassSide instanceVariableNames: 'baseTrait' classVariableNames: '' poolDictionaries: '' category: 'Traits-Kernel'! !ClassTrait commentStamp: '' prior: 0! While every class has an associated metaclass, a trait can have an associated classtrait, an instance of me. To preserve metaclass compatibility, the associated classtrait (if there is one) is automatically applied to the metaclass, whenever a trait is applied to a class. Consequently, a trait with an associated classtrait can only be applied to classes, whereas a trait without a classtrait can be applied to both classes and metaclasses.! !ClassTrait methodsFor: '*monticello' stamp: 'damiencassou 7/30/2009 12:10'! asMCDefinition ^MCClassTraitDefinition baseTraitName: self baseTrait name classTraitComposition: self traitCompositionString category: self category ! ! !ClassTrait methodsFor: 'accessing' stamp: 'damiencassou 8/6/2009 11:37'! category ^ self baseTrait category! ! !ClassTrait methodsFor: 'accessing' stamp: 'al 4/21/2004 09:38'! name ^self baseTrait name , ' classTrait'! ! !ClassTrait methodsFor: 'accessing parallel hierarchy' stamp: 'al 3/16/2004 10:38'! baseTrait ^baseTrait! ! !ClassTrait methodsFor: 'accessing parallel hierarchy' stamp: 'al 3/16/2004 10:48'! baseTrait: aTrait self assert: aTrait isBaseTrait. baseTrait := aTrait ! ! !ClassTrait methodsFor: 'accessing parallel hierarchy' stamp: 'al 3/16/2004 10:38'! classTrait ^self! ! !ClassTrait methodsFor: 'accessing parallel hierarchy' stamp: 'al 4/20/2004 09:44'! classTrait: aClassTrait self error: 'Trait is already a class trait!!' ! ! !ClassTrait methodsFor: 'accessing parallel hierarchy' stamp: 'al 3/16/2004 10:41'! hasClassTrait ^false! ! !ClassTrait methodsFor: 'accessing parallel hierarchy' stamp: 'al 3/16/2004 10:48'! isBaseTrait ^false! ! !ClassTrait methodsFor: 'accessing parallel hierarchy' stamp: 'al 3/16/2004 10:48'! isClassTrait ^true! ! !ClassTrait methodsFor: 'compiling' stamp: 'al 4/7/2004 14:54'! compile: text classified: category withStamp: changeStamp notifying: requestor logSource: logSource | classSideUsersOfBaseTrait message | classSideUsersOfBaseTrait := self baseTrait users select: [:each | each isClassSide]. classSideUsersOfBaseTrait isEmpty ifFalse: [ message := String streamContents: [:stream | stream nextPutAll: 'The instance side of this trait is used on '; cr. classSideUsersOfBaseTrait do: [:each | stream nextPutAll: each name] separatedBy: [ stream nextPutAll: ', ']. stream cr; nextPutAll: ' You can not add methods to the class side of this trait!!']. ^TraitException signal: message]. ^super compile: text classified: category withStamp: changeStamp notifying: requestor logSource: logSource! ! !ClassTrait methodsFor: 'composition'! assertConsistantCompositionsForNew: aTraitComposition "Applying or modifying a trait composition on the class side of a behavior has some restrictions." | baseTraits notAddable message | baseTraits := aTraitComposition traits select: [:each | each isBaseTrait]. baseTraits isEmpty ifFalse: [ notAddable := (baseTraits reject: [:each | each classSide methodDict isEmpty]). notAddable isEmpty ifFalse: [ message := String streamContents: [:stream | stream nextPutAll: 'You can not add the base trait(s)'; cr. notAddable do: [:each | stream nextPutAll: each name] separatedBy: [ stream nextPutAll: ', ']. stream cr; nextPutAll: 'to this composition because it/they define(s) methods on the class side.']. ^TraitCompositionException signal: message]]. (self instanceSide traitComposition traits asSet = (aTraitComposition traits select: [:each | each isClassTrait] thenCollect: [:each | each baseTrait]) asSet) ifFalse: [ ^TraitCompositionException signal: 'You can not add or remove class side traits on the class side of a composition. (But you can specify aliases or exclusions for existing traits or add a trait which does not have any methods on the class side.)']! ! !ClassTrait methodsFor: 'composition'! noteNewBaseTraitCompositionApplied: aTraitComposition "The argument is the new trait composition of my base trait - add the new traits or remove non existing traits on my class side composition. (Each class trait in my composition has its base trait on the instance side of the composition - manually added traits to the class side are always base traits.)" | newComposition traitsFromInstanceSide | traitsFromInstanceSide := self traitComposition traits select: [:each | each isClassTrait] thenCollect: [:each | each baseTrait]. newComposition := self traitComposition copyTraitExpression. (traitsFromInstanceSide copyWithoutAll: aTraitComposition traits) do: [:each | newComposition removeFromComposition: each classTrait]. (aTraitComposition traits copyWithoutAll: traitsFromInstanceSide) do: [:each | newComposition add: (each classTrait)]. self setTraitComposition: newComposition! ! !ClassTrait methodsFor: 'composition' stamp: 'al 7/18/2004 14:02'! uses: aTraitCompositionOrArray | copyOfOldTrait newComposition | copyOfOldTrait := self copy. newComposition := aTraitCompositionOrArray asTraitComposition. self assertConsistantCompositionsForNew: newComposition. self setTraitComposition: newComposition. SystemChangeNotifier uniqueInstance traitDefinitionChangedFrom: copyOfOldTrait to: self.! ! !ClassTrait methodsFor: 'copying' stamp: 'dvf 8/30/2005 16:51'! copy "Make a copy of the receiver. Share the reference to the base trait." ^(self class new) baseTrait: self baseTrait; initializeFrom: self; yourself! ! !ClassTrait methodsFor: 'filein/out' stamp: 'al 3/26/2006 21:31'! definitionST80 ^String streamContents: [:stream | stream nextPutAll: self name; crtab; nextPutAll: 'uses: '; nextPutAll: self traitCompositionString]! ! !ClassTrait methodsFor: 'initialize' stamp: 'al 7/18/2004 12:11'! baseClass: aTrait traitComposition: aComposition methodDict: aMethodDict localSelectors: aSet organization: aClassOrganization self baseTrait: aTrait. self traitComposition: aComposition methodDict: aMethodDict localSelectors: aSet organization: aClassOrganization ! ! !ClassTrait methodsFor: 'initialize' stamp: 'dvf 8/30/2005 16:48'! initializeFrom: anotherClassTrait traitComposition := self traitComposition copyTraitExpression. methodDict := self methodDict copy. localSelectors := self localSelectors copy. organization := self organization copy.! ! !ClassTrait methodsFor: 'initialize' stamp: 'al 3/24/2004 20:37'! initializeWithBaseTrait: aTrait self baseTrait: aTrait. self noteNewBaseTraitCompositionApplied: aTrait traitComposition. aTrait users do: [:each | self addUser: each classSide]. ! ! !ClassTrait methodsFor: 'initialize' stamp: 'al 7/17/2004 22:56'! traitComposition: aComposition methodDict: aMethodDict localSelectors: aSet organization: aClassOrganization "Used by copy of Trait" localSelectors := aSet. methodDict := aMethodDict. traitComposition := aComposition. self organization: aClassOrganization! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClassTrait class uses: TApplyingOnClassSide classTrait instanceVariableNames: ''! !ClassTrait class methodsFor: 'instance creation' stamp: 'al 3/23/2004 19:41'! for: aTrait ^self new initializeWithBaseTrait: aTrait; yourself! ! TraitsTestCase subclass: #ClassTraitTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Traits'! !ClassTraitTest methodsFor: 'testing' stamp: 'al 3/26/2006 12:15'! testChanges "Test the most important features to ensure that general functionality of class traits are working." "self run: #testChanges" | classTrait | classTrait := self t1 classTrait. classTrait compile: 'm1ClassSide ^17' classified: 'mycategory'. "local selectors" self assert: (classTrait includesLocalSelector: #m1ClassSide). self deny: (classTrait includesLocalSelector: #otherSelector). "propagation" self assert: (self t5 classSide methodDict includesKey: #m1ClassSide). self assert: (self c2 class methodDict includesKey: #m1ClassSide). self shouldnt: [self c2 m1ClassSide] raise: Error. self assert: self c2 m1ClassSide = 17. "category" self assert: (self c2 class organization categoryOfElement: #m1ClassSide) = 'mycategory'. "conflicts" self t2 classSide compile: 'm1ClassSide' classified: 'mycategory'. self assert: (self c2 class methodDict includesKey: #m1ClassSide). self deny: (self c2 class includesLocalSelector: #m1ClassSide). self should: [self c2 m1ClassSide] raise: Error. "conflict category" self assert: (self c2 class organization categoryOfElement: #m1ClassSide) = #mycategory! ! !ClassTraitTest methodsFor: 'testing' stamp: 'dvf 8/26/2005 14:32'! testConflictsAliasesAndExclusions "conflict" self t1 classTrait compile: 'm2ClassSide: x ^99' classified: 'mycategory'. self assert: (self t1 classTrait includesLocalSelector: #m2ClassSide:). self assert: (self t5 classTrait >> #m2ClassSide:) isConflict. self assert: (self c2 class >> #m2ClassSide:) isConflict. "exclusion and alias" self assert: self t5 classSide traitComposition asString = 'T1 classTrait + T2 classTrait'. self t5 classSide setTraitCompositionFrom: (self t1 classTrait @ { (#m2ClassSideAlias1: -> #m2ClassSide:) } + self t2 classTrait) @ { (#m2ClassSideAlias2: -> #m2ClassSide:) } - { #m2ClassSide: }. self deny: (self t5 classTrait >> #m2ClassSide:) isConflict. self deny: (self c2 class >> #m2ClassSide:) isConflict. self assert: (self c2 m2ClassSideAlias1: 13) = 99. self assert: (self c2 m2ClassSideAlias2: 13) = 13! ! !ClassTraitTest methodsFor: 'testing' stamp: 'dvf 8/30/2005 16:17'! testInitialization "self run: #testInitialization" | classTrait | classTrait := self t1 classTrait. self assert: self t1 hasClassTrait. self assert: self t1 classTrait == classTrait. self assert: classTrait isClassTrait. self assert: classTrait classSide == classTrait. self deny: classTrait isBaseTrait. self assert: classTrait baseTrait == self t1. "assert classtrait methods are propagated to users when setting traitComposition" self assert: self t4 hasClassTrait. self assert: self t5 hasClassTrait. self assert: (self t2 classSide includesLocalSelector: #m2ClassSide:). self assert: (self t4 classSide methodDict includesKey: #m2ClassSide:). self assert: (self t5 classSide methodDict includesKey: #m2ClassSide:). self assert: (self c2 m2ClassSide: 17) = 17! ! !ClassTraitTest methodsFor: 'testing' stamp: 'al 3/26/2006 12:06'! testUsers self assert: self t2 classSide users size = 3. self assert: (self t2 classSide users includesAllOf: { (self t4 classTrait). (self t5 classTrait). (self t6 classTrait) }). self assert: self t5 classSide users size = 1. self assert: self t5 classSide users anyOne = self c2 class. self c2 setTraitCompositionFrom: self t1 + self t5. self assert: self t5 classSide users size = 1. self assert: self t5 classSide users anyOne = self c2 class. self c2 setTraitComposition: self t2 asTraitComposition. self assert: self t5 classSide users isEmpty! ! Object subclass: #Clipboard instanceVariableNames: 'contents recent' classVariableNames: 'Default' poolDictionaries: '' category: 'System-Clipboard'! !Clipboard commentStamp: 'michael.rueger 3/2/2009 13:22' prior: 0! The Clipboard class is the abstract superclass for the concrete platform specific clipboard. The legacy clipboard support using the VM supplied primitives was moved to SqueakClipboard. The Clipboard implements a basic buffering scheme for text. The currently selected text is also exported to the OS so that text can be copied from and to other applications. Commonly only a single instance is used (the default clipboard) but applications are free to use other than the default clipboard if necessary.! !Clipboard methodsFor: 'accessing' stamp: 'ar 1/15/2001 18:32'! chooseRecentClipping "Clipboard chooseRecentClipping" "Choose by menu from among the recent clippings" recent ifNil: [^ nil]. ^ (SelectionMenu labelList: (recent collect: [:txt | ((txt asString contractTo: 50) copyReplaceAll: Character cr asString with: '\') copyReplaceAll: Character tab asString with: '|']) selections: recent) startUp. ! ! !Clipboard methodsFor: 'accessing' stamp: 'michael.rueger 6/10/2009 13:42'! clipboardText "Return the text currently in the clipboard. If the system clipboard is empty, or if it differs from the Smalltalk clipboard text, use the Smalltalk clipboard. This is done since (a) the Mac clipboard gives up on very large chunks of text and (b) since not all platforms support the notion of a clipboard." | string decodedString | string := self primitiveClipboardText. (string isEmpty or: [string = contents asString]) ifTrue: [^ contents]. decodedString := string convertFromWithConverter: UTF8TextConverter new. decodedString := decodedString replaceAll: 10 asCharacter with: 13 asCharacter. ^ decodedString = contents asString ifTrue: [contents] ifFalse: [decodedString asText]. ! ! !Clipboard methodsFor: 'accessing' stamp: 'michael.rueger 3/25/2009 14:23'! clipboardText: text | string | string := text asString. self noteRecentClipping: text asText. contents := text asText. string := string convertToWithConverter: UTF8TextConverter new. self primitiveClipboardText: string. ! ! !Clipboard methodsFor: 'initialize' stamp: 'alain.plantec 5/28/2009 09:47'! initialize super initialize. contents := '' asText. recent := OrderedCollection new! ! !Clipboard methodsFor: 'primitives' stamp: 'michael.rueger 3/25/2009 14:23'! primitiveClipboardText "Get the current clipboard text. Return the empty string if the primitive fails." ^ ''! ! !Clipboard methodsFor: 'primitives' stamp: 'michael.rueger 3/25/2009 14:23'! primitiveClipboardText: aString "Set the current clipboard text to the given string." "don't fail if the primitive is not implemented"! ! !Clipboard methodsFor: 'private' stamp: 'ar 1/15/2001 18:34'! noteRecentClipping: text "Keep most recent clippings in a queue for pasteRecent (paste... command)" text isEmpty ifTrue: [^ self]. text size > 50000 ifTrue: [^ self]. (recent includes: text) ifTrue: [^ self]. recent addFirst: text. [recent size > 5] whileTrue: [recent removeLast]. ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Clipboard class instanceVariableNames: ''! !Clipboard class methodsFor: 'accessing' stamp: 'ar 1/15/2001 18:45'! chooseRecentClipping "Clipboard chooseRecentClipping" "Choose by menu from among the recent clippings" ^self default chooseRecentClipping! ! !Clipboard class methodsFor: 'accessing' stamp: 'ar 1/15/2001 18:35'! clipboardText "Clipboard clipboardText" ^self default clipboardText.! ! !Clipboard class methodsFor: 'accessing' stamp: 'ar 1/15/2001 18:35'! clipboardText: aText ^self default clipboardText: aText! ! !Clipboard class methodsFor: 'accessing' stamp: 'michael.rueger 3/2/2009 11:12'! default ^Default ifNil: [Default := OSPlatform current clipboardClass new].! ! !Clipboard class methodsFor: 'initialization' stamp: 'michael.rueger 3/2/2009 11:11'! initialize "Clipboard initialize" Smalltalk addToStartUpList: self. Smalltalk addToShutDownList: self. self startUp: true.! ! !Clipboard class methodsFor: 'initialization' stamp: 'michael.rueger 3/2/2009 11:11'! shutDown: quitting "Squeak is shutting down. If this platform requires specific shutdown code, this is a great place to put it." ! ! !Clipboard class methodsFor: 'initialization' stamp: 'michael.rueger 3/2/2009 11:12'! startUp: resuming "Squeak is starting up. If this platform requires specific intialization, this is a great place to put it." resuming ifTrue: [Default := nil]! ! PluggableCanvas subclass: #ClippingCanvas instanceVariableNames: 'canvas clipRect' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'! !ClippingCanvas commentStamp: '' prior: 0! A modified canvas which clips all drawing commands.! !ClippingCanvas methodsFor: 'accessing' stamp: 'ls 3/25/2000 22:56'! clipRect ^clipRect! ! !ClippingCanvas methodsFor: 'accessing' stamp: 'ls 3/26/2000 14:22'! contentsOfArea: aRectangle into: aForm self flag: #hack. "ignore the clipping specification for this command. This is purely so that CachingCanvas will work properly when clipped. There *has* to be a clean way to do this...." ^canvas contentsOfArea: aRectangle into: aForm! ! !ClippingCanvas methodsFor: 'accessing' stamp: 'ls 3/20/2000 21:17'! form ^canvas form! ! !ClippingCanvas methodsFor: 'accessing' stamp: 'ls 3/20/2000 21:15'! shadowColor ^canvas shadowColor! ! !ClippingCanvas methodsFor: 'initialization' stamp: 'ls 3/20/2000 20:44'! canvas: aCanvas clipRect: aRectangle canvas := aCanvas. clipRect := aRectangle.! ! !ClippingCanvas methodsFor: 'testing' stamp: 'ls 3/20/2000 21:17'! isBalloonCanvas ^canvas isBalloonCanvas! ! !ClippingCanvas methodsFor: 'testing' stamp: 'ls 3/20/2000 21:18'! isShadowDrawing ^canvas isShadowDrawing! ! !ClippingCanvas methodsFor: 'private' stamp: 'ls 3/20/2000 20:44'! apply: aBlock "apply the given block to the inner canvas with clipRect as the clipping rectangle" canvas clipBy: clipRect during: aBlock! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClippingCanvas class instanceVariableNames: ''! !ClippingCanvas class methodsFor: 'instance creation' stamp: 'ls 3/20/2000 20:45'! canvas: aCanvas clipRect: aRectangle ^self new canvas: aCanvas clipRect: aRectangle! ! TestCase subclass: #ClosureCompilerTest instanceVariableNames: '' classVariableNames: 'CmpRR CogRTLOpcodes Jump MoveCqR Nop' poolDictionaries: '' category: 'Tests-Compiler'! !ClosureCompilerTest methodsFor: 'source' stamp: 'eem 7/1/2009 10:51'! closureCases ^#( '| n | n := 1. ^n + n' '| i | i := 0. [i := i + 1. i <= 10] whileTrue. ^i' '[:c :s| | mn | mn := Compiler new compile: (c sourceCodeAt: s) in: c notifying: nil ifFail: [self halt]. mn generate: #(0 0 0 0). {mn blockExtentsToTempsMap. mn encoder schematicTempNames}] value: AbstractInstructionTests value: #runBinaryConditionalJumps:' 'inject: thisValue into: binaryBlock | nextValue | nextValue := thisValue. self do: [:each | nextValue := binaryBlock value: nextValue value: each]. ^nextValue' 'runBinaryConditionalJumps: assertPrintBar "CogIA32CompilerTests new runBinaryConditionalJumps: false" | mask reg1 reg2 reg3 | mask := 1 << self processor bitsInWord - 1. self concreteCompilerClass dataRegistersWithAccessorsDo: [:n :get :set| n = 0 ifTrue: [reg1 := get]. n = 1 ifTrue: [reg2 := set]. n = 2 ifTrue: [reg3 := set]]. #( (JumpAbove > unsigned) (JumpBelowOrEqual <= unsigned) (JumpBelow < unsigned) (JumpAboveOrEqual >= unsigned) (JumpGreater > signed) (JumpLessOrEqual <= signed) (JumpLess < signed) (JumpGreaterOrEqual >= signed) (JumpZero = signed) (JumpNonZero ~= signed)) do: [:triple| [:opName :relation :signednessOrResult| | opcode jumpNotTaken jumpTaken nop memory bogus | self resetGen. opcode := CogRTLOpcodes classPool at: opName. self gen: CmpRR operand: 2 operand: 1. jumpTaken := self gen: opcode. self gen: MoveCqR operand: 0 operand: 0. jumpNotTaken := self gen: Jump. jumpTaken jmpTarget: (self gen: MoveCqR operand: 1 operand: 0). jumpNotTaken jmpTarget: (nop := self gen: Nop). memory := self generateInstructions. bogus := false. self pairs: (-2 to: 2) do: [:a :b| | taken | self processor reset; perform: reg2 with: a signedIntToLong; perform: reg3 with: b signedIntToLong. [self processor singleStepIn: memory. self processor pc ~= nop address] whileTrue. taken := (self processor perform: reg1) = 1. assertPrintBar ifTrue: [self assert: taken = (signednessOrResult == #unsigned ifTrue: [(a bitAnd: mask) perform: relation with: (b bitAnd: mask)] ifFalse: [a perform: relation with: b])] ifFalse: [Transcript nextPutAll: reg2; nextPut: $(; print: a; nextPutAll: '') ''; nextPutAll: relation; space; nextPutAll: reg3; nextPut: $(; print: b; nextPutAll: '') = ''; print: taken; cr; flush. taken = (signednessOrResult == #unsigned ifTrue: [(a bitAnd: mask) perform: relation with: (b bitAnd: mask)] ifFalse: [a perform: relation with: b]) ifFalse: [bogus := true]]]. bogus ifTrue: [self processor printRegistersOn: Transcript. Transcript show: (self processor disassembleInstructionAt: jumpTaken address In: memory); cr]] valueWithArguments: triple]' 'mapFromBlockStartsIn: aMethod toTempVarsFrom: schematicTempNamesString constructor: aDecompilerConstructor | map | map := aMethod mapFromBlockKeys: aMethod startpcsToBlockExtents keys asSortedCollection toSchematicTemps: schematicTempNamesString. map keysAndValuesDo: [:startpc :tempNameTupleVector| | subMap tempVector numTemps | subMap := Dictionary new. "Find how many temp slots there are (direct & indirect temp vectors) and for each indirect temp vector find how big it is." tempNameTupleVector do: [:tuple| tuple last isArray ifTrue: [subMap at: tuple last first put: tuple last last. numTemps := tuple last first] ifFalse: [numTemps := tuple last]]. "create the temp vector for this scope level." tempVector := Array new: numTemps. "fill it in with any indirect temp vectors" subMap keysAndValuesDo: [:index :size| tempVector at: index put: (Array new: size)]. "fill it in with temp nodes." tempNameTupleVector do: [:tuple| | itv | tuple last isArray ifTrue: [itv := tempVector at: tuple last first. itv at: tuple last last put: (aDecompilerConstructor codeTemp: tuple last last - 1 named: tuple first)] ifFalse: [tempVector at: tuple last put: (aDecompilerConstructor codeTemp: tuple last - 1 named: tuple first)]]. "replace any indirect temp vectors with proper RemoteTempVectorNodes" subMap keysAndValuesDo: [:index :size| tempVector at: index put: (aDecompilerConstructor codeRemoteTemp: index remoteTemps: (tempVector at: index))]. "and update the entry in the map" map at: startpc put: tempVector]. ^map' 'gnuifyFrom: inFileStream to: outFileStream "convert interp.c to use GNU features" | inData beforeInterpret inInterpret inInterpretVars beforePrimitiveResponse inPrimitiveResponse | inData := inFileStream upToEnd withSqueakLineEndings. inFileStream close. "print a header" outFileStream nextPutAll: ''/* This file has been post-processed for GNU C */''; cr; cr; cr. beforeInterpret := true. "whether we are before the beginning of interpret()" inInterpret := false. "whether we are in the middle of interpret" inInterpretVars := false. "whether we are in the variables of interpret" beforePrimitiveResponse := true. "whether we are before the beginning of primitiveResponse()" inPrimitiveResponse := false. "whether we are inside of primitiveResponse" ''Gnuifying'' displayProgressAt: Sensor cursorPoint from: 1 to: (inData occurrencesOf: Character cr) during: [:bar | | lineNumber | lineNumber := 0. inData linesDo: [ :inLine | | outLine extraOutLine caseLabel | bar value: (lineNumber := lineNumber + 1). outLine := inLine. "print out one line for each input line; by default, print out the line that was input, but some rules modify it" extraOutLine := nil. "occasionally print a second output line..." beforeInterpret ifTrue: [ inLine = ''#include "sq.h"'' ifTrue: [ outLine := ''#include "sqGnu.h"'' ]. inLine = ''interpret(void) {'' ifTrue: [ "reached the beginning of interpret" beforeInterpret := false. inInterpret := true. inInterpretVars := true ] ] ifFalse: [ inInterpretVars ifTrue: [ (inLine findString: ''register struct foo * foo = &fum;'') > 0 ifTrue: [ outLine := ''register struct foo * foo FOO_REG = &fum;'' ]. (inLine findString: '' localIP;'') > 0 ifTrue: [ outLine := '' char* localIP IP_REG;'' ]. (inLine findString: '' localFP;'') > 0 ifTrue: [ outLine := '' char* localFP FP_REG;'' ]. (inLine findString: '' localSP;'') > 0 ifTrue: [ outLine := '' char* localSP SP_REG;'' ]. (inLine findString: '' currentBytecode;'') > 0 ifTrue: [ outLine := '' sqInt currentBytecode CB_REG;'' ]. inLine isEmpty ifTrue: [ "reached end of variables" inInterpretVars := false. outLine := '' JUMP_TABLE;''. extraOutLine := inLine ] ] ifFalse: [ inInterpret ifTrue: [ "working inside interpret(); translate the switch statement" (inLine beginsWith: '' case '') ifTrue: [ caseLabel := (inLine findTokens: '' :'') second. outLine := '' CASE('', caseLabel, '')'' ]. inLine = '' break;'' ifTrue: [ outLine := '' BREAK;'' ]. inLine = ''}'' ifTrue: [ "all finished with interpret()" inInterpret := false ] ] ifFalse: [ beforePrimitiveResponse ifTrue: [ (inLine beginsWith: ''primitiveResponse('') ifTrue: [ "into primitiveResponse we go" beforePrimitiveResponse := false. inPrimitiveResponse := true. extraOutLine := '' PRIM_TABLE;'' ] ] ifFalse: [ inPrimitiveResponse ifTrue: [ inLine = '' switch (primitiveIndex) {'' ifTrue: [ extraOutLine := outLine. outLine := '' PRIM_DISPATCH;'' ]. inLine = '' switch (GIV(primitiveIndex)) {'' ifTrue: [ extraOutLine := outLine. outLine := '' PRIM_DISPATCH;'' ]. (inLine beginsWith: '' case '') ifTrue: [ caseLabel := (inLine findTokens: '' :'') second. outLine := '' CASE('', caseLabel, '')'' ]. inLine = ''}'' ifTrue: [ inPrimitiveResponse := false ] ] ] ] ] ]. outFileStream nextPutAll: outLine; cr. extraOutLine ifNotNil: [ outFileStream nextPutAll: extraOutLine; cr ]]]. outFileStream close' )! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/24/2008 12:28'! doTestDebuggerTempAccessWith: one with: two "Test debugger access for temps" | outerContext local1 remote1 | outerContext := thisContext. local1 := 3. remote1 := 1/2. self assert: (Compiler new evaluate: 'one' in: thisContext to: self) == one. self assert: (Compiler new evaluate: 'two' in: thisContext to: self) == two. self assert: (Compiler new evaluate: 'local1' in: thisContext to: self) == local1. self assert: (Compiler new evaluate: 'remote1' in: thisContext to: self) == remote1. Compiler new evaluate: 'local1 := -3.0' in: thisContext to: self. self assert: local1 = -3.0. (1 to: 2) do: [:i| | local2 r1 r2 r3 r4 | local2 := i * 3. remote1 := local2 / 7. self assert: thisContext ~~ outerContext. self assert: (r1 := Compiler new evaluate: 'one' in: thisContext to: self) == one. self assert: (r2 := Compiler new evaluate: 'two' in: thisContext to: self) == two. self assert: (r3 := Compiler new evaluate: 'i' in: thisContext to: self) == i. self assert: (r4 := Compiler new evaluate: 'local2' in: thisContext to: self) == local2. self assert: (r4 := Compiler new evaluate: 'remote1' in: thisContext to: self) == remote1. self assert: (r4 := Compiler new evaluate: 'remote1' in: outerContext to: self) == remote1. Compiler new evaluate: 'local2 := 15' in: thisContext to: self. self assert: local2 = 15. Compiler new evaluate: 'local1 := 25' in: thisContext to: self. self assert: local1 = 25. { r1. r2. r3. r4 } "placate the compiler"]. self assert: local1 = 25. self assert: remote1 = (6/7)! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/4/2008 16:58'! supportTestSourceRangeAccessForDecompiledInjectInto: method source: source "Test debugger source range selection for inject:into:" ^self supportTestSourceRangeAccessForInjectInto: method source: source selectionSequence: #( ':= t1' 'do: [:t4 | t3 := t2 value: t3 value: t4]' 'value: t3 value: t4' ':= t2 value: t3 value: t4' ']' 'value: t3 value: t4' ':= t2 value: t3 value: t4' ']' '^t3')! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/4/2008 19:44'! supportTestSourceRangeAccessForDecompiledNoBytecodeInjectInto: method source: source "Test debugger source range selection for inject:into:" ^self supportTestSourceRangeAccessForInjectInto: method source: source selectionSequence: #( 'at: 1 put: t1' 'do: [:t4 | t3 at: 1 put: (t2 value: (t3 at: 1) value: t4)]' 'value: (t3 at: 1) value: t4' 'at: 1 put: (t2 value: (t3 at: 1) value: t4)' ']' 'value: (t3 at: 1) value: t4' 'at: 1 put: (t2 value: (t3 at: 1) value: t4)' ']' '^t3 at: 1')! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 7/24/2009 20:53'! supportTestSourceRangeAccessForInjectInto: method source: source "Test debugger source range selection for inject:into:" ^self supportTestSourceRangeAccessForInjectInto: method source: source selectionSequence: #( ':= thisValue' 'do: [:each | nextValue := binaryBlock value: nextValue value: each]' 'value: nextValue value: each' ':= binaryBlock value: nextValue value: each' 'nextValue := binaryBlock value: nextValue value: each' 'value: nextValue value: each' ':= binaryBlock value: nextValue value: each' 'nextValue := binaryBlock value: nextValue value: each' '^nextValue')! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 7/29/2008 17:16'! supportTestSourceRangeAccessForInjectInto: method source: source selectionSequence: selections "Test debugger source range selection for inject:into:" | evaluationCount sourceMap debugTokenSequence debugCount | DebuggerMethodMap voidMapCache. evaluationCount := 0. sourceMap := method debuggerMap abstractSourceMap. debugTokenSequence := selections collect: [:string| Scanner new scanTokens: string]. debugCount := 0. thisContext runSimulated: [(1 to: 2) withArgs: { 0. [:sum :each| evaluationCount := evaluationCount + 1. sum + each]} executeMethod: method] contextAtEachStep: [:ctxt| | range debugTokens | (ctxt method == method and: ["Exclude the send of #blockCopy: or #closureCopy:copiedValues: and braceWith:with: to create the block, and the #new: and #at:'s for the indirect temp vector. This for compilation without closure bytecodes. (Note that at:put:'s correspond to stores)" (ctxt willSend and: [(#(closureCopy:copiedValues: blockCopy: new: at: braceWith:with:) includes: ctxt selectorToSendOrSelf) not]) "Exclude the store of the argument into the home context (for BlueBook blocks) and the store of an indirection vector into an initial temp" or: [(ctxt willStore and: [(ctxt isBlock and: [ctxt pc = ctxt startpc]) not and: [(ctxt isBlock not and: [(method usesClosureBytecodes and: [ctxt abstractPC = 2])]) not]]) or: [ctxt willReturn]]]) ifTrue: [debugTokens := debugTokenSequence at: (debugCount := debugCount + 1) ifAbsent: [#(bogusToken)]. self assert: (sourceMap includesKey: ctxt abstractPC). range := sourceMap at: ctxt abstractPC ifAbsent: [(1 to: 0)]. self assert: (Scanner new scanTokens: (source copyFrom: range first to: range last)) = debugTokens]]. self assert: evaluationCount = 2! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/5/2009 17:11'! testBlockNumbering "Test that the compiler and CompiledMethod agree on the block numbering of a substantial doit." "self new testBlockNumbering" | methodNode method tempRefs | methodNode := Parser new encoderClass: EncoderForV3PlusClosures; parse: 'foo | numCopiedValuesCounts | numCopiedValuesCounts := Dictionary new. 0 to: 32 do: [:i| numCopiedValuesCounts at: i put: 0]. Transcript clear. Smalltalk allClasses remove: GeniePlugin; do: [:c| {c. c class} do: [:b| Transcript nextPut: b name first; endEntry. b selectorsAndMethodsDo: [:s :m| | pn | m isQuick not ifTrue: [pn := b parserClass new encoderClass: EncoderForV3PlusClosures; parse: (b sourceCodeAt: s) class: b. pn generate: #(0 0 0 0). [pn accept: nil] on: MessageNotUnderstood do: [:ex| | msg numCopied | msg := ex message. (msg selector == #visitBlockNode: and: [(msg argument instVarNamed: ''optimized'') not]) ifTrue: [numCopied := (msg argument computeCopiedValues: pn) size. numCopiedValuesCounts at: numCopied put: (numCopiedValuesCounts at: numCopied) + 1]. msg setSelector: #==. ex resume: nil]]]]]. numCopiedValuesCounts' class: Object. method := methodNode generate: #(0 0 0 0). tempRefs := methodNode encoder blockExtentsToTempsMap. self assert: tempRefs keys = method startpcsToBlockExtents values asSet! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/5/2009 17:13'! testBlockNumberingForInjectInto "Test that the compiler and CompiledMethod agree on the block numbering of Collection>>inject:into: and that temp names for inject:into: are recorded." "self new testBlockNumberingForInjectInto" | methodNode method tempRefs | methodNode := Parser new encoderClass: EncoderForV3PlusClosures; parse: (Collection sourceCodeAt: #inject:into:) class: Collection. method := methodNode generate: #(0 0 0 0). tempRefs := methodNode encoder blockExtentsToTempsMap. self assert: tempRefs keys = method startpcsToBlockExtents values asSet. self assert: ((tempRefs includesKey: (0 to: 6)) and: [(tempRefs at: (0 to: 6)) hasEqualElements: #(('thisValue' 1) ('binaryBlock' 2) ('nextValue' (3 1)))]). self assert: ((tempRefs includesKey: (2 to: 4)) and: [(tempRefs at: (2 to: 4)) hasEqualElements: #(('each' 1) ('binaryBlock' 2) ('nextValue' (3 1)))])! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/24/2008 11:03'! testDebuggerTempAccess self doTestDebuggerTempAccessWith: 1 with: 2! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 7/24/2009 21:12'! testDecompiledDoitMethodTempNames "self new testDecompiledDoitMethodTempNames" "Test that a decompiled doit that has been copied with temps decompiles to the input" | removeComments | removeComments := [:n| n comment: nil]. self closureCases do: [:source| | mns m mps mnps | "Need to compare an ungenerated tree with the generated method's methodNode because generating code alters the tree when it introduces remote temp vectors." mns := #(first last) collect: [:ignored| source first isLetter ifTrue: [self class compilerClass new compile: source in: self class notifying: nil ifFail: [self error: 'compilation error']] ifFalse: [self class compilerClass new compileNoPattern: source in: self class context: nil notifying: nil ifFail: [self error: 'compilation error']]]. m := (mns last generate: #(0 0 0 0)) copyWithTempsFromMethodNode: mns last. removeComments value: mns first. mns first nodesDo: removeComments. self assert: (mnps := mns first printString) = (mps := m methodNode printString)]! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/4/2008 16:57'! testInjectIntoDecompilations "Test various compilations decompile to the same code for a method sufficiently simple that this is possible and sufficiently complex that the code generated varies between the compilations." "self new testInjectIntoDecompilations" | source | source := (Collection sourceCodeAt: #inject:into:) asString. { Encoder. EncoderForV3. EncoderForLongFormV3. EncoderForV3PlusClosures. EncoderForLongFormV3PlusClosures } do: [:encoderClass| | method | method := (Parser new encoderClass: encoderClass; parse: source class: Collection) generate: #(0 0 0 0). self assert: (Scanner new scanTokens: method decompileString) = #(inject: t1 into: t2 | t3 | t3 ':=' t1 . self do: [ ':t4' | t3 ':=' t2 value: t3 value: t4 ] . ^ t3)]! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 7/29/2008 17:17'! testInjectIntoDecompiledDebugs "Test various debugs of the decompiled form debug correctly." "self new testInjectIntoDecompiledDebugs" | source | source := (Collection sourceCodeAt: #inject:into:) asString. { Encoder. EncoderForV3PlusClosures. EncoderForLongFormV3PlusClosures } do: [:encoderClass| | method | method := (Parser new encoderClass: encoderClass; parse: source class: Collection) generate: #(0 0 0 0). self supportTestSourceRangeAccessForDecompiledInjectInto: method source: method decompileString]! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 7/24/2009 11:51'! testInlineBlockCollectionEM1 | a1 b1 i1 a2 b2 i2 we wb | b1 := OrderedCollection new. i1 := 1. [a1 := i1. i1 <= 3] whileTrue: [b1 add: [a1]. i1 := i1 + 1]. b1 := b1 asArray collect: [:b | b value]. b2 := OrderedCollection new. i2 := 1. we := [a2 := i2. i2 <= 3]. wb := [b2 add: [a2]. i2 := i2 + 1]. we whileTrue: wb. "defeat optimization" b2 := b2 asArray collect: [:b | b value]. self assert: b1 = b2! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 3/7/2009 11:25'! testInlineBlockCollectionLR1 "Test case from Lukas Renggli" | col | col := OrderedCollection new. 1 to: 11 do: [ :each | col add: [ each ] ]. self assert: (col collect: [ :each | each value ]) asArray = (1 to: 11) asArray! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 3/7/2009 11:39'! testInlineBlockCollectionLR2 "Test case from Lukas Renggli" | col | col := OrderedCollection new. 1 to: 11 do: [ :each | #(1) do: [:ignored| col add: [ each ]] ]. self assert: (col collect: [ :each | each value ]) asArray = (1 to: 11) asArray! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 3/9/2009 11:00'! testInlineBlockCollectionLR3 | col | col := OrderedCollection new. 1 to: 11 do: [ :each | | i | i := each. col add: [ i ]. i := i + 1 ]. self assert: (col collect: [ :each | each value ]) asArray = (2 to: 12) asArray! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 7/22/2009 16:55'! testInlineBlockCollectionSD1 | a1 b1 a2 b2 | b1 := OrderedCollection new. 1 to: 3 do: [:i | a1 := i. b1 add: [a1]]. b1 := b1 asArray collect: [:b | b value]. b2 := OrderedCollection new. 1 to: 3 do: [:i | a2 := i. b2 add: [a2]] yourself. "defeat optimization" b2 := b2 asArray collect: [:b | b value]. self assert: b1 = b2! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/30/2009 12:15'! testMethodAndNodeTempNames "self new testMethodAndNodeTempNames" "Test that BytecodeAgnosticMethodNode>>blockExtentsToTempRefs answers the same structure as CompiledMethod>>blockExtentsToTempRefs when the method has been copied with the appropriate temps. This tests whether doit methods are debuggable since they carry their own temps." self closureCases do: [:source| | mn om m mbe obe | mn := source first isLetter ifTrue: [self class compilerClass new compile: source in: self class notifying: nil ifFail: [self error: 'compilation error']] ifFalse: [self class compilerClass new compileNoPattern: source in: self class context: nil notifying: nil ifFail: [self error: 'compilation error']]. m := (om := mn generate: #(0 0 0 0)) copyWithTempsFromMethodNode: mn. self assert: m holdsTempNames. self assert: m endPC = om endPC. mbe := m blockExtentsToTempsMap. obe := mn blockExtentsToTempsMap. self assert: mbe keys = obe keys. (mbe keys intersection: obe keys) do: [:interval| self assert: (mbe at: interval) = (obe at: interval)]]! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/4/2008 15:20'! testSourceRangeAccessForBlueBookInjectInto "Test debugger source range selection for inject:into: for a version compiled with closures" "self new testSourceRangeAccessForBlueBookInjectInto" | source method | source := (Collection sourceCodeAt: #inject:into:) asString. method := (Parser new encoderClass: EncoderForV3; parse: source class: Collection) generate: (Collection compiledMethodAt: #inject:into:) trailer. self supportTestSourceRangeAccessForInjectInto: method source: source! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/4/2008 15:20'! testSourceRangeAccessForBlueBookLongFormInjectInto "Test debugger source range selection for inject:into: for a version compiled with closures" "self new testSourceRangeAccessForBlueBookLongFormInjectInto" | source method | source := (Collection sourceCodeAt: #inject:into:) asString. method := (Parser new encoderClass: EncoderForLongFormV3; parse: source class: Collection) generate: (Collection compiledMethodAt: #inject:into:) trailer. self supportTestSourceRangeAccessForInjectInto: method source: source! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/4/2008 15:20'! testSourceRangeAccessForClosureBytecodeInjectInto "Test debugger source range selection for inject:into: for a version compiled with closures" "self new testSourceRangeAccessForClosureBytecodeInjectInto" | source method | source := (Collection sourceCodeAt: #inject:into:) asString. method := (Parser new encoderClass: EncoderForV3PlusClosures; parse: source class: Collection) generate: (Collection compiledMethodAt: #inject:into:) trailer. self supportTestSourceRangeAccessForInjectInto: method source: source! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/4/2008 15:20'! testSourceRangeAccessForClosureLongFormBytecodeInjectInto "Test debugger source range selection for inject:into: for a version compiled with closures" "self new testSourceRangeAccessForClosureLongFormBytecodeInjectInto" | source method | source := (Collection sourceCodeAt: #inject:into:) asString. method := (Parser new encoderClass: EncoderForLongFormV3PlusClosures; parse: source class: Collection) generate: (Collection compiledMethodAt: #inject:into:) trailer. self supportTestSourceRangeAccessForInjectInto: method source: source! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/4/2008 11:40'! testSourceRangeAccessForInjectInto "Test debugger source range selection for inject:into: for the current version of the method" "self new testSourceRangeAccessForInjectInto" self supportTestSourceRangeAccessForInjectInto: (Collection compiledMethodAt: #inject:into:) source: (Collection sourceCodeAt: #inject:into:) asString! ! !ClosureCompilerTest methodsFor: 'tests' stamp: 'eem 6/15/2008 11:26'! testTempNameAccessForInjectInto "self new testTempNameAccessForInjectInto" | methodNode method evaluationCount block debuggerMap | methodNode := Parser new encoderClass: EncoderForV3PlusClosures; parse: (Collection sourceCodeAt: #inject:into:) class: Collection. method := methodNode generate: #(0 0 0 0). debuggerMap := DebuggerMethodMap forMethod: method methodNode: methodNode. evaluationCount := 0. block := [:prev :each| | theContext tempNames | evaluationCount := evaluationCount + 1. theContext := thisContext sender. tempNames := debuggerMap tempNamesForContext: theContext. self assert: (tempNames hasEqualElements: tempNames). #('thisValue' 'each' 'binaryBlock' 'nextValue') with: { 0. each. block. prev} do: [:tempName :value| self assert: (debuggerMap namedTempAt: (tempNames indexOf: tempName) in: theContext) == value. tempName ~= 'each' ifTrue: [self assert: (debuggerMap namedTempAt: (tempNames indexOf: tempName) in: theContext home) == value]]]. (1 to: 10) withArgs: { 0. block } executeMethod: method. self assert: evaluationCount = 10! ! !ClosureCompilerTest methodsFor: 'testing' stamp: 'AdrianLienhard 10/19/2009 09:31'! expectedFailures "The problem in the tests #testDebuggerTempAccess is that a compiler evaluate message is sent and this prevents the proper temp analysis of the closure compiler" ^#(testDebuggerTempAccess testInjectIntoDecompilations testInjectIntoDecompiledDebugs)! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClosureCompilerTest class instanceVariableNames: ''! !ClosureCompilerTest class methodsFor: 'code examples' stamp: 'eem 5/20/2008 09:40'! methodWithCopiedAndAssignedTemps | blk "0w" a "0w" b "0w" c "0w" t "0w" r1 "0w" r2 "0w" | a := 1. "1w" b := 2. "1w" c := 4. "1w" t := 0. "1w" blk "5w" := ["2" t "3w" := t "3r" + a "3r" + b "3r" + c "3r" ] "4". r1 "5w" := blk "5r" value. b "5w" := -100. r2 "5w" := blk "5r" value. ^r1 "5r" -> r2 "5r" -> t "5r" "a: main(read(),write(0,1)), block(read(3),write()) => copy; no writes follow read b: main(read(),write(0,1,5)), block(read(3),write()) => remote; write follows contained read blk: main(read(5),write(0,5)), block(read(),write()) => no copy in blocks < 5 c: main(read(),write(0,1)), block(read(3),write()) => copy; no writes follow read r1: main(read(5),write(0,5)), block(read(),write()) => no copy in blocks < 5 r2: main(read(5),write(0,5)), block(read(),write()) => no copy in blocks < 5 t: main(read(5),write(0,1)), block(read(3),write(3)) => remote; read follows contained write" "(Parser new encoderClass: EncoderForV3; parse: (self class sourceCodeAt: #methodWithCopiedAndAssignedTemps) class: self class) generateUsingClosures: #(0 0 0 0)"! ! !ClosureCompilerTest class methodsFor: 'code examples' stamp: 'eem 5/19/2008 20:45'! methodWithCopiedAndPostClosedOverAssignedTemps | blk a b c r1 r2 | a := 1. b := 2. c := 4. blk := [a + b + c]. r1 := blk value. b := nil. r2 := blk value. r1 -> r2 "(Parser new encoderClass: EncoderForV3; parse: (self class sourceCodeAt: #methodWithCopiedAndPostClosedOverAssignedTemps) class: self class) generateUsingClosures: #(0 0 0 0)"! ! !ClosureCompilerTest class methodsFor: 'code examples' stamp: 'eem 5/19/2008 20:10'! methodWithCopiedTemps | a b c r | a := 1. b := 2. c := 4. r := [a + b + c] value. b := nil. r "Parser new parse: (self class sourceCodeAt: #methodWithCopiedTemps) class: self class" "(Parser new encoderClass: EncoderForV3; parse: (self class sourceCodeAt: #methodWithCopiedTemps) class: self class) generateUsingClosures: #(0 0 0 0)"! ! !ClosureCompilerTest class methodsFor: 'code examples' stamp: 'eem 5/19/2008 14:24'! methodWithOptimizedBlocks | s c | s := self isNil ifTrue: [| a | a := 'isNil'. a] ifFalse: [| b | b := 'notNil'. b]. c := String new: s size. 1 to: s size do: [:i| c at: i put: (s at: i)]. ^c "Parser new parse: (self class sourceCodeAt: #methodWithOptimizedBlocks) class: self class"! ! !ClosureCompilerTest class methodsFor: 'code examples' stamp: 'eem 5/19/2008 14:24'! methodWithOptimizedBlocksA | s c | s := self isNil ifTrue: [| a | a := 'isNil'. a] ifFalse: [| a | a := 'notNil'. a]. c := String new: s size. 1 to: s size do: [:i| c at: i put: (s at: i)]. ^c "Parser new parse: (self class sourceCodeAt: #methodWithOptimizedBlocksA) class: self class"! ! !ClosureCompilerTest class methodsFor: 'code examples' stamp: 'eem 5/19/2008 14:12'! methodWithVariousTemps | classes total totalLength | classes := self withAllSuperclasses. total := totalLength := 0. classes do: [:class| | className | className := class name. total := total + 1. totalLength := totalLength + className size]. ^total -> totalLength "Parser new parse: (self class sourceCodeAt: #methodWithVariousTemps) class: self class"! ! TestCase subclass: #ClosureTests instanceVariableNames: 'collection' classVariableNames: '' poolDictionaries: '' category: 'Tests-Compiler'! !ClosureTests methodsFor: 'utilities' stamp: 'lr 3/9/2009 16:48'! assertValues: anArray | values | values := collection collect: [ :each | each value ]. self assert: anArray asArray = values asArray description: 'Expected: ' , anArray asArray printString , ', but got ' , values asArray printString! ! !ClosureTests methodsFor: 'running' stamp: 'lr 3/9/2009 16:48'! setUp super setUp. collection := OrderedCollection new! ! !ClosureTests methodsFor: 'testing' stamp: 'lr 3/11/2009 17:35'! methodArgument: anObject ^ [ anObject ] ! ! !ClosureTests methodsFor: 'testing' stamp: 'lr 3/11/2009 17:33'! testBlockArgument | block block1 block2 | block := [ :arg | | temp | temp := arg. [ temp ] ]. block1 := block value: 1. block2 := block value: 2. self assert: block1 value = 1. self assert: block2 value = 2! ! !ClosureTests methodsFor: 'testing' stamp: 'lr 3/11/2009 17:33'! testBlockTemp | block block1 block2 | block := [ :arg | [ arg ] ]. block1 := block value: 1. block2 := block value: 2. self assert: block1 value = 1. self assert: block2 value = 2! ! !ClosureTests methodsFor: 'testing' stamp: 'lr 3/11/2009 17:36'! testMethodArgument | temp block | temp := 0. block := [ [ temp ] ]. temp := 1. block := block value. temp := 2. self assert: block value = 2! ! !ClosureTests methodsFor: 'testing' stamp: 'lr 3/11/2009 17:36'! testMethodTemp | block1 block2 | block1 := self methodArgument: 1. block2 := self methodArgument: 2. self assert: block1 value = 1. self assert: block2 value = 2! ! !ClosureTests methodsFor: 'testing-todo' stamp: 'lr 3/10/2009 14:51'! testToDoArgument 1 to: 5 do: [ :index | collection add: [ index ] ]. self assertValues: #(1 2 3 4 5)! ! !ClosureTests methodsFor: 'testing-todo' stamp: 'lr 3/10/2009 14:51'! testToDoArgumentNotInlined | block | block := [ :index | collection add: [ index ] ]. 1 to: 5 do: block. self assertValues: #(1 2 3 4 5)! ! !ClosureTests methodsFor: 'testing-todo' stamp: 'lr 3/10/2009 14:51'! testToDoInsideTemp 1 to: 5 do: [ :index | | temp | temp := index. collection add: [ temp ] ]. self assertValues: #(1 2 3 4 5)! ! !ClosureTests methodsFor: 'testing-todo' stamp: 'lr 3/10/2009 14:51'! testToDoInsideTempNotInlined | block | block := [ :index | | temp | temp := index. collection add: [ temp ] ]. 1 to: 5 do: block. self assertValues: #(1 2 3 4 5)! ! !ClosureTests methodsFor: 'testing-todo' stamp: 'lr 3/10/2009 14:51'! testToDoOutsideTemp | temp | 1 to: 5 do: [ :index | temp := index. collection add: [ temp ] ]. self assertValues: #(5 5 5 5 5)! ! !ClosureTests methodsFor: 'testing-todo' stamp: 'lr 3/10/2009 14:51'! testToDoOutsideTempNotInlined | block temp | block := [ :index | temp := index. collection add: [ temp ] ]. 1 to: 5 do: block. self assertValues: #(5 5 5 5 5)! ! !ClosureTests methodsFor: 'testing-while' stamp: 'lr 3/10/2009 14:29'! testWhileModificationAfter | index | index := 0. [ index < 5 ] whileTrue: [ collection add: [ index ]. index := index + 1 ]. self assertValues: #(5 5 5 5 5)! ! !ClosureTests methodsFor: 'testing-while' stamp: 'lr 3/10/2009 14:29'! testWhileModificationAfterNotInlined | index block | index := 0. block := [ collection add: [ index ]. index := index + 1 ]. [ index < 5 ] whileTrue: block. self assertValues: #(5 5 5 5 5)! ! !ClosureTests methodsFor: 'testing-while' stamp: 'lr 3/10/2009 14:29'! testWhileModificationBefore | index | index := 0. [ index < 5 ] whileTrue: [ index := index + 1. collection add: [ index ] ]. self assertValues: #(5 5 5 5 5)! ! !ClosureTests methodsFor: 'testing-while' stamp: 'lr 3/10/2009 14:29'! testWhileModificationBeforeNotInlined | index block | index := 0. block := [ index := index + 1. collection add: [ index ] ]. [ index < 5 ] whileTrue: block. self assertValues: #(5 5 5 5 5)! ! !ClosureTests methodsFor: 'testing-while' stamp: 'lr 3/10/2009 14:52'! testWhileWithTemp | index | index := 0. [ index < 5 ] whileTrue: [ | temp | temp := index := index + 1. collection add: [ temp ] ]. self assertValues: #(1 2 3 4 5)! ! !ClosureTests methodsFor: 'testing-while' stamp: 'lr 3/10/2009 14:53'! testWhileWithTempNotInlined | index block | index := 0. block := [ | temp | temp := index := index + 1. collection add: [ temp ] ]. [ index < 5 ] whileTrue: block. self assertValues: #(1 2 3 4 5)! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ClosureTests class instanceVariableNames: ''! TextDiffBuilder subclass: #CodeDiffBuilder instanceVariableNames: 'class' classVariableNames: '' poolDictionaries: '' category: 'System-FilePackage'! !CodeDiffBuilder commentStamp: '' prior: 0! I am a differencer that compares source in tokens tokenised by a parser. I consider comments significant, but consider sequences of whitespace equivalent. Depending on the definition of WhitespaceForCodeDiff>>at: sequences of whitespace containing carriage-returns may be considered different to sequences of whitespace lacking carriage-returns (which may result in better-formatted diffs).! ]style[(392)i! StringHolder subclass: #CodeHolder instanceVariableNames: 'currentCompiledMethod contentsSymbol' classVariableNames: '' poolDictionaries: '' category: 'Tools-Base'! !CodeHolder commentStamp: '' prior: 0! An ancestor class for all models which can show code. Eventually, much of the code that currently resides in StringHolder which only applies to code-holding StringHolders might get moved down here.! !CodeHolder methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 2/5/2009 11:36'! optionalButtonRow "Answer a row of control buttons" | buttons aLabel | buttons := OrderedCollection new. Preferences menuButtonInToolPane ifTrue: [buttons add: self menuButton]. self optionalButtonPairs do: [:tuple | aLabel := Preferences abbreviatedBrowserButtons ifTrue: [self abbreviatedWordingFor: tuple second]. buttons add: ((PluggableButtonMorph on: self getState: nil action: tuple second) hResizing: #spaceFill; vResizing: #spaceFill; label: (aLabel ifNil: [tuple first asString]); setBalloonText: (tuple size > 2 ifTrue: [tuple third]); triggerOnMouseDown: (tuple size > 3 ifTrue: [tuple fourth] ifFalse: [false]))]. buttons add: self codePaneProvenanceButton. ^(UITheme builder newRow: buttons) setNameTo: 'buttonPane'; cellInset: 2! ! !CodeHolder methodsFor: '*services-base' stamp: 'rr 3/15/2004 09:21'! requestor ^ (BrowserRequestor new) browser: self; yourself! ! !CodeHolder methodsFor: 'annotation' stamp: 'md 2/24/2006 15:25'! addOptionalAnnotationsTo: window at: fractions plus: verticalOffset "Add an annotation pane to the window if preferences indicate a desire for it, and return the incoming verticalOffset plus the height of the added pane, if any" | aTextMorph divider delta | self wantsAnnotationPane ifFalse: [^ verticalOffset]. aTextMorph := PluggableTextMorph on: self text: #annotation accept: #annotation: readSelection: nil menu: #annotationPaneMenu:shifted:. aTextMorph askBeforeDiscardingEdits: true; acceptOnCR: true; borderWidth: 0; hideScrollBarsIndefinitely. divider := BorderedSubpaneDividerMorph forBottomEdge. divider extent: 4@4; color: Color transparent; borderColor: #raised; borderWidth: 2. delta := self defaultAnnotationPaneHeight. window addMorph: aTextMorph fullFrame: (LayoutFrame fractions: fractions offsets: (0@verticalOffset corner: 0@(verticalOffset + delta - 2))). window addMorph: divider fullFrame: (LayoutFrame fractions: fractions offsets: (0@(verticalOffset + delta - 2) corner: 0@(verticalOffset + delta))). ^ verticalOffset + delta! ! !CodeHolder methodsFor: 'annotation' stamp: 'sd 11/20/2005 21:27'! addPriorVersionsCountForSelector: aSelector ofClass: aClass to: aStream "add an annotation detailing the prior versions count" | versionsCount | versionsCount := VersionsBrowser versionCountForSelector: aSelector class: aClass. aStream nextPutAll: ((versionsCount > 1 ifTrue: [versionsCount == 2 ifTrue: ['1 prior version'] ifFalse: [versionsCount printString, ' prior versions']] ifFalse: ['no prior versions']), self annotationSeparator)! ! !CodeHolder methodsFor: 'annotation' stamp: 'sd 11/20/2005 21:27'! annotation "Provide a line of content for an annotation pane, representing information about the method associated with the selected class and selector in the receiver." | aSelector aClass | ((aSelector := self selectedMessageName) == nil or: [(aClass := self selectedClassOrMetaClass) == nil]) ifTrue: [^ '------']. ^ self annotationForSelector: aSelector ofClass: aClass! ! !CodeHolder methodsFor: 'annotation' stamp: 'sd 11/20/2005 21:27'! annotationForClassCommentFor: aClass "Provide a line of content for an annotation pane, given that the receiver is pointing at the clas comment of the given class." | aStamp nonMeta | aStamp := (nonMeta := aClass theNonMetaClass) organization commentStamp. ^ aStamp ifNil: [nonMeta name, ' has no class comment'] ifNotNil: ['class comment for ', nonMeta name, (aStamp = '' ifFalse: [' - ', aStamp] ifTrue: [''])]! ! !CodeHolder methodsFor: 'annotation' stamp: 'sw 8/26/2002 10:19'! annotationForClassDefinitionFor: aClass "Provide a line of content for an annotation pane, given that the receiver is pointing at the class definition of the given class." ^ 'Class definition for ', aClass name! ! !CodeHolder methodsFor: 'annotation' stamp: 'sw 8/26/2002 10:19'! annotationForHierarchyFor: aClass "Provide a line of content for an annotation pane, given that the receiver is pointing at the hierarchy of the given class." ^ 'Hierarchy for ', aClass name! ! !CodeHolder methodsFor: 'annotation' stamp: 'sd 11/20/2005 21:27'! annotationForSelector: aSelector ofClass: aClass "Provide a line of content for an annotation pane, representing information about the given selector and class" | stamp sendersCount implementorsCount aCategory separator aString aList aComment aStream requestList | aSelector == #Comment ifTrue: [^ self annotationForClassCommentFor: aClass]. aSelector == #Definition ifTrue: [^ self annotationForClassDefinitionFor: aClass]. aSelector == #Hierarchy ifTrue: [^ self annotationForHierarchyFor: aClass]. aStream := ReadWriteStream on: ''. requestList := self annotationRequests. separator := requestList size > 1 ifTrue: [self annotationSeparator] ifFalse: ['']. requestList do: [:aRequest | aRequest == #firstComment ifTrue: [aComment := aClass firstCommentAt: aSelector. aComment isEmptyOrNil ifFalse: [aStream nextPutAll: aComment , separator]]. aRequest == #masterComment ifTrue: [aComment := aClass supermostPrecodeCommentFor: aSelector. aComment isEmptyOrNil ifFalse: [aStream nextPutAll: aComment , separator]]. aRequest == #documentation ifTrue: [aComment := aClass precodeCommentOrInheritedCommentFor: aSelector. aComment isEmptyOrNil ifFalse: [aStream nextPutAll: aComment , separator]]. aRequest == #timeStamp ifTrue: [stamp := self timeStamp. aStream nextPutAll: (stamp size > 0 ifTrue: [stamp , separator] ifFalse: ['no timeStamp' , separator])]. aRequest == #messageCategory ifTrue: [aCategory := aClass organization categoryOfElement: aSelector. aCategory ifNotNil: ["woud be nil for a method no longer present, e.g. in a recent-submissions browser" aStream nextPutAll: aCategory , separator]]. aRequest == #sendersCount ifTrue: [sendersCount := (self systemNavigation allCallsOn: aSelector) size. sendersCount := sendersCount == 1 ifTrue: ['1 sender'] ifFalse: [sendersCount printString , ' senders']. aStream nextPutAll: sendersCount , separator]. aRequest == #implementorsCount ifTrue: [implementorsCount := self systemNavigation numberOfImplementorsOf: aSelector. implementorsCount := implementorsCount == 1 ifTrue: ['1 implementor'] ifFalse: [implementorsCount printString , ' implementors']. aStream nextPutAll: implementorsCount , separator]. aRequest == #priorVersionsCount ifTrue: [self addPriorVersionsCountForSelector: aSelector ofClass: aClass to: aStream]. aRequest == #priorTimeStamp ifTrue: [stamp := VersionsBrowser timeStampFor: aSelector class: aClass reverseOrdinal: 2. stamp ifNotNil: [aStream nextPutAll: 'prior time stamp: ' , stamp , separator]]. aRequest == #recentChangeSet ifTrue: [aString := ChangeSorter mostRecentChangeSetWithChangeForClass: aClass selector: aSelector. aString size > 0 ifTrue: [aStream nextPutAll: aString , separator]]. aRequest == #allChangeSets ifTrue: [aList := ChangeSorter allChangeSetsWithClass: aClass selector: aSelector. aList size > 0 ifTrue: [aList size = 1 ifTrue: [aStream nextPutAll: 'only in change set '] ifFalse: [aStream nextPutAll: 'in change sets: ']. aList do: [:aChangeSet | aStream nextPutAll: aChangeSet name , ' ']] ifFalse: [aStream nextPutAll: 'in no change set']. aStream nextPutAll: separator]]. ^ aStream contents! ! !CodeHolder methodsFor: 'annotation' stamp: 'RAA 1/13/2001 07:20'! annotationPaneMenu: aMenu shifted: shifted ^ aMenu labels: 'change pane size' lines: #() selections: #(toggleAnnotationPaneSize)! ! !CodeHolder methodsFor: 'annotation' stamp: 'sw 9/27/1999 14:13'! annotationRequests ^ Preferences defaultAnnotationRequests! ! !CodeHolder methodsFor: 'annotation' stamp: 'sw 2/22/2001 10:02'! annotationSeparator "Answer the separator to be used between annotations" ^ ' · '! ! !CodeHolder methodsFor: 'annotation' stamp: 'sw 9/28/2001 08:43'! defaultAnnotationPaneHeight "Answer the receiver's preferred default height for new annotation panes." ^ Preferences parameterAt: #defaultAnnotationPaneHeight ifAbsentPut: [25]! ! !CodeHolder methodsFor: 'annotation' stamp: 'md 7/24/2009 15:51'! defaultButtonPaneHeight "Answer the user's preferred default height for new button panes." ^ (Preferences parameterAt: #defaultButtonPaneHeight ifAbsentPut: [25]) + 2 ! ! !CodeHolder methodsFor: 'breakpoints' stamp: 'marcus.denker 10/9/2008 20:31'! toggleBreakOnEntry "Install or uninstall a halt-on-entry breakpoint" | selectedMethod | self selectedClassOrMetaClass isNil ifTrue:[^self]. selectedMethod := self selectedClassOrMetaClass >> self selectedMessageName. selectedMethod hasBreakpoint ifTrue: [BreakpointManager unInstall: selectedMethod] ifFalse: [BreakpointManager installInClass: self selectedClassOrMetaClass selector: self selectedMessageName].! ! !CodeHolder methodsFor: 'categories' stamp: 'sd 11/8/2005 22:06'! categoryFromUserWithPrompt: aPrompt for: aClass "self new categoryFromUserWithPrompt: 'testing' for: SystemDictionary" | labels myCategories reject lines cats newName menuIndex | labels := OrderedCollection with: 'new...'. labels addAll: (myCategories := aClass organization categories asSortedCollection: [:a :b | a asLowercase < b asLowercase]). reject := myCategories asSet. reject add: ClassOrganizer nullCategory; add: ClassOrganizer default. lines := OrderedCollection with: 1 with: (myCategories size + 1). aClass allSuperclasses do: [:cls | cats := cls organization categories reject: [:cat | reject includes: cat]. cats isEmpty ifFalse: [lines add: labels size. labels addAll: (cats asSortedCollection: [:a :b | a asLowercase < b asLowercase]). reject addAll: cats]]. newName := (labels size = 1 or: [menuIndex := (UIManager default chooseFrom: labels lines: lines title: aPrompt). menuIndex = 0 ifTrue: [^ nil]. menuIndex = 1]) ifTrue: [UIManager default request: 'Please type new category name' initialAnswer: 'category name'] ifFalse: [labels at: menuIndex]. ^ newName ifNotNil: [newName asSymbol]! ! !CodeHolder methodsFor: 'categories' stamp: 'sd 11/20/2005 21:27'! categoryOfCurrentMethod "Answer the category that owns the current method. If unable to determine a category, answer nil." | aClass aSelector | ^ (aClass := self selectedClassOrMetaClass) ifNotNil: [(aSelector := self selectedMessageName) ifNotNil: [aClass whichCategoryIncludesSelector: aSelector]]! ! !CodeHolder methodsFor: 'categories' stamp: 'sd 11/20/2005 21:26'! changeCategory "Present a menu of the categories of messages for the current class, and let the user choose a new category for the current message" | aClass aSelector | (aClass := self selectedClassOrMetaClass) ifNotNil: [(aSelector := self selectedMessageName) ifNotNil: [(self letUserReclassify: aSelector in: aClass) ifTrue: ["ChangeSet current reorganizeClass: aClass." "Decided on further review that the above, when present, could cause more unexpected harm than good" self methodCategoryChanged]]]! ! !CodeHolder methodsFor: 'categories' stamp: 'sd 11/20/2005 21:27'! letUserReclassify: anElement in: aClass "Put up a list of categories and solicit one from the user. Answer true if user indeed made a change, else false" | currentCat newCat | currentCat := aClass organization categoryOfElement: anElement. newCat := self categoryFromUserWithPrompt: 'choose category (currently "', currentCat, '")' for: aClass. (newCat ~~ nil and: [newCat ~= currentCat]) ifTrue: [aClass organization classify: anElement under: newCat suppressIfDefault: false. ^ true] ifFalse: [^ false]! ! !CodeHolder methodsFor: 'categories' stamp: 'sw 9/27/1999 14:11'! methodCategoryChanged self changed: #annotation! ! !CodeHolder methodsFor: 'categories' stamp: 'sw 3/22/2000 23:04'! selectedMessageCategoryName "Answer the name of the message category of the message of the currently selected context." ^ self selectedClass organization categoryOfElement: self selectedMessageName! ! !CodeHolder methodsFor: 'categories & search pane' stamp: 'sd 11/20/2005 21:27'! listPaneWithSelector: aSelector "If, among my window's paneMorphs, there is a list pane defined with aSelector as its retriever, answer it, else answer nil" | aWindow | ^ (aWindow := self containingWindow) ifNotNil: [aWindow paneMorphSatisfying: [:aMorph | (aMorph isKindOf: PluggableListMorph) and: [aMorph getListSelector == aSelector]]]! ! !CodeHolder methodsFor: 'categories & search pane' stamp: 'sd 11/20/2005 21:27'! newSearchPane "Answer a new search pane for the receiver" | aTextMorph | aTextMorph := PluggableTextMorph on: self text: #lastSearchString accept: #lastSearchString: readSelection: nil menu: nil. aTextMorph setProperty: #alwaysAccept toValue: true. aTextMorph askBeforeDiscardingEdits: false. aTextMorph acceptOnCR: true. aTextMorph setBalloonText: 'Type here and hit ENTER, and all methods whose selectors match what you typed will appear in the list pane below.'. ^ aTextMorph! ! !CodeHolder methodsFor: 'categories & search pane' stamp: 'sw 3/7/2001 12:22'! searchPane "Answer the search pane associated with the receiver in its window, or nil if none. Morphic only" ^ self textPaneWithSelector: #lastSearchString! ! !CodeHolder methodsFor: 'categories & search pane' stamp: 'sd 11/20/2005 21:27'! textPaneWithSelector: aSelector "If, among my window's paneMorphs, there is a text pane defined with aSelector as its retriever, answer it, else answer nil" | aWindow | ^ (aWindow := self containingWindow) ifNotNil: [aWindow paneMorphSatisfying: [:aMorph | (aMorph isKindOf: PluggableTextMorph) and: [aMorph getTextSelector == aSelector]]]! ! !CodeHolder methodsFor: 'commands' stamp: 'sd 5/23/2003 14:35'! adoptMessageInCurrentChangeset "Add the receiver's method to the current change set if not already there" self setClassAndSelectorIn: [:cl :sel | cl ifNotNil: [ChangeSet current adoptSelector: sel forClass: cl. self changed: #annotation]] ! ! !CodeHolder methodsFor: 'commands' stamp: 'sd 11/20/2005 21:27'! browseImplementors "Create and schedule a message set browser on all implementors of the currently selected message selector. Do nothing if no message is selected." | aMessageName | (aMessageName := self selectedMessageName) ifNotNil: [self systemNavigation browseAllImplementorsOf: aMessageName]! ! !CodeHolder methodsFor: 'commands' stamp: 'nk 6/26/2003 21:43'! browseSenders "Create and schedule a message set browser on all senders of the currently selected message selector. Of there is no message currently selected, offer a type-in" self sendQuery: #browseAllCallsOn: to: self systemNavigation! ! !CodeHolder methodsFor: 'commands' stamp: 'alain.plantec 5/30/2008 11:24'! copyUpOrCopyDown "Used to copy down code from a superclass to a subclass or vice-versa in one easy step, if you know what you're doing. Prompt the user for which class to copy down or copy up to, then spawn a fresh browser for that class, with the existing code planted in it, and with the existing method category also established." | aClass aSelector allClasses implementors aMenu aColor | ((aClass := self selectedClassOrMetaClass) isNil or: [(aSelector := self selectedMessageName) == nil]) ifTrue: [^ Beeper beep]. allClasses := self systemNavigation hierarchyOfClassesSurrounding: aClass. implementors := self systemNavigation hierarchyOfImplementorsOf: aSelector forClass: aClass. aMenu := MenuMorph new defaultTarget: self. aMenu title: aClass name, '.', aSelector, ' Choose where to insert a copy of this method (blue = current, black = available, red = other implementors'. allClasses do: [:cl | aColor := cl == aClass ifTrue: [#blue] ifFalse: [(implementors includes: cl) ifTrue: [#red] ifFalse: [#black]]. (aColor == #red) ifFalse: [aMenu add: cl name selector: #spawnToClass: argument: cl] ifTrue: [aMenu add: cl name selector: #spawnToCollidingClass: argument: cl]. aMenu lastItem color: (Color colorFrom: aColor)]. aMenu popUpInWorld! ! !CodeHolder methodsFor: 'commands' stamp: 'sw 5/18/2001 17:51'! offerMenu "Offer a menu to the user from the bar of tool buttons" self offerDurableMenuFrom: #messageListMenu:shifted: shifted: false! ! !CodeHolder methodsFor: 'commands' stamp: 'sw 2/27/2001 12:14'! offerShiftedClassListMenu "Offer the shifted class-list menu." ^ self offerMenuFrom: #classListMenu:shifted: shifted: true! ! !CodeHolder methodsFor: 'commands' stamp: 'sw 2/27/2001 12:15'! offerUnshiftedClassListMenu "Offer the shifted class-list menu." ^ self offerMenuFrom: #classListMenu:shifted: shifted: false! ! !CodeHolder methodsFor: 'commands' stamp: 'sd 11/20/2005 21:27'! removeClass "Remove the selected class from the system, at interactive user request. Make certain the user really wants to do this, since it is not reversible. Answer true if removal actually happened." | message className classToRemove result | self okToChange ifFalse: [^ false]. classToRemove := self selectedClassOrMetaClass ifNil: [Beeper beep. ^ false]. classToRemove := classToRemove theNonMetaClass. className := classToRemove name. message := 'Are you certain that you want to REMOVE the class ', className, ' from the system?'. (result := self confirm: message) ifTrue: [classToRemove subclasses size > 0 ifTrue: [(self confirm: 'class has subclasses: ' , message) ifFalse: [^ false]]. classToRemove removeFromSystem. self changed: #classList. true]. ^ result! ! !CodeHolder methodsFor: 'commands' stamp: 'sw 3/6/2001 15:18'! shiftedYellowButtonActivity "Offer the shifted selector-list menu" ^ self offerMenuFrom: #messageListMenu:shifted: shifted: true! ! !CodeHolder methodsFor: 'commands' stamp: 'sd 11/20/2005 21:27'! spawnFullProtocol "Create and schedule a new protocol browser on the currently selected class or meta." | aClassOrMetaclass | (aClassOrMetaclass := self selectedClassOrMetaClass) ifNotNil: [ProtocolBrowser openFullProtocolForClass: aClassOrMetaclass]! ! !CodeHolder methodsFor: 'commands' stamp: 'sd 11/20/2005 21:27'! spawnProtocol | aClassOrMetaclass | "Create and schedule a new protocol browser on the currently selected class or meta." (aClassOrMetaclass := self selectedClassOrMetaClass) ifNotNil: [ProtocolBrowser openSubProtocolForClass: aClassOrMetaclass]! ! !CodeHolder methodsFor: 'commands' stamp: 'sd 11/20/2005 21:27'! spawnToClass: aClass "Used to copy down code from a superclass to a subclass in one easy step, if you know what you're doing. Spawns a new message-category browser for the indicated class, populating it with the source code seen in the current tool." | aCategory newBrowser org | (aCategory := self categoryOfCurrentMethod) ifNil: [self buildClassBrowserEditString: self contents] ifNotNil: [((org := aClass organization) categories includes: aCategory) ifFalse: [org addCategory: aCategory]. newBrowser := Browser new setClass: aClass selector: nil. newBrowser selectMessageCategoryNamed: aCategory. Browser openBrowserView: (newBrowser openMessageCatEditString: self contents) label: 'category "', aCategory, '" in ', newBrowser selectedClassOrMetaClassName]! ! !CodeHolder methodsFor: 'commands' stamp: 'sw 3/20/2001 15:11'! spawnToCollidingClass: aClass "Potentially used to copy down code from a superclass to a subclass in one easy step, in the case where the given class already has its own version of code, which would consequently be clobbered if the spawned code were accepted." self inform: 'That would be destructive of some pre-existing code already in that class for this selector. For the moment, we will not let you do this to yourself.'! ! !CodeHolder methodsFor: 'commands' stamp: 'sw 3/6/2001 15:19'! unshiftedYellowButtonActivity "Offer the unshifted shifted selector-list menu" ^ self offerMenuFrom: #messageListMenu:shifted: shifted: false! ! !CodeHolder methodsFor: 'construction' stamp: 'sd 11/20/2005 21:27'! addLowerPanesTo: window at: nominalFractions with: editString | verticalOffset row innerFractions | row := AlignmentMorph newColumn hResizing: #spaceFill; vResizing: #spaceFill; layoutInset: 0; borderWidth: 1; borderColor: Color black; layoutPolicy: ProportionalLayout new. verticalOffset := 0. innerFractions := 0@0 corner: 1@0. verticalOffset := self addOptionalAnnotationsTo: row at: innerFractions plus: verticalOffset. verticalOffset := self addOptionalButtonsTo: row at: innerFractions plus: verticalOffset. row addMorph: ((self buildMorphicCodePaneWith: editString) borderWidth: 0) fullFrame: ( LayoutFrame fractions: (innerFractions withBottom: 1) offsets: (0@verticalOffset corner: 0@0) ). window addMorph: row frame: nominalFractions. row on: #mouseEnter send: #paneTransition: to: window. row on: #mouseLeave send: #paneTransition: to: window.! ! !CodeHolder methodsFor: 'construction' stamp: 'sd 11/20/2005 21:27'! buildClassBrowserEditString: aString "Create and schedule a new class browser for the current selection, with initial textual contents set to aString. This is used specifically in spawning where a class is established but a method-category is not." | newBrowser | newBrowser := Browser new. newBrowser setClass: self selectedClassOrMetaClass selector: nil. newBrowser editSelection: #newMessage. Browser openBrowserView: (newBrowser openOnClassWithEditString: aString) label: 'Class Browser: ', self selectedClassOrMetaClass name ! ! !CodeHolder methodsFor: 'construction' stamp: 'tween 8/27/2004 12:18'! buildMorphicCodePaneWith: editString "Construct the pane that shows the code. Respect the Preference for standardCodeFont." | codePane | codePane := MorphicTextEditor default on: self text: #contents accept: #contents:notifying: readSelection: #contentsSelection menu: #codePaneMenu:shifted:. codePane font: Preferences standardCodeFont. editString ifNotNil: [codePane editString: editString. codePane hasUnacceptedEdits: true]. ^ codePane! ! !CodeHolder methodsFor: 'contents' stamp: 'sd 11/20/2005 21:27'! commentContents "documentation for the selected method" | poss aClass aSelector | ^ (poss := (aClass := self selectedClassOrMetaClass) ifNil: ['----'] ifNotNil: [(aSelector := self selectedMessageName) ifNil: ['---'] ifNotNil: [(aClass precodeCommentOrInheritedCommentFor: aSelector)", String cr, String cr, self timeStamp" "which however misses comments that are between the temps declaration and the body of the method; those are picked up by ·aClass commentOrInheritedCommentFor: aSelector· but that method will get false positives from comments *anywhere* in the method source"]]) isEmptyOrNil ifTrue: [aSelector ifNotNil: [((aClass methodHeaderFor: aSelector), ' Has no comment') asText makeSelectorBoldIn: aClass] ifNil: ['Hamna']] ifFalse: [aSelector ifNotNil: [((aClass methodHeaderFor: aSelector), ' ', poss) asText makeSelectorBoldIn: aClass] ifNil: [poss]]! ! !CodeHolder methodsFor: 'contents' stamp: 'di 10/1/2001 22:25'! contents "Answer the source code or documentation for the selected method" self showingByteCodes ifTrue: [^ self selectedBytecodes]. self showingDocumentation ifTrue: [^ self commentContents]. ^ self selectedMessage! ! !CodeHolder methodsFor: 'contents' stamp: 'alain.plantec 5/18/2009 15:31'! contentsSymbol "Answer a symbol indicating what kind of content should be shown for the method; for normal showing of source code, this symbol is #source. A nil value in the contentsSymbol slot will be set to #source by this method" ^ contentsSymbol ifNil: [contentsSymbol := Preferences browseWithPrettyPrint ifTrue: [#prettyPrint] ifFalse: [#source]]! ! !CodeHolder methodsFor: 'contents' stamp: 'sd 11/20/2005 21:27'! contentsSymbol: aSymbol "Set the contentsSymbol as indicated. #source means to show source code, #comment means to show the first comment found in the source code" contentsSymbol := aSymbol! ! !CodeHolder methodsFor: 'controls' stamp: 'gm 2/16/2003 20:37'! buttonWithSelector: aSelector "If receiver has a control button with the given action selector answer it, else answer nil. morphic only at this point" | aWindow aPane | ((aWindow := self containingWindow) isSystemWindow) ifFalse: [^nil]. (aPane := aWindow submorphNamed: 'buttonPane') ifNil: [^nil]. ^aPane submorphThat: [:m | (m isKindOf: PluggableButtonMorph) and: [m actionSelector == aSelector]] ifNone: [^nil]! ! !CodeHolder methodsFor: 'controls' stamp: 'gvc 1/20/2009 15:55'! codePaneProvenanceButton "Answer a button that reports on, and allow the user to modify, the code-pane-provenance setting" ^(UITheme builder newDropListFor: self list: #codePaneProvenanceList getSelected: #codePaneProvenanceIndex setSelected: #codePaneProvenanceIndex: help: 'Select what is shown in the code pane' translated) useRoundedCorners; hResizing: #spaceFill; vResizing: #spaceFill; minWidth: 88! ! !CodeHolder methodsFor: 'controls' stamp: 'gvc 1/20/2009 15:34'! codePaneProvenanceIndex "Answer the selected code provenance index." ^((self contentsSymbolQuints select: [:e | e ~= #-]) collect: [:e | e first]) indexOf: self contentsSymbol ifAbsent: [0]! ! !CodeHolder methodsFor: 'controls' stamp: 'gvc 1/20/2009 15:33'! codePaneProvenanceIndex: anInteger "Set the code provenance to the item with the given index." self perform: ((self contentsSymbolQuints select: [:e | e ~= #-]) at: anInteger) second! ! !CodeHolder methodsFor: 'controls' stamp: 'gvc 1/20/2009 15:31'! codePaneProvenanceList "Answer a list of the display strings for code provenance." ^(self contentsSymbolQuints select: [:e | e ~= #-]) collect: [:e | e fourth]! ! !CodeHolder methodsFor: 'controls' stamp: 'sd 11/20/2005 21:26'! codePaneProvenanceString "Answer a string that reports on code-pane-provenance" | symsAndWordings | (symsAndWordings := self contentsSymbolQuints) do: [:aQuad | contentsSymbol == aQuad first ifTrue: [^ aQuad fourth]]. ^ symsAndWordings first fourth "default to plain source, for example if nil as initially"! ! !CodeHolder methodsFor: 'controls' stamp: 'alain.plantec 5/18/2009 15:31'! contentsSymbolQuints "Answer a list of quintuplets representing information on the alternative views available in the code pane first element: the contentsSymbol used second element: the selector to call when this item is chosen. third element: the selector to call to obtain the wording of the menu item. fourth element: the wording to represent this view fifth element: balloon help A hypen indicates a need for a seperator line in a menu of such choices" ^ #( (source togglePlainSource showingPlainSourceString 'source' 'the textual source code as writen') (documentation toggleShowDocumentation showingDocumentationString 'documentation' 'the first comment in the method') - (prettyPrint togglePrettyPrint prettyPrintString 'prettyPrint' 'the method source presented in a standard text format') - (showDiffs toggleRegularDiffing showingRegularDiffsString 'showDiffs' 'the textual source diffed from its prior version') (prettyDiffs togglePrettyDiffing showingPrettyDiffsString 'prettyDiffs' 'formatted textual source diffed from formatted form of prior version') - (decompile toggleDecompile showingDecompileString 'decompile' 'source code decompiled from byteCodes') (byteCodes toggleShowingByteCodes showingByteCodesString 'byteCodes' 'the bytecodes that comprise the compiled method'))! ! !CodeHolder methodsFor: 'controls' stamp: 'ar 2/12/2005 14:28'! decorateButtons "Change screen feedback for any buttons in the UI of the receiver that may wish it. Initially, it is only the Inheritance button that is decorated, but one can imagine others." self changed: #inheritanceButtonColor. self decorateForInheritance ! ! !CodeHolder methodsFor: 'controls' stamp: 'marcus.denker 8/17/2008 21:04'! decorateForInheritance "Check to see if the currently-viewed method has a super send or an override, and if so, change screen feedback, unless the #decorateBrowserButtons says not to." | aButton | (aButton := self inheritanceButton) ifNil: [^ self]. ((currentCompiledMethod isKindOf: CompiledMethod) and: [Preferences decorateBrowserButtons]) ifFalse: [^aButton offColor: Color transparent]. "This table duplicates the old logic, but adds two new colors for the cases where there is a superclass definition, but this method doesn't call it." aButton offColor: self color! ! !CodeHolder methodsFor: 'controls' stamp: 'sw 1/25/2001 14:44'! inheritanceButton "If receiver has an Inheritance button, answer it, else answer nil. morphic only at this point" ^ self buttonWithSelector: #methodHierarchy! ! !CodeHolder methodsFor: 'controls' stamp: 'sd 11/20/2005 21:27'! optionalButtonPairs "Answer a tuple (formerly pairs) defining buttons, in the format: button label selector to send help message" | aList | aList := #( ('browse' browseMethodFull 'view this method in a browser') ('senders' browseSendersOfMessages 'browse senders of...') ('implementors' browseMessages 'browse implementors of...') ('versions' browseVersions 'browse versions')), (Preferences decorateBrowserButtons ifTrue: [{#('inheritance' methodHierarchy 'browse method inheritance green: sends to super tan: has override(s) mauve: both of the above pink: is an override but doesn''t call super pinkish tan: has override(s), also is an override but doesn''t call super' )}] ifFalse: [{#('inheritance' methodHierarchy 'browse method inheritance')}]), #( ('hierarchy' classHierarchy 'browse class hierarchy') ('inst vars' browseInstVarRefs 'inst var refs...') ('class vars' browseClassVarRefs 'class var refs...')). ^ aList! ! !CodeHolder methodsFor: 'controls' stamp: 'sw 11/13/2001 09:12'! sourceAndDiffsQuintsOnly "Answer a list of quintuplets representing information on the alternative views available in the code pane for the case where the only plausible choices are showing source or either of the two kinds of diffs" ^ #( (source togglePlainSource showingPlainSourceString 'source' 'the textual source code as writen') (showDiffs toggleRegularDiffing showingRegularDiffsString 'showDiffs' 'the textual source diffed from its prior version') (prettyDiffs togglePrettyDiffing showingPrettyDiffsString 'prettyDiffs' 'formatted textual source diffed from formatted form of prior version'))! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 9/5/2001 13:36'! defaultDiffsSymbol "Answer the code symbol to use when generically switching to diffing" ^ Preferences diffsWithPrettyPrint ifTrue: [#prettyDiffs] ifFalse: [#showDiffs]! ! !CodeHolder methodsFor: 'diffs' stamp: 'sd 11/20/2005 21:27'! diffButton "Return a checkbox that lets the user decide whether diffs should be shown or not. Not sent any more but retained against the possibility of existing subclasses outside the base image using it." | outerButton aButton | outerButton := AlignmentMorph newRow. outerButton wrapCentering: #center; cellPositioning: #leftCenter. outerButton color: Color transparent. outerButton hResizing: #shrinkWrap; vResizing: #shrinkWrap. outerButton addMorph: (aButton := UpdatingThreePhaseButtonMorph checkBox). aButton target: self; actionSelector: #toggleRegularDiffing; getSelector: #showingRegularDiffs. outerButton addMorphBack: (StringMorph contents: 'diffs') lock. outerButton setBalloonText: 'If checked, then code differences from the previous version, if any, will be shown.'. ^ outerButton ! ! !CodeHolder methodsFor: 'diffs' stamp: 'sd 11/20/2005 21:27'! diffFromPriorSourceFor: sourceCode "If there is a prior version of source for the selected method, return a diff, else just return the source code" | prior | ^ (prior := self priorSourceOrNil) ifNil: [sourceCode] ifNotNil: [TextDiffBuilder buildDisplayPatchFrom: prior to: sourceCode inClass: self selectedClass prettyDiffs: self showingPrettyDiffs]! ! !CodeHolder methodsFor: 'diffs' stamp: 'sd 11/20/2005 21:27'! prettyDiffButton "Return a checkbox that lets the user decide whether prettyDiffs should be shown or not" | outerButton aButton | outerButton := AlignmentMorph newRow. outerButton wrapCentering: #center; cellPositioning: #leftCenter. outerButton color: Color transparent. outerButton hResizing: #shrinkWrap; vResizing: #shrinkWrap. outerButton addMorph: (aButton := UpdatingThreePhaseButtonMorph checkBox). aButton target: self; actionSelector: #togglePrettyDiffing; getSelector: #showingPrettyDiffs. outerButton addMorphBack: (StringMorph contents: 'prettyDiffs') lock. (self isKindOf: VersionsBrowser) ifTrue: [outerButton setBalloonText: 'If checked, then pretty-printed code differences from the previous version, if any, will be shown.'] ifFalse: [outerButton setBalloonText: 'If checked, then pretty-printed code differences between the file-based method and the in-memory version, if any, will be shown.']. ^ outerButton ! ! !CodeHolder methodsFor: 'diffs' stamp: 'sd 11/20/2005 21:27'! regularDiffButton "Return a checkbox that lets the user decide whether regular diffs should be shown or not" | outerButton aButton | outerButton := AlignmentMorph newRow. outerButton wrapCentering: #center; cellPositioning: #leftCenter. outerButton color: Color transparent. outerButton hResizing: #shrinkWrap; vResizing: #shrinkWrap. outerButton addMorph: (aButton := UpdatingThreePhaseButtonMorph checkBox). aButton target: self; actionSelector: #toggleRegularDiffing; getSelector: #showingRegularDiffs. outerButton addMorphBack: (StringMorph contents: 'diffs') lock. outerButton setBalloonText: 'If checked, then code differences from the previous version, if any, will be shown.'. ^ outerButton ! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 11/13/2001 07:49'! showDiffs "Answer whether the receiver is showing diffs of source code. The preferred protocol here is #showingRegularDiffs, but this message is still sent by some preexisting buttons so is retained." ^ contentsSymbol == #showDiffs ! ! !CodeHolder methodsFor: 'diffs' stamp: 'sd 11/20/2005 21:27'! showDiffs: aBoolean "Set whether I'm showing diffs as indicated; use the global preference to determine which kind of diffs to institute." self showingAnyKindOfDiffs ifFalse: [aBoolean ifTrue: [contentsSymbol := self defaultDiffsSymbol]] ifTrue: [aBoolean ifFalse: [contentsSymbol := #source]]. self setContentsToForceRefetch. self contentsChanged! ! !CodeHolder methodsFor: 'diffs' stamp: 'sd 11/20/2005 21:26'! showPrettyDiffs: aBoolean "Set whether I'm showing pretty diffs as indicated" self showingPrettyDiffs ifFalse: [aBoolean ifTrue: [contentsSymbol := #prettyDiffs]] ifTrue: [aBoolean ifFalse: [contentsSymbol := #source]]. self setContentsToForceRefetch. self contentsChanged! ! !CodeHolder methodsFor: 'diffs' stamp: 'sd 11/20/2005 21:26'! showRegularDiffs: aBoolean "Set whether I'm showing regular diffs as indicated" self showingRegularDiffs ifFalse: [aBoolean ifTrue: [contentsSymbol := #showDiffs]] ifTrue: [aBoolean ifFalse: [contentsSymbol := #source]]. self setContentsToForceRefetch. self contentsChanged! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 9/5/2001 13:32'! showingAnyKindOfDiffs "Answer whether the receiver is currently set to show any kind of diffs" ^ #(showDiffs prettyDiffs) includes: contentsSymbol! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 11/13/2001 09:10'! showingDiffsString "Answer a string representing whether I'm showing diffs. Not sent any more but retained so that prexisting buttons that sent this will not raise errors." ^ (self showingRegularDiffs ifTrue: [''] ifFalse: ['']), 'showDiffs'! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 5/19/2001 00:07'! showingPrettyDiffs "Answer whether the receiver is showing pretty diffs of source code" ^ contentsSymbol == #prettyDiffs ! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 5/22/2001 16:41'! showingPrettyDiffsString "Answer a string representing whether I'm showing pretty diffs" ^ (self showingPrettyDiffs ifTrue: [''] ifFalse: ['']), 'prettyDiffs'! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 11/13/2001 07:07'! showingRegularDiffs "Answer whether the receiver is showing regular diffs of source code" ^ contentsSymbol == #showDiffs ! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 11/13/2001 07:43'! showingRegularDiffsString "Answer a string representing whether I'm showing regular diffs" ^ (self showingRegularDiffs ifTrue: [''] ifFalse: ['']), 'showDiffs'! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 1/18/2001 13:58'! toggleDiff "Retained for backward compatibility with existing buttons in existing images" self toggleDiffing! ! !CodeHolder methodsFor: 'diffs' stamp: 'marcus.denker 9/20/2008 20:31'! toggleDiffing "Toggle whether diffs should be shown in the code pane. If any kind of diffs were being shown, stop showing diffs. If no kind of diffs were being shown, start showing whatever kind of diffs are called for by default." | wasShowingDiffs | self okToChange ifTrue: [wasShowingDiffs := self showingAnyKindOfDiffs. self showDiffs: wasShowingDiffs not. self setContentsToForceRefetch. self contentsChanged] ! ! !CodeHolder methodsFor: 'diffs' stamp: 'marcus.denker 9/20/2008 20:31'! togglePlainSource "Toggle whether plain source shown in the code pane" | wasShowingPlainSource | self okToChange ifTrue: [wasShowingPlainSource := self showingPlainSource. wasShowingPlainSource ifTrue: [self showDocumentation: true] ifFalse: [contentsSymbol := #source]. self setContentsToForceRefetch. self changed: #contents] ! ! !CodeHolder methodsFor: 'diffs' stamp: 'marcus.denker 9/20/2008 20:31'! togglePrettyDiffing "Toggle whether pretty-diffing should be shown in the code pane" | wasShowingDiffs | self okToChange ifTrue: [wasShowingDiffs := self showingPrettyDiffs. self showPrettyDiffs: wasShowingDiffs not. self setContentsToForceRefetch. self contentsChanged] ! ! !CodeHolder methodsFor: 'diffs' stamp: 'marcus.denker 9/20/2008 20:31'! togglePrettyPrint "Toggle whether pretty-print is in effectin the code pane" self okToChange ifTrue: [self showingPrettyPrint ifTrue: [contentsSymbol := #source] ifFalse: [contentsSymbol := #prettyPrint]. self setContentsToForceRefetch. self contentsChanged] ! ! !CodeHolder methodsFor: 'diffs' stamp: 'marcus.denker 9/20/2008 20:31'! toggleRegularDiffing "Toggle whether regular-diffing should be shown in the code pane" | wasShowingDiffs | self okToChange ifTrue: [wasShowingDiffs := self showingRegularDiffs. self showRegularDiffs: wasShowingDiffs not. self setContentsToForceRefetch. self contentsChanged] ! ! !CodeHolder methodsFor: 'diffs' stamp: 'sw 11/13/2001 07:24'! wantsDiffFeedback "Answer whether the receiver is showing diffs of source code" ^ self showingAnyKindOfDiffs! ! !CodeHolder methodsFor: 'message category functions' stamp: 'sw 10/8/2001 14:19'! canShowMultipleMessageCategories "Answer whether the receiver is capable of showing multiple message categories" ^ false! ! !CodeHolder methodsFor: 'message list' stamp: 'md 2/22/2006 16:10'! decompiledSourceIntoContents "Obtain a source string by decompiling the method's code, and place that source string into my contents. Also return the string. Get temps from source file if shift key is pressed." | class | class := self selectedClassOrMetaClass. "Was method deleted while in another project?" currentCompiledMethod := (class compiledMethodAt: self selectedMessageName ifAbsent: [^ '']). contents := (Sensor leftShiftDown not) ifTrue: [currentCompiledMethod decompileWithTemps] ifFalse: [currentCompiledMethod decompile]. contents := contents decompileString asText makeSelectorBoldIn: class. ^ contents copy! ! !CodeHolder methodsFor: 'message list' stamp: 'sw 8/16/2002 23:23'! selectedBytecodes "Answer text to show in a code pane when in showing-byte-codes mode" ^ (self selectedClassOrMetaClass compiledMethodAt: self selectedMessageName ifAbsent: [^ '' asText]) symbolic asText! ! !CodeHolder methodsFor: 'message list' stamp: 'md 2/20/2006 15:02'! selectedMessage "Answer a copy of the source code for the selected message. This generic version is probably actually never reached, since every subclass probably reimplements and does not send to super. In time, ideally, most, or all, reimplementors would vanish and all would defer instead to a universal version right here. Everything in good time." | class selector method | contents ifNotNil: [^ contents copy]. self showingDecompile ifTrue:[^ self decompiledSourceIntoContents]. class := self selectedClassOrMetaClass. (class isNil or: [(selector := self selectedMessageName) isNil]) ifTrue: [^ '']. method := class compiledMethodAt: selector ifAbsent: [^ '']. "method deleted while in another project" currentCompiledMethod := method. ^ contents := (self showComment ifFalse: [self sourceStringPrettifiedAndDiffed] ifTrue: [ self commentContents]) copy asText makeSelectorBoldIn: class! ! !CodeHolder methodsFor: 'message list' stamp: 'alain.plantec 5/18/2009 15:44'! sourceStringPrettifiedAndDiffed "Answer a copy of the source code for the selected message, transformed by diffing and pretty-printing exigencies" | class selector sourceString | class := self selectedClassOrMetaClass. selector := self selectedMessageName. (class isNil or: [selector isNil]) ifTrue: [^'missing']. sourceString := class ultimateSourceCodeAt: selector ifAbsent: [^'error']. self validateMessageSource: sourceString forSelector: selector. (#(#prettyPrint #prettyDiffs) includes: contentsSymbol) ifTrue: [sourceString := class prettyPrinterClass format: sourceString in: class notifying: nil]. self showingAnyKindOfDiffs ifTrue: [sourceString := self diffFromPriorSourceFor: sourceString]. ^sourceString! ! !CodeHolder methodsFor: 'message list' stamp: 'sd 11/20/2005 21:27'! validateMessageSource: sourceString forSelector: aSelector "Check whether there is evidence that method source is invalid" | sourcesName | (self selectedClass compilerClass == Object compilerClass and: [(sourceString asString findString: aSelector keywords first ) ~= 1]) ifTrue: [sourcesName := FileDirectory localNameFor: SmalltalkImage current sourcesName. self inform: 'There may be a problem with your sources file!! The source code for every method should (usually) start with the method selector but this is not the case with this method!! You may proceed with caution but it is recommended that you get a new source file. This can happen if you download the "' , sourcesName , '" file, or the ".changes" file you use, as TEXT. It must be transfered in BINARY mode, even if it looks like a text file, to preserve the CR line ends. Mac users: This may have been caused by Stuffit Expander. To prevent the files above to be converted to Mac line ends when they are expanded, do this: Start the program, then from Preferences... in the File menu, choose the Cross Platform panel, then select "Never" and press OK. Then expand the compressed archive again. (Occasionally, the source code for a method may legitimately start with a non-alphabetic character -- for example, Behavior method #formalHeaderPartsFor:. In such rare cases, you can happily disregard this warning.)'].! ! !CodeHolder methodsFor: 'message list menu' stamp: 'sd 11/20/2005 21:27'! messageListKey: aChar from: view "Respond to a Command key. I am a model with a code pane, and I also have a listView that has a list of methods. The view knows how to get the list and selection." | sel class | aChar == $D ifTrue: [^ self toggleDiffing]. sel := self selectedMessageName. aChar == $m ifTrue: "These next two put up a type in if no message selected" [^ self useSelector: sel orGetSelectorAndSendQuery: #browseAllImplementorsOf: to: self systemNavigation]. aChar == $n ifTrue: [^ self useSelector: sel orGetSelectorAndSendQuery: #browseAllCallsOn: to: self systemNavigation]. "The following require a class selection" (class := self selectedClassOrMetaClass) ifNil: [^ self arrowKey: aChar from: view]. aChar == $b ifTrue: [^ Browser fullOnClass: class selector: sel]. aChar == $N ifTrue: [^ self browseClassRefs]. aChar == $i ifTrue: [^ self methodHierarchy]. aChar == $h ifTrue: [^ self classHierarchy]. aChar == $p ifTrue: [^ self browseFullProtocol]. "The following require a method selection" sel ifNotNil: [aChar == $o ifTrue: [^ self fileOutMessage]. aChar == $c ifTrue: [^ self copySelector]. aChar == $v ifTrue: [^ self browseVersions]. aChar == $O ifTrue: [^ self openSingleMessageBrowser]. aChar == $x ifTrue: [^ self removeMessage]. aChar == $d ifTrue: [^ self removeMessageFromBrowser]. (aChar == $C and: [self canShowMultipleMessageCategories]) ifTrue: [^ self showHomeCategory]]. ^ self arrowKey: aChar from: view! ! !CodeHolder methodsFor: 'misc' stamp: 'md 2/24/2006 15:25'! addOptionalButtonsTo: window at: fractions plus: verticalOffset "If the receiver wishes it, add a button pane to the window, and answer the verticalOffset plus the height added" | delta buttons divider | self wantsOptionalButtons ifFalse: [^ verticalOffset]. delta := self defaultButtonPaneHeight. buttons := self optionalButtonRow color: Color white. divider := BorderedSubpaneDividerMorph forBottomEdge. divider extent: 4 @ 4; color: Color gray; borderColor: #simple; borderWidth: 1. window addMorph: buttons fullFrame: (LayoutFrame fractions: fractions offsets: (0 @ verticalOffset corner: 0 @ (verticalOffset + delta - 1))). window addMorph: divider fullFrame: (LayoutFrame fractions: fractions offsets: (0 @ (verticalOffset + delta - 1) corner: 0 @ (verticalOffset + delta))). ^ verticalOffset + delta! ! !CodeHolder methodsFor: 'misc' stamp: 'nk 4/10/2001 07:52'! getSelectorAndSendQuery: querySelector to: queryPerformer "Obtain a selector relevant to the current context, and then send the querySelector to the queryPerformer with the selector obtained as its argument. If no message is currently selected, then obtain a method name from a user type-in" self getSelectorAndSendQuery: querySelector to: queryPerformer with: { }. ! ! !CodeHolder methodsFor: 'misc' stamp: 'StephaneDucasse 10/15/2009 18:01'! getSelectorAndSendQuery: querySelector to: queryPerformer with: queryArgs "Obtain a selector relevant to the current context, and then send the querySelector to the queryPerformer with the selector obtained and queryArgs as its arguments. If no message is currently selected, then obtain a method name from a user type-in" | strm array | strm := (array := Array new: queryArgs size + 1) writeStream. strm nextPut: nil. strm nextPutAll: queryArgs. self selectedMessageName ifNil: [ | selector | selector := UIManager default request: 'Type selector:' initialAnswer: 'flag:'. selector ifNil: [selector := String new]. selector := selector copyWithout: Character space. ^ selector isEmptyOrNil ifFalse: [ (Symbol hasInterned: selector ifTrue: [ :aSymbol | array at: 1 put: aSymbol. queryPerformer perform: querySelector withArguments: array]) ifFalse: [ self inform: 'no such selector'] ] ]. self selectMessageAndEvaluate: [:selector | array at: 1 put: selector. queryPerformer perform: querySelector withArguments: array ]! ! !CodeHolder methodsFor: 'misc' stamp: 'md 2/24/2006 15:28'! isThereAnOverride "Answer whether any subclass of my selected class implements my selected selector" | aName aClass | aName := self selectedMessageName ifNil: [^ false]. aClass := self selectedClassOrMetaClass ifNil: [^ false]. aClass allSubclassesDo: [ :cls | (cls includesSelector: aName) ifTrue: [ ^true ]]. ^ false! ! !CodeHolder methodsFor: 'misc' stamp: 'md 2/24/2006 15:28'! isThisAnOverride "Answer whether any superclass of my selected class implements my selected selector" | aName aClass | aName := self selectedMessageName ifNil: [^ false]. aClass := self selectedClassOrMetaClass ifNil: [^ false]. aClass allSuperclassesDo: [ :cls | (cls includesSelector: aName) ifTrue: [ ^true ]]. ^ false! ! !CodeHolder methodsFor: 'misc' stamp: 'sd 11/20/2005 21:27'! menuButton "Answer a button that brings up a menu. Useful when adding new features, but at present is between uses" | aButton | aButton := IconicButton new target: self; borderWidth: 0; labelGraphic: (ScriptingSystem formAtKey: #TinyMenu); color: Color transparent; actWhen: #buttonDown; actionSelector: #offerMenu; yourself. aButton setBalloonText: 'click here to get a menu with further options'. ^ aButton ! ! !CodeHolder methodsFor: 'misc' stamp: 'sw 9/27/2001 01:26'! modelWakeUpIn: aWindow "The window has been activated. Respond to possible changes that may have taken place while it was inactive" self updateListsAndCodeIn: aWindow. self decorateButtons. self refreshAnnotation. super modelWakeUpIn: aWindow! ! !CodeHolder methodsFor: 'misc' stamp: 'alain.plantec 2/6/2009 16:46'! okayToAccept "Answer whether it is okay to accept the receiver's input" self showingDocumentation ifTrue: [self inform: 'Sorry, for the moment you can only submit changes here when you are showing source. Later, you will be able to edit the isolated comment here and save it back, but only if you implement it!!.' translated. ^ false]. self showingAnyKindOfDiffs ifFalse: [^ true]. ^ self confirm: 'Caution!! You are "showing diffs" here, so there is a danger that some of the text in the code pane is contaminated by the "diff" display' translated ! ! !CodeHolder methodsFor: 'misc' stamp: 'sd 11/20/2005 21:27'! priorSourceOrNil "If the currently-selected method has a previous version, return its source, else return nil" | aClass aSelector changeRecords | (aClass := self selectedClassOrMetaClass) ifNil: [^ nil]. (aSelector := self selectedMessageName) ifNil: [^ nil]. changeRecords := aClass changeRecordsAt: aSelector. (changeRecords == nil or: [changeRecords size <= 1]) ifTrue: [^ nil]. ^ (changeRecords at: 2) string ! ! !CodeHolder methodsFor: 'misc' stamp: 'marcus.denker 11/10/2008 10:04'! refreshAnnotation "If the receiver has an annotation pane that does not bear unaccepted edits, refresh it" (self dependents detect: [:m | (m inheritsFromAnyIn: #('PluggableTextView' 'PluggableTextMorph')) and: [m getTextSelector == #annotation]] ifNone: [nil]) ifNotNil: [:aPane | aPane hasUnacceptedEdits ifFalse: [aPane update: #annotation]]! ! !CodeHolder methodsFor: 'misc' stamp: 'stephane.ducasse 10/26/2008 15:13'! refusesToAcceptCode "Answer whether receiver, given its current contentsSymbol, could accept code happily if asked to" ^ (#(byteCodes documentation) includes: self contentsSymbol)! ! !CodeHolder methodsFor: 'misc' stamp: 'sd 11/20/2005 21:27'! releaseCachedState "Can always be found again. Don't write on a file." currentCompiledMethod := nil.! ! !CodeHolder methodsFor: 'misc' stamp: 'sd 11/20/2005 21:27'! sampleInstanceOfSelectedClass | aClass | "Return a sample instance of the class currently being pointed at" (aClass := self selectedClassOrMetaClass) ifNil: [^ nil]. ^ aClass theNonMetaClass initializedInstance! ! !CodeHolder methodsFor: 'misc' stamp: 'rbb 3/1/2005 10:31'! sendQuery: querySelector to: queryPerformer "Apply a query to the primary selector associated with the current context. If no such selection exists, obtain one by user type-in. Then send querySelector to queryPerformer with the selector as its argument." | aSelector aString | aSelector := self selectedMessageName ifNil: [aString :=UIManager default request: 'Type selector:' initialAnswer: 'flag:'. ^ aString isEmptyOrNil ifFalse: [(Symbol hasInterned: aString ifTrue: [:aSymbol | queryPerformer perform: querySelector with: aSymbol]) ifFalse: [self inform: 'no such selector']]]. queryPerformer perform: querySelector with: aSelector! ! !CodeHolder methodsFor: 'misc' stamp: 'sd 11/20/2005 21:27'! setClassAndSelectorIn: csBlock "Evaluate csBlock with my selected class and and selector as its arguments; provide nil arguments if I don't have a method currently selected" | aName | (aName := self selectedMessageName) ifNil: [csBlock value: nil value: nil] ifNotNil: [csBlock value: self selectedClassOrMetaClass value: aName] ! ! !CodeHolder methodsFor: 'misc' stamp: 'sw 2/22/2001 06:37'! suggestCategoryToSpawnedBrowser: aBrowser "aBrowser is a message-category browser being spawned from the receiver. Tell it what it needs to know to get its category info properly set up." aBrowser setOriginalCategoryIndexForCurrentMethod! ! !CodeHolder methodsFor: 'misc' stamp: 'rbb 3/1/2005 10:31'! useSelector: incomingSelector orGetSelectorAndSendQuery: querySelector to: queryPerformer "If incomingSelector is not nil, use it, else obtain a selector from user type-in. Using the determined selector, send the query to the performer provided." | aSelector | incomingSelector ifNotNil: [queryPerformer perform: querySelector with: incomingSelector] ifNil: [aSelector :=UIManager default request: 'Type selector:' initialAnswer: 'flag:'. aSelector isEmptyOrNil ifFalse: [(Symbol hasInterned: aSelector ifTrue: [:aSymbol | queryPerformer perform: querySelector with: aSymbol]) ifFalse: [self inform: 'no such selector']]]! ! !CodeHolder methodsFor: 'self-updating' stamp: 'nk 4/29/2004 12:25'! didCodeChangeElsewhere "Determine whether the code for the currently selected method and class has been changed somewhere else." | aClass aSelector aCompiledMethod | currentCompiledMethod ifNil: [^ false]. (aClass := self selectedClassOrMetaClass) ifNil: [^ false]. (aSelector := self selectedMessageName) ifNil: [^ false]. self classCommentIndicated ifTrue: [^ currentCompiledMethod ~~ aClass organization commentRemoteStr]. ^ (aCompiledMethod := aClass compiledMethodAt: aSelector ifAbsent: [^ false]) ~~ currentCompiledMethod and: [aCompiledMethod last ~= 0 "either not yet installed" or: [ currentCompiledMethod last = 0 "or these methods don't have source pointers"]]! ! !CodeHolder methodsFor: 'self-updating' stamp: 'sw 10/19/1999 08:37'! stepIn: aSystemWindow self updateListsAndCodeIn: aSystemWindow! ! !CodeHolder methodsFor: 'self-updating' stamp: 'sw 2/14/2001 15:34'! updateCodePaneIfNeeded "If the code for the currently selected method has changed underneath me, then update the contents of my code pane unless it holds unaccepted edits" self didCodeChangeElsewhere ifTrue: [self hasUnacceptedEdits ifFalse: [self setContentsToForceRefetch. self contentsChanged] ifTrue: [self changed: #codeChangedElsewhere]]! ! !CodeHolder methodsFor: 'self-updating' stamp: 'sw 10/19/1999 14:14'! updateListsAndCodeIn: aWindow super updateListsAndCodeIn: aWindow. self updateCodePaneIfNeeded! ! !CodeHolder methodsFor: 'self-updating' stamp: 'sw 10/20/1999 12:22'! wantsStepsIn: aWindow ^ Preferences smartUpdating! ! !CodeHolder methodsFor: 'tiles' stamp: 'alain.plantec 5/30/2008 11:23'! addModelItemsToWindowMenu: aMenu "Add model-related item to the window menu" super addModelItemsToWindowMenu: aMenu. aMenu addLine. aMenu add: 'what to show...' translated target: self action: #offerWhatToShowMenu! ! !CodeHolder methodsFor: 'toolbuilder' stamp: 'ar 2/12/2005 14:32'! buildCodeProvenanceButtonWith: builder | buttonSpec | buttonSpec := builder pluggableActionButtonSpec new. buttonSpec model: self. buttonSpec label: #codePaneProvenanceString. buttonSpec action: #offerWhatToShowMenu. buttonSpec help: 'Governs what view is shown in the code pane. Click here to change the view'. ^buttonSpec! ! !CodeHolder methodsFor: 'toolbuilder' stamp: 'ar 2/12/2005 14:32'! buildOptionalButtonsWith: builder | panelSpec buttonSpec | panelSpec := builder pluggablePanelSpec new. panelSpec children: OrderedCollection new. self optionalButtonPairs do:[:spec| buttonSpec := builder pluggableActionButtonSpec new. buttonSpec model: self. buttonSpec label: spec first. buttonSpec action: spec second. spec second == #methodHierarchy ifTrue:[ buttonSpec color: #inheritanceButtonColor. ]. spec size > 2 ifTrue:[buttonSpec help: spec third]. panelSpec children add: buttonSpec. ]. "What to show" panelSpec children add: (self buildCodeProvenanceButtonWith: builder). panelSpec layout: #horizontal. "buttons" ^panelSpec! ! !CodeHolder methodsFor: 'toolbuilder' stamp: 'marcus.denker 8/17/2008 21:02'! color | flags aColor | flags := 0. self isThisAnOverride ifTrue: [ flags := flags bitOr: 4 ]. currentCompiledMethod sendsToSuper ifTrue: [ flags := flags bitOr: 2 ]. self isThereAnOverride ifTrue: [ flags := flags bitOr: 1 ]. aColor := { Color transparent. Color tan lighter. Color green muchLighter. Color blue muchLighter. Color red muchLighter. "has super but doesn't call it" (Color r: 0.94 g: 0.823 b: 0.673). "has sub; has super but doesn't call it" Color green muchLighter. Color blue muchLighter. } at: flags + 1. ^aColor! ! !CodeHolder methodsFor: 'toolbuilder' stamp: 'marcus.denker 8/17/2008 21:04'! inheritanceButtonColor "Check to see if the currently-viewed method has a super send or an override, and if so, change screen feedback, unless the #decorateBrowserButtons says not to." ((currentCompiledMethod isKindOf: CompiledMethod) and: [Preferences decorateBrowserButtons]) ifFalse: [^Color transparent]. "This table duplicates the old logic, but adds two new colors for the cases where there is a superclass definition, but this method doesn't call it." ^ self color ! ! !CodeHolder methodsFor: 'traits' stamp: 'alain.plantec 5/30/2008 11:25'! makeSampleInstance | aClass nonMetaClass anInstance | ((aClass := self selectedClassOrMetaClass) isNil or: [aClass isTrait]) ifTrue: [^ self]. nonMetaClass := aClass theNonMetaClass. anInstance := self sampleInstanceOfSelectedClass. (anInstance isNil and: [nonMetaClass ~~ UndefinedObject]) ifTrue: [^ self inform: 'Sorry, cannot make an instance of ' , nonMetaClass name]. anInstance isMorph ifTrue: [self currentHand attachMorph: anInstance] ifFalse: [anInstance inspectWithLabel: 'An instance of ' , nonMetaClass name]! ! !CodeHolder methodsFor: 'traits' stamp: 'alain.plantec 2/6/2009 16:49'! showUnreferencedClassVars "Search for all class variables known to the selected class, and put up a list of those that have no references anywhere in the system. The search includes superclasses, so that you don't need to navigate your way to the class that defines each class variable in order to determine whether it is unreferenced" | cls aList aReport | ((cls := self selectedClass) isNil or: [cls isTrait]) ifTrue: [^ self]. aList := self systemNavigation allUnreferencedClassVariablesOf: cls. aList size == 0 ifTrue: [^ self inform: 'There are no unreferenced class variables in ' , cls name]. aReport := String streamContents: [:aStream | aStream nextPutAll: 'Unreferenced class variable(s) in ' translated, cls name; cr. aList do: [:el | aStream tab; nextPutAll: el; cr]]. Transcript cr; show: aReport. self inform: aReport! ! !CodeHolder methodsFor: 'traits' stamp: 'alain.plantec 2/6/2009 16:51'! showUnreferencedInstVars "Search for all instance variables known to the selected class, and put up a list of those that have no references anywhere in the system. The search includes superclasses, so that you don't need to navigate your way to the class that defines each inst variable in order to determine whether it is unreferenced" | cls aList aReport | ((cls := self selectedClassOrMetaClass) isNil or: [cls isTrait]) ifTrue: [^ self]. aList := cls allUnreferencedInstanceVariables. aList size == 0 ifTrue: [^ self inform: 'There are no unreferenced instance variables in ', cls name]. aReport := String streamContents: [:aStream | aStream nextPutAll: 'Unreferenced instance variable(s) in ' translated, cls name; cr. aList do: [:el | aStream tab; nextPutAll: el; cr]]. Transcript cr; show: aReport. self inform: aReport! ! !CodeHolder methodsFor: 'traits' stamp: 'alain.plantec 5/30/2008 11:27'! spawnHierarchy "Create and schedule a new hierarchy browser on the currently selected class or meta." | newBrowser aSymbol aBehavior messageCatIndex selectedClassOrMetaClass | (selectedClassOrMetaClass := self selectedClassOrMetaClass) ifNil: [^ self]. selectedClassOrMetaClass isTrait ifTrue: [^ self]. newBrowser := HierarchyBrowser new initHierarchyForClass: selectedClassOrMetaClass. ((aSymbol := self selectedMessageName) notNil and: [(MessageSet isPseudoSelector: aSymbol) not]) ifTrue: [aBehavior := selectedClassOrMetaClass. messageCatIndex := aBehavior organization numberOfCategoryOfElement: aSymbol. newBrowser messageCategoryListIndex: messageCatIndex + 1. newBrowser messageListIndex: ((aBehavior organization listAtCategoryNumber: messageCatIndex) indexOf: aSymbol)]. Browser openBrowserView: (newBrowser openSystemCatEditString: nil) label: newBrowser labelString. newBrowser assureSelectionsShow! ! !CodeHolder methodsFor: 'what to show' stamp: 'alain.plantec 5/30/2008 11:22'! addContentsTogglesTo: aMenu "Add updating menu toggles governing contents to aMenu." self contentsSymbolQuints do: [:aQuint | aQuint == #- ifTrue: [aMenu addLine] ifFalse: [aMenu addUpdating: aQuint third target: self action: aQuint second. aMenu balloonTextForLastItem: aQuint fifth]]! ! !CodeHolder methodsFor: 'what to show' stamp: 'alain.plantec 5/30/2008 11:26'! offerWhatToShowMenu "Offer a menu governing what to show" | aMenu | aMenu := MenuMorph new defaultTarget: self. aMenu addTitle: 'What to show' translated. aMenu addStayUpItem. self addContentsTogglesTo: aMenu. aMenu popUpInWorld! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/22/2001 16:36'! prettyPrintString "Answer whether the receiver is showing pretty-print" ^ ((contentsSymbol == #prettyPrint) ifTrue: [''] ifFalse: ['']), 'prettyPrint'! ! !CodeHolder methodsFor: 'what to show' stamp: 'sd 11/20/2005 21:27'! setContentsToForceRefetch "Set the receiver's contents such that on the next update the contents will be formulated afresh. This is a critical and obscure difference between Browsers on the one hand and MessageSets on the other, and has over the years been the source of much confusion and much difficulty. By centralizing the different handling here, we don't need so many idiosyncratic overrides in MessageSet any more" contents := nil! ! !CodeHolder methodsFor: 'what to show' stamp: 'sd 11/20/2005 21:27'! showByteCodes: aBoolean "Get into or out of bytecode-showoing mode" self okToChange ifFalse: [^ self changed: #flash]. aBoolean ifTrue: [contentsSymbol := #byteCodes] ifFalse: [contentsSymbol == #byteCodes ifTrue: [contentsSymbol := #source]]. self contentsChanged! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 12/5/2000 11:32'! showComment "Answer whether the receiver should show documentation rather than, say, source code" ^ self contentsSymbol == #documentation ! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/20/2001 09:14'! showDecompile: aBoolean "Set the decompile toggle as indicated" self contentsSymbol: (aBoolean ifFalse: [#source] ifTrue: [#decompile])! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 12/5/2000 12:25'! showDocumentation: aBoolean "Set the showDocumentation toggle as indicated" self contentsSymbol: (aBoolean ifFalse: [#source] ifTrue: [#documentation])! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/18/2001 18:05'! showingByteCodes "Answer whether the receiver is showing bytecodes" ^ contentsSymbol == #byteCodes! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/22/2001 18:28'! showingByteCodesString "Answer whether the receiver is showing bytecodes" ^ (self showingByteCodes ifTrue: [''] ifFalse: ['']), 'byteCodes'! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/20/2001 06:52'! showingDecompile "Answer whether the receiver should show decompile rather than, say, source code" ^ self contentsSymbol == #decompile ! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/20/2001 06:50'! showingDecompileString "Answer a string characerizing whether decompilation is showing" ^ (self showingDecompile ifTrue: [''] ifFalse: ['']), 'decompile'! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 12/5/2000 12:12'! showingDocumentation "Answer whether the receiver should show documentation rather than, say, source code" ^ self contentsSymbol == #documentation ! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/18/2001 20:05'! showingDocumentationString "Answer a string characerizing whether documentation is showing" ^ (self showingDocumentation ifTrue: [''] ifFalse: ['']), 'documentation'! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/18/2001 19:43'! showingPlainSource "Answer whether the receiver is showing plain source" ^ contentsSymbol == #source! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/22/2001 09:31'! showingPlainSourceString "Answer a string telling whether the receiver is showing plain source" ^ (self showingPlainSource ifTrue: [''] ifFalse: ['']), 'source'! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 5/18/2001 18:36'! showingPrettyPrint "Answer whether the receiver is showing pretty-print" ^ contentsSymbol == #prettyPrint! ! !CodeHolder methodsFor: 'what to show' stamp: 'sw 12/5/2000 11:48'! showingSource "Answer whether the receiver is currently showing source code" ^ self contentsSymbol == #source ! ! !CodeHolder methodsFor: 'what to show' stamp: 'marcus.denker 9/20/2008 20:31'! toggleDecompile "Toggle the setting of the showingDecompile flag, unless there are unsubmitted edits that the user declines to discard" | wasShowing | self okToChange ifTrue: [wasShowing := self showingDecompile. self showDecompile: wasShowing not. self setContentsToForceRefetch. self contentsChanged] ! ! !CodeHolder methodsFor: 'what to show' stamp: 'marcus.denker 9/20/2008 20:32'! toggleShowDocumentation "Toggle the setting of the showingDocumentation flag, unless there are unsubmitted edits that the user declines to discard" | wasShowing | self okToChange ifTrue: [wasShowing := self showingDocumentation. self showDocumentation: wasShowing not. self setContentsToForceRefetch. self contentsChanged] ! ! !CodeHolder methodsFor: 'what to show' stamp: 'marcus.denker 9/20/2008 20:32'! toggleShowingByteCodes "Toggle whether the receiver is showing bytecodes" self showByteCodes: self showingByteCodes not. self setContentsToForceRefetch. self contentsChanged! ! Object subclass: #CodeLoader instanceVariableNames: 'baseURL sourceFiles segments publicKey' classVariableNames: 'DefaultBaseURL DefaultKey' poolDictionaries: '' category: 'System-Download'! !CodeLoader commentStamp: '' prior: 0! CodeLoader provides a simple facility for loading code from the network. Examples: | loader | loader _ CodeLoader new. loader baseURL:'http://isgwww.cs.uni-magdeburg.de/~raab/test/'. loader localCache: #('.cache' 'source'). "Sources and segments can be loaded in parallel" loader loadSourceFiles: #('file1.st' 'file2.st.gz'). loader localCache: #('.cache' 'segments'). loader loadSegments: #('is1.extseg' 'is2.extseg.gz'). "Install sources first - will wait until the files are actually loaded" loader installSourceFiles. "And then the segments" loader installSegments.! !CodeLoader methodsFor: 'accessing' stamp: 'ar 12/13/1999 18:19'! baseURL ^baseURL! ! !CodeLoader methodsFor: 'accessing' stamp: 'ar 12/13/1999 18:19'! baseURL: aString baseURL := aString.! ! !CodeLoader methodsFor: 'accessing' stamp: 'ar 12/22/1999 15:07'! publicKey ^publicKey! ! !CodeLoader methodsFor: 'accessing' stamp: 'ar 12/22/1999 15:07'! publicKey: aPublicKey publicKey := aPublicKey! ! !CodeLoader methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:47'! initialize super initialize. publicKey := DefaultKey. baseURL := self class defaultBaseURL! ! !CodeLoader methodsFor: 'installing' stamp: 'RAA 2/19/2001 08:23'! installProject "Assume that we're loading a single file and it's a project" | aStream | aStream := sourceFiles first contentStream. aStream ifNil:[^self error:'Project was not loaded']. ProjectLoading openName: nil "<--do we want to cache this locally? Need a name if so" stream: aStream fromDirectory: nil withProjectView: nil. ! ! !CodeLoader methodsFor: 'installing' stamp: 'sd 1/30/2004 15:16'! installSegment: reqEntry "Install the previously loaded segment" | contentStream contents trusted | contentStream := reqEntry value contentStream. contentStream ifNil:[^self error:'No content to install: ', reqEntry key printString]. trusted := SecurityManager default positionToSecureContentsOf: contentStream. trusted ifFalse:[(SecurityManager default enterRestrictedMode) ifFalse:[ contentStream close. ^self error:'Insecure content encountered: ', reqEntry key printString]]. contents := contentStream ascii upToEnd unzipped. (contentStream respondsTo: #close) ifTrue:[contentStream close]. ^(RWBinaryOrTextStream with: contents) reset fileInObjectAndCode install.! ! !CodeLoader methodsFor: 'installing' stamp: 'mir 1/20/2000 13:37'! installSegments "Install the previously loaded segments" segments == nil ifTrue:[^self]. segments do:[:req| self installSegment: req]. segments := nil.! ! !CodeLoader methodsFor: 'installing' stamp: 'sd 1/30/2004 15:16'! installSourceFile: aStream "Install the previously loaded source file" | contents trusted | aStream ifNil:[^self error:'No content to install']. trusted := SecurityManager default positionToSecureContentsOf: aStream. trusted ifFalse:[(SecurityManager default enterRestrictedMode) ifFalse:[ aStream close. ^ self error:'Insecure content encountered']]. contents := aStream ascii upToEnd unzipped. (aStream respondsTo: #close) ifTrue:[aStream close]. ^(RWBinaryOrTextStream with: contents) reset fileIn! ! !CodeLoader methodsFor: 'installing' stamp: 'ar 12/22/1999 15:02'! installSourceFiles "Install the previously loaded source files" sourceFiles == nil ifTrue:[^self]. sourceFiles do:[:req| self installSourceFile: req contentStream]. sourceFiles := nil.! ! !CodeLoader methodsFor: 'loading' stamp: 'mir 10/13/2000 12:24'! loadSegments: anArray "Load all the source files in the given array." | loader request reqName | loader := HTTPLoader default. segments := anArray collect:[:name | reqName := (FileDirectory extensionFor: name) isEmpty ifTrue: [FileDirectory fileName: name extension: ImageSegment compressedFileExtension] ifFalse: [name]. request := self createRequestFor: reqName in: loader. name->request]. ! ! !CodeLoader methodsFor: 'loading' stamp: 'ar 12/14/1999 14:40'! loadSourceFiles: anArray "Load all the source files in the given array." | loader request | loader := HTTPLoader default. sourceFiles := anArray collect:[:name| request := self createRequestFor: name in: loader. request]. ! ! !CodeLoader methodsFor: 'private' stamp: 'mir 2/2/2001 14:44'! createRequestFor: name in: aLoader "Create a URL request for the given string, which can be cached locally." | request | request := HTTPLoader httpRequestClass for: self baseURL , name in: aLoader. aLoader addRequest: request. "fetch from URL" ^request! ! !CodeLoader methodsFor: 'private' stamp: 'avi 4/30/2004 01:40'! httpRequestClass ^HTTPDownloadRequest! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CodeLoader class instanceVariableNames: ''! !CodeLoader class methodsFor: 'accessing' stamp: 'mir 1/11/2000 13:45'! defaultBaseURL ^DefaultBaseURL ifNil: ['']! ! !CodeLoader class methodsFor: 'accessing' stamp: 'mir 1/11/2000 13:45'! defaultBaseURL: aURLString DefaultBaseURL := aURLString! ! !CodeLoader class methodsFor: 'accessing' stamp: 'ar 12/22/1999 15:08'! defaultKey "Return the default key used for verifying signatures of loaded code" ^DefaultKey! ! !CodeLoader class methodsFor: 'accessing' stamp: 'mir 1/10/2000 18:16'! defaultKey: aPublicKey "Store the default key used for verifying signatures of loaded code" DefaultKey := aPublicKey "CodeLoader defaultKey: DOLPublicKey" "CodeLoader defaultKey: (DigitalSignatureAlgorithm testKeySet at: 2)"! ! !CodeLoader class methodsFor: 'utilities' stamp: 'mir 9/6/2000 15:03'! compressFileNamed: aFileName self compressFileNamed: aFileName in: FileDirectory default! ! !CodeLoader class methodsFor: 'utilities' stamp: 'mir 10/13/2000 13:27'! compressFileNamed: aFileName in: aDirectory "Compress the currently selected file" | zipped buffer unzipped zipFileName | unzipped := aDirectory readOnlyFileNamed: (aDirectory fullNameFor: aFileName). unzipped binary. zipFileName := aFileName copyUpToLast: $. . zipped := aDirectory newFileNamed: (zipFileName, FileDirectory dot, ImageSegment compressedFileExtension). zipped binary. zipped := GZipWriteStream on: zipped. buffer := ByteArray new: 50000. 'Compressing ', zipFileName displayProgressAt: Sensor cursorPoint from: 0 to: unzipped size during:[:bar| [unzipped atEnd] whileFalse:[ bar value: unzipped position. zipped nextPutAll: (unzipped nextInto: buffer)]. zipped close. unzipped close]. ! ! !CodeLoader class methodsFor: 'utilities' stamp: 'mir 1/18/2000 16:22'! exportCategories: catList to: aFileName "CodeLoader exportCategories: #( 'Game-Animation' 'Game-Framework' ) to: 'Game-Framework'" | list classList | classList := OrderedCollection new. catList do: [:catName | list := SystemOrganization listAtCategoryNamed: catName asSymbol. list do: [:nm | classList add: (Smalltalk at: nm); add: (Smalltalk at: nm) class]]. self exportCodeSegment: aFileName classes: classList keepSource: true! ! !CodeLoader class methodsFor: 'utilities' stamp: 'mir 1/18/2000 20:53'! exportCategoryNamed: catName "CodeLoader exportCategoryNamed: 'OceanicPanic' " | list | list := SystemOrganization listAtCategoryNamed: catName asSymbol. self exportClassesNamed: list to: catName! ! !CodeLoader class methodsFor: 'utilities' stamp: 'mir 1/18/2000 20:53'! exportClassesNamed: classNameList to: aFileName | classList | classList := OrderedCollection new. classNameList do: [:nm | classList add: (Smalltalk at: nm); add: (Smalltalk at: nm) class]. self exportCodeSegment: aFileName classes: classList keepSource: true! ! !CodeLoader class methodsFor: 'utilities' stamp: 'eem 7/1/2009 13:51'! exportCodeSegment: exportName classes: aClassList keepSource: keepSources "Code for writing out a specific category of classes as an external image segment. Perhaps this should be a method." | is oldMethods newMethods classList symbolHolder fileName | keepSources ifTrue: [ self confirm: 'We are going to abandon sources. Quit without saving after this has run.' orCancel: [^self]]. classList := aClassList asArray. "Strong pointers to symbols" symbolHolder := Symbol allInstances. oldMethods := OrderedCollection new: classList size * 150. newMethods := OrderedCollection new: classList size * 150. keepSources ifTrue: [ classList do: [:cl | cl selectors do: [:selector | | m oldCodeString methodNode | m := cl compiledMethodAt: selector. m fileIndex > 0 ifTrue: [oldCodeString := cl sourceCodeAt: selector. methodNode := cl compilerClass new parse: oldCodeString in: cl notifying: nil. oldMethods addLast: m. newMethods addLast: (m copyWithTempsFromMethodNode: methodNode)]]]]. oldMethods asArray elementsExchangeIdentityWith: newMethods asArray. oldMethods := newMethods := nil. Smalltalk garbageCollect. is := ImageSegment new copyFromRootsForExport: classList. "Classes and MetaClasses" fileName := FileDirectory fileName: exportName extension: ImageSegment fileExtension. is writeForExport: fileName. self compressFileNamed: fileName ! ! !CodeLoader class methodsFor: 'utilities' stamp: 'mir 10/12/2000 17:39'! loadCode: codeSegmentName from: baseURL ifClassNotLoaded: testClass CodeLoader defaultBaseURL: baseURL. (Smalltalk includesKey: testClass) ifFalse: [CodeLoader loadCodeSegment: codeSegmentName]. ! ! !CodeLoader class methodsFor: 'utilities' stamp: 'mir 2/2/2001 14:56'! loadCodeSegment: segmentName | loader | loader := self new. loader loadSegments: (Array with: segmentName). loader installSegments.! ! !CodeLoader class methodsFor: 'utilities' stamp: 'asm 12/6/2002 08:11'! signFile: fileName renameAs: destFile key: privateKey dsa: dsa "Sign the given file using the private key." | in out | in := FileStream readOnlyFileNamed: fileName. in binary. out := FileStream newFileNamed: destFile. out binary. [in atEnd] whileFalse:[out nextPutAll: (in next: 4096)]. in close. out close. FileDirectory activeDirectoryClass splitName: destFile to:[:path :file| SecurityManager default signFile: file directory: (FileDirectory on: path). ]. ! ! !CodeLoader class methodsFor: 'utilities' stamp: 'mir 2/14/2000 16:47'! signFiles: fileNames in: dirName key: privateKey "Sign the files in the current directory and put them into a folder signed." | newNames oldNames | oldNames := fileNames collect:[:fileName | dirName , FileDirectory slash, fileName]. newNames := fileNames collect:[:fileName | dirName , FileDirectory slash, 'signed', FileDirectory slash, fileName]. CodeLoader signFilesFrom: oldNames to: newNames key: privateKey! ! !CodeLoader class methodsFor: 'utilities' stamp: 'mir 1/18/2000 18:49'! signFiles: fileNames key: privateKey "Sign the files in the current directory and put them into a folder signed." | newNames | newNames := fileNames collect:[:fileName | 'signed', FileDirectory slash, fileName]. CodeLoader signFilesFrom: fileNames to: newNames key: privateKey! ! !CodeLoader class methodsFor: 'utilities' stamp: 'ads 7/31/2003 14:00'! signFilesFrom: sourceNames to: destNames key: privateKey "Sign all the given files using the private key. This will add an 's' to the extension of the file." "| fd oldNames newNames | fd := FileDirectory default directoryNamed:'unsigned'. oldNames := fd fileNames. newNames := oldNames collect:[:name| 'signed', FileDirectory slash, name]. oldNames := oldNames collect:[:name| 'unsigned', FileDirectory slash, name]. CodeLoader signFilesFrom: oldNames to: newNames key: DOLPrivateKey." | dsa | dsa := DigitalSignatureAlgorithm new. dsa initRandomNonInteractively. 'Signing files...' displayProgressAt: Sensor cursorPoint from: 1 to: sourceNames size during:[:bar| 1 to: sourceNames size do:[:i| bar value: i. self signFile: (sourceNames at: i) renameAs: (destNames at: i) key: privateKey dsa: dsa]]. ! ! !CodeLoader class methodsFor: 'utilities' stamp: 'ar 2/6/2001 19:17'! verifySignedFileNamed: aFileName "CodeLoader verifySignedFileNamed: 'signed\dummy1.dsq' " | secured signedFileStream | signedFileStream := FileStream fileNamed: aFileName. secured := SecurityManager default positionToSecureContentsOf: signedFileStream. signedFileStream close. Transcript show: aFileName , ' verified: '; show: secured printString; cr. ! ! ModelExtension subclass: #CodeModelExtension instanceVariableNames: 'perClassCache' classVariableNames: '' poolDictionaries: '' category: 'Traits-LocalSends'! !CodeModelExtension methodsFor: 'access to cache' stamp: 'dvf 9/6/2005 15:29'! cacheFor: aClass ^perClassCache at: aClass ifAbsentPut: [self newCacheFor: aClass]! ! !CodeModelExtension methodsFor: 'access to cache' stamp: 'dvf 9/1/2005 21:17'! clearOut: aClass ^perClassCache removeKey: aClass ifAbsent: []! ! !CodeModelExtension methodsFor: 'access to cache' stamp: 'dvf 9/5/2005 14:20'! for: aClass | newSendCache | ^perClassCache at: aClass ifAbsent: [newSendCache := self newCacheFor: aClass. (self haveInterestsIn: aClass) ifTrue: [perClassCache at: aClass put: newSendCache]. newSendCache]! ! !CodeModelExtension methodsFor: 'access to cache' stamp: 'dvf 9/1/2005 21:18'! initialize super initialize. perClassCache := IdentityDictionary new.! ! !CodeModelExtension methodsFor: 'invalidation' stamp: 'dvf 1/31/2006 23:38'! classChanged: modificationEvent "We dont want to provide an out of date reply" modificationEvent itemClass ifNil: [self]. self clearOut: modificationEvent itemClass ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CodeModelExtension class instanceVariableNames: ''! !CodeModelExtension class methodsFor: 'initialization' stamp: 'dvf 9/2/2005 12:20'! isAbstract ^self == CodeModelExtension! ! SystemWindow subclass: #CollapsedMorph instanceVariableNames: 'uncollapsedMorph' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Windows'! !CollapsedMorph methodsFor: 'collapse/expand' stamp: 'sw 5/9/2000 00:18'! beReplacementFor: aMorph | itsWorld priorPosition | (itsWorld := aMorph world) ifNil: [^self]. uncollapsedMorph := aMorph. self setLabel: aMorph externalName. aMorph delete. itsWorld addMorphFront: self. self collapseOrExpand. (priorPosition := aMorph valueOfProperty: #collapsedPosition ifAbsent: [nil]) ifNotNil: [self position: priorPosition]. ! ! !CollapsedMorph methodsFor: 'collapse/expand' stamp: 'sw 4/9/2001 14:23'! uncollapseToHand "Hand the uncollapsedMorph to the user, placing it in her hand, after remembering appropriate state for possible future use" | nakedMorph | nakedMorph := uncollapsedMorph. uncollapsedMorph := nil. nakedMorph setProperty: #collapsedPosition toValue: self position. mustNotClose := false. "so the delete will succeed" self delete. ActiveHand attachMorph: nakedMorph! ! !CollapsedMorph methodsFor: 'menu' stamp: 'dgd 8/30/2003 16:41'! buildWindowMenu "Answer the menu to be put up in response to the user's clicking on the window-menu control in the window title. Specialized for CollapsedMorphs." | aMenu | aMenu := MenuMorph new defaultTarget: self. aMenu add: 'change name...' translated action: #relabel. aMenu addLine. aMenu add: 'send to back' translated action: #sendToBack. aMenu add: 'make next-to-topmost' translated action: #makeSecondTopmost. aMenu addLine. self mustNotClose ifFalse: [aMenu add: 'make unclosable' translated action: #makeUnclosable] ifTrue: [aMenu add: 'make closable' translated action: #makeClosable]. aMenu add: (self isSticky ifTrue: ['make draggable'] ifFalse: ['make undraggable']) translated action: #toggleStickiness. ^aMenu! ! !CollapsedMorph methodsFor: 'resize/collapse' stamp: 'sw 9/1/2000 11:07'! collapseOrExpand "Toggle the expand/collapsd state of the receiver. If expanding, copy the window title back to the name of the expanded morph" | aWorld | isCollapsed ifTrue: [uncollapsedMorph setProperty: #collapsedPosition toValue: self position. labelString ifNotNil: [uncollapsedMorph setNameTo: labelString]. mustNotClose := false. "We're not closing but expanding" self delete. (aWorld := self currentWorld) addMorphFront: uncollapsedMorph. aWorld startSteppingSubmorphsOf: uncollapsedMorph] ifFalse: [super collapseOrExpand]! ! !CollapsedMorph methodsFor: 'resize/collapse' stamp: 'sw 6/5/2001 22:55'! wantsExpandBox "Answer whether I'd like an expand box" ^ false! ! Object subclass: #Collection instanceVariableNames: '' classVariableNames: 'MutexForPicking RandomForPicking' poolDictionaries: '' category: 'Collections-Abstract'! !Collection commentStamp: '' prior: 0! I am the abstract superclass of all classes that represent a group of elements.! !Collection methodsFor: '*morphic-objectmenu' stamp: 'wiz 7/20/2004 13:06'! asKnownNameMenu "Return a menu to select an element of the collection. Menu uses the knownName or class name as only description of element." | menu | menu := CustomMenu new. self do: [:m | menu add: (m knownName ifNil: [m class name asString]) action: m]. ^ menu! ! !Collection methodsFor: '*packageinfo-base' stamp: 'ab 9/30/2002 19:26'! gather: aBlock ^ Array streamContents: [:stream | self do: [:ea | stream nextPutAll: (aBlock value: ea)]]! ! !Collection methodsFor: '*services-base' stamp: 'rr 3/21/2006 11:59'! chooseOne: caption "pops up a menu asking for one of the elements in the collection. If none is chosen, raises a ServiceCancelled notification" | m | m := MenuMorph entitled: caption. self do: [:ea | m add: ea target: [:n | ^ n] selector: #value: argument: ea]. m invokeModal. ServiceCancelled signal! ! !Collection methodsFor: 'accessing' stamp: 'sma 5/12/2000 11:33'! anyOne "Answer a representative sample of the receiver. This method can be helpful when needing to preinfer the nature of the contents of semi-homogeneous collections." self emptyCheck. self do: [:each | ^ each]! ! !Collection methodsFor: 'accessing' stamp: 'sd 11/4/2003 22:05'! atRandom "Answer a random element of the receiver. Uses a shared random number generator owned by class Collection. If you use this a lot, define your own instance of Random and use #atRandom:. Causes an error if self has no elements." ^ self class mutexForPicking critical: [ self atRandom: self class randomForPicking ] "Examples: #('one' 'or' 'the' 'other') atRandom (1 to: 10) atRandom 'Just pick one of these letters at random' atRandom #(3 7 4 9 21) asSet atRandom (just to show it also works for Sets) "! ! !Collection methodsFor: 'accessing' stamp: 'damiencassou 4/13/2009 12:02'! atRandom: aGenerator "Answer a random element of the receiver. Uses aGenerator which     should be kept by the user in a variable and used every time. Use     this instead of #atRandom for better uniformity of random numbers because only you use the generator. Causes an error if self has no elements." | rand index | self emptyCheck. rand := aGenerator nextInt: self size. index := 1. self do: [:each | index == rand ifTrue: [^each]. index := index + 1]. ^ self errorEmptyCollection ! ! !Collection methodsFor: 'accessing' stamp: 'sma 5/12/2000 11:41'! capacity "Answer the current capacity of the receiver." ^ self size! ! !Collection methodsFor: 'accessing' stamp: 'sma 5/12/2000 11:34'! size "Answer how many elements the receiver contains." | tally | tally := 0. self do: [:each | tally := tally + 1]. ^ tally! ! !Collection methodsFor: 'adapting' stamp: 'di 11/6/1998 13:34'! adaptToCollection: rcvr andSend: selector "If I am involved in arithmetic with another Collection, return a Collection of the results of each element combined with the scalar in that expression." rcvr isSequenceable & self isSequenceable ifFalse: [self error: 'Only sequenceable collections may be combined arithmetically']. ^ rcvr with: self collect: [:rcvrElement :myElement | rcvrElement perform: selector with: myElement]! ! !Collection methodsFor: 'adapting' stamp: 'mk 10/27/2003 21:48'! adaptToComplex: rcvr andSend: selector "If I am involved in arithmetic with a scalar, return a Collection of the results of each element combined with the scalar in that expression." ^ self collect: [:element | rcvr perform: selector with: element]! ! !Collection methodsFor: 'adapting' stamp: 'di 11/9/1998 12:16'! adaptToNumber: rcvr andSend: selector "If I am involved in arithmetic with a scalar, return a Collection of the results of each element combined with the scalar in that expression." ^ self collect: [:element | rcvr perform: selector with: element]! ! !Collection methodsFor: 'adapting' stamp: 'di 11/6/1998 13:37'! adaptToPoint: rcvr andSend: selector "If I am involved in arithmetic with a scalar, return a Collection of the results of each element combined with the scalar in that expression." ^ self collect: [:element | rcvr perform: selector with: element]! ! !Collection methodsFor: 'adapting' stamp: 'di 11/6/1998 13:37'! adaptToString: rcvr andSend: selector "If I am involved in arithmetic with a String, convert it to a Number." ^ rcvr asNumber perform: selector with: self! ! !Collection methodsFor: 'adding'! add: newObject "Include newObject as one of the receiver's elements. Answer newObject. ArrayedCollections cannot respond to this message." self subclassResponsibility! ! !Collection methodsFor: 'adding' stamp: 'sma 5/12/2000 17:21'! add: newObject withOccurrences: anInteger "Add newObject anInteger times to the receiver. Answer newObject." anInteger timesRepeat: [self add: newObject]. ^ newObject! ! !Collection methodsFor: 'adding' stamp: 'sma 5/12/2000 17:26'! addAll: aCollection "Include all the elements of aCollection as the receiver's elements. Answer aCollection. Actually, any object responding to #do: can be used as argument." aCollection do: [:each | self add: each]. ^ aCollection! ! !Collection methodsFor: 'adding' stamp: 'sma 5/12/2000 17:23'! addIfNotPresent: anObject "Include anObject as one of the receiver's elements, but only if there is no such element already. Anwser anObject." (self includes: anObject) ifFalse: [self add: anObject]. ^ anObject! ! !Collection methodsFor: 'arithmetic' stamp: 'G.C 10/23/2008 10:12'! * arg ^ arg adaptToCollection: self andSend: #*! ! !Collection methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:53'! + arg ^ arg adaptToCollection: self andSend: #+! ! !Collection methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:53'! - arg ^ arg adaptToCollection: self andSend: #-! ! !Collection methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:53'! / arg ^ arg adaptToCollection: self andSend: #/! ! !Collection methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:54'! // arg ^ arg adaptToCollection: self andSend: #//! ! !Collection methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:54'! \\ arg ^ arg adaptToCollection: self andSend: #\\! ! !Collection methodsFor: 'arithmetic' stamp: 'raok 10/22/2002 00:17'! raisedTo: arg ^ arg adaptToCollection: self andSend: #raisedTo:! ! !Collection methodsFor: 'comparing' stamp: 'SqR 8/3/2000 13:36'! hash "Answer an integer hash value for the receiver such that, -- the hash value of an unchanged object is constant over time, and -- two equal objects have equal hash values" | hash | hash := self species hash. self size <= 10 ifTrue: [self do: [:elem | hash := hash bitXor: elem hash]]. ^hash bitXor: self size hash! ! !Collection methodsFor: 'converting' stamp: 'sma 5/6/2000 20:22'! asArray "Answer an Array whose elements are the elements of the receiver. Implementation note: Cannot use ''Array withAll: self'' as that only works for SequenceableCollections which support the replacement primitive." | array index | array := Array new: self size. index := 0. self do: [:each | array at: (index := index + 1) put: each]. ^ array! ! !Collection methodsFor: 'converting' stamp: 'sma 5/6/2000 20:10'! asBag "Answer a Bag whose elements are the elements of the receiver." ^ Bag withAll: self! ! !Collection methodsFor: 'converting' stamp: 'sma 5/6/2000 20:22'! asByteArray "Answer a ByteArray whose elements are the elements of the receiver. Implementation note: Cannot use ''ByteArray withAll: self'' as that only works for SequenceableCollections which support the replacement primitive." | array index | array := ByteArray new: self size. index := 0. self do: [:each | array at: (index := index + 1) put: each]. ^ array! ! !Collection methodsFor: 'converting' stamp: 'sma 5/6/2000 20:26'! asCharacterSet "Answer a CharacterSet whose elements are the unique elements of the receiver. The reciever should only contain characters." ^ CharacterSet newFrom: self! ! !Collection methodsFor: 'converting' stamp: 'ar 9/22/2000 10:12'! asIdentitySet ^(IdentitySet new: self size) addAll: self; yourself! ! !Collection methodsFor: 'converting' stamp: 'sma 5/12/2000 17:43'! asOrderedCollection "Answer an OrderedCollection whose elements are the elements of the receiver. The order in which elements are added depends on the order in which the receiver enumerates its elements. In the case of unordered collections, the ordering is not necessarily the same for multiple requests for the conversion." ^ self as: OrderedCollection! ! !Collection methodsFor: 'converting' stamp: 'sma 5/6/2000 20:29'! asSet "Answer a Set whose elements are the unique elements of the receiver." ^ Set withAll: self! ! !Collection methodsFor: 'converting' stamp: 'LC 6/18/2001 18:46'! asSkipList: aSortBlock "Answer a SkipList whose elements are the elements of the receiver. The sort order is defined by the argument, aSortBlock." | skipList | skipList := SortedCollection new: self size. skipList sortBlock: aSortBlock. skipList addAll: self. ^ skipList! ! !Collection methodsFor: 'converting'! asSortedArray "Return a copy of the receiver in sorted order, as an Array. 6/10/96 sw" ^ self asSortedCollection asArray! ! !Collection methodsFor: 'converting' stamp: 'sma 5/12/2000 17:44'! asSortedCollection "Answer a SortedCollection whose elements are the elements of the receiver. The sort order is the default less than or equal." ^ self as: SortedCollection! ! !Collection methodsFor: 'converting' stamp: 'sma 5/12/2000 17:46'! asSortedCollection: aSortBlock "Answer a SortedCollection whose elements are the elements of the receiver. The sort order is defined by the argument, aSortBlock." | aSortedCollection | aSortedCollection := SortedCollection new: self size. aSortedCollection sortBlock: aSortBlock. aSortedCollection addAll: self. ^ aSortedCollection! ! !Collection methodsFor: 'copying' stamp: 'al 12/12/2003 14:31'! , aCollection ^self copy addAll: aCollection; yourself! ! !Collection methodsFor: 'copying' stamp: 'sma 5/12/2000 14:41'! copyWith: newElement "Answer a new collection with newElement added (as last element if sequenceable)." ^ self copy add: newElement; yourself! ! !Collection methodsFor: 'copying' stamp: 'ar 2/11/2001 01:55'! copyWithDependent: newElement "Answer a new collection with newElement added (as last element if sequenceable)." ^self copyWith: newElement! ! !Collection methodsFor: 'copying' stamp: 'sma 5/12/2000 14:43'! copyWithout: oldElement "Answer a copy of the receiver that does not contain any elements equal to oldElement." ^ self reject: [:each | each = oldElement] "Examples: 'fred the bear' copyWithout: $e #(2 3 4 5 5 6) copyWithout: 5 "! ! !Collection methodsFor: 'copying' stamp: 'sma 5/12/2000 18:08'! copyWithoutAll: aCollection "Answer a copy of the receiver that does not contain any elements equal to those in aCollection." ^ self reject: [:each | aCollection includes: each]! ! !Collection methodsFor: 'enumerating' stamp: 'sma 4/30/2000 11:17'! allSatisfy: aBlock "Evaluate aBlock with the elements of the receiver. If aBlock returns false for any element return false. Otherwise return true." self do: [:each | (aBlock value: each) ifFalse: [^ false]]. ^ true! ! !Collection methodsFor: 'enumerating' stamp: 'sma 4/30/2000 11:17'! anySatisfy: aBlock "Evaluate aBlock with the elements of the receiver. If aBlock returns true for any element return true. Otherwise return false." self do: [:each | (aBlock value: each) ifTrue: [^ true]]. ^ false! ! !Collection methodsFor: 'enumerating'! associationsDo: aBlock "Evaluate aBlock for each of the receiver's elements (key/value associations). If any non-association is within, the error is not caught now, but later, when a key or value message is sent to it." self do: aBlock! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 11:45'! collect: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Collect the resulting values into a collection like the receiver. Answer the new collection." | newCollection | newCollection := self species new. self do: [:each | newCollection add: (aBlock value: each)]. ^ newCollection! ! !Collection methodsFor: 'enumerating' stamp: 'dgd 9/13/2004 23:42'! collect: collectBlock thenDo: doBlock "Utility method to improve readability." ^ (self collect: collectBlock) do: doBlock! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 11:51'! collect: collectBlock thenSelect: selectBlock "Utility method to improve readability." ^ (self collect: collectBlock) select: selectBlock! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 11:52'! count: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Answer the number of elements that answered true." | sum | sum := 0. self do: [:each | (aBlock value: each) ifTrue: [sum := sum + 1]]. ^ sum! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 11:20'! detect: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Answer the first element for which aBlock evaluates to true." ^ self detect: aBlock ifNone: [self errorNotFound: aBlock]! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 11:52'! detect: aBlock ifNone: exceptionBlock "Evaluate aBlock with each of the receiver's elements as the argument. Answer the first element for which aBlock evaluates to true. If none evaluate to true, then evaluate the argument, exceptionBlock." self do: [:each | (aBlock value: each) ifTrue: [^ each]]. ^ exceptionBlock value! ! !Collection methodsFor: 'enumerating'! detectMax: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Answer the element for which aBlock evaluates to the highest magnitude. If collection empty, return nil. This method might also be called elect:." | maxElement maxValue val | self do: [:each | maxValue == nil ifFalse: [ (val := aBlock value: each) > maxValue ifTrue: [ maxElement := each. maxValue := val]] ifTrue: ["first element" maxElement := each. maxValue := aBlock value: each]. "Note that there is no way to get the first element that works for all kinds of Collections. Must test every one."]. ^ maxElement! ! !Collection methodsFor: 'enumerating'! detectMin: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Answer the element for which aBlock evaluates to the lowest number. If collection empty, return nil." | minElement minValue val | self do: [:each | minValue == nil ifFalse: [ (val := aBlock value: each) < minValue ifTrue: [ minElement := each. minValue := val]] ifTrue: ["first element" minElement := each. minValue := aBlock value: each]. "Note that there is no way to get the first element that works for all kinds of Collections. Must test every one."]. ^ minElement! ! !Collection methodsFor: 'enumerating'! detectSum: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Return the sum of the answers." | sum | sum := 0. self do: [:each | sum := (aBlock value: each) + sum]. ^ sum! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 17:52'! difference: aCollection "Answer the set theoretic difference of two collections." ^ self reject: [:each | aCollection includes: each]! ! !Collection methodsFor: 'enumerating'! do: aBlock "Evaluate aBlock with each of the receiver's elements as the argument." self subclassResponsibility! ! !Collection methodsFor: 'enumerating' stamp: 'md 7/22/2005 16:26'! do: aBlock displayingProgress: aString aString displayProgressAt: Sensor cursorPoint from: 0 to: self size during: [:bar | self inject: 1 into: [:index :each | bar value: index. aBlock value: each. index + 1]]! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 11:57'! do: elementBlock separatedBy: separatorBlock "Evaluate the elementBlock for all elements in the receiver, and evaluate the separatorBlock between." | beforeFirst | beforeFirst := true. self do: [:each | beforeFirst ifTrue: [beforeFirst := false] ifFalse: [separatorBlock value]. elementBlock value: each]! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 11:59'! do: aBlock without: anItem "Enumerate all elements in the receiver. Execute aBlock for those elements that are not equal to the given item" ^ self do: [:each | anItem = each ifFalse: [aBlock value: each]]! ! !Collection methodsFor: 'enumerating' stamp: 'yo 8/27/2008 23:45'! explorerContents ^self explorerContentsWithIndexCollect: [:value :index | ObjectExplorerWrapper with: value name: index printString model: self]! ! !Collection methodsFor: 'enumerating' stamp: 'yo 8/27/2008 23:29'! explorerContentsWithIndexCollect: twoArgBlock ^ self asOrderedCollection withIndexCollect: twoArgBlock ! ! !Collection methodsFor: 'enumerating' stamp: 'dvf 6/10/2000 18:32'! groupBy: keyBlock having: selectBlock "Like in SQL operation - Split the recievers contents into collections of elements for which keyBlock returns the same results, and return those collections allowed by selectBlock. keyBlock should return an Integer." | result key | result := PluggableDictionary integerDictionary. self do: [:e | key := keyBlock value: e. (result includesKey: key) ifFalse: [result at: key put: OrderedCollection new]. (result at: key) add: e]. ^ result := result select: selectBlock! ! !Collection methodsFor: 'enumerating'! inject: thisValue into: binaryBlock "Accumulate a running value associated with evaluating the argument, binaryBlock, with the current value of the argument, thisValue, and the receiver as block arguments. For instance, to sum the numeric elements of a collection, aCollection inject: 0 into: [:subTotal :next | subTotal + next]." | nextValue | nextValue := thisValue. self do: [:each | nextValue := binaryBlock value: nextValue value: each]. ^nextValue! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 17:52'! intersection: aCollection "Answer the set theoretic intersection of two collections." ^ self select: [:each | aCollection includes: each]! ! !Collection methodsFor: 'enumerating' stamp: 'gh 9/18/2001 15:59'! noneSatisfy: aBlock "Evaluate aBlock with the elements of the receiver. If aBlock returns false for all elements return true. Otherwise return false" self do: [:item | (aBlock value: item) ifTrue: [^ false]]. ^ true! ! !Collection methodsFor: 'enumerating'! reject: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Collect into a new collection like the receiver only those elements for which aBlock evaluates to false. Answer the new collection." ^self select: [:element | (aBlock value: element) == false]! ! !Collection methodsFor: 'enumerating' stamp: 'dgd 9/13/2004 23:42'! reject: rejectBlock thenDo: doBlock "Utility method to improve readability." ^ (self reject: rejectBlock) do: doBlock! ! !Collection methodsFor: 'enumerating'! select: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Collect into a new collection like the receiver, only those elements for which aBlock evaluates to true. Answer the new collection." | newCollection | newCollection := self species new. self do: [:each | (aBlock value: each) ifTrue: [newCollection add: each]]. ^newCollection! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 11:59'! select: selectBlock thenCollect: collectBlock "Utility method to improve readability." ^ (self select: selectBlock) collect: collectBlock! ! !Collection methodsFor: 'enumerating' stamp: 'hfm 2/12/2009 13:38'! select: selectBlock thenDo: doBlock "Utility method to improve readability. Do not create the intermediate collection." self do: [: each | ( selectBlock value: each ) ifTrue: [ doBlock value: each ] ].! ! !Collection methodsFor: 'enumerating' stamp: 'sma 5/12/2000 17:54'! union: aCollection "Answer the set theoretic union of two collections." ^ self asSet addAll: aCollection; yourself! ! !Collection methodsFor: 'filter streaming' stamp: 'sma 5/12/2000 12:07'! contents ^ self! ! !Collection methodsFor: 'filter streaming' stamp: 'sma 5/12/2000 12:08'! flattenOnStream: aStream ^ aStream writeCollection: self! ! !Collection methodsFor: 'filter streaming' stamp: 'sma 5/12/2000 12:07'! write: anObject ^ self add: anObject! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:51'! abs "Absolute value of all elements in the collection" ^ self collect: [:a | a abs]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:20'! arcCos ^self collect: [:each | each arcCos]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:20'! arcSin ^self collect: [:each | each arcSin]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:20'! arcTan ^self collect: [:each | each arcTan]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:57'! average ^ self sum / self size! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:51'! ceiling ^ self collect: [:a | a ceiling]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:20'! cos ^self collect: [:each | each cos]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:20'! degreeCos ^self collect: [:each | each degreeCos]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:21'! degreeSin ^self collect: [:each | each degreeSin]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:21'! exp ^self collect: [:each | each exp]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:51'! floor ^ self collect: [:a | a floor]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:21'! ln ^self collect: [:each | each ln]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:52'! log ^ self collect: [:each | each log]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:58'! max ^ self inject: self anyOne into: [:max :each | max max: each]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 16:00'! median ^ self asSortedCollection median! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 16:00'! min ^ self inject: self anyOne into: [:min :each | min min: each]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:52'! negated "Negated value of all elements in the collection" ^ self collect: [:a | a negated]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 16:00'! range ^ self max - self min! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:53'! reciprocal "Return the reciever full of reciprocated elements" ^ self collect: [:a | a reciprocal]! ! !Collection methodsFor: 'math functions' stamp: 'nk 12/30/2003 15:47'! roundTo: quantum ^self collect: [ :ea | ea roundTo: quantum ]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:53'! rounded ^ self collect: [:a | a rounded]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:23'! sign ^self collect: [:each | each sign]! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:22'! sin ^self collect: [:each | each sin]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:53'! sqrt ^ self collect: [:each | each sqrt]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:53'! squared ^ self collect: [:each | each * each]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 16:02'! sum "This is implemented using a variant of the normal inject:into: pattern. The reason for this is that it is not known whether we're in the normal number line, i.e. whether 0 is a good initial value for the sum. Consider a collection of measurement objects, 0 would be the unitless value and would not be appropriate to add with the unit-ed objects." | sum sample | sample := self anyOne. sum := self inject: sample into: [:accum :each | accum + each]. ^ sum - sample! ! !Collection methodsFor: 'math functions' stamp: 'raok 10/22/2002 00:22'! tan ^self collect: [:each | each tan]! ! !Collection methodsFor: 'math functions' stamp: 'TAG 11/6/1998 15:54'! truncated ^ self collect: [:a | a truncated]! ! !Collection methodsFor: 'printing' stamp: 'gk 1/14/2005 08:19'! asCommaString "Return collection printed as 'a, b, c' " ^String streamContents: [:s | self asStringOn: s delimiter: ', '] ! ! !Collection methodsFor: 'printing' stamp: 'gk 1/14/2005 08:20'! asCommaStringAnd "Return collection printed as 'a, b and c' " ^String streamContents: [:s | self asStringOn: s delimiter: ', ' last: ' and '] ! ! !Collection methodsFor: 'printing' stamp: 'gk 1/14/2005 08:27'! asStringOn: aStream delimiter: delimString "Print elements on a stream separated with a delimiter String like: 'a, b, c' Uses #asString instead of #print:." self do: [:elem | aStream nextPutAll: elem asString] separatedBy: [aStream nextPutAll: delimString]! ! !Collection methodsFor: 'printing' stamp: 'gk 1/14/2005 08:27'! asStringOn: aStream delimiter: delimString last: lastDelimString "Print elements on a stream separated with a delimiter between all the elements and with a special one before the last like: 'a, b and c'. Uses #asString instead of #print: Note: Feel free to improve the code to detect the last element." | n sz | n := 1. sz := self size. self do: [:elem | n := n + 1. aStream nextPutAll: elem asString] separatedBy: [ aStream nextPutAll: (n = sz ifTrue: [lastDelimString] ifFalse: [delimString])]! ! !Collection methodsFor: 'printing' stamp: 'apb 4/21/2006 09:37'! printElementsOn: aStream "The original code used #skip:, but some streams do not support that, and we don't really need it." aStream nextPut: $(. self do: [:element | aStream print: element] separatedBy: [aStream space]. aStream nextPut: $)! ! !Collection methodsFor: 'printing' stamp: 'sma 6/1/2000 09:41'! printNameOn: aStream super printOn: aStream! ! !Collection methodsFor: 'printing' stamp: 'sma 6/1/2000 09:41'! printOn: aStream "Append a sequence of characters that identify the receiver to aStream." self printNameOn: aStream. self printElementsOn: aStream! ! !Collection methodsFor: 'printing' stamp: 'gk 1/14/2005 08:01'! printOn: aStream delimiter: delimString "Print elements on a stream separated with a delimiter String like: 'a, b, c' " self do: [:elem | aStream print: elem] separatedBy: [aStream print: delimString] ! ! !Collection methodsFor: 'printing' stamp: 'fbs 1/14/2005 10:54'! printOn: aStream delimiter: delimString last: lastDelimString "Print elements on a stream separated with a delimiter between all the elements and with a special one before the last like: 'a, b and c' Note: Feel free to improve the code to detect the last element." | n sz | n := 1. sz := self size. self do: [:elem | n := n + 1. aStream print: elem] separatedBy: [ n = sz ifTrue: [aStream print: lastDelimString] ifFalse: [aStream print: delimString]]! ! !Collection methodsFor: 'printing'! storeOn: aStream "Refer to the comment in Object|storeOn:." | noneYet | aStream nextPutAll: '(('. aStream nextPutAll: self class name. aStream nextPutAll: ' new)'. noneYet := true. self do: [:each | noneYet ifTrue: [noneYet := false] ifFalse: [aStream nextPut: $;]. aStream nextPutAll: ' add: '. aStream store: each]. noneYet ifFalse: [aStream nextPutAll: '; yourself']. aStream nextPut: $)! ! !Collection methodsFor: 'removing' stamp: 'sma 5/12/2000 11:22'! remove: oldObject "Remove oldObject from the receiver's elements. Answer oldObject unless no element is equal to oldObject, in which case, raise an error. ArrayedCollections cannot respond to this message." ^ self remove: oldObject ifAbsent: [self errorNotFound: oldObject]! ! !Collection methodsFor: 'removing' stamp: 'sma 5/12/2000 11:14'! remove: oldObject ifAbsent: anExceptionBlock "Remove oldObject from the receiver's elements. If several of the elements are equal to oldObject, only one is removed. If no element is equal to oldObject, answer the result of evaluating anExceptionBlock. Otherwise, answer the argument, oldObject. ArrayedCollections cannot respond to this message." self subclassResponsibility! ! !Collection methodsFor: 'removing' stamp: 'nice 9/14/2009 20:30'! removeAll "Remove each element from the receiver and leave it empty. ArrayedCollections cannot respond to this message. There are two good reasons why a subclass should override this message: 1) the subclass does not support being modified while being iterated 2) the subclass provides a much faster way than iterating through each element" self do: [:each | self remove: each].! ! !Collection methodsFor: 'removing' stamp: 'nice 1/10/2009 00:01'! removeAll: aCollection "Remove each element of aCollection from the receiver. If successful for each, answer aCollection. Otherwise create an error notification. ArrayedCollections cannot respond to this message." aCollection == self ifTrue: [^self removeAll]. aCollection do: [:each | self remove: each]. ^ aCollection! ! !Collection methodsFor: 'removing' stamp: 'sma 5/12/2000 11:16'! removeAllFoundIn: aCollection "Remove each element of aCollection which is present in the receiver from the receiver. Answer aCollection. No error is raised if an element isn't found. ArrayedCollections cannot respond to this message." aCollection do: [:each | self remove: each ifAbsent: []]. ^ aCollection! ! !Collection methodsFor: 'removing' stamp: 'sma 5/12/2000 11:19'! removeAllSuchThat: aBlock "Evaluate aBlock for each element and remove all that elements from the receiver for that aBlock evaluates to true. Use a copy to enumerate collections whose order changes when an element is removed (i.e. Sets)." self copy do: [:each | (aBlock value: each) ifTrue: [self remove: each]]! ! !Collection methodsFor: 'testing'! contains: aBlock "VW compatibility" ^self anySatisfy: aBlock! ! !Collection methodsFor: 'testing' stamp: 'ls 3/27/2000 17:25'! identityIncludes: anObject "Answer whether anObject is one of the receiver's elements." self do: [:each | anObject == each ifTrue: [^true]]. ^false! ! !Collection methodsFor: 'testing' stamp: 'jf 12/1/2003 15:37'! ifEmpty: aBlock "Evaluate the block if I'm empty" ^ self isEmpty ifTrue: aBlock! ! !Collection methodsFor: 'testing' stamp: 'md 10/7/2004 14:49'! ifEmpty: emptyBlock ifNotEmpty: notEmptyBlock "Evaluate emptyBlock if I'm empty, notEmptyBlock otherwise" " If the notEmptyBlock has an argument, eval with the receiver as its argument" ^ self isEmpty ifTrue: emptyBlock ifFalse: [notEmptyBlock valueWithPossibleArgument: self]! ! !Collection methodsFor: 'testing' stamp: 'md 10/7/2004 15:36'! ifEmpty: emptyBlock ifNotEmptyDo: notEmptyBlock "Evaluate emptyBlock if I'm empty, notEmptyBlock otherwise" "Evaluate the notEmptyBlock with the receiver as its argument" ^ self isEmpty ifTrue: emptyBlock ifFalse: [notEmptyBlock value: self]! ! !Collection methodsFor: 'testing' stamp: 'md 10/7/2004 14:58'! ifNotEmpty: aBlock "Evaluate the given block unless the receiver is empty. If the block has an argument, eval with the receiver as its argument, but it might be better to use ifNotEmptyDo: to make the code easier to understand" ^self isEmpty ifFalse: [aBlock valueWithPossibleArgument: self]. ! ! !Collection methodsFor: 'testing' stamp: 'md 10/7/2004 14:48'! ifNotEmpty: notEmptyBlock ifEmpty: emptyBlock "Evaluate emptyBlock if I'm empty, notEmptyBlock otherwise If the notEmptyBlock has an argument, eval with the receiver as its argument" ^ self isEmpty ifFalse: [notEmptyBlock valueWithPossibleArgument: self] ifTrue: emptyBlock! ! !Collection methodsFor: 'testing' stamp: 'md 10/7/2004 14:28'! ifNotEmptyDo: aBlock "Evaluate the given block with the receiver as its argument." ^self isEmpty ifFalse: [aBlock value: self]. ! ! !Collection methodsFor: 'testing' stamp: 'md 10/7/2004 15:36'! ifNotEmptyDo: notEmptyBlock ifEmpty: emptyBlock "Evaluate emptyBlock if I'm empty, notEmptyBlock otherwise Evaluate the notEmptyBlock with the receiver as its argument" ^ self isEmpty ifFalse: [notEmptyBlock value: self] ifTrue: emptyBlock! ! !Collection methodsFor: 'testing' stamp: 'sma 5/12/2000 14:07'! includes: anObject "Answer whether anObject is one of the receiver's elements." ^ self anySatisfy: [:each | each = anObject]! ! !Collection methodsFor: 'testing'! includesAllOf: aCollection "Answer whether all the elements of aCollection are in the receiver." aCollection do: [:elem | (self includes: elem) ifFalse: [^ false]]. ^ true! ! !Collection methodsFor: 'testing'! includesAnyOf: aCollection "Answer whether any element of aCollection is one of the receiver's elements." aCollection do: [:elem | (self includes: elem) ifTrue: [^ true]]. ^ false! ! !Collection methodsFor: 'testing' stamp: 'nk 8/30/2004 07:49'! includesSubstringAnywhere: testString "Answer whether the receiver includes, anywhere in its nested structure, a string that has testString as a substring" self do: [:element | (element isString) ifTrue: [(element includesSubString: testString) ifTrue: [^ true]]. (element isCollection) ifTrue: [(element includesSubstringAnywhere: testString) ifTrue: [^ true]]]. ^ false "#(first (second third) ((allSentMessages ('Elvis' includes:)))) includesSubstringAnywhere: 'lvi'"! ! !Collection methodsFor: 'testing' stamp: 'ar 8/17/1999 19:43'! isCollection "Return true if the receiver is some sort of Collection and responds to basic collection messages such as #size and #do:" ^true! ! !Collection methodsFor: 'testing'! isEmpty "Answer whether the receiver contains any elements." ^self size = 0! ! !Collection methodsFor: 'testing' stamp: 'bf 3/10/2000 09:29'! isEmptyOrNil "Answer whether the receiver contains any elements, or is nil. Useful in numerous situations where one wishes the same reaction to an empty collection or to nil" ^ self isEmpty! ! !Collection methodsFor: 'testing' stamp: 'di 11/6/1998 09:16'! isSequenceable ^ false! ! !Collection methodsFor: 'testing' stamp: 'sma 5/12/2000 17:49'! notEmpty "Answer whether the receiver contains any elements." ^ self isEmpty not! ! !Collection methodsFor: 'testing'! occurrencesOf: anObject "Answer how many of the receiver's elements are equal to anObject." | tally | tally := 0. self do: [:each | anObject = each ifTrue: [tally := tally + 1]]. ^tally! ! !Collection methodsFor: 'private'! emptyCheck self isEmpty ifTrue: [self errorEmptyCollection]! ! !Collection methodsFor: 'private'! errorEmptyCollection self error: 'this collection is empty'! ! !Collection methodsFor: 'private'! errorNoMatch self error: 'collection sizes do not match'! ! !Collection methodsFor: 'private' stamp: 'sma 5/12/2000 11:22'! errorNotFound: anObject "Actually, this should raise a special Exception not just an error." self error: 'Object is not in the collection.'! ! !Collection methodsFor: 'private' stamp: 'yo 6/29/2004 13:14'! errorNotKeyed self error: ('Instances of {1} do not respond to keyed accessing messages.' translated format: {self class name}) ! ! !Collection methodsFor: 'private'! toBraceStack: itsSize "Push receiver's elements onto the stack of thisContext sender. Error if receiver does not have itsSize elements or if receiver is unordered. Do not call directly: this is called by {a. b} := ... constructs." self size ~= itsSize ifTrue: [self error: 'Trying to store ', self size printString, ' values into ', itsSize printString, ' variables.']. thisContext sender push: itsSize fromIndexable: self! ! !Collection methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 07:12'! isZero "Answer whether the receiver is zero" self deprecated: 'You should not use this method.'. ^ false! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Collection class instanceVariableNames: ''! !Collection class methodsFor: 'instance creation' stamp: 'apb 10/15/2000 22:05'! ofSize: n "Create a new collection of size n with nil as its elements. This method exists because OrderedCollection new: n creates an empty collection, not one of size n." ^ self new: n! ! !Collection class methodsFor: 'instance creation' stamp: 'sma 5/6/2000 19:58'! with: anObject "Answer an instance of me containing anObject." ^ self new add: anObject; yourself! ! !Collection class methodsFor: 'instance creation' stamp: 'sma 5/6/2000 20:01'! with: firstObject with: secondObject "Answer an instance of me containing the two arguments as elements." ^ self new add: firstObject; add: secondObject; yourself! ! !Collection class methodsFor: 'instance creation' stamp: 'sma 5/6/2000 20:03'! with: firstObject with: secondObject with: thirdObject "Answer an instance of me containing the three arguments as elements." ^ self new add: firstObject; add: secondObject; add: thirdObject; yourself! ! !Collection class methodsFor: 'instance creation' stamp: 'sma 5/6/2000 20:06'! with: firstObject with: secondObject with: thirdObject with: fourthObject "Answer an instance of me, containing the four arguments as the elements." ^ self new add: firstObject; add: secondObject; add: thirdObject; add: fourthObject; yourself! ! !Collection class methodsFor: 'instance creation' stamp: 'sma 5/6/2000 20:06'! with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject "Answer an instance of me, containing the five arguments as the elements." ^ self new add: firstObject; add: secondObject; add: thirdObject; add: fourthObject; add: fifthObject; yourself! ! !Collection class methodsFor: 'instance creation' stamp: 'sma 5/6/2000 20:06'! with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject with: sixthObject "Answer an instance of me, containing the six arguments as the elements." ^ self new add: firstObject; add: secondObject; add: thirdObject; add: fourthObject; add: fifthObject; add: sixthObject; yourself! ! !Collection class methodsFor: 'instance creation' stamp: 'sma 5/6/2000 20:07'! withAll: aCollection "Create a new collection containing all the elements from aCollection." ^ (self new: aCollection size) addAll: aCollection; yourself! ! !Collection class methodsFor: 'private' stamp: 'lr 11/4/2003 12:07'! initialize "Set up a Random number generator to be used by atRandom when the user does not feel like creating his own Random generator." RandomForPicking := Random new. MutexForPicking := Semaphore forMutualExclusion! ! !Collection class methodsFor: 'private' stamp: 'lr 11/4/2003 12:08'! mutexForPicking ^ MutexForPicking! ! !Collection class methodsFor: 'private' stamp: 'sma 5/12/2000 12:31'! randomForPicking ^ RandomForPicking! ! Object subclass: #CollectionCombinator instanceVariableNames: 'resultProcessingBlock collectionOfArrays buffer' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'! !CollectionCombinator commentStamp: '' prior: 0! For a collection of collections, enumerate all elements of the cartesian product. The code shows how recursion is used to implement variable nesting of loops. The cartesian product is usually a huge collection, that should not be kept in memory. Therefore the user of the class has to provide a block with one argument that is called each time a tuple is constructed. When possible, that block should not build a collection of all these tuples, but should immediately drop unsuitable tuples. To get a first impression, try this with 'inspect it': | result | result := OrderedCollection new. CollectionCombinator new forArrays: (OrderedCollection with: #(#a #b #c) with: #(1 2 3 4 5) with: #('v' 'w' 'x' 'y' 'z') with: #('one' 'two' 'three') ) processWith: [:item |result addLast: item]. result ! !CollectionCombinator methodsFor: 'as yet unclassified' stamp: 'BG 12/20/2001 21:33'! combineFromIdx: myIdx " this method is recursive. Recursion runs from values 1 to collectionOfArrays size of parameter myIdx. Each time it is called, this method has the responsiblity to provide all possible values for one index position of the result tuples. That index position is given by the value of myIdx." (collectionOfArrays at: myIdx) do: [:item | buffer at: myIdx put: item. myIdx = collectionOfArrays size ifTrue: [resultProcessingBlock value: buffer shallowCopy] ifFalse: [self combineFromIdx: myIdx + 1] ]. " The buffer is a shared object and its contents are later changed. It is therefore necessary to make a copy. "! ! !CollectionCombinator methodsFor: 'as yet unclassified' stamp: 'BG 12/20/2001 21:32'! forArrays: anArray processWith: aBlock " anArray is a kind of a sequenceable collection of arrays. aBlock is a block with one argument, that is used to process a tuple immediately after it is constructed. " collectionOfArrays := anArray. resultProcessingBlock := aBlock. buffer := Array new: anArray size. self combineFromIdx: 1 ! ! ClassTestCase subclass: #CollectionRootTest uses: TIterateTest + TEmptyTest + TSizeTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Abstract'! !CollectionRootTest commentStamp: 'stephane.ducasse 1/12/2009 17:41' prior: 0! I'm the root of the hierarchy of the collection tests. ! !CollectionRootTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 10:36'! collectionWithoutNilElements " return a collection that doesn't includes a nil element and that doesn't includes equal elements'" self subclassResponsibility! ! !CollectionRootTest methodsFor: 'requirements' stamp: 'damienpollet 1/30/2009 17:20'! doWithoutNumber ^ 2! ! !CollectionRootTest methodsFor: 'requirements' stamp: 'damienpollet 1/30/2009 17:32'! element ^ 3! ! !CollectionRootTest methodsFor: 'requirements' stamp: 'damienpollet 1/30/2009 17:14'! elementTwiceIn ^ 1 "12332312322"! ! !CollectionRootTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 10:36'! empty self subclassResponsibility! ! !CollectionRootTest methodsFor: 'requirements' stamp: 'damienpollet 1/21/2009 18:25'! expectedElementByDetect ^ -2! ! !CollectionRootTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 10:35'! nonEmpty self subclassResponsibility! ! !CollectionRootTest methodsFor: 'requirements'! sizeCollection "Answers a collection not empty" ^ self explicitRequirement! ! !CollectionRootTest methodsFor: 'test - fixture'! test0FixtureIterateTest | res | self shouldnt: [ self collectionWithoutNilElements ] raise: Error. self assert: ( self collectionWithoutNilElements occurrencesOf: nil) = 0. res := true. self collectionWithoutNilElements detect: [ :each | (self collectionWithoutNilElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false.! ! !CollectionRootTest methodsFor: 'tests - empty'! testIfEmpty self nonEmpty ifEmpty: [ self assert: false] . self empty ifEmpty: [ self assert: true] . ! ! !CollectionRootTest methodsFor: 'tests - empty'! testIfEmptyifNotEmpty self assert: (self empty ifEmpty: [true] ifNotEmpty: [false]). self assert: (self nonEmpty ifEmpty: [false] ifNotEmpty: [true]). ! ! !CollectionRootTest methodsFor: 'tests - empty'! testIfEmptyifNotEmptyDo "self debug #testIfEmptyifNotEmptyDo" self assert: (self empty ifEmpty: [true] ifNotEmptyDo: [:s | false]). self assert: (self nonEmpty ifEmpty: [false] ifNotEmptyDo: [:s | true]). self assert: (self nonEmpty ifEmpty: [false] ifNotEmptyDo: [:s | s]) == self nonEmpty.! ! !CollectionRootTest methodsFor: 'tests - empty'! testIfNotEmpty self empty ifNotEmpty: [self assert: false]. self nonEmpty ifNotEmpty: [self assert: true]. self assert: (self nonEmpty ifNotEmpty: [:s | s ]) = self nonEmpty ! ! !CollectionRootTest methodsFor: 'tests - empty'! testIfNotEmptyDo self empty ifNotEmptyDo: [:s | self assert: false]. self assert: (self nonEmpty ifNotEmptyDo: [:s | s]) == self nonEmpty ! ! !CollectionRootTest methodsFor: 'tests - empty'! testIfNotEmptyDoifNotEmpty self assert: (self empty ifNotEmptyDo: [:s | false] ifEmpty: [true]). self assert: (self nonEmpty ifNotEmptyDo: [:s | s] ifEmpty: [false]) == self nonEmpty! ! !CollectionRootTest methodsFor: 'tests - empty'! testIfNotEmptyifEmpty self assert: (self empty ifNotEmpty: [false] ifEmpty: [true]). self assert: (self nonEmpty ifNotEmpty: [true] ifEmpty: [false]). ! ! !CollectionRootTest methodsFor: 'tests - empty'! testIsEmpty self assert: (self empty isEmpty). self deny: (self nonEmpty isEmpty).! ! !CollectionRootTest methodsFor: 'tests - empty'! testIsEmptyOrNil self assert: (self empty isEmptyOrNil). self deny: (self nonEmpty isEmptyOrNil).! ! !CollectionRootTest methodsFor: 'tests - empty'! testNotEmpty self assert: (self nonEmpty notEmpty). self deny: (self empty notEmpty).! ! !CollectionRootTest methodsFor: 'tests - fixture'! test0FixtureEmptyTest self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty.! ! !CollectionRootTest methodsFor: 'tests - fixture'! test0TSizeTest self shouldnt: [self empty] raise: Error. self shouldnt: [self sizeCollection] raise: Error. self assert: self empty isEmpty. self deny: self sizeCollection isEmpty.! ! !CollectionRootTest methodsFor: 'tests - iterate' stamp: 'delaunay 5/14/2009 11:03'! testDoSeparatedBy | string expectedString beforeFirst | string := ''. self collectionWithoutNilElements do: [ :each | string := string , each asString ] separatedBy: [ string := string , '|' ]. expectedString := ''. beforeFirst := true. self collectionWithoutNilElements do: [ :each | beforeFirst = true ifTrue: [ beforeFirst := false ] ifFalse: [ expectedString := expectedString , '|' ]. expectedString := expectedString , each asString ]. self assert: expectedString = string! ! !CollectionRootTest methodsFor: 'tests - iterate' stamp: 'delaunay 5/14/2009 11:08'! testRejectNoReject | res collection | collection := self collectionWithoutNilElements . res := collection reject: [ :each | each isNil ]. self assert: res size = collection size! ! !CollectionRootTest methodsFor: 'tests - iterating'! testAllSatisfy | element | " when all element satisfy the condition, should return true : " self assert: ( self collectionWithoutNilElements allSatisfy: [:each | (each notNil) ] ). " when all element don't satisfy the condition, should return false : " self deny: ( self collectionWithoutNilElements allSatisfy: [:each | (each notNil) not ] ). " when only one element doesn't satisfy the condition' should return false'" element := self collectionWithoutNilElements anyOne. self deny: ( self collectionWithoutNilElements allSatisfy: [:each | (each = element) not] ).! ! !CollectionRootTest methodsFor: 'tests - iterating'! testAllSatisfyEmpty self assert: ( self empty allSatisfy: [:each | false]). ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testAnySastify | element | " when all elements satisty the condition, should return true :" self assert: ( self collectionWithoutNilElements anySatisfy: [:each | each notNil ]). " when only one element satisfy the condition, should return true :" element := self collectionWithoutNilElements anyOne. self assert: ( self collectionWithoutNilElements anySatisfy: [:each | (each = element) ] ). " when all elements don't satisty the condition, should return false :" self deny: ( self collectionWithoutNilElements anySatisfy: [:each | (each notNil) not ]). ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testBasicCollect | res index | index := 0. res := self collectionWithoutNilElements collect: [ :each | index := index + 1. each ]. res do:[:each | self assert: (self collectionWithoutNilElements occurrencesOf: each) = (res occurrencesOf: each)]. self assert: index = self collectionWithoutNilElements size. ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testBasicCollectEmpty | res | res := self empty collect: [:each | each class]. self assert: res isEmpty ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testCollectOnEmpty self assert: (self empty collect: [:e | self fail]) isEmpty! ! !CollectionRootTest methodsFor: 'tests - iterating'! testCollectThenSelectOnEmpty self assert: (self empty collect: [:e | self fail] thenSelect: [:e | self fail]) isEmpty! ! !CollectionRootTest methodsFor: 'tests - iterating'! testDetect | res element | element := self collectionWithoutNilElements anyOne . res := self collectionWithoutNilElements detect: [:each | each = element]. self assert: (res = element). ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testDetectIfNone | res element | res := self collectionWithoutNilElements detect: [:each | each notNil not] ifNone: [100]. self assert: res = 100. element := self collectionWithoutNilElements anyOne. res := self collectionWithoutNilElements detect: [:each | each = element] ifNone: [100]. self assert: res = element. ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testDo2 "dc: Bad test, it assumes that a new instance of #speciesClass allows addition with #add:. This is not the case of Interval for which species is Array." "res := self speciesClass new. self collection do: [:each | res add: each class]. self assert: res = self result. " | collection cptElementsViewed cptElementsIn | collection := self collectionWithoutNilElements. cptElementsViewed := 0. cptElementsIn := OrderedCollection new. collection do: [ :each | cptElementsViewed := cptElementsViewed + 1. " #do doesn't iterate with the same objects than those in the collection for FloatArray( I don' t know why ) . That's why I use #includes: and not #identityIncludes: '" (collection includes: each) ifTrue: [ " the collection used doesn't include equal elements. Therefore each element viewed should not have been viewed before " ( cptElementsIn includes: each ) ifFalse: [ cptElementsIn add: each ] . ]. ]. self assert: cptElementsViewed = collection size. self assert: cptElementsIn size = collection size. ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testDoWithout "self debug: #testDoWithout" | res element collection | collection := self collectionWithoutNilElements . res := OrderedCollection new. element := self collectionWithoutNilElements anyOne . collection do: [:each | res add: each] without: element . " verifying result :" self assert: res size = (collection size - (collection occurrencesOf: element)). res do: [:each | self assert: (collection occurrencesOf: each) = ( res occurrencesOf: each ) ]. ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testInjectInto |result| result:= self collectionWithoutNilElements inject: 0 into: [:inj :ele | ele notNil ifTrue: [ inj + 1 ]]. self assert: self collectionWithoutNilElements size = result .! ! !CollectionRootTest methodsFor: 'tests - iterating'! testNoneSatisfy | element | self assert: ( self collectionWithoutNilElements noneSatisfy: [:each | each notNil not ] ). element := self collectionWithoutNilElements anyOne. self deny: ( self collectionWithoutNilElements noneSatisfy: [:each | (each = element)not ] ).! ! !CollectionRootTest methodsFor: 'tests - iterating'! testNoneSatisfyEmpty self assert: ( self empty noneSatisfy: [:each | false]). ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testReject | res element | res := self collectionWithoutNilElements reject: [:each | each notNil not]. self assert: res size = self collectionWithoutNilElements size. element := self collectionWithoutNilElements anyOne. res := self collectionWithoutNilElements reject: [:each | each = element]. self assert: res size = (self collectionWithoutNilElements size - 1). ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testRejectEmpty | res | res := self empty reject: [:each | each odd]. self assert: res size = self empty size ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testSelect | res element | res := self collectionWithoutNilElements select: [:each | each notNil]. self assert: res size = self collectionWithoutNilElements size. element := self collectionWithoutNilElements anyOne. res := self collectionWithoutNilElements select: [:each | (each = element) not]. self assert: res size = (self collectionWithoutNilElements size - 1). ! ! !CollectionRootTest methodsFor: 'tests - iterating'! testSelectOnEmpty self assert: (self empty select: [:e | self fail]) isEmpty ! ! !CollectionRootTest methodsFor: 'tests - size capacity'! testSize | size | self assert: self empty size = 0. size := 0. self sizeCollection do: [ :each | size := size + 1]. self assert: self sizeCollection size = size.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CollectionRootTest class instanceVariableNames: ''! !CollectionRootTest class methodsFor: 'as yet unclassified' stamp: 'damienpollet 1/13/2009 15:28'! isAbstract ^ self name = #CollectionRootTest! ! Object subclass: #Color instanceVariableNames: 'rgb cachedDepth cachedBitPattern' classVariableNames: 'Black Blue BlueShift Brown CachedColormaps ColorChart ColorNames ComponentMask ComponentMax Cyan DarkGray Gray GrayToIndexMap Green GreenShift HalfComponentMask HighLightBitmaps IndexedColors LightBlue LightBrown LightCyan LightGray LightGreen LightMagenta LightOrange LightRed LightYellow Magenta MaskingMap Orange PureBlue PureCyan PureGreen PureMagenta PureRed PureYellow RandomStream Red RedShift TranslucentPatterns Transparent VeryDarkGray VeryLightGray VeryVeryDarkGray VeryVeryLightGray White Yellow' poolDictionaries: '' category: 'Graphics-Primitives'! !Color commentStamp: '' prior: 0! This class represents abstract color, regardless of the depth of bitmap it will be shown in. At the very last moment a Color is converted to a pixelValue that depends on the depth of the actual Bitmap inside the Form it will be used with. The supported depths (in bits) are 1, 2, 4, 8, 16, and 32. The number of actual colors at these depths are: 2, 4, 16, 256, 32768, and 16 million. (See comment in BitBlt.) To change the depth of the Display and set how many colors you can see, execute: (Display newDepth: 8). (See comment in DisplayMedium) Color is represented as the amount of light in red, green, and blue. White is (1.0, 1.0, 1.0) and black is (0, 0, 0). Pure red is (1.0, 0, 0). These colors are "additive". Think of Color's instance variables as: r amount of red, a Float between 0.0 and 1.0. g amount of green, a Float between 0.0 and 1.0. b amount of blue, a Float between 0.0 and 1.0. (But, in fact, the three are encoded as values from 0 to 1023 and combined in a single integer, rgb. The user does not need to know this.) Many colors are named. You find a color by name by sending a message to class Color, for example (Color lightBlue). Also, (Color red: 0.2 green: 0.6 blue: 1.0) or (Color r: 0.2 g: 0.6 b: 1.0) creates a color. (see below) A color is essentially immutable. Once you set red, green, and blue, you cannot change them. Instead, create a new Color and use it. Applications such as contour maps and bar graphs will want to display one of a set of shades based on a number. Convert the range of this number to an integer from 1 to N. Then call (Color green lightShades: N) to get an Array of colors from white to green. Use the Array messages at:, atPin:, or atWrap: to pull out the correct color from the array. atPin: gives the first (or last) color if the index is out of range. atWrap: wraps around to the other end if the index is out of range. Here are some fun things to run in when your screen has color: Pen new mandala: 30 diameter: Display height-100. Pen new web "Draw with the mouse, opt-click to end" Display fillWhite. Pen new hilberts: 5. Form toothpaste: 30 "Draw with mouse, opt-click to end" You might also want to try the comment in Form>class>examples>tinyText... Messages: mixed: proportion with: aColor Answer this color mixed with the given color additively. The proportion, a number between 0.0 and 1.0, determines what what fraction of the receiver to use in the mix. + add two colors - subtract two colors * multiply the values of r, g, b by a number or an Array of factors. ((Color named: #white) * 0.3) gives a darkish gray. (aColor * #(0 0 0.9)) gives a color with slightly less blue. / divide a color by a factor or an array of three factors. errorForDepth: d How close the nearest color at this depth is to this abstract color. Sum of the squares of the RGB differences, square rooted and normalized to 1.0. Multiply by 100 to get percent. hue Returns the hue of the color. On a wheel from 0 to 360 with pure red at 0 and again at 360. saturation Returns the saturation of the color. 0.0 to 1.0 brightness Returns the brightness of the color. 0.0 to 1.0 name Look to see if this Color has a name. display Show a swatch of this color tracking the cursor. lightShades: thisMany An array of thisMany colors from white to the receiver. darkShades: thisMany An array of thisMany colors from black to the receiver. Array is of length num. mix: color2 shades: thisMany An array of thisMany colors from the receiver to color2. wheel: thisMany An array of thisMany colors around the color wheel starting and ending at the receiver. pixelValueForDepth: d Returns the bits that appear be in a Bitmap of this depth for this color. Represents the nearest available color at this depth. Normal users do not need to know which pixelValue is used for which color. Messages to Class Color. red: r green: g blue: b Return a color with the given r, g, and b components. r: g: b: Same as above, for fast typing. hue: h saturation: s brightness: b Create a color with the given hue, saturation, and brightness. pink blue red ... Many colors have messages that return an instance of Color. canUnderstand: #brown Returns true if #brown is a defined color. names An OrderedCollection of the names of the colors. named: #notAllThatGray put: aColor Add a new color to the list and create an access message and a class variable for it. fromUser Shows the palette of colors available at this display depth. Click anywhere to return the color you clicked on. hotColdShades: thisMany An array of thisMany colors showing temperature from blue to red to white hot. stdColorsForDepth: d An Array of colors available at this depth. For 16 bit and 32 bits, returns a ColorGenerator. It responds to at: with a Color for that index, simulating a very big Array. colorFromPixelValue: value depth: d Returns a Color whose bit pattern (inside a Bitmap) at this depth is the number specified. Normal users do not need to use this. (See also comments in these classes: Form, Bitmap, BitBlt, Pattern, MaskedForm.)! !Color methodsFor: '*Polymorph-Widgets' stamp: 'gvc 4/17/2007 11:41'! contrastingColor "Answer black or white depending on the luminance." self isTransparent ifTrue: [^Color black]. ^self luminance > 0.5 ifTrue: [Color black] ifFalse: [Color white]! ! !Color methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/21/2008 16:35'! fillRectangle: aRectangle on: aCanvas "Fill the given rectangle on the given canvas with the receiver." aCanvas fillRectangle: aRectangle basicFillStyle: self! ! !Color methodsFor: '*Polymorph-Widgets' stamp: 'gvc 9/21/2006 09:48'! pixelWord32 "Returns an integer representing the bits that appear in a single pixel of this color in a Form of depth 32. Transparency: The pixel value zero is reserved for transparent. For depths greater than 8, black maps to the darkest possible blue. Just a little quicker if we are dealing with RGBA colors at 32 bit depth." | val | "eight bits per component; top 8 bits set to all ones (opaque alpha)" val := LargePositiveInteger new: 4. val at: 3 put: ((rgb bitShift: -22) bitAnd: 16rFF). val at: 2 put: ((rgb bitShift: -12) bitAnd: 16rFF). val at: 1 put: ((rgb bitShift: -2) bitAnd: 16rFF). val = 0 ifTrue: [val at: 1 put: 1]. "closest non-transparent black" val at: 4 put: 16rFF. "opaque alpha" ^val ! ! !Color methodsFor: '*morphic' stamp: 'ar 7/8/2006 21:00'! iconOrThumbnailOfSize: aNumberOrPoint "Answer an appropiate form to represent the receiver" | form | form := Form extent: aNumberOrPoint asPoint asPoint depth: 32. form fillColor: self. ^ form! ! !Color methodsFor: 'access'! alpha "Return the opacity ('alpha') value of opaque so that normal colors can be compared to TransparentColors." ^ 1.0 ! ! !Color methodsFor: 'access'! blue "Return the blue component of this color, a float in the range [0.0..1.0]." ^ self privateBlue asFloat / ComponentMax! ! !Color methodsFor: 'access'! brightness "Return the brightness of this color, a float in the range [0.0..1.0]." ^ ((self privateRed max: self privateGreen) max: self privateBlue) asFloat / ComponentMax! ! !Color methodsFor: 'access'! green "Return the green component of this color, a float in the range [0.0..1.0]." ^ self privateGreen asFloat / ComponentMax! ! !Color methodsFor: 'access' stamp: 'lr 7/4/2009 10:42'! hue "Return the hue of this color, an angle in the range [0.0..360.0]." | r g b max min span h | r := self privateRed. g := self privateGreen. b := self privateBlue. max := (r max: g) max: b. min := (r min: g) min: b. span := (max - min) asFloat. span = 0.0 ifTrue: [ ^ 0.0 ]. r = max ifTrue: [ h := (g - b) asFloat / span * 60.0 ] ifFalse: [ g = max ifTrue: [ h := 120.0 + ((b - r) asFloat / span * 60.0) ] ifFalse: [ h := 240.0 + ((r - g) asFloat / span * 60.0) ] ]. h < 0.0 ifTrue: [ h := 360.0 + h ]. ^ h! ! !Color methodsFor: 'access'! luminance "Return the luminance of this color, a brightness value weighted by the human eye's color sensitivity." ^ ((299 * self privateRed) + (587 * self privateGreen) + (114 * self privateBlue)) / (1000 * ComponentMax) ! ! !Color methodsFor: 'access'! red "Return the red component of this color, a float in the range [0.0..1.0]." ^ self privateRed asFloat / ComponentMax! ! !Color methodsFor: 'access' stamp: 'lr 7/4/2009 10:42'! saturation "Return the saturation of this color, a value between 0.0 and 1.0." | r g b max min | r := self privateRed. g := self privateGreen. b := self privateBlue. max := min := r. g > max ifTrue: [ max := g ]. b > max ifTrue: [ max := b ]. g < min ifTrue: [ min := g ]. b < min ifTrue: [ min := b ]. max = 0 ifTrue: [ ^ 0.0 ] ifFalse: [ ^ (max - min) asFloat / max asFloat ]! ! !Color methodsFor: 'conversions' stamp: 'ar 11/2/1998 12:19'! asColor "Convert the receiver into a color" ^self! ! !Color methodsFor: 'conversions' stamp: 'TBn 6/15/2000 20:37'! asColorref "Convert the receiver into a colorref" ^(self red * 255) asInteger + ((self green * 255) asInteger << 8) + ((self green * 255) asInteger << 16)! ! !Color methodsFor: 'conversions' stamp: 'bf 2/19/2008 12:10'! asHTMLColor | s | s := '#000000' copy. s at: 2 put: (Character digitValue: ((rgb bitShift: -6 - RedShift) bitAnd: 15)). s at: 3 put: (Character digitValue: ((rgb bitShift: -2 - RedShift) bitAnd: 15)). s at: 4 put: (Character digitValue: ((rgb bitShift: -6 - GreenShift) bitAnd: 15)). s at: 5 put: (Character digitValue: ((rgb bitShift: -2 - GreenShift) bitAnd: 15)). s at: 6 put: (Character digitValue: ((rgb bitShift: -6 - BlueShift) bitAnd: 15)). s at: 7 put: (Character digitValue: ((rgb bitShift: -2 - BlueShift) bitAnd: 15)). ^ s! ! !Color methodsFor: 'conversions' stamp: 'sw 10/27/1999 10:51'! asNontranslucentColor ^ self! ! !Color methodsFor: 'conversions' stamp: 'lr 7/4/2009 10:42'! balancedPatternForDepth: depth "A generalization of bitPatternForDepth: as it exists. Generates a 2x2 stipple of color. The topLeft and bottomRight pixel are closest approx to this color" | pv1 pv2 mask1 mask2 pv3 c | (depth == cachedDepth and: [ cachedBitPattern size = 2 ]) ifTrue: [ ^ cachedBitPattern ]. (depth between: 4 and: 16) ifFalse: [ ^ self bitPatternForDepth: depth ]. cachedDepth := depth. pv1 := self pixelValueForDepth: depth. " Subtract error due to pv1 to get pv2. pv2 _ (self - (err1 _ (Color colorFromPixelValue: pv1 depth: depth) - self)) pixelValueForDepth: depth. Subtract error due to 2 pv1's and pv2 to get pv3. pv3 _ (self - err1 - err1 - ((Color colorFromPixelValue: pv2 depth: depth) - self)) pixelValueForDepth: depth. " "Above two statements computed faster by the following..." pv2 := (c := self - ((Color colorFromPixelValue: pv1 depth: depth) - self)) pixelValueForDepth: depth. pv3 := c + (c - (Color colorFromPixelValue: pv2 depth: depth)) pixelValueForDepth: depth. "Return to a 2-word bitmap that encodes a 2x2 stipple of the given pixelValues." mask1 := #( #- #- #- 16843009 #- #- #- 65537 #- #- #- #- #- #- #- 1 ) at: depth. "replicates every other 4 bits" "replicates every other 8 bits" "replicates every other 16 bits" mask2 := #( #- #- #- 269488144 #- #- #- 16777472 #- #- #- #- #- #- #- 65536 ) at: depth. "replicates the other 4 bits" "replicates the other 8 bits" "replicates the other 16 bits" ^ cachedBitPattern := Bitmap with: mask1 * pv1 + (mask2 * pv2) with: mask1 * pv3 + (mask2 * pv1)! ! !Color methodsFor: 'conversions' stamp: 'lr 7/4/2009 10:42'! bitPatternForDepth: depth "Return a Bitmap, possibly containing a stipple pattern, that best represents this color at the given depth. BitBlt calls this method to convert colors into Bitmaps. The resulting Bitmap may be multiple words to represent a stipple pattern of several lines. " "See also: pixelValueAtDepth: -- value for single pixel pixelWordAtDepth: -- a 32-bit word filled with the pixel value" "Details: The pattern for the most recently requested depth is cached." "Note for depths > 2, there are stippled and non-stippled versions (generated with #balancedPatternForDepth: and #bitPatternForDepth:, respectively). The stippled versions don't work with the window bit caching of StandardSystemView, so we make sure that for these depths, only unstippled patterns are returned" (depth == cachedDepth and: [ depth <= 2 or: [ cachedBitPattern size = 1 ] ]) ifTrue: [ ^ cachedBitPattern ]. cachedDepth := depth. depth > 2 ifTrue: [ ^ cachedBitPattern := Bitmap with: (self pixelWordForDepth: depth) ]. depth = 1 ifTrue: [ ^ cachedBitPattern := self halfTonePattern1 ]. depth = 2 ifTrue: [ ^ cachedBitPattern := self halfTonePattern2 ]! ! !Color methodsFor: 'conversions'! closestPixelValue1 "Return the nearest approximation to this color for a monochrome Form." "fast special cases" rgb = 0 ifTrue: [^ 1]. "black" rgb = 16r3FFFFFFF ifTrue: [^ 0]. "white" self luminance > 0.5 ifTrue: [^ 0] "white" ifFalse: [^ 1]. "black" ! ! !Color methodsFor: 'conversions' stamp: 'lr 7/4/2009 10:42'! closestPixelValue2 "Return the nearest approximation to this color for a 2-bit deep Form." "fast special cases" | lum | rgb = 0 ifTrue: [ ^ 1 ]. "black" rgb = 1073741823 ifTrue: [ ^ 2 ]. "opaque white" lum := self luminance. lum < 0.2 ifTrue: [ ^ 1 ]. "black" lum > 0.6 ifTrue: [ ^ 2 ]. "opaque white" ^ 3 "50% gray"! ! !Color methodsFor: 'conversions' stamp: 'lr 7/4/2009 10:42'! closestPixelValue4 "Return the nearest approximation to this color for a 4-bit deep Form." "fast special cases" | bIndex | rgb = 0 ifTrue: [ ^ 1 ]. "black" rgb = 1073741823 ifTrue: [ ^ 2 ]. "opaque white" rgb = PureRed privateRGB ifTrue: [ ^ 4 ]. rgb = PureGreen privateRGB ifTrue: [ ^ 5 ]. rgb = PureBlue privateRGB ifTrue: [ ^ 6 ]. rgb = PureCyan privateRGB ifTrue: [ ^ 7 ]. rgb = PureYellow privateRGB ifTrue: [ ^ 8 ]. rgb = PureMagenta privateRGB ifTrue: [ ^ 9 ]. bIndex := (self luminance * 8.0) rounded. "bIndex in [0..8]" ^ #(1 10 11 12 3 13 14 15 2 ) at: bIndex + 1 "black" "1/8 gray" "2/8 gray" "3/8 gray" "4/8 gray" "5/8 gray" "6/8 gray" "7/8 gray" "opaque white"! ! !Color methodsFor: 'conversions'! closestPixelValue8 "Return the nearest approximation to this color for an 8-bit deep Form." "fast special cases" rgb = 0 ifTrue: [^ 1]. "black" rgb = 16r3FFFFFFF ifTrue: [^ 255]. "white" self saturation < 0.2 ifTrue: [ ^ GrayToIndexMap at: (self privateGreen >> 2) + 1. "nearest gray" ] ifFalse: [ "compute nearest entry in the color cube" ^ 40 + ((((self privateRed * 5) + HalfComponentMask) // ComponentMask) * 36) + ((((self privateBlue * 5) + HalfComponentMask) // ComponentMask) * 6) + (((self privateGreen * 5) + HalfComponentMask) // ComponentMask)]. ! ! !Color methodsFor: 'conversions' stamp: 'di 9/2/97 20:21'! dominantColor ^ self! ! !Color methodsFor: 'conversions' stamp: 'lr 7/4/2009 10:42'! halfTonePattern1 "Return a halftone-pattern to approximate luminance levels on 1-bit deep Forms." | lum | lum := self luminance. lum < 0.1 ifTrue: [ ^ Bitmap with: 4294967295 ]. "black" lum < 0.4 ifTrue: [ ^ Bitmap with: 3149642683 with: 4008636142 ]. "dark gray" lum < 0.6 ifTrue: [ ^ Bitmap with: 1431655765 with: 2863311530 ]. "medium gray" lum < 0.9 ifTrue: [ ^ Bitmap with: 1145324612 with: 286331153 ]. "light gray" ^ Bitmap with: 0 "1-bit white"! ! !Color methodsFor: 'conversions' stamp: 'lr 7/4/2009 10:42'! halfTonePattern2 "Return a halftone-pattern to approximate luminance levels on 2-bit deep Forms." | lum | lum := self luminance. lum < 0.125 ifTrue: [ ^ Bitmap with: 1431655765 ]. "black" lum < 0.25 ifTrue: [ ^ Bitmap with: 1431655765 with: 3722304989 ]. "1/8 gray" lum < 0.375 ifTrue: [ ^ Bitmap with: 3722304989 with: 2004318071 ]. "2/8 gray" lum < 0.5 ifTrue: [ ^ Bitmap with: 4294967295 with: 2004318071 ]. "3/8 gray" lum < 0.625 ifTrue: [ ^ Bitmap with: 4294967295 ]. "4/8 gray" lum < 0.75 ifTrue: [ ^ Bitmap with: 4294967295 with: 3149642683 ]. "5/8 gray" lum < 0.875 ifTrue: [ ^ Bitmap with: 4008636142 with: 3149642683 ]. "6/8 gray" lum < 1.0 ifTrue: [ ^ Bitmap with: 2863311530 with: 3149642683 ]. "7/8 gray" ^ Bitmap with: 2863311530 "opaque white" "handy expression for computing patterns for 2x2 tiles; set p to a string of 4 letters (e.g., 'wggw' for a gray-and- white checkerboard) and print the result of evaluating: | p d w1 w2 | p _ 'wggw'. d _ Dictionary new. d at: $b put: '01'. d at: $w put: '10'. d at: $g put: '11'. w1 _ (d at: (p at: 1)), (d at: (p at: 2)). w1 _ '2r', w1, w1, w1, w1, w1, w1, w1, w1, ' hex'. w2 _ (d at: (p at: 3)), (d at: (p at: 4)). w2 _ '2r', w2, w2, w2, w2, w2, w2, w2, w2, ' hex'. Array with: (Compiler evaluate: w1) with: (Compiler evaluate: w2) "! ! !Color methodsFor: 'conversions' stamp: 'tk 4/24/97'! indexInMap: aColorMap "Return the index corresponding to this color in the given color map. RGB colors are truncated to 3-, 4-, or 5-bits per color component when indexing into such a colorMap. " aColorMap size = 2 ifTrue: [^ (self pixelValueForDepth: 1) + 1]. aColorMap size = 4 ifTrue: [^ (self pixelValueForDepth: 2) + 1]. aColorMap size = 16 ifTrue: [^ (self pixelValueForDepth: 4) + 1]. aColorMap size = 256 ifTrue: [^ (self pixelValueForDepth: 8) + 1]. aColorMap size = 512 ifTrue: [^ (self pixelValueForDepth: 9) + 1]. aColorMap size = 4096 ifTrue: [^ (self pixelValueForDepth: 12) + 1]. aColorMap size = 32768 ifTrue: [^ (self pixelValueForDepth: 16) + 1]. self error: 'unknown pixel depth'. ! ! !Color methodsFor: 'conversions' stamp: 'bf 4/18/2001 16:25'! makeForegroundColor "Make a foreground color contrasting with me" ^self luminance >= 0.5 ifTrue: [Color black] ifFalse: [Color white]! ! !Color methodsFor: 'conversions' stamp: 'ar 5/15/2001 16:12'! pixelValue32 "Note: pixelWord not pixelValue so we include translucency" ^self pixelWordForDepth: 32! ! !Color methodsFor: 'conversions' stamp: 'lr 7/4/2009 10:42'! pixelValueForDepth: d "Returns an integer representing the bits that appear in a single pixel of this color in a Form of the given depth. The depth must be one of 1, 2, 4, 8, 16, or 32. Contrast with pixelWordForDepth: and bitPatternForDepth:, which return either a 32-bit word packed with the given pixel value or a multiple-word Bitmap containing a pattern. The inverse is the class message colorFromPixelValue:depth:" "Details: For depths of 8 or less, the result is a colorMap index. For depths of 16 and 32, it is a direct color value with 5 or 8 bits per color component." "Transparency: The pixel value zero is reserved for transparent. For depths greater than 8, black maps to the darkest possible blue." | rgbBlack val | d = 8 ifTrue: [ ^ self closestPixelValue8 ]. "common case" d < 8 ifTrue: [ d = 4 ifTrue: [ ^ self closestPixelValue4 ]. d = 2 ifTrue: [ ^ self closestPixelValue2 ]. d = 1 ifTrue: [ ^ self closestPixelValue1 ] ]. rgbBlack := 1. "closest black that is not transparent in RGB" d = 16 ifTrue: [ "five bits per component; top bits ignored" val := (((rgb bitShift: -15) bitAnd: 31744) bitOr: ((rgb bitShift: -10) bitAnd: 992)) bitOr: ((rgb bitShift: -5) bitAnd: 31). ^ val = 0 ifTrue: [ rgbBlack ] ifFalse: [ val ] ]. d = 32 ifTrue: [ "eight bits per component; top 8 bits set to all ones (opaque alpha)" val := LargePositiveInteger new: 4. val at: 3 put: ((rgb bitShift: -22) bitAnd: 255). val at: 2 put: ((rgb bitShift: -12) bitAnd: 255). val at: 1 put: ((rgb bitShift: -2) bitAnd: 255). val = 0 ifTrue: [ val at: 1 put: 1 ]. "closest non-transparent black" val at: 4 put: 255. "opaque alpha" ^ val ]. d = 12 ifTrue: [ "for indexing a color map with 4 bits per color component" val := (((rgb bitShift: -18) bitAnd: 3840) bitOr: ((rgb bitShift: -12) bitAnd: 240)) bitOr: ((rgb bitShift: -6) bitAnd: 15). ^ val = 0 ifTrue: [ rgbBlack ] ifFalse: [ val ] ]. d = 9 ifTrue: [ "for indexing a color map with 3 bits per color component" val := (((rgb bitShift: -21) bitAnd: 448) bitOr: ((rgb bitShift: -14) bitAnd: 56)) bitOr: ((rgb bitShift: -7) bitAnd: 7). ^ val = 0 ifTrue: [ rgbBlack ] ifFalse: [ val ] ]. self error: 'unknown pixel depth: ' , d printString! ! !Color methodsFor: 'conversions' stamp: 'lr 7/4/2009 10:42'! pixelWordFor: depth filledWith: pixelValue "Return to a 32-bit word that concatenates enough copies of the given pixel value to fill the word (i.e., 32/depth copies). Depth should be one of 1, 2, 4, 8, 16, or 32. The pixel value should be an integer in 0..2^depth-1." | halfword | depth = 32 ifTrue: [ ^ pixelValue ]. depth = 16 ifTrue: [ halfword := pixelValue ] ifFalse: [ halfword := pixelValue * (#( 65535 21845 #- 4369 #- #- #- 257 ) at: depth) "replicates at every bit" "replicates every 2 bits" "replicates every 4 bits" "replicates every 8 bits" ]. ^ halfword bitOr: (halfword bitShift: 16)! ! !Color methodsFor: 'conversions' stamp: 'lr 7/4/2009 10:42'! pixelWordForDepth: depth "Return to a 32-bit word that concatenates enough copies of the receiver's pixel value to fill the word (i.e., 32/depth copies). Depth should be one of 1, 2, 4, 8, 16, or 32. The pixel value should be an integer in 0..2^depth-1." | pixelValue | pixelValue := self pixelValueForDepth: depth. ^ self pixelWordFor: depth filledWith: pixelValue! ! !Color methodsFor: 'conversions' stamp: 'ar 1/14/1999 15:28'! scaledPixelValue32 "Return the alpha scaled pixel value for depth 32" ^self pixelWordForDepth: 32! ! !Color methodsFor: 'copying' stamp: 'tk 8/19/1998 16:12'! veryDeepCopyWith: deepCopier "Return self. I am immutable in the Morphic world. Do not record me."! ! !Color methodsFor: 'equality' stamp: 'di 1/6/1999 20:26'! = aColor "Return true if the receiver equals the given color. This method handles TranslucentColors, too." aColor isColor ifFalse: [^ false]. ^ aColor privateRGB = rgb and: [aColor privateAlpha = self privateAlpha] ! ! !Color methodsFor: 'equality' stamp: 'di 9/27/2000 08:07'! diff: theOther "Returns a number between 0.0 and 1.0" ^ ((self privateRed - theOther privateRed) abs + (self privateGreen - theOther privateGreen) abs + (self privateBlue - theOther privateBlue) abs) / 3.0 / ComponentMax! ! !Color methodsFor: 'equality'! hash ^ rgb! ! !Color methodsFor: 'groups of shades' stamp: 'tk 6/18/96'! darkShades: thisMany "An array of thisMany colors from black to the receiver. Array is of length num. Very useful for displaying color based on a variable in your program. " "Color showColors: (Color red darkShades: 12)" ^ self class black mix: self shades: thisMany ! ! !Color methodsFor: 'groups of shades' stamp: 'tk 6/18/96'! lightShades: thisMany "An array of thisMany colors from white to self. Very useful for displaying color based on a variable in your program. " "Color showColors: (Color red lightShades: 12)" ^ self class white mix: self shades: thisMany ! ! !Color methodsFor: 'groups of shades' stamp: 'lr 7/4/2009 10:42'! mix: color2 shades: thisMany "Return an array of thisMany colors from self to color2. Very useful for displaying color based on a variable in your program. " "Color showColors: (Color red mix: Color green shades: 12)" | redInc greenInc blueInc rr gg bb c out | thisMany = 1 ifTrue: [ ^ Array with: color2 ]. redInc := (color2 red - self red) / (thisMany - 1). greenInc := (color2 green - self green) / (thisMany - 1). blueInc := (color2 blue - self blue) / (thisMany - 1). rr := self red. gg := self green. bb := self blue. out := (1 to: thisMany) collect: [ :num | c := Color r: rr g: gg b: bb. rr := rr + redInc. gg := gg + greenInc. bb := bb + blueInc. c ]. out at: out size put: color2. "hide roundoff errors" ^ out! ! !Color methodsFor: 'groups of shades' stamp: 'lr 7/4/2009 10:42'! wheel: thisMany "An array of thisMany colors around the color wheel starting at self and ending all the way around the hue space just before self. Array is of length thisMany. Very useful for displaying color based on a variable in your program. " | sat bri hue step c | sat := self saturation. bri := self brightness. hue := self hue. step := 360.0 / (thisMany max: 1). ^ (1 to: thisMany) collect: [ :num | c := Color h: hue s: sat v: bri. "hue is taken mod 360" hue := hue + step. c ] " (Color wheel: 8) withIndexDo: [:c :i | Display fill: (i*10@20 extent: 10@20) fillColor: c] "! ! !Color methodsFor: 'html' stamp: 'stephane.ducasse 5/25/2008 18:10'! printHtmlString "answer a string whose characters are the html representation of the receiver" ^ ((self red * 255) asInteger printStringBase: 16 length: 2 padded: true) , ((self green * 255) asInteger printStringBase: 16 length: 2 padded: true) , ((self blue * 255) asInteger printStringBase: 16 length: 2 padded: true)! ! !Color methodsFor: 'morphic menu' stamp: 'dgd 10/17/2003 12:10'! addFillStyleMenuItems: aMenu hand: aHand from: aMorph "Add the items for changing the current fill style of the receiver" aMenu add: 'change color...' translated target: self selector: #changeColorIn:event: argument: aMorph! ! !Color methodsFor: 'morphic menu' stamp: 'ar 10/5/2000 18:50'! changeColorIn: aMorph event: evt "Note: This is just a workaround to make sure we don't use the old color inst var" aMorph changeColorTarget: aMorph selector: #fillStyle: originalColor: self hand: evt hand! ! !Color methodsFor: 'other' stamp: 'sw 2/16/98 03:42'! colorForInsets ^ self! ! !Color methodsFor: 'other' stamp: 'lr 7/4/2009 10:42'! display "Show a swatch of this color tracking the cursor until the next mouseClick. " "Color red display" | f | f := Form extent: 40 @ 20 depth: Display depth. f fillColor: self. Cursor blank showWhile: [ f follow: [ Sensor cursorPoint ] while: [ Sensor noButtonPressed ] ]! ! !Color methodsFor: 'other' stamp: 'jm 12/4/97 10:24'! name "Return this color's name, or nil if it has no name. Only returns a name if it exactly matches the named color." ColorNames do: [:name | (Color perform: name) = self ifTrue: [^ name]]. ^ nil ! ! !Color methodsFor: 'other' stamp: 'ar 8/16/2001 12:47'! raisedColor ^ self! ! !Color methodsFor: 'other' stamp: 'jm 12/4/97 10:27'! rgbTriplet "Color fromUser rgbTriplet" ^ Array with: (self red roundTo: 0.01) with: (self green roundTo: 0.01) with: (self blue roundTo: 0.01) ! ! !Color methodsFor: 'printing' stamp: 'MPW 1/1/1901 22:14'! byteEncode: aStream aStream print: '('; print: self class name; print: ' r: '; write: (self red roundTo: 0.001); print: ' g: '; write: (self green roundTo: 0.001); print: ' b: '; write: (self blue roundTo: 0.001) ; print: ')'. ! ! !Color methodsFor: 'printing' stamp: 'lr 7/4/2009 10:42'! printOn: aStream | name | (name := self name) ifNotNil: [ ^ aStream nextPutAll: 'Color '; nextPutAll: name ]. self storeOn: aStream! ! !Color methodsFor: 'printing' stamp: 'PeterHugossonMiller 9/3/2009 00:56'! shortPrintString "Return a short (but less precise) print string for use where space is tight." | s | s := String new writeStream. s nextPutAll: '(' , self class name; nextPutAll: ' r: '; nextPutAll: (self red roundTo: 0.01) printString; nextPutAll: ' g: '; nextPutAll: (self green roundTo: 0.01) printString; nextPutAll: ' b: '; nextPutAll: (self blue roundTo: 0.01) printString; nextPutAll: ')'. ^ s contents! ! !Color methodsFor: 'printing' stamp: 'mir 7/21/1999 11:41'! storeArrayOn: aStream aStream nextPutAll: '#('. self storeArrayValuesOn: aStream. aStream nextPutAll: ') ' ! ! !Color methodsFor: 'printing' stamp: 'mir 7/21/1999 11:41'! storeArrayValuesOn: aStream (self red roundTo: 0.001) storeOn: aStream. aStream space. (self green roundTo: 0.001) storeOn: aStream. aStream space. (self blue roundTo: 0.001) storeOn: aStream. ! ! !Color methodsFor: 'printing' stamp: 'di 9/27/2000 13:34'! storeOn: aStream aStream nextPutAll: '(' , self class name; nextPutAll: ' r: '; print: (self red roundTo: 0.001); nextPutAll: ' g: '; print: (self green roundTo: 0.001); nextPutAll: ' b: '; print: (self blue roundTo: 0.001); nextPutAll: ')'. ! ! !Color methodsFor: 'queries' stamp: 'sw 9/27/2001 17:26'! basicType "Answer a symbol representing the inherent type of the receiver" ^ #Color! ! !Color methodsFor: 'queries' stamp: 'ar 1/14/1999 15:27'! isBitmapFill ^false! ! !Color methodsFor: 'queries' stamp: 'ar 11/12/1998 19:43'! isBlack "Return true if the receiver represents black" ^rgb = 0! ! !Color methodsFor: 'queries'! isColor ^ true ! ! !Color methodsFor: 'queries' stamp: 'ar 6/18/1999 06:58'! isGradientFill ^false! ! !Color methodsFor: 'queries' stamp: 'ar 11/12/1998 19:44'! isGray "Return true if the receiver represents a shade of gray" ^(self privateRed = self privateGreen) and:[self privateRed = self privateBlue]! ! !Color methodsFor: 'queries' stamp: 'ar 4/20/2001 04:33'! isOpaque ^true! ! !Color methodsFor: 'queries' stamp: 'ar 6/18/1999 07:57'! isOrientedFill "Return true if the receiver keeps an orientation (e.g., origin, direction, and normal)" ^false! ! !Color methodsFor: 'queries' stamp: 'ar 11/7/1998 20:20'! isSolidFill ^true! ! !Color methodsFor: 'queries' stamp: 'di 12/30/1998 14:33'! isTranslucent ^ false ! ! !Color methodsFor: 'queries' stamp: 'di 1/3/1999 12:23'! isTranslucentColor "This means: self isTranslucent, but isTransparent not" ^ false! ! !Color methodsFor: 'queries'! isTransparent ^ false ! ! !Color methodsFor: 'self evaluating' stamp: 'sd 7/31/2005 21:46'! isSelfEvaluating ^ self class == Color! ! !Color methodsFor: 'transformations' stamp: 'fbs 2/3/2005 13:09'! * aNumberOrArray "Answer this color with its RGB multiplied by the given number, or multiply this color's RGB values by the corresponding entries in the given array." "(Color brown * 2) display" "(Color brown * #(1 0 1)) display" | multipliers | multipliers := aNumberOrArray isCollection ifTrue: [aNumberOrArray] ifFalse: [Array with: aNumberOrArray with: aNumberOrArray with: aNumberOrArray]. ^ Color basicNew setPrivateRed: (self privateRed * multipliers first) asInteger green: (self privateGreen * multipliers second) asInteger blue: (self privateBlue * multipliers third) asInteger.! ! !Color methodsFor: 'transformations' stamp: 'di 11/2/97 14:05'! + aColor "Answer this color mixed with the given color in an additive color space. " "(Color blue + Color green) display" ^ Color basicNew setPrivateRed: self privateRed + aColor privateRed green: self privateGreen + aColor privateGreen blue: self privateBlue + aColor privateBlue ! ! !Color methodsFor: 'transformations' stamp: 'di 11/2/97 14:05'! - aColor "Answer aColor is subtracted from the given color in an additive color space. " "(Color white - Color red) display" ^ Color basicNew setPrivateRed: self privateRed - aColor privateRed green: self privateGreen - aColor privateGreen blue: self privateBlue - aColor privateBlue ! ! !Color methodsFor: 'transformations' stamp: 'di 11/2/97 14:07'! / aNumber "Answer this color with its RGB divided by the given number. " "(Color red / 2) display" ^ Color basicNew setPrivateRed: (self privateRed / aNumber) asInteger green: (self privateGreen / aNumber) asInteger blue: (self privateBlue / aNumber) asInteger ! ! !Color methodsFor: 'transformations' stamp: 'dew 3/19/2002 23:50'! adjustBrightness: brightness "Adjust the relative brightness of this color. (lowest value is 0.005 so that hue information is not lost)" ^ Color h: self hue s: self saturation v: (self brightness + brightness min: 1.0 max: 0.005) alpha: self alpha! ! !Color methodsFor: 'transformations' stamp: 'dew 3/19/2002 23:51'! adjustSaturation: saturation brightness: brightness "Adjust the relative saturation and brightness of this color. (lowest value is 0.005 so that hue information is not lost)" ^ Color h: self hue s: (self saturation + saturation min: 1.0 max: 0.005) v: (self brightness + brightness min: 1.0 max: 0.005) alpha: self alpha! ! !Color methodsFor: 'transformations' stamp: 'sma 6/25/2000 15:36'! alpha: alphaValue "Answer a new Color with the given amount of opacity ('alpha')." alphaValue = 1.0 ifFalse: [^ TranslucentColor basicNew setRgb: rgb alpha: alphaValue]! ! !Color methodsFor: 'transformations' stamp: 'lr 7/4/2009 10:42'! alphaMixed: proportion with: aColor "Answer this color mixed with the given color. The proportion, a number between 0.0 and 1.0, determines what what fraction of the receiver to use in the mix. For example, 0.9 would yield a color close to the receiver. This method uses RGB interpolation; HSV interpolation can lead to surprises. Mixes the alphas (for transparency) also." | frac1 frac2 | frac1 := proportion asFloat min: 1.0 max: 0.0. frac2 := 1.0 - frac1. ^ Color r: self red * frac1 + (aColor red * frac2) g: self green * frac1 + (aColor green * frac2) b: self blue * frac1 + (aColor blue * frac2) alpha: self alpha * frac1 + (aColor alpha * frac2)! ! !Color methodsFor: 'transformations' stamp: 'lr 7/4/2009 10:42'! atLeastAsLuminentAs: aFloat | revisedColor | revisedColor := self. [ revisedColor luminance < aFloat ] whileTrue: [ revisedColor := revisedColor slightlyLighter ]. ^ revisedColor! ! !Color methodsFor: 'transformations' stamp: 'lr 7/4/2009 10:42'! atMostAsLuminentAs: aFloat | revisedColor | revisedColor := self. [ revisedColor luminance > aFloat ] whileTrue: [ revisedColor := revisedColor slightlyDarker ]. ^ revisedColor! ! !Color methodsFor: 'transformations' stamp: 'dew 3/23/2002 01:38'! blacker ^ self alphaMixed: 0.8333 with: Color black ! ! !Color methodsFor: 'transformations' stamp: 'dew 3/19/2002 23:54'! dansDarker "Return a darker shade of the same color. An attempt to do better than the current darker method. (now obsolete, since darker has been changed to do this. -dew)" ^ Color h: self hue s: self saturation v: (self brightness - 0.16 max: 0.0)! ! !Color methodsFor: 'transformations' stamp: 'dew 3/4/2002 01:40'! darker "Answer a darker shade of this color." ^ self adjustBrightness: -0.08! ! !Color methodsFor: 'transformations' stamp: 'dew 3/8/2002 00:13'! duller ^ self adjustSaturation: -0.03 brightness: -0.2! ! !Color methodsFor: 'transformations' stamp: 'dew 1/23/2002 20:19'! lighter "Answer a lighter shade of this color." ^ self adjustSaturation: -0.03 brightness: 0.08! ! !Color methodsFor: 'transformations' stamp: 'lr 7/4/2009 10:42'! mixed: proportion with: aColor "Mix with another color and do not preserve transpareny. Only use this for extracting the RGB value and mixing it. All other callers should use instead: aColor alphaMixed: proportion with: anotherColor " | frac1 frac2 | frac1 := proportion asFloat min: 1.0 max: 0.0. frac2 := 1.0 - frac1. ^ Color r: self red * frac1 + (aColor red * frac2) g: self green * frac1 + (aColor green * frac2) b: self blue * frac1 + (aColor blue * frac2)! ! !Color methodsFor: 'transformations' stamp: 'dew 1/19/2002 01:29'! muchDarker ^ self alphaMixed: 0.5 with: Color black ! ! !Color methodsFor: 'transformations' stamp: 'tk 7/4/2000 12:07'! muchLighter ^ self alphaMixed: 0.233 with: Color white ! ! !Color methodsFor: 'transformations' stamp: 'ar 6/19/1999 00:36'! negated "Return an RGB inverted color" ^Color r: 1.0 - self red g: 1.0 - self green b: 1.0 - self blue! ! !Color methodsFor: 'transformations' stamp: 'di 9/27/2000 08:14'! orColorUnlike: theOther "If this color is a lot like theOther, then return its complement, otherwide, return self" (self diff: theOther) < 0.3 ifTrue: [^ theOther negated] ifFalse: [^ self]! ! !Color methodsFor: 'transformations' stamp: 'dew 3/4/2002 01:42'! paler "Answer a paler shade of this color." ^ self adjustSaturation: -0.09 brightness: 0.09 ! ! !Color methodsFor: 'transformations' stamp: 'dew 3/4/2002 01:43'! slightlyDarker ^ self adjustBrightness: -0.03 ! ! !Color methodsFor: 'transformations' stamp: 'dew 3/4/2002 01:43'! slightlyLighter ^ self adjustSaturation: -0.01 brightness: 0.03! ! !Color methodsFor: 'transformations' stamp: 'dew 1/19/2002 01:25'! slightlyWhiter ^ self alphaMixed: 0.85 with: Color white ! ! !Color methodsFor: 'transformations' stamp: 'dew 3/4/2002 01:44'! twiceDarker "Answer a significantly darker shade of this color." ^ self adjustBrightness: -0.15! ! !Color methodsFor: 'transformations' stamp: 'dew 3/4/2002 01:45'! twiceLighter "Answer a significantly lighter shade of this color." ^ self adjustSaturation: -0.06 brightness: 0.15! ! !Color methodsFor: 'transformations' stamp: 'tk 7/4/2000 12:07'! veryMuchLighter ^ self alphaMixed: 0.1165 with: Color white ! ! !Color methodsFor: 'transformations' stamp: 'dew 3/23/2002 01:38'! whiter ^ self alphaMixed: 0.8333 with: Color white ! ! !Color methodsFor: 'private'! attemptToMutateError "A color is immutable. Once a color's red, green, and blue have been initialized, you cannot change them. Instead, create a new Color and use it." self error: 'Color objects are immutable once created' ! ! !Color methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! flushCache "Flush my cached bit pattern." cachedDepth := nil. cachedBitPattern := nil! ! !Color methodsFor: 'private'! privateAlpha "Private!! Return the raw alpha value for opaque. Used only for equality testing." ^ 255! ! !Color methodsFor: 'private'! privateBlue "Private!! Return the internal representation of my blue component." ^ rgb bitAnd: ComponentMask! ! !Color methodsFor: 'private'! privateGreen "Private!! Return the internal representation of my green component. Replaced >> by bitShift: 0 -. SqR!! 2/25/1999 23:08" ^ (rgb bitShift: 0 - GreenShift) bitAnd: ComponentMask! ! !Color methodsFor: 'private'! privateRGB "Private!! Return the internal representation of my RGB components." ^ rgb ! ! !Color methodsFor: 'private'! privateRed "Private!! Return the internal representation of my red component." ^ (rgb bitShift: 0 - RedShift) bitAnd: ComponentMask! ! !Color methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setHue: hue saturation: saturation brightness: brightness "Initialize this color to the given hue, saturation, and brightness. See the comment in the instance creation method for details." | s v hf i f p q t | s := (saturation asFloat max: 0.0) min: 1.0. v := (brightness asFloat max: 0.0) min: 1.0. "zero saturation yields gray with the given brightness" s = 0.0 ifTrue: [ ^ self setRed: v green: v blue: v ]. hf := hue asFloat. (hf < 0.0 or: [ hf >= 360.0 ]) ifTrue: [ hf := hf - ((hf quo: 360.0) asFloat * 360.0) ]. hf := hf / 60.0. i := hf asInteger. "integer part of hue" f := hf fractionPart. "fractional part of hue" p := (1.0 - s) * v. q := (1.0 - (s * f)) * v. t := (1.0 - (s * (1.0 - f))) * v. 0 = i ifTrue: [ ^ self setRed: v green: t blue: p ]. 1 = i ifTrue: [ ^ self setRed: q green: v blue: p ]. 2 = i ifTrue: [ ^ self setRed: p green: v blue: t ]. 3 = i ifTrue: [ ^ self setRed: p green: q blue: v ]. 4 = i ifTrue: [ ^ self setRed: t green: p blue: v ]. 5 = i ifTrue: [ ^ self setRed: v green: p blue: q ]. self error: 'implementation error'! ! !Color methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setPrivateRed: r green: g blue: b "Initialize this color's r, g, and b components to the given values in the range [0..ComponentMax]. Encoded in a single variable as 3 integers in [0..1023]." rgb == nil ifFalse: [ self attemptToMutateError ]. rgb := ((r min: ComponentMask max: 0) bitShift: RedShift) + ((g min: ComponentMask max: 0) bitShift: GreenShift) + (b min: ComponentMask max: 0). cachedDepth := nil. cachedBitPattern := nil! ! !Color methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setRGB: rgb0 rgb == nil ifFalse: [ self attemptToMutateError ]. rgb := rgb0! ! !Color methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setRed: r green: g blue: b "Initialize this color's r, g, and b components to the given values in the range [0.0..1.0]. Encoded in a single variable as 3 integers in [0..1023]." rgb == nil ifFalse: [ self attemptToMutateError ]. rgb := (((r * ComponentMax) rounded bitAnd: ComponentMask) bitShift: RedShift) + (((g * ComponentMax) rounded bitAnd: ComponentMask) bitShift: GreenShift) + ((b * ComponentMax) rounded bitAnd: ComponentMask). cachedDepth := nil. cachedBitPattern := nil! ! !Color methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setRed: r green: g blue: b range: range "Initialize this color's r, g, and b components to the given values in the range [0..r]." rgb == nil ifFalse: [ self attemptToMutateError ]. rgb := ((r * ComponentMask // range bitAnd: ComponentMask) bitShift: RedShift) + ((g * ComponentMask // range bitAnd: ComponentMask) bitShift: GreenShift) + (b * ComponentMask // range bitAnd: ComponentMask). cachedDepth := nil. cachedBitPattern := nil! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Color class instanceVariableNames: ''! !Color class methodsFor: 'class initialization' stamp: 'lr 7/4/2009 10:42'! initializeNames "Name some colors." "Color initializeNames" ColorNames := OrderedCollection new. self named: #black put: (Color r: 0 g: 0 b: 0). self named: #veryVeryDarkGray put: (Color r: 0.125 g: 0.125 b: 0.125). self named: #veryDarkGray put: (Color r: 0.25 g: 0.25 b: 0.25). self named: #darkGray put: (Color r: 0.375 g: 0.375 b: 0.375). self named: #gray put: (Color r: 0.5 g: 0.5 b: 0.5). self named: #lightGray put: (Color r: 0.625 g: 0.625 b: 0.625). self named: #veryLightGray put: (Color r: 0.75 g: 0.75 b: 0.75). self named: #veryVeryLightGray put: (Color r: 0.875 g: 0.875 b: 0.875). self named: #white put: (Color r: 1.0 g: 1.0 b: 1.0). self named: #red put: (Color r: 1.0 g: 0 b: 0). self named: #yellow put: (Color r: 1.0 g: 1.0 b: 0). self named: #green put: (Color r: 0 g: 1.0 b: 0). self named: #cyan put: (Color r: 0 g: 1.0 b: 1.0). self named: #blue put: (Color r: 0 g: 0 b: 1.0). self named: #magenta put: (Color r: 1.0 g: 0 b: 1.0). self named: #brown put: (Color r: 0.6 g: 0.2 b: 0). self named: #orange put: (Color r: 1.0 g: 0.6 b: 0). self named: #lightRed put: (Color r: 1.0 g: 0.8 b: 0.8). self named: #lightYellow put: (Color r: 1.0 g: 1.0 b: 0.8). self named: #lightGreen put: (Color r: 0.8 g: 1.0 b: 0.6). self named: #lightCyan put: (Color r: 0.4 g: 1.0 b: 1.0). self named: #lightBlue put: (Color r: 0.8 g: 1.0 b: 1.0). self named: #lightMagenta put: (Color r: 1.0 g: 0.8 b: 1.0). self named: #lightBrown put: (Color r: 1.0 g: 0.6 b: 0.2). self named: #lightOrange put: (Color r: 1.0 g: 0.8 b: 0.4). self named: #transparent put: (TranslucentColor new alpha: 0.0)! ! !Color class methodsFor: 'color from user' stamp: 'lr 7/4/2009 10:42'! colorTest: depth extent: chartExtent colorMapper: colorMapper "Create a palette of colors sorted horizontally by hue and vertically by lightness. Useful for eyeballing the color gamut of the display, or for choosing a color interactively." "Note: It is slow to build this palette, so it should be cached for quick access." "(Color colorTest: 32 extent: 570@180 colorMapper: [:c | c]) display" "(Color colorTest: 32 extent: 570@180 colorMapper: [:c | Color r: (c red * 7) asInteger / 7 g: (c green * 7) asInteger / 7 b: (c blue * 3) asInteger / 3]) display" "(Color colorTest: 32 extent: 570@180 colorMapper: [:c | Color r: (c red * 5) asInteger / 5 g: (c green * 5) asInteger / 5 b: (c blue * 5) asInteger / 5]) display" "(Color colorTest: 32 extent: 570@180 colorMapper: [:c | Color r: (c red * 15) asInteger / 15 g: (c green * 15) asInteger / 15 b: (c blue * 15) asInteger / 15]) display" "(Color colorTest: 32 extent: 570@180 colorMapper: [:c | Color r: (c red * 31) asInteger / 31 g: (c green * 31) asInteger / 31 b: (c blue * 31) asInteger / 31]) display" | basicHue x y c startHue palette transHt vSteps transCaption grayWidth hSteps | palette := Form extent: chartExtent depth: depth. transCaption := Form extent: 34 @ 9 depth: 1 fromArray: #( 0 0 256 0 256 0 3808663859 2147483648 2491688266 2147483648 2491688266 0 2491688266 0 2466486578 0 0 0 ) offset: 0 @ 0. "(DisplayText text: 'no color' asText textStyle: (TextConstants at: #ComicPlain)) form storeString" transHt := transCaption height. palette fillWhite: (0 @ 0 extent: palette width @ transHt). palette fillBlack: (0 @ transHt extent: palette width @ 1). transCaption displayOn: palette at: palette boundingBox topCenter - ((transCaption width // 2) @ 0). grayWidth := 10. startHue := 338.0. vSteps := (palette height - transHt) // 2. hSteps := palette width - grayWidth. x := 0. startHue to: startHue + 360.0 by: 360.0 / hSteps do: [ :h | basicHue := Color h: h asFloat s: 1.0 v: 1.0. y := transHt + 1. 0 to: vSteps do: [ :n | c := basicHue mixed: n asFloat / vSteps asFloat with: Color white. c := colorMapper value: c. palette fill: (x @ y extent: 1 @ 1) fillColor: c. y := y + 1 ]. 1 to: vSteps do: [ :n | c := Color black mixed: n asFloat / vSteps asFloat with: basicHue. c := colorMapper value: c. palette fill: (x @ y extent: 1 @ 1) fillColor: c. y := y + 1 ]. x := x + 1 ]. y := transHt + 1. 1 to: vSteps * 2 do: [ :n | c := Color black mixed: n asFloat / (vSteps * 2) asFloat with: Color white. c := colorMapper value: c. palette fill: (x @ y extent: 10 @ 1) fillColor: c. y := y + 1 ]. ^ palette! ! !Color class methodsFor: 'color from user' stamp: 'lr 7/4/2009 10:42'! fromUser "Displays a color palette of colors, waits for a mouse click, and returns the selected color. Any pixel on the Display can be chosen, not just those in the color palette." "Note: Since the color chart is cached, you may need to do 'ColorChart _ nil' after changing the oldColorPaletteForDepth:extent: method." "Color fromUser" | d startPt save tr oldColor c here s | d := Display depth. (ColorChart == nil or: [ ColorChart depth ~= Display depth ]) ifTrue: [ ColorChart := self oldColorPaletteForDepth: d extent: (2 * 144) @ 80 ]. Sensor cursorPoint y < Display center y ifTrue: [ startPt := 0 @ (Display boundingBox bottom - ColorChart height) ] ifFalse: [ startPt := 0 @ 0 ]. save := Form fromDisplay: (startPt extent: ColorChart extent). ColorChart displayAt: startPt. tr := ColorChart extent - (50 @ 19) corner: ColorChart extent. tr := tr translateBy: startPt. oldColor := nil. [ Sensor anyButtonPressed ] whileFalse: [ c := Display colorAt: (here := Sensor cursorPoint). (tr containsPoint: here) ifFalse: [ Display fill: (0 @ 61 + startPt extent: 20 @ 19) fillColor: c ] ifTrue: [ c := Color transparent. Display fill: (0 @ 61 + startPt extent: 20 @ 19) fillColor: Color white ]. c = oldColor ifFalse: [ Display fillWhite: (20 @ 61 + startPt extent: 135 @ 19). c isTransparent ifTrue: [ s := 'transparent' ] ifFalse: [ s := c shortPrintString. s := s copyFrom: 7 to: s size - 1 ]. s displayAt: 20 @ 61 + startPt. oldColor := c ] ]. save displayAt: startPt. Sensor waitNoButton. ^ c! ! !Color class methodsFor: 'color from user' stamp: 'lr 7/4/2009 10:42'! oldColorPaletteForDepth: depth extent: paletteExtent "Returns a form of the given size showing a color palette for the given depth." "(Color oldColorPaletteForDepth: Display depth extent: 720@100) display" | c p f nSteps rect w h q | f := Form extent: paletteExtent depth: depth. f fill: f boundingBox fillColor: Color white. nSteps := depth > 8 ifTrue: [ 12 ] ifFalse: [ 6 ]. w := paletteExtent x // (nSteps * nSteps). h := (paletteExtent y - 20) // nSteps. 0 to: nSteps - 1 do: [ :r | 0 to: nSteps - 1 do: [ :g | 0 to: nSteps - 1 do: [ :b | c := Color r: r g: g b: b range: nSteps - 1. rect := (r * nSteps * w + (b * w)) @ (g * h) extent: w @ (h + 1). f fill: rect fillColor: c ] ] ]. q := Quadrangle origin: paletteExtent - (50 @ 19) corner: paletteExtent. q displayOn: f. 'Trans.' displayOn: f at: q origin + (9 @ 1). w := (paletteExtent x - q width - 130) // 64 max: 1. p := (paletteExtent x - q width - (64 * w) - 1) @ (paletteExtent y - 19). 0 to: 63 do: [ :v | c := Color r: v g: v b: v range: 63. f fill: ((v * w) @ 0 + p extent: (w + 1) @ 19) fillColor: c ]. ^ f! ! !Color class methodsFor: 'colormaps' stamp: 'lr 7/4/2009 10:42'! cachedColormapFrom: sourceDepth to: destDepth "Return a cached colormap for mapping between the given depths. Always return a real colormap, not nil; this allows the client to get an identity colormap that can then be copied and modified to do color transformations." "Note: This method returns a shared, cached colormap to save time and space. Clients that need to modify a colormap returned by this method should make a copy and modify that!!" "Note: The colormap cache may be cleared by evaluating 'Color shutDown'." | srcIndex map | CachedColormaps class == Array ifFalse: [ CachedColormaps := (1 to: 9) collect: [ :i | Array new: 32 ] ]. srcIndex := sourceDepth. sourceDepth > 8 ifTrue: [ srcIndex := 9 ]. (map := (CachedColormaps at: srcIndex) at: destDepth) ~~ nil ifTrue: [ ^ map ]. map := self computeColormapFrom: sourceDepth to: destDepth. (CachedColormaps at: srcIndex) at: destDepth put: map. ^ map! ! !Color class methodsFor: 'colormaps'! colorMapIfNeededFrom: sourceDepth to: destDepth "Return a colormap for mapping between the given depths, or nil if no colormap is needed." "Note: This method returns a shared, cached colormap to save time and space. Clients that need to modify a colormap returned by this method should make a copy and modify that!!" sourceDepth = destDepth ifTrue: [^ nil]. "not needed if depths are the same" (sourceDepth >= 16) & (destDepth >= 16) ifTrue: [ "mapping is done in BitBlt by zero-filling or truncating each color component" ^ nil]. ^ Color cachedColormapFrom: sourceDepth to: destDepth ! ! !Color class methodsFor: 'colormaps' stamp: 'jmv 8/2/2009 21:32'! computeColorConvertingMap: targetColor from: sourceDepth to: destDepth keepSubPixelAA: keepSubPix sourceDepth < 16 ifTrue: [ "source is 1-, 2-, 4-, or 8-bit indexed color. Assumed not to include subpixelAA" ^ self computeIndexedColorConvertingMap: targetColor from: sourceDepth to: destDepth ] ifFalse: [ "source is 16-bit or 32-bit RGB. Might include subpixelAA" ^ self computeRGBColorConvertingMap: targetColor to: destDepth keepSubPixelAA: keepSubPix ]! ! !Color class methodsFor: 'colormaps' stamp: 'lr 7/4/2009 10:42'! computeColormapFrom: sourceDepth to: destDepth "Compute a colorMap for translating between the given depths. A colormap is a Bitmap whose entries contain the pixel values for the destination depth. Typical clients use cachedColormapFrom:to: instead." | map bitsPerColor | sourceDepth < 16 ifTrue: [ "source is 1-, 2-, 4-, or 8-bit indexed color" map := (IndexedColors copyFrom: 1 to: (1 bitShift: sourceDepth)) collect: [ :c | c pixelValueForDepth: destDepth ]. map := map as: Bitmap ] ifFalse: [ "source is 16-bit or 32-bit RGB" destDepth > 8 ifTrue: [ bitsPerColor := 5 "retain maximum color resolution" ] ifFalse: [ bitsPerColor := 4 ]. map := self computeRGBColormapFor: destDepth bitsPerColor: bitsPerColor ]. "Note: zero is transparent except when source depth is one-bit deep" sourceDepth > 1 ifTrue: [ map at: 1 put: 0 ]. ^ map! ! !Color class methodsFor: 'colormaps' stamp: 'StephaneDucasse 10/17/2009 17:15'! computeIndexedColorConvertingMap: targetColor from: sourceDepth to: destDepth | map f c | map := (IndexedColors copyFrom: 1 to: (1 bitShift: sourceDepth)) collect: [ :cc | f := 1.0 - ((cc red + cc green + cc blue) / 3.0). c := targetColor notNil ifTrue: [ destDepth = 32 ifTrue: [ targetColor * f alpha: f ] ifFalse: [ targetColor alphaMixed: f * 1.5 with: Color white ] ] ifFalse: [ cc ]. destDepth = 32 ifTrue: [ c pixelValueForDepth: destDepth ] ifFalse: [ f = 0.0 ifTrue: [ 0 ] ifFalse: [ c pixelValueForDepth: destDepth ] ] ]. map := map as: Bitmap. ^ map! ! !Color class methodsFor: 'colormaps' stamp: 'StephaneDucasse 10/17/2009 17:15'! computeRGBColorConvertingMap: targetColor to: destDepth keepSubPixelAA: keepSubPix "Builds a colormap intended to convert from subpixelAA black values to targetColor values. keepSubPix ifTrue: [ Answer colors that also include subpixelAA ] ifFalse: [ Take fullpixel luminance level. Apply it to targetColor. I.e. answer colors with NO subpixelAA ]" | mask map c bitsPerColor r g b f v | destDepth > 8 ifTrue: [ bitsPerColor := 5 "retain maximum color resolution" ] ifFalse: [ bitsPerColor := 4 ]. "Usually a bit less is enough, but make it configurable" bitsPerColor := bitsPerColor min: Preferences aaFontsColormapDepth. mask := (1 bitShift: bitsPerColor) - 1. map := Bitmap new: (1 bitShift: 3 * bitsPerColor). 0 to: map size - 1 do: [ :i | r := (i bitShift: 0 - (2 * bitsPerColor)) bitAnd: mask. g := (i bitShift: 0 - bitsPerColor) bitAnd: mask. b := (i bitShift: 0) bitAnd: mask. f := 1.0 - ((r + g + b) / 3.0 / mask). c := targetColor notNil ifTrue: [ (keepSubPix and: [ destDepth > 8 ]) ifTrue: [ Color r: (1.0 - (r / mask)) * targetColor red g: (1.0 - (g / mask)) * targetColor green b: (1.0 - (b / mask)) * targetColor blue alpha: f * targetColor alpha "alpha will be ignored below, in #pixelValueForDepth: if destDepth ~= 32" ] ifFalse: [ destDepth = 32 ifTrue: [ targetColor * f alpha: f * targetColor alpha ] ifFalse: [ targetColor alphaMixed: f * 1.5 with: Color white ] ] ] ifFalse: [ Color r: r g: g b: b range: mask ]. "This is currently used only to keep some SubPixelAA on destDepth = 8, using a single pass of rule 25" v := destDepth = 32 ifTrue: [ c pixelValueForDepth: destDepth ] ifFalse: [ f < 0.1 ifTrue: [ 0 ] ifFalse: [ c pixelValueForDepth: destDepth ] ]. map at: i + 1 put: v ]. ^ map! ! !Color class methodsFor: 'colormaps' stamp: 'lr 7/4/2009 10:42'! computeRGBColormapFor: destDepth bitsPerColor: bitsPerColor "Compute a colorMap for translating from 16-bit or 32-bit RGB color to the given depth, using the given number of of bits per color component." | mask map c | (#(3 4 5 ) includes: bitsPerColor) ifFalse: [ self error: 'BitBlt only supports 3, 4, or 5 bits per color component' ]. mask := (1 bitShift: bitsPerColor) - 1. map := Bitmap new: (1 bitShift: 3 * bitsPerColor). 0 to: map size - 1 do: [ :i | c := Color r: ((i bitShift: 0 - (2 * bitsPerColor)) bitAnd: mask) g: ((i bitShift: 0 - bitsPerColor) bitAnd: mask) b: ((i bitShift: 0) bitAnd: mask) range: mask. map at: i + 1 put: (c pixelValueForDepth: destDepth) ]. map at: 1 put: (Color transparent pixelWordForDepth: destDepth). "zero always transparent" ^ map! ! !Color class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! colorRampForDepth: depth extent: aPoint "Returns a form of the given size showing R, G, B, and gray ramps for the given depth. Useful for testing color conversions between different depths." "(Color colorRampForDepth: Display depth extent: 256@80) display" "(Color colorRampForDepth: 32 extent: 256@80) displayOn: Display at: 0@0 rule: Form paint" | f dx dy r | f := Form extent: aPoint depth: depth. dx := aPoint x // 256. dy := aPoint y // 4. 0 to: 255 do: [ :i | r := (dx * i) @ 0 extent: dx @ dy. f fill: r fillColor: (Color r: i g: 0 b: 0 range: 255). r := r translateBy: 0 @ dy. f fill: r fillColor: (Color r: 0 g: i b: 0 range: 255). r := r translateBy: 0 @ dy. f fill: r fillColor: (Color r: 0 g: 0 b: i range: 255). r := r translateBy: 0 @ dy. f fill: r fillColor: (Color r: i g: i b: i range: 255) ]. ^ f! ! !Color class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! hotColdShades: thisMany "An array of thisMany colors showing temperature from blue to red to white hot. (Later improve this by swinging in hue.) " "Color showColors: (Color hotColdShades: 25)" | n s1 s2 s3 s4 s5 | thisMany < 5 ifTrue: [ ^ self error: 'must be at least 5 shades' ]. n := thisMany // 5. s1 := self white mix: self yellow shades: thisMany - (n * 4). s2 := self yellow mix: self red shades: n + 1. s2 := s2 copyFrom: 2 to: n + 1. s3 := self red mix: self green darker shades: n + 1. s3 := s3 copyFrom: 2 to: n + 1. s4 := self green darker mix: self blue shades: n + 1. s4 := s4 copyFrom: 2 to: n + 1. s5 := self blue mix: self black shades: n + 1. s5 := s5 copyFrom: 2 to: n + 1. ^ s1 , s2 , s3 , s4 , s5! ! !Color class methodsFor: 'examples'! showColorCube "Show a 12x12x12 color cube." "Color showColorCube" 0 to: 11 do: [:r | 0 to: 11 do: [:g | 0 to: 11 do: [:b | Display fill: (((r*60) + (b*5)) @ (g*5) extent: 5@5) fillColor: (Color r: r g: g b: b range: 11)]]]. ! ! !Color class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! showColors: colorList "Display the given collection of colors across the top of the Display." | w r | w := Display width // colorList size. r := 0 @ 0 extent: w @ ((w min: 30) max: 10). colorList do: [ :c | Display fill: r fillColor: c. r := r translateBy: w @ 0 ]! ! !Color class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! showHSVPalettes "Shows a palette of hues, varying the saturation and brightness for each one. Best results are with depths 16 and 32." "Color showHSVPalettes" | left top c | left := top := 0. 0 to: 179 by: 15 do: [ :h | 0 to: 10 do: [ :s | left := h * 4 + (s * 4). 0 to: 10 do: [ :v | c := Color h: h s: s asFloat / 10.0 v: v asFloat / 10.0. top := v * 4. Display fill: (left @ top extent: 4 @ 4) fillColor: c. c := Color h: h + 180 s: s asFloat / 10.0 v: v asFloat / 10.0. top := v * 4 + 50. Display fill: (left @ top extent: 4 @ 4) fillColor: c ] ] ]! ! !Color class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! showHuesInteractively "Shows a palette of hues at a (saturation, brightness) point determined by the mouse position. Click the mouse button to exit and return the selected (saturation, brightness) point." "Color showHuesInteractively" | p s v | [ Sensor anyButtonPressed ] whileFalse: [ p := Sensor cursorPoint. s := p x asFloat / 300.0. v := p y asFloat / 300.0. self showColors: (self wheel: 12 saturation: s brightness: v) ]. ^ (s min: 1.0) @ (v min: 1.0)! ! !Color class methodsFor: 'examples'! wheel: thisMany "Return a collection of thisMany colors evenly spaced around the color wheel." "Color showColors: (Color wheel: 12)" ^ Color wheel: thisMany saturation: 0.9 brightness: 0.7 ! ! !Color class methodsFor: 'examples'! wheel: thisMany saturation: s brightness: v "Return a collection of thisMany colors evenly spaced around the color wheel, all of the given saturation and brightness." "Color showColors: (Color wheel: 12 saturation: 0.4 brightness: 1.0)" "Color showColors: (Color wheel: 12 saturation: 0.8 brightness: 0.5)" ^ (Color h: 0.0 s: s v: v) wheel: thisMany ! ! !Color class methodsFor: 'initialization' stamp: 'lr 7/4/2009 10:42'! initialize "Color initialize" "Details: Externally, the red, green, and blue components of color are floats in the range [0.0..1.0]. Internally, they are represented as integers in the range [0..ComponentMask] packing into a small integer to save space and to allow fast hashing and equality testing. For a general description of color representations for computer graphics, including the relationship between the RGB and HSV color models used here, see Chapter 17 of Foley and van Dam, Fundamentals of Interactive Computer Graphics, Addison-Wesley, 1982." ComponentMask := 1023. HalfComponentMask := 512. "used to round up in integer calculations" ComponentMax := 1023.0. "a Float used to normalize components" RedShift := 20. GreenShift := 10. BlueShift := 0. PureRed := self r: 1 g: 0 b: 0. PureGreen := self r: 0 g: 1 b: 0. PureBlue := self r: 0 g: 0 b: 1. PureYellow := self r: 1 g: 1 b: 0. PureCyan := self r: 0 g: 1 b: 1. PureMagenta := self r: 1 g: 0 b: 1. RandomStream := Random new. self initializeIndexedColors. self initializeGrayToIndexMap. self initializeNames. self initializeHighLights! ! !Color class methodsFor: 'initialization' stamp: 'lr 7/4/2009 10:42'! initializeGrayToIndexMap "Build an array of gray values available in the 8-bit colormap. This array is indexed by a gray level between black (1) and white (256) and returns the pixel value for the corresponding gray level." "Note: This method must be called after initializeIndexedColors, since it uses IndexedColors." "Color initializeGrayToIndexMap" "record the level and index of each gray in the 8-bit color table" | grayLevels grayIndices c distToClosest dist indexOfClosest | grayLevels := OrderedCollection new. grayIndices := OrderedCollection new. "Note: skip the first entry, which is reserved for transparent" 2 to: IndexedColors size do: [ :i | c := IndexedColors at: i. c saturation = 0.0 ifTrue: [ "c is a gray" grayLevels add: c privateBlue >> 2. "top 8 bits; R, G, and B are the same" grayIndices add: i - 1 ] ]. "pixel values are zero-based" grayLevels := grayLevels asArray. grayIndices := grayIndices asArray. "for each gray level in [0..255], select the closest match" GrayToIndexMap := ByteArray new: 256. 0 to: 255 do: [ :level | distToClosest := 10000. "greater than distance to any real gray" 1 to: grayLevels size do: [ :i | dist := (level - (grayLevels at: i)) abs. dist < distToClosest ifTrue: [ distToClosest := dist. indexOfClosest := grayIndices at: i ] ]. GrayToIndexMap at: level + 1 put: indexOfClosest ]! ! !Color class methodsFor: 'initialization' stamp: 'lr 7/4/2009 10:42'! initializeHighLights "Create a set of Bitmaps for quickly reversing areas of the screen without converting colors. " "Color initializeHighLights" | t | t := Array new: 32. t at: 1 put: (Bitmap with: 4294967295). t at: 2 put: (Bitmap with: 4294967295). t at: 4 put: (Bitmap with: 1431655765). t at: 8 put: (Bitmap with: 117901063). t at: 16 put: (Bitmap with: 4294967295). t at: 32 put: (Bitmap with: 4294967295). HighLightBitmaps := t! ! !Color class methodsFor: 'initialization' stamp: 'lr 7/4/2009 10:42'! initializeIndexedColors "Build an array of colors corresponding to the fixed colormap used for display depths of 1, 2, 4, or 8 bits." "Color initializeIndexedColors" | a index grayVal | a := Array new: 256. "1-bit colors (monochrome)" a at: 1 put: (Color r: 1.0 g: 1.0 b: 1.0). "white or transparent" a at: 2 put: (Color r: 0.0 g: 0.0 b: 0.0). "black" "additional colors for 2-bit color" a at: 3 put: (Color r: 1.0 g: 1.0 b: 1.0). "opaque white" a at: 4 put: (Color r: 0.5 g: 0.5 b: 0.5). "1/2 gray" "additional colors for 4-bit color" a at: 5 put: (Color r: 1.0 g: 0.0 b: 0.0). "red" a at: 6 put: (Color r: 0.0 g: 1.0 b: 0.0). "green" a at: 7 put: (Color r: 0.0 g: 0.0 b: 1.0). "blue" a at: 8 put: (Color r: 0.0 g: 1.0 b: 1.0). "cyan" a at: 9 put: (Color r: 1.0 g: 1.0 b: 0.0). "yellow" a at: 10 put: (Color r: 1.0 g: 0.0 b: 1.0). "magenta" a at: 11 put: (Color r: 0.125 g: 0.125 b: 0.125). "1/8 gray" a at: 12 put: (Color r: 0.25 g: 0.25 b: 0.25). "2/8 gray" a at: 13 put: (Color r: 0.375 g: 0.375 b: 0.375). "3/8 gray" a at: 14 put: (Color r: 0.625 g: 0.625 b: 0.625). "5/8 gray" a at: 15 put: (Color r: 0.75 g: 0.75 b: 0.75). "6/8 gray" a at: 16 put: (Color r: 0.875 g: 0.875 b: 0.875). "7/8 gray" "additional colors for 8-bit color" "24 more shades of gray (1/32 increments but not repeating 1/8 increments)" index := 17. 1 to: 31 do: [ :v | v \\ 4 = 0 ifFalse: [ grayVal := v / 32.0. a at: index put: (Color r: grayVal g: grayVal b: grayVal). index := index + 1 ] ]. "The remainder of color table defines a color cube with six steps for each primary color. Note that the corners of this cube repeat previous colors, but this simplifies the mapping between RGB colors and color map indices. This color cube spans indices 40 through 255 (indices 41-256 in this 1-based array)." 0 to: 5 do: [ :r | 0 to: 5 do: [ :g | 0 to: 5 do: [ :b | index := 41 + (36 * r + (6 * b) + g). index > 256 ifTrue: [ self error: 'index out of range in color table compuation' ]. a at: index put: (Color r: r g: g b: b range: 5) ] ] ]. IndexedColors := a! ! !Color class methodsFor: 'initialization' stamp: 'lr 7/4/2009 10:42'! initializeTranslucentPatterns "Color initializeTranslucentPatterns" | mask bits pattern patternList | TranslucentPatterns := Array new: 8. #(1 2 4 8 ) do: [ :d | patternList := Array new: 5. mask := (1 bitShift: d) - 1. bits := 2 * d. [ bits >= 32 ] whileFalse: [ mask := mask bitOr: (mask bitShift: bits). "double the length of mask" bits := bits + bits ]. "0% pattern" pattern := Bitmap with: 0 with: 0. patternList at: 1 put: pattern. "25% pattern" pattern := Bitmap with: mask with: 0. patternList at: 2 put: pattern. "50% pattern" pattern := Bitmap with: mask with: mask bitInvert32. patternList at: 3 put: pattern. "75% pattern" pattern := Bitmap with: mask with: 4294967295. patternList at: 4 put: pattern. "100% pattern" pattern := Bitmap with: 4294967295 with: 4294967295. patternList at: 5 put: pattern. TranslucentPatterns at: d put: patternList ]! ! !Color class methodsFor: 'initialization' stamp: 'lr 7/4/2009 10:42'! named: newName put: aColor "Add a new color to the list and create an access message and a class variable for it. The name should start with a lowercase letter. (The class variable will start with an uppercase letter.) (Color colorNames) returns a list of all color names. " | str cap sym accessor csym | str := newName asString. sym := str asSymbol. cap := str capitalized. csym := cap asSymbol. (self class canUnderstand: sym) ifFalse: [ "define access message" accessor := str , (String with: Character cr with: Character tab) , '^' , cap. self class compile: accessor classified: 'named colors' ]. (self classPool includesKey: csym) ifFalse: [ self addClassVarName: cap ]. (ColorNames includes: sym) ifFalse: [ ColorNames add: sym ]. ^ self classPool at: csym put: aColor! ! !Color class methodsFor: 'instance creation' stamp: 'ar 4/10/2005 18:45'! colorFrom: parm "Return an instantiated color from parm. If parm is already a color, return it, else return the result of my performing it if it's a symbol or, if it is a list, it can either be an array of three numbers, which will be interpreted as RGB values, or a list of symbols, the first of which is sent to me and then the others of which are in turn sent to the prior result, thus allowing entries of the form #(blue darker). Else just return the thing" | aColor firstParm | (parm isKindOf: Color) ifTrue: [^ parm]. (parm isSymbol) ifTrue: [^ self perform: parm]. (parm isString) ifTrue: [^ self fromString: parm]. ((parm isKindOf: SequenceableCollection) and: [parm size > 0]) ifTrue: [firstParm := parm first. (firstParm isKindOf: Number) ifTrue: [^ self fromRgbTriplet: parm]. aColor := self colorFrom: firstParm. parm doWithIndex: [:sym :ind | ind > 1 ifTrue: [aColor := aColor perform: sym]]. ^ aColor]. ^ parm " Color colorFrom: #(blue darker) Color colorFrom: Color blue darker Color colorFrom: #blue Color colorFrom: #(0.0 0.0 1.0) "! ! !Color class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! colorFromPixelValue: p depth: d "Convert a pixel value for the given display depth into a color." "Details: For depths of 8 or less, the pixel value is simply looked up in a table. For greater depths, the color components are extracted and converted into a color." | r g b alpha | d = 8 ifTrue: [ ^ IndexedColors at: (p bitAnd: 255) + 1 ]. d = 4 ifTrue: [ ^ IndexedColors at: (p bitAnd: 15) + 1 ]. d = 2 ifTrue: [ ^ IndexedColors at: (p bitAnd: 3) + 1 ]. d = 1 ifTrue: [ ^ IndexedColors at: (p bitAnd: 1) + 1 ]. d = 16 | (d = 15) ifTrue: [ "five bits per component" r := (p bitShift: -10) bitAnd: 31. g := (p bitShift: -5) bitAnd: 31. b := p bitAnd: 31. (r = 0 and: [ g = 0 ]) ifTrue: [ b = 0 ifTrue: [ ^ Color transparent ]. b = 1 ifTrue: [ ^ Color black ] ]. ^ Color r: r g: g b: b range: 31 ]. d = 32 ifTrue: [ "eight bits per component; 8 bits of alpha" r := (p bitShift: -16) bitAnd: 255. g := (p bitShift: -8) bitAnd: 255. b := p bitAnd: 255. alpha := p bitShift: -24. alpha = 0 ifTrue: [ ^ Color transparent ]. (r = 0 and: [ g = 0 and: [ b = 0 ] ]) ifTrue: [ ^ Color transparent ]. alpha < 255 ifTrue: [ ^ (Color r: r g: g b: b range: 255) alpha: alpha asFloat / 255.0 ] ifFalse: [ ^ Color r: r g: g b: b range: 255 ] ]. d = 12 ifTrue: [ "four bits per component" r := (p bitShift: -8) bitAnd: 15. g := (p bitShift: -4) bitAnd: 15. b := p bitAnd: 15. ^ Color r: r g: g b: b range: 15 ]. d = 9 ifTrue: [ "three bits per component" r := (p bitShift: -6) bitAnd: 7. g := (p bitShift: -3) bitAnd: 7. b := p bitAnd: 7. ^ Color r: r g: g b: b range: 7 ]. self error: 'unknown pixel depth: ' , d printString! ! !Color class methodsFor: 'instance creation' stamp: 'mir 7/21/1999 11:54'! fromArray: colorDef colorDef size == 3 ifTrue: [^self r: (colorDef at: 1) g: (colorDef at: 2) b: (colorDef at: 3)]. colorDef size == 0 ifTrue: [^Color transparent]. colorDef size == 4 ifTrue: [^(TranslucentColor r: (colorDef at: 1) g: (colorDef at: 2) b: (colorDef at: 3)) alpha: (colorDef at: 4)]. self error: 'Undefined color definition'! ! !Color class methodsFor: 'instance creation' stamp: 'sw 8/8/97 22:03'! fromRgbTriplet: list ^ self r: list first g: list second b: list last! ! !Color class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! fromString: aString "for HTML color spec: #FFCCAA or white/black" "Color fromString: '#FFCCAA'. Color fromString: 'white'. Color fromString: 'orange'" | aColorHex red green blue | aString isEmptyOrNil ifTrue: [ ^ Color white ]. aString first = $# ifTrue: [ aColorHex := aString copyFrom: 2 to: aString size ] ifFalse: [ aColorHex := aString ]. [ aColorHex size = 6 ifTrue: [ aColorHex := aColorHex asUppercase. red := ('16r' , (aColorHex copyFrom: 1 to: 2)) asNumber / 255. green := ('16r' , (aColorHex copyFrom: 3 to: 4)) asNumber / 255. blue := ('16r' , (aColorHex copyFrom: 5 to: 6)) asNumber / 255. ^ self r: red g: green b: blue ] ] ifError: [ :err :rcvr | "not a hex color triplet" ]. "try to match aColorHex with known named colors" aColorHex := aColorHex asLowercase. ^ self perform: (ColorNames detect: [ :i | i asString asLowercase = aColorHex ] ifNone: [ #white ])! ! !Color class methodsFor: 'instance creation' stamp: 'jm 12/4/97 13:05'! gray: brightness "Return a gray shade with the given brightness in the range [0.0..1.0]." ^ self basicNew setRed: brightness green: brightness blue: brightness ! ! !Color class methodsFor: 'instance creation'! h: hue s: saturation v: brightness "Create a color with the given hue, saturation, and brightness. Hue is given as the angle in degrees of the color on the color circle where red is zero degrees. Saturation and brightness are numbers in [0.0..1.0] where larger values are more saturated or brighter colors. For example, (Color h: 0 s: 1 v: 1) is pure red." "Note: By convention, brightness is abbreviated 'v' to to avoid confusion with blue." ^ self basicNew setHue: hue saturation: saturation brightness: brightness! ! !Color class methodsFor: 'instance creation' stamp: 'dew 3/19/2002 23:49'! h: h s: s v: v alpha: alpha ^ (self h: h s: s v: v) alpha: alpha! ! !Color class methodsFor: 'instance creation'! new ^ self r: 0.0 g: 0.0 b: 0.0! ! !Color class methodsFor: 'instance creation' stamp: 'jm 12/4/97 13:04'! r: r g: g b: b "Return a color with the given r, g, and b components in the range [0.0..1.0]." ^ self basicNew setRed: r green: g blue: b ! ! !Color class methodsFor: 'instance creation'! r: r g: g b: b alpha: alpha ^ (self r: r g: g b: b) alpha: alpha! ! !Color class methodsFor: 'instance creation'! r: r g: g b: b range: range "Return a color with the given r, g, and b components specified as integers in the range [0..r]. This avoids the floating point arithmetic in the red:green:blue: message and is thus a bit faster for certain applications (such as computing a sequence of colors for a palette)." ^ self basicNew setRed: r green: g blue: b range: range! ! !Color class methodsFor: 'instance creation'! random "Return a random color that isn't too dark or under-saturated." ^ self basicNew setHue: (360.0 * RandomStream next) saturation: (0.3 + (RandomStream next * 0.7)) brightness: (0.4 + (RandomStream next * 0.6))! ! !Color class methodsFor: 'named colors'! black ^Black! ! !Color class methodsFor: 'named colors'! blue ^Blue! ! !Color class methodsFor: 'named colors'! brown ^Brown! ! !Color class methodsFor: 'named colors'! cyan ^Cyan! ! !Color class methodsFor: 'named colors'! darkGray ^DarkGray! ! !Color class methodsFor: 'named colors'! gray ^Gray! ! !Color class methodsFor: 'named colors'! green ^Green! ! !Color class methodsFor: 'named colors'! lightBlue ^LightBlue! ! !Color class methodsFor: 'named colors'! lightBrown ^LightBrown! ! !Color class methodsFor: 'named colors'! lightCyan ^LightCyan! ! !Color class methodsFor: 'named colors'! lightGray ^LightGray! ! !Color class methodsFor: 'named colors'! lightGreen ^LightGreen! ! !Color class methodsFor: 'named colors'! lightMagenta ^LightMagenta! ! !Color class methodsFor: 'named colors'! lightOrange ^LightOrange! ! !Color class methodsFor: 'named colors'! lightRed ^LightRed! ! !Color class methodsFor: 'named colors'! lightYellow ^LightYellow! ! !Color class methodsFor: 'named colors'! magenta ^Magenta! ! !Color class methodsFor: 'named colors'! orange ^Orange! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:06'! paleBlue ^(Color r: 0.87 g: 0.976 b: 0.995) ! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:07'! paleBuff ^(Color r: 0.995 g: 0.979 b: 0.921)! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:06'! paleGreen ^(Color r: 0.874 g: 1.0 b: 0.835)! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:05'! paleMagenta ^(Color r: 1.0 g: 0.901 b: 1.0)! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:03'! paleOrange ^ (Color r: 0.991 g: 0.929 b: 0.843) ! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:03'! palePeach ^(Color r: 1.0 g: 0.929 b: 0.835)! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:07'! paleRed ^(Color r: 1.0 g: 0.901 b: 0.901)! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:02'! paleTan ^(Color r: 0.921 g: 0.878 b: 0.78) ! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:05'! paleYellow ^(Color r: 1.0 g: 1.0 b: 0.85)! ! !Color class methodsFor: 'named colors'! red ^Red! ! !Color class methodsFor: 'named colors' stamp: 'wod 5/24/1998 01:56'! tan ^ Color r: 0.8 g: 0.8 b: 0.5! ! !Color class methodsFor: 'named colors'! transparent ^Transparent! ! !Color class methodsFor: 'named colors'! veryDarkGray ^VeryDarkGray! ! !Color class methodsFor: 'named colors'! veryLightGray ^VeryLightGray! ! !Color class methodsFor: 'named colors' stamp: 'yo 8/28/2008 01:06'! veryPaleRed ^(Color r: 1.0 g: 0.948 b: 0.948)! ! !Color class methodsFor: 'named colors'! veryVeryDarkGray ^VeryVeryDarkGray! ! !Color class methodsFor: 'named colors'! veryVeryLightGray ^VeryVeryLightGray! ! !Color class methodsFor: 'named colors'! white ^White! ! !Color class methodsFor: 'named colors'! yellow ^Yellow! ! !Color class methodsFor: 'other'! colorNames "Return a collection of color names." ^ ColorNames! ! !Color class methodsFor: 'other' stamp: 'BG 3/16/2005 08:18'! hex: aFloat "Return an hexadecimal two-digits string between 00 and FF for a float between 0.0 and 1.0" | str | str := ((aFloat * 255) asInteger printStringHex) asLowercase. str size = 1 ifTrue: [^'0',str] ifFalse: [^str]! ! !Color class methodsFor: 'other'! indexedColors ^ IndexedColors! ! !Color class methodsFor: 'other' stamp: 'lr 7/4/2009 10:42'! maskingMap: depth "Return a color map that maps all colors except transparent to words of all ones. Used to create a mask for a Form whose transparent pixel value is zero. Cache the most recently used map." | sizeNeeded | depth <= 8 ifTrue: [ sizeNeeded := 1 bitShift: depth ] ifFalse: [ sizeNeeded := 4096 ]. (MaskingMap == nil or: [ MaskingMap size ~= sizeNeeded ]) ifTrue: [ MaskingMap := Bitmap new: sizeNeeded withAll: 4294967295. MaskingMap at: 1 put: 0 "transparent" ]. ^ MaskingMap! ! !Color class methodsFor: 'other' stamp: 'lr 7/4/2009 10:42'! pixelScreenForDepth: depth "Return a 50% stipple containing alternating pixels of all-zeros and all-ones to be used as a mask at the given depth." | mask bits | mask := (1 bitShift: depth) - 1. bits := 2 * depth. [ bits >= 32 ] whileFalse: [ mask := mask bitOr: (mask bitShift: bits). "double the length of mask" bits := bits + bits ]. ^ Bitmap with: mask with: mask bitInvert32! ! !Color class methodsFor: 'other'! quickHighLight: depth "Quickly return a Bitblt-ready raw colorValue for highlighting areas. 6/22/96 tk" ^ HighLightBitmaps at: depth! ! !Color class methodsFor: 'other' stamp: 'lr 7/4/2009 10:42'! shutDown "Color shutDown" ColorChart := nil. "Palette of colors for the user to pick from" CachedColormaps := nil. "Maps to translate between color depths" MaskingMap := nil "Maps all colors except transparent to black for creating a mask"! ! !Color class methodsFor: 'other' stamp: 'ar 2/16/2000 21:56'! translucentMaskFor: alphaValue depth: d "Return a pattern representing a mask usable for stipple transparency" ^(TranslucentPatterns at: d) at: ((alphaValue min: 1.0 max: 0.0) * 4) rounded + 1! ! ArrayedCollection variableWordSubclass: #ColorArray instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Collections-Arrayed'! !ColorArray methodsFor: 'accessing' stamp: 'ar 3/3/2001 20:03'! at: index ^(super at: index) asColorOfDepth: 32! ! !ColorArray methodsFor: 'accessing' stamp: 'ar 3/3/2001 20:04'! at: index put: aColor ^super at: index put: (aColor pixelWordForDepth: 32).! ! !ColorArray methodsFor: 'converting' stamp: 'ar 3/3/2001 20:06'! asColorArray ^self! ! !ColorArray methodsFor: 'converting' stamp: 'RAA 3/8/2001 06:24'! bytesPerElement ^4! ! ColorPresenterMorph subclass: #ColorChooserMorph uses: TEnableOnHaloMenu instanceVariableNames: 'setColorSelector enabled getEnabledSelector' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !ColorChooserMorph commentStamp: 'gvc 5/18/2007 13:45' prior: 0! ColorPresenter that opens a colour selector when clicked.! !ColorChooserMorph methodsFor: 'accessing' stamp: 'gvc 10/12/2006 13:47'! getEnabledSelector "Answer the value of getEnabledSelector" ^ getEnabledSelector! ! !ColorChooserMorph methodsFor: 'accessing' stamp: 'gvc 10/12/2006 13:51'! getEnabledSelector: anObject "Set the value of getEnabledSelector" getEnabledSelector := anObject. self updateEnabled! ! !ColorChooserMorph methodsFor: 'as yet unclassified'! addToggleItemsToHaloMenu: aCustomMenu "Add toggle-items to the halo menu" super addToggleItemsToHaloMenu: aCustomMenu. aCustomMenu addUpdating: #enabledString target: self action: #toggleEnabled! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 11:03'! chooseColor "Popup the color picker for now." |newColor| newColor := self theme chooseColorIn: ((self ownerThatIsA: SystemWindow) ifNil: [self]) title: 'Choose Color' color: self labelMorph color. newColor ifNil: [^self]. self labelMorph color: newColor. self solidLabelMorph color: newColor asNontranslucentColor. self setColorSelector ifNotNil: [self model perform: self setColorSelector with: newColor]! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/12/2006 13:46'! enabled "Answer the enabled state of the receiver." ^enabled! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/30/2009 13:57'! enabled: aBoolean "Set the enabled state of the receiver." enabled := aBoolean. self contentMorph ifNotNilDo: [:m | m enabled: aBoolean]. self changed: #enabled! ! !ColorChooserMorph methodsFor: 'as yet unclassified'! enabledString "Answer the string to be shown in a menu to represent the 'enabled' status" ^ (self enabled ifTrue: [''] ifFalse: ['']), 'enabled' translated! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/22/2007 11:44'! initialize "Initialize the receiver." enabled := true. super initialize! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/8/2008 19:40'! newContentMorph "Answer a new button morph" |b| b := (self theme newButtonIn: self for: self getState: nil action: #chooseColor arguments: #() getEnabled: #enabled label: (self newHatchMorph layoutInset: 2) help: nil) hResizing: #spaceFill. b contentHolder hResizing: #spaceFill. ^b! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 09:46'! on: anObject color: getColSel changeColor: setColSel "Set the receiver to the given model parameterized by the given message selectors." self on: anObject color: getColSel; setColorSelector: setColSel! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/14/2009 18:41'! setColorSelector "Answer the value of setColorSelector" ^ setColorSelector! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/14/2009 18:41'! setColorSelector: anObject "Set the value of setColorSelector" setColorSelector := anObject! ! !ColorChooserMorph methodsFor: 'as yet unclassified'! toggleEnabled "Toggle the enabled state." self enabled: self enabled not! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/12/2006 13:51'! update: aSymbol "Refer to the comment in View|update:." super update: aSymbol. aSymbol == self getEnabledSelector ifTrue: [self updateEnabled. ^ self]! ! !ColorChooserMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/8/2009 13:25'! updateEnabled "Update the enablement state." self model ifNotNil: [ self getEnabledSelector ifNotNil: [ self enabled: (self model perform: self getEnabledSelector)]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ColorChooserMorph class uses: TEnableOnHaloMenu classTrait instanceVariableNames: ''! !ColorChooserMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 09:49'! on: anObject color: getSel changeColor: setSel "Answer a new instance of the receiver on the given model using the given selectors as the interface." ^self new on: anObject color: getSel changeColor: setSel! ! SolidFillStyle subclass: #ColorFillStyle instanceVariableNames: 'origin extent' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-FillStyles'! !ColorFillStyle commentStamp: 'gvc 12/8/2008 13:05' prior: 0! Simple fillstyle that draws a color at the specified origin with option extent.! !ColorFillStyle methodsFor: 'accessing' stamp: 'gvc 12/8/2008 13:05'! extent "Answer the value of extent" ^ extent! ! !ColorFillStyle methodsFor: 'accessing' stamp: 'gvc 12/8/2008 13:05'! extent: anObject "Set the value of extent" extent := anObject! ! !ColorFillStyle methodsFor: 'accessing' stamp: 'gvc 12/8/2008 13:05'! origin "Answer the value of origin" ^ origin! ! !ColorFillStyle methodsFor: 'accessing' stamp: 'gvc 12/8/2008 13:05'! origin: anObject "Set the value of origin" origin := anObject! ! !ColorFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 12/8/2008 13:11'! fillRectangle: aRectangle on: aCanvas "Fill the given rectangle on the given canvas with the receiver." |o c| o := self origin ifNil: [aRectangle origin] ifNotNil: [self origin]. c := self extent ifNil: [aRectangle corner] ifNotNil: [o + self extent]. aCanvas fillRectangle: (o corner: c) basicFillStyle: self! ! !ColorFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 12/8/2008 13:14'! isOrientedFill "Answer true if origin is not nil so that morph movement adjusts origin." ^self origin notNil! ! Form subclass: #ColorForm instanceVariableNames: 'colors cachedDepth cachedColormap' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Display Objects'! !ColorForm commentStamp: '' prior: 0! ColorForm is a normal Form plus a color map of up to 2^depth Colors. Typically, one reserves one entry in the color map for transparent. This allows 1, 3, 15, or 255 non-transparent colors in ColorForms of depths 1, 2, 4, and 8 bits per pixel. ColorForms don't support depths greater than 8 bits because that would require excessively large color maps with little real benefit, since 16-bit and 32-bit depths already support thousands and millions of colors. ColorForms have several uses: 1) Precise colors. You can have up to 256 true colors, instead being limited to the 8-bit color palette. 2) Easy transparency. Just store (Color transparent) at the desired position in the color map. 3) Cheap color remapping by changing the color map. A color map is an Array of up to 2^depth Color objects. A Bitmap colorMap is automatically computed and cached for rapid display. Note that if you change the color map, you must resubmit it via the colors: method to flush this cache. ColorForms can be a bit tricky. Note that: a) When you BitBlt from one ColorForm to another, you must remember to copy the color map of the source ColorForm to the destination ColorForm. b) A ColorForm's color map is an array of depth-independent Color objects. BitBlt requires a BitMap of actual pixel values, adjusted to the destination depth. These are different things!! ColorForms automatically maintain a cache of the BitBlt-style color map corresponding to the colors array for the last depth on which the ColorForm was displayed, so there should be little need for clients to work with BitBlt-style color maps. c) The default map for 8 bit depth has black in the first entry, not transparent. Say (cform colors at: 1 put: Color transparent). ! !ColorForm methodsFor: 'accessing' stamp: 'jm 11/14/97 17:39'! colors "Return my color palette." self ensureColorArrayExists. ^ colors ! ! !ColorForm methodsFor: 'accessing' stamp: 'ar 5/17/2001 15:45'! colors: colorList "Set my color palette to the given collection." | colorArray colorCount newColors | colorList ifNil: [ colors := cachedDepth := cachedColormap := nil. ^ self]. colorArray := colorList asArray. colorCount := colorArray size. newColors := Array new: (1 bitShift: self depth). 1 to: newColors size do: [:i | i <= colorCount ifTrue: [newColors at: i put: (colorArray at: i)] ifFalse: [newColors at: i put: Color transparent]]. colors := newColors. cachedDepth := nil. cachedColormap := nil. ! ! !ColorForm methodsFor: 'accessing' stamp: 'mir 7/21/1999 11:51'! colorsFromArray: colorArray | colorList | colorList := colorArray collect: [:colorDef | Color fromArray: colorDef]. self colors: colorList! ! !ColorForm methodsFor: 'color manipulation' stamp: 'di 11/11/1998 13:20'! asGrayScale "Return a grayscale ColorForm computed by mapping each color into its grayscale equivalent" ^ self copy colors: (colors collect: [:c | c isTransparent ifTrue: [c] ifFalse: [Color gray: c luminance]])! ! !ColorForm methodsFor: 'color manipulation' stamp: 'ar 5/17/2001 15:44'! colormapIfNeededForDepth: destDepth "Return a colormap for displaying the receiver at the given depth, or nil if no colormap is needed." | newMap | colors == nil ifTrue: [ "use the standard colormap" ^ Color colorMapIfNeededFrom: self depth to: destDepth]. (destDepth = cachedDepth and:[cachedColormap isColormap not]) ifTrue: [^ cachedColormap]. newMap := Bitmap new: colors size. 1 to: colors size do: [:i | newMap at: i put: ((colors at: i) pixelValueForDepth: destDepth)]. cachedDepth := destDepth. ^ cachedColormap := newMap. ! ! !ColorForm methodsFor: 'color manipulation' stamp: 'jm 4/18/98 20:34'! colorsUsed "Return a list of the colors actually used by this ColorForm." | myColor list | myColor := self colors. list := OrderedCollection new. self tallyPixelValues doWithIndex: [:count :i | count > 0 ifTrue: [list add: (myColor at: i)]]. ^ list asArray ! ! !ColorForm methodsFor: 'color manipulation' stamp: 'jm 11/16/97 11:18'! ensureTransparentColor "Ensure that the receiver (a) includes Color transparent in its color map and (b) that the entry for Color transparent is the first entry in its color map." | i | self error: 'not yet implemented'. (colors includes: Color transparent) ifTrue: [ (colors indexOf: Color transparent) = 1 ifTrue: [^ self]. "shift the entry for color transparent"] ifFalse: [ i := self unusedColormapEntry. i = 0 ifTrue: [self error: 'no color map entry is available']. colors at: i put: Color transparent. "shift the entry for color transparent"]. ! ! !ColorForm methodsFor: 'color manipulation' stamp: 'di 8/28/1998 15:48'! indexOfColor: aColor "Return the index of aColor in my color array" self ensureColorArrayExists. ^ colors indexOf: aColor ifAbsent: [0]! ! !ColorForm methodsFor: 'color manipulation' stamp: 'jm 10/19/1998 10:52'! mapColor: oldColor to: newColor "Replace all occurances of the given color with the given new color in my color map." self ensureColorArrayExists. 1 to: colors size do: [:i | (colors at: i) = oldColor ifTrue: [colors at: i put: newColor]]. self clearColormapCache. ! ! !ColorForm methodsFor: 'color manipulation' stamp: 'jm 11/16/97 09:08'! replaceColor: oldColor with: newColor "Replace all occurances of the given color with the given new color in my color map." self ensureColorArrayExists. 1 to: colors size do: [:i | (colors at: i) = oldColor ifTrue: [colors at: i put: newColor]]. self clearColormapCache. ! ! !ColorForm methodsFor: 'color manipulation' stamp: 'tk 3/2/98 15:42'! replaceColorAt: aPoint with: newColor "Replace a color map entry with newColor. The entry replaced is the one used by aPoint. If there are are two entries in the colorMap for the oldColor, just replace ONE!!!! There are often two whites or two blacks, and this is what you want, when replacing one." | oldIndex | self ensureColorArrayExists. oldIndex := self pixelValueAt: aPoint. colors at: oldIndex+1 put: newColor. self clearColormapCache. ! ! !ColorForm methodsFor: 'color manipulation' stamp: 'di 8/28/1998 15:49'! replaceColorAtIndex: index with: newColor "Replace a color map entry with newColor." self ensureColorArrayExists. colors at: index put: newColor. cachedColormap == nil ifFalse: [cachedColormap at: index put: (newColor pixelValueForDepth: cachedDepth)]! ! !ColorForm methodsFor: 'color manipulation' stamp: 'tk 3/2/98 11:26'! transparentAllPixelsLike: aPoint "Make all occurances of the given pixel value transparent. Very useful when two entries in the colorMap have the same value. This only changes ONE." self replaceColorAt: aPoint with: Color transparent. ! ! !ColorForm methodsFor: 'color manipulation' stamp: 'tk 3/2/98 11:27'! transparentColor: aColor "Make all occurances of the given color transparent. Note: for colors like black and white, which have two entries in the colorMap, this changes BOTH of them. Not always what you want." self replaceColor: aColor with: Color transparent. ! ! !ColorForm methodsFor: 'color manipulation' stamp: 'ar 5/28/2000 12:06'! twoToneFromDisplay: aRectangle backgroundColor: bgColor "Copy one-bit deep ColorForm from the Display using a color map that maps all colors except the background color to black. Used for caching the contents of inactive MVC windows." | map | (width = aRectangle width and: [height = aRectangle height]) ifFalse: [self setExtent: aRectangle extent depth: depth]. "make a color map mapping the background color to zero and all other colors to one" map := Bitmap new: (1 bitShift: (Display depth min: 9)). 1 to: map size do: [:i | map at: i put: 16rFFFFFFFF]. map at: (bgColor indexInMap: map) put: 0. (BitBlt current toForm: self) destOrigin: 0@0; sourceForm: Display; sourceRect: aRectangle; combinationRule: Form over; colorMap: map; copyBits. ! ! !ColorForm methodsFor: 'color mapping' stamp: 'ar 5/17/2001 15:44'! colormapIfNeededFor: destForm | newMap color pv | (self hasNonStandardPalette or:[destForm hasNonStandardPalette]) ifFalse:[ ^self colormapIfNeededForDepth: destForm depth. ]. colors == nil ifTrue: [ "use the standard colormap" ^ super colormapIfNeededFor: destForm]. (destForm depth = cachedDepth and:[cachedColormap isColormap]) ifTrue: [^ cachedColormap]. newMap := WordArray new: (1 bitShift: self depth). 1 to: colors size do: [:i | color := colors at: i. pv := destForm pixelValueFor: color. (pv = 0 and:[color isTransparent not]) ifTrue:[pv := 1]. newMap at: i put: pv]. cachedDepth := destForm depth. ^cachedColormap := ColorMap shifts: nil masks: nil colors: newMap.! ! !ColorForm methodsFor: 'copying' stamp: 'RAA 8/14/2000 10:45'! asCursorForm ^ (self asFormOfDepth: 32) offset: offset; as: StaticForm! ! !ColorForm methodsFor: 'copying' stamp: 'ar 10/24/2005 22:25'! blankCopyOf: aRectangle scaledBy: scale ^Form extent: (aRectangle extent * scale) truncated depth: 32! ! !ColorForm methodsFor: 'copying' stamp: 'ar 5/28/2000 12:06'! copy: aRect "Return a new ColorForm containing the portion of the receiver delineated by aRect." | newForm | newForm := self class extent: aRect extent depth: depth. ((BitBlt current destForm: newForm sourceForm: self fillColor: nil combinationRule: Form over destOrigin: 0@0 sourceOrigin: aRect origin extent: aRect extent clipRect: newForm boundingBox) colorMap: nil) copyBits. colors ifNotNil: [newForm colors: colors copy]. ^ newForm ! ! !ColorForm methodsFor: 'copying' stamp: 'jm 2/27/98 09:38'! deepCopy ^ self shallowCopy bits: bits copy; offset: offset copy; colors: colors ! ! !ColorForm methodsFor: 'displaying' stamp: 'di 7/17/97 10:04'! displayOnPort: port at: location port copyForm: self to: location rule: Form paint! ! !ColorForm methodsFor: 'displaying' stamp: 'ar 12/14/2001 18:14'! maskingMap "Return a color map that maps all colors except transparent to words of all ones. Used to create a mask for a Form whose transparent pixel value is zero." | maskingMap | maskingMap := Bitmap new: (1 bitShift: depth) withAll: 16rFFFFFFFF. 1 to: colors size do:[:i| (colors at: i) isTransparent ifTrue:[maskingMap at: i put: 0]. ]. colors size+1 to: maskingMap size do:[:i| maskingMap at: i put: 0]. ^maskingMap! ! !ColorForm methodsFor: 'filein/out' stamp: 'ar 3/3/2001 20:07'! hibernate "Make myself take up less space. See comment in Form>hibernate." super hibernate. self clearColormapCache. colors ifNotNil:[colors := colors asColorArray].! ! !ColorForm methodsFor: 'filein/out' stamp: 'mu 8/17/2003 00:46'! readAttributesFrom: aBinaryStream super readAttributesFrom: aBinaryStream. colors := ColorArray new: (2 raisedTo: depth). 1 to: colors size do: [:idx | colors basicAt: idx put: (aBinaryStream nextLittleEndianNumber: 4). ]. ! ! !ColorForm methodsFor: 'filein/out' stamp: 'bf 5/25/2000 16:31'! storeOn: aStream aStream nextPut: $(. super storeOn: aStream. aStream cr; tab; nextPutAll: 'colorsFromArray: #('. self colors do: [:color | color storeArrayOn: aStream]. aStream nextPutAll: ' ))'.! ! !ColorForm methodsFor: 'filein/out' stamp: 'ar 3/3/2001 20:07'! unhibernate colors ifNotNil:[colors := colors asArray]. ^super unhibernate. ! ! !ColorForm methodsFor: 'filein/out' stamp: 'mu 8/17/2003 00:42'! writeAttributesOn: file | colorArray | super writeAttributesOn: file. colorArray := self colors asColorArray. 1 to: (2 raisedTo: depth) do: [:idx | file nextLittleEndianNumber: 4 put: (colorArray basicAt: idx). ] ! ! !ColorForm methodsFor: 'pixel accessing' stamp: 'jm 11/14/97 17:25'! colorAt: aPoint "Return the color of the pixel at aPoint." ^ self colors at: (self pixelValueAt: aPoint) + 1 ! ! !ColorForm methodsFor: 'pixel accessing' stamp: 'jm 11/14/97 17:25'! colorAt: aPoint put: aColor "Store the given color into the pixel at aPoint. The given color must match one of the colors in the receiver's colormap." | i | i := self colors indexOf: aColor ifAbsent: [^ self error: 'trying to use a color that is not in my colormap']. self pixelValueAt: aPoint put: i - 1. ! ! !ColorForm methodsFor: 'pixel accessing' stamp: 'tk 10/21/97 12:27'! isTransparentAt: aPoint "Return true if the receiver is transparent at the given point." ^ (self colorAt: aPoint) isTransparent ! ! !ColorForm methodsFor: 'pixel accessing' stamp: 'ar 5/28/2000 12:06'! pixelValueAt: aPoint "Return the raw pixel value at the given point. Typical clients use colorAt: to get a Color." "Details: To get the raw pixel value, be sure the peeker's colorMap is nil." ^ (BitBlt current bitPeekerFromForm: self) colorMap: nil; pixelAt: aPoint ! ! !ColorForm methodsFor: 'postscript generation'! asFormWithSingleTransparentColors | transparentIndexes | transparentIndexes := self transparentColorIndexes. transparentIndexes size <= 1 ifTrue:[^self] ifFalse:[^self mapTransparencies:transparentIndexes].! ! !ColorForm methodsFor: 'postscript generation'! decodeArray ^self depth = 1 ifTrue:['[1 0]'] ifFalse:['[0 255]'].! ! !ColorForm methodsFor: 'postscript generation'! getTransparencyUnificationLUT | lut transparentIndex | lut := Array new:colors size. transparentIndex := self indexOfColor:Color transparent. 1 to: colors size do: [ :i | lut at:i put:(((colors at:i) = Color transparent) ifTrue:[transparentIndex] ifFalse:[i])]. ! ! !ColorForm methodsFor: 'postscript generation'! mapTransparencies:transparentIndexes ^self deepCopy mapColors:transparentIndexes to:(transparentIndexes at:1).! ! !ColorForm methodsFor: 'postscript generation'! setColorspaceOn:aStream self depth = 1 ifTrue:[ aStream print:'/DeviceRGB setcolorspace 0 setgray'; cr. ] ifFalse:[ aStream print:'[ /Indexed /DeviceRGB '; write:self colors size-1; print:' <'. (self colormapIfNeededForDepth: 32 ) storeBits:20 to:0 on:aStream. aStream print:'> ] setcolorspace'; cr.]. ! ! !ColorForm methodsFor: 'postscript generation'! transparentColorIndexes ^(1 to: colors size) select: [ :index | (colors at:index) isTransparent ]. ! ! !ColorForm methodsFor: 'scaling, rotation' stamp: 'ar 3/15/1999 14:28'! flipBy: direction centerAt: aPoint | oldColors newForm | oldColors := colors. self colors: nil. newForm := super flipBy: direction centerAt: aPoint. self colors: oldColors. newForm colors: oldColors. ^newForm ! ! !ColorForm methodsFor: 'scaling, rotation' stamp: 'RAA 8/5/2000 18:12'! scaledToSize: newExtent "super method did not seem to work so well on ColorForms" ^(self asFormOfDepth: 16) scaledToSize: newExtent! ! !ColorForm methodsFor: 'testing' stamp: 'ar 5/27/2001 16:34'! isColorForm ^true! ! !ColorForm methodsFor: 'testing' stamp: 'ar 2/10/2004 17:18'! isTranslucent "Answer whether this form may be translucent" ^true! ! !ColorForm methodsFor: 'private' stamp: 'jm 11/16/97 09:07'! clearColormapCache cachedDepth := nil. cachedColormap := nil. ! ! !ColorForm methodsFor: 'private' stamp: 'jm 11/16/97 09:12'! depth: bitsPerPixel bitsPerPixel > 8 ifTrue: [self error: 'ColorForms only support depths up to 8 bits']. super depth: bitsPerPixel. ! ! !ColorForm methodsFor: 'private' stamp: 'ar 5/17/2001 15:44'! ensureColorArrayExists "Return my color palette." colors ifNil: [ self depth > 8 ifTrue: [^ self error: 'ColorForms only support depths up to 8 bits']. self colors: (Color indexedColors copyFrom: 1 to: (1 bitShift: self depth))]. ! ! !ColorForm methodsFor: 'private' stamp: 'jm 4/5/1999 10:11'! setColors: colorArray cachedColormap: aBitmap depth: anInteger "Semi-private. Set the color array, cached colormap, and cached colormap depth to avoid having to recompute the colormap when switching color palettes in animations." colors := colorArray. cachedDepth := anInteger. cachedColormap := aBitmap. ! ! !ColorForm methodsFor: 'private' stamp: 'jm 11/16/97 08:37'! setExtent: extent depth: bitsPerPixel "Create a virtual bit map with the given extent and bitsPerPixel." bitsPerPixel > 8 ifTrue: [self error: 'ColorForms only support depths up to 8 bits']. super setExtent: extent depth: bitsPerPixel. ! ! !ColorForm methodsFor: 'private' stamp: 'jm 2/24/98 18:53'! unusedColormapEntry "Return the index of an unused color map entry, or zero if there isn't one." | tallies | tallies := self tallyPixelValues. 1 to: tallies size do: [:i | (tallies at: i) = 0 ifTrue: [^ i]]. ^ 0 ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ColorForm class instanceVariableNames: ''! !ColorForm class methodsFor: 'as yet unclassified' stamp: 'StephaneDucasse 8/19/2009 23:24'! extent: extentPoint depth: bitsPerPixel "Answer an instance of me with blank bitmap of the given dimensions and depth max 8." ^ bitsPerPixel > 8 ifTrue: [ self basicNew setExtent: extentPoint depth: 8] ifFalse: [ self basicNew setExtent: extentPoint depth: bitsPerPixel] ! ! !ColorForm class methodsFor: 'as yet unclassified' stamp: 'nk 4/17/2004 19:44'! mappingWhiteToTransparentFrom: aFormOrCursor "Return a ColorForm copied from the given Form or Cursor with white mapped to transparent." | f map | aFormOrCursor depth <= 8 ifFalse: [ ^ self error: 'argument depth must be 8-bits per pixel or less']. (aFormOrCursor isColorForm) ifTrue: [ f := aFormOrCursor deepCopy. map := aFormOrCursor colors. ] ifFalse: [ f := ColorForm extent: aFormOrCursor extent depth: aFormOrCursor depth. f copyBits: aFormOrCursor boundingBox from: aFormOrCursor at: 0@0 clippingBox: aFormOrCursor boundingBox rule: Form over fillColor: nil. map := Color indexedColors copyFrom: 1 to: (1 bitShift: aFormOrCursor depth)]. map := map collect: [:c | c = Color white ifTrue: [Color transparent] ifFalse: [c]]. f colors: map. ^ f ! ! !ColorForm class methodsFor: 'as yet unclassified'! twoToneFromDisplay: aRectangle using: oldForm backgroundColor: bgColor "Return a 1-bit deep ColorForm copied from the given rectangle of the display. All colors except the background color will be mapped to black." | f | ((oldForm ~~ nil) and: [oldForm extent = aRectangle extent]) ifTrue: [ f := oldForm fromDisplay: aRectangle. ] ifFalse: [ f := ColorForm extent: aRectangle extent depth: 1. f twoToneFromDisplay: aRectangle backgroundColor: bgColor. f colors: (Array with: bgColor with: Color black)]. ^ f ! ! Object subclass: #ColorMap instanceVariableNames: 'shifts masks colors' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Primitives'! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:54'! alphaMask ^masks at: 4! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:55'! alphaMask: value masks at: 4 put: value! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:31'! alphaShift ^shifts at: 4! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:31'! alphaShift: value shifts at: 4 put: value! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:39'! at: index ^colors at: index! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:39'! at: index put: value ^colors at: index put: value! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:31'! blueMask ^masks at: 3! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:31'! blueMask: value masks at: 3 put: value! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:31'! blueShift ^shifts at: 3! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:32'! blueShift: value shifts at: 3 put: value! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 2/10/2000 17:12'! colors ^colors! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:32'! greenMask ^masks at: 2! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:32'! greenMask: value masks at: 2 put: value! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:32'! greenShift ^shifts at: 2! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:36'! greenShift: value shifts at: 2 put: value.! ! !ColorMap methodsFor: 'accessing' stamp: 'PeterHugossonMiller 9/3/2009 00:57'! inverseMap "Return the inverse map of the receiver" | newMasks newShifts | colors ifNotNil: [ ^ self error: 'Not yet implemented' ]. newMasks := (Array new: 4) writeStream. newShifts := (Array new: 4) writeStream. masks with: shifts do: [ :mask :shift | newMasks nextPut: (mask bitShift: shift). newShifts nextPut: shift negated ]. ^ ColorMap shifts: newShifts contents masks: newMasks contents! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 5/27/2000 19:16'! masks ^masks! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:36'! redMask ^masks at: 1! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:37'! redMask: value masks at: 1 put: value! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:37'! redShift ^shifts at: 1! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 1/16/2000 15:37'! redShift: value shifts at: 1 put: value! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 5/27/2000 20:48'! rgbaBitMasks "Return the rgba bit masks for the receiver" ^masks asArray with: shifts collect:[:m :s| m bitShift: s]! ! !ColorMap methodsFor: 'accessing' stamp: 'ar 5/27/2000 19:16'! shifts ^shifts! ! !ColorMap methodsFor: 'comparing' stamp: 'tk 7/5/2001 21:59'! = aColorMap "Return true if the receiver is equal to aColorMap" self species == aColorMap species ifFalse:[^false]. self isIndexed == aColorMap isIndexed ifFalse:[^false]. ^self colors = aColorMap colors and:[ self shifts = aColorMap shifts and:[ self masks = aColorMap masks]]! ! !ColorMap methodsFor: 'comparing' stamp: 'ar 5/27/2000 19:29'! hash "Hash is re-implemented because #= is re-implemented" ^colors hash bitXor: (shifts hash bitXor: masks hash)! ! !ColorMap methodsFor: 'pixel mapping' stamp: 'lr 7/4/2009 10:42'! mapPixel: pixelValue "Perform a forward pixel mapping operation" | pv | (shifts == nil and: [ masks == nil ]) ifFalse: [ pv := (((pixelValue bitAnd: self redMask) bitShift: self redShift) bitOr: ((pixelValue bitAnd: self greenMask) bitShift: self greenShift)) bitOr: (((pixelValue bitAnd: self blueMask) bitShift: self blueShift) bitOr: ((pixelValue bitAnd: self alphaMask) bitShift: self alphaShift)) ] ifTrue: [ pv := pixelValue ]. colors ifNotNil: [ pv := colors at: pv ]. "Need to check for translucency else Form>>paint goes gaga" pv = 0 ifTrue: [ pixelValue = 0 ifFalse: [ pv := 1 ] ]. ^ pv! ! !ColorMap methodsFor: 'pixel mapping' stamp: 'lr 7/4/2009 10:42'! mappingTo: aColorMap "Compute a new color map through the receiver and aColorMap. Both maps are assumed to be mappings into canonical ARGB space" | fixedMap | self = aColorMap ifTrue: [ ^ nil ]. "No mapping needed" aColorMap isIndexed ifTrue: [ ^ nil ]. "We can't compute mappings to an indexed map yet" fixedMap := self class mappingFrom: self rgbaBitMasks to: aColorMap rgbaBitMasks. self isIndexed ifFalse: [ ^ fixedMap ]. "If the receiver is indexed then we need to map the colors as well" self flag: #untested. ^ ColorMap shifts: fixedMap shifts masks: fixedMap masks colors: (colors collect: [ :pv | aColorMap pixelMap: pv ])! ! !ColorMap methodsFor: 'pixel mapping' stamp: 'lr 7/4/2009 10:42'! pixelMap: pixelValue "Perform a reverse pixel mapping operation" | pv | colors == nil ifTrue: [ pv := pixelValue ] ifFalse: [ pv := colors at: pixelValue ]. (shifts == nil and: [ masks == nil ]) ifFalse: [ pv := (((pv bitAnd: self redMask) bitShift: self redShift) bitOr: ((pv bitAnd: self greenMask) bitShift: self greenShift)) bitOr: (((pv bitAnd: self blueMask) bitShift: self blueShift) bitOr: ((pv bitAnd: self alphaMask) bitShift: self alphaShift)) ]. "Need to check for translucency else Form>>paint goes gaga" pv = 0 ifTrue: [ pixelValue = 0 ifFalse: [ pv := 1 ] ]. ^ pv! ! !ColorMap methodsFor: 'testing' stamp: 'ar 5/25/2000 19:41'! isColormap ^true! ! !ColorMap methodsFor: 'testing' stamp: 'ar 5/27/2000 19:06'! isFixed "Return true if the receiver does not use a lookup mechanism for pixel mapping" ^self isIndexed not! ! !ColorMap methodsFor: 'testing' stamp: 'ar 5/27/2000 19:06'! isIndexed "Return true if the receiver uses a lookup mechanism for pixel mapping" ^colors notNil! ! !ColorMap methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setShifts: shiftArray masks: maskArray colors: colorArray shiftArray ifNotNil: [ shifts := shiftArray asIntegerArray ]. maskArray ifNotNil: [ masks := maskArray asWordArray ]. colorArray ifNotNil: [ colors := colorArray asWordArray ]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ColorMap class instanceVariableNames: ''! !ColorMap class methodsFor: 'instance creation' stamp: 'ar 2/22/2000 14:08'! colors: colorArray ^self new setShifts: nil masks: nil colors: colorArray! ! !ColorMap class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! mapBitsFrom: srcBitMask to: dstBitMask "Return an array consisting of the shift and the mask for mapping component values out of srcBitMask and into dstBitMask. While this computation is somewhat complicated it eases the batch conversion of all the pixels in BitBlt." | srcBits dstBits srcLow srcHigh dstLow dstHigh bits mask shift | (srcBitMask = 0 or: [ dstBitMask = 0 ]) ifTrue: [ ^ #(0 0 ) ]. "Zero mask and shift" "Compute low and high bit position for source and dest bit mask" srcLow := srcBitMask lowBit - 1. srcHigh := srcBitMask highBit. dstLow := dstBitMask lowBit - 1. dstHigh := dstBitMask highBit. "Compute the number of bits in source and dest bit mask" srcBits := srcHigh - srcLow. dstBits := dstHigh - dstLow. "Compute the maximum number of bits we can transfer inbetween" bits := srcBits min: dstBits. "Compute the (unshifted) transfer mask" mask := (1 bitShift: bits) - 1. "Shift the transfer mask to the mask the highest n bits of srcBitMask" mask := mask bitShift: srcHigh - bits. "Compute the delta shift so that the most significant bit of the source bit mask falls on the most significant bit of the dest bit mask. Note that delta is used for #bitShift: so shift > 0 : shift right shift < 0 : shift left e.g., if dstHigh > srcHigh we need to shift left and if dstHigh < srcHigh we need to shift right. This leads to:" shift := dstHigh - srcHigh. "And that's all we need" ^ Array with: shift with: mask! ! !ColorMap class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! mappingFrom: srcBitMasks to: dstBitMasks "Return a color map mapping from the array of source bit masks to the array of dest bit masks." | shifts masks shiftAndMask | shifts := IntegerArray new: 4. masks := WordArray new: 4. 1 to: 4 do: [ :i | shiftAndMask := self mapBitsFrom: (srcBitMasks at: i) to: (dstBitMasks at: i). shifts at: i put: (shiftAndMask at: 1). masks at: i put: (shiftAndMask at: 2) ]. ^ self shifts: shifts masks: masks! ! !ColorMap class methodsFor: 'instance creation' stamp: 'ar 5/27/2000 20:08'! mappingFromARGB: dstBitMasks "Return a ColorMap mapping from canonical ARGB space into dstBitMasks" ^self mappingFrom: #(16rFF0000 16rFF00 16rFF 16rFF000000) to: dstBitMasks! ! !ColorMap class methodsFor: 'instance creation' stamp: 'ar 5/27/2000 20:08'! mappingToARGB: srcBitMasks "Return a ColorMap mapping from srcBitMasks into canonical ARGB space" ^self mappingFrom: srcBitMasks to: #(16rFF0000 16rFF00 16rFF 16rFF000000)! ! !ColorMap class methodsFor: 'instance creation' stamp: 'ar 5/4/2001 15:59'! masks: maskArray shifts: shiftArray ^self shifts: shiftArray masks: maskArray colors: nil.! ! !ColorMap class methodsFor: 'instance creation' stamp: 'ar 1/16/2000 16:02'! shifts: shiftArray masks: maskArray ^self shifts: shiftArray masks: maskArray colors: nil.! ! !ColorMap class methodsFor: 'instance creation' stamp: 'ar 1/16/2000 16:02'! shifts: shiftArray masks: maskArray colors: colorArray ^self new setShifts: shiftArray masks: maskArray colors: colorArray! ! Canvas subclass: #ColorMappingCanvas instanceVariableNames: 'myCanvas' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'! !ColorMappingCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 17:40'! clipRect ^myCanvas clipRect! ! !ColorMappingCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 17:39'! depth ^myCanvas depth! ! !ColorMappingCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 17:39'! extent ^myCanvas extent! ! !ColorMappingCanvas methodsFor: 'accessing' stamp: 'ar 6/24/1999 17:54'! form ^myCanvas form! ! !ColorMappingCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 17:39'! origin ^myCanvas origin! ! !ColorMappingCanvas methodsFor: 'drawing' stamp: 'ar 6/22/1999 18:15'! line: pt1 to: pt2 width: w color: c "Draw a line using the given width and color" myCanvas line: pt1 to: pt2 width: w color: (self mapColor: c).! ! !ColorMappingCanvas methodsFor: 'drawing' stamp: 'ar 6/22/1999 18:16'! paragraph: paragraph bounds: bounds color: c "Draw the given paragraph" myCanvas paragraph: paragraph bounds: bounds color: (self mapColor: c)! ! !ColorMappingCanvas methodsFor: 'drawing-images' stamp: 'ar 6/24/1999 18:26'! stencil: aForm at: aPoint color: aColor myCanvas stencil: aForm at: aPoint color: (self mapColor: aColor)! ! !ColorMappingCanvas methodsFor: 'drawing-images' stamp: 'ar 6/24/1999 18:26'! stencil: aForm at: aPoint sourceRect: aRect color: aColor myCanvas stencil: aForm at: aPoint sourceRect: aRect color: (self mapColor: aColor)! ! !ColorMappingCanvas methodsFor: 'drawing-ovals' stamp: 'ar 6/22/1999 17:59'! fillOval: r color: c borderWidth: borderWidth borderColor: borderColor "Fill the given oval." myCanvas fillOval: r color: (self mapColor: c) borderWidth: borderWidth borderColor: (self mapColor: borderColor)! ! !ColorMappingCanvas methodsFor: 'drawing-polygons' stamp: 'mir 9/12/2001 14:24'! drawPolygon: vertices color: aColor borderWidth: bw borderColor: bc "Draw the given polygon." ^myCanvas drawPolygon: vertices color: aColor borderWidth: bw borderColor: (self mapColor: bc)! ! !ColorMappingCanvas methodsFor: 'drawing-rectangles' stamp: 'ar 6/22/1999 17:59'! frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth borderColor: borderColor "Draw the rectangle using the given attributes" myCanvas frameAndFillRectangle: r fillColor: (self mapColor: fillColor) borderWidth: borderWidth borderColor: (self mapColor: borderColor)! ! !ColorMappingCanvas methodsFor: 'drawing-rectangles' stamp: 'ar 6/22/1999 18:01'! frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth topLeftColor: topLeftColor bottomRightColor: bottomRightColor "Draw the rectangle using the given attributes" myCanvas frameAndFillRectangle: r fillColor: (self mapColor: fillColor) borderWidth: borderWidth topLeftColor: (self mapColor: topLeftColor) bottomRightColor: (self mapColor: bottomRightColor)! ! !ColorMappingCanvas methodsFor: 'drawing-support' stamp: 'ar 6/22/1999 18:19'! clipBy: aRectangle during: aBlock "Set a clipping rectangle active only during the execution of aBlock. Note: In the future we may want to have more general clip shapes - not just rectangles" | oldCanvas | oldCanvas := myCanvas. myCanvas clipBy: aRectangle during:[:newCanvas| myCanvas := newCanvas. aBlock value: self]. myCanvas := oldCanvas! ! !ColorMappingCanvas methodsFor: 'drawing-support' stamp: 'ar 6/22/1999 18:19'! preserveStateDuring: aBlock "Preserve the full canvas state during the execution of aBlock" | oldCanvas | oldCanvas := myCanvas. myCanvas preserveStateDuring:[:newCanvas| myCanvas := newCanvas. aBlock value: self]. myCanvas := oldCanvas.! ! !ColorMappingCanvas methodsFor: 'drawing-support' stamp: 'di 10/16/1999 16:01'! transformBy: aDisplayTransform clippingTo: aClipRect during: aBlock smoothing: cellSize "Transform the receiver by the given display transformation during the execution of aBlock. The given clip rectangle defines the *global* (e.g., outer) rectangle against which the receiver should clip (which would be equivalent to 'self clipRect: aClipRect; transformBy: aDisplayTransform')." | oldCanvas | oldCanvas := myCanvas. myCanvas transformBy: aDisplayTransform clippingTo: aClipRect during: [:newCanvas | myCanvas := newCanvas. aBlock value: self] smoothing: cellSize. myCanvas := oldCanvas.! ! !ColorMappingCanvas methodsFor: 'drawing-support' stamp: 'ar 6/22/1999 18:22'! translateBy: delta during: aBlock "Set a translation only during the execution of aBlock." | oldCanvas | oldCanvas := myCanvas. myCanvas translateBy: delta during:[:newCanvas| myCanvas := newCanvas. aBlock value: self]. myCanvas := oldCanvas.! ! !ColorMappingCanvas methodsFor: 'drawing-support' stamp: 'ar 6/22/1999 18:22'! translateTo: newOrigin clippingTo: aRectangle during: aBlock "Set a new origin and clipping rectangle only during the execution of aBlock." | oldCanvas | oldCanvas := myCanvas. myCanvas translateTo: newOrigin clippingTo: aRectangle during:[:newCanvas| myCanvas := newCanvas. aBlock value: self]. myCanvas := oldCanvas.! ! !ColorMappingCanvas methodsFor: 'drawing-text' stamp: 'ar 12/31/2001 02:28'! drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: c "Draw the given string in the given font and color clipped to the given rectangle. If the font is nil, the default font is used." myCanvas drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: (self mapColor: c)! ! !ColorMappingCanvas methodsFor: 'drawing-text' stamp: 'tween 3/10/2009 07:45'! drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: c underline: underline underlineColor: uc strikethrough: strikethrough strikethroughColor: sc "Draw the given string in the given font and color clipped to the given rectangle. If the font is nil, the default font is used." myCanvas drawString: s from: firstIndex to: lastIndex in: boundsRect font: fontOrNil color: (self mapColor: c) underline: underline underlineColor: (self mapColor: uc) strikethrough: strikethrough strikethroughColor: (self mapColor: sc)! ! !ColorMappingCanvas methodsFor: 'initialization' stamp: 'ar 6/22/1999 18:24'! flush myCanvas flush.! ! !ColorMappingCanvas methodsFor: 'initialization' stamp: 'ar 8/8/2001 14:14'! on: aCanvas myCanvas := aCanvas.! ! !ColorMappingCanvas methodsFor: 'initialization' stamp: 'ar 6/22/1999 18:23'! reset myCanvas reset.! ! !ColorMappingCanvas methodsFor: 'other' stamp: 'ar 6/22/1999 18:21'! translateBy: delta clippingTo: aRectangle during: aBlock "Set a translation and clipping rectangle only during the execution of aBlock." | oldCanvas | oldCanvas := myCanvas. myCanvas translateBy: delta clippingTo: aRectangle during:[:newCanvas| myCanvas := newCanvas. aBlock value: self]. myCanvas := oldCanvas.! ! !ColorMappingCanvas methodsFor: 'testing' stamp: 'ar 8/8/2001 14:16'! isShadowDrawing ^myCanvas isShadowDrawing! ! !ColorMappingCanvas methodsFor: 'private' stamp: 'ar 8/8/2001 14:15'! image: aForm at: aPoint sourceRect: sourceRect rule: rule "Draw the given form. For the 'paint' combination rule use stenciling otherwise simply fill the source rectangle." ^myCanvas image: aForm at: aPoint sourceRect: sourceRect rule: rule.! ! !ColorMappingCanvas methodsFor: 'private' stamp: 'ar 8/8/2001 14:15'! mapColor: aColor ^aColor! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ColorMappingCanvas class instanceVariableNames: ''! !ColorMappingCanvas class methodsFor: 'instance creation' stamp: 'ar 6/22/1999 18:23'! on: aCanvas ^self new on: aCanvas! ! FormCanvas subclass: #ColorPatchCanvas instanceVariableNames: 'stopMorph foundMorph doStop' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'! !ColorPatchCanvas commentStamp: '' prior: 0! I generate patches of Morphic worlds that views below certain Morphs. This facility is used for the end-user scripting system.! !ColorPatchCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 16:15'! doStop ^doStop! ! !ColorPatchCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 16:15'! doStop: aBoolean doStop := aBoolean! ! !ColorPatchCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 16:15'! foundMorph ^foundMorph! ! !ColorPatchCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 16:38'! foundMorph: aBoolean foundMorph := aBoolean! ! !ColorPatchCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 16:14'! stopMorph ^stopMorph! ! !ColorPatchCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 16:14'! stopMorph: aMorph stopMorph := aMorph! ! !ColorPatchCanvas methodsFor: 'drawing-general' stamp: 'ar 6/22/1999 16:14'! fullDrawMorph: aMorph (foundMorph and:[doStop]) ifTrue:[^self]. "Found it and should stop" aMorph == stopMorph ifTrue:[ "Never draw the stopMorph" foundMorph := true. ^self]. ^super fullDrawMorph: aMorph.! ! !ColorPatchCanvas methodsFor: 'drawing-support' stamp: 'ar 6/22/1999 16:34'! clipBy: aRectangle during: aBlock "Set a clipping rectangle active only during the execution of aBlock. Note: In the future we may want to have more general clip shapes - not just rectangles" | tempCanvas | tempCanvas := (self copyClipRect: aRectangle). aBlock value: tempCanvas. foundMorph := tempCanvas foundMorph.! ! !ColorPatchCanvas methodsFor: 'drawing-support' stamp: 'ar 6/22/1999 16:42'! preserveStateDuring: aBlock "Preserve the full canvas state during the execution of aBlock. Note: This does *not* include the state in the receiver (e.g., foundMorph)." | tempCanvas | tempCanvas := self copy. aBlock value: tempCanvas. foundMorph := tempCanvas foundMorph.! ! !ColorPatchCanvas methodsFor: 'drawing-support' stamp: 'ar 2/17/2000 00:15'! transformBy: aDisplayTransform clippingTo: aClipRect during: aBlock smoothing: cellSize "Note: This method has been originally copied from TransformationMorph." | innerRect patchRect sourceQuad warp start subCanvas | (aDisplayTransform isPureTranslation) ifTrue:[ subCanvas := self copyOffset: aDisplayTransform offset negated truncated clipRect: aClipRect. aBlock value: subCanvas. foundMorph := subCanvas foundMorph. ^self ]. "Prepare an appropriate warp from patch to innerRect" innerRect := aClipRect. patchRect := aDisplayTransform globalBoundsToLocal: (self clipRect intersect: innerRect). sourceQuad := (aDisplayTransform sourceQuadFor: innerRect) collect: [:p | p - patchRect topLeft]. warp := self warpFrom: sourceQuad toRect: innerRect. warp cellSize: cellSize. "Render the submorphs visible in the clipping rectangle, as patchForm" start := (self depth = 1 and: [self isShadowDrawing not]) "If this is true B&W, then we need a first pass for erasure." ifTrue: [1] ifFalse: [2]. start to: 2 do: [:i | "If i=1 we first make a shadow and erase it for opaque whites in B&W" subCanvas := ColorPatchCanvas extent: patchRect extent depth: self depth. subCanvas stopMorph: stopMorph. subCanvas foundMorph: foundMorph. subCanvas doStop: doStop. i=1 ifTrue: [subCanvas shadowColor: Color black. warp combinationRule: Form erase] ifFalse: [self isShadowDrawing ifTrue: [subCanvas shadowColor: self shadowColor]. warp combinationRule: Form paint]. subCanvas translateBy: patchRect topLeft negated during:[:offsetCanvas| aBlock value: offsetCanvas]. i = 2 ifTrue:[foundMorph := subCanvas foundMorph]. warp sourceForm: subCanvas form; warpBits. warp sourceForm: nil. subCanvas := nil "release space for next loop"] ! ! !ColorPatchCanvas methodsFor: 'drawing-support' stamp: 'ar 6/22/1999 16:39'! translateBy: delta during: aBlock "Set a translation only during the execution of aBlock." | tempCanvas | tempCanvas := self copyOffset: delta. aBlock value: tempCanvas. foundMorph := tempCanvas foundMorph.! ! !ColorPatchCanvas methodsFor: 'drawing-support' stamp: 'ar 6/22/1999 16:40'! translateTo: newOrigin clippingTo: aRectangle during: aBlock "Set a new origin and clipping rectangle only during the execution of aBlock." | tempCanvas | tempCanvas := self copyOrigin: newOrigin clipRect: aRectangle. aBlock value: tempCanvas. foundMorph := tempCanvas foundMorph.! ! !ColorPatchCanvas methodsFor: 'initialization' stamp: 'ar 6/22/1999 16:18'! reset "Initialize the receiver to act just as a FormCanvas" super reset. foundMorph := false. doStop := false. stopMorph := nil.! ! !ColorPatchCanvas methodsFor: 'other' stamp: 'ar 6/22/1999 16:39'! translateBy: delta clippingTo: aRectangle during: aBlock "Set a translation and clipping rectangle only during the execution of aBlock." | tempCanvas | tempCanvas := self copyOffset: delta clipRect: aRectangle. aBlock value: tempCanvas. foundMorph := tempCanvas foundMorph.! ! !ColorPatchCanvas methodsFor: 'private' stamp: 'ar 6/22/1999 16:18'! setForm: aForm "Initialize the receiver to act just as a FormCanvas" super setForm: aForm. stopMorph := nil. doStop := false. foundMorph := false.! ! SketchMorph subclass: #ColorPickerMorph instanceVariableNames: 'selectedColor sourceHand deleteOnMouseUp updateContinuously target selector argument originalColor theSelectorDisplayMorph isModal clickedTranslucency' classVariableNames: 'ColorChart DragBox FeedbackBox RevertBox TransText TransparentBox' poolDictionaries: '' category: 'Morphic-Widgets'! !ColorPickerMorph commentStamp: 'kfr 10/27/2003 16:16' prior: 0! A gui for setting color and transparency. Behaviour can be changed with the Preference modalColorPickers.! !ColorPickerMorph methodsFor: 'accessing' stamp: 'ar 6/25/1999 11:33'! argument ^argument! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'ar 6/25/1999 11:33'! argument: anObject argument := anObject! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'jm 11/4/97 07:15'! deleteOnMouseUp ^ deleteOnMouseUp ! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'jm 11/4/97 07:15'! deleteOnMouseUp: aBoolean deleteOnMouseUp := aBoolean. ! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'ar 8/25/2001 20:44'! locationIndicator | loc | ^self valueOfProperty: #locationIndicator ifAbsent:[ loc := EllipseMorph new. loc color: Color transparent; borderWidth: 1; borderColor: Color red; extent: 6@6. self setProperty: #locationIndicator toValue: loc. self addMorphFront: loc. loc]! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'KR 12/9/2005 22:51'! originalColor: colorOrSymbol "Set the receiver's original color. It is at this point that a command is launched to represent the action of the picker, in support of Undo." originalColor := (colorOrSymbol isColor) ifTrue: [colorOrSymbol] ifFalse: [Color lightGreen]. originalForm fill: RevertBox fillColor: originalColor. selectedColor := originalColor. self updateAlpha: originalColor alpha. self locationIndicator center: self topLeft + (self positionOfColor: originalColor)! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'jm 11/4/97 07:15'! selectedColor ^ selectedColor ! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'jm 11/4/97 07:15'! selector ^ selector ! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'di 8/30/2000 13:40'! selector: aSymbol "Set the selector to be associated with the receiver. Store it in the receiver's command, if appropriate" selector := aSymbol. self updateSelectorDisplay! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'jm 11/4/97 07:15'! sourceHand ^ sourceHand ! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'jm 11/4/97 07:15'! sourceHand: aHand sourceHand := aHand. ! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'jm 11/4/97 07:15'! target ^ target ! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'aoy 2/15/2003 21:24'! target: anObject target := anObject. selectedColor := (target respondsTo: #color) ifTrue: [target color] ifFalse: [Color white]! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'jm 11/4/97 07:46'! updateContinuously ^ updateContinuously ! ! !ColorPickerMorph methodsFor: 'accessing' stamp: 'jm 11/4/97 07:46'! updateContinuously: aBoolean updateContinuously := aBoolean. ! ! !ColorPickerMorph methodsFor: 'drawing' stamp: 'di 9/3/1999 13:34'! drawOn: aCanvas aCanvas depth = 1 ifTrue: [aCanvas fillRectangle: self bounds color: Color white]. Display depth = originalForm depth ifFalse: [self buildChartForm]. super drawOn: aCanvas! ! !ColorPickerMorph methodsFor: 'event handling' stamp: 'jm 11/4/97 07:15'! handlesMouseDown: evt ^ true ! ! !ColorPickerMorph methodsFor: 'event handling' stamp: 'RAA 2/19/2001 13:16'! inhibitDragging ^self hasProperty: #noDraggingThisPicker! ! !ColorPickerMorph methodsFor: 'event handling' stamp: 'RAA 2/19/2001 13:17'! mouseDown: evt | localPt | localPt := evt cursorPoint - self topLeft. self deleteAllBalloons. clickedTranslucency := TransparentBox containsPoint: localPt. self inhibitDragging ifFalse: [ (DragBox containsPoint: localPt) ifTrue: [^ evt hand grabMorph: self]. ]. (RevertBox containsPoint: localPt) ifTrue: [^ self updateColor: originalColor feedbackColor: originalColor]. self inhibitDragging ifFalse: [self comeToFront]. sourceHand := evt hand. self startStepping. ! ! !ColorPickerMorph methodsFor: 'event handling' stamp: 'stephane.ducasse 11/5/2008 21:51'! mouseUp: evt self stopStepping. sourceHand := nil. deleteOnMouseUp ifTrue: [self delete]. self updateTargetColor. ! ! !ColorPickerMorph methodsFor: 'geometry testing' stamp: 'LC 2/2/2000 04:28'! containsPoint: aPoint ^ (super containsPoint: aPoint) or: [RevertBox containsPoint: aPoint - self topLeft]! ! !ColorPickerMorph methodsFor: 'halos and balloon help' stamp: 'sw 7/6/1999 09:07'! isLikelyRecipientForMouseOverHalos ^ false! ! !ColorPickerMorph methodsFor: 'initialization' stamp: 'di 9/28/2000 12:05'! buildChartForm | chartForm | chartForm := ColorChart deepCopy asFormOfDepth: Display depth. chartForm fill: ((TransparentBox left + 9)@0 extent: 1@9) fillColor: Color lightGray. chartForm fill: ((TransparentBox right - 10)@0 extent: 1@9) fillColor: Color lightGray. TransText displayOn: chartForm at: 62@0. Display depth = 32 ifTrue: ["Set opaque bits for 32-bit display" chartForm fill: chartForm boundingBox rule: Form under fillColor: (Color r: 0.0 g: 0.0 b: 0.0 alpha: 1.0)]. chartForm borderWidth: 1. self form: chartForm. selectedColor ifNotNil: [self updateAlpha: selectedColor alpha]. self updateSelectorDisplay. ! ! !ColorPickerMorph methodsFor: 'initialization' stamp: 'sw 9/8/2000 18:14'! choseModalityFromPreference "Decide whether to be modal or not by consulting the prevailing preference" self initializeModal: Preferences modalColorPickers! ! !ColorPickerMorph methodsFor: 'initialization' stamp: 'ar 9/4/2001 13:26'! initialize "Initialize the receiver. Obey the modalColorPickers preference when deciding how to configure myself. This is not quite satisfactory -- we'd like to have explicit calls tell us things like whether whether to be modal, whether to allow transparency, but for the moment, in grand Morphic fashion, this is rather inflexibly all housed right here" super initialize. self clipSubmorphs: true. self buildChartForm. selectedColor := Color white. sourceHand := nil. deleteOnMouseUp := false. clickedTranslucency := false. updateContinuously := true. selector := nil. target := nil! ! !ColorPickerMorph methodsFor: 'initialization' stamp: 'yo 2/23/2005 17:17'! initializeForPropertiesPanel "Initialize the receiver. If beModal is true, it will be a modal color picker, else not" isModal := false. self removeAllMorphs. self setProperty: #noDraggingThisPicker toValue: true. self addMorph: ((Morph newBounds: (RevertBox translateBy: self topLeft)) color: Color transparent; setCenteredBalloonText: 'restore original color' translated). self addMorph: ((Morph newBounds: (FeedbackBox translateBy: self topLeft)) color: Color transparent; setCenteredBalloonText: 'shows selected color' translated). self addMorph: ((Morph newBounds: (TransparentBox translateBy: self topLeft)) color: Color transparent; setCenteredBalloonText: 'adjust translucency' translated). self buildChartForm. selectedColor ifNil: [selectedColor := Color white]. sourceHand := nil. deleteOnMouseUp := false. updateContinuously := true. ! ! !ColorPickerMorph methodsFor: 'initialization' stamp: 'yo 2/23/2005 17:13'! initializeModal: beModal "Initialize the receiver. If beModal is true, it will be a modal color picker, else not" isModal := beModal. self removeAllMorphs. isModal ifFalse: [theSelectorDisplayMorph := AlignmentMorph newRow color: Color white; borderWidth: 1; borderColor: Color red; hResizing: #shrinkWrap; vResizing: #shrinkWrap; addMorph: (StringMorph contents: 'theSelector' translated). self addMorph: theSelectorDisplayMorph. self addMorph: (SimpleButtonMorph new borderWidth: 0; label: 'x' font: nil; color: Color transparent; actionSelector: #delete; target: self; useSquareCorners; position: self topLeft - (0@3); extent: 10@12; setCenteredBalloonText: 'dismiss color picker' translated)]. self addMorph: ((Morph newBounds: (DragBox translateBy: self topLeft)) color: Color transparent; setCenteredBalloonText: 'put me somewhere' translated). self addMorph: ((Morph newBounds: (RevertBox translateBy: self topLeft)) color: Color transparent; setCenteredBalloonText: 'restore original color' translated). self addMorph: ((Morph newBounds: (FeedbackBox translateBy: self topLeft)) color: Color transparent; setCenteredBalloonText: 'shows selected color' translated). self addMorph: ((Morph newBounds: (TransparentBox translateBy: self topLeft)) color: Color transparent; setCenteredBalloonText: 'adjust translucency' translated). self buildChartForm. selectedColor ifNil: [selectedColor := Color white]. sourceHand := nil. deleteOnMouseUp := false. updateContinuously := true. ! ! !ColorPickerMorph methodsFor: 'initialization' stamp: 'sma 4/22/2000 19:39'! updateSelectorDisplay theSelectorDisplayMorph ifNil: [^self]. theSelectorDisplayMorph position: self bottomLeft. theSelectorDisplayMorph firstSubmorph contents: selector asString , ' ' , selectedColor printString! ! !ColorPickerMorph methodsFor: 'menu' stamp: 'dgd 8/30/2003 21:17'! addCustomMenuItems: aCustomMenu hand: aHandMorph super addCustomMenuItems: aCustomMenu hand: aHandMorph. deleteOnMouseUp ifTrue: [aCustomMenu add: 'stay up' translated action: #toggleDeleteOnMouseUp] ifFalse: [aCustomMenu add: 'do not stay up' translated action: #toggleDeleteOnMouseUp]. updateContinuously ifTrue: [aCustomMenu add: 'update only at end' translated action: #toggleUpdateContinuously] ifFalse: [aCustomMenu add: 'update continuously' translated action: #toggleUpdateContinuously]. ! ! !ColorPickerMorph methodsFor: 'menu' stamp: 'michael.rueger 4/15/2009 14:01'! pickUpColorFor: aMorph "Show the eyedropper cursor, and modally track the mouse through a mouse-down and mouse-up cycle" | aHand localPt | aHand := aMorph ifNil: [self activeHand] ifNotNil: [aMorph activeHand]. aHand ifNil: [aHand := self currentHand]. self addToWorld: aHand world near: (aMorph ifNil: [aHand world]) fullBounds. self owner ifNil: [^ self]. aHand showTemporaryCursor: (ScriptingSystem formAtKey: #Eyedropper) hotSpotOffset: 6 negated @ 4 negated. "<<<< the form was changed a bit??" self updateContinuously: false. [Sensor anyButtonPressed] whileFalse: [self trackColorUnderMouse]. self deleteAllBalloons. localPt := Sensor cursorPoint - self topLeft. self inhibitDragging ifFalse: [ (DragBox containsPoint: localPt) ifTrue: ["Click or drag the drag-dot means to anchor as a modeless picker" ^ self anchorAndRunModeless: aHand]. ]. (clickedTranslucency := TransparentBox containsPoint: localPt) ifTrue: [selectedColor := originalColor]. self updateContinuously: true. [Sensor anyButtonPressed] whileTrue: [self updateTargetColorWith: self indicateColorUnderMouse]. aHand newMouseFocus: nil; showTemporaryCursor: nil. self delete. ! ! !ColorPickerMorph methodsFor: 'menu' stamp: 'jm 11/4/97 07:46'! toggleDeleteOnMouseUp deleteOnMouseUp := deleteOnMouseUp not. ! ! !ColorPickerMorph methodsFor: 'menu' stamp: 'jm 11/4/97 07:46'! toggleUpdateContinuously updateContinuously := updateContinuously not. ! ! !ColorPickerMorph methodsFor: 'other' stamp: 'di 11/27/1999 09:12'! addToWorld: world near: box | goodLocation | goodLocation := self bestPositionNear: box inWorld: world. world allMorphsDo: [:p | (p isMemberOf: ColorPickerMorph) ifTrue: [(p ~~ self and: [p owner notNil and: [p target == target]]) ifTrue: [(p selector == selector and: [p argument == argument]) ifTrue: [^ p comeToFront "uncover existing picker"] ifFalse: ["place second picker relative to first" goodLocation := self bestPositionNear: p bounds inWorld: world]]]]. self position: goodLocation. world addMorphFront: self. self changed ! ! !ColorPickerMorph methodsFor: 'other' stamp: 'di 11/27/1999 08:51'! bestPositionNear: box inWorld: world | points b | points := #(topCenter rightCenter bottomCenter leftCenter). "possible anchors" 1 to: 4 do: [:i | "Try the four obvious anchor points" b := self bounds align: (self bounds perform: (points at: i)) with: (box perform: (points atWrap: i + 2)). (world viewBox containsRect: b) ifTrue: [^ b topLeft" Yes, it fits"]]. ^ 20@20 "when all else fails" ! ! !ColorPickerMorph methodsFor: 'other' stamp: 'di 9/25/2000 15:38'! indicateColorUnderMouse "Track the mouse with the special eyedropper cursor, and accept whatever color is under the mouse as the currently-chosen color; reflect that choice in the feedback box, and return that color." | pt | self pickColorAt: (pt := Sensor cursorPoint). isModal ifTrue: [self activeHand position: pt. self world displayWorldSafely; runStepMethods]. ^ selectedColor ! ! !ColorPickerMorph methodsFor: 'other' stamp: 'ar 12/8/2000 15:32'! putUpFor: aMorph near: aRectangle "Put the receiver up on the screen. Note highly variant behavior depending on the setting of the #modalColorPickers preference" | layerNumber | aMorph isMorph ifTrue: [ layerNumber := aMorph morphicLayerNumber. aMorph allOwnersDo:[:m| layerNumber := layerNumber min: m morphicLayerNumber]. self setProperty: #morphicLayerNumber toValue: layerNumber - 0.1 ]. isModal == true "backward compatibility" ifTrue: [self pickUpColorFor: aMorph] ifFalse: [self addToWorld: ((aMorph notNil and: [aMorph world notNil]) ifTrue: [aMorph world] ifFalse: [self currentWorld]) near: (aRectangle ifNil: [aMorph ifNil: [100@100 extent: 1@1] ifNotNil: [aMorph fullBoundsInWorld]])]! ! !ColorPickerMorph methodsFor: 'other' stamp: 'di 9/27/2000 11:48'! trackColorUnderMouse "Track the mouse with the special eyedropper cursor, and accept whatever color is under the mouse as the currently-chosen color; reflect that choice in the feedback box, and return that color." | pt | selectedColor := originalColor. self trackColorAt: (pt := Sensor cursorPoint). isModal ifTrue: [self activeHand position: pt. self world displayWorldSafely; runStepMethods. self modalBalloonHelpAtPoint: pt]. ^ selectedColor ! ! !ColorPickerMorph methodsFor: 'stepping and presenter' stamp: 'jm 11/4/97 07:15'! step sourceHand ifNotNil: [self pickColorAt: sourceHand position]. ! ! !ColorPickerMorph methodsFor: 'submorphs-add/remove' stamp: 'nk 4/17/2004 19:34'! delete "The moment of departure has come. If the receiver has an affiliated command, finalize it and have the system remember it. In any case, delete the receiver" (selector isNil or: [ target isNil ]) ifFalse: [ self rememberCommand: (Command new cmdWording: 'color change' translated; undoTarget: target selector: selector arguments: (self argumentsWith: originalColor); redoTarget: target selector: selector arguments: (self argumentsWith: selectedColor)). ]. super delete! ! !ColorPickerMorph methodsFor: 'testing' stamp: 'jm 11/4/97 07:15'! stepTime ^ 50 ! ! !ColorPickerMorph methodsFor: 'private' stamp: 'mir 11/19/2008 12:47'! anchorAndRunModeless: aHand "If user clicks on the drag-dot of a modal picker, anchor it, and change to modeless operation." aHand showTemporaryCursor: nil. "revert to normal cursor" self initializeModal: false; originalColor: originalColor. "reset as modeless" aHand position: Sensor cursorPoint; grabMorph: self. "Slip into drag operation" ! ! !ColorPickerMorph methodsFor: 'private' stamp: 'ar 7/19/2003 20:40'! argumentsWith: aColor "Return an argument array appropriate to this action selector" | nArgs | nArgs := selector ifNil:[0] ifNotNil:[selector numArgs]. nArgs = 0 ifTrue:[^#()]. nArgs = 1 ifTrue:[^ {aColor}]. nArgs = 2 ifTrue:[^ {aColor. sourceHand}]. nArgs = 3 ifTrue:[^ {aColor. argument. sourceHand}]. ! ! !ColorPickerMorph methodsFor: 'private' stamp: 'di 9/27/2000 12:55'! deleteAllBalloons self submorphsDo: [:m | m deleteBalloon]. ! ! !ColorPickerMorph methodsFor: 'private' stamp: 'dgd 2/21/2003 22:59'! modalBalloonHelpAtPoint: cursorPoint self flag: #arNote. "Throw this away. There needs to be another way." self submorphsDo: [:m | m wantsBalloon ifTrue: [(m valueOfProperty: #balloon) isNil ifTrue: [(m containsPoint: cursorPoint) ifTrue: [m showBalloon: m balloonText]] ifFalse: [(m containsPoint: cursorPoint) ifFalse: [m deleteBalloon]]]]! ! !ColorPickerMorph methodsFor: 'private' stamp: 'stephane.ducasse 11/5/2008 21:50'! pickColorAt: aGlobalPoint | alpha selfRelativePoint pickedColor | clickedTranslucency ifNil: [clickedTranslucency := false]. selfRelativePoint := (self globalPointToLocal: aGlobalPoint) - self topLeft. (FeedbackBox containsPoint: selfRelativePoint) ifTrue: [^ self]. (RevertBox containsPoint: selfRelativePoint) ifTrue: [^ self updateColor: originalColor feedbackColor: originalColor]. "check for transparent color and update using appropriate feedback color " (TransparentBox containsPoint: selfRelativePoint) ifTrue: [clickedTranslucency ifFalse: [^ self]. "Can't wander into translucency control" alpha := (selfRelativePoint x - TransparentBox left - 10) asFloat / (TransparentBox width - 20) min: 1.0 max: 0.0. "(alpha roundTo: 0.01) printString , ' ' displayAt: 0@0." " -- debug" self updateColor: (selectedColor alpha: alpha) feedbackColor: (selectedColor alpha: alpha). ^ self]. "pick up color, either inside or outside this world" clickedTranslucency ifTrue: [^ self]. "Can't wander out of translucency control" self locationIndicator visible: false. self refreshWorld. pickedColor := Display colorAt: aGlobalPoint. self locationIndicator visible: true. self refreshWorld. self updateColor: ( (selectedColor isColor and: [selectedColor isTranslucentColor]) ifTrue: [pickedColor alpha: selectedColor alpha] ifFalse: [pickedColor] ) feedbackColor: pickedColor! ! !ColorPickerMorph methodsFor: 'private' stamp: 'ar 9/4/2001 13:27'! positionOfColor: aColor "Compute the position of the given color in the color chart form" | rgbRect x y h s v | rgbRect := (0@0 extent: originalForm boundingBox extent) insetBy: (1@10 corner: 11@1). h := aColor hue. s := aColor saturation. v := aColor brightness. h = 0.0 ifTrue:["gray" ^(rgbRect right + 6) @ (rgbRect height * (1.0 - v) + rgbRect top)]. x := (h + 22 \\ 360 / 360.0 * rgbRect width) rounded. y := 0.5. s < 1.0 ifTrue:[y := y - (1.0 - s * 0.5)]. v < 1.0 ifTrue:[y := y + (1.0 - v * 0.5)]. y := (y * rgbRect height) rounded. ^x@y + (1@10)! ! !ColorPickerMorph methodsFor: 'private' stamp: 'di 9/30/2000 10:07'! trackColorAt: aGlobalPoint "Before the mouse comes down in a modal color picker, track the color under the cursor, and show it in the feedback box, but do not make transparency changes" | selfRelativePoint pickedColor | selfRelativePoint := (self globalPointToLocal: aGlobalPoint) - self topLeft. (FeedbackBox containsPoint: selfRelativePoint) ifTrue: [^ self]. (RevertBox containsPoint: selfRelativePoint) ifTrue: [^ self updateColor: originalColor feedbackColor: originalColor]. "check for transparent color and update using appropriate feedback color " (TransparentBox containsPoint: selfRelativePoint) ifTrue: [^ self]. "pick up color, either inside or outside this world" pickedColor := Display colorAt: aGlobalPoint. self updateColor: (pickedColor alpha: originalColor alpha) feedbackColor: pickedColor! ! !ColorPickerMorph methodsFor: 'private' stamp: 'di 9/28/2000 11:10'! updateAlpha: alpha | sliderRect | sliderRect := (TransparentBox left + 10)@1 corner: (TransparentBox right - 9)@9. originalForm fill: (sliderRect withRight: sliderRect left + (alpha*sliderRect width)) fillColor: Color lightGray. originalForm fillWhite: (sliderRect withLeft: sliderRect left + (alpha*sliderRect width)). originalForm fill: ((TransparentBox right - 9)@1 extent: 8@8) fillColor: (alpha < 1.0 ifTrue: [Color white] ifFalse: [Color lightGray]). TransText displayOn: originalForm at: 62@1 rule: Form paint. ! ! !ColorPickerMorph methodsFor: 'private' stamp: 'ar 8/25/2001 20:50'! updateColor: aColor feedbackColor: feedbackColor "Set my selected color to the given color if it is different. Give user feedback. Inform the target of the change if the target and selector are not nil." selectedColor = aColor ifTrue: [^ self]. "do nothing if color doesn't change" self updateAlpha: aColor alpha. originalForm fill: FeedbackBox fillColor: feedbackColor. self form: originalForm. selectedColor := aColor. updateContinuously ifTrue: [self updateTargetColor]. self locationIndicator center: self topLeft + (self positionOfColor: feedbackColor).! ! !ColorPickerMorph methodsFor: 'private' stamp: 'dgd 2/22/2003 18:41'! updateTargetColor | nArgs | (target notNil and: [selector notNil]) ifTrue: [self updateSelectorDisplay. nArgs := selector numArgs. nArgs = 1 ifTrue: [^target perform: selector with: selectedColor]. nArgs = 2 ifTrue: [^target perform: selector with: selectedColor with: sourceHand]. nArgs = 3 ifTrue: [^target perform: selector with: selectedColor with: argument with: sourceHand]]! ! !ColorPickerMorph methodsFor: 'private' stamp: 'dgd 2/22/2003 18:41'! updateTargetColorWith: aColor "Update the target so that it reflects aColor as the color choice" (target notNil and: [selector notNil]) ifTrue: [self updateSelectorDisplay. ^target perform: selector withArguments: (self argumentsWith: aColor)]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ColorPickerMorph class instanceVariableNames: ''! !ColorPickerMorph class methodsFor: 'as yet unclassified' stamp: 'sw 10/27/1999 11:40'! perniciousBorderColor "Answer the color of the border lines of a color picker; this color gets reported as you drag the mouse through from the translucent box to the true color area, for example, and can cause some difficulties in some special cases, so it is faithfully reported here in this hard-coded fashion in order that energetic clients wishing to handle it as special-case it can do so." ^ Color r: 0.0 g: 0.0 b: 0.032! ! !ColorPickerMorph class methodsFor: 'initialization' stamp: 'ar 7/8/2006 20:32'! colorPaletteForDepth: depth extent: chartExtent "Display a palette of colors sorted horizontally by hue and vertically by lightness. Useful for eyeballing the color gamut of the display, or for choosing a color interactively." "Note: It is slow to build this palette, so it should be cached for quick access." "(Color colorPaletteForDepth: 16 extent: 190@60) display" | basicHue x y c startHue palette transHt vSteps transCaption grayWidth hSteps | palette := Form extent: chartExtent depth: depth. transCaption := "(DisplayText text: 'no color' asText textStyle: (TextConstants at: #ComicPlain)) form storeString" (Form extent: 34@9 depth: 1 fromArray: #(0 0 256 0 256 0 3808663859 2147483648 2491688266 2147483648 2491688266 0 2491688266 0 2466486578 0 0 0) offset: 0@0). transHt := transCaption height. palette fillWhite: (0@0 extent: palette width@transHt). palette fillBlack: (0@transHt extent: palette width@1). transCaption displayOn: palette at: palette boundingBox topCenter - ((transCaption width // 2)@0). grayWidth := 10. startHue := 338.0. vSteps := palette height - transHt // 2. hSteps := palette width - grayWidth. x := 0. startHue to: startHue + 360.0 by: 360.0/hSteps do: [:h | basicHue := Color h: h asFloat s: 1.0 v: 1.0. y := transHt+1. 0 to: vSteps do: [:n | c := basicHue mixed: (n asFloat / vSteps asFloat) with: Color white. palette fill: (x@y extent: 1@1) fillColor: c. y := y + 1]. 1 to: vSteps do: [:n | c := Color black mixed: (n asFloat / vSteps asFloat) with: basicHue. palette fill: (x@y extent: 1@1) fillColor: c. y := y + 1]. x := x + 1]. y := transHt + 1. 1 to: vSteps * 2 do: [:n | c := Color black mixed: (n asFloat / (vSteps*2) asFloat) with: Color white. palette fill: (x@y extent: 10@1) fillColor: c. y := y + 1]. ^ palette ! ! !ColorPickerMorph class methodsFor: 'initialization' stamp: 'ar 7/8/2006 20:33'! initialize "ColorPickerMorph initialize" ColorChart := ColorPickerMorph colorPaletteForDepth: 16 extent: 190@60. DragBox := (11@0) extent: 9@8. RevertBox := (ColorChart width - 20)@1 extent: 9@8. FeedbackBox := (ColorChart width - 10)@1 extent: 9@8. TransparentBox := DragBox topRight corner: RevertBox bottomLeft. ColorChart fillBlack: ((DragBox left - 1)@0 extent: 1@9). ColorChart fillBlack: ((TransparentBox left)@0 extent: 1@9). ColorChart fillBlack: ((FeedbackBox left - 1)@0 extent: 1@9). ColorChart fillBlack: ((RevertBox left - 1)@0 extent: 1@9). (Form dotOfSize: 5) displayOn: ColorChart at: DragBox center + (0@1). self localeChanged.! ! !ColorPickerMorph class methodsFor: 'initialization' stamp: 'tak 8/4/2005 14:26'! localeChanged | formTranslator | formTranslator := NaturalLanguageFormTranslator localeID: Locale current localeID. TransText := formTranslator translate: 'translucent'. TransText ifNil: [TransText := Form extent: 63 @ 8 depth: 1 fromArray: #(4194306 1024 4194306 1024 15628058 2476592640 4887714 2485462016 1883804850 2486772764 4756618 2485462016 4748474 1939416064 0 0 ) offset: 0 @ 0]. TransText := ColorForm mappingWhiteToTransparentFrom: TransText! ! !ColorPickerMorph class methodsFor: 'initialization' stamp: 'ar 7/8/2006 20:33'! noColorCaption | formTranslator | formTranslator := NaturalLanguageFormTranslator localeID: Locale current localeID. ^ (formTranslator translate: 'no color') ifNil: [Form extent: 34 @ 9 depth: 1 fromArray: #(0 0 256 0 256 0 3808663859 2147483648 2491688266 2147483648 2491688266 0 2491688266 0 2466486578 0 0 0 ) offset: 0 @ 0] ! ! MorphicModel subclass: #ColorPresenterMorph instanceVariableNames: 'contentMorph labelMorph solidLabelMorph getColorSelector' classVariableNames: 'HatchForm' poolDictionaries: '' category: 'Polymorph-Widgets'! !ColorPresenterMorph commentStamp: 'gvc 5/18/2007 13:38' prior: 0! Displays a colour with alpha against a white, hatched and black background.! !ColorPresenterMorph methodsFor: 'accessing' stamp: 'gvc 9/22/2006 09:25'! contentMorph "Answer the value of contentMorph" ^ contentMorph! ! !ColorPresenterMorph methodsFor: 'accessing' stamp: 'gvc 9/22/2006 09:25'! contentMorph: anObject "Set the value of contentMorph" contentMorph := anObject! ! !ColorPresenterMorph methodsFor: 'accessing' stamp: 'gvc 9/18/2006 15:48'! getColorSelector "Answer the value of getColorSelector" ^ getColorSelector! ! !ColorPresenterMorph methodsFor: 'accessing' stamp: 'gvc 9/18/2006 15:48'! getColorSelector: anObject "Set the value of getColorSelector" getColorSelector := anObject! ! !ColorPresenterMorph methodsFor: 'accessing' stamp: 'gvc 9/18/2006 15:48'! labelMorph "Answer the value of labelMorph" ^ labelMorph! ! !ColorPresenterMorph methodsFor: 'accessing' stamp: 'gvc 9/18/2006 15:48'! labelMorph: anObject "Set the value of labelMorph" labelMorph := anObject! ! !ColorPresenterMorph methodsFor: 'accessing' stamp: 'gvc 9/18/2006 16:17'! solidLabelMorph "Answer the value of solidLabelMorph" ^ solidLabelMorph! ! !ColorPresenterMorph methodsFor: 'accessing' stamp: 'gvc 9/18/2006 16:17'! solidLabelMorph: anObject "Set the value of solidLabelMorph" solidLabelMorph := anObject! ! !ColorPresenterMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/18/2006 16:04'! hatchForm "Answer a form showing a grid hatch pattern." ^self class hatchForm! ! !ColorPresenterMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 09:34'! initialize "Initialize the receiver." super initialize. self borderWidth: 0; changeTableLayout; labelMorph: self newLabelMorph; solidLabelMorph: self newLabelMorph; contentMorph: self newContentMorph; addMorphBack: self contentMorph! ! !ColorPresenterMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 09:23'! newContentMorph "Answer a new content morph" ^Morph new color: Color transparent; changeTableLayout; borderStyle: (BorderStyle inset width: 1); vResizing: #spaceFill; hResizing: #spaceFill; addMorph: self newHatchMorph; yourself! ! !ColorPresenterMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/8/2008 19:40'! newHatchMorph "Answer a new morph showing a grid hatch pattern." ^Morph new color: Color transparent; changeProportionalLayout; vResizing: #spaceFill; hResizing: #spaceFill; minWidth: 48; minHeight: 12; addMorph: (Morph new color: Color white) fullFrame: (LayoutFrame fractions: (0@0 corner: 0.3@1)); addMorph: (Morph new fillStyle: (InfiniteForm with: self hatchForm)) fullFrame: (LayoutFrame fractions: (0.3@0 corner: 0.7@1)); addMorph: self solidLabelMorph fullFrame: (LayoutFrame fractions: (0.7@0 corner: 1@1)); addMorph: self labelMorph fullFrame: (LayoutFrame fractions: (0@0 corner: 1@1))! ! !ColorPresenterMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/18/2006 16:20'! newLabelMorph "Answer a new label morph" ^Morph new! ! !ColorPresenterMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 09:45'! on: anObject color: getColSel "Set the receiver to the given model parameterized by the given message selectors." self model: anObject; getColorSelector: getColSel; updateColor! ! !ColorPresenterMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/3/2009 18:14'! setColor: aColor "Update the colour of the labels." self labelMorph color: aColor. self solidLabelMorph color: aColor asNontranslucentColor! ! !ColorPresenterMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 09:34'! update: aSymbol "Refer to the comment in View|update:." aSymbol == self getColorSelector ifTrue: [self updateColor. ^ self]! ! !ColorPresenterMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/30/2009 18:36'! updateColor "Update the color state." |col| self getColorSelector ifNotNil: [ col := (self model perform: self getColorSelector) ifNil: [Color transparent]. self setColor: col]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ColorPresenterMorph class instanceVariableNames: ''! !ColorPresenterMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 9/18/2006 16:05'! hatchForm "Answer a form showing a grid hatch pattern." ^HatchForm ifNil: [HatchForm := self newHatchForm]! ! !ColorPresenterMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 9/18/2006 16:24'! newHatchForm "Answer a new hatch form." ^(Form extent: 8@8 depth: 1 fromArray: #( 4026531840 4026531840 4026531840 4026531840 251658240 251658240 251658240 251658240) offset: 0@0)! ! !ColorPresenterMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 09:49'! on: anObject color: getSel "Answer a new instance of the receiver on the given model using the given selectors as the interface." ^self new on: anObject color: getSel! ! DialogWindow subclass: #ColorSelectorDialogWindow instanceVariableNames: 'selectedColor hsvaMorph' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !ColorSelectorDialogWindow commentStamp: 'gvc 5/18/2007 13:35' prior: 0! Standard dialog for selecting a colour by HSVA colour selector, picking from the screen or editing of values.! !ColorSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/22/2006 16:39'! basicSelectedColor: anObject "Set the value of selectedColor" selectedColor := anObject. self changed: #selectedColor; changed: #red; changed: #green; changed: #blue; changed: #hue; changed: #saturation; changed: #brightness; changed: #alpha! ! !ColorSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/22/2006 10:04'! hsvaMorph "Answer the value of hsvaMorph" ^ hsvaMorph! ! !ColorSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/22/2006 10:04'! hsvaMorph: anObject "Set the value of hsvaMorph" hsvaMorph := anObject! ! !ColorSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/22/2006 09:49'! selectedColor "Answer the value of selectedColor" ^ selectedColor! ! !ColorSelectorDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/22/2006 10:03'! selectedColor: aColor "Set the value of selectedColor. Update the color selectors." self basicSelectedColor: aColor. self hsvaMorph selectedColor: aColor! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:30'! alpha "Answer the alpha value of the selected color." ^(self selectedColor alpha * 255) asInteger! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:21'! alpha: anInteger "Set the alpha value of the selected color." |c| c := self selectedColor. self selectedColor: (c alpha: anInteger / 255)! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:30'! blue "Answer the blue value of the selected color." ^(self selectedColor blue * 255) asInteger! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/28/2006 12:14'! blue: anInteger "Set the blue value of the selected color." |c| c := self selectedColor. self selectedColor: ((Color r: c red * 255 g: c green * 255 b: anInteger range: 255) alpha: c alpha)! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:38'! brightness "Answer the brightness value of the selected color." ^(self selectedColor brightness * 255) asInteger! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:37'! brightness: anInteger "Set the brightness value of the selected color." |c| c := self selectedColor. self selectedColor: ((Color h: c hue s: c saturation v: anInteger / 255) alpha: c alpha)! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 11:13'! colorSelected: aColor "A color has been selected.." self basicSelectedColor: aColor! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/1/2007 12:16'! defaultLabel "Answer the default label for the receiver." ^'Colour Selector' translated! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:30'! green "Answer the green value of the selected color." ^(self selectedColor green * 255) asInteger! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/28/2006 12:14'! green: anInteger "Set the green value of the selected color." |c| c := self selectedColor. self selectedColor: ((Color r: c red * 255 g: anInteger b: c blue * 255 range: 255) alpha: c alpha)! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:38'! hue "Answer the hue value of the selected color." ^(self selectedColor hue / 359 * 255) asInteger! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/28/2006 12:16'! hue: anInteger "Set the hue value of the selected color." |c| c := self selectedColor. self selectedColor: ((Color h: (anInteger / 255 * 359) rounded s: c saturation v: c brightness) alpha: c alpha)! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 10:06'! initialize "Initialize the receiver." self basicSelectedColor: Color blue. super initialize. self selectedColor: self selectedColor! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/28/2006 12:11'! newColorComponentFieldMorph: aspect "Answer a text entry for the specified aspect of the color." ^(self newTextEntryFor: self get: aspect set: (aspect, ':') asSymbol class: Integer getEnabled: nil help: nil) acceptOnFocusChange: true; minWidth: 40! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:04'! newColorPickerButtonMorph "Answer a button to enable picking of colour." ^self newButtonFor: self getState: nil action: #pickColor arguments: nil getEnabled: nil labelForm: ((ScriptingSystem formAtKey: #Eyedropper) scaledIntoFormOfSize: 16) help: 'Pick a colour from the screen' translated! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/1/2007 12:32'! newColorPresenterMorph "Answer a color presenter." ^self newColorPresenterFor: self getColor: #selectedColor help: 'Shows the selected colour' translated! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/1/2007 12:14'! newContentMorph "Answer a new content morph." self hsvaMorph: self newHSVAColorSelectorMorph. ^self newRow: { self newGroupbox: 'Colour' translated forAll: { self hsvaMorph. (self newRow: { (self newLabelGroup: { 'Selected colour' translated -> self newColorPresenterMorph}) vResizing: #shrinkWrap. self newColorPickerButtonMorph}) cellPositioning: #leftCenter}. (self newGroupbox: 'Values' translated for: (self newLabelGroup: { 'Red' translated -> (self newColorComponentFieldMorph: #red). 'Green' translated -> (self newColorComponentFieldMorph: #green). 'Blue' translated -> (self newColorComponentFieldMorph: #blue). 'Hue' translated -> (self newColorComponentFieldMorph: #hue). 'Saturation' translated -> (self newColorComponentFieldMorph: #saturation). 'Brightness' translated -> (self newColorComponentFieldMorph: #brightness). 'Alpha' translated -> (self newColorComponentFieldMorph: #alpha)})) hResizing: #shrinkWrap}! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/26/2006 13:11'! newHSVAColorSelectorMorph "Answer a hsva color selector." ^HSVAColorSelectorMorph new extent: (40@28) + 152; when: #selectedColor send: #colorSelected: to: self! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/21/2009 18:25'! pickColor "Pick a colour from the screen." |p d c h| h := self world activeHand. d := Delay forMilliseconds: 20. h showTemporaryCursor: (ScriptingSystem formAtKey: #Eyedropper) hotSpotOffset: 6 negated @ 4 negated. [Sensor anyButtonPressed] whileFalse: [[Sensor nextEvent isNil] whileFalse. "Pharo compatability" p := Sensor cursorPoint. (self hsvaMorph containsPoint: p) ifFalse: ["deal with the fact that 32 bit displays may have garbage in the alpha bits" c := Display depth = 32 ifTrue: [Color colorFromPixelValue: ((Display pixelValueAt: p) bitOr: 16rFF000000) depth: 32] ifFalse: [Display colorAt: p]]. self world activeHand position: p. self selectedColor ~= c ifTrue: [ self selectedColor: c]. self world displayWorldSafely. d wait]. h showTemporaryCursor: nil! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:29'! red "Answer the red value of the selected color." ^(self selectedColor red * 255) asInteger! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/28/2006 12:14'! red: anInteger "Set the red value of the selected color." |c| c := self selectedColor. self selectedColor: ((Color r: anInteger g: c green * 255 b: c blue * 255 range: 255) alpha: c alpha)! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:38'! saturation "Answer the saturation value of the selected color." ^(self selectedColor saturation * 255) asInteger! ! !ColorSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2006 16:36'! saturation: anInteger "Set the saturation value of the selected color." |c| c := self selectedColor. self selectedColor: ((Color h: c hue s: anInteger / 255 v: c brightness) alpha: c alpha)! ! ClassTestCase subclass: #ColorTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'GraphicsTests-Primitives'! !ColorTest methodsFor: 'testing' stamp: 'dg 2/19/2008 13:19'! testAsHTMLColor | table aColorString | table := #('0' '1' '2' '3' '4' '5' '6' '7' '8' '9' 'A' 'B' 'C' 'D' 'E' 'F'). table do: [ :each | aColorString := '#', each, each, '0000'. self assert: ((Color fromString: aColorString) asHTMLColor sameAs: aColorString)]. table do: [ :each | aColorString := '#', '00', each, each, '00'. self assert: ((Color fromString: aColorString) asHTMLColor sameAs: aColorString)]. table do: [ :each | aColorString := '#', '0000', each, each. self assert: ((Color fromString: aColorString) asHTMLColor sameAs: aColorString)]. table do: [ :each | aColorString := '#', each, each, each, each, each, each. self assert: ((Color fromString: aColorString) asHTMLColor sameAs: aColorString)].! ! !ColorTest methodsFor: 'testing' stamp: 'dg 2/19/2008 12:43'! testColorFrom self assert: ((Color colorFrom: #white) asHTMLColor sameAs: '#ffffff'). self assert: ((Color colorFrom: #(1.0 0.5 0.0)) asHTMLColor sameAs: '#ff8000'). self assert: ((Color colorFrom: (Color white)) asHTMLColor sameAs: '#ffffff'). self assert: ((Color colorFrom: '#FF8800') asHTMLColor sameAs: '#ff8800'). self assert: ((Color colorFrom: '#222222') asHTMLColor sameAs: '#222222').! ! !ColorTest methodsFor: 'testing' stamp: 'dg 2/19/2008 12:43'! testFromString self assert: ((Color fromString: '#FF8800') asHTMLColor sameAs: '#ff8800').! ! !ColorTest methodsFor: 'testing' stamp: 'fbs 2/3/2005 13:13'! testMultiplyByArray | newColor oldColor tolerance | tolerance := 0.001. oldColor := Color r: 0.75 g: 0.5 b: 0.25. newColor := oldColor * #(0.1 2 3). self assert: (0.075 - newColor red) abs < tolerance. self assert: (1 - newColor green) abs < tolerance. self assert: (0.75 - newColor blue) abs < tolerance.! ! !ColorTest methodsFor: 'testing' stamp: 'fbs 2/3/2005 12:57'! testMultiplyByArrayIdentityTransform | newColor oldColor tolerance | tolerance := 0.001. oldColor := Color r: 0.75 g: 0.5 b: 0.25. newColor := oldColor * 2. self assert: (1 - newColor red) abs < tolerance. self assert: (1 - newColor green) abs < tolerance. self assert: (0.5 - newColor blue) abs < tolerance.! ! !ColorTest methodsFor: 'testing' stamp: 'fbs 2/3/2005 12:56'! testMultiplyByNumber | newColor oldColor tolerance | tolerance := 0.001. oldColor := Color r: 0.75 g: 0.5 b: 0.25. newColor := oldColor * 2. self assert: (1 - newColor red) abs < tolerance. self assert: (1 - newColor green) abs < tolerance. self assert: (0.5 - newColor blue) abs < tolerance.! ! !ColorTest methodsFor: 'tests' stamp: 'sd 6/16/2006 13:12'! testPrintHtmlString "self debug: #testPrintHtmlString" self shouldnt: [Color white printHtmlString ] raise: Error. self assert: Color white printHtmlString = 'FFFFFF'. self assert: Color red printHtmlString = 'FF0000'. self assert: Color black printHtmlString = '000000'.! ! Object subclass: #ColorTheme instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Support'! !ColorTheme methodsFor: 'theme' stamp: 'marcus.denker 11/29/2008 22:55'! baseColors ^ Array with: (Color fromArray: #(0.2 0.3 0.9 )) with: (Color fromArray: #(0.6 0.7 1.0 )) with: (Color fromArray: #(0.85 0.9 1.0 ))! ! !ColorTheme methodsFor: 'theme' stamp: 'dgd 11/2/2004 21:23'! cancelColor ^ Color lightRed! ! !ColorTheme methodsFor: 'theme' stamp: 'marcus.denker 11/29/2008 22:57'! helpColor ^ self okColor! ! !ColorTheme methodsFor: 'theme' stamp: 'marcus.denker 11/29/2008 23:06'! normal: index ^ (self baseColors second wheel: 8) at: index! ! !ColorTheme methodsFor: 'theme' stamp: 'dgd 11/2/2004 21:22'! okColor ^ Color lightGreen! ! !ColorTheme methodsFor: 'theme - dialogs' stamp: 'dgd 11/3/2004 19:27'! dialog3DTitles ^ true! ! !ColorTheme methodsFor: 'theme - dialogs' stamp: 'dgd 11/2/2004 19:56'! dialogBorderColor ^ Color fromArray: #(0.355 0.516 1.0 )! ! !ColorTheme methodsFor: 'theme - dialogs' stamp: 'dgd 11/2/2004 19:54'! dialogBorderWidth ^ 4! ! !ColorTheme methodsFor: 'theme - dialogs' stamp: 'dgd 11/2/2004 19:59'! dialogButtonBorderWidth ^ 0! ! !ColorTheme methodsFor: 'theme - dialogs' stamp: 'dgd 11/2/2004 21:09'! dialogColor ^ Color paleYellow! ! !ColorTheme methodsFor: 'theme - dialogs' stamp: 'dgd 11/3/2004 19:49'! dialogPaneBorderColor ^ Color black ! ! !ColorTheme methodsFor: 'theme - dialogs' stamp: 'dgd 11/3/2004 19:44'! dialogPaneBorderWidth ^ 0! ! !ColorTheme methodsFor: 'theme - dialogs' stamp: 'dgd 11/3/2004 19:30'! dialogPaneRampOrColor ^ {0.0 -> (Color r: 0.742 g: 0.871 b: 1.0). 1.0 -> (Color r: 0.516 g: 0.645 b: 1.0)}! ! !ColorTheme methodsFor: 'theme - dialogs' stamp: 'dgd 11/3/2004 19:38'! dialogRampOrColor ^ {0.0 -> (Color r: 0.516 g: 0.645 b: 1.0). 1.0 -> (Color r: 0.742 g: 0.871 b: 1.0)}! ! !ColorTheme methodsFor: 'theme - dockingbar' stamp: 'marcus.denker 11/29/2008 22:52'! dockingBarAutoGradient ^ true! ! !ColorTheme methodsFor: 'theme - dockingbar' stamp: 'marcus.denker 11/29/2008 22:52'! dockingBarColor ^self normal:1! ! !ColorTheme methodsFor: 'theme - dockingbar' stamp: 'marcus.denker 11/29/2008 22:52'! dockingBarGradientRamp ^ {0.0 -> Color white. 1.0 -> (self normal:1)}! ! !ColorTheme methodsFor: 'theme - menus' stamp: 'dgd 11/2/2004 17:30'! menuBorderColor ^ self subclassResponsibility! ! !ColorTheme methodsFor: 'theme - menus' stamp: 'dgd 11/2/2004 17:31'! menuBorderWidth ^ self subclassResponsibility! ! !ColorTheme methodsFor: 'theme - menus' stamp: 'dgd 11/2/2004 17:31'! menuColor ^ self subclassResponsibility! ! !ColorTheme methodsFor: 'theme - menus' stamp: 'dgd 11/2/2004 17:32'! menuLineColor ^ self subclassResponsibility! ! !ColorTheme methodsFor: 'theme - menus' stamp: 'dgd 11/2/2004 17:32'! menuSelectionColor ^ self subclassResponsibility! ! !ColorTheme methodsFor: 'theme - menus' stamp: 'dgd 11/2/2004 17:32'! menuTitleBorderColor ^ self subclassResponsibility! ! !ColorTheme methodsFor: 'theme - menus' stamp: 'dgd 11/2/2004 17:32'! menuTitleBorderWidth ^ self subclassResponsibility! ! !ColorTheme methodsFor: 'theme - menus' stamp: 'dgd 11/2/2004 17:32'! menuTitleColor ^ self subclassResponsibility! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ColorTheme class instanceVariableNames: ''! !ColorTheme class methodsFor: 'accessing' stamp: 'marcus.denker 11/29/2008 22:53'! current ^ self new! ! TextStream subclass: #ColoredCodeStream instanceVariableNames: 'dialect colorTable' classVariableNames: 'ST80ColorTable' poolDictionaries: '' category: 'Compiler-Kernel'! !ColoredCodeStream methodsFor: 'color/style' stamp: 'md 8/14/2005 17:33'! colorTable "Answer the table to use to determine colors" ^ colorTable ifNil: [colorTable := ST80ColorTable]! ! !ColoredCodeStream methodsFor: 'color/style' stamp: 'sw 5/20/2001 21:05'! withColor: colorSymbol emphasis: emphasisSymbol do: aBlock "Evaluate the given block with the given color and style text attribute" ^ self withAttributes: {TextColor color: (Color perform: colorSymbol). TextEmphasis perform: emphasisSymbol} do: aBlock! ! !ColoredCodeStream methodsFor: 'color/style' stamp: 'sw 5/20/2001 11:30'! withStyleFor: elementType do: aBlock "Evaluate aBlock with appropriate emphasis and color for the given elementType" | colorAndStyle | colorAndStyle := self colorTable at: elementType. ^ self withColor: colorAndStyle first emphasis: colorAndStyle second do: aBlock! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ColoredCodeStream class instanceVariableNames: ''! !ColoredCodeStream class methodsFor: 'initialization' stamp: 'wiz 9/12/2005 00:41'! initialize "Initialize the colors that characterize the ST80 dialect" ST80ColorTable := IdentityDictionary new. #( (temporaryVariable blue italic) (methodArgument blue normal) (methodSelector black bold) (blockArgument red normal) (comment brown normal) (variable magenta normal) (literal orange normal) (keyword darkGray bold) (prefixKeyword veryDarkGray bold) (setOrReturn black bold)) do: [:aTriplet | ST80ColorTable at: aTriplet first put: aTriplet allButFirst] "ColoredCodeStream initialize"! ! !ColoredCodeStream class methodsFor: 'instance creation' stamp: 'md 8/15/2005 11:00'! contents: blockWithArg "Evaluate blockWithArg on a DialectStream of the given description" | stream | stream := self on: (Text new: 400). blockWithArg value: stream. ^ stream contents! ! Object subclass: #CombinedChar instanceVariableNames: 'codes combined' classVariableNames: 'Compositions Decompositions Diacriticals' poolDictionaries: '' category: 'Multilingual-Scanning'! !CombinedChar methodsFor: 'as yet unclassified' stamp: 'sd 2/4/2008 21:22'! add: char | dict elem | codes ifNil: [codes := Array with: char. combined := char. ^ true]. dict := Compositions at: combined charCode ifAbsent: [^ false]. elem := dict at: combined charCode ifAbsent: [^ false]. codes := codes copyWith: char. combined := elem. ^ true. ! ! !CombinedChar methodsFor: 'as yet unclassified' stamp: 'yo 2/10/2004 07:08'! base ^ codes first. ! ! !CombinedChar methodsFor: 'as yet unclassified' stamp: 'yo 2/10/2004 07:08'! combined ^ combined. ! ! !CombinedChar methodsFor: 'as yet unclassified' stamp: 'yo 10/10/2007 19:50'! simpleAdd: char | dict elem | codes ifNil: [codes := Array with: char. combined := char. ^ true]. dict := Compositions at: combined charCode ifAbsent: [^ false]. elem := dict at: char charCode ifAbsent: [^ false]. combined := Character leadingChar: self base leadingChar code: elem. codes at: 1 put: combined. ^ true. ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CombinedChar class instanceVariableNames: ''! !CombinedChar class methodsFor: 'testing' stamp: 'michael.rueger 3/2/2009 10:13'! isCompositionCharacter: charCode ^Compositions includesKey: charCode! ! !CombinedChar class methodsFor: 'testing' stamp: 'yo 12/31/2002 19:21'! isDiacriticals: unicode ^ Diacriticals includes: unicode. ! ! !CombinedChar class methodsFor: 'utility' stamp: 'sd 2/4/2008 21:22'! parseCompositionMappingFrom: stream " self halt. self parseCompositionMapping " | line fieldEnd point fieldStart compositions toNumber diacritical result | toNumber := [:quad | ('16r', quad) asNumber]. Compositions := IdentityDictionary new: 2048. Decompositions := IdentityDictionary new: 2048. Diacriticals := IdentitySet new: 2048. [(line := stream upTo: Character cr) size > 0] whileTrue: [ fieldEnd := line indexOf: $; startingAt: 1. point := ('16r', (line copyFrom: 1 to: fieldEnd - 1)) asNumber. 2 to: 6 do: [:i | fieldStart := fieldEnd + 1. fieldEnd := line indexOf: $; startingAt: fieldStart. ]. compositions := line copyFrom: fieldStart to: fieldEnd - 1. (compositions size > 0 and: [compositions first ~= $<]) ifTrue: [ compositions := compositions substrings collect: toNumber. compositions size > 1 ifTrue: [ diacritical := compositions first. Diacriticals add: diacritical. result := compositions second. (Decompositions includesKey: point) ifTrue: [ self error: 'should not happen'. ] ifFalse: [ Decompositions at: point put: (Array with: diacritical with: result). ]. (Compositions includesKey: diacritical) ifTrue: [ (Compositions at: diacritical) at: result put: point. ] ifFalse: [ Compositions at: diacritical put: (IdentityDictionary new at: result put: point; yourself). ]. ]. ]. ]. ! ! Object subclass: #Command instanceVariableNames: 'phase cmdWording undoTarget undoSelector undoArguments redoTarget redoSelector redoArguments parameters' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Undo'! !Command commentStamp: '' prior: 0! An object representing an undoable command to be done in the environment. Structure: phase indicates whether the cmd is current in undone or redone mode cmdWording The wording of the command (used in arming the "undo"/"redo" menu items parameters an IdentityDictionary /NOT USED/ undoTarget Receiver, selector and arguments to accomplish undo undoSelector undoArguments redoTarget Receiver, selector and arguments to accomplish redo redoSelector redoArguments To use this, for any command you wish to use, you * Create an instance of Command, as follows... cmd _ Command new cmdWording: 'resizing'. * Give the the command undo state and redo state, as follows... cmd undoTarget: target selector: #extent: argument: oldExtent. cmd redoTarget: target selector: #extent: argument: newExtent. * Send a message of the form Command rememberCommand: cmd LastCommand is the last command that was actually done or undone. CommandHistory, applicable only when infiniteUndo is set, holds a 'tape' of the complete history of commands, as far back as it's possible to go. CommandExcursions, also applicable only in the infiniteUndo case, and rather at the fringe even then, holds segments of former CommandHistory that have been lopped off because of variant paths taken.! !Command methodsFor: 'command execution' stamp: 'di 8/30/2000 16:04'! doCommand "Do the command represented by the receiver. Not actually called by active current code, but reachable by the not-yet-unsealed promoteToCurrent: action." redoTarget ifNotNil: [redoTarget perform: redoSelector withArguments: redoArguments]! ! !Command methodsFor: 'command execution' stamp: 'di 8/30/2000 16:04'! redoCommand "Perform the 'redo' operation" redoTarget ifNotNil: [redoTarget perform: redoSelector withArguments: redoArguments]! ! !Command methodsFor: 'command execution' stamp: 'sw 2/2/2006 02:00'! stillValid "Answer whether the receiver is still valid." ^ (undoTarget isMorph and: [undoTarget isInWorld]) or: [redoTarget isMorph and: [redoTarget isInWorld]]! ! !Command methodsFor: 'command execution' stamp: 'di 8/30/2000 16:02'! undoCommand "Perform the 'undo' operation" undoTarget ifNotNil: [undoTarget perform: undoSelector withArguments: undoArguments]! ! !Command methodsFor: 'copying' stamp: 'tk 2/25/2001 17:53'! veryDeepFixupWith: deepCopier | old | "ALL inst vars were weakly copied. If they were in the tree being copied, fix them up, otherwise point to the originals!!!!" super veryDeepFixupWith: deepCopier. 1 to: self class instSize do: [:ii | old := self instVarAt: ii. self instVarAt: ii put: (deepCopier references at: old ifAbsent: [old])]. ! ! !Command methodsFor: 'copying' stamp: 'tk 2/25/2001 17:53'! veryDeepInner: deepCopier "ALL fields are weakly copied!! Can't duplicate an object by duplicating a Command that involves it. See DeepCopier." super veryDeepInner: deepCopier. "just keep old pointers to all fields" parameters := parameters.! ! !Command methodsFor: 'initialization' stamp: 'sw 8/29/2000 14:12'! cmdWording: wrd "Set the wording to be used in a menu item referring to the receiver" cmdWording := wrd! ! !Command methodsFor: 'initialization' stamp: 'sw 8/29/2000 14:13'! phase: aPhase "Set the phase of the command to the supplied symbol" phase := aPhase! ! !Command methodsFor: 'initialization' stamp: 'di 8/30/2000 13:04'! redoTarget: target selector: aSymbol argument: argument ^ self redoTarget: target selector: aSymbol arguments: {argument}! ! !Command methodsFor: 'initialization' stamp: 'di 8/30/2000 20:53'! redoTarget: target selector: selector arguments: arguments "Give target morph a chance to refine its undo operation" target refineRedoTarget: target selector: selector arguments: arguments in: [:rTarget :rSelector :rArguments | redoTarget := rTarget. redoSelector := rSelector. redoArguments := rArguments]! ! !Command methodsFor: 'initialization' stamp: 'di 8/30/2000 13:04'! undoTarget: target selector: aSymbol argument: argument ^ self undoTarget: target selector: aSymbol arguments: {argument}! ! !Command methodsFor: 'initialization' stamp: 'di 8/30/2000 20:53'! undoTarget: target selector: selector arguments: arguments "Give target morph a chance to refine its undo operation" target refineUndoTarget: target selector: selector arguments: arguments in: [:rTarget :rSelector :rArguments | undoTarget := rTarget. undoSelector := rSelector. undoArguments := rArguments]! ! !Command methodsFor: 'parameters' stamp: 'sw 8/29/2000 14:12'! parameterAt: aSymbol "Answer the parameter stored at the given symbol, or nil if none" ^ self parameterAt: aSymbol ifAbsent: [nil]! ! !Command methodsFor: 'parameters' stamp: 'sw 8/29/2000 14:12'! parameterAt: aSymbol ifAbsent: aBlock "Answer the parameter stored at the aSymbol, but if none, return the result of evaluating aBlock" ^ self assuredParameterDictionary at: aSymbol ifAbsent: [aBlock value]! ! !Command methodsFor: 'parameters' stamp: 'sw 8/29/2000 14:12'! parameterAt: aSymbol put: aValue "Place aValue in the parameters dictionary using aSymbol as key" ^ self assuredParameterDictionary at: aSymbol put: aValue! ! !Command methodsFor: 'printing' stamp: 'di 8/30/2000 14:09'! printOn: aStream "Provide more detailed info about the receiver, put in for debugging, maybe should be removed" super printOn: aStream. aStream nextPutAll: ' phase: ', phase printString. cmdWording ifNotNil: [aStream nextPutAll: '; ', cmdWording asString]. parameters ifNotNil: [parameters associationsDo: [:assoc | aStream nextPutAll: ': ', assoc printString]]! ! !Command methodsFor: 'private' stamp: 'sw 8/29/2000 14:09'! assuredParameterDictionary "Private!! Answer the parameters dictionary, creating it if necessary" ^ parameters ifNil: [parameters := IdentityDictionary new]! ! !Command methodsFor: 'private' stamp: 'dgd 8/26/2003 21:43'! cmdWording "Answer the wording to be used to refer to the command in a menu" ^ cmdWording ifNil: ['last command' translated]! ! !Command methodsFor: 'private' stamp: 'sw 8/29/2000 14:13'! phase "Answer the phase of the command" ^ phase! ! !Command methodsFor: 'private' stamp: 'di 12/12/2000 12:36'! undoTarget ^ undoTarget! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Command class instanceVariableNames: ''! !Command class methodsFor: 'dog simple ui' stamp: 'ar 8/31/2000 23:13'! redoEnabled | w | ^(w := self currentWorld) == nil ifTrue:[false] ifFalse:[w commandHistory redoEnabled]! ! !Command class methodsFor: 'dog simple ui' stamp: 'ar 8/31/2000 23:13'! redoNextCommand | w | ^(w := self currentWorld) == nil ifFalse:[w commandHistory redoNextCommand]! ! !Command class methodsFor: 'dog simple ui' stamp: 'ar 8/31/2000 23:13'! undoEnabled | w | ^(w := self currentWorld) == nil ifTrue:[false] ifFalse:[w commandHistory undoEnabled]! ! !Command class methodsFor: 'dog simple ui' stamp: 'ar 8/31/2000 23:14'! undoLastCommand | w | ^(w := self currentWorld) == nil ifFalse:[w commandHistory undoLastCommand]! ! !Command class methodsFor: 'dog simple ui' stamp: 'ar 11/9/2000 20:38'! undoRedoButtons "Answer a morph that offers undo and redo buttons" | aButton wrapper | "self currentHand attachMorph: Command undoRedoButtons" wrapper := AlignmentMorph newColumn. wrapper color: Color veryVeryLightGray lighter; borderWidth: 0; layoutInset: 0; vResizing: #shrinkWrap; hResizing: #shrinkWrap. #((CrudeUndo undoLastCommand 'undo last command done' undoEnabled CrudeUndoDisabled CrudeUndoDisabled) (CrudeRedo redoNextCommand 'redo last undone command' redoEnabled CrudeRedoDisabled CrudeRedoDisabled)) do: [:tuple | wrapper addTransparentSpacerOfSize: (8@0). aButton := UpdatingThreePhaseButtonMorph new. aButton onImage: (ScriptingSystem formAtKey: tuple first); offImage: (ScriptingSystem formAtKey: tuple fifth); pressedImage: (ScriptingSystem formAtKey: tuple sixth); getSelector: tuple fourth; color: Color transparent; target: self; actionSelector: tuple second; setNameTo: tuple second; setBalloonText: tuple third; extent: aButton onImage extent. wrapper addMorphBack: aButton. wrapper addTransparentSpacerOfSize: (8@0)]. ^ wrapper! ! !Command class methodsFor: 'initialization' stamp: 'RAA 9/21/2000 14:02'! zapObsolete "Command zapObsolete" "kill some obsolete stuff still retained by the CompiledMethods in change records" | before after histories lastCmd histCount lastCount | Smalltalk garbageCollect. before := Command allInstances size. histories := Association allInstances select: [ :each | each key == #CommandHistory and: [ (each value isKindOf: OrderedCollection) and: [ each value isEmpty not and: [ each value first isKindOf: Command]]] ]. histCount := histories size. lastCmd := Association allInstances select: [ :each | each key == #LastCommand and: [each value isKindOf: Command] ]. lastCount := lastCmd size. histories do: [ :each | each value: OrderedCollection new]. lastCmd do: [ :each | each value: Command new]. Smalltalk garbageCollect. Smalltalk garbageCollect. after := Command allInstances size. Transcript show: {before. after. histCount. histories. lastCount. lastCmd} printString; cr; cr. ! ! Object subclass: #CommandHistory instanceVariableNames: 'lastCommand history excursions' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Undo'! !CommandHistory methodsFor: 'called by programmer' stamp: 'sw 2/2/2006 01:48'! assureLastCommandStillValid "If the lastCommand is not valid, set it to nil; answer the lastCommand." lastCommand ifNotNil: [lastCommand stillValid ifFalse: [self cantUndo]]. ^ lastCommand! ! !CommandHistory methodsFor: 'called by programmer' stamp: 'ar 8/31/2000 22:46'! cantUndo "Called by client to indicate that the prior undoable command is no longer undoable" lastCommand := nil. history := OrderedCollection new.! ! !CommandHistory methodsFor: 'called by programmer' stamp: 'ar 8/31/2000 22:47'! promoteToCurrent: aCommand "Very unusual and speculative and unfinished!!. Not currently reachable. For the real thing, we presumably march forward or backward from the current command pointer to the target command in an orderly fashion, doing or undoing each command in turn." | itsIndex | Preferences useUndo ifFalse: [^ self]. itsIndex := history indexOf: aCommand ifAbsent: [nil]. itsIndex ifNotNil: [history remove: aCommand ifAbsent: []]. history add: (lastCommand := aCommand). itsIndex < history size ifTrue: [excursions add: (history copyFrom: (itsIndex to: history size))]. history := (history copyFrom: 1 to: itsIndex) copyWith: aCommand. lastCommand := aCommand. aCommand doCommand. lastCommand phase: #done.! ! !CommandHistory methodsFor: 'called by programmer' stamp: 'aoy 2/15/2003 21:14'! purgeAllCommandsSuchThat: cmdBlock "Remove a bunch of commands, as in [:cmd | cmd undoTarget == zort]" Preferences useUndo ifFalse: [^self]. history := history reject: cmdBlock. lastCommand := history isEmpty ifTrue: [nil] ifFalse: [history last] ! ! !CommandHistory methodsFor: 'called from the ui' stamp: 'ar 8/31/2000 22:49'! commandToUndo "Undo the last command, i.e. move backward in the recent-commands tape, if possible." | anIndex | lastCommand ifNil: [^ nil]. lastCommand phase == #done ifTrue: [^ lastCommand]. (lastCommand phase == #undone and: [(anIndex := history indexOf: lastCommand) > 1]) ifTrue: [^ history at: anIndex - 1] ifFalse: [^ nil] ! ! !CommandHistory methodsFor: 'called from the ui' stamp: 'nb 6/17/2003 12:25'! redoNextCommand "If there is a way to 'redo' (move FORWARD) in the undo/redo history tape, do it." | anIndex | lastCommand ifNil: [^ Beeper beep]. lastCommand phase == #undone ifFalse: [anIndex := history indexOf: lastCommand. (anIndex < history size) ifTrue: [lastCommand := history at: anIndex + 1] ifFalse: [^ Beeper beep]]. lastCommand redoCommand. lastCommand phase: #done ! ! !CommandHistory methodsFor: 'called from the ui' stamp: 'nb 6/17/2003 12:25'! undoLastCommand "Undo the last command, i.e. move backward in the recent-commands tape, if possible." | aPhase anIndex | lastCommand ifNil: [^ Beeper beep]. (aPhase := lastCommand phase) == #done ifFalse: [aPhase == #undone ifTrue: [anIndex := history indexOf: lastCommand. anIndex > 1 ifTrue: [lastCommand := history at: anIndex - 1]]]. lastCommand undoCommand. lastCommand phase: #undone "Command undoLastCommand" ! ! !CommandHistory methodsFor: 'called from the ui' stamp: 'nb 6/17/2003 12:25'! undoOrRedoCommand "This gives a feature comparable to standard Mac undo/redo. If the undo/redo action taken was a simple do or a redo, then undo it. But if the last undo/redo action taken was an undo, then redo it." "Command undoOrRedoCommand" | aPhase | lastCommand ifNil: [^ Beeper beep]. (aPhase := lastCommand phase) == #done ifTrue: [lastCommand undoCommand. lastCommand phase: #undone] ifFalse: [aPhase == #undone ifTrue: [lastCommand redoCommand. lastCommand phase: #done]]! ! !CommandHistory methodsFor: 'called from the ui' stamp: 'alain.plantec 2/6/2009 16:53'! undoTo "Not yet functional, and not yet sent. Allow the user to choose a point somewhere in the undo/redo tape, and undo his way to there. Applicable only if infiniteUndo is set. " | anIndex commandList reply | (anIndex := self historyIndexOfLastCommand) == 0 ifTrue: [^ Beeper beep]. commandList := history copyFrom: ((anIndex - 10) max: 1) to: ((anIndex + 10) min: history size). reply := UIManager default chooseFrom: (commandList collect: [:cmd | cmd cmdWording truncateWithElipsisTo: 20]) values: commandList title: 'undo or redo to...' translated. reply ifNotNil: [self inform: #deferred] "ActiveWorld commandHistory undoTo" ! ! !CommandHistory methodsFor: 'command history' stamp: 'ar 8/31/2000 22:44'! historyIndexOfLastCommand "Answer which position of the CommandHistory list is occupied by the LastCommand" ^ history indexOf: lastCommand ifAbsent: [0]! ! !CommandHistory methodsFor: 'command history' stamp: 'ar 8/31/2000 22:45'! lastCommand "Answer the last command done or undone" ^ lastCommand! ! !CommandHistory methodsFor: 'command history' stamp: 'ar 8/31/2000 22:45'! nextCommand "Answer the command object that would be sent the #redoCommand message if the user were to request Redo, or nil if none" | anIndex | lastCommand ifNil: [^ nil]. lastCommand phase == #undone ifTrue: [^ lastCommand]. anIndex := history indexOf: lastCommand ifAbsent: [^ nil]. ^ anIndex = history size ifTrue: [nil] ifFalse: [history at: (anIndex + 1)]! ! !CommandHistory methodsFor: 'command history' stamp: 'di 12/12/2000 13:46'! resetCommandHistory "CommandHistory allInstancesDo: [:ch | ch resetCommandHistory]" "Clear out the command history so that no commands are held" lastCommand := nil. history := OrderedCollection new.! ! !CommandHistory methodsFor: 'initialize' stamp: 'alain.plantec 5/28/2009 09:48'! initialize super initialize. lastCommand := nil. history := OrderedCollection new. excursions := OrderedCollection new.! ! !CommandHistory methodsFor: 'menu' stamp: 'ar 8/31/2000 22:41'! nextCommandToUndo | anIndex | lastCommand ifNil: [^ nil]. lastCommand phase == #done ifTrue: [^ lastCommand]. (lastCommand phase == #undone and: [(anIndex := history indexOf: lastCommand) > 1]) ifTrue: [^ history at: anIndex - 1] ifFalse: [^ nil]! ! !CommandHistory methodsFor: 'menu' stamp: 'ar 8/31/2000 22:39'! redoEnabled "Answer whether the redo command is currently available" ^ self nextCommand notNil! ! !CommandHistory methodsFor: 'menu' stamp: 'dgd 4/3/2006 14:26'! redoMenuWording "Answer the wording to be used in a menu offering the current Redo command" | nextCommand | ((nextCommand := self nextCommand) isNil or: [Preferences useUndo not]) ifTrue: [^ 'can''t redo' translated]. ^ String streamContents: [:aStream | aStream nextPutAll: 'redo' translated. aStream nextPutAll: ' "'. aStream nextPutAll: (nextCommand cmdWording truncateWithElipsisTo: 20). aStream nextPut: $". lastCommand phase == #done ifFalse: [aStream nextPutAll: ' (z)']]! ! !CommandHistory methodsFor: 'menu' stamp: 'ar 8/31/2000 22:40'! undoEnabled "Answer whether there is an undoable command at the ready" ^ lastCommand notNil! ! !CommandHistory methodsFor: 'menu' stamp: 'dgd 4/3/2006 14:26'! undoMenuWording "Answer the wording to be used in an 'undo' menu item" (lastCommand isNil or: [Preferences useUndo not] or: [Preferences infiniteUndo not and: [lastCommand phase == #undone]] or: [self nextCommandToUndo isNil]) ifTrue: [^ 'can''t undo' translated]. ^ String streamContents: [:aStream | aStream nextPutAll: 'undo' translated. aStream nextPutAll: ' "'. aStream nextPutAll: (self nextCommandToUndo cmdWording truncateWithElipsisTo: 20). aStream nextPut: $". lastCommand phase == #done ifTrue: [aStream nextPutAll: ' (z)']].! ! !CommandHistory methodsFor: 'menu' stamp: 'sw 2/2/2006 01:53'! undoOrRedoMenuWording "Answer the wording to be used in a menu item offering undo/redo (i.e., the form used when the #infiniteUndo preference is false)" | pre | self assureLastCommandStillValid. lastCommand ifNil: [^ 'can''t undo' translated]. pre := lastCommand phase == #done ifTrue: ['undo' translated] ifFalse: ['redo' translated]. ^ pre, ' "', (lastCommand cmdWording truncateWithElipsisTo: 20), '" (z)'! ! !CommandHistory methodsFor: 'undo' stamp: 'di 12/12/2000 10:16'! rememberCommand: aCommand "Make the supplied command be the 'LastCommand', and mark it 'done'" | currentCommandIndex | Preferences useUndo ifFalse: [^ self]. "Command initialize" Preferences infiniteUndo ifTrue: [currentCommandIndex := history indexOf: lastCommand. ((currentCommandIndex < history size) and: [Preferences preserveCommandExcursions]) ifTrue: [excursions add: (history copyFrom: (currentCommandIndex to: history size)). history := history copyFrom: 1 to: currentCommandIndex]. history addLast: aCommand]. lastCommand := aCommand. lastCommand phase: #done.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CommandHistory class instanceVariableNames: ''! !CommandHistory class methodsFor: 'initialization' stamp: 'dgd 4/3/2006 14:28'! initialize "CommandHistory initialize" Smalltalk addToStartUpList: self. Smalltalk addToShutDownList: self.! ! !CommandHistory class methodsFor: 'system startup' stamp: 'tk 5/16/2002 13:52'! forgetAllGrabCommandsFrom: starter "Forget all the commands that might be held on to in the properties dicitonary of various morphs for various reasons." | object | object := starter. [ [0 == object] whileFalse: [ object isMorph ifTrue: [object removeProperty: #undoGrabCommand]. object := object nextObject]. ] ifError: [:err :rcvr | "object is obsolete" self forgetAllGrabCommandsFrom: object nextObject]. "CommandHistory forgetAllGrabCommandsFrom: true someObject" ! ! !CommandHistory class methodsFor: 'system startup' stamp: 'tk 5/16/2002 13:38'! resetAllHistory "Reset all command histories, and make all morphs that might be holding on to undo-grab-commands forget them" self allInstancesDo: [:c | c resetCommandHistory]. self forgetAllGrabCommandsFrom: self someObject. "CommandHistory resetAllHistory" ! ! !CommandHistory class methodsFor: 'system startup' stamp: 'adrian_lienhard 2/16/2009 10:49'! shutDown: aboutToQuit aboutToQuit ifFalse: [^ self]. Preferences purgeUndoOnQuit ifTrue: [self resetAllHistory]! ! !CommandHistory class methodsFor: 'system startup' stamp: 'adrian_lienhard 2/16/2009 10:49'! startUp: resuming resuming ifFalse: [^ self]. Preferences purgeUndoOnQuit ifFalse: [self resetAllHistory] ! ! AbstractLauncher subclass: #CommandLineLauncherExample instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Download'! !CommandLineLauncherExample commentStamp: '' prior: 0! CommandLineLauncherExample provides an example for a command line application. if you start squeak with a command line 'class Integer' it will launch a class browser on class Integer. To enable this execute CommandLineLauncherExample activate before you save the image. To disable execute CommandLineLauncherExample deactivate! !CommandLineLauncherExample methodsFor: 'running' stamp: 'ar 9/27/2005 20:23'! startUp | className | className := self parameterAt: 'class'. ToolSet browse: (Smalltalk at: className asSymbol ifAbsent: [Object]) selector: nil! ! ParseNode subclass: #CommentNode instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Compiler-ParseNodes'! !CommentNode methodsFor: 'visiting' stamp: 'eem 5/30/2008 09:43'! accept: aVisitor aVisitor visitCommentNode: self! ! AbstractEvent subclass: #CommentedEvent instanceVariableNames: 'oldComment newComment oldStamp newStamp' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'! !CommentedEvent methodsFor: 'accessing' stamp: 'gk 8/15/2007 01:17'! newComment ^newComment! ! !CommentedEvent methodsFor: 'accessing' stamp: 'gk 8/15/2007 01:17'! newComment: aString newComment := aString! ! !CommentedEvent methodsFor: 'accessing' stamp: 'gk 8/23/2007 21:37'! newStamp ^newStamp! ! !CommentedEvent methodsFor: 'accessing' stamp: 'gk 8/23/2007 21:37'! newStamp: aString newStamp := aString! ! !CommentedEvent methodsFor: 'accessing' stamp: 'gk 8/15/2007 01:18'! oldComment ^oldComment! ! !CommentedEvent methodsFor: 'accessing' stamp: 'gk 8/15/2007 01:17'! oldComment: aString oldComment := aString! ! !CommentedEvent methodsFor: 'accessing' stamp: 'gk 8/23/2007 21:37'! oldStamp ^oldStamp! ! !CommentedEvent methodsFor: 'accessing' stamp: 'gk 8/23/2007 21:37'! oldStamp: aString oldStamp := aString! ! !CommentedEvent methodsFor: 'printing' stamp: 'rw 7/1/2003 11:37'! printEventKindOn: aStream aStream nextPutAll: 'Commented'! ! !CommentedEvent methodsFor: 'testing' stamp: 'rw 7/1/2003 11:37'! isCommented ^true! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CommentedEvent class instanceVariableNames: ''! !CommentedEvent class methodsFor: 'accessing' stamp: 'rw 7/10/2003 12:08'! changeKind ^#Commented! ! !CommentedEvent class methodsFor: 'accessing'! class: aClass oldComment: oldComment newComment: newComment ^(self class: aClass) oldComment: oldComment; newComment: newComment; yourself! ! !CommentedEvent class methodsFor: 'accessing' stamp: 'gk 8/23/2007 21:36'! class: aClass oldComment: oldComment newComment: newComment oldStamp: oldStamp newStamp: newStamp ^(self class: aClass) oldComment: oldComment; newComment: newComment; oldStamp: oldStamp; newStamp: newStamp; yourself! ! !CommentedEvent class methodsFor: 'accessing' stamp: 'rw 7/10/2003 11:20'! supportedKinds ^Array with: self classKind! ! ByteArray variableByteSubclass: #CompiledMethod instanceVariableNames: '' classVariableNames: 'LargeFrame SmallFrame' poolDictionaries: '' category: 'Kernel-Methods'! !CompiledMethod commentStamp: 'ls 7/5/2003 13:48' prior: 0! My instances are methods suitable for interpretation by the virtual machine. This is the only class in the system whose instances intermix both indexable pointer fields and indexable integer fields. The current format of a CompiledMethod is as follows: header (4 bytes) literals (4 bytes each) bytecodes (variable) trailer (variable) The header is a 30-bit integer with the following format: (index 0) 9 bits: main part of primitive number (#primitive) (index 9) 8 bits: number of literals (#numLiterals) (index 17) 1 bit: whether a large frame size is needed (#frameSize) (index 18) 6 bits: number of temporary variables (#numTemps) (index 24) 4 bits: number of arguments to the method (#numArgs) (index 28) 1 bit: high-bit of primitive number (#primitive) (index 29) 1 bit: flag bit, ignored by the VM (#flag) The trailer has two variant formats. In the first variant, the last byte is at least 252 and the last four bytes represent a source pointer into one of the sources files (see #sourcePointer). In the second variant, the last byte is less than 252, and the last several bytes are a compressed version of the names of the method's temporary variables. The number of bytes used for this purpose is the value of the last byte in the method. ! !CompiledMethod methodsFor: '*Tools-Inspector' stamp: 'eem 5/15/2008 13:14'! explorerContents "(CompiledMethod compiledMethodAt: #explorerContents) explore" ^Array streamContents: [:s| | tokens | tokens := Scanner new scanTokens: (self headerDescription readStream skipTo: $"; upTo: $"). s nextPut: (ObjectExplorerWrapper with: ((0 to: tokens size by: 2) collect: [:i| i = 0 ifTrue: [self header] ifFalse: [{tokens at: i - 1. tokens at: i}]]) name: 'header' model: self). (1 to: self numLiterals) do: [:key| s nextPut: (ObjectExplorerWrapper with: (self literalAt: key) name: ('literal', key printString contractTo: 32) model: self)]. self isQuick ifTrue: [s nextPut: (ObjectExplorerWrapper with: self symbolic name: #symbolic model: self)] ifFalse: [self symbolicLinesDo: [:pc :line| pc <= 1 ifTrue: [s nextPut: (ObjectExplorerWrapper with: line name: 'pragma' model: self)] ifFalse: [s nextPut: (ObjectExplorerWrapper with: line name: pc printString model: self)]]]. "should be self numLiterals + 1 * Smalltalk wordSize + 1" self endPC + 1 to: self basicSize do: [:key| s nextPut: (ObjectExplorerWrapper with: (self basicAt: key) name: key printString model: self)]]! ! !CompiledMethod methodsFor: '*Tools-Inspector' stamp: 'ar 9/27/2005 18:32'! inspectorClass "Answer the class of the inspector to be used on the receiver. Called by inspect; use basicInspect to get a normal (less useful) type of inspector." ^ CompiledMethodInspector! ! !CompiledMethod methodsFor: 'accessing' stamp: 'md 3/31/2007 19:45'! classBinding ^(self literalAt: self numLiterals) ! ! !CompiledMethod methodsFor: 'accessing' stamp: 'eem 8/20/2009 11:43'! clearFlag "Clear the user-level flag bit" self objectAt: 1 put: (self header bitAnd: (1 << 29) bitInvert)! ! !CompiledMethod methodsFor: 'accessing' stamp: 'md 2/18/2006 13:11'! defaultSelector "Invent and answer an appropriate message selector (a Symbol) for me, that is, one that will parse with the correct number of arguments." ^#DoIt numArgs: self numArgs! ! !CompiledMethod methodsFor: 'accessing' stamp: 'eem 6/30/2009 12:38'! endPC "Answer the index of the last bytecode." | size flagByte | "Can't create a zero-sized CompiledMethod so no need to use last for the errorEmptyCollection check. We can reuse size." size := self size. flagByte := self at: size. flagByte = 0 ifTrue: ["If last byte = 0, may be either 0, 0, 0, 0 or just 0" 1 to: 4 do: [:i | (self at: size - i) = 0 ifFalse: [^size - i]]]. flagByte < 252 ifTrue: ["Magic sources (temp names encoded in last few bytes)" ^flagByte <= 127 ifTrue: [size - flagByte - 1] ifFalse: [size - (flagByte - 128 * 128) - (self at: size - 1) - 2]]. "Normal 4-byte source pointer" ^size - 4! ! !CompiledMethod methodsFor: 'accessing' stamp: 'eem 8/20/2009 11:42'! flag "Answer the user-level flag bit" ^((self header bitShift: -29) bitAnd: 1) = 1! ! !CompiledMethod methodsFor: 'accessing' stamp: 'di 1/2/1999 17:00'! flushCache "Tell the interpreter to remove all references to this method from its method lookup cache, if it has one. This primitive must be called whenever a method is defined or removed. NOTE: Only one of two selective flush methods needs to be used. Squeak 2.2 and earlier uses 119 (See Symbol flushCache). Squeak 2.3 and later uses 116 (See CompiledMethod flushCache)." ! ! !CompiledMethod methodsFor: 'accessing' stamp: 'di 10/23/1999 22:00'! frameSize "Answer the size of temporary frame needed to run the receiver." "NOTE: Versions 2.7 and later use two sizes of contexts." (self header noMask: 16r20000) ifTrue: [^ SmallFrame] ifFalse: [^ LargeFrame] ! ! !CompiledMethod methodsFor: 'accessing'! initialPC "Answer the program counter for the receiver's first bytecode." ^ (self numLiterals + 1) * 4 + 1! ! !CompiledMethod methodsFor: 'accessing' stamp: 'eem 11/29/2008 11:38'! methodClass "answer the class that I am installed in" ^(self literalAt: self numLiterals) value.! ! !CompiledMethod methodsFor: 'accessing' stamp: 'md 2/16/2006 11:30'! methodClass: aClass "set the class binding in the last literal to aClass" self literalAt: self numLiterals put: aClass binding! ! !CompiledMethod methodsFor: 'accessing' stamp: 'eem 11/29/2008 11:38'! methodClassAssociation "answer the association to the class that I am installed in, or nil if none." ^self literalAt: self numLiterals! ! !CompiledMethod methodsFor: 'accessing' stamp: 'md 2/16/2006 14:00'! methodReference | class selector | class := self methodClass ifNil: [^nil]. selector := self selector ifNil: [^nil]. ^MethodReference class: class selector: selector. ! ! !CompiledMethod methodsFor: 'accessing' stamp: 'ar 6/2/1998 16:26'! numArgs "Answer the number of arguments the receiver takes." ^ (self header bitShift: -24) bitAnd: 16r0F! ! !CompiledMethod methodsFor: 'accessing'! numLiterals "Answer the number of literals used by the receiver." ^ (self header bitShift: -9) bitAnd: 16rFF! ! !CompiledMethod methodsFor: 'accessing'! numTemps "Answer the number of temporary variables used by the receiver." ^ (self header bitShift: -18) bitAnd: 16r3F! ! !CompiledMethod methodsFor: 'accessing' stamp: 'adrian_lienhard 2/21/2009 13:40'! origin ^ self methodClass traitOrClassOfSelector: self selector! ! !CompiledMethod methodsFor: 'accessing' stamp: 'ls 6/22/2000 14:35'! primitive "Answer the primitive index associated with the receiver. Zero indicates that this is not a primitive method. We currently allow 10 bits of primitive index, but they are in two places for backward compatibility. The time to unpack is negligible, since the reconstituted full index is stored in the method cache." | primBits | primBits := self header bitAnd: 16r100001FF. ^ (primBits bitAnd: 16r1FF) + (primBits bitShift: -19) ! ! !CompiledMethod methodsFor: 'accessing' stamp: 'eem 11/30/2008 08:55'! properties "Answer the method properties of the receiver." | propertiesOrSelector | ^(propertiesOrSelector := self penultimateLiteral) isMethodProperties ifTrue: [propertiesOrSelector] ifFalse: [AdditionalMethodState forMethod: self selector: propertiesOrSelector]! ! !CompiledMethod methodsFor: 'accessing' stamp: 'eem 11/29/2008 17:23'! properties: aMethodProperties "Set the method-properties of the receiver to aMethodProperties." self literalAt: self numLiterals - 1 put: (aMethodProperties isEmpty ifTrue: [aMethodProperties selector] ifFalse: [aMethodProperties setMethod: self; yourself])! ! !CompiledMethod methodsFor: 'accessing'! returnField "Answer the index of the instance variable returned by a quick return method." | prim | prim := self primitive. prim < 264 ifTrue: [self error: 'only meaningful for quick-return'] ifFalse: [^ prim - 264]! ! !CompiledMethod methodsFor: 'accessing' stamp: 'md 1/20/2006 16:09'! scanner ^ InstructionStream on: self! ! !CompiledMethod methodsFor: 'accessing' stamp: 'md 2/15/2006 20:51'! searchForClass "search me in all classes, if found, return my class. Slow!!" self systemNavigation allBehaviorsDo: [:class | (class methodDict keyAtIdentityValue: self ifAbsent: [nil]) ifNotNil: [^class]]. ^nil.! ! !CompiledMethod methodsFor: 'accessing' stamp: 'md 2/15/2006 20:51'! searchForSelector "search me in all classes, if found, return my selector. Slow!!" | selector | self systemNavigation allBehaviorsDo: [:class | (selector := class methodDict keyAtIdentityValue: self ifAbsent: [nil]) ifNotNil: [^selector]]. ^nil.! ! !CompiledMethod methodsFor: 'accessing' stamp: 'eem 11/28/2008 12:54'! selector "Answer a method's selector. This is either the penultimate literal, or, if the method has any properties or pragmas, the selector of the MethodProperties stored in the penultimate literal." | penultimateLiteral | ^(penultimateLiteral := self penultimateLiteral) isMethodProperties ifTrue: [penultimateLiteral selector] ifFalse: [penultimateLiteral]! ! !CompiledMethod methodsFor: 'accessing' stamp: 'eem 11/28/2008 12:58'! selector: aSelector "Set a method's selector. This is either the penultimate literal, or, if the method has any properties or pragmas, the selector of the MethodProperties stored in the penultimate literal." | penultimateLiteral nl | (penultimateLiteral := self penultimateLiteral) isMethodProperties ifTrue: [penultimateLiteral selector: aSelector] ifFalse: [(nl := self numLiterals) < 2 ifTrue: [self error: 'insufficient literals to hold selector']. self literalAt: nl - 1 put: aSelector]! ! !CompiledMethod methodsFor: 'accessing' stamp: 'ajh 11/17/2001 14:30'! trailer | end trailer | end := self endPC. trailer := ByteArray new: self size - end. end + 1 to: self size do: [:i | trailer at: i - end put: (self at: i)]. ^ trailer! ! !CompiledMethod methodsFor: 'class accessing' stamp: 'stephane.ducasse 3/30/2009 22:43'! category ^self methodClass organization categoryOfElement:self selector! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:10'! allEmbeddedBlockMethods | set | set := OrderedCollection new. 1 to: self numLiterals do: [:i | | lit | lit := self literalAt: i. (lit isKindOf: CompiledMethod) ifTrue: [ set add: lit. set addAll: lit allEmbeddedBlockMethods. ] ifFalse: [(lit isKindOf: BlockClosure) ifTrue: [ set add: lit method. set addAll: lit method allEmbeddedBlockMethods ]]. ]. ^ set! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:01'! containsBlockClosures ^ self embeddedBlockMethods size > 0! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:10'! createBlock: env ^ BlockClosure new env: env; method: self! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:00'! embeddedBlockMethods | set | set := OrderedCollection new. 1 to: self numLiterals do: [:i | | lit | lit := self literalAt: i. (lit isKindOf: CompiledMethod) ifTrue: [ set add: lit. ] ifFalse: [(lit isKindOf: BlockClosure) ifTrue: [ set add: lit method. ]]. ]. ^ set! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:08'! isBlockMethod "Is this a sub-method (embedded block's method) of another method. If so the last literal points to its outer method" ^ (self header bitAnd: 1 << 29) ~= 0! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:08'! isBlockMethod: bool "Use the sign bit in the header to mark methods that are sub-methods of an outer method. The outer method will be held in my last literal." self objectAt: 1 put: (bool ifTrue: [self header bitOr: 1 << 29] ifFalse: [self header bitAnd: (1 << 29) bitInvert])! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:09'! isClosureCompiled: bool "Use the sign bit in the header to mark methods that have been compiled using the new closure compiler (Parser2)." self objectAt: 1 put: (bool ifTrue: [(self header bitOr: 1 << 30) as31BitSmallInt] ifFalse: [(self header bitAnd: (1 << 30) bitInvert) as31BitSmallInt])! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:09'! method "polymorphic with closure" ^ self! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:09'! remoteReturns "For closure methods only" ^ self messages includes: #privRemoteReturnTo:! ! !CompiledMethod methodsFor: 'closures' stamp: 'md 1/20/2006 16:56'! searchImageForHomeMethod Smalltalk allObjectsDo: [:obj | obj class == CompiledMethod ifTrue: [ (obj pointsTo: self) ifTrue: [^ obj searchImageForHomeMethod] ] ifFalse: [obj class == BlockClosure ifTrue: [ (obj method == self and: [obj size = 0]) ifTrue: [^ obj searchImageForHomeMethod] ]] ]. ^ self "must be a loner block method"! ! !CompiledMethod methodsFor: 'comparing' stamp: 'eem 7/29/2008 14:46'! = method | numLits | "Answer whether the receiver implements the same code as the argument, method." (method isKindOf: CompiledMethod) ifFalse: [^false]. self size = method size ifFalse: [^false]. self header = method header ifFalse: [^false]. self initialPC to: self endPC do: [:i | (self at: i) = (method at: i) ifFalse: [^false]]. (numLits := self numLiterals) ~= method numLiterals ifTrue: [^false]. "``Dont bother checking FFI and named primitives'' (#(117 120) includes: self primitive) ifTrue: [^ true]." 1 to: numLits do: [:i| | lit1 lit2 | lit1 := self literalAt: i. lit2 := method literalAt: i. lit1 = lit2 ifFalse: [(i = 1 and: [#(117 120) includes: self primitive]) ifTrue: [lit1 isArray ifTrue: [(lit2 isArray and: [lit1 allButLast = lit2 allButLast]) ifFalse: [^false]] ifFalse: "ExternalLibraryFunction" [(lit1 analogousCodeTo: lit2) ifFalse: [^false]]] ifFalse: [i = (numLits - 1) ifTrue: "properties" [(lit1 analogousCodeTo: lit2) ifFalse: [^false]] ifFalse: [lit1 isFloat ifTrue: ["Floats match if values are close, due to roundoff error." (lit1 closeTo: lit2) ifFalse: [^false]. self flag: 'just checking'. self halt] ifFalse: ["any other discrepancy is a failure" ^ false]]]]]. ^true! ! !CompiledMethod methodsFor: 'comparing' stamp: 'md 2/16/2006 17:07'! equivalentTo: aCompiledMethod "does not work yet with non-RB parseTrees" ^ self = aCompiledMethod or: [self class == aCompiledMethod class and: [self numArgs == aCompiledMethod numArgs and: [self decompile = aCompiledMethod decompile]]].! ! !CompiledMethod methodsFor: 'debugger support' stamp: 'eem 6/5/2008 10:32'! abstractPCForConcretePC: concretePC "Answer the abstractPC matching concretePC." | abstractPC scanner client | self flag: 'belongs in DebuggerMethodMap?'. abstractPC := 1. scanner := InstructionStream on: self. client := InstructionClient new. [(scanner atEnd or: [scanner pc >= concretePC]) ifTrue: [^abstractPC]. abstractPC := abstractPC + 1. scanner interpretNextInstructionFor: client. true] whileTrue! ! !CompiledMethod methodsFor: 'debugger support' stamp: 'eem 6/3/2008 16:15'! blockExtentsInto: aDictionary from: initialPC to: endPC scanner: scanner numberer: numbererBlock "Support routine for startpcsToBlockExtents" | extentStart blockSizeOrLocator | self flag: 'belongs in DebuggerMethodMap'. extentStart := numbererBlock value. [scanner pc <= endPC] whileTrue: [blockSizeOrLocator := scanner interpretNextInstructionFor: BlockStartLocator new. blockSizeOrLocator isInteger ifTrue: [self blockExtentsInto: aDictionary from: scanner pc to: scanner pc + blockSizeOrLocator - 1 scanner: scanner numberer: numbererBlock]]. aDictionary at: initialPC put: (extentStart to: numbererBlock value). ^aDictionary! ! !CompiledMethod methodsFor: 'debugger support' stamp: 'eem 6/30/2009 12:37'! blockExtentsToTempsMap "If the receiver has been copied with temp names answer a map from blockExtent to temps map in the same format as BytecodeEncoder>>blockExtentsToTempNamesMap. if the receiver has not been copied with temps answer nil." ^self holdsTempNames ifTrue: [self mapFromBlockKeys: ((self startpcsToBlockExtents associations asSortedCollection: [:a1 :a2| a1 key < a2 key]) collect: [:assoc| assoc value]) toSchematicTemps: self tempNamesString]! ! !CompiledMethod methodsFor: 'debugger support' stamp: 'eem 6/5/2008 09:10'! debuggerMap ^DebuggerMethodMap forMethod: self! ! !CompiledMethod methodsFor: 'debugger support' stamp: 'emm 5/30/2002 09:22'! hasBreakpoint ^BreakpointManager methodHasBreakpoint: self! ! !CompiledMethod methodsFor: 'debugger support' stamp: 'eem 6/29/2009 09:48'! mapFromBlockKeys: keys toSchematicTemps: schematicTempNamesString "Decode a schematicTempNamesString that encodes the layout of temp names in a method and any closures/blocks within it, matching keys in keys to vectors of temp names." | map tempNames | map := Dictionary new. tempNames := schematicTempNamesString readStream. keys do: [:key| | tempSequence tempIndex | tempSequence := OrderedCollection new. tempIndex := 0. [(tempNames skipSeparators; peek) ifNil: [true] ifNotNil: [:ch| '[]' includes: ch]] whileFalse: [tempNames peek = $( ifTrue: [tempSequence addAllLast: ((self tempsSubSequenceFrom: (tempNames next; yourself)) withIndexCollect: [:temp :index| { temp. { tempIndex + 1. index } }]). tempNames peek ~= $) ifTrue: [self error: 'parse error']. tempIndex := tempIndex + 1. tempNames next] ifFalse: [tempSequence addAllLast: ((self tempsSubSequenceFrom: tempNames) withIndexCollect: [:temp :index| { temp. tempIndex := tempIndex + 1 }])]]. map at: key put: tempSequence asArray. [tempNames peek = $]] whileTrue: [tempNames next]. tempNames peek = $[ ifTrue: [tempNames next]]. ^map! ! !CompiledMethod methodsFor: 'debugger support' stamp: 'eem 6/14/2008 18:58'! pcPreviousTo: pc | scanner client prevPc | self flag: 'belongs in DebuggerMethodMap?'. pc > self endPC ifTrue: [^self endPC]. scanner := InstructionStream on: self. client := InstructionClient new. [scanner pc < pc] whileTrue: [prevPc := scanner pc. scanner interpretNextInstructionFor: client]. ^prevPc! ! !CompiledMethod methodsFor: 'debugger support' stamp: 'eem 6/29/2009 09:50'! startpcsToBlockExtents "Answer a Dictionary of startpc to Interval of blockExtent, using the identical numbering scheme described in and orchestrated by BlockNode>>analyseArguments:temporaries:rootNode:. This is used in part to find the temp names for any block in a method, as needed by the debugger. The other half is to recompile the method, obtaining the temp names for each block extent. By indirecting through the blockExtent instead of using the startpc directly we decouple the debugger's access to temp names from the exact bytecode; insulating debugging from minor changes in the compiler (e.g. changes in literal pooling, adding prefix bytecodes, adding inst vars to CompiledMethod in literals towards the end of the literal frame, etc). If the recompilation doesn't produce exactly the same bytecode at exactly the same offset no matter; the blockExtents will be the same." | index | self flag: 'belongs in DebuggerMethodMap'. index := 0. ^self blockExtentsInto: Dictionary new from: self initialPC to: self endPC scanner: (InstructionStream on: self) numberer: [| value | value := index. index := index + 2. value]! ! !CompiledMethod methodsFor: 'debugger support' stamp: 'eem 7/1/2009 10:09'! tempsSubSequenceFrom: tempNamesStream ^Array streamContents: [:tsss| [tempNamesStream skipSeparators. tempNamesStream atEnd or: ['[]()' includes: tempNamesStream peek]] whileFalse: [tsss nextPut: (String streamContents: [:s| [s nextPut: tempNamesStream next. tempNamesStream peek ifNil: [true] ifNotNil: [:peek| ' []()' includes: peek]] whileFalse])]] "thisContext method tempsSubSequenceFrom: 'les temps perdu(sont n''est pas la)' readStream" "thisContext method tempsSubSequenceFrom: ('les temps perdu(sont n''est pas la)' readStream skipTo: $(; yourself)"! ! !CompiledMethod methodsFor: 'decompiling' stamp: 'eem 4/30/2009 18:13'! compilerClass ^self methodClass ifNil: [Compiler] ifNotNil: [:class | class compilerClass].! ! !CompiledMethod methodsFor: 'decompiling' stamp: 'md 2/16/2006 17:08'! decompile "Return the decompiled parse tree that represents self" | class selector | class := self methodClass ifNil: [Object]. selector := self selector ifNil: [self defaultSelector]. ^class decompilerClass new decompile: selector in: class method: self.! ! !CompiledMethod methodsFor: 'decompiling' stamp: 'md 2/22/2006 15:59'! decompileWithTemps "Return the decompiled parse tree that represents self, but get the temp names by compiling the sourcecode..." | class selector | class := self methodClass ifNil: [Object]. selector := self selector ifNil: [self defaultSelector]. (self fileIndex > 0 and: [(SourceFiles at: self fileIndex) isNil]) ifTrue: [ "Emergency or no source file -- decompile without temp names " ^self decompile. ]. ^((self decompilerClass new withTempNames: self methodNode tempNames) decompile: selector in: class method: self)! ! !CompiledMethod methodsFor: 'decompiling' stamp: 'eem 9/5/2009 14:17'! decompilerClass ^self compilerClass decompilerClass! ! !CompiledMethod methodsFor: 'decompiling' stamp: 'eem 7/6/2009 15:57'! methodNode "Return the parse tree that represents self" | aClass source | aClass := self methodClass. source := self getSourceFor: (self selector ifNil: [self defaultSelector]) in: aClass. ^(aClass parserClass new encoderClass: (self isBlueBookCompiled ifTrue: [EncoderForV3] ifFalse: [EncoderForV3PlusClosures]); parse: source class: aClass) sourceText: source; yourself! ! !CompiledMethod methodsFor: 'decompiling' stamp: 'alain.plantec 5/18/2009 15:52'! methodNodeFormatted "Answer a method node made from pretty-printed (and colorized, if decorate is true) source text." | class source node | source := self getSourceFromFile. class := self methodClass ifNil: [self sourceClass]. source ifNil: [^self decompile]. source := class prettyPrinterClass format: source in: class notifying: nil. node := class parserClass new parse: source class: class. node sourceText: source. ^node! ! !CompiledMethod methodsFor: 'decompiling' stamp: 'eem 4/30/2009 18:14'! parserClass ^self methodClass ifNil: [Compiler parserClass] ifNotNil: [:class | class parserClass].! ! !CompiledMethod methodsFor: 'evaluating' stamp: 'ajh 1/28/2003 12:33'! valueWithReceiver: aReceiver arguments: anArray ^ aReceiver withArgs: anArray executeMethod: self! ! !CompiledMethod methodsFor: 'file in/out' stamp: 'yo 10/28/2004 22:38'! objectForDataStream: refStrm self primitive = 117 ifTrue: [self literals first at: 4 put: 0]. ! ! !CompiledMethod methodsFor: 'file in/out' stamp: 'tk 10/6/2000 14:22'! readDataFrom: aDataStream size: varsOnDisk "Fill in my fields. My header and number of literals are already installed. Must read both objects for the literals and bytes for the bytecodes." self error: 'Must use readMethod'.! ! !CompiledMethod methodsFor: 'file in/out' stamp: 'tk 3/26/98 09:10'! storeDataOn: aDataStream "Store myself on a DataStream. I am a mixture of objects and raw data bytes. Only use this for blocks. Normal methodDictionaries should not be put out using ReferenceStreams. Their fileOut should be attached to the beginning of the file." | byteLength lits | "No inst vars of the normal type" byteLength := self basicSize. aDataStream beginInstance: self class size: byteLength. lits := self numLiterals + 1. "counting header" 1 to: lits do: [:ii | aDataStream nextPut: (self objectAt: ii)]. lits*4+1 to: byteLength do: [:ii | aDataStream byteStream nextPut: (self basicAt: ii)]. "write bytes straight through to the file"! ! !CompiledMethod methodsFor: 'file in/out' stamp: 'tk 8/19/1998 16:20'! veryDeepCopyWith: deepCopier "Return self. I am always shared. Do not record me. Only use this for blocks. Normally methodDictionaries should not be copied this way."! ! !CompiledMethod methodsFor: 'file in/out' stamp: 'RAA 8/21/2001 23:10'! zapSourcePointer "clobber the source pointer since it will be wrong" 0 to: 3 do: [ :i | self at: self size - i put: 0]. ! ! !CompiledMethod methodsFor: 'initialize-release'! copyWithTrailerBytes: bytes "Testing: (CompiledMethod compiledMethodAt: #copyWithTrailerBytes:) tempNamesPut: 'copy end ' " | copy end start | start := self initialPC. end := self endPC. copy := CompiledMethod newMethod: end - start + 1 + bytes size header: self header. 1 to: self numLiterals do: [:i | copy literalAt: i put: (self literalAt: i)]. start to: end do: [:i | copy at: i put: (self at: i)]. 1 to: bytes size do: [:i | copy at: end + i put: (bytes at: i)]. ^ copy! ! !CompiledMethod methodsFor: 'initialize-release' stamp: 'di 10/22/1999 13:14'! needsFrameSize: newFrameSize "Set the largeFrameBit to accomodate the newFrameSize" | largeFrameBit header | largeFrameBit := 16r20000. (self numTemps + newFrameSize) > LargeFrame ifTrue: [^ self error: 'Cannot compile -- stack including temps is too deep']. header := self objectAt: 1. (header bitAnd: largeFrameBit) ~= 0 ifTrue: [header := header - largeFrameBit]. self objectAt: 1 put: header + ((self numTemps + newFrameSize) > SmallFrame ifTrue: [largeFrameBit] ifFalse: [0])! ! !CompiledMethod methodsFor: 'literals' stamp: 'eem 5/6/2008 11:28'! allLiterals ^self literals! ! !CompiledMethod methodsFor: 'literals' stamp: 'eem 11/29/2008 11:37'! hasLiteral: literal "Answer whether the receiver references the argument, literal." 2 to: self numLiterals - 1 "exclude superclass + selector/properties" do:[:index | literal == (self objectAt: index) ifTrue: [^true]]. ^false! ! !CompiledMethod methodsFor: 'literals' stamp: 'eem 11/29/2008 17:01'! hasLiteralSuchThat: litBlock "Answer true if litBlock returns true for any literal in this method, even if embedded in array structure." (self penultimateLiteral isMethodProperties and: [self penultimateLiteral hasLiteralSuchThat: litBlock]) ifTrue: [^true]. 2 to: self numLiterals + 1 do: [:index | | lit | lit := self objectAt: index. ((litBlock value: lit) or: [lit isArray and: [lit hasLiteralSuchThat: litBlock]]) ifTrue: [^true]]. ^false! ! !CompiledMethod methodsFor: 'literals' stamp: 'eem 8/7/2009 11:43'! hasLiteralThorough: literal "Answer true if any literal in this method is literal, even if embedded in array structure." (self penultimateLiteral isMethodProperties and: [self penultimateLiteral hasLiteralThorough: literal]) ifTrue:[^true]. 2 to: self numLiterals - 1 "exclude superclass + selector/properties" do:[:index | | lit | ((lit := self objectAt: index) == literal or: [(lit isVariableBinding and: [lit key == literal]) or: [lit isArray and: [lit hasLiteral: literal]]]) ifTrue: [^ true]]. ^ false ! ! !CompiledMethod methodsFor: 'literals'! header "Answer the word containing the information about the form of the receiver and the form of the context needed to run the receiver." ^self objectAt: 1! ! !CompiledMethod methodsFor: 'literals' stamp: 'eem 7/29/2008 17:23'! headerDescription "Answer a description containing the information about the form of the receiver and the form of the context needed to run the receiver." | s | s := '' writeStream. self header printOn: s. s cr; nextPutAll: '"primitive: '. self primitive printOn: s. s cr; nextPutAll: ' numArgs: '. self numArgs printOn: s. s cr; nextPutAll: ' numTemps: '. self numTemps printOn: s. s cr; nextPutAll: ' numLiterals: '. self numLiterals printOn: s. s cr; nextPutAll: ' frameSize: '. self frameSize printOn: s. s cr; nextPutAll: ' isClosureCompiled: '. self isBlueBookCompiled not printOn: s. s nextPut: $"; cr. ^ s contents! ! !CompiledMethod methodsFor: 'literals' stamp: 'eem 11/29/2008 11:38'! indexOfLiteral: literal "Answer the literal index of the argument, literal, or zero if none." 2 to: self numLiterals - 1 "exclude superclass + selector/properties" do: [:index | literal == (self objectAt: index) ifTrue: [^index - 1]]. ^0! ! !CompiledMethod methodsFor: 'literals'! literalAt: index "Answer the literal indexed by the argument." ^self objectAt: index + 1! ! !CompiledMethod methodsFor: 'literals'! literalAt: index put: value "Replace the literal indexed by the first argument with the second argument. Answer the second argument." ^self objectAt: index + 1 put: value! ! !CompiledMethod methodsFor: 'literals' stamp: 'eem 4/30/2009 18:03'! literalStrings | litStrs | litStrs := OrderedCollection new: self numLiterals. self literalsDo: [:lit | (lit isVariableBinding) ifTrue: [litStrs addLast: lit key] ifFalse: [(lit isSymbol) ifTrue: [litStrs addAll: lit keywords] ifFalse: [litStrs addLast: lit printString]]]. ^ litStrs! ! !CompiledMethod methodsFor: 'literals' stamp: 'marcus.denker 9/29/2008 08:44'! literals "Answer an Array of the literals referenced by the receiver." | literals numberLiterals | literals := Array new: (numberLiterals := self numLiterals). 1 to: numberLiterals do: [:index | literals at: index put: (self objectAt: index + 1)]. ^literals! ! !CompiledMethod methodsFor: 'literals' stamp: 'eem 10/28/2008 10:47'! literalsDo: aBlock "Evaluate aBlock for each of the literals referenced by the receiver." 1 to: self numLiterals do: [:index | aBlock value: (self objectAt: index + 1)]! ! !CompiledMethod methodsFor: 'literals'! objectAt: index "Primitive. Answer the method header (if index=1) or a literal (if index >1) from the receiver. Essential. See Object documentation whatIsAPrimitive." self primitiveFailed! ! !CompiledMethod methodsFor: 'literals'! objectAt: index put: value "Primitive. Store the value argument into a literal in the receiver. An index of 2 corresponds to the first literal. Fails if the index is less than 2 or greater than the number of literals. Answer the value as the result. Normally only the compiler sends this message, because only the compiler stores values in CompiledMethods. Essential. See Object documentation whatIsAPrimitive." self primitiveFailed! ! !CompiledMethod methodsFor: 'literals' stamp: 'JohanBrichau 10/8/2009 10:07'! refersToLiteral: aLiteral "Answer true if any literal in this method is literal, even if embedded in array structure or within its pragmas." "only iterate to numLiterals - 1, as the last has the classBinding and the last-but-one needs special treatment" 2 to: self numLiterals - 1 do: [ :index | | literal | literal := self objectAt: index. literal == aLiteral ifTrue: [ ^ true ]. (literal refersToLiteral: aLiteral) ifTrue: [ ^ true ] ]. "last-but-one has the additional method state -or- the method's own selector!!" ^ (self objectAt: self numLiterals) refersToLiteral: aLiteral. ! ! !CompiledMethod methodsFor: 'literals' stamp: 'dvf 11/12/2002 00:44'! sendsSelector: aSymbol ^ self messages includes: aSymbol! ! !CompiledMethod methodsFor: 'printing' stamp: 'PeterHugossonMiller 9/3/2009 00:59'! abstractSymbolic "Answer a String that contains a list of all the byte codes in a method with a short description of each, using relative addresses and not including code bytes." | aStream | aStream := (String new: 1000) writeStream. self longPrintRelativeOn: aStream indent: 0. ^aStream contents! ! !CompiledMethod methodsFor: 'printing' stamp: 'stephane.ducasse 8/9/2009 12:05'! asString ^self getSource! ! !CompiledMethod methodsFor: 'printing' stamp: 'sw 7/29/2002 02:24'! dateMethodLastSubmitted "Answer a Date object indicating when a method was last submitted. If there is no date stamp, return nil" "(CompiledMethod compiledMethodAt: #dateMethodLastSubmitted) dateMethodLastSubmitted" | aStamp tokens | aStamp := self timeStamp. tokens := aStamp findBetweenSubStrs: ' '. "space is expected delimiter, but cr is sometimes seen, though of mysterious provenance" ^ tokens size > 1 ifTrue: [[tokens second asDate] ifError: [nil]] ifFalse: [nil]! ! !CompiledMethod methodsFor: 'printing' stamp: 'md 2/16/2006 13:26'! decompileString ^self decompile decompileString! ! !CompiledMethod methodsFor: 'printing' stamp: 'ajh 2/9/2003 14:17'! longPrintOn: aStream "List of all the byte codes in a method with a short description of each" self longPrintOn: aStream indent: 0! ! !CompiledMethod methodsFor: 'printing' stamp: 'ar 6/28/2003 00:08'! longPrintOn: aStream indent: tabs "List of all the byte codes in a method with a short description of each" self isQuick ifTrue: [self isReturnSpecial ifTrue: [^ aStream tab: tabs; nextPutAll: 'Quick return ' , (#('self' 'true' 'false' 'nil' '-1' '0' '1' '2') at: self primitive - 255)]. ^ aStream nextPutAll: 'Quick return field ' , self returnField printString , ' (0-based)']. self primitive = 0 ifFalse: [ aStream tab: tabs. self printPrimitiveOn: aStream. ]. (InstructionPrinter on: self) indent: tabs; printInstructionsOn: aStream. ! ! !CompiledMethod methodsFor: 'printing' stamp: 'eem 5/15/2008 10:57'! longPrintRelativeOn: aStream indent: tabs "List of all the byte codes in a method with a short description of each" self isQuick ifTrue: [^self longPrintOn: aStream indent: tabs]. self primitive = 0 ifFalse: [aStream tab: tabs. self printPrimitiveOn: aStream]. (RelativeInstructionPrinter on: self) indent: tabs; printCode: false; printInstructionsOn: aStream. ! ! !CompiledMethod methodsFor: 'printing' stamp: 'eem 1/19/2009 10:28'! primitiveErrorVariableName "Answer the primitive error code temp name, or nil if none." self primitive > 0 ifTrue: [self pragmas do: [:pragma| | kwds ecIndex | ((kwds := pragma keyword keywords) first = 'primitive:' and: [(ecIndex := kwds indexOf: 'error:') > 0]) ifTrue: [^pragma argumentAt: ecIndex]]]. ^nil! ! !CompiledMethod methodsFor: 'printing' stamp: 'ar 1/9/2008 11:21'! printOn: aStream "Overrides method inherited from the byte arrayed collection." self printNameOn: aStream. aStream nextPut: $(; print: self identityHash; nextPutAll: ': '; print: self methodClass; nextPutAll: '>>'; nextPutAll: self selector; nextPut: $). "aStream space; nextPutAll: self identityHashPrintString" ! ! !CompiledMethod methodsFor: 'printing' stamp: 'MPW 1/1/1901 22:09'! printOnStream: aStream "Overrides method inherited from the byte arrayed collection." aStream print: 'a CompiledMethod'! ! !CompiledMethod methodsFor: 'printing' stamp: 'eem 12/5/2008 09:48'! printPrimitiveOn: aStream "Print the primitive on aStream" | primIndex primDecl | (primIndex := self primitive) = 0 ifTrue: [^self]. primIndex = 120 ifTrue: "External call spec" [^aStream print: (self literalAt: 1); cr]. aStream nextPutAll: '; cr! ! !CompiledMethod methodsFor: 'printing'! storeLiteralsOn: aStream forClass: aBehavior "Store the literals referenced by the receiver on aStream, each terminated by a space." | literal | 2 to: self numLiterals + 1 do: [:index | aBehavior storeLiteral: (self objectAt: index) on: aStream. aStream space]! ! !CompiledMethod methodsFor: 'printing'! storeOn: aStream | noneYet | aStream nextPutAll: '(('. aStream nextPutAll: self class name. aStream nextPutAll: ' newMethod: '. aStream store: self size - self initialPC + 1. aStream nextPutAll: ' header: '. aStream store: self header. aStream nextPut: $). noneYet := self storeElementsFrom: self initialPC to: self endPC on: aStream. 1 to: self numLiterals do: [:index | noneYet ifTrue: [noneYet := false] ifFalse: [aStream nextPut: $;]. aStream nextPutAll: ' literalAt: '. aStream store: index. aStream nextPutAll: ' put: '. aStream store: (self literalAt: index)]. noneYet ifFalse: [aStream nextPutAll: '; yourself']. aStream nextPut: $)! ! !CompiledMethod methodsFor: 'printing' stamp: 'PeterHugossonMiller 9/3/2009 01:00'! symbolic "Answer a String that contains a list of all the byte codes in a method with a short description of each." | aStream | aStream := (String new: 1000) writeStream. self longPrintOn: aStream. ^aStream contents! ! !CompiledMethod methodsFor: 'printing' stamp: 'eem 5/29/2008 13:59'! symbolicLinesDo: aBlock "Evaluate aBlock with each of the lines in the symbolic output." | aStream pc | aStream := ReadWriteStream on: (String new: 64). self isQuick ifTrue: [self longPrintOn: aStream. aBlock value: 0 value: aStream contents. ^self]. self primitive ~= 0 ifTrue: [self printPrimitiveOn: aStream. aBlock value: 1 value: aStream contents. aStream resetContents]. pc := self initialPC. (InstructionPrinter on: self) indent: 0; printPC: false; "explorer provides pc anyway" printInstructionsOn: aStream do: [:printer :scanner :stream| | line index | line := stream contents allButLast. (line includes: Character cr) ifTrue: [line := (line copyUpTo: Character cr), '...'' (continues)']. (index := line indexOf: $>) > 0 ifTrue: [[(line at: index + 1) isSeparator] whileTrue: [index := index + 1]. line := ((line copyFrom: 1 to: index) copyReplaceAll: (String with: Character tab) with: (String new: 8 withAll: Character space)), (line copyFrom: index + 1 to: line size)]. aBlock value: pc value: line. pc := scanner pc. stream resetContents]! ! !CompiledMethod methodsFor: 'printing' stamp: 'AlexandreBergel 7/30/2008 13:32'! timeStamp "Answer the authoring time-stamp for the given method, retrieved from the sources or changes file. Answer the empty string if no time stamp is available." "(CompiledMethod compiledMethodAt: #timeStamp) timeStamp" | file preamble stamp tokens tokenCount | self fileIndex == 0 ifTrue: [^ String new]. "no source pointer for this method" file := SourceFiles at: self fileIndex. file ifNil: [^ String new]. "sources file not available" "file does not exist happens in secure mode" file := [file readOnlyCopy] on: FileDoesNotExistException do:[:ex| ^ String new]. preamble := self getPreambleFrom: file at: (0 max: self filePosition - 3). stamp := String new. tokens := (preamble findString: 'methodsFor:' startingAt: 1) > 0 ifTrue: [Scanner new scanTokens: preamble] ifFalse: [Array new "ie cant be back ref"]. (((tokenCount := tokens size) between: 7 and: 8) and: [(tokens at: tokenCount - 5) = #methodsFor:]) ifTrue: [(tokens at: tokenCount - 3) = #stamp: ifTrue: ["New format gives change stamp and unified prior pointer" stamp := tokens at: tokenCount - 2]]. ((tokenCount between: 5 and: 6) and: [(tokens at: tokenCount - 3) = #methodsFor:]) ifTrue: [(tokens at: tokenCount - 1) = #stamp: ifTrue: ["New format gives change stamp and unified prior pointer" stamp := tokens at: tokenCount]]. file close. ^ stamp ! ! !CompiledMethod methodsFor: 'printing' stamp: 'eem 6/11/2008 17:08'! who "Answer an Array of the class in which the receiver is defined and the selector to which it corresponds." self hasNewPropertyFormat ifTrue:[^{self methodClass. self selector}]. self systemNavigation allBehaviorsDo: [:class | (class methodDict keyAtIdentityValue: self ifAbsent: [nil]) ifNotNil: [:sel| ^Array with: class with: sel]]. ^Array with: #unknown with: #unknown! ! !CompiledMethod methodsFor: 'scanning' stamp: 'md 4/27/2006 15:12'! hasInstVarRef "Answer whether the method references an instance variable." | scanner end printer | scanner := InstructionStream on: self. printer := InstVarRefLocator new. end := self endPC. [scanner pc <= end] whileTrue: [ (printer interpretNextInstructionUsing: scanner) ifTrue: [^true]. ]. ^false! ! !CompiledMethod methodsFor: 'scanning' stamp: 'marcus.denker 9/29/2008 08:50'! messages "Answer a Set of all the message selectors sent by this method." | scanner aSet | aSet := Set new. scanner := InstructionStream on: self. scanner scanFor: [:x | scanner addSelectorTo: aSet. false "keep scanning"]. ^aSet! ! !CompiledMethod methodsFor: 'scanning' stamp: 'dvf 11/12/2002 00:44'! messagesDo: aBlock ^ self messages do:aBlock.! ! !CompiledMethod methodsFor: 'scanning' stamp: 'eem 12/13/2008 15:48'! messagesSequence "Answer a Set of all the message selectors sent by this method." ^Array streamContents: [:str| | scanner | scanner := InstructionStream on: self. scanner scanFor: [:x | | selectorOrSelf | (selectorOrSelf := scanner selectorToSendOrSelf) == scanner ifFalse: [str nextPut: selectorOrSelf]. false "keep scanning"]]! ! !CompiledMethod methodsFor: 'scanning' stamp: 'eem 6/19/2008 09:21'! readsField: varIndex "Answer whether the receiver loads the instance variable indexed by the argument." "eem 5/24/2008 Rewritten to no longer assume the compiler uses the most compact encoding available (for EncoderForLongFormV3 support)." | varIndexCode scanner | varIndexCode := varIndex - 1. self isReturnField ifTrue: [^self returnField = varIndexCode]. ^(scanner := InstructionStream on: self) scanFor: [:b| b < 16 ifTrue: [b = varIndexCode] ifFalse: [b = 128 ifTrue: [scanner followingByte = varIndexCode and: [varIndexCode <= 63]] ifFalse: [b = 132 and: [(scanner followingByte between: 64 and: 95) and: [scanner thirdByte = varIndexCode]]]]]! ! !CompiledMethod methodsFor: 'scanning' stamp: 'eem 5/24/2008 16:19'! readsRef: literalAssociation "Answer whether the receiver loads the argument." "eem 5/24/2008 Rewritten to no longer assume the compler uses the most compact encoding available (for EncoderForLongFormV3 support)." | litIndex scanner | (litIndex := self indexOfLiteral: literalAssociation) = 0 ifTrue: [^false]. litIndex := litIndex - 1. ^(scanner := InstructionStream on: self) scanFor: [:b| b >= 64 and: [b <= 95 ifTrue: [b - 64 = litIndex] ifFalse: [b = 128 ifTrue: [scanner followingByte - 192 = litIndex] ifFalse: [b = 132 and: [(scanner followingByte between: 128 and: 159) and: [scanner thirdByte = litIndex]]]]]]! ! !CompiledMethod methodsFor: 'scanning'! scanFor: byte "Answer whether the receiver contains the argument as a bytecode." ^ (InstructionStream on: self) scanFor: [:instr | instr = byte] " Smalltalk browseAllSelect: [:m | m scanFor: 134] "! ! !CompiledMethod methodsFor: 'scanning'! scanLongLoad: extension "Answer whether the receiver contains a long load whose extension is the argument." | scanner | scanner := InstructionStream on: self. ^scanner scanFor: [:instr | instr = 128 and: [scanner followingByte = extension]]! ! !CompiledMethod methodsFor: 'scanning'! scanLongStore: extension "Answer whether the receiver contains a long store whose extension is the argument." | scanner | scanner := InstructionStream on: self. ^scanner scanFor: [:instr | (instr = 129 or: [instr = 130]) and: [scanner followingByte = extension]]! ! !CompiledMethod methodsFor: 'scanning'! scanVeryLongLoad: extension offset: offset "Answer whether the receiver contains a long load whose extension is the argument." | scanner | scanner := InstructionStream on: self. ^ scanner scanFor: [:instr | (instr = 132 and: [scanner followingByte = extension]) and: [scanner thirdByte = offset]]! ! !CompiledMethod methodsFor: 'scanning' stamp: 'eem 6/11/2008 17:07'! scanVeryLongStore: extension offset: offset "Answer whether the receiver contains a long load with the given offset. Note that the constant +32 is the known difference between a store and a storePop for instVars, and it will always fail on literal variables, but these only use store (followed by pop) anyway." | scanner | scanner := InstructionStream on: self. ^scanner scanFor: [:instr | | ext | (instr = 132 and: [(ext := scanner followingByte) = extension or: ["might be a store/pop into rcvr" ext = (extension+32)]]) and: [scanner thirdByte = offset]]! ! !CompiledMethod methodsFor: 'scanning'! sendsToSuper "Answer whether the receiver sends any message to super." | scanner | scanner := InstructionStream on: self. ^ scanner scanFor: [:instr | instr = 16r85 or: [instr = 16r84 and: [scanner followingByte between: 16r20 and: 16r3F]]]! ! !CompiledMethod methodsFor: 'scanning' stamp: 'eem 5/24/2008 16:21'! writesField: varIndex "Answer whether the receiver stores into the instance variable indexed by the argument." "eem 5/24/2008 Rewritten to no longer assume the compler uses the most compact encoding available (for EncoderForLongFormV3 support)." | varIndexCode scanner | self isQuick ifTrue: [^false]. varIndexCode := varIndex - 1. ^(scanner := InstructionStream on: self) scanFor: [:b| b >= 96 and: [b <= 103 ifTrue: [b - 96 = varIndexCode] ifFalse: [(b = 129 or: [b = 130]) ifTrue: [scanner followingByte = varIndexCode and: [varIndexCode <= 63]] ifFalse: [b = 132 and: [(scanner followingByte between: 160 and: 223) and: [scanner thirdByte = varIndexCode]]]]]]! ! !CompiledMethod methodsFor: 'scanning' stamp: 'eem 5/24/2008 16:14'! writesRef: literalAssociation "Answer whether the receiver stores into the argument." "eem 5/24/2008 Rewritten to no longer assume the compler uses the most compact encoding available (for EncoderForLongFormV3 support)." | litIndex scanner | (litIndex := self indexOfLiteral: literalAssociation) = 0 ifTrue: [^false]. litIndex := litIndex - 1. ^(scanner := InstructionStream on: self) scanFor: [:b| (b = 129 or: [b = 130]) ifTrue: [scanner followingByte - 192 = litIndex] ifFalse: [b = 132 and: [scanner followingByte >= 224 and: [scanner thirdByte = litIndex]]]]! ! !CompiledMethod methodsFor: 'source code management' stamp: 'tk 12/7/2000 12:28'! checkOKToAdd: size at: filePosition "Issue several warnings as the end of the changes file approaches its limit, and finally halt with an error when the end is reached." | fileSizeLimit margin | fileSizeLimit := 16r2000000. 3 to: 1 by: -1 do: [:i | margin := i*100000. (filePosition + size + margin) > fileSizeLimit ifTrue: [(filePosition + margin) > fileSizeLimit ifFalse: [self inform: 'WARNING: your changes file is within ' , margin printString , ' characters of its size limit. You should take action soon to reduce its size. You may proceed.']] ifFalse: [^ self]]. (filePosition + size > fileSizeLimit) ifFalse: [^ self]. self error: 'You have reached the size limit of the changes file. You must take action now to reduce it. Close this error. Do not attempt to proceed.'! ! !CompiledMethod methodsFor: 'source code management' stamp: 'di 1/7/2004 15:32'! copyWithTempNames: tempNames | tempStr compressed | tempStr := String streamContents: [:strm | tempNames do: [:n | strm nextPutAll: n; space]]. compressed := self qCompress: tempStr firstTry: true. compressed ifNil: ["failure case (tempStr too big) will just decompile with tNN names" ^ self copyWithTrailerBytes: #(0 0 0 0)]. ^ self copyWithTrailerBytes: compressed! ! !CompiledMethod methodsFor: 'source code management' stamp: 'eem 6/8/2009 14:32'! copyWithTempsFromMethodNode: aMethodNode ^self copyWithTrailerBytes: (self qCompress: aMethodNode schematicTempNamesString)! ! !CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 20:44'! fileIndex ^SourceFiles fileIndexFromSourcePointer: self sourcePointer! ! !CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 20:45'! filePosition ^SourceFiles filePositionFromSourcePointer: self sourcePointer! ! !CompiledMethod methodsFor: 'source code management' stamp: 'yo 3/16/2004 12:23'! getPreambleFrom: aFileStream at: position | writeStream | writeStream := String new writeStream. position to: 0 by: -1 do: [:p | | c | aFileStream position: p. c := aFileStream basicNext. c == $!! ifTrue: [^ writeStream contents reverse] ifFalse: [writeStream nextPut: c]]! ! !CompiledMethod methodsFor: 'source code management' stamp: 'AdrianLienhard 10/11/2009 20:28'! getSource ^ self getSourceFor: self selector in: self methodClass! ! !CompiledMethod methodsFor: 'source code management' stamp: 'AdrianLienhard 10/11/2009 19:52'! getSourceFor: selector in: class "Retrieve or reconstruct the source code for this method." | flagByte source | flagByte := self last. (flagByte = 0 or: [flagByte = 251 "some source-less methods have flag = 251, rest = 0" and: [((1 to: 3) allSatisfy: [:i | (self at: self size - i) = 0])]]) ifTrue: ["No source pointer -- decompile without temp names" ^ (class decompilerClass new decompile: selector in: class method: self) decompileString]. flagByte < 252 ifTrue: ["Magic sources -- decompile with temp names" ^ ((class decompilerClass new withTempNames: self tempNamesString) decompile: selector in: class method: self) decompileString]. "Situation normal; read the sourceCode from the file" source := [self getSourceFromFile] on: Error "An error can happen here if, for example, the changes file has been truncated by an aborted download. The present solution is to ignore the error and fall back on the decompiler. A more thorough solution should probably trigger a systematic invalidation of all source pointers past the end of the changes file. Consider that, as time goes on, the changes file will eventually grow large enough to cover the lost code, and then instead of falling into this error case, random source code will get returned." do: [ :ex | ex return: nil]. source ifNotNil: [ ^ source ]. "Something really wrong -- decompile blind (no temps)" ^ (class decompilerClass new decompile: selector in: class method: self) decompileString! ! !CompiledMethod methodsFor: 'source code management' stamp: 'tk 12/12/97 13:03'! getSourceFromFile "Read the source code from file, determining source file index and file position from the last 3 bytes of this method." | position | (position := self filePosition) = 0 ifTrue: [^ nil]. ^ (RemoteString newFileNumber: self fileIndex position: position) text! ! !CompiledMethod methodsFor: 'source code management' stamp: 'eem 5/29/2009 12:16'! holdsTempNames "Are tempNames stored in trailer bytes" | flagByte | flagByte := self last. (flagByte = 0 or: [flagByte = 251 "some source-less methods have flag = 251, rest = 0" and: [(1 to: 3) allSatisfy: [:i | (self at: self size - i) = 0]]]) ifTrue: [^ false]. "No source pointer & no temp names" flagByte < 252 ifTrue: [^ true]. "temp names compressed" ^ false "Source pointer" ! ! !CompiledMethod methodsFor: 'source code management' stamp: 'damiencassou 5/30/2008 10:56'! linesOfCode "An approximate measure of lines of code. Includes comments, but excludes blank lines." | strm line lines | lines := 0. strm := self getSource readStream. [ strm atEnd ] whileFalse: [ line := strm upTo: Character cr. line isEmpty ifFalse: [ lines := lines + 1 ] ]. ^ lines! ! !CompiledMethod methodsFor: 'source code management'! putSource: sourceStr fromParseNode: methodNode class: class category: catName inFile: fileIndex priorMethod: priorMethod ^ self putSource: sourceStr fromParseNode: methodNode inFile: fileIndex withPreamble: [:file | class printCategoryChunk: catName on: file priorMethod: priorMethod. file cr]! ! !CompiledMethod methodsFor: 'source code management' stamp: '6/5/97 di'! putSource: sourceStr fromParseNode: methodNode class: class category: catName withStamp: changeStamp inFile: fileIndex priorMethod: priorMethod ^ self putSource: sourceStr fromParseNode: methodNode inFile: fileIndex withPreamble: [:file | class printCategoryChunk: catName on: file withStamp: changeStamp priorMethod: priorMethod. file cr]! ! !CompiledMethod methodsFor: 'source code management' stamp: 'eem 7/1/2009 13:52'! putSource: sourceStr fromParseNode: methodNode inFile: fileIndex withPreamble: preambleBlock "Store the source code for the receiver on an external file. If no sources are available, i.e., SourceFile is nil, then store temp names for decompilation at the end of the method. If the fileIndex is 1, print on *.sources; if it is 2, print on *.changes, in each case, storing a 4-byte source code pointer at the method end." | file remoteString | (SourceFiles == nil or: [(file := SourceFiles at: fileIndex) == nil]) ifTrue: [^self become: (self copyWithTempsFromMethodNode: methodNode)]. SmalltalkImage current assureStartupStampLogged. file setToEnd. preambleBlock value: file. "Write the preamble" remoteString := RemoteString newString: sourceStr onFileNumber: fileIndex toFile: file. file nextChunkPut: ' '. InMidstOfFileinNotification signal ifFalse: [file flush]. self checkOKToAdd: sourceStr size at: remoteString position. self setSourcePosition: remoteString position inFile: fileIndex! ! !CompiledMethod methodsFor: 'source code management' stamp: 'eem 7/21/2009 13:26'! qCompress: string "A very simple text compression routine designed for method temp names. Most common 11 chars get values 1-11 packed in one 4-bit nibble; the next most common get values 12-15 (2 bits) * 16 plus next nibble; unusual ones get three nibbles, the first being the escape nibble 0. CompiledMethod>>endPC determines the maximum length of encoded output, which means 1 to (251 - 128) * 128 + 127, or 15871 bytes" string isEmpty ifTrue: [^self qCompress: ' ']. ^ ByteArray streamContents: [:strm | | ix oddNibble sz | oddNibble := nil. string do: [:char | ix := 'ear tonsilcmbdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ012345[]()' indexOf: char ifAbsent: 0. (ix = 0 ifTrue: [char asInteger > 255 ifTrue: [^nil]. "Could use UTF8 here; too lazy right now" { 0. char asInteger // 16. char asInteger \\ 16 }] ifFalse: [ix <= 11 ifTrue: [{ ix }] ifFalse: [{ ix//16+12. ix\\16 }]]) do: [:nibble | oddNibble ifNotNil: [strm nextPut: oddNibble*16 + nibble. oddNibble := nil] ifNil: [oddNibble := nibble]]]. oddNibble ifNotNil: "4 = 'ear tonsil' indexOf: Character space" [strm nextPut: oddNibble * 16 + 4]. (sz := strm position) > ((251 - 128) * 128 + 127) ifTrue: [^nil]. sz <= 127 ifTrue: [strm nextPut: sz] ifFalse: [strm nextPut: sz \\ 128; nextPut: sz // 128 + 128]]! ! !CompiledMethod methodsFor: 'source code management' stamp: 'eem 6/24/2008 14:27'! qCompress: string firstTry: firstTry "A very simple text compression routine designed for method temp names. Most common 12 chars get values 0-11 packed in one 4-bit nibble; others get values 12-15 (2 bits) * 16 plus next nibble. Last char of str must be a space so it may be dropped without consequence if output ends on odd nibble. Normal call is with firstTry == true." | charTable odd ix oddNibble names shorterStr maybe str temps | str := string isOctetString ifTrue: [string] ifFalse: [temps := string findTokens: ' '. String streamContents: [:stream | 1 to: temps size do: [:index | stream nextPut: $t. stream nextPutAll: index asString. stream space]]]. charTable := "Character encoding table must match qDecompress:" ' eatrnoislcm_bdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ0123456789'. ^ ByteArray streamContents: [:strm | odd := true. "Flag for odd or even nibble out" oddNibble := nil. str do: [:char | ix := (charTable indexOf: char) - 1. (ix <= 12 ifTrue: [Array with: ix] ifFalse: [Array with: ix//16+12 with: ix\\16]) do: [:nibble | (odd := odd not) ifTrue: [strm nextPut: oddNibble*16 + nibble] ifFalse: [oddNibble := nibble]]]. strm position > 251 ifTrue: ["Only values 1...251 are available for the flag byte that signals compressed temps. See the logic in endPC." "Before giving up completely, we attempt to encode most of the temps, but with the last few shortened to tNN-style names." firstTry ifFalse: [^ nil "already tried --give up now"]. names := str findTokens: ' '. names size < 8 ifTrue: [^ nil "weird case -- give up now"]. 4 to: names size//2 by: 4 do: [:i | shorterStr := String streamContents: [:s | 1 to: names size - i do: [:j | s nextPutAll: (names at: j); space]. 1 to: i do: [:j | s nextPutAll: 't' , j printString; space]]. (maybe := self qCompress: shorterStr firstTry: false) ifNotNil: [^ maybe]]. ^ nil]. strm nextPut: strm position] " | m s | m := CompiledMethod new. s := 'charTable odd ix oddNibble '. ^ Array with: s size with: (m qCompress: s) size with: (m qDecompress: (m qCompress: s)) " ! ! !CompiledMethod methodsFor: 'source code management' stamp: 'eem 6/24/2008 14:30'! qDecompress: byteArray "Decompress strings compressed by qCompress:. Most common 12 chars get values 0-11 packed in one 4-bit nibble; others get values 12-15 (2 bits) * 16 plus next nibble" | charTable extended ext | charTable := "Character encoding table must match qCompress:" ' eatrnoislcm_bdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ0123456789'. ^ String streamContents: [:strm | extended := false. "Flag for 2-nibble characters" byteArray do: [:byte | (Array with: byte//16 with: byte\\16) do: [:nibble | extended ifTrue: [strm nextPut: (charTable at: ext*16+nibble + 1). extended := false] ifFalse: [nibble < 12 ifTrue: [strm nextPut: (charTable at: nibble + 1)] ifFalse: [ext := nibble-12. extended := true]]]]]! ! !CompiledMethod methodsFor: 'source code management' stamp: 'eem 6/5/2009 18:07'! qDecompressFrom: input " ^" "Decompress strings compressed by qCompress:. Most common 11 chars get values 0-10 packed in one 4-bit nibble; next most common 52 get values 12-15 (2 bits) * 16 plus next nibble; escaped chars get three nibbles" ^ String streamContents: [:strm | | nextNibble nibble peek charTable char | charTable := "Character encoding table must match qCompress:" 'ear tonsilcmbdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ012345[]()'. peek := true. nextNibble := [peek ifTrue: [peek := false. input peek ifNil: [0] ifNotNil: [:b| b // 16]] ifFalse: [peek := true. input next ifNil: [0] ifNotNil: [:b| b \\ 16]]]. [input atEnd] whileFalse: [(nibble := nextNibble value) = 0 ifTrue: [input atEnd ifFalse: [strm nextPut: (Character value: nextNibble value * 16 + nextNibble value)]] ifFalse: [nibble <= 11 ifTrue: [strm nextPut: (charTable at: nibble)] ifFalse: [strm nextPut: (charTable at: nibble-12 * 16 + nextNibble value)]]]]! ! !CompiledMethod methodsFor: 'source code management' stamp: 'md 1/20/2006 16:36'! setMySourcePointer: srcPointer srcPointer = 0 ifTrue: [ self at: self size put: 0. ^self]. (srcPointer between: 16r1000000 and: 16r4FFFFFF) ifFalse: [self error: 'Source pointer out of range']. self at: self size put: (srcPointer bitShift: -24) + 251. 1 to: 3 do: [:i | self at: self size-i put: ((srcPointer bitShift: (i-3)*8) bitAnd: 16rFF)]! ! !CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 21:00'! setSourcePointer: srcPointer srcPointer = 0 ifTrue: [ self at: self size put: 0. ^self]. (srcPointer between: 16r1000000 and: 16r4FFFFFF) ifFalse: [self error: 'Source pointer out of range']. self at: self size put: (srcPointer bitShift: -24) + 251. 1 to: 3 do: [:i | self at: self size-i put: ((srcPointer bitShift: (i-3)*8) bitAnd: 16rFF)]! ! !CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 21:02'! setSourcePosition: position inFile: fileIndex self setSourcePointer: (SourceFiles sourcePointerFromFileIndex: fileIndex andPosition: position)! ! !CompiledMethod methodsFor: 'source code management' stamp: 'nice 5/1/2009 18:31'! sourceClass "Get my receiver class (method class) from the preamble of my source. Return nil if not found." ^ [| theFile | theFile := self sourceFileStream. [(Compiler evaluate: (theFile backChunk "blank"; backChunk "preamble")) theClass] ensure: [theFile close]] on: Error do: [nil]! ! !CompiledMethod methodsFor: 'source code management' stamp: 'ajh 8/13/2002 18:18'! sourceFileStream "Answer the sources file stream with position set at the beginning of my source string" | pos | (pos := self filePosition) = 0 ifTrue: [^ nil]. ^ (RemoteString newFileNumber: self fileIndex position: pos) fileStream! ! !CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 20:44'! sourcePointer "Answer the integer which can be used to find the source file and position for this method. The returned value is either 0 (if no source is stored) or a number between 16r1000000 and 16r4FFFFFF. The actual interpretation of this number is up to the SourceFileArray stored in the global variable SourceFiles." | pos | self last < 252 ifTrue: [^ 0 "no source"]. pos := self last - 251. self size - 1 to: self size - 3 by: -1 do: [:i | pos := pos * 256 + (self at: i)]. ^pos! ! !CompiledMethod methodsFor: 'source code management' stamp: 'md 8/2/2006 20:25'! sourceSelector "Answer my selector extracted from my source. If no source answer nil" | sourceString | sourceString := self getSourceFromFile ifNil: [^ nil]. ^self methodClass parserClass new parseSelector: sourceString! ! !CompiledMethod methodsFor: 'source code management' stamp: 'ajh 7/21/2003 00:29'! tempNames | byteCount bytes | self holdsTempNames ifFalse: [ ^ (1 to: self numTemps) collect: [:i | 't', i printString] ]. byteCount := self at: self size. byteCount = 0 ifTrue: [^ Array new]. bytes := (ByteArray new: byteCount) replaceFrom: 1 to: byteCount with: self startingAt: self size - byteCount. ^ (self qDecompress: bytes) findTokens: ' '! ! !CompiledMethod methodsFor: 'source code management' stamp: 'eem 6/8/2009 10:29'! tempNamesString "Decompress the encoded temp names into a schematicTempNames string." | sz flagByte | flagByte := self at: (sz := self size). (flagByte = 0 or: [flagByte > 251]) ifTrue: [^self error: 'not yet implemented']. (flagByte = 251 and: [(1 to: 3) allSatisfy: [:i | (self at: self size - i) = 0]]) ifTrue: [^self error: 'not yet implemented']. ^self qDecompressFrom: (flagByte <= 127 ifTrue: [ReadStream on: self from: sz - flagByte to: sz - 1] ifFalse: [ReadStream on: self from: sz - (flagByte - 128 * 128 + (self at: sz - 1)) - 1 to: sz - 2])! ! !CompiledMethod methodsFor: 'testing' stamp: 'eem 11/29/2008 11:28'! hasNewPropertyFormat "As of the closure compiler all methods have (or better have) the new format where the penultimate literal is either the method's selector or its properties and the ultimate literal is the class association." ^true! ! !CompiledMethod methodsFor: 'testing' stamp: 'md 1/21/2006 10:54'! hasReportableSlip "Answer whether the receiver contains anything that should be brought to the attention of the author when filing out. Customize the lists here to suit your preferences. If slips do not get reported in spite of your best efforts here, make certain that the Preference 'checkForSlips' is set to true." | assoc | #(#doOnlyOnce: #halt #halt: #hottest #printDirectlyToDisplay #toRemove #personal #urgent #haltOnce #haltOnce: #haltIf: ) do: [:aLit | (self hasLiteral: aLit) ifTrue: [^ true]]. #(#Transcript #AA #BB #CC #DD #EE ) do: [:aSymbol | (assoc := Smalltalk associationAt: aSymbol ifAbsent: []) ifNotNil: [(self hasLiteral: assoc) ifTrue: [^ true]]]. ^ false! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 12/12/2003 15:18'! isAbstract | marker | marker := self markerOrNil. ^ marker notNil and: [self class abstractMarkers includes: marker].! ! !CompiledMethod methodsFor: 'testing' stamp: 'eem 7/29/2008 16:51'! isBlueBookCompiled "Answer whether the receiver was compiled using the closure compiler. This is used to help DebuggerMethodMap choose which mechanisms to use to inspect activations of the receiver. This method answers false negatives in that it only identifies methods that create old BlockClosures or use the new BlockClosure bytecodes. It cannot tell if a method which uses neither the old nor the new block bytecodes is compiled with the blue-book compiler or the new compiler. But since methods that don't create blocks have essentially the same code when compiled with either compiler this makes little difference." ^((InstructionStream on: self) scanFor: [:instr | (instr >= 138 and: [instr <= 143]) ifTrue: [^false]. instr = 200]) or: [(self hasLiteral: #blockCopy:) and: [self messages includes: #blockCopy:]]! ! !CompiledMethod methodsFor: 'testing' stamp: 'eem 6/3/2008 13:30'! isClosureCompiled "Answer whether the receiver was compiled using the closure compiler. This is used to help DebuggerMethodMap choose which mechanisms to use to inspect activations of the receiver. This method answers false negatives in that it only identifies methods that create new BlockClosures or use the new BlockClosure bytecodes. But since methods that don't create blocks have essentially the same code when compiled with either compiler this makes little difference." ^((InstructionStream on: self) scanFor: [:instr | instr >= 138 and: [instr <= 143]]) or: [(self hasLiteral: #closureCopy:copiedValues:) and: [self messages includes: #closureCopy:copiedValues:]]! ! !CompiledMethod methodsFor: 'testing' stamp: 'md 11/21/2003 12:15'! isCompiledMethod ^ true! ! !CompiledMethod methodsFor: 'testing' stamp: 'al 1/23/2004 13:12'! isConflict ^ self markerOrNil == self class conflictMarker! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:32'! isDisabled ^ self isDisabled: self markerOrNil! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:32'! isDisabled: marker ^ marker == self class disabledMarker! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:32'! isExplicitlyRequired ^ self isExplicitlyRequired: self markerOrNil! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:32'! isExplicitlyRequired: marker ^ marker == self class explicitRequirementMarker! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:32'! isImplicitlyRequired ^ self isImplicitlyRequired: self markerOrNil! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:32'! isImplicitlyRequired: marker ^ marker == self class implicitRequirementMarker! ! !CompiledMethod methodsFor: 'testing' stamp: 'eem 12/1/2008 11:14'! isInstalled self methodClass ifNotNil: [:class| self selector ifNotNil: [:selector| ^self == (class methodDict at: selector ifAbsent: [])]]. ^false! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:40'! isProvided ^ self isProvided: self markerOrNil! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:40'! isProvided: marker marker ifNil: [^ true]. ^ (self isRequired: marker) not and: [(self isDisabled: marker) not]! ! !CompiledMethod methodsFor: 'testing' stamp: 'di 12/26/1998 21:31'! isQuick "Answer whether the receiver is a quick return (of self or of an instance variable)." ^ self primitive between: 256 and: 519! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:38'! isRequired ^ self isRequired: self markerOrNil! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:38'! isRequired: marker marker ifNil: [^ false]. (self isImplicitlyRequired: marker) ifTrue: [^ true]. (self isExplicitlyRequired: marker) ifTrue: [^ true]. (self isSubclassResponsibility: marker) ifTrue: [^ true]. ^ false! ! !CompiledMethod methodsFor: 'testing' stamp: 'ar 6/2/1998 16:11'! isReturnField "Answer whether the receiver is a quick return of an instance variable." ^ self primitive between: 264 and: 519! ! !CompiledMethod methodsFor: 'testing'! isReturnSelf "Answer whether the receiver is a quick return of self." ^ self primitive = 256! ! !CompiledMethod methodsFor: 'testing'! isReturnSpecial "Answer whether the receiver is a quick return of self or constant." ^ self primitive between: 256 and: 263! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:38'! isSubclassResponsibility ^ self isSubclassResponsibility: self markerOrNil! ! !CompiledMethod methodsFor: 'testing' stamp: 'NS 3/22/2005 16:38'! isSubclassResponsibility: marker ^ marker == self class subclassResponsibilityMarker! ! !CompiledMethod methodsFor: 'testing' stamp: 'eem 6/4/2008 16:19'! usesClosureBytecodes "Answer whether the receiver was compiled using the closure compiler. This is used to help DebuggerMethodMap choose which mechanisms to use to inspect activations of the receiver. This method answers false negatives in that it only identifies methods that use the new BlockClosure bytecodes. But since methods that don't create blocks have essentially the same code when compiled with either compiler this makes little difference." ^(InstructionStream on: self) scanFor: [:instr | instr >= 138 and: [instr <= 143]]! ! !CompiledMethod methodsFor: 'private' stamp: 'PeterHugossonMiller 9/2/2009 16:04'! getSourceReplacingSelectorWith: newSelector | oldKeywords newKeywords args newSelectorWithArgs source oldSelector s | source := self getSource. oldSelector := self parserClass new parseSelector: source. oldSelector = newSelector ifTrue: [ ^ source ]. oldKeywords := oldSelector keywords. newKeywords := (newSelector ifNil: [self defaultSelector]) keywords. self assert: oldKeywords size = newKeywords size. args := (self methodClass parserClass new parseArgsAndTemps: source string notifying: nil) copyFrom: 1 to: self numArgs. newSelectorWithArgs := String streamContents: [:stream | newKeywords withIndexDo: [:keyword :index | stream nextPutAll: keyword. stream space. args size >= index ifTrue: [ stream nextPutAll: (args at: index); space]]]. s := source string readStream. oldKeywords do: [ :each | s match: each ]. args isEmpty ifFalse: [ s match: args last ]. ^newSelectorWithArgs withBlanksTrimmed asText , s upToEnd! ! !CompiledMethod methodsFor: 'private' stamp: 'al 2/13/2006 17:44'! markerOrNil "If I am a marker method, answer the symbol used to mark me. Otherwise answer nil. What is a marker method? It is method with body like 'self subclassResponsibility' or '^ self subclassResponsibility' used to indicate ('mark') a special property. Marker methods compile to bytecode like: 9 <70> self 10 send: 11 <87> pop 12 <78> returnSelf for the first form, or 9 <70> self 10 send: 11 <7C> returnTop for the second form." | e | ((e := self endPC) = 19 or: [e = 20]) ifFalse: [^ nil]. (self numLiterals = 3) ifFalse:[^ nil]. (self at: 17) = 16r70 ifFalse:[^ nil]. "push self" (self at: 18) = 16rD0 ifFalse:[^ nil]. "send " "If we reach this point, we have a marker method that sends self " ^ self literalAt: 1 ! ! !CompiledMethod methodsFor: 'private' stamp: 'eem 11/29/2008 11:10'! penultimateLiteral "Answer the penultimate literal of the receiver, which holds either the receiver's selector or its properties (which will hold the selector)." | pIndex | ^(pIndex := self numLiterals - 1) > 0 ifTrue: [self literalAt: pIndex] ifFalse: [nil]! ! !CompiledMethod methodsFor: 'private' stamp: 'eem 11/29/2008 11:52'! penultimateLiteral: anObject "Answer the penultimate literal of the receiver, which holds either the receiver's selector or its properties (which will hold the selector)." | pIndex | (pIndex := self numLiterals - 1) > 0 ifTrue: [self literalAt: pIndex put: anObject] ifFalse: [self error: 'insufficient literals']! ! !CompiledMethod methodsFor: 'private' stamp: 'md 8/2/2006 20:25'! replace: oldSelector with: newSelector in: aText | oldKeywords newKeywords args newSelectorWithArgs startOfSource lastSelectorToken | oldKeywords := oldSelector keywords. newKeywords := (newSelector ifNil: [self defaultSelector]) keywords. self assert: oldKeywords size = newKeywords size. args := (self methodClass parserClass new parseArgsAndTemps: aText string notifying: nil) copyFrom: 1 to: self numArgs. newSelectorWithArgs := String streamContents: [:stream | newKeywords withIndexDo: [:keyword :index | stream nextPutAll: keyword. stream space. args size >= index ifTrue: [ stream nextPutAll: (args at: index); space]]]. lastSelectorToken := args isEmpty ifFalse: [args last] ifTrue: [oldKeywords last]. startOfSource := (aText string indexOfSubCollection: lastSelectorToken startingAt: 1) + lastSelectorToken size. ^newSelectorWithArgs withBlanksTrimmed asText , (aText copyFrom: startOfSource to: aText size)! ! !CompiledMethod methodsFor: 'accessing-pragmas & properties' stamp: 'eem 12/1/2008 16:58'! pragmaAt: aKey "Answer the pragma with selector aKey, or nil if none." | propertiesOrSelector | ^(propertiesOrSelector := self penultimateLiteral) isMethodProperties ifTrue: [propertiesOrSelector at: aKey ifAbsent: [nil]] ifFalse: [nil]! ! !CompiledMethod methodsFor: 'accessing-pragmas & properties' stamp: 'eem 11/29/2008 16:36'! pragmas | selectorOrProperties | ^(selectorOrProperties := self penultimateLiteral) isMethodProperties ifTrue: [selectorOrProperties pragmas] ifFalse: [#()]! ! !CompiledMethod methodsFor: 'accessing-pragmas & properties' stamp: 'eem 11/29/2008 17:33'! propertyKeysAndValuesDo: aBlock "Enumerate the receiver with all the keys and values." | propertiesOrSelector | (propertiesOrSelector := self penultimateLiteral) isMethodProperties ifTrue: [propertiesOrSelector propertyKeysAndValuesDo: aBlock]! ! !CompiledMethod methodsFor: 'accessing-pragmas & properties' stamp: 'eem 11/29/2008 11:45'! propertyValueAt: propName | propertiesOrSelector | ^(propertiesOrSelector := self penultimateLiteral) isMethodProperties ifTrue: [propertiesOrSelector propertyValueAt: propName ifAbsent: [nil]] ifFalse: [nil]! ! !CompiledMethod methodsFor: 'accessing-pragmas & properties' stamp: 'eem 11/29/2008 11:50'! propertyValueAt: propName ifAbsent: aBlock | propertiesOrSelector | ^(propertiesOrSelector := self penultimateLiteral) isMethodProperties ifTrue: [propertiesOrSelector propertyValueAt: propName ifAbsent: aBlock] ifFalse: [aBlock value]! ! !CompiledMethod methodsFor: 'accessing-pragmas & properties' stamp: 'eem 11/30/2008 08:55'! propertyValueAt: propName put: propValue "Set or add the property with key propName and value propValue. If the receiver does not yet have a method properties create one and replace the selector with it. Otherwise, either relace propValue in the method properties or replace method properties with one containing the new property." | propertiesOrSelector | (propertiesOrSelector := self penultimateLiteral) isMethodProperties ifFalse: [self penultimateLiteral: ((AdditionalMethodState selector: propertiesOrSelector with: (Association key: propName asSymbol value: propValue)) setMethod: self; yourself). ^propValue]. (propertiesOrSelector includesProperty: propName) ifTrue: [^propertiesOrSelector at: propName put: propValue]. self penultimateLiteral: (propertiesOrSelector copyWith: (Association key: propName asSymbol value: propValue)). ^propValue! ! !CompiledMethod methodsFor: 'accessing-pragmas & properties' stamp: 'eem 12/1/2008 11:02'! removeProperty: propName "Remove the property propName if it exists. Do _not_ raise an error if the property is missing." | value | value := self propertyValueAt: propName ifAbsent: [^nil]. self penultimateLiteral: (self penultimateLiteral copyWithout: (Association key: propName value: value)). ^value! ! !CompiledMethod methodsFor: 'accessing-pragmas & properties' stamp: 'eem 12/1/2008 11:02'! removeProperty: propName ifAbsent: aBlock "Remove the property propName if it exists. Answer the evaluation of aBlock if the property is missing." | value | value := self propertyValueAt: propName ifAbsent: [^aBlock value]. self penultimateLiteral: (self penultimateLiteral copyWithout: (Association key: propName value: value)). ^value! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CompiledMethod class instanceVariableNames: ''! !CompiledMethod class methodsFor: 'class initialization' stamp: 'di 1/11/1999 22:13'! fullFrameSize "CompiledMethod fullFrameSize" ^ LargeFrame! ! !CompiledMethod class methodsFor: 'class initialization' stamp: 'eem 6/5/2008 09:05'! initialize "CompiledMethod initialize" "Initialize class variables specifying the size of the temporary frame needed to run instances of me." SmallFrame := 16. "Context range for temps+stack" LargeFrame := 56! ! !CompiledMethod class methodsFor: 'class initialization' stamp: 'ajh 7/18/2001 02:04'! smallFrameSize ^ SmallFrame! ! !CompiledMethod class methodsFor: 'constants' stamp: 'NS 12/12/2003 15:17'! abstractMarkers ^ #(subclassResponsibility shouldNotImplement)! ! !CompiledMethod class methodsFor: 'constants' stamp: 'al 1/23/2004 13:11'! conflictMarker ^ #traitConflict! ! !CompiledMethod class methodsFor: 'constants' stamp: 'al 1/23/2004 13:11'! disabledMarker ^ #shouldNotImplement! ! !CompiledMethod class methodsFor: 'constants' stamp: 'al 1/23/2004 13:11'! explicitRequirementMarker ^ #explicitRequirement! ! !CompiledMethod class methodsFor: 'constants' stamp: 'al 1/23/2004 13:11'! implicitRequirementMarker ^ #requirement! ! !CompiledMethod class methodsFor: 'constants' stamp: 'al 1/23/2004 13:11'! subclassResponsibilityMarker ^ #subclassResponsibility! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'tk 9/9/2000 20:36'! basicNew: size self error: 'CompiledMethods may only be created with newMethod:header:' ! ! !CompiledMethod class methodsFor: 'instance creation'! new "This will not make a meaningful method, but it could be used to invoke some otherwise useful method in this class." ^ self newMethod: 0 header: 0! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'tk 1/21/2000 15:25'! new: size self error: 'CompiledMethods may only be created with newMethod:header:'! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'md 7/14/2006 21:21'! newBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex "Answer an instance of me. The header is specified by the message arguments. The remaining parts are not as yet determined." | largeBit primBits method | nTemps > 63 ifTrue: [^ self error: 'Cannot compile -- too many temporary variables']. nLits > 255 ifTrue: [^ self error: 'Cannot compile -- too many literals variables']. largeBit := (nTemps + stackSize) > SmallFrame ifTrue: [1] ifFalse: [0]. primBits := primitiveIndex <= 16r1FF ifTrue: [primitiveIndex] ifFalse: ["For now the high bit of primitive no. is in the 29th bit of header" primitiveIndex > 16r3FF ifTrue: [self error: 'prim num too large']. (primitiveIndex bitAnd: 16r1FF) + ((primitiveIndex bitAnd: 16r200) bitShift: 19)]. method := self newMethod: numberOfBytes + trailer size header: (nArgs bitShift: 24) + (nTemps bitShift: 18) + (largeBit bitShift: 17) + (nLits bitShift: 9) + primBits. 1 to: trailer size do: "Copy the source code trailer to the end" [:i | method at: method size - trailer size + i put: (trailer at: i)]. ^ method! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'md 7/14/2006 21:21'! newBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex flag: flag "Answer an instance of me. The header is specified by the message arguments. The remaining parts are not as yet determined." | largeBit primBits method flagBit | nTemps > 63 ifTrue: [^ self error: 'Cannot compile -- too many temporary variables']. nLits > 255 ifTrue: [^ self error: 'Cannot compile -- too many literals variables']. largeBit := (nTemps + stackSize) > SmallFrame ifTrue: [1] ifFalse: [0]. "For now the high bit of the primitive no. is in a high bit of the header" primBits := (primitiveIndex bitAnd: 16r1FF) + ((primitiveIndex bitAnd: 16r200) bitShift: 19). flagBit := flag ifTrue: [ 1 ] ifFalse: [ 0 ]. method := self newMethod: numberOfBytes + trailer size header: (nArgs bitShift: 24) + (nTemps bitShift: 18) + (largeBit bitShift: 17) + (nLits bitShift: 9) + primBits + (flagBit bitShift: 29). "Copy the source code trailer to the end" 1 to: trailer size do: [:i | method at: method size - trailer size + i put: (trailer at: i)]. ^ method! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'NS 12/12/2003 15:03'! newFrom: aCompiledMethod | inst | inst := super basicNew: aCompiledMethod size. 1 to: aCompiledMethod size do: [:index | inst at: index put: (aCompiledMethod at: index)]. ^ inst.! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'NS 12/12/2003 15:08'! newInstanceFrom: oldInstance variable: variable size: instSize map: map "Create a new instance of the receiver based on the given old instance. The supplied map contains a mapping of the old instVar names into the receiver's instVars" | new | new := self newFrom: oldInstance. 1 to: instSize do: [:offset | (map at: offset) > 0 ifTrue: [new instVarAt: offset put: (oldInstance instVarAt: (map at: offset))]]. ^new! ! !CompiledMethod class methodsFor: 'instance creation'! newMethod: numberOfBytes header: headerWord "Primitive. Answer an instance of me. The number of literals (and other information) is specified the headerWord. The first argument specifies the number of fields for bytecodes in the method. Fail if either argument is not a SmallInteger, or if numberOfBytes is negative. Once the header of a method is set by this primitive, it cannot be changed in any way. Essential. See Object documentation whatIsAPrimitive." (numberOfBytes isInteger and: [headerWord isInteger and: [numberOfBytes >= 0]]) ifTrue: [ "args okay; space must be low" Smalltalk signalLowSpace. "retry if user proceeds" ^ self newMethod: numberOfBytes header: headerWord ]. ^self primitiveFailed! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'md 2/20/2006 21:10'! primitive: primNum numArgs: numArgs numTemps: numTemps stackSize: stackSize literals: literals bytecodes: bytecodes trailer: trailerBytes "Create method with given attributes. numTemps includes numArgs. stackSize does not include numTemps." | compiledMethod | compiledMethod := self newBytes: bytecodes size trailerBytes: trailerBytes nArgs: numArgs nTemps: numTemps nStack: stackSize nLits: literals size primitive: primNum. (WriteStream with: compiledMethod) position: compiledMethod initialPC - 1; nextPutAll: bytecodes. literals withIndexDo: [:obj :i | compiledMethod literalAt: i put: obj]. ^ compiledMethod! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'md 8/5/2005 17:06'! toReturnConstant: index trailerBytes: trailer "Answer an instance of me that is a quick return of the constant indexed in (true false nil -1 0 1 2)." ^ self newBytes: 0 trailerBytes: trailer nArgs: 0 nTemps: 0 nStack: 0 nLits: 2 primitive: 256 + index ! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'md 8/5/2005 17:06'! toReturnField: field trailerBytes: trailer "Answer an instance of me that is a quick return of the instance variable indexed by the argument, field." ^ self newBytes: 0 trailerBytes: trailer nArgs: 0 nTemps: 0 nStack: 0 nLits: 2 primitive: 264 + field ! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'di 5/25/2000 06:51'! toReturnSelf "Answer an instance of me that is a quick return of the instance (^self)." ^ self toReturnSelfTrailerBytes: #(0 0 0 0)! ! !CompiledMethod class methodsFor: 'instance creation' stamp: 'md 8/5/2005 17:05'! toReturnSelfTrailerBytes: trailer "Answer an instance of me that is a quick return of the instance (^self)." ^ self newBytes: 0 trailerBytes: trailer nArgs: 0 nTemps: 0 nStack: 0 nLits: 2 primitive: 256 ! ! TestCase subclass: #CompiledMethodAsStringTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Compiler'! !CompiledMethodAsStringTest methodsFor: 'running' stamp: 'stephane.ducasse 8/9/2009 12:33'! testCompiledMethodAsString "self debug: #testCompiledMethodAsString" self shouldnt: [CompiledMethod allInstances first asString] raise: Error! ! Inspector subclass: #CompiledMethodInspector instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tools-Inspector'! !CompiledMethodInspector methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'! fieldList | keys | keys := OrderedCollection new. keys add: 'self'. keys add: 'all bytecodes'. keys add: 'header'. 1 to: object numLiterals do: [ :i | keys add: 'literal', i printString ]. object initialPC to: object size do: [ :i | keys add: i printString ]. ^ keys asArray ! ! !CompiledMethodInspector methodsFor: 'selecting' stamp: 'ajh 3/20/2003 00:17'! contentsIsString "Hacked so contents empty when deselected" ^ #(0 2 3) includes: selectionIndex! ! !CompiledMethodInspector methodsFor: 'selecting' stamp: 'sd 11/20/2005 21:27'! selection | bytecodeIndex | selectionIndex = 0 ifTrue: [^ '']. selectionIndex = 1 ifTrue: [^ object ]. selectionIndex = 2 ifTrue: [^ object symbolic]. selectionIndex = 3 ifTrue: [^ object headerDescription]. selectionIndex <= (object numLiterals + 3) ifTrue: [ ^ object objectAt: selectionIndex - 2 ]. bytecodeIndex := selectionIndex - object numLiterals - 3. ^ object at: object initialPC + bytecodeIndex - 1! ! !CompiledMethodInspector methodsFor: 'selecting' stamp: 'ajh 3/20/2001 11:56'! selectionUnmodifiable "Answer if the current selected variable is unmodifiable via acceptance in the code pane. For most inspectors, no selection and a selection of self (selectionIndex = 1) are unmodifiable" ^ true! ! ClassTestCase subclass: #CompiledMethodTest instanceVariableNames: 'x y' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'! !CompiledMethodTest commentStamp: '' prior: 0! This is the unit test for the class CompiledMethod. Unit tests are a good way to exercise the functionality of your system in a repeatable and automatic manner. They are therefore recommended if you plan to release anything. For more information, see: - http://www.c2.com/cgi/wiki?UnitTest - http://minnow.cc.gatech.edu/squeak/1547 - the sunit class category! !CompiledMethodTest methodsFor: 'examples' stamp: 'sd 4/6/2009 21:27'! readX | tmp | tmp := x. ^ tmp! ! !CompiledMethodTest methodsFor: 'examples' stamp: 'sd 4/6/2009 21:23'! readXandY ^ x + y ! ! !CompiledMethodTest methodsFor: 'examples' stamp: 'md 2/18/2006 20:09'! returnPlusOne: anInteger ^anInteger + 1. ! ! !CompiledMethodTest methodsFor: 'examples' stamp: 'md 2/18/2006 20:09'! returnTrue ^true ! ! !CompiledMethodTest methodsFor: 'examples' stamp: 'sd 4/6/2009 21:23'! writeX x := 33 ! ! !CompiledMethodTest methodsFor: 'examples' stamp: 'sd 4/6/2009 21:23'! writeXandY x := 33. y := 66 ! ! !CompiledMethodTest methodsFor: 'tests - accessing' stamp: 'md 2/18/2006 20:10'! testMethodClass | method cls | method := self class >> #returnTrue. self assert: method selector = #returnTrue. "now make an orphaned method by just deleting the class. old: #unknown new semantics: return Absolete class" Smalltalk removeClassNamed: #TUTU. cls := Object subclass: #TUTU instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'. cls compile: 'foo ^ 10'. method := cls >> #foo. Smalltalk removeClassNamed: #TUTU. self assert: method methodClass = cls! ! !CompiledMethodTest methodsFor: 'tests - accessing' stamp: 'md 2/15/2006 20:54'! testSearchForClass | method cls | method := (self class)>>#returnTrue. self assert: (method searchForClass = self class). "now make an orphaned method. we want to get nil as the class" Smalltalk removeClassNamed: #TUTU. cls := Object subclass: #TUTU instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'. cls compile: 'foo ^ 10'. method := cls >> #foo. Smalltalk removeClassNamed: #TUTU. self assert: method searchForClass = nil. ! ! !CompiledMethodTest methodsFor: 'tests - accessing' stamp: 'md 2/15/2006 20:55'! testSearchForSelector | method cls | method := (self class)>>#returnTrue. self assert: (method searchForSelector = #returnTrue). "now make an orphaned method. we want to get nil as the selector" Smalltalk removeClassNamed: #TUTU. cls := Object subclass: #TUTU instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'. cls compile: 'foo ^ 10'. method := cls >> #foo. Smalltalk removeClassNamed: #TUTU. self assert: method searchForSelector = nil. ! ! !CompiledMethodTest methodsFor: 'tests - accessing' stamp: 'md 2/16/2006 20:28'! testSelector | method cls | method := (self class)>>#returnTrue. self assert: (method selector = #returnTrue). "now make an orphaned method. new semantics: return corrent name" Smalltalk removeClassNamed: #TUTU. cls := Object subclass: #TUTU instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'. cls compile: 'foo ^ 10'. method := cls >> #foo. Smalltalk removeClassNamed: #TUTU. self assert: method selector = #foo. ! ! !CompiledMethodTest methodsFor: 'tests - decompiling' stamp: 'md 2/16/2006 20:29'! testDecompile "self debug: #testDecompileTree" | method cls stream | Smalltalk removeClassNamed: #TUTU. cls := Object subclass: #TUTU instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'. cls compile: 'foo ^ 10'. method := cls >> #foo. Smalltalk removeClassNamed: #TUTU. stream := ReadWriteStream on: String new. method decompile printOn: stream. self assert: stream contents = 'foo ^ 10' ! ! !CompiledMethodTest methodsFor: 'tests - evaluating' stamp: 'md 4/16/2003 15:30'! testValueWithReceiverArguments | method value | method := self class compiledMethodAt: #returnTrue. value := method valueWithReceiver: nil arguments: #(). self assert: (value = true). method := self class compiledMethodAt: #returnPlusOne:. value := method valueWithReceiver: nil arguments: #(1). self assert: (value = 2). ! ! !CompiledMethodTest methodsFor: 'tests - instance variable' stamp: 'sd 4/6/2009 21:30'! testHasInstVarRef "self debug: #testHasInstVarRef" | method | method := self class compiledMethodAt: #readX. self assert: (method hasInstVarRef). method := self class compiledMethodAt: #readXandY. self assert: (method hasInstVarRef). method := self class compiledMethodAt: #writeX. self assert: (method hasInstVarRef). method := self class compiledMethodAt: #writeXandY. self assert: (method hasInstVarRef). ! ! !CompiledMethodTest methodsFor: 'tests - instance variable' stamp: 'sd 4/6/2009 21:46'! testReadsField "self debug: #testReadsField" | method | method := self class compiledMethodAt: #readX. self assert: (method readsField: 2). method := self class compiledMethodAt: #readXandY. self assert: (method readsField: 3). "read is not write" method := self class compiledMethodAt: #writeX. self deny: (method readsField: 2). method := self class compiledMethodAt: #writeXandY. self deny: (method readsField: 2). method := self class compiledMethodAt: #writeXandY. self deny: (method readsField: 3).! ! !CompiledMethodTest methodsFor: 'tests - instance variable' stamp: 'sd 4/6/2009 21:48'! testWritesField "self debug: #testWritesField" | method | method := self class compiledMethodAt: #writeX. self assert: (method writesField: 2). method := self class compiledMethodAt: #writeXandY. self assert: (method writesField: 2). method := self class compiledMethodAt: #writeXandY. self assert: (method writesField: 3). "write is not read" method := self class compiledMethodAt: #readX. self deny: (method writesField: 2). method := self class compiledMethodAt: #readXandY. self deny: (method writesField: 2). method := self class compiledMethodAt: #readXandY. self deny: (method writesField: 3).! ! !CompiledMethodTest methodsFor: 'tests - testing' stamp: 'md 2/19/2006 11:28'! testHasNewPropertyFormat | method | method := (self class)>>#returnTrue. self assert: method hasNewPropertyFormat. ! ! !CompiledMethodTest methodsFor: 'tests - testing' stamp: 'md 2/18/2006 20:10'! testIsInstalled | method cls | method := (self class)>>#returnTrue. self assert: method isInstalled. "now make an orphaned method by just deleting the class." Smalltalk removeClassNamed: #TUTU. cls := Object subclass: #TUTU instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Methods'. cls compile: 'foo ^ 10'. method := cls >> #foo. Smalltalk removeClassNamed: #TUTU. self deny: method isInstalled. ! ! !CompiledMethodTest methodsFor: 'tests - testing' stamp: 'md 4/16/2003 15:32'! testIsQuick | method | method := self class compiledMethodAt: #returnTrue. self assert: (method isQuick). method := self class compiledMethodAt: #returnPlusOne:. self deny: (method isQuick). ! ! Object subclass: #CompiledMethodWithNode instanceVariableNames: 'node method' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Support'! !CompiledMethodWithNode methodsFor: 'accessing' stamp: 'NS 1/28/2004 09:03'! method ^ method! ! !CompiledMethodWithNode methodsFor: 'accessing' stamp: 'NS 1/28/2004 09:04'! node ^ node! ! !CompiledMethodWithNode methodsFor: 'accessing' stamp: 'NS 1/28/2004 09:04'! selector ^ self node selector! ! !CompiledMethodWithNode methodsFor: 'private' stamp: 'NS 1/28/2004 09:03'! method: aCompiledMethod method := aCompiledMethod! ! !CompiledMethodWithNode methodsFor: 'private' stamp: 'NS 1/28/2004 09:04'! node: aMethodNode node := aMethodNode! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CompiledMethodWithNode class instanceVariableNames: ''! !CompiledMethodWithNode class methodsFor: 'instance creation' stamp: 'NS 1/28/2004 09:05'! generateMethodFromNode: aMethodNode trailer: bytes ^ self method: (aMethodNode generate: bytes) node: aMethodNode.! ! !CompiledMethodWithNode class methodsFor: 'instance creation' stamp: 'NS 1/28/2004 09:05'! method: aCompiledMethod node: aMethodNode ^ self new method: aCompiledMethod; node: aMethodNode.! ! Object subclass: #Compiler instanceVariableNames: 'sourceStream requestor class category context parser' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Kernel'! !Compiler commentStamp: '' prior: 0! The compiler accepts Smalltalk source code and compiles it with respect to a given class. The user of the compiler supplies a context so that temporary variables are accessible during compilation. If there is an error, a requestor (usually a kind of StringHolderController) is sent the message notify:at:in: so that the error message can be displayed. If there is no error, then the result of compilation is a MethodNode, which is the root of a parse tree whose nodes are kinds of ParseNodes. The parse tree can be sent messages to (1) generate code for a CompiledMethod (this is done for compiling methods or evaluating expressions); (2) pretty-print the code (for formatting); or (3) produce a map from object code back to source code (used by debugger program-counter selection). See also Parser, Encoder, ParseNode.! !Compiler methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 07:15'! format: textOrStream in: aClass notifying: aRequestor contentsSymbol: aSymbol "Compile a parse tree from the argument, textOrStream. Answer a string containing the original code, formatted nicely." self deprecated: 'Use ''format: in: notifying:'' instead.'. ^ self format: textOrStream in: aClass notifying: aRequestor! ! !Compiler methodsFor: 'error handling' stamp: 'pavel.krivanek 11/21/2008 16:50'! interactive ^ UIManager default interactiveParserFor: requestor! ! !Compiler methodsFor: 'error handling'! notify: aString "Refer to the comment in Object|notify:." ^self notify: aString at: sourceStream position + 1! ! !Compiler methodsFor: 'error handling' stamp: 'eem 9/25/2008 12:41'! notify: aString at: location "Refer to the comment in Object|notify:." ^requestor == nil ifTrue: [SyntaxErrorNotification inClass: class category: category withCode: (sourceStream contents copyReplaceFrom: location to: location - 1 with: aString) doitFlag: false errorMessage: aString location: location] ifFalse: [requestor notify: aString at: location in: sourceStream]! ! !Compiler methodsFor: 'public access' stamp: 'md 2/28/2006 10:04'! compile: textOrStream in: aClass classified: aCategory notifying: aRequestor ifFail: failBlock "Answer a MethodNode for the argument, textOrStream. If the MethodNode can not be created, notify the argument, aRequestor; if aRequestor is nil, evaluate failBlock instead. The MethodNode is the root of a parse tree. It can be told to generate a CompiledMethod to be installed in the method dictionary of the argument, aClass." | methodNode | self from: textOrStream class: aClass classified: aCategory context: nil notifying: aRequestor. methodNode := self translate: sourceStream noPattern: false ifFail: failBlock. methodNode encoder requestor: requestor. ^methodNode. ! ! !Compiler methodsFor: 'public access' stamp: 'md 2/28/2006 10:45'! compile: textOrStream in: aClass notifying: aRequestor ifFail: failBlock ^self compile: textOrStream in: aClass classified: nil notifying: aRequestor ifFail: failBlock ! ! !Compiler methodsFor: 'public access' stamp: 'vb 8/13/2001 23:11'! compileNoPattern: textOrStream in: aClass context: aContext notifying: aRequestor ifFail: failBlock "Similar to #compile:in:notifying:ifFail:, but the compiled code is expected to be a do-it expression, with no message pattern." self from: textOrStream class: aClass context: aContext notifying: aRequestor. ^self translate: sourceStream noPattern: true ifFail: failBlock! ! !Compiler methodsFor: 'public access' stamp: 'eem 9/4/2009 08:47'! compiledMethodFor: textOrStream in: aContext to: receiver notifying: aRequestor ifFail: failBlock logged: logFlag "Compiles the sourceStream into a parse tree, then generates code into a method, and answers it. If receiver is not nil, then the text can refer to instance variables of that receiver (the Inspector uses this). If aContext is not nil, the text can refer to temporaries in that context (the Debugger uses this). If aRequestor is not nil, then it will receive a notify:at: message before the attempt to evaluate is aborted." | methodNode method | class := (aContext == nil ifTrue: [receiver] ifFalse: [aContext receiver]) class. self from: textOrStream class: class context: aContext notifying: aRequestor. methodNode := self translate: sourceStream noPattern: true ifFail: [^failBlock value]. method := methodNode generate: #(0 0 0 0). self interactive ifTrue: [method := method copyWithTempsFromMethodNode: methodNode]. logFlag ifTrue: [SystemChangeNotifier uniqueInstance evaluated: sourceStream contents context: aContext]. ^method! ! !Compiler methodsFor: 'public access' stamp: 'sd 1/19/2004 20:58'! evaluate: aString in: aContext to: aReceiver "evaluate aString in the given context, and return the result. 2/2/96 sw" | result | result := self evaluate: aString in: aContext to: aReceiver notifying: nil ifFail: [^ #failedDoit]. ^ result! ! !Compiler methodsFor: 'public access' stamp: 'NS 1/19/2004 09:05'! evaluate: textOrStream in: aContext to: receiver notifying: aRequestor ifFail: failBlock ^ self evaluate: textOrStream in: aContext to: receiver notifying: aRequestor ifFail: failBlock logged: false.! ! !Compiler methodsFor: 'public access' stamp: 'eem 7/1/2009 13:53'! evaluate: textOrStream in: aContext to: receiver notifying: aRequestor ifFail: failBlock logged: logFlag "Compiles the sourceStream into a parse tree, then generates code into a method. This method is then installed in the receiver's class so that it can be invoked. In other words, if receiver is not nil, then the text can refer to instance variables of that receiver (the Inspector uses this). If aContext is not nil, the text can refer to temporaries in that context (the Debugger uses this). If aRequestor is not nil, then it will receive a notify:at: message before the attempt to evaluate is aborted. Finally, the compiled method is invoked from here as DoIt or (in the case of evaluation in aContext) DoItIn:. The method is subsequently removed from the class, but this will not get done if the invocation causes an error which is terminated. Such garbage can be removed by executing: Smalltalk allBehaviorsDo: [:cl | cl removeSelector: #DoIt; removeSelector: #DoItIn:]." | methodNode method value toLog itsSelection itsSelectionString | class := (aContext == nil ifTrue: [receiver] ifFalse: [aContext receiver]) class. self from: textOrStream class: class context: aContext notifying: aRequestor. methodNode := self translate: sourceStream noPattern: true ifFail: [^failBlock value]. method := methodNode generate: #(0 0 0 0). self interactive ifTrue: [method := method copyWithTempsFromMethodNode: methodNode]. value := receiver withArgs: (context ifNil: [#()] ifNotNil: [{context}]) executeMethod: method. logFlag ifTrue:[ toLog := ((requestor respondsTo: #selection) and:[(itsSelection := requestor selection) notNil and:[(itsSelectionString := itsSelection asString) isEmptyOrNil not]]) ifTrue:[itsSelectionString] ifFalse:[sourceStream contents]. SystemChangeNotifier uniqueInstance evaluated: toLog context: aContext]. ^ value! ! !Compiler methodsFor: 'public access' stamp: 'alain.plantec 5/18/2009 15:54'! format: textOrStream in: aClass notifying: aRequestor "Compile a parse tree from the argument, textOrStream. Answer a string containing the original code, formatted nicely. If aBoolean is true, then decorate the resulting text with color and hypertext actions" | aNode | self from: textOrStream class: aClass context: nil notifying: aRequestor. aNode := self format: sourceStream noPattern: false ifFail: [^ nil]. ^ aNode decompileString! ! !Compiler methodsFor: 'public access' stamp: 'alain.plantec 5/30/2009 22:41'! format: textOrStream in: aClass notifying: aRequestor decorated: aBoolean self deprecated: #colorWhenPrettyPrintingAsBeenRemoved. ^ self format: textOrStream in: aClass notifying: aRequestor ! ! !Compiler methodsFor: 'public access' stamp: 'marcus.denker 8/17/2008 21:14'! from: textOrStream class: aClass classified: aCategory context: aContext notifying: req self from: textOrStream class: aClass context: aContext notifying: req. category := aCategory ! ! !Compiler methodsFor: 'public access' stamp: 'eem 5/15/2008 15:11'! parse: textOrStream in: aClass notifying: req "Compile the argument, textOrStream, with respect to the class, aClass, and answer the MethodNode that is the root of the resulting parse tree. Notify the argument, req, if an error occurs. The failBlock is defaulted to an empty block." self from: textOrStream class: aClass context: nil notifying: req. ^self parser parse: sourceStream class: class noPattern: false context: context notifying: requestor ifFail: []! ! !Compiler methodsFor: 'public access' stamp: 'eem 5/15/2008 15:13'! parser parser ifNil: [parser := self parserClass new]. ^parser! ! !Compiler methodsFor: 'public access' stamp: 'eem 5/15/2008 15:07'! parser: aParser parser := aParser! ! !Compiler methodsFor: 'public access' stamp: 'eem 5/15/2008 15:05'! parserClass ^parser ifNil: [self class parserClass] ifNotNil: [parser class]! ! !Compiler methodsFor: 'public access' stamp: 'eem 5/15/2008 15:06'! parserClass: aParserClass parser := aParserClass new! ! !Compiler methodsFor: 'public access' stamp: 'md 2/20/2006 21:16'! translate: aStream noPattern: noPattern ifFail: failBlock parser: parser | tree | tree := parser parse: aStream class: class noPattern: noPattern context: context notifying: requestor ifFail: [^ failBlock value]. ^ tree! ! !Compiler methodsFor: 'private' stamp: 'eem 5/15/2008 15:10'! format: aStream noPattern: noPattern ifFail: failBlock ^self parser parse: aStream class: class noPattern: noPattern context: context notifying: requestor ifFail: [^failBlock value]! ! !Compiler methodsFor: 'private' stamp: 'PeterHugossonMiller 9/2/2009 16:05'! from: textOrStream class: aClass context: aContext notifying: req (textOrStream isKindOf: PositionableStream) ifTrue: [sourceStream := textOrStream] ifFalse: [sourceStream := textOrStream asString readStream]. class := aClass. context := aContext. requestor := req! ! !Compiler methodsFor: 'private' stamp: 'eem 5/15/2008 15:11'! translate: aStream noPattern: noPattern ifFail: failBlock ^self parser parse: aStream class: class category: category noPattern: noPattern context: context notifying: requestor ifFail: [^failBlock value]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Compiler class instanceVariableNames: ''! !Compiler class methodsFor: 'accessing' stamp: 'nk 8/30/2004 07:56'! couldEvaluate: anObject "Answer true if anObject can be passed to my various #evaluate: methods." ^anObject isString or: [ anObject isText or: [ anObject isStream ]]! ! !Compiler class methodsFor: 'accessing' stamp: 'md 3/1/2006 21:12'! decompilerClass ^Decompiler! ! !Compiler class methodsFor: 'accessing' stamp: 'eem 5/15/2008 15:12'! new ^ super new parser: self parserClass new! ! !Compiler class methodsFor: 'accessing' stamp: 'eem 5/13/2008 11:37'! parserClass "Answer a parser class to use for parsing methods compiled by instances of the receiver." ^Parser! ! !Compiler class methodsFor: 'deprecated' stamp: 'stephane.ducasse 6/8/2009 22:31'! format: textOrStream in: aClass notifying: aRequestor contentsSymbol: aSymbol ^ self new format: textOrStream in: aClass notifying: aRequestor contentsSymbol: aSymbol! ! !Compiler class methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 07:50'! format: textOrStream in: aClass notifying: aRequestor decorated: aBoolean self deprecated: 'colorization when PrettyPrinting has been removed.'. ^ self format: textOrStream in: aClass notifying: aRequestor ! ! !Compiler class methodsFor: 'evaluating' stamp: 'NS 1/19/2004 10:07'! evaluate: textOrString "See Compiler|evaluate:for:notifying:logged:. If a compilation error occurs, a Syntax Error view is created rather than notifying any requestor. Compilation is carried out with respect to nil, i.e., no object, and the invocation is not logged." ^self evaluate: textOrString for: nil logged: false! ! !Compiler class methodsFor: 'evaluating'! evaluate: textOrString for: anObject logged: logFlag "See Compiler|evaluate:for:notifying:logged:. If a compilation error occurs, a Syntax Error view is created rather than notifying any requestor." ^self evaluate: textOrString for: anObject notifying: nil logged: logFlag! ! !Compiler class methodsFor: 'evaluating' stamp: 'NS 1/19/2004 09:50'! evaluate: textOrString for: anObject notifying: aController logged: logFlag "Compile and execute the argument, textOrString with respect to the class of anObject. If a compilation error occurs, notify aController. If both compilation and execution are successful then, if logFlag is true, log (write) the text onto a system changes file so that it can be replayed if necessary." ^ self new evaluate: textOrString in: nil to: anObject notifying: aController ifFail: [^nil] logged: logFlag.! ! !Compiler class methodsFor: 'evaluating'! evaluate: textOrString logged: logFlag "See Compiler|evaluate:for:notifying:logged:. If a compilation error occurs, a Syntax Error view is created rather than notifying any requestor. Compilation is carried out with respect to nil, i.e., no object." ^self evaluate: textOrString for: nil logged: logFlag! ! !Compiler class methodsFor: 'evaluating'! evaluate: textOrString notifying: aController logged: logFlag "See Compiler|evaluate:for:notifying:logged:. Compilation is carried out with respect to nil, i.e., no object." ^self evaluate: textOrString for: nil notifying: aController logged: logFlag! ! !Compiler class methodsFor: 'evaluating' stamp: 'alain.plantec 5/18/2009 15:53'! format: textOrStream in: aClass notifying: aRequestor ^self new format: textOrStream in: aClass notifying: aRequestor! ! !Compiler class methodsFor: 'utilities' stamp: 'al 1/13/2006 00:02'! recompileAll "Recompile all classes, starting with given name." Smalltalk forgetDoIts. Smalltalk allClassesAndTraits do: [:classOrTrait | classOrTrait compileAll] displayingProgress: 'Recompiling all classes and traits'. ! ! !Compiler class methodsFor: 'utilities' stamp: 'sd 9/25/2004 15:07'! recompileAllFrom: firstName "Recompile all classes, starting with given name." Smalltalk forgetDoIts. Smalltalk allClassesDo: [:class | class name >= firstName ifTrue: [Transcript show: class name; cr. class compileAll]] "Compiler recompileAllFrom: 'AAABodyShop'." ! ! TestCase subclass: #CompilerExceptionsTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Compiler'! !CompilerExceptionsTest methodsFor: 'as yet unclassified' stamp: 'cwp 8/25/2009 20:27'! griffle | goo |! ! !CompilerExceptionsTest methodsFor: 'emulating' stamp: 'cwp 8/25/2009 20:23'! select ! ! !CompilerExceptionsTest methodsFor: 'emulating' stamp: 'cwp 8/25/2009 20:23'! selectFrom: start to: end ! ! !CompilerExceptionsTest methodsFor: 'emulating' stamp: 'cwp 8/25/2009 20:22'! selectionInterval ^ 1 to: 0! ! !CompilerExceptionsTest methodsFor: 'emulating' stamp: 'cwp 8/25/2009 20:26'! text ^ self unusedVariableSource! ! !CompilerExceptionsTest methodsFor: 'tests' stamp: 'cwp 8/25/2009 20:25'! testUnknownSelector self should: [self class compile: 'griffle self reallyHopeThisIsntImplementedAnywhere' notifying: self] raise: UnknownSelector! ! !CompilerExceptionsTest methodsFor: 'private' stamp: 'cwp 8/25/2009 20:28'! unusedVariableSource ^ 'griffle | goo | ^ nil'! ! TestCase subclass: #CompilerTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Compiler'! !CompilerTest commentStamp: 'nice 12/3/2007 22:15' prior: 0! CompilerTest is a holder for SUnit test of Compiler! !CompilerTest methodsFor: 'literals' stamp: 'nice 12/3/2007 22:20'! testScaledDecimalLiterals "Equal ScaledDecimal with different scales should use different slots This is related to http://bugs.squeak.org/view.php?id=6797" "This correctly works when evaluated separately" self deny: (Compiler evaluate: '0.5s1') scale = (Compiler evaluate: '0.5s2') scale. "But not when evaluated together if literal reduction is too agressive" self deny: (Compiler evaluate: '0.5s1 scale = 0.5s2 scale').! ! Object subclass: #Complex instanceVariableNames: 'real imaginary' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Numbers'! !Complex commentStamp: 'mk 10/31/2003 22:19' prior: 0! I represent a complex number. real -- real part of the complex number imaginary -- imaginary part of the complex number Complex number constructors: 5 i 6 + 7 i. 5.6 - 8 i. Complex real: 10 imaginary: 5. Complex abs: 5 arg: (Float pi / 4) Arithmetic operation with other complex or non-complex numbers work. (5 - 6 i) + (-5 + 8 i). "Arithmetic between two complex numbers." 5 * (5 - 6 i). "Arithmetic between a non-complex and a complex number." It is also possible to perform arithmetic operations between a complex number and a array of (complex) numbers: 2 * {1 + 2i. 3 + 4i. 5 + 6i} 5 + 5i * {1 + 2i. 3. 5 + 6i} It behaves analogously as it is with normal numbers and an array. NOTE: Although Complex something similiar to the Smalltalk's Number class, it would not be a good idea to make a Complex to be a subclass of a Number because: - Number is subclass of Magnitude and Complex is certainly not a magnitude. Complex does not behave very well as a Magnitude. Operations such as < > <= >= do not have sense in case of complex numbers. - Methods in the following Number methods' categories do not have sense for a Complex numbers trucation and round off testing intervals comparing - However the following Number methods' categories do have sense for a Complex number arithmetic (with the exception of operation // \\ quo: rem: mathematical functions Thus Complex is somewhat similar to a Number but it is not a subclass of it. Some operations we would like to inherit (e.g. #abs, #negated, #reciprocal) but some of the Number operation do not have sens to inherit or to overload. Classes are not always neat mechanism. !!!!!! We had to COPY the implementation of the abs negated reciprocal log: isZero reciprocal ... methods from the Number class to the Complex class. Awful solution. Now I begin to appreciate the Self. Missing methods String | converting | asComplex Complex | mathematical functions | arcSin Complex | mathematical functions | arcCos Complex | mathematical functions | arcTan! !Complex methodsFor: 'accessing' stamp: 'mk 10/27/2003 17:39'! imaginary ^ imaginary! ! !Complex methodsFor: 'accessing' stamp: 'mk 10/27/2003 17:39'! real ^ real! ! !Complex methodsFor: 'arithmetic' stamp: 'md 7/21/2004 11:25'! * anObject "Answer the result of multiplying the receiver by aNumber." | a b c d newReal newImaginary | anObject isComplex ifTrue: [a := self real. b := self imaginary. c := anObject real. d := anObject imaginary. newReal := (a * c) - (b * d). newImaginary := (a * d) + (b * c). ^ Complex real: newReal imaginary: newImaginary] ifFalse: [^ anObject adaptToComplex: self andSend: #*]! ! !Complex methodsFor: 'arithmetic' stamp: 'mk 1/18/2004 23:31'! + anObject "Answer the sum of the receiver and aNumber." | a b c d newReal newImaginary | anObject isComplex ifTrue: [a := self real. b := self imaginary. c := anObject real. d := anObject imaginary. newReal := a + c. newImaginary := b + d. ^ Complex real: newReal imaginary: newImaginary] ifFalse: [^ anObject adaptToComplex: self andSend: #+]! ! !Complex methodsFor: 'arithmetic' stamp: 'md 7/22/2004 11:45'! - anObject "Answer the difference between the receiver and aNumber." | a b c d newReal newImaginary | anObject isComplex ifTrue: [a := self real. b := self imaginary. c := anObject real. d := anObject imaginary. newReal := a - c. newImaginary := b - d. ^ Complex real: newReal imaginary: newImaginary] ifFalse: [^ anObject adaptToComplex: self andSend: #-]! ! !Complex methodsFor: 'arithmetic' stamp: 'md 7/22/2004 11:45'! / anObject "Answer the result of dividing receiver by aNumber" | a b c d newReal newImaginary | anObject isComplex ifTrue: [a := self real. b := self imaginary. c := anObject real. d := anObject imaginary. newReal := ((a * c) + (b * d)) / ((c * c) + (d * d)). newImaginary := ((b * c) - (a * d)) / ((c * c) + (d * d)). ^ Complex real: newReal imaginary: newImaginary]. ^ anObject adaptToComplex: self andSend: #/.! ! !Complex methodsFor: 'arithmetic' stamp: 'mk 10/27/2003 20:48'! abs "Answer the distance of the receiver from zero (0 + 0 i)." ^ ((real * real) + (imaginary * imaginary)) sqrt! ! !Complex methodsFor: 'arithmetic' stamp: 'mk 10/27/2003 22:08'! arg "Answer the argument of the receiver." self isZero ifTrue: [self error: 'zero has no argument.']. 0 < real ifTrue: [^ (imaginary / real) arcTan]. 0 = real ifTrue: [0 < imaginary ifTrue: [^ Float pi / 2] ifFalse: [^ (Float pi / 2) negated]]. real < 0 ifTrue: [0 <= imaginary ifTrue: [^ (imaginary / real) arcTan + Float pi] ifFalse: [^ (imaginary / real) arcTan - Float pi]]! ! !Complex methodsFor: 'arithmetic' stamp: 'md 7/22/2004 11:48'! divideFastAndSecureBy: anObject "Answer the result of dividing receiver by aNumber" " Both operands are scaled to avoid arithmetic overflow. This algorithm works for a wide range of values, and it needs only three divisions. Note: #reciprocal uses #/ for devision " | r d newReal newImaginary | anObject isComplex ifTrue: [anObject real abs > anObject imaginary abs ifTrue: [r := anObject imaginary / anObject real. d := r*anObject imaginary + anObject real. newReal := r*imaginary + real/d. newImaginary := r negated * real + imaginary/d. ] ifFalse: [r := anObject real / anObject imaginary. d := r*anObject real + anObject imaginary. newReal := r*real + imaginary/d. newImaginary := r*imaginary - real/d. ]. ^ Complex real: newReal imaginary: newImaginary]. ^ anObject adaptToComplex: self andSend: #/.! ! !Complex methodsFor: 'arithmetic' stamp: 'md 7/22/2004 11:48'! divideSecureBy: anObject "Answer the result of dividing receiver by aNumber" " Both operands are scaled to avoid arithmetic overflow. This algorithm works for a wide range of values, but it requires six divisions. #divideFastAndSecureBy: is also quite good, but it uses only 3 divisions. Note: #reciprocal uses #/ for devision" | s ars ais brs bis newReal newImaginary | anObject isComplex ifTrue: [s := anObject real abs + anObject imaginary abs. ars := self real / s. ais := self imaginary / s. brs := anObject real / s. bis := anObject imaginary / s. s := brs squared + bis squared. newReal := ars*brs + (ais*bis) /s. newImaginary := ais*brs - (ars*bis)/s. ^ Complex real: newReal imaginary: newImaginary]. ^ anObject adaptToComplex: self andSend: #/.! ! !Complex methodsFor: 'arithmetic' stamp: 'mk 10/27/2003 19:33'! negated "Answer a Number that is the negation of the receiver." ^0 - self! ! !Complex methodsFor: 'arithmetic' stamp: 'md 7/22/2004 11:47'! reciprocal "Answer 1 divided by the receiver. Create an error notification if the receiver is 0." self = 0 ifTrue: [^ (ZeroDivide dividend: self) signal] ifFalse: [^1 / self] ! ! !Complex methodsFor: 'comparing' stamp: 'hmm 11/1/2006 23:29'! = anObject anObject isNumber ifFalse: [^false]. anObject isComplex ifTrue: [^ (real = anObject real) & (imaginary = anObject imaginary)] ifFalse: [^ anObject adaptToComplex: self andSend: #=]! ! !Complex methodsFor: 'comparing' stamp: 'mk 10/27/2003 20:35'! hash "Hash is reimplemented because = is implemented." ^ real hash bitXor: imaginary hash.! ! !Complex methodsFor: 'converting' stamp: 'mk 10/27/2003 21:51'! adaptToCollection: rcvr andSend: selector "If I am involved in arithmetic with a Collection, return a Collection of the results of each element combined with me in that expression." ^ rcvr collect: [:element | element perform: selector with: self]! ! !Complex methodsFor: 'converting' stamp: 'mk 10/27/2003 18:32'! adaptToFloat: rcvr andSend: selector "If I am involved in arithmetic with a Float, convert it to a Complex number." ^ rcvr asComplex perform: selector with: self! ! !Complex methodsFor: 'converting' stamp: 'mk 10/27/2003 18:32'! adaptToFraction: rcvr andSend: selector "If I am involved in arithmetic with a Fraction, convert it to a Complex number." ^ rcvr asComplex perform: selector with: self! ! !Complex methodsFor: 'converting' stamp: 'mk 10/27/2003 18:31'! adaptToInteger: rcvr andSend: selector "If I am involved in arithmetic with an Integer, convert it to a Complex number." ^ rcvr asComplex perform: selector with: self! ! !Complex methodsFor: 'mathematical functions' stamp: 'md 7/16/2004 16:16'! cos "Answer receiver's cosine." | iself | iself := 1 i * self. ^ (iself exp + iself negated exp) / 2! ! !Complex methodsFor: 'mathematical functions' stamp: 'mk 10/27/2003 21:34'! cosh "Answer receiver's hyperbolic cosine." ^ (self exp + self negated exp) / 2! ! !Complex methodsFor: 'mathematical functions' stamp: 'md 7/16/2004 16:16'! exp "Answer the exponential of the receiver." ^ real exp * (imaginary cos + (1 i * imaginary sin))! ! !Complex methodsFor: 'mathematical functions' stamp: 'laza 9/26/2005 10:25'! ln "Answer the natural log of the receiver." ^ self abs ln + (1 i * self arg)! ! !Complex methodsFor: 'mathematical functions' stamp: 'mk 10/27/2003 22:05'! log: aNumber "Answer the log base aNumber of the receiver." ^self ln / aNumber ln! ! !Complex methodsFor: 'mathematical functions' stamp: 'md 7/16/2004 16:16'! sin "Answer receiver's sine." | iself | iself := 1 i * self. ^ (iself exp - iself negated exp) / 2 i! ! !Complex methodsFor: 'mathematical functions' stamp: 'mk 10/27/2003 21:33'! sinh "Answer receiver's hyperbolic sine." ^ (self exp - self negated exp) / 2! ! !Complex methodsFor: 'mathematical functions' stamp: 'md 7/20/2004 12:02'! squared "Answer the receiver multipled by itself." ^self * self! ! !Complex methodsFor: 'mathematical functions' stamp: 'mk 10/27/2003 22:04'! tan "Answer receivers tangent." ^ self sin / self cos! ! !Complex methodsFor: 'printing' stamp: 'mk 10/27/2003 18:02'! printOn: aStream real printOn: aStream. aStream nextPut: Character space. 0 <= imaginary ifTrue: [aStream nextPut: $+] ifFalse: [aStream nextPut: $-]. aStream nextPut: Character space. imaginary abs printOn: aStream. aStream nextPut: Character space. aStream nextPut: $i ! ! !Complex methodsFor: 'testing' stamp: 'mk 10/27/2003 17:33'! isComplex ^ true! ! !Complex methodsFor: 'testing' stamp: 'hmm 11/1/2006 23:34'! isNumber ^ true! ! !Complex methodsFor: 'testing' stamp: 'mk 10/27/2003 20:06'! isZero ^ self = 0! ! !Complex methodsFor: 'private' stamp: 'mk 10/27/2003 17:26'! imaginary: aNumber imaginary := aNumber.! ! !Complex methodsFor: 'private' stamp: 'mk 10/27/2003 17:26'! real: aNumber real := aNumber.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Complex class instanceVariableNames: ''! !Complex class methodsFor: 'instance creation' stamp: 'mk 10/27/2003 21:03'! abs: aNumber1 arg: aNumber2 | real imaginary | real := aNumber1 * aNumber2 cos. imaginary := aNumber1 * aNumber2 sin. ^ real + imaginary i! ! !Complex class methodsFor: 'instance creation' stamp: 'mk 10/27/2003 17:28'! new ^ self real: 0 imaginary: 0! ! !Complex class methodsFor: 'instance creation' stamp: 'mk 10/27/2003 17:27'! real: aNumber1 imaginary: aNumber2 | newComplex | newComplex := super new. newComplex real: aNumber1; imaginary: aNumber2. ^ newComplex! ! SimpleBorder subclass: #ComplexBorder instanceVariableNames: 'style colors lineStyles' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Borders'! !ComplexBorder commentStamp: 'kfr 10/27/2003 10:18' prior: 0! see BorderedMorph. poly _ polygon250 baseColor _ Color blue twiceLighter. border _ (ComplexBorder framed: 10) baseColor: poly color. border frameRectangle: ((100@100 extent: 200@200) insetBy: -5) on: Display getCanvas. baseColor _ Color red twiceLighter. border _ (ComplexBorder framed: 10) baseColor: baseColor. border drawPolygon: {100@100. 300@100. 300@300. 100@300} on: Display getCanvas. border drawPolyPatchFrom: 100@200 via: 100@100 via: 200@100 to: 200@200 on: Display getCanvas. border drawPolyPatchFrom: 100@100 via: 200@100 via: 200@200 to: 100@200 on: Display getCanvas. border drawPolyPatchFrom: 200@100 via: 200@200 via: 100@200 to: 100@100 on: Display getCanvas. border drawPolyPatchFrom: 200@200 via: 100@200 via: 100@100 to: 200@100 on: Display getCanvas. border _ (ComplexBorder raised: 10) baseColor: poly color. border drawPolygon: poly getVertices on: Display getCanvas 360 / 16.0 22.5 points _ (0 to: 15) collect:[:i| (Point r: 100 degrees: i*22.5) + 200]. Display getCanvas fillOval: (100@100 extent: 200@200) color: baseColor. border drawPolygon: points on: Display getCanvas. -1 to: points size + 1 do:[:i| border drawPolyPatchFrom: (points atWrap: i) via: (points atWrap: i+1) via: (points atWrap: i+2) to: (points atWrap: i+3) on: Display getCanvas. ]. Display getCanvas fillOval: (100@100 extent: 200@200) color: baseColor. 0 to: 36 do:[:i| border drawLineFrom: (Point r: 100 degrees: i*10) + 200 to: (Point r: 100 degrees: i+1*10) + 200 on: Display getCanvas. ]. drawPolygon: Point r: 1.0 degrees: 10 MessageTally spyOn:[ Display deferUpdates: true. t1 _ [1 to: 1000 do:[:i| border drawLineFrom: (100@100) to: (300@100) on: Display getCanvas. border drawLineFrom: (300@100) to: (300@300) on: Display getCanvas. border drawLineFrom: (300@300) to: (100@300) on: Display getCanvas. border drawLineFrom: (100@300) to: (100@100) on: Display getCanvas]] timeToRun. Display deferUpdates: false. ]. MessageTally spyOn:[ Display deferUpdates: true. t2 _ [1 to: 1000 do:[:i| border drawLine2From: (100@100) to: (300@100) on: Display getCanvas. border drawLine2From: (300@100) to: (300@300) on: Display getCanvas. border drawLine2From: (300@300) to: (100@300) on: Display getCanvas. border drawLine2From: (100@300) to: (100@100) on: Display getCanvas]] timeToRun. Display deferUpdates: false. ]. ! !ComplexBorder methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:13'! colors ^colors ifNil:[colors := self computeColors].! ! !ComplexBorder methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:22'! style ^style! ! !ComplexBorder methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:22'! style: newStyle style == newStyle ifTrue:[^self]. style := newStyle. self releaseCachedState.! ! !ComplexBorder methodsFor: 'accessing' stamp: 'ar 8/25/2001 16:14'! widthForRounding ^0! ! !ComplexBorder methodsFor: 'color tracking' stamp: 'ar 8/25/2001 18:17'! trackColorFrom: aMorph baseColor ifNil:[self color: aMorph raisedColor].! ! !ComplexBorder methodsFor: 'drawing' stamp: 'aoy 2/17/2003 01:08'! drawLineFrom: startPoint to: stopPoint on: aCanvas "Here we're using the balloon engine since this is much faster than BitBlt w/ brushes." | delta length dir cos sin tfm w h w1 w2 h1 h2 fill | width isPoint ifTrue: [w := width x. h := width y] ifFalse: [w := h := width]. w1 := w // 2. w2 := w - w1. h1 := h // 2. h2 := h - h1. "Compute the rotational transform from (0@0) -> (1@0) to startPoint -> stopPoint" delta := stopPoint - startPoint. length := delta r. dir := length > 1.0e-10 ifTrue: [delta / length] ifFalse: [ 1 @ 0]. cos := dir dotProduct: 1 @ 0. sin := dir crossProduct: 1 @ 0. tfm := (MatrixTransform2x3 new) a11: cos; a12: sin; a21: sin negated; a22: cos. "Install the start point offset" tfm offset: startPoint. "Now get the fill style appropriate for the given direction" fill := self fillStyleForDirection: dir. "And draw..." aCanvas asBalloonCanvas transformBy: tfm during: [:cc | cc drawPolygon: { (0 - w1) @ (0 - h1). "top left" (length + w2) @ (0 - h1). "top right" (length + w2) @ h2. "bottom right" (0 - w1) @ h2 "bottom left"} fillStyle: fill]! ! !ComplexBorder methodsFor: 'drawing' stamp: 'ar 11/26/2001 15:10'! drawPolyPatchFrom: startPoint to: stopPoint on: aCanvas usingEnds: endsArray | cos sin tfm fill dir fsOrigin fsDirection points x y | dir := (stopPoint - startPoint) normalized. "Compute the rotational transform from (0@0) -> (1@0) to startPoint -> stopPoint" cos := dir dotProduct: (1@0). sin := dir crossProduct: (1@0). "Now get the fill style appropriate for the given direction" fill := self fillStyleForDirection: dir. false ifTrue:[ "Transform the fill appropriately" fill := fill clone. "Note: Code below is inlined from tfm transformPoint:/transformDirection:" x := fill origin x. y := fill origin y. fsOrigin := ((x * cos) + (y * sin) + startPoint x) @ ((y * cos) - (x * sin) + startPoint y). x := fill direction x. y := fill direction y. fsDirection := ((x * cos) + (y * sin)) @ ((y * cos) - (x * sin)). fill origin: fsOrigin; direction: fsDirection rounded; "NOTE: This is a bug in the balloon engine!!!!!!" normal: nil. aCanvas asBalloonCanvas drawPolygon: endsArray fillStyle: fill. ] ifFalse:[ "Transform the points rather than the fills" tfm := (MatrixTransform2x3 new) a11: cos; a12: sin; a21: sin negated; a22: cos. "Install the start point offset" tfm offset: startPoint. points := endsArray collect:[:pt| tfm invertPoint: pt]. aCanvas asBalloonCanvas transformBy: tfm during:[:cc| cc drawPolygon: points fillStyle: fill. ]. ].! ! !ComplexBorder methodsFor: 'drawing' stamp: 'ar 9/4/2001 19:51'! framePolygon2: vertices on: aCanvas | dir1 dir2 dir3 nrm1 nrm2 nrm3 point1 point2 point3 cross1 cross2 pointA pointB pointC pointD w p1 p2 p3 p4 balloon ends | balloon := aCanvas asBalloonCanvas. balloon == aCanvas ifFalse:[balloon deferred: true]. ends := Array new: 4. w := width * 0.5. pointA := nil. 1 to: vertices size do:[:i| p1 := vertices atWrap: i. p2 := vertices atWrap: i+1. p3 := vertices atWrap: i+2. p4 := vertices atWrap: i+3. dir1 := p2 - p1. dir2 := p3 - p2. dir3 := p4 - p3. i = 1 ifTrue:[ "Compute the merge points of p1->p2 with p2->p3" cross1 := dir2 crossProduct: dir1. nrm1 := dir1 normalized. nrm1 := (nrm1 y * w) @ (0 - nrm1 x * w). nrm2 := dir2 normalized. nrm2 := (nrm2 y * w) @ (0 - nrm2 x * w). cross1 < 0 ifTrue:[nrm1 := nrm1 negated. nrm2 := nrm2 negated]. point1 := (p1 x + nrm1 x) @ (p1 y + nrm1 y). point2 := (p2 x + nrm2 x) @ (p2 y + nrm2 y). pointA := self intersectFrom: point1 with: dir1 to: point2 with: dir2. point1 := (p1 x - nrm1 x) @ (p1 y - nrm1 y). point2 := (p2 x - nrm2 x) @ (p2 y - nrm2 y). pointB := self intersectFrom: point1 with: dir1 to: point2 with: dir2. pointB ifNotNil:[ (pointB x - p2 x) abs + (pointB y - p2 y) abs > (4*w) ifTrue:[pointA := pointB := nil]. ]. ]. "Compute the merge points of p2->p3 with p3->p4" cross2 := dir3 crossProduct: dir2. nrm2 := dir2 normalized. nrm2 := (nrm2 y * w) @ (0 - nrm2 x * w). nrm3 := dir3 normalized. nrm3 := (nrm3 y * w) @ (0 - nrm3 x * w). cross2 < 0 ifTrue:[nrm2 := nrm2 negated. nrm3 := nrm3 negated]. point2 := (p2 x + nrm2 x) @ (p2 y + nrm2 y). point3 := (p3 x + nrm3 x) @ (p3 y + nrm3 y). pointC := self intersectFrom: point2 with: dir2 to: point3 with: dir3. point2 := (p2 x - nrm2 x) @ (p2 y - nrm2 y). point3 := (p3 x - nrm3 x) @ (p3 y - nrm3 y). pointD := self intersectFrom: point2 with: dir2 to: point3 with: dir3. pointD ifNotNil:[ (pointD x - p3 x) abs + (pointD y - p3 y) abs > (4*w) ifTrue:[pointC := pointD := nil]. ]. cross1 * cross2 < 0.0 ifTrue:[ point1 := pointA. pointA := pointB. pointB := point1. cross1 := 0.0 - cross1]. ends at: 1 put: pointA; at: 2 put: pointB; at: 3 put: pointD; at: 4 put: pointC. pointA ifNil:["degenerate and slow" nrm2 := dir2 normalized. nrm2 := (nrm2 y * w) @ (0 - nrm2 x * w). cross1 < 0 ifTrue:[nrm2 := nrm2 negated]. point2 := (p2 x + nrm2 x) @ (p2 y + nrm2 y). ends at: 1 put: point2]. pointB ifNil:["degenerate and slow" nrm2 := dir2 normalized. nrm2 := (nrm2 y * w) @ (0 - nrm2 x * w). cross1 < 0 ifTrue:[nrm2 := nrm2 negated]. point2 := (p2 x - nrm2 x) @ (p2 y - nrm2 y). ends at: 2 put: point2]. pointC ifNil:["degenerate and slow" nrm2 := dir2 normalized. nrm2 := (nrm2 y * w) @ (0 - nrm2 x * w). cross2 < 0 ifTrue:[nrm2 := nrm2 negated]. point2 := (p3 x + nrm2 x) @ (p3 y + nrm2 y). ends at: 4 put: point2]. pointD ifNil:["degenerate and slow" nrm2 := dir2 normalized. nrm2 := (nrm2 y * w) @ (0 - nrm2 x * w). cross2 < 0 ifTrue:[nrm2 := nrm2 negated]. point2 := (p3 x - nrm2 x) @ (p3 y - nrm2 y). ends at: 3 put: point2]. self drawPolyPatchFrom: p2 to: p3 on: balloon usingEnds: ends. pointA := pointC. pointB := pointD. cross1 := cross2. ]. balloon == aCanvas ifFalse:[balloon flush].! ! !ComplexBorder methodsFor: 'drawing' stamp: 'ar 9/4/2001 19:50'! framePolygon: vertices on: aCanvas | dir1 dir2 dir3 nrm1 nrm2 nrm3 point1 point2 point3 cross1 cross2 pointA pointB pointC pointD w p1 p2 p3 p4 balloon ends pointE pointF | balloon := aCanvas asBalloonCanvas. balloon == aCanvas ifFalse:[balloon deferred: true]. ends := Array new: 6. w := width * 0.5. pointA := nil. 1 to: vertices size do:[:i| p1 := vertices atWrap: i. p2 := vertices atWrap: i+1. p3 := vertices atWrap: i+2. p4 := vertices atWrap: i+3. dir1 := p2 - p1. dir2 := p3 - p2. dir3 := p4 - p3. (i = 1 | true) ifTrue:[ "Compute the merge points of p1->p2 with p2->p3" cross1 := dir2 crossProduct: dir1. nrm1 := dir1 normalized. nrm1 := (nrm1 y * w) @ (0 - nrm1 x * w). nrm2 := dir2 normalized. nrm2 := (nrm2 y * w) @ (0 - nrm2 x * w). cross1 < 0 ifTrue:[nrm1 := nrm1 negated. nrm2 := nrm2 negated]. point1 := (p1 x + nrm1 x) @ (p1 y + nrm1 y). point2 := (p2 x + nrm2 x) @ (p2 y + nrm2 y). pointA := self intersectFrom: point1 with: dir1 to: point2 with: dir2. point1 := (p1 x - nrm1 x) @ (p1 y - nrm1 y). point2 := (p2 x - nrm2 x) @ (p2 y - nrm2 y). pointB := point1 + dir1 + point2 * 0.5. pointB := p2 + ((pointB - p2) normalized * w). pointC := point2. ]. "Compute the merge points of p2->p3 with p3->p4" cross2 := dir3 crossProduct: dir2. nrm2 := dir2 normalized. nrm2 := (nrm2 y * w) @ (0 - nrm2 x * w). nrm3 := dir3 normalized. nrm3 := (nrm3 y * w) @ (0 - nrm3 x * w). cross2 < 0 ifTrue:[nrm2 := nrm2 negated. nrm3 := nrm3 negated]. point2 := (p2 x + nrm2 x) @ (p2 y + nrm2 y). point3 := (p3 x + nrm3 x) @ (p3 y + nrm3 y). pointD := self intersectFrom: point2 with: dir2 to: point3 with: dir3. point2 := (p2 x - nrm2 x) @ (p2 y - nrm2 y). point3 := (p3 x - nrm3 x) @ (p3 y - nrm3 y). pointF := point2 + dir2. pointE := pointF + point3 * 0.5. pointE := p3 + ((pointE - p3) normalized * w). cross1 * cross2 < 0.0 ifTrue:[ ends at: 1 put: pointA; at: 2 put: pointB; at: 3 put: pointC; at: 4 put: pointD; at: 5 put: pointE; at: 6 put: pointF. ] ifFalse:[ ends at: 1 put: pointA; at: 2 put: pointB; at: 3 put: pointC; at: 4 put: pointF; at: 5 put: pointE; at: 6 put: pointD. ]. self drawPolyPatchFrom: p2 to: p3 on: balloon usingEnds: ends. pointA := pointD. pointB := pointE. pointC := pointF. cross1 := cross2. ]. balloon == aCanvas ifFalse:[balloon flush].! ! !ComplexBorder methodsFor: 'drawing' stamp: 'ar 8/26/2001 19:01'! frameRectangle: aRectangle on: aCanvas "Note: This uses BitBlt since it's roughly a factor of two faster for rectangles" | w h r | self colors ifNil:[^super frameRectangle: aRectangle on: aCanvas]. w := self width. w isPoint ifTrue:[h := w y. w := w x] ifFalse:[h := w]. 1 to: h do:[:i| "top/bottom" r := (aRectangle topLeft + (i-1)) extent: (aRectangle width - (i-1*2))@1. "top" aCanvas fillRectangle: r color: (colors at: i). r := (aRectangle bottomLeft + (i @ (0-i))) extent: (aRectangle width - (i-1*2) - 1)@1. "bottom" aCanvas fillRectangle: r color: (colors at: colors size - i + 1). ]. 1 to: w do:[:i| "left/right" r := (aRectangle topLeft + (i-1)) extent: 1@(aRectangle height - (i-1*2)). "left" aCanvas fillRectangle: r color: (colors at: i). r := aRectangle topRight + ((0-i)@i) extent: 1@(aRectangle height - (i-1*2) - 1). "right" aCanvas fillRectangle: r color: (colors at: colors size - i + 1). ].! ! !ComplexBorder methodsFor: 'initialize' stamp: 'ar 11/26/2001 14:43'! releaseCachedState colors := nil. lineStyles := nil.! ! !ComplexBorder methodsFor: 'testing' stamp: 'ar 8/26/2001 19:30'! isComplex ^true! ! !ComplexBorder methodsFor: 'private' stamp: 'aoy 2/17/2003 01:02'! colorsForDirection: direction "Return an array of colors describing the receiver in the given direction" | colorArray dT cc | cc := self colors. direction x * direction y <= 0 ifTrue: ["within up->right or down->left transition; no color blend needed" colorArray := (direction x > 0 or: [direction y < 0]) ifTrue: ["up->right" cc copyFrom: 1 to: width] ifFalse: ["down->left" "colors are stored in reverse direction when following a line" (cc copyFrom: width + 1 to: cc size) reversed]] ifFalse: ["right->down or left->up transition; need color blend" colorArray := Array new: width. dT := direction x asFloat / (direction x + direction y). (direction x > 0 or: [direction y >= 0]) ifTrue: ["top-right" 1 to: width do: [:i | colorArray at: i put: ((cc at: i) mixed: dT with: (cc at: cc size - i + 1))]] ifFalse: ["bottom-left" 1 to: width do: [:i | colorArray at: i put: ((cc at: cc size - i + 1) mixed: dT with: (cc at: i))]]]. ^colorArray! ! !ComplexBorder methodsFor: 'private' stamp: 'ar 8/25/2001 16:16'! computeAltFramedColors | base light dark w hw colorArray param | base := self color asColor. light := Color white. dark := Color black. w := self width isPoint ifTrue:[self width x max: self width y] ifFalse:[self width]. w := w asInteger. w = 1 ifTrue:[^{base mixed: 0.5 with: light. base mixed: 0.5 with: dark}]. colorArray := Array new: w. hw := w // 2. "brighten" 0 to: hw-1 do:[:i| param := 0.5 + (i asFloat / hw * 0.5). colorArray at: i+1 put: (base mixed: param with: dark). "brighten" colorArray at: w-i put: (base mixed: param with: light). "darken" ]. w odd ifTrue:[colorArray at: hw+1 put: base]. ^colorArray, colorArray! ! !ComplexBorder methodsFor: 'private' stamp: 'aoy 2/17/2003 01:03'! computeAltInsetColors | base light dark w colorArray param hw | base := self color asColor. light := Color white. dark := Color black. w := self width isPoint ifTrue: [self width x max: self width y] ifFalse: [self width]. w := w asInteger. colorArray := Array new: w * 2. hw := 0.5 / w. 0 to: w - 1 do: [:i | param := false ifTrue: ["whats this ???!! false ifTrue:[]" 0.5 + (hw * i)] ifFalse: [0.5 + (hw * (w - i))]. colorArray at: i + 1 put: (base mixed: param with: dark). "darken" colorArray at: colorArray size - i put: (base mixed: param with: light) "brighten"]. ^colorArray! ! !ComplexBorder methodsFor: 'private' stamp: 'aoy 2/17/2003 01:05'! computeAltRaisedColors | base light dark w colorArray param hw | base := self color asColor. light := Color white. dark := Color black. w := self width isPoint ifTrue: [self width x max: self width y] ifFalse: [self width]. w := w asInteger. colorArray := Array new: w * 2. hw := 0.5 / w. 0 to: w - 1 do: [:i | "again !! false ifTrue:[] ?!!" param := false ifTrue: [0.5 + (hw * i)] ifFalse: [0.5 + (hw * (w - i))]. colorArray at: i + 1 put: (base mixed: param with: light). "brighten" colorArray at: colorArray size - i put: (base mixed: param with: dark) "darken"]. ^colorArray! ! !ComplexBorder methodsFor: 'private' stamp: 'ar 11/26/2001 15:00'! computeColors width = 0 ifTrue:[^colors := #()]. style == #complexFramed ifTrue:[^self computeFramedColors]. style == #complexAltFramed ifTrue:[^self computeAltFramedColors]. style == #complexRaised ifTrue:[^self computeRaisedColors]. style == #complexAltRaised ifTrue:[^self computeAltRaisedColors]. style == #complexInset ifTrue:[^self computeInsetColors]. style == #complexAltInset ifTrue:[^self computeAltInsetColors]. self error:'Unknown border style: ', style printString.! ! !ComplexBorder methodsFor: 'private' stamp: 'ar 8/25/2001 16:35'! computeFramedColors | base light dark w hw colorArray param | base := self color asColor. light := Color white. dark := Color black. w := self width isPoint ifTrue:[self width x max: self width y] ifFalse:[self width]. w := w asInteger. w = 1 ifTrue:[^{base mixed: 0.5 with: light. base mixed: 0.5 with: dark}]. colorArray := Array new: w. hw := w // 2. "brighten" 0 to: hw-1 do:[:i| param := 0.5 + (i asFloat / hw * 0.5). colorArray at: i+1 put: (base mixed: param with: light). "brighten" colorArray at: w-i put: (base mixed: param with: dark). "darken" ]. w odd ifTrue:[colorArray at: hw+1 put: base]. ^colorArray, colorArray! ! !ComplexBorder methodsFor: 'private' stamp: 'aoy 2/17/2003 01:06'! computeInsetColors | base light dark w colorArray param hw | base := self color asColor. light := Color white. dark := Color black. w := self width isPoint ifTrue: [self width x max: self width y] ifFalse: [self width]. w := w asInteger. colorArray := Array new: w * 2. hw := 0.5 / w. 0 to: w - 1 do: [:i | param := true ifTrue: [ 0.5 + (hw * i)] ifFalse: [0.5 + (hw * (w - i))]. colorArray at: i + 1 put: (base mixed: param with: dark). "darken" colorArray at: colorArray size - i put: (base mixed: param with: light) "brighten"]. ^colorArray! ! !ComplexBorder methodsFor: 'private' stamp: 'aoy 2/17/2003 01:07'! computeRaisedColors | base light dark w colorArray param hw | base := self color asColor. light := Color white. dark := Color black. w := self width isPoint ifTrue: [self width x max: self width y] ifFalse: [self width]. w := w asInteger. colorArray := Array new: w * 2. hw := 0.5 / w. 0 to: w - 1 do: [:i | param := true ifTrue: [0.5 + (hw * i)] ifFalse: [0.5 + (hw * (w - i))]. colorArray at: i + 1 put: (base mixed: param with: light). "brighten" colorArray at: colorArray size - i put: (base mixed: param with: dark) "darken"]. ^colorArray! ! !ComplexBorder methodsFor: 'private' stamp: 'ar 9/4/2001 19:51'! fillStyleForDirection: direction "Fill the given form describing the receiver's look at a particular direction" | index fill dir | index := direction degrees truncated // 10 + 1. lineStyles ifNotNil:[ fill := lineStyles at: index. fill ifNotNil:[^fill]. ]. dir := Point r: 1.0 degrees: index - 1 * 10 + 5. fill := GradientFillStyle colors: (self colorsForDirection: dir). fill direction: 0 @ width asPoint y; radial: false. fill origin: ((width asPoint x // 2) @ (width asPoint y // 2)) negated. fill pixelRamp: (fill computePixelRampOfSize: 16). fill isTranslucent. "precompute" lineStyles ifNil:[lineStyles := Array new: 37]. lineStyles at: index put: fill. ^fill! ! !ComplexBorder methodsFor: 'private' stamp: 'ar 8/26/2001 23:39'! intersectFrom: startPt with: startDir to: endPt with: endDir "Compute the intersection of two lines. Return nil if either * the intersection does not exist, or * the intersection is 'before' startPt, or * the intersection is 'after' endPt " | det deltaPt alpha beta | det := (startDir x * endDir y) - (startDir y * endDir x). det = 0.0 ifTrue:[^nil]. "There's no solution for it" deltaPt := endPt - startPt. alpha := (deltaPt x * endDir y) - (deltaPt y * endDir x). beta := (deltaPt x * startDir y) - (deltaPt y * startDir x). alpha := alpha / det. beta := beta / det. alpha < 0 ifTrue:[^nil]. beta > 1.0 ifTrue:[^nil]. "And compute intersection" ^(startPt x + (alpha * startDir x)) @ (startPt y + (alpha * startDir y))! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ComplexBorder class instanceVariableNames: ''! !ComplexBorder class methodsFor: 'instance creation' stamp: 'ar 8/25/2001 16:22'! style: aSymbol ^self new style: aSymbol! ! TestCase subclass: #ComplexTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Numbers'! !ComplexTest methodsFor: 'testing' stamp: 'nice 2/8/2006 22:09'! testEquality "self run: #testEquality" "self debug: #testEquality" self assert: 0i = 0. self assert: (2 - 5i) = ((1 -4 i) + (1 - 1i)). self assert: 0i isZero. self deny: (1 + 3 i) = 1. self deny: (1 + 3 i) = (1 + 2i). "Some more stuff" self deny: (1 i) = nil. self deny: nil = (1 i). self deny: (1 i) = #(1 2 3). self deny: #(1 2 3) = (1 i). self deny: (1 i) = 0. self deny: 0 = (1 i). self assert: (1 + 0 i) = 1. self assert: 1 = (1+ 0 i). self assert: (1 + 0 i) = 1.0. self assert: 1.0 = (1+ 0 i). self assert: (1/2 + 0 i) = (1/2). self assert: (1/2) = (1/2+ 0 i).! ! !ComplexTest methodsFor: 'testing - bugs' stamp: 'md 2/18/2006 16:53'! testBug1 self assert: (0.5 * (2+0i) ln) exp = (0.5 * 2 ln) exp.! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 14:00'! testAbs "self run: #testAbs" "self debug: #testAbs" | c | c := (6 - 6 i). self assert: c abs = 72 sqrt. ! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 13:59'! testAdding "self run: #testAdding" | c | c := (5 - 6 i) + (-5 + 8 i). "Complex with Complex" self assert: (c = (0 + 2 i)).! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 14:02'! testArg "self run: #testArg" "self debug: #testArg" | c | c := (0 + 5 i) . self assert: c arg = (Float pi/ 2). ! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 14:13'! testComplexCollection "self run: #testComplexCollection" "self debug: #testComplexCollection" | array array2 | array := Array with: 1 + 2i with: 3 + 4i with: 5 + 6i. array2 := 2 * array. array with: array2 do: [:one :two | self assert: (2 * one) = two ] ! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 14:16'! testConversion "self run: #testConversion" "self debug: #testConversion" self assert: ((1 + 2i) + 1) = (2 + 2 i). self assert: (1 + (1 + 2i)) = (2 + 2 i). self assert: ((1 + 2i) + 1.0) = (2.0 + 2 i). self assert: (1.0 + (1 + 2i)) = (2.0 + 2 i). self assert: ((1 + 2i) + (2/3)) = ((5/3) + 2 i ). self assert: ((2/3) + (1 + 2i)) = ((5/3) + 2 i )! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 13:59'! testCreation "self run: #testCreation" | c | c := 5 i. self assert: (c real = 0). self assert: (c imaginary = 5). c := 6 + 7 i. self assert: (c real = 6). self assert: ( c imaginary = 7). c := 5.6 - 8 i. self assert: (c real = 5.6). self assert: (c imaginary = -8). c := Complex real: 10 imaginary: 5. self assert: (c real = 10). self assert: (c imaginary = 5). c := Complex abs: 5 arg: (Float pi/2). self assert: (c real rounded = 0). self assert: (c imaginary = 5). ! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 6/5/2005 08:29'! testDivision1 "self run: #testDivision1" "self debug: #testDivision1" | c1 c2 quotient | c1 := 2.0e252 + 3.0e70 i. c2 := c1. quotient := c1 / c2. self deny: (quotient - 1) isZero. "This test fails due to the wonders of floating point arithmetic. Please have a look at Complex>>divideSecureBy: and #divideFastAndSecureBy: how this can be avoided." ! ! !ComplexTest methodsFor: 'tests' stamp: 'laza 9/26/2005 10:24'! testLn self assert: (Float e + 0 i) ln = Float e ln "See Bug 1815 on Mantis"! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 14:03'! testNegated "self run: #testNegated" "self debug: #testNegated" | c | c := (2 + 5 i) . self assert: c negated = (-2 - 5i). ! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 14:05'! testReciprocal "self run: #testReciprocal" "self debug: #testReciprocal" | c | c := (2 + 5 i). self assert: c reciprocal = ((2/29) - (5/29)i). ! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 14:07'! testReciprocalError "self run: #testReciprocalError" "self debug: #testReciprocalError" | c | c := (0 i). self should: [c reciprocal] raise: ZeroDivide ! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 6/5/2005 08:29'! testSecureDivision1 "self run: #testSecureDivision1" "self debug: #testSecureDivision1" | c1 c2 quotient | c1 := 2.0e252 + 3.0e70 i. c2 := c1. quotient := c1 divideSecureBy: c2. self assert: (quotient - 1) isZero. ! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 6/5/2005 08:29'! testSecureDivision2 "self run: #testSecureDivision2" "self debug: #testSecureDivision2" | c1 c2 quotient | c1 := 2.0e252 + 3.0e70 i. c2 := c1. quotient := c1 divideFastAndSecureBy: c2. self assert: (quotient - 1) isZero. ! ! !ComplexTest methodsFor: 'tests' stamp: 'sd 7/17/2004 13:24'! testSquared "self run: #testSquared" "self debug: #testSquared" | c c2 | c := (6 - 6 i). c2 := (c squared). self assert: c2 imaginary = -72. self assert: c2 real = 0.! ! MorphicModel subclass: #ComposableMorph uses: TEasilyThemed instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !ComposableMorph commentStamp: 'gvc 5/18/2007 13:32' prior: 0! Morph with an inset border by default and theme access.! !ComposableMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/30/2006 09:39'! defaultBorderColor "Answer the default border color/fill style for the receiver" ^#inset! ! !ComposableMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/30/2006 09:39'! defaultBorderWidth "Answer the default border width for the receiver." ^ 1! ! !ComposableMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/29/2006 18:25'! defaultTitle "Answer the default title label for the receiver." ^'Composite' translated! ! !ComposableMorph methodsFor: 'as yet unclassified' stamp: 'gvc 4/29/2008 15:41'! newWindow "Answer a new window with the receiver as model, except when the receiver is a morph (which can cause an infinte loop asking for #requestor, from Services)." |w| w := StandardWindow new model: (self isMorph ifFalse: [self]); title: self defaultTitle; addMorph: self fullFrame: (LayoutFrame fractions: (0@0 corner: 1@1)); yourself. self borderWidth: 0. ^w! ! !ComposableMorph methodsFor: 'controls'! newAlphaImage: aForm help: helpText "Answer an alpha image morph." ^self theme newAlphaImageIn: self image: aForm help: helpText! ! !ComposableMorph methodsFor: 'controls'! newAlphaSelector: aModel getAlpha: getSel setAlpha: setSel help: helpText "Answer an alpha channel selector with the given selectors." ^self theme newAlphaSelectorIn: self for: aModel getAlpha: getSel setAlpha: setSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newAutoAcceptTextEditorFor: aModel getText: getSel setText: setSel getEnabled: enabledSel "Answer a text editor for the given model." ^self theme newAutoAcceptTextEditorIn: self for: aModel getText: getSel setText: setSel getEnabled: enabledSel! ! !ComposableMorph methodsFor: 'controls'! newAutoAcceptTextEntryFor: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel font: aFont help: helpText "Answer a text entry for the given model." ^self theme newAutoAcceptTextEntryIn: self for: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel font: aFont help: helpText! ! !ComposableMorph methodsFor: 'controls'! newAutoAcceptTextEntryFor: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel help: helpText "Answer a text entry for the given model." ^self theme newAutoAcceptTextEntryIn: self for: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newAutoAcceptTextEntryFor: aModel getText: getSel setText: setSel getEnabled: enabledSel font: aFont help: helpText "Answer a text entry for the given model." ^self theme newAutoAcceptTextEntryIn: self for: aModel get: getSel set: setSel class: String getEnabled: enabledSel font: aFont help: helpText ! ! !ComposableMorph methodsFor: 'controls'! newAutoAcceptTextEntryFor: aModel getText: getSel setText: setSel getEnabled: enabledSel help: helpText "Answer a text entry for the given model." ^self theme newAutoAcceptTextEntryIn: self for: aModel get: getSel set: setSel class: String getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newBalloonHelp: aTextStringOrMorph for: aMorph "Answer a new balloon help with the given contents for aMorph at a given corner." ^self theme newBalloonHelpIn: self contents: aTextStringOrMorph for: aMorph corner: #bottomLeft! ! !ComposableMorph methodsFor: 'controls'! newBalloonHelp: aTextStringOrMorph for: aMorph corner: cornerSymbol "Answer a new balloon help with the given contents for aMorph at a given corner." ^self theme newBalloonHelpIn: self contents: aTextStringOrMorph for: aMorph corner: cornerSymbol! ! !ComposableMorph methodsFor: 'controls'! newBracketSliderFor: aModel getValue: getSel setValue: setSel min: minValue max: maxValue quantum: quantum getEnabled: enabledSel help: helpText "Answer a bracket slider with the given selectors." ^self theme newBracketSliderIn: self for: aModel getValue: getSel setValue: setSel min: minValue max: maxValue quantum: quantum getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newBracketSliderFor: aModel getValue: getSel setValue: setSel min: minValue max: maxValue quantum: quantum help: helpText "Answer a bracket slider with the given selectors." ^self newBracketSliderFor: aModel getValue: getSel setValue: setSel min: minValue max: maxValue quantum: quantum getEnabled: nil help: helpText! ! !ComposableMorph methodsFor: 'controls'! newButtonFor: aModel action: actionSel getEnabled: enabledSel label: stringOrText help: helpText "Answer a new button." ^self newButtonFor: aModel getState: nil action: actionSel arguments: nil getEnabled: enabledSel label: stringOrText help: helpText! ! !ComposableMorph methodsFor: 'controls'! newButtonFor: aModel action: actionSel label: stringOrText help: helpText "Answer a new button." ^self newButtonFor: aModel getState: nil action: actionSel arguments: nil getEnabled: nil label: stringOrText help: helpText! ! !ComposableMorph methodsFor: 'controls'! newButtonFor: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel getLabel: labelSel help: helpText "Answer a new button." ^self theme newButtonIn: self for: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel getLabel: labelSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newButtonFor: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel label: stringOrText help: helpText "Answer a new button." ^self theme newButtonIn: self for: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel label: stringOrText help: helpText! ! !ComposableMorph methodsFor: 'controls'! newButtonFor: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel labelForm: aForm help: helpText "Answer a new button." ^self theme newButtonIn: self for: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel label: (AlphaImageMorph new image: aForm) help: helpText! ! !ComposableMorph methodsFor: 'controls'! newCancelButton "Answer a new cancel button." ^self newCancelButtonFor: self! ! !ComposableMorph methodsFor: 'controls'! newCancelButtonFor: aModel "Answer a new cancel button." ^self theme newCancelButtonIn: self for: aModel! ! !ComposableMorph methodsFor: 'controls'! newCheckboxFor: aModel getSelected: getSel setSelected: setSel getEnabled: enabledSel label: stringOrText help: helpText "Answer a checkbox with the given label." ^self theme newCheckboxIn: self for: aModel getSelected: getSel setSelected: setSel getEnabled: enabledSel label: stringOrText help: helpText! ! !ComposableMorph methodsFor: 'controls'! newCheckboxFor: aModel getSelected: getSel setSelected: setSel label: stringOrText help: helpText "Answer a checkbox with the given label." ^self theme newCheckboxIn: self for: aModel getSelected: getSel setSelected: setSel getEnabled: nil label: stringOrText help: helpText! ! !ComposableMorph methodsFor: 'controls'! newCloseButton "Answer a new close button." ^self newCloseButtonFor: self ! ! !ComposableMorph methodsFor: 'controls'! newCloseButtonFor: aModel "Answer a new close button." ^self theme newCloseButtonIn: self for: aModel! ! !ComposableMorph methodsFor: 'controls'! newColorChooserFor: aModel getColor: getSel setColor: setSel getEnabled: enabledSel help: helpText "Answer a color chooser with the given selectors." ^self theme newColorChooserIn: self for: aModel getColor: getSel setColor: setSel getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newColorChooserFor: aModel getColor: getSel setColor: setSel help: helpText "Answer a color chooser with the given selectors." ^self theme newColorChooserIn: self for: aModel getColor: getSel setColor: setSel getEnabled: nil help: helpText! ! !ComposableMorph methodsFor: 'controls'! newColorPickerFor: target getter: getterSymbol setter: setterSymbol "Answer a new color picker for the given morph and accessors." ^self theme newColorPickerIn: self for: target getter: getterSymbol setter: setterSymbol! ! !ComposableMorph methodsFor: 'controls'! newColorPresenterFor: aModel getColor: getSel help: helpText "Answer a color presenter with the given selectors." ^self theme newColorPresenterIn: self for: aModel getColor: getSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newColumn: controls "Answer a morph laid out with a column of controls." ^self theme newColumnIn: self for: controls! ! !ComposableMorph methodsFor: 'controls'! newDialogPanel "Answer a new main dialog panel." ^self theme newDialogPanelIn: self! ! !ComposableMorph methodsFor: 'controls'! newDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel help: helpText "Answer a drop list for the given model." ^self theme newDropListIn: self for: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: true help: helpText! ! !ComposableMorph methodsFor: 'controls'! newDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: useIndex help: helpText "Answer a drop list for the given model." ^self theme newDropListIn: self for: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: useIndex help: helpText! ! !ComposableMorph methodsFor: 'controls'! newDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel help: helpText "Answer a drop list for the given model." ^self newDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: nil useIndex: true help: helpText! ! !ComposableMorph methodsFor: 'controls'! newEmbeddedMenu "Answer a new menu." ^self theme newEmbeddedMenuIn: self for: self! ! !ComposableMorph methodsFor: 'controls'! newExpander: aString "Answer an expander with the given label." ^self theme newExpanderIn: self label: aString forAll: #()! ! !ComposableMorph methodsFor: 'controls'! newExpander: aString for: aControl "Answer an expander with the given label and control." ^self theme newExpanderIn: self label: aString forAll: {aControl}! ! !ComposableMorph methodsFor: 'controls'! newExpander: aString forAll: controls "Answer an expander with the given label and controls." ^self theme newExpanderIn: self label: aString forAll: controls! ! !ComposableMorph methodsFor: 'controls'! newFuzzyLabel: aString "Answer a new fuzzy label." ^self theme newFuzzyLabelIn: self for: nil label: aString offset: 1 alpha: 0.5 getEnabled: nil! ! !ComposableMorph methodsFor: 'controls'! newFuzzyLabelFor: aModel label: aString getEnabled: enabledSel "Answer a new fuzzy label." ^self theme newFuzzyLabelIn: self for: aModel label: aString offset: 1 alpha: 0.5 getEnabled: enabledSel! ! !ComposableMorph methodsFor: 'controls'! newFuzzyLabelFor: aModel label: aString offset: offset alpha: alpha getEnabled: enabledSel "Answer a new fuzzy label." ^self theme newFuzzyLabelIn: self for: aModel label: aString offset: offset alpha: alpha getEnabled: enabledSel! ! !ComposableMorph methodsFor: 'controls'! newGroupbox "Answer a plain groupbox." ^self theme newGroupboxIn: self! ! !ComposableMorph methodsFor: 'controls'! newGroupbox: aString "Answer a groupbox with the given label." ^self theme newGroupboxIn: self label: aString! ! !ComposableMorph methodsFor: 'controls'! newGroupbox: aString for: control "Answer a groupbox with the given label and control." ^self theme newGroupboxIn: self label: aString for: control! ! !ComposableMorph methodsFor: 'controls'! newGroupbox: aString forAll: controls "Answer a groupbox with the given label and controls." ^self theme newGroupboxIn: self label: aString forAll: controls! ! !ComposableMorph methodsFor: 'controls'! newGroupboxFor: control "Answer a plain groupbox with the given control." ^self theme newGroupboxIn: self for: control! ! !ComposableMorph methodsFor: 'controls'! newGroupboxForAll: controls "Answer a plain groupbox with the given controls." ^self theme newGroupboxIn: self forAll: controls! ! !ComposableMorph methodsFor: 'controls'! newHSVASelector: aColor help: helpText "Answer a hue-saturation-volume selector with the given color." ^self theme newHSVASelectorIn: self color: aColor help: helpText! ! !ComposableMorph methodsFor: 'controls'! newHSVSelector: aColor help: helpText "Answer a hue-saturation-volume selector with the given color." ^self theme newHSVSelectorIn: self color: aColor help: helpText! ! !ComposableMorph methodsFor: 'controls'! newHueSelector: aModel getHue: getSel setHue: setSel help: helpText "Answer a hue selector with the given selectors." ^self theme newHueSelectorIn: self for: aModel getHue: getSel setHue: setSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newImage: aForm "Answer a new image." ^self theme newImageIn: self form: aForm! ! !ComposableMorph methodsFor: 'controls'! newImage: aForm size: aPoint "Answer a new image." ^self theme newImageIn: self form: aForm size: aPoint! ! !ComposableMorph methodsFor: 'controls'! newIncrementalSliderFor: aModel getValue: getSel setValue: setSel min: min max: max quantum: quantum getEnabled: enabledSel help: helpText "Answer an inremental slider with the given selectors." ^self theme newIncrementalSliderIn: self for: aModel getValue: getSel setValue: setSel min: min max: max quantum: quantum getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newLabel: aString "Answer a new text label." ^self newLabelFor: nil label: aString getEnabled: nil! ! !ComposableMorph methodsFor: 'controls'! newLabelFor: aModel label: aString getEnabled: enabledSel "Answer a new text label." ^self theme newLabelIn: self for: aModel label: aString getEnabled: enabledSel! ! !ComposableMorph methodsFor: 'controls'! newLabelGroup: labelsAndControls "Answer a morph laid out with a column of labels and a column of associated controls." ^self theme newLabelGroupIn: self for: labelsAndControls spaceFill: false! ! !ComposableMorph methodsFor: 'controls'! newLabelGroup: labelsAndControls font: aFont labelColor: aColor "Answer a morph laid out with a column of labels and a column of associated controls." ^self theme newLabelGroupIn: self for: labelsAndControls spaceFill: false font: aFont labelColor: aColor ! ! !ComposableMorph methodsFor: 'controls'! newLabelGroupSpread: labelsAndControls "Answer a morph laid out with a column of labels and a column of associated controls." ^self theme newLabelGroupIn: self for: labelsAndControls spaceFill: true! ! !ComposableMorph methodsFor: 'controls'! newListFor: aModel list: listSelector selected: getSelector changeSelected: setSelector getEnabled: enabledSel help: helpText "Answer a list for the given model." ^self theme newListIn: self for: aModel list: listSelector selected: getSelector changeSelected: setSelector getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newListFor: aModel list: listSelector selected: getSelector changeSelected: setSelector help: helpText "Answer a list for the given model." ^self newListFor: aModel list: listSelector selected: getSelector changeSelected: setSelector getEnabled: nil help: helpText! ! !ComposableMorph methodsFor: 'controls'! newMenu "Answer a new menu." ^self theme newMenuIn: self for: self! ! !ComposableMorph methodsFor: 'controls'! newMenuFor: aModel "Answer a new menu." ^self theme newMenuIn: self for: aModel! ! !ComposableMorph methodsFor: 'controls'! newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel help: helpText "Answer a morph drop list for the given model." ^self newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: true help: helpText! ! !ComposableMorph methodsFor: 'controls'! newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: useIndex help: helpText "Answer a morph drop list for the given model." ^self theme newMorphDropListIn: self for: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: useIndex help: helpText! ! !ComposableMorph methodsFor: 'controls'! newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel help: helpText "Answer a morph drop list for the given model." ^self newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: nil useIndex: true help: helpText! ! !ComposableMorph methodsFor: 'controls'! newMorphListFor: aModel list: listSelector getSelected: getSelector setSelected: setSelector getEnabled: enabledSel help: helpText "Answer a morph list for the given model." ^self theme newMorphListIn: self for: aModel list: listSelector getSelected: getSelector setSelected: setSelector getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newMorphListFor: aModel list: listSelector getSelected: getSelector setSelected: setSelector help: helpText "Answer a morph list for the given model." ^self newMorphListFor: aModel list: listSelector getSelected: getSelector setSelected: setSelector getEnabled: nil help: helpText! ! !ComposableMorph methodsFor: 'controls'! newNoButton "Answer a new No button." ^self newNoButtonFor: self! ! !ComposableMorph methodsFor: 'controls'! newNoButtonFor: aModel "Answer a new No button." ^self theme newNoButtonIn: self for: aModel! ! !ComposableMorph methodsFor: 'controls'! newOKButton "Answer a new OK button." ^self newOKButtonFor: self! ! !ComposableMorph methodsFor: 'controls'! newOKButtonFor: aModel "Answer a new OK button." ^self newOKButtonFor: aModel getEnabled: nil! ! !ComposableMorph methodsFor: 'controls'! newOKButtonFor: aModel getEnabled: enabledSel "Answer a new OK button." ^self theme newOKButtonIn: self for: aModel getEnabled: enabledSel! ! !ComposableMorph methodsFor: 'controls'! newPanel "Answer a new panel." ^self theme newPanelIn: self! ! !ComposableMorph methodsFor: 'controls'! newPluggableDialogWindow "Answer a new pluggable dialog." ^self newPluggableDialogWindow: 'Dialog'! ! !ComposableMorph methodsFor: 'controls'! newPluggableDialogWindow: title "Answer a new pluggable dialog with the given content." ^self newPluggableDialogWindow: title for: nil! ! !ComposableMorph methodsFor: 'controls'! newPluggableDialogWindow: title for: contentMorph "Answer a new pluggable dialog with the given content." ^self theme newPluggableDialogWindowIn: self title: title for: contentMorph! ! !ComposableMorph methodsFor: 'controls'! newRadioButtonFor: aModel getSelected: getSel setSelected: setSel getEnabled: enabledSel label: stringOrText help: helpText "Answer a checkbox (radio button appearance) with the given label." ^self theme newRadioButtonIn: self for: aModel getSelected: getSel setSelected: setSel getEnabled: enabledSel label: stringOrText help: helpText! ! !ComposableMorph methodsFor: 'controls'! newRadioButtonFor: aModel getSelected: getSel setSelected: setSel label: stringOrText help: helpText "Answer a checkbox (radio button appearance) with the given label." ^self newRadioButtonFor: aModel getSelected: getSel setSelected: setSel getEnabled: nil label: stringOrText help: helpText! ! !ComposableMorph methodsFor: 'controls'! newRow "Answer a morph laid out as a row." ^self theme newRowIn: self for: #()! ! !ComposableMorph methodsFor: 'controls'! newRow: controls "Answer a morph laid out with a row of controls." ^self theme newRowIn: self for: controls! ! !ComposableMorph methodsFor: 'controls'! newSVSelector: aColor help: helpText "Answer a saturation-volume selector with the given color." ^self theme newSVSelectorIn: self color: aColor help: helpText! ! !ComposableMorph methodsFor: 'controls'! newSeparator "Answer an horizontal separator." ^self theme newSeparatorIn: self! ! !ComposableMorph methodsFor: 'controls'! newSliderFor: aModel getValue: getSel setValue: setSel getEnabled: enabledSel help: helpText "Answer a slider with the given selectors." ^self theme newSliderIn: self for: aModel getValue: getSel setValue: setSel min: 0 max: 1 quantum: nil getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newSliderFor: aModel getValue: getSel setValue: setSel help: helpText "Answer a slider with the given selectors." ^self theme newSliderIn: self for: aModel getValue: getSel setValue: setSel min: 0 max: 1 quantum: nil getEnabled: nil help: helpText! ! !ComposableMorph methodsFor: 'controls'! newSliderFor: aModel getValue: getSel setValue: setSel min: min max: max quantum: quantum getEnabled: enabledSel help: helpText "Answer a slider with the given selectors." ^self theme newSliderIn: self for: aModel getValue: getSel setValue: setSel min: min max: max quantum: quantum getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newString: aStringOrText "Answer a new embossed string." ^self theme newStringIn: self label: aStringOrText font: self theme labelFont style: #plain! ! !ComposableMorph methodsFor: 'controls'! newString: aStringOrText font: aFont style: aStyle "Answer a new embossed string." ^self theme newStringIn: self label: aStringOrText font: aFont style: aStyle! ! !ComposableMorph methodsFor: 'controls'! newString: aStringOrText style: aStyle "Answer a new embossed string." ^self theme newStringIn: self label: aStringOrText font: self theme labelFont style: aStyle! ! !ComposableMorph methodsFor: 'controls'! newTabGroup: labelsAndPages "Answer a tab group with the given tab labels associated with pages." ^self theme newTabGroupIn: self for: labelsAndPages! ! !ComposableMorph methodsFor: 'controls'! newText: aStringOrText "Answer a new text." ^self theme newTextIn: self text: aStringOrText! ! !ComposableMorph methodsFor: 'controls'! newTextEditorFor: aModel getText: getSel setText: setSel "Answer a text editor for the given model." ^self newTextEditorFor: aModel getText: getSel setText: setSel getEnabled: nil! ! !ComposableMorph methodsFor: 'controls'! newTextEditorFor: aModel getText: getSel setText: setSel getEnabled: enabledSel "Answer a text editor for the given model." ^self theme newTextEditorIn: self for: aModel getText: getSel setText: setSel getEnabled: enabledSel ! ! !ComposableMorph methodsFor: 'controls'! newTextEntryFor: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel help: helpText "Answer a text entry for the given model." ^self theme newTextEntryIn: self for: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newTextEntryFor: aModel getText: getSel setText: setSel getEnabled: enabledSel help: helpText "Answer a text entry for the given model." ^self theme newTextEntryIn: self for: aModel get: getSel set: setSel class: String getEnabled: enabledSel help: helpText! ! !ComposableMorph methodsFor: 'controls'! newTextEntryFor: aModel getText: getSel setText: setSel help: helpText "Answer a text entry for the given model." ^self newTextEntryFor: aModel get: getSel set: setSel class: String getEnabled: nil help: helpText! ! !ComposableMorph methodsFor: 'controls'! newTitle: aString for: control "Answer a morph laid out with a column with a title." ^self theme newTitleIn: self label: aString for: control! ! !ComposableMorph methodsFor: 'controls'! newToolDockingBar "Answer a tool docking bar." ^self theme newToolDockingBarIn: self! ! !ComposableMorph methodsFor: 'controls'! newToolSpacer "Answer a tool spacer." ^self theme newToolSpacerIn: self! ! !ComposableMorph methodsFor: 'controls'! newToolbar "Answer a toolbar." ^self theme newToolbarIn: self! ! !ComposableMorph methodsFor: 'controls'! newToolbar: controls "Answer a toolbar with the given controls." ^self theme newToolbarIn: self for: controls! ! !ComposableMorph methodsFor: 'controls'! newToolbarHandle "Answer a toolbar handle." ^self theme newToolbarHandleIn: self! ! !ComposableMorph methodsFor: 'controls'! newTreeFor: aModel list: listSelector selected: getSelector changeSelected: setSelector "Answer a new tree morph." ^self theme newTreeIn: self for: aModel list: listSelector selected: getSelector changeSelected: setSelector! ! !ComposableMorph methodsFor: 'controls'! newVerticalSeparator "Answer a vertical separator." ^self theme newVerticalSeparatorIn: self! ! !ComposableMorph methodsFor: 'controls'! newYesButton "Answer a new Yes button." ^self newYesButtonFor: self! ! !ComposableMorph methodsFor: 'controls'! newYesButtonFor: aModel "Answer a new yes button." ^self theme newYesButtonIn: self for: aModel! ! !ComposableMorph methodsFor: 'services'! abort: aStringOrText "Open an error dialog." ^self abort: aStringOrText title: 'Error' translated! ! !ComposableMorph methodsFor: 'services'! abort: aStringOrText title: aString "Open an error dialog." ^self theme abortIn: self text: aStringOrText title: aString! ! !ComposableMorph methodsFor: 'services'! alert: aStringOrText "Open an alert dialog." ^self alert: aStringOrText title: 'Alert' translated! ! !ComposableMorph methodsFor: 'services'! alert: aStringOrText title: aString "Open an alert dialog." ^self alert: aStringOrText title: aString configure: [:d | ]! ! !ComposableMorph methodsFor: 'services'! alert: aStringOrText title: aString configure: aBlock "Open an alert dialog. Configure the dialog with the 1 argument block before opening modally." ^self theme alertIn: self text: aStringOrText title: aString configure: aBlock! ! !ComposableMorph methodsFor: 'services'! chooseColor "Answer the result of a color selector dialog ." ^self chooseColor: Color black! ! !ComposableMorph methodsFor: 'services'! chooseColor: aColor "Answer the result of a color selector dialog with the given color." ^self theme chooseColorIn: self title: 'Colour Selector' translated color: aColor! ! !ComposableMorph methodsFor: 'services'! chooseColor: aColor title: title "Answer the result of a color selector dialog with the given title and initial colour." ^self theme chooseColorIn: self title: title color: aColor! ! !ComposableMorph methodsFor: 'services'! chooseDirectory: title "Answer the result of a file dialog with the given title, answer a directory." ^self chooseDirectory: title path: nil! ! !ComposableMorph methodsFor: 'services'! chooseDirectory: title path: path "Answer the result of a file dialog with the given title, answer a directory." ^self theme chooseDirectoryIn: self title: title path: path! ! !ComposableMorph methodsFor: 'services'! chooseDropList: aStringOrText list: aList "Open a drop list chooser dialog." ^self chooseDropList: aStringOrText title: 'Choose' translated list: aList! ! !ComposableMorph methodsFor: 'services'! chooseDropList: aStringOrText title: aString list: aList "Open a drop list chooser dialog." ^self theme chooseDropListIn: self text: aStringOrText title: aString list: aList! ! !ComposableMorph methodsFor: 'services'! chooseFileName: title extensions: exts path: path preview: preview "Answer the result of a file name chooser dialog with the given title, extensions to show, path and preview type." ^self theme chooseFileNameIn: self title: title extensions: exts path: path preview: preview! ! !ComposableMorph methodsFor: 'services'! chooseFont "Answer the result of a font selector dialog." ^self chooseFont: nil! ! !ComposableMorph methodsFor: 'services'! chooseFont: aFont "Answer the result of a font selector dialog with the given initial font." ^self theme chooseFontIn: self title: 'Font Selector' translated font: aFont! ! !ComposableMorph methodsFor: 'services'! deny: aStringOrText "Open a denial dialog." ^self deny: aStringOrText title: 'Access Denied' translated! ! !ComposableMorph methodsFor: 'services'! deny: aStringOrText title: aString "Open a denial dialog." ^self theme denyIn: self text: aStringOrText title: aString! ! !ComposableMorph methodsFor: 'services'! fileOpen: title "Answer the result of a file open dialog with the given title." ^self fileOpen: title extensions: nil! ! !ComposableMorph methodsFor: 'services'! fileOpen: title extensions: exts "Answer the result of a file open dialog with the given title and extensions to show." ^self fileOpen: title extensions: exts path: nil! ! !ComposableMorph methodsFor: 'services'! fileOpen: title extensions: exts path: path "Answer the result of a file open dialog with the given title, extensions to show and path." ^self fileOpen: title extensions: exts path: path preview: nil! ! !ComposableMorph methodsFor: 'services'! fileOpen: title extensions: exts path: path preview: preview "Answer the result of a file open dialog with the given title, extensions to show, path and preview type." ^self theme fileOpenIn: self title: title extensions: exts path: path preview: preview! ! !ComposableMorph methodsFor: 'services'! fileSave: title "Answer the result of a file save dialog with the given title." ^self fileSave: title extensions: nil path: nil! ! !ComposableMorph methodsFor: 'services'! fileSave: title extensions: exts "Answer the result of a file save dialog with the given title." ^self fileSave: title extensions: exts path: nil! ! !ComposableMorph methodsFor: 'services'! fileSave: title extensions: exts path: path "Answer the result of a file save dialog with the given title, extensions to show and path." ^self theme fileSaveIn: self title: title extensions: exts path: path! ! !ComposableMorph methodsFor: 'services'! fileSave: title path: path "Answer the result of a file save open dialog with the given title." ^self fileSave: title extensions: nil path: path! ! !ComposableMorph methodsFor: 'services'! longMessage: aStringOrText title: aString "Open a (long) message dialog." ^self theme longMessageIn: self text: aStringOrText title: aString! ! !ComposableMorph methodsFor: 'services'! message: aStringOrText "Open a message dialog." ^self message: aStringOrText title: 'Information' translated! ! !ComposableMorph methodsFor: 'services'! message: aStringOrText title: aString "Open a message dialog." ^self theme messageIn: self text: aStringOrText title: aString! ! !ComposableMorph methodsFor: 'services'! proceed: aStringOrText "Open a proceed dialog." ^self proceed: aStringOrText title: 'Proceed' translated! ! !ComposableMorph methodsFor: 'services'! proceed: aStringOrText title: aString "Open a proceed dialog and answer true if not cancelled, false otherwise." ^self theme proceedIn: self text: aStringOrText title: aString! ! !ComposableMorph methodsFor: 'services'! question: aStringOrText "Open a question dialog." ^self question: aStringOrText title: 'Question' translated! ! !ComposableMorph methodsFor: 'services'! question: aStringOrText title: aString "Open a question dialog and answer true if yes, false if no and nil if cancelled." ^self theme questionIn: self text: aStringOrText title: aString! ! !ComposableMorph methodsFor: 'services'! questionWithoutCancel: aStringOrText "Open a question dialog." ^self questionWithoutCancel: aStringOrText title: 'Question' translated! ! !ComposableMorph methodsFor: 'services'! questionWithoutCancel: aStringOrText title: aString "Open a question dialog and answer true if yes, false if no and nil if cancelled." ^self theme questionWithoutCancelIn: self text: aStringOrText title: aString! ! !ComposableMorph methodsFor: 'services'! textEntry: aStringOrText "Open a text entry dialog." ^self textEntry: aStringOrText title: 'Entry' translated! ! !ComposableMorph methodsFor: 'services'! textEntry: aStringOrText title: aString "Open a text entry dialog." ^self textEntry: aStringOrText title: aString entryText: ''! ! !ComposableMorph methodsFor: 'services'! textEntry: aStringOrText title: aString entryText: defaultEntryText "Open a text entry dialog." ^self theme textEntryIn: self text: aStringOrText title: aString entryText: defaultEntryText! ! !ComposableMorph methodsFor: 'theme'! theme "Answer the ui theme that provides controls." ^UITheme current! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ComposableMorph class uses: TEasilyThemed classTrait instanceVariableNames: ''! SimpleBorder subclass: #CompositeBorder instanceVariableNames: 'borders' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Borders'! !CompositeBorder commentStamp: 'gvc 5/18/2007 13:28' prior: 0! Border supporting multiple "sub-borders".! !CompositeBorder methodsFor: 'accessing' stamp: 'gvc 3/12/2007 11:15'! borders "Answer the value of borders" ^ borders! ! !CompositeBorder methodsFor: 'accessing' stamp: 'gvc 3/12/2007 11:15'! borders: anObject "Set the value of borders" borders := anObject! ! !CompositeBorder methodsFor: 'as yet unclassified' stamp: 'gvc 3/29/2007 17:32'! = aBorderStyle "Check the sub-borders too" ^super = aBorderStyle and: [ self borders = aBorderStyle borders]! ! !CompositeBorder methodsFor: 'as yet unclassified' stamp: 'gvc 3/12/2007 12:13'! colorsAtCorners "Return the colors of the first border." ^self borders first colorsAtCorners! ! !CompositeBorder methodsFor: 'as yet unclassified' stamp: 'gvc 3/14/2007 10:47'! frameRectangle: aRectangle on: aCanvas "Draw each border in turn." |r| r := aRectangle. self borders do: [:b | b frameRectangle: r on: aCanvas. r := r insetBy: b width]! ! !CompositeBorder methodsFor: 'as yet unclassified' stamp: 'gvc 5/18/2007 13:29'! hash "Since #= is overridden." ^super hash bitXor: self borders hash! ! !CompositeBorder methodsFor: 'as yet unclassified' stamp: 'gvc 3/14/2007 10:32'! isComposite "Answer true." ^true! ! FillStyle subclass: #CompositeFillStyle instanceVariableNames: 'fillStyles' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-FillStyles'! !CompositeFillStyle commentStamp: 'gvc 9/23/2008 12:05' prior: 0! Fillstyle supporting compositing of multiple sub-fillstyles.! !CompositeFillStyle methodsFor: 'accessing' stamp: 'gvc 3/20/2008 23:05'! fillStyles "Answer the value of fillStyles. The first item in the collection is considered to be topmost when rendered." ^ fillStyles! ! !CompositeFillStyle methodsFor: 'accessing' stamp: 'gvc 3/21/2008 16:24'! fillStyles: aCollection "Set the value of fillStyles. The first item in the collection is considered to be topmost when rendering." fillStyles := aCollection! ! !CompositeFillStyle methodsFor: 'accessing' stamp: 'gvc 3/20/2008 23:02'! initialize "Initialize the receiver." super initialize. self fillStyles: OrderedCollection new! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 3/21/2008 17:25'! addFillStyleMenuItems: aMenu hand: aHand from: aMorph "Add the items for changing the current fill style of the receiver" aMenu add: 'change origin' translated target: self selector: #changeOriginIn:event: argument: aMorph. aMenu add: 'change orientation' translated target: self selector: #changeOrientationIn:event: argument: aMorph.! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 21:02'! asColor "Answer a colour that is a best match to the receiver. Simple approach for the moment." ^self fillStyles ifEmpty: [Color transparent] ifNotEmpty: [self fillStyles last asColor]! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 3/21/2008 17:25'! changeOrientationIn: aMorph event: evt "Interactively change the origin of the receiver" | handle | handle := HandleMorph new forEachPointDo:[:pt| self direction: pt - self origin. self normal: nil. aMorph changed]. evt hand attachMorph: handle. handle startStepping.! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 3/21/2008 17:25'! changeOriginIn: aMorph event: evt "Interactively change the origin of the receiver" | handle | handle := HandleMorph new forEachPointDo:[:pt| self origin: pt. aMorph changed]. evt hand attachMorph: handle. handle startStepping.! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 21:01'! direction "Answer an effective direction of any oriented fill styles. Answer the bottom-right maxima." |dir| dir := nil. self fillStyles reverseDo: [:fs | fs isOrientedFill ifTrue: [ dir := dir ifNil: [fs direction] ifNotNil: [dir max: fs direction]]]. ^dir ifNil: [0@0] "just in case"! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 21:01'! direction: aPoint "Change the effective direction of any oriented fill styles." |delta| delta := aPoint - self direction. self fillStyles reverseDo: [:fs | fs isOrientedFill ifTrue: [ fs direction: fs direction + delta]]! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 20:32'! fillRectangle: aRectangle on: aCanvas "Fill the given rectangle on the given canvas with the receiver. Render from bottom to top." self fillStyles do: [:fs | fs fillRectangle: aRectangle on: aCanvas]! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 3/20/2008 23:04'! isCompositeFill "Answer whether the receiver is a composite fill. True for kinds of the receiver's class." ^true! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 20:37'! isGradientFill "Answer whether any of the composited fill styles are gradients." self fillStyles reverseDo: [:fs | fs isGradientFill ifTrue: [^true]]. ^false! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 20:38'! isOrientedFill "Answer whether any of the composited fill styles are oriented." self fillStyles reverseDo: [:fs | fs isOrientedFill ifTrue: [^true]]. ^false! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 3/20/2008 23:07'! isTranslucent "Answer whether all of the composited fill styles are transparent." ^self fillStyles allSatisfy: [:fs | fs isTranslucent]! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 3/20/2008 23:07'! isTransparent "Answer whether all of the composited fill styles are transparent." ^self fillStyles allSatisfy: [:fs | fs isTransparent]! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 21:00'! normal "Answer an effective normal of any oriented fill styles. Answer the top-left minima (probably not an accurate assumption)." |normal| normal := nil. self fillStyles reverseDo: [:fs | fs isOrientedFill ifTrue: [ normal := normal ifNil: [fs normal] ifNotNil: [normal min: fs normal]]]. ^normal ifNil: [0@0] "just in case"! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 21:01'! normal: aPoint "Change the effective normal of any oriented fill styles." |delta| aPoint ifNil: [ self fillStyles reverseDo: [:fs | fs isOrientedFill ifTrue: [ fs normal: nil]]. ^self]. delta := aPoint - self normal. self fillStyles reverseDo: [:fs | fs isOrientedFill ifTrue: [ fs normal: fs normal + delta]]! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 21:01'! origin "Answer an effective origin of any oriented fill styles. Answer the top-left minima." |origin| origin := nil. self fillStyles reverseDo: [:fs | fs isOrientedFill ifTrue: [ origin := origin ifNil: [fs origin] ifNotNil: [origin min: fs origin]]]. ^origin ifNil: [0@0] "just in case"! ! !CompositeFillStyle methodsFor: 'as yet unclassified' stamp: 'gvc 5/27/2008 21:01'! origin: aPoint "Change the effective origin of any oriented fill styles." |delta| delta := aPoint - self origin. self fillStyles reverseDo: [:fs | fs isOrientedFill ifTrue: [ fs origin: fs origin + delta]] ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CompositeFillStyle class instanceVariableNames: ''! !CompositeFillStyle class methodsFor: 'as yet unclassified' stamp: 'gvc 3/21/2008 16:49'! fillStyles: aCollection "Answer a new instance of the receiver with the specfied fill styles." ^self new fillStyles: aCollection! ! WidgetStub subclass: #CompositeStub instanceVariableNames: 'children' classVariableNames: '' poolDictionaries: '' category: 'ToolBuilder-SUnit'! !CompositeStub methodsFor: 'accessing' stamp: 'cwp 4/25/2005 03:50'! children ^children! ! !CompositeStub methodsFor: 'accessing' stamp: 'cwp 4/25/2005 03:50'! children: anObject children := anObject! ! !CompositeStub methodsFor: 'accessing' stamp: 'cwp 4/25/2005 03:51'! eventAccessors ^ #(children)! ! !CompositeStub methodsFor: 'accessing' stamp: 'marcus.denker 11/10/2008 10:04'! widgetNamed: aString self name = aString ifTrue: [^ self] ifFalse: [children do: [:ea | (ea widgetNamed: aString) ifNotNil: [:w | ^ w]]]. ^ nil! ! DisplayTransform subclass: #CompositeTransform instanceVariableNames: 'globalTransform localTransform' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Transformations'! !CompositeTransform commentStamp: '' prior: 0! A composite transform provides the effect of several levels of coordinate transformations.! !CompositeTransform methodsFor: 'accessing' stamp: 'di 10/26/1999 17:06'! angle ^ localTransform angle + globalTransform angle! ! !CompositeTransform methodsFor: 'accessing' stamp: 'ar 11/2/1998 19:45'! inverseTransformation "Return the inverse transformation of the receiver" ^self species new globalTransform: localTransform inverseTransformation localTransform: globalTransform inverseTransformation! ! !CompositeTransform methodsFor: 'accessing' stamp: 'di 10/26/1999 15:40'! offset ^ (self localPointToGlobal: 0@0) negated! ! !CompositeTransform methodsFor: 'accessing' stamp: 'di 10/26/1999 15:39'! scale ^ localTransform scale * globalTransform scale! ! !CompositeTransform methodsFor: 'converting' stamp: 'ar 11/2/1998 20:00'! asCompositeTransform ^self! ! !CompositeTransform methodsFor: 'converting' stamp: 'ar 11/2/1998 19:56'! asMatrixTransform2x3 ^globalTransform asMatrixTransform2x3 composedWithLocal: localTransform asMatrixTransform2x3! ! !CompositeTransform methodsFor: 'converting' stamp: 'di 10/26/1999 17:03'! asMorphicTransform "Squash a composite transform down to a simple one" ^ MorphicTransform offset: self offset angle: self angle scale: self scale! ! !CompositeTransform methodsFor: 'initialization' stamp: 'di 10/26/1999 17:08'! composedWith: aTransform "Return a new transform that has the effect of transforming points first by the receiver and then by the argument." self isIdentity ifTrue: [^ aTransform]. aTransform isIdentity ifTrue: [^ self]. ^ CompositeTransform new globalTransform: self localTransform: aTransform! ! !CompositeTransform methodsFor: 'initialization' stamp: 'lr 7/4/2009 10:42'! globalTransform: gt localTransform: lt globalTransform := gt. localTransform := lt! ! !CompositeTransform methodsFor: 'testing' stamp: 'ar 11/2/1998 20:00'! isCompositeTransform ^true! ! !CompositeTransform methodsFor: 'testing' stamp: 'di 3/4/98 19:18'! isIdentity ^ globalTransform isIdentity and: [localTransform isIdentity]! ! !CompositeTransform methodsFor: 'testing' stamp: 'di 3/4/98 19:18'! isPureTranslation ^ globalTransform isPureTranslation and: [localTransform isPureTranslation]! ! !CompositeTransform methodsFor: 'transformations' stamp: 'di 10/1/1998 13:51'! invert: aPoint ^ globalTransform invert: (localTransform invert: aPoint)! ! !CompositeTransform methodsFor: 'transformations' stamp: 'di 3/4/98 19:20'! transform: aPoint ^ localTransform transform: (globalTransform transform: aPoint)! ! !CompositeTransform methodsFor: 'transforming points' stamp: 'ar 11/2/1998 16:39'! globalPointToLocal: aPoint "Transform aPoint from global coordinates into local coordinates" ^localTransform globalPointToLocal: (globalTransform globalPointToLocal: aPoint)! ! !CompositeTransform methodsFor: 'transforming points' stamp: 'ar 11/2/1998 16:39'! localPointToGlobal: aPoint "Transform aPoint from global coordinates into local coordinates" ^globalTransform localPointToGlobal: (localTransform localPointToGlobal: aPoint)! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CompositeTransform class instanceVariableNames: ''! !CompositeTransform class methodsFor: 'instance creation' stamp: 'ls 3/19/2000 16:44'! globalTransform: gt localTransform: lt ^self new globalTransform: gt localTransform: lt! ! CharacterScanner subclass: #CompositionScanner instanceVariableNames: 'spaceX spaceIndex lineHeight baseline lineHeightAtSpace baselineAtSpace' classVariableNames: '' poolDictionaries: 'TextConstants' category: 'Graphics-Text'! !CompositionScanner commentStamp: '' prior: 0! CompositionScanners are used to measure text and determine where line breaks and space padding should occur.! !CompositionScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 11:13'! columnBreak "Answer true. Set up values for the text line interval currently being composed." pendingKernX := 0. line stop: lastIndex. spaceX := destX. line paddingWidth: rightMargin - spaceX. ^true! ! !CompositionScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 11:14'! cr "Answer true. Set up values for the text line interval currently being composed." pendingKernX := 0. line stop: lastIndex. spaceX := destX. line paddingWidth: rightMargin - spaceX. ^true! ! !CompositionScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 11:14'! crossedX "There is a word that has fallen across the right edge of the composition rectangle. This signals the need for wrapping which is done to the last space that was encountered, as recorded by the space stop condition." pendingKernX := 0. spaceCount >= 1 ifTrue: ["The common case. First back off to the space at which we wrap." line stop: spaceIndex. lineHeight := lineHeightAtSpace. baseline := baselineAtSpace. spaceCount := spaceCount - 1. spaceIndex := spaceIndex - 1. "Check to see if any spaces preceding the one at which we wrap. Double space after punctuation, most likely." [(spaceCount > 1 and: [(text at: spaceIndex) = Space])] whileTrue: [spaceCount := spaceCount - 1. "Account for backing over a run which might change width of space." font := text fontAt: spaceIndex withStyle: textStyle. spaceIndex := spaceIndex - 1. spaceX := spaceX - (font widthOf: Space)]. line paddingWidth: rightMargin - spaceX. line internalSpaces: spaceCount] ifFalse: ["Neither internal nor trailing spaces -- almost never happens." lastIndex := lastIndex - 1. [destX <= rightMargin] whileFalse: [destX := destX - (font widthOf: (text at: lastIndex)). lastIndex := lastIndex - 1]. spaceX := destX. line paddingWidth: rightMargin - destX. line stop: (lastIndex max: line first)]. ^true! ! !CompositionScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 11:14'! space "Record left x and character index of the space character just encounted. Used for wrap-around. Answer whether the character has crossed the right edge of the composition rectangle of the paragraph." pendingKernX := 0. spaceX := destX. destX := spaceX + spaceWidth. spaceIndex := lastIndex. lineHeightAtSpace := lineHeight. baselineAtSpace := baseline. lastIndex := lastIndex + 1. spaceCount := spaceCount + 1. destX > rightMargin ifTrue: [^self crossedX]. ^false ! ! !CompositionScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 11:15'! tab "Advance destination x according to tab settings in the paragraph's textStyle. Answer whether the character has crossed the right edge of the composition rectangle of the paragraph." pendingKernX := 0. destX := textStyle nextTabXFrom: destX leftMargin: leftMargin rightMargin: rightMargin. destX > rightMargin ifTrue: [^self crossedX]. lastIndex := lastIndex + 1. ^false ! ! !CompositionScanner methodsFor: 'accessing' stamp: 'ar 1/8/2000 14:35'! rightX "Meaningful only when a line has just been composed -- refers to the line most recently composed. This is a subtrefuge to allow for easy resizing of a composition rectangle to the width of the maximum line. Useful only when there is only one line in the form or when each line is terminated by a carriage return. Handy for sizing menus and lists." ^spaceX! ! !CompositionScanner methodsFor: 'intialize-release' stamp: 'ar 5/17/2000 19:14'! forParagraph: aParagraph "Initialize the receiver for scanning the given paragraph." self initializeFromParagraph: aParagraph clippedBy: aParagraph clippingRectangle. ! ! !CompositionScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! composeFrom: startIndex inRectangle: lineRectangle firstLine: firstLine leftSide: leftSide rightSide: rightSide "Answer an instance of TextLineInterval that represents the next line in the paragraph." "Set up margins" | runLength done stopCondition | leftMargin := lineRectangle left. leftSide ifTrue: [ leftMargin := leftMargin + (firstLine ifTrue: [ textStyle firstIndent ] ifFalse: [ textStyle restIndent ]) ]. destX := spaceX := leftMargin. rightMargin := lineRectangle right. rightSide ifTrue: [ rightMargin := rightMargin - textStyle rightIndent ]. lastIndex := startIndex. "scanning sets last index" destY := lineRectangle top. lineHeight := baseline := 0. "Will be increased by setFont" self setStopConditions. "also sets font" runLength := text runLengthFor: startIndex. runStopIndex := (lastIndex := startIndex) + (runLength - 1). line := (TextLine start: lastIndex stop: 0 internalSpaces: 0 paddingWidth: 0) rectangle: lineRectangle. spaceCount := 0. self handleIndentation. leftMargin := destX. line leftMargin: leftMargin. done := false. [ done ] whileFalse: [ stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex in: text string rightX: rightMargin stopConditions: stopConditions kern: kern. "See setStopConditions for stopping conditions for composing." (self perform: stopCondition) ifTrue: [ ^ line lineHeight: lineHeight + textStyle leading baseline: baseline + textStyle leading ] ]! ! !CompositionScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! composeLine: lineIndex fromCharacterIndex: startIndex inParagraph: aParagraph "Answer an instance of TextLineInterval that represents the next line in the paragraph." | runLength done stopCondition | destX := spaceX := leftMargin := aParagraph leftMarginForCompositionForLine: lineIndex. destY := 0. rightMargin := aParagraph rightMarginForComposition. leftMargin >= rightMargin ifTrue: [ self error: 'No room between margins to compose' ]. lastIndex := startIndex. "scanning sets last index" lineHeight := textStyle lineGrid. "may be increased by setFont:..." baseline := textStyle baseline. self setStopConditions. "also sets font" self handleIndentation. runLength := text runLengthFor: startIndex. runStopIndex := (lastIndex := startIndex) + (runLength - 1). line := TextLineInterval start: lastIndex stop: 0 internalSpaces: 0 paddingWidth: 0. spaceCount := 0. done := false. [ done ] whileFalse: [ stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex in: text string rightX: rightMargin stopConditions: stopConditions kern: kern. "See setStopConditions for stopping conditions for composing." (self perform: stopCondition) ifTrue: [ ^ line lineHeight: lineHeight + textStyle leading baseline: baseline + textStyle leading ] ]! ! !CompositionScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! setActualFont: aFont "Keep track of max height and ascent for auto lineheight" | descent | super setActualFont: aFont. lineHeight == nil ifTrue: [ descent := font descent. baseline := font ascent. lineHeight := baseline + descent ] ifFalse: [ descent := lineHeight - baseline max: font descent. baseline := baseline max: font ascent. lineHeight := lineHeight max: baseline + descent ]! ! !CompositionScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! endOfRun "Answer true if scanning has reached the end of the paragraph. Otherwise step conditions (mostly install potential new font) and answer false." | runLength | lastIndex = text size ifTrue: [ line stop: lastIndex. spaceX := destX. line paddingWidth: rightMargin - destX. ^ true ] ifFalse: [ runLength := text runLengthFor: (lastIndex := lastIndex + 1). runStopIndex := lastIndex + (runLength - 1). self setStopConditions. ^ false ]! ! !CompositionScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! placeEmbeddedObject: anchoredMorph "Workaround: The following should really use #textAnchorType" | descent | anchoredMorph relativeTextAnchorPosition ifNotNil: [ ^ true ]. (super placeEmbeddedObject: anchoredMorph) ifFalse: [ "It doesn't fit" "But if it's the first character then leave it here" lastIndex < line first ifFalse: [ line stop: lastIndex - 1. ^ false ] ]. descent := lineHeight - baseline. lineHeight := lineHeight max: anchoredMorph height. baseline := lineHeight - descent. line stop: lastIndex. ^ true! ! !CompositionScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! setFont super setFont. stopConditions == DefaultStopConditions ifTrue: [ stopConditions := stopConditions copy ]. stopConditions at: Space asciiValue + 1 put: #space. wantsColumnBreaks == true ifTrue: [ stopConditions at: TextComposer characterForColumnBreak asciiValue + 1 put: #columnBreak ]! ! !CompositionScanner methodsFor: 'stop conditions' stamp: 'ar 1/8/2000 14:37'! setStopConditions "Set the font and the stop conditions for the current run." self setFont! ! TextConverter subclass: #CompoundTextConverter instanceVariableNames: 'state' classVariableNames: '' poolDictionaries: '' category: 'Multilingual-TextConversion'! !CompoundTextConverter commentStamp: '' prior: 0! Text converter for X Compound Text.! !CompoundTextConverter methodsFor: 'conversion' stamp: 'ar 4/9/2005 22:25'! nextFromStream: aStream | character character2 size leadingChar offset result | aStream isBinary ifTrue: [^ aStream basicNext]. character := aStream basicNext. character ifNil: [^ nil]. character == Character escape ifTrue: [ self parseShiftSeqFromStream: aStream. character := aStream basicNext. character ifNil: [^ nil]]. character asciiValue < 128 ifTrue: [ size := state g0Size. leadingChar := state g0Leading. offset := 16r21. ] ifFalse: [ size :=state g1Size. leadingChar := state g1Leading. offset := 16rA1. ]. size = 1 ifTrue: [ leadingChar = 0 ifTrue: [^ character] ifFalse: [^ Character leadingChar: leadingChar code: character asciiValue] ]. size = 2 ifTrue: [ character2 := aStream basicNext. character2 ifNil: [^ nil. "self errorMalformedInput"]. character := character asciiValue - offset. character2 := character2 asciiValue - offset. result := Character leadingChar: leadingChar code: character * 94 + character2. ^ result asUnicodeChar. "^ self toUnicode: result" ]. self error: 'unsupported encoding'. ! ! !CompoundTextConverter methodsFor: 'conversion' stamp: 'ar 4/12/2005 14:10'! nextPut: aCharacter toStream: aStream | ascii leadingChar class | aStream isBinary ifTrue: [^aCharacter storeBinaryOn: aStream]. aCharacter isTraditionalDomestic ifFalse: [ class := (EncodedCharSet charsetAt: aCharacter leadingChar) traditionalCharsetClass. ascii := (class charFromUnicode: aCharacter asUnicode) charCode. leadingChar := class leadingChar. ] ifTrue: [ ascii := aCharacter charCode. leadingChar := aCharacter leadingChar. ]. self nextPutValue: ascii toStream: aStream withShiftSequenceIfNeededForLeadingChar: leadingChar. ! ! !CompoundTextConverter methodsFor: 'friend' stamp: 'yo 8/18/2003 17:50'! emitSequenceToResetStateIfNeededOn: aStream Latin1 emitSequenceToResetStateIfNeededOn: aStream forState: state. ! ! !CompoundTextConverter methodsFor: 'friend' stamp: 'yo 11/4/2002 12:33'! restoreStateOf: aStream with: aConverterState state := aConverterState copy. aStream position: state streamPosition. ! ! !CompoundTextConverter methodsFor: 'friend' stamp: 'yo 11/4/2002 13:52'! saveStateOf: aStream | inst | inst := state clone. inst streamPosition: aStream position. ^ inst. ! ! !CompoundTextConverter methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:49'! initialize super initialize. state := CompoundTextConverterState g0Size: 1 g1Size: 1 g0Leading: 0 g1Leading: 0 charSize: 1 streamPosition: 0. " unused acceptingEncodings := #(ascii iso88591 jisx0208 gb2312 ksc5601 ksx1001 ) copy." ! ! !CompoundTextConverter methodsFor: 'private' stamp: 'yo 11/4/2002 14:36'! nextPutValue: ascii toStream: aStream withShiftSequenceIfNeededForLeadingChar: leadingChar | charset | charset := EncodedCharSet charsetAt: leadingChar. charset ifNotNil: [ charset nextPutValue: ascii toStream: aStream withShiftSequenceIfNeededForTextConverterState: state. ] ifNil: [ "..." ]. ! ! !CompoundTextConverter methodsFor: 'private' stamp: 'marcus.denker 9/14/2008 21:14'! parseShiftSeqFromStream: aStream | c set target id | c := aStream basicNext. c = $$ ifTrue: [ set := #multibyte. c := aStream basicNext. c = $( ifTrue: [target := 1]. c = $) ifTrue: [target := 2]. target ifNil: [target := 1. id := c] ifNotNil: [id := aStream basicNext]. ] ifFalse: [ c = $( ifTrue: [target := 1. set := #nintyfour]. c = $) ifTrue: [target := 2. set := #nintyfour]. c = $- ifTrue: [target := 2. set := #nintysix]. id := aStream basicNext. ]. (set = #multibyte and: [id = $B]) ifTrue: [ state charSize: 2. target = 1 ifTrue: [ state g0Size: 2. state g0Leading: 1. ] ifFalse: [ state g1Size: 2. state g1Leading: 1. ]. ^ self ]. (set = #multibyte and: [id = $A]) ifTrue: [ state charSize: 2. target = 1 ifTrue: [ state g0Size: 2. state g0Leading: 2. ] ifFalse: [ state g1Size: 2. state g1Leading: 2. ]. ^ self ]. (set = #nintyfour and: [id = $B or: [id = $J]]) ifTrue: [ state charSize: 1. state g0Size: 1. state g0Leading: 0. ^ self ]. (set = #nintysix and: [id = $A]) ifTrue: [ state charSize: 1. state g1Size: 1. state g1Leading: 0. ^ self ].! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CompoundTextConverter class instanceVariableNames: ''! !CompoundTextConverter class methodsFor: 'utilities' stamp: 'yo 10/24/2002 14:16'! encodingNames ^ #('iso-2022-jp' 'x-ctext') copy ! ! Object subclass: #CompoundTextConverterState instanceVariableNames: 'g0Size g1Size g0Leading g1Leading charSize streamPosition' classVariableNames: '' poolDictionaries: '' category: 'Multilingual-TextConversion'! !CompoundTextConverterState commentStamp: '' prior: 0! This represents the state of CompoundTextConverter.! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 8/23/2002 21:30'! charSize ^ charSize ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 9/16/2002 20:41'! charSize: s charSize := s. ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 8/23/2002 21:29'! g0Leading ^ g0Leading ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 9/16/2002 20:41'! g0Leading: l g0Leading := l. ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 8/23/2002 21:29'! g0Size ^ g0Size ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 9/16/2002 20:41'! g0Size: s g0Size := s. ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 8/23/2002 14:37'! g0Size: g0 g1Size: g1 g0Leading: g0l g1Leading: g1l charSize: cSize streamPosition: pos g0Size := g0. g1Size := g1. g0Leading := g0l. g1Leading := g1l. charSize := cSize. streamPosition := pos. ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 8/23/2002 21:30'! g1Leading ^ g1Leading ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 9/16/2002 20:41'! g1Leading: l g1Leading := l. ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 8/23/2002 21:29'! g1Size ^ g1Size ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 9/16/2002 20:41'! g1Size: s g1Size := s. ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 11/4/2002 12:31'! printOn: aStream aStream nextPut: $(; nextPutAll: g0Size printString; space; nextPutAll: g1Size printString; space; nextPutAll: g0Leading printString; space; nextPutAll: g1Leading printString; space; nextPutAll: charSize printString; space; nextPutAll: streamPosition printString. aStream nextPut: $). ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 8/23/2002 21:30'! streamPosition ^ streamPosition ! ! !CompoundTextConverterState methodsFor: 'accessing' stamp: 'yo 9/16/2002 20:40'! streamPosition: pos streamPosition := pos. ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CompoundTextConverterState class instanceVariableNames: ''! !CompoundTextConverterState class methodsFor: 'instance creation' stamp: 'yo 8/19/2002 17:04'! g0Size: g0 g1Size: g1 g0Leading: g0l g1Leading: g1l charSize: cSize streamPosition: pos ^ (self new) g0Size: g0 g1Size: g1 g0Leading: g0l g1Leading: g1l charSize: cSize streamPosition: pos ; yourself. ! ! Object subclass: #CompressedBoundaryShape instanceVariableNames: 'points leftFills rightFills lineWidths lineFills fillStyles' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Geometry'! !CompressedBoundaryShape commentStamp: '' prior: 0! This class represents a very compact representation of a boundary shape. It consists of a number of compressed arrays that can be handled by the balloon engine directly. Due to this, there are certain restrictions (see below). Boundaries are always represented by three subsequent points that define a quadratic bezier segment. It is recommended that for straight line segments the control point is set either to the previous or the next point. Instance variables: points Point storage area leftFills Containing the "left" fill index of each segment rightFills Containing the "right" fill index of each segment lineWidths Containing the line width of each segment lineFills Containing the line fill (e.g., line color) of each segment fillStyles Contains the actual fill styles referenced by the indexes RESTRICTIONS: None of the ShortRunArrays may contain a run of length Zero. Also, due to the use of ShortRunArrays a) you cannot have more than 32768 different fill styles b) you cannot have a line width that exceeds 32768 In case you have trouble with a), try to merge some of the fills into one. You might do so by converting colors to 32bit pixel values. In case you have trouble with b) you might change the general resolution of the compressed shape to have less accuracy. ! !CompressedBoundaryShape methodsFor: 'accessing' stamp: 'ls 10/10/1999 13:52'! bounds | min max width | points isEmpty ifTrue:[^0@0 corner: 1@1]. min := max := points first. points do:[:pt| min := min min: pt. max := max max: pt ]. width := 0. lineWidths valuesDo:[:w| width := width max: w]. ^(min corner: max) insetBy: (width negated asPoint)! ! !CompressedBoundaryShape methodsFor: 'accessing' stamp: 'ar 11/3/1998 21:55'! fillStyles ^fillStyles! ! !CompressedBoundaryShape methodsFor: 'accessing' stamp: 'ar 11/3/1998 21:55'! leftFills ^leftFills! ! !CompressedBoundaryShape methodsFor: 'accessing' stamp: 'ar 11/3/1998 21:55'! lineFills ^lineFills! ! !CompressedBoundaryShape methodsFor: 'accessing' stamp: 'ar 11/3/1998 21:55'! lineWidths ^lineWidths! ! !CompressedBoundaryShape methodsFor: 'accessing' stamp: 'ar 11/4/1998 13:50'! numSegments ^points size // 3! ! !CompressedBoundaryShape methodsFor: 'accessing' stamp: 'ar 11/3/1998 20:42'! points ^points! ! !CompressedBoundaryShape methodsFor: 'accessing' stamp: 'ar 11/3/1998 21:55'! rightFills ^rightFills! ! !CompressedBoundaryShape methodsFor: 'accessing' stamp: 'PeterHugossonMiller 9/3/2009 01:01'! segments "Return all the segments in the receiver" | out | out := Array new writeStream. self segmentsDo:[:seg| out nextPut: seg]. ^out contents! ! !CompressedBoundaryShape methodsFor: 'editing' stamp: 'ar 11/12/1998 21:12'! collectFills: aBlock fillStyles := fillStyles collect: aBlock.! ! !CompressedBoundaryShape methodsFor: 'editing' stamp: 'ar 11/12/1998 21:11'! copyAndCollectFills: aBlock ^self copy collectFills: aBlock! ! !CompressedBoundaryShape methodsFor: 'enumerating' stamp: 'ar 11/9/1998 14:10'! segmentsDo: aBlock "Enumerate all segments in the receiver and execute aBlock" | p1 p2 p3 | 1 to: points size by: 3 do:[:i| p1 := points at: i. p2 := points at: i+1. p3 := points at: i+2. (p1 = p2 or:[p2 = p3]) ifTrue:[ aBlock value: (LineSegment from: p1 to: p3). ] ifFalse:[ aBlock value: (Bezier2Segment from: p1 via: p2 to: p3). ]. ].! ! !CompressedBoundaryShape methodsFor: 'morphing' stamp: 'ar 9/3/1999 17:19'! morphFrom: srcShape to: dstShape at: ratio | scale unscale srcPoints dstPoints pt1 pt2 x y | scale := (ratio * 1024) asInteger. scale < 0 ifTrue:[scale := 0]. scale > 1024 ifTrue:[scale := 1024]. unscale := 1024 - scale. srcPoints := srcShape points. dstPoints := dstShape points. 1 to: points size do:[:i| pt1 := srcPoints at: i. pt2 := dstPoints at: i. x := ((pt1 x * unscale) + (pt2 x * scale)) bitShift: -10. y := ((pt1 y * unscale) + (pt2 y * scale)) bitShift: -10. points at: i put: x@y].! ! !CompressedBoundaryShape methodsFor: 'private' stamp: 'ar 11/3/1998 18:03'! setPoints: pointList leftFills: leftFillList rightFills: rightFillList fillStyles: fillStyleList lineWidths: lineWidthList lineFills: lineFillList points := pointList. leftFills := leftFillList. rightFills := rightFillList. lineWidths := lineWidthList. lineFills := lineFillList. fillStyles := fillStyleList.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CompressedBoundaryShape class instanceVariableNames: ''! !CompressedBoundaryShape class methodsFor: 'instance creation' stamp: 'ar 11/3/1998 18:02'! points: pointList leftFills: leftFillList rightFills: rightFillList fillStyles: fillStyleList lineWidths: lineWidthList lineFills: lineFillList ^self new setPoints: pointList leftFills: leftFillList rightFills: rightFillList fillStyles: fillStyleList lineWidths: lineWidthList lineFills: lineFillList! ! ReadWriteStream subclass: #CompressedSourceStream instanceVariableNames: 'segmentFile segmentSize nSegments segmentTable segmentIndex dirty endOfFile' classVariableNames: '' poolDictionaries: '' category: 'Files-System'! !CompressedSourceStream commentStamp: 'di 11/3/2003 17:58' prior: 0! I implement a file format that compresses segment by segment to allow incremental writing and browsing. Note that the file can only be written at the end. Structure: segmentFile The actual compressed file. segmentSize This is the quantum of compression. The virtual file is sliced up into segments of this size. nSegments The maximum number of segments to which this file can be grown. endOfFile The user's endOfFile pointer. segmentTable When a file is open, this table holds the physical file positions of the compressed segments. segmentIndex Index of the most recently accessed segment. Inherited from ReadWriteStream... collection The segment buffer, uncompressed position This is the position *local* to the current segment buffer readLimit ReadLimit for the current buffer writeLimit WriteLimit for the current buffer Great care must be exercised to distinguish between the position relative to the segment buffer and the full file position (and, or course, the segment file position ;-). The implementation defaults to a buffer size of 20k, and a max file size of 34MB (conveniently chosen to be greater than the current 33MB limit of source code pointers). The format of the file is as follows: segmentSize 4 bytes nSegments 4 bytes endOfFile 4 bytes segmentTable 4 bytes * (nSegments+1) beginning of first compressed segment It is possible to override the default allocation by sending the message #segmentSize:nSegments: immediately after opening a new file for writing, as follows: bigFile _ (CompressedSourceStream on: (FileStream newFileNamed: 'biggy.stc')) segmentSize: 50000 maxSize: 200000000 The difference between segment table entries reveals the size of each compressed segment. When a file is being written, it may lack the final segment, but any flush, position:, or close will force a dirty segment to be written.! !CompressedSourceStream methodsFor: 'access' stamp: 'di 11/3/2003 00:41'! atEnd position >= readLimit ifFalse: [^ false]. "more in segment" ^ self position >= endOfFile "more in file"! ! !CompressedSourceStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! contentsOfEntireFile | contents | self position: 0. contents := self next: self size. self close. ^ contents! ! !CompressedSourceStream methodsFor: 'access' stamp: 'di 11/1/2003 19:50'! flush dirty ifTrue: ["Write buffer, compressed, to file, and also write the segment offset and eof" self writeSegment].! ! !CompressedSourceStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! next position >= readLimit ifTrue: [^ (self next: 1) at: 1] ifFalse: [^ collection at: (position := position + 1)]! ! !CompressedSourceStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! next: n | str | n <= (readLimit - position) ifTrue: ["All characters are available in buffer" str := collection copyFrom: position + 1 to: position + n. position := position + n. ^ str]. "Read limit could be segment boundary or real end of file" (readLimit + self segmentOffset) = endOfFile ifTrue: ["Real end of file -- just return what's available" ^ self next: readLimit - position]. "Read rest of segment. Then (after positioning) read what remains" str := self next: readLimit - position. self position: self position. ^ str , (self next: n - str size) ! ! !CompressedSourceStream methodsFor: 'access' stamp: 'di 11/2/2003 11:27'! nextPut: char "Slow, but we don't often write, and then not a lot" self nextPutAll: char asString. ^ char! ! !CompressedSourceStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! nextPutAll: str | n nInSeg | n := str size. n <= (writeLimit - position) ifTrue: ["All characters fit in buffer" collection replaceFrom: position + 1 to: position + n with: str. dirty := true. position := position + n. readLimit := readLimit max: position. endOfFile := endOfFile max: self position. ^ str]. "Write what fits in segment. Then (after positioning) write what remains" nInSeg := writeLimit - position. nInSeg = 0 ifTrue: [self position: self position. self nextPutAll: str] ifFalse: [self nextPutAll: (str first: nInSeg). self position: self position. self nextPutAll: (str allButFirst: nInSeg)] ! ! !CompressedSourceStream methodsFor: 'access' stamp: 'di 11/2/2003 09:27'! position ^ position + self segmentOffset! ! !CompressedSourceStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! position: newPosition | compressedBuffer newSegmentIndex | newPosition > endOfFile ifTrue: [self error: 'Attempt to position beyond the end of file']. newSegmentIndex := (newPosition // segmentSize) + 1. newSegmentIndex ~= segmentIndex ifTrue: [self flush. segmentIndex := newSegmentIndex. newSegmentIndex > nSegments ifTrue: [self error: 'file size limit exceeded']. segmentFile position: (segmentTable at: segmentIndex). (segmentTable at: segmentIndex+1) = 0 ifTrue: [newPosition ~= endOfFile ifTrue: [self error: 'Internal logic error']. collection size = segmentSize ifFalse: [self error: 'Internal logic error']. "just leave garbage beyond end of file"] ifFalse: [compressedBuffer := segmentFile next: ((segmentTable at: segmentIndex+1) - (segmentTable at: segmentIndex)). collection := (GZipReadStream on: compressedBuffer) upToEnd asString]. readLimit := collection size min: endOfFile - self segmentOffset]. position := newPosition \\ segmentSize. ! ! !CompressedSourceStream methodsFor: 'access' stamp: 'di 11/1/2003 11:41'! size ^ endOfFile ifNil: [0]! ! !CompressedSourceStream methodsFor: 'open/close' stamp: 'di 11/1/2003 22:36'! binary self error: 'Compressed source files are ascii to the user (though binary underneath)'! ! !CompressedSourceStream methodsFor: 'open/close' stamp: 'di 11/1/2003 22:36'! close self flush. segmentFile close! ! !CompressedSourceStream methodsFor: 'open/close' stamp: 'stephaneducasse 2/4/2006 20:31'! openOn: aFile "Open the receiver." segmentFile := aFile. segmentFile binary. segmentFile size > 0 ifTrue: [self readHeaderInfo. "If file exists, then read the parameters"] ifFalse: [self segmentSize: 20000 maxSize: 34000000. "Otherwise write default values"]! ! !CompressedSourceStream methodsFor: 'open/close' stamp: 'di 11/3/2003 10:13'! openReadOnly segmentFile openReadOnly! ! !CompressedSourceStream methodsFor: 'open/close' stamp: 'stephaneducasse 2/4/2006 20:31'! readHeaderInfo | valid a b | segmentFile position: 0. segmentSize := segmentFile nextNumber: 4. nSegments := segmentFile nextNumber: 4. endOfFile := segmentFile nextNumber: 4. segmentFile size < (nSegments+1 + 3 * 4) ifTrue: "Check for reasonable segment info" [self error: 'This file is not in valid compressed source format']. segmentTable := (1 to: nSegments+1) collect: [:x | segmentFile nextNumber: 4]. segmentTable first ~= self firstSegmentLoc ifTrue: [self error: 'This file is not in valid compressed source format']. valid := true. 1 to: nSegments do: "Check that segment offsets are ascending" [:i | a := segmentTable at: i. b := segmentTable at: i+1. (a = 0 and: [b ~= 0]) ifTrue: [valid := false]. (a ~= 0 and: [b ~= 0]) ifTrue: [b <= a ifTrue: [valid := false]]]. valid ifFalse: [self error: 'This file is not in valid compressed source format']. dirty := false. self position: 0.! ! !CompressedSourceStream methodsFor: 'open/close' stamp: 'di 11/3/2003 10:09'! readOnlyCopy ^ self class on: segmentFile readOnlyCopy! ! !CompressedSourceStream methodsFor: 'open/close' stamp: 'di 11/2/2003 23:07'! test "FileDirectory default deleteFileNamed: 'test.stc'. (CompressedSourceStream on: (FileStream newFileNamed: 'test.stc')) fileOutChanges" "FileDirectory default deleteFileNamed: 'test2.stc'. ((CompressedSourceStream on: (FileStream newFileNamed: 'test2.stc')) segmentSize: 100 nSegments: 1000) fileOutChanges" "FileDirectory default deleteFileNamed: 'test3.st'. (FileStream newFileNamed: 'test3.st') fileOutChanges" "(CompressedSourceStream on: (FileStream oldFileNamed: 'test.stc')) contentsOfEntireFile" ! ! !CompressedSourceStream methodsFor: 'private' stamp: 'di 11/20/2003 12:45'! fileID "Only needed for OSProcess stuff" ^ segmentFile fileID ! ! !CompressedSourceStream methodsFor: 'private' stamp: 'di 11/2/2003 09:35'! firstSegmentLoc "First segment follows 3 header words and segment table" ^ (3 + nSegments+1) * 4! ! !CompressedSourceStream methodsFor: 'private' stamp: 'di 11/2/2003 09:24'! segmentOffset ^ segmentIndex - 1 * segmentSize! ! !CompressedSourceStream methodsFor: 'private' stamp: 'stephaneducasse 2/4/2006 20:31'! segmentSize: segSize maxSize: maxSize "Note that this method can be called after the initial open, provided that no writing has yet taken place. This is how to override the default segmentation." self size = 0 ifFalse: [self error: 'Cannot set parameters after the first write']. segmentFile position: 0. segmentFile nextNumber: 4 put: (segmentSize := segSize). segmentFile nextNumber: 4 put: (nSegments := maxSize // segSize + 2). segmentFile nextNumber: 4 put: (endOfFile := 0). segmentTable := Array new: nSegments+1 withAll: 0. segmentTable at: 1 put: self firstSegmentLoc. "Loc of first segment, always." segmentTable do: [:i | segmentFile nextNumber: 4 put: i]. segmentIndex := 1. collection := String new: segmentSize. writeLimit := segmentSize. readLimit := 0. position := 0. endOfFile := 0. self writeSegment. ! ! !CompressedSourceStream methodsFor: 'private' stamp: 'stephaneducasse 2/4/2006 20:31'! writeSegment "The current segment must be the last in the file." | compressedSegment | segmentFile position: (segmentTable at: segmentIndex). compressedSegment := ByteArray streamContents: [:strm | (GZipWriteStream on: strm) nextPutAll: collection asByteArray; close]. segmentFile nextPutAll: compressedSegment. segmentTable at: segmentIndex + 1 put: segmentFile position. segmentFile position: 2 * 4. segmentFile nextNumber: 4 put: endOfFile. segmentFile position: (segmentIndex + 3) * 4. segmentFile nextNumber: 4 put: (segmentTable at: segmentIndex + 1). dirty := false! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CompressedSourceStream class instanceVariableNames: ''! !CompressedSourceStream class methodsFor: 'as yet unclassified' stamp: 'di 11/1/2003 22:58'! on: aFile ^ self basicNew openOn: aFile! ! NetworkError subclass: #ConnectionClosed instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Network-Kernel'! !ConnectionClosed commentStamp: 'mir 5/12/2003 18:12' prior: 0! Signals a prematurely closed connection. ! Object subclass: #ConnectionQueue instanceVariableNames: 'portNumber maxQueueLength connections accessSema socket process' classVariableNames: '' poolDictionaries: '' category: 'Network-Kernel'! !ConnectionQueue commentStamp: '' prior: 0! A ConnectionQueue listens on a given port number and collects a queue of client connections. In order to handle state changes quickly, a ConnectionQueue has its own process that: (a) tries to keep a socket listening on the port whenever the queue isn't already full of connections and (b) prunes stale connections out of the queue to make room for fresh ones. ! !ConnectionQueue methodsFor: 'public' stamp: 'jm 3/10/98 17:31'! connectionCount "Return an estimate of the number of currently queued connections. This is only an estimate since a new connection could be made, or an existing one aborted, at any moment." | count | self pruneStaleConnections. accessSema critical: [count := connections size]. ^ count ! ! !ConnectionQueue methodsFor: 'public' stamp: 'jm 3/9/98 14:34'! destroy "Terminate the listener process and destroy all sockets in my possesion." process ifNotNil: [ process terminate. process := nil]. socket ifNotNil: [ socket destroy. socket := nil]. connections do: [:s | s destroy]. connections := OrderedCollection new. ! ! !ConnectionQueue methodsFor: 'public' stamp: 'jm 3/10/98 09:18'! getConnectionOrNil "Return a connected socket, or nil if no connection has been established." | result | accessSema critical: [ connections isEmpty ifTrue: [result := nil] ifFalse: [ result := connections removeFirst. ((result isValid) and: [result isConnected]) ifFalse: [ "stale connection" result destroy. result := nil]]]. ^ result ! ! !ConnectionQueue methodsFor: 'public' stamp: 'RAA 7/15/2000 12:36'! getConnectionOrNilLenient "Return a connected socket, or nil if no connection has been established." | result | accessSema critical: [ connections isEmpty ifTrue: [ result := nil ] ifFalse: [ result := connections removeFirst. (result isValid and: [result isConnected or: [result isOtherEndClosed]]) ifFalse: [ "stale connection" result destroy. result := nil ] ] ]. ^ result ! ! !ConnectionQueue methodsFor: 'public' stamp: 'ls 9/26/1999 15:34'! isValid ^process notNil! ! !ConnectionQueue methodsFor: 'private' stamp: 'jm 3/10/98 11:07'! initPortNumber: anInteger queueLength: queueLength "Private!! Initialize the receiver to listen on the given port number. Up to queueLength connections will be queued." portNumber := anInteger. maxQueueLength := queueLength. connections := OrderedCollection new. accessSema := Semaphore forMutualExclusion. socket := nil. process := [self listenLoop] newProcess. process priority: Processor highIOPriority. process resume. ! ! !ConnectionQueue methodsFor: 'private' stamp: 'bf 6/29/2007 17:58'! listenLoop "Private!! This loop is run in a separate process. It will establish up to maxQueueLength connections on the given port." "Details: When out of sockets or queue is full, retry more frequently, since a socket may become available, space may open in the queue, or a previously queued connection may be aborted by the client, making it available for a fresh connection." "Note: If the machine is disconnected from the network while the server is running, the currently waiting socket will go from 'isWaitingForConnection' to 'unconnected', and attempts to create new sockets will fail. When this happens, delete the broken socket and keep trying to create a socket in case the network connection is re-established. Connecting and disconnecting was tested under PPP on Mac system 8.1. It is not if this will work on other platforms." | newConnection adressInfos | NetNameResolver useOldNetwork ifTrue: [^self oldListenLoop]. adressInfos := SocketAddressInformation forHost: '' service: portNumber asString flags: SocketAddressInformation passiveFlag addressFamily: SocketAddressInformation addressFamilyINET4 socketType: SocketAddressInformation socketTypeStream protocol: SocketAddressInformation protocolTCP. "We'll accept four simultanous connections at the same time" socket := adressInfos first listenWithBacklog: 4. "If the listener is not valid then the we cannot use the BSD style accept() mechanism." socket isValid ifFalse: [^self oldStyleListenLoop]. [true] whileTrue: [ socket isValid ifFalse: [ "socket has stopped listening for some reason" socket destroy. (Delay forMilliseconds: 10) wait. ^self listenLoop ]. newConnection := socket waitForAcceptFor: 10. (newConnection notNil and:[newConnection isConnected]) ifTrue: [accessSema critical: [connections addLast: newConnection]. newConnection := nil]. self pruneStaleConnections]. ! ! !ConnectionQueue methodsFor: 'private' stamp: 'bf 6/29/2007 17:29'! oldListenLoop "Private!! This loop is run in a separate process. It will establish up to maxQueueLength connections on the given port." "Details: When out of sockets or queue is full, retry more frequently, since a socket may become available, space may open in the queue, or a previously queued connection may be aborted by the client, making it available for a fresh connection." "Note: If the machine is disconnected from the network while the server is running, the currently waiting socket will go from 'isWaitingForConnection' to 'unconnected', and attempts to create new sockets will fail. When this happens, delete the broken socket and keep trying to create a socket in case the network connection is re-established. Connecting and disconnecting was tested under PPP on Mac system 8.1. It is not if this will work on other platforms." | newConnection | socket := Socket newTCP. "We'll accept four simultanous connections at the same time" socket listenOn: portNumber backlogSize: 4. "If the listener is not valid then the we cannot use the BSD style accept() mechanism." socket isValid ifFalse: [^self oldStyleListenLoop]. [true] whileTrue: [ socket isValid ifFalse: [ "socket has stopped listening for some reason" socket destroy. (Delay forMilliseconds: 10) wait. ^self oldListenLoop ]. newConnection := socket waitForAcceptFor: 10. (newConnection notNil and:[newConnection isConnected]) ifTrue: [accessSema critical: [connections addLast: newConnection]. newConnection := nil]. self pruneStaleConnections]. ! ! !ConnectionQueue methodsFor: 'private' stamp: 'mir 5/15/2003 18:28'! oldStyleListenLoop "Private!! This loop is run in a separate process. It will establish up to maxQueueLength connections on the given port." "Details: When out of sockets or queue is full, retry more frequently, since a socket may become available, space may open in the queue, or a previously queued connection may be aborted by the client, making it available for a fresh connection." "Note: If the machine is disconnected from the network while the server is running, the currently waiting socket will go from 'isWaitingForConnection' to 'unconnected', and attempts to create new sockets will fail. When this happens, delete the broken socket and keep trying to create a socket in case the network connection is re-established. Connecting and disconnecting was tested under PPP on Mac system 8.1. It is not if this will work on other platforms." [true] whileTrue: [ ((socket == nil) and: [connections size < maxQueueLength]) ifTrue: [ "try to create a new socket for listening" socket := Socket createIfFail: [nil]]. socket == nil ifTrue: [(Delay forMilliseconds: 100) wait] ifFalse: [ socket isUnconnected ifTrue: [socket listenOn: portNumber]. [socket waitForConnectionFor: 10] on: ConnectionTimedOut do: [:ex | socket isConnected ifTrue: [ "connection established" accessSema critical: [connections addLast: socket]. socket := nil] ifFalse: [ socket isWaitingForConnection ifFalse: [socket destroy. socket := nil]]]]. "broken socket; start over" self pruneStaleConnections]. ! ! !ConnectionQueue methodsFor: 'private' stamp: 'jm 3/10/98 17:30'! pruneStaleConnections "Private!! The client may establish a connection and then disconnect while it is still in the connection queue. This method is called periodically to prune such sockets out of the connection queue and make room for fresh connections." | foundStaleConnection | accessSema critical: [ foundStaleConnection := false. connections do: [:s | s isUnconnected ifTrue: [ s destroy. foundStaleConnection := true]]. foundStaleConnection ifTrue: [ connections := connections select: [:s | s isValid]]]. ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ConnectionQueue class instanceVariableNames: ''! !ConnectionQueue class methodsFor: 'instance creation' stamp: 'jm 3/9/98 14:09'! portNumber: anInteger queueLength: queueLength ^ self new initPortNumber: anInteger queueLength: queueLength ! ! NetworkError subclass: #ConnectionRefused instanceVariableNames: 'host port' classVariableNames: '' poolDictionaries: '' category: 'Network-Kernel'! !ConnectionRefused commentStamp: 'mir 5/12/2003 18:14' prior: 0! Signals that a connection to the specified host and port was refused. host host which refused the connection port prot to which the connection was refused ! !ConnectionRefused methodsFor: 'accessing' stamp: 'len 12/14/2002 11:58'! host ^ host! ! !ConnectionRefused methodsFor: 'accessing' stamp: 'len 12/14/2002 11:39'! host: addressOrHostName port: portNumber host := addressOrHostName. port := portNumber! ! !ConnectionRefused methodsFor: 'accessing' stamp: 'len 12/14/2002 11:58'! port ^ port! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ConnectionRefused class instanceVariableNames: ''! !ConnectionRefused class methodsFor: 'instance creation' stamp: 'len 12/14/2002 11:39'! host: addressOrHostName port: portNumber ^ self new host: addressOrHostName port: portNumber! ! NetworkError subclass: #ConnectionTimedOut instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Network-Kernel'! !ConnectionTimedOut commentStamp: 'mir 5/12/2003 18:14' prior: 0! Signals that a connection attempt timed out. ! TestCase subclass: #ContextCompilationTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Compiler'! !ContextCompilationTest methodsFor: 'tests' stamp: 'eem 6/19/2008 10:11'! testVariablesAndOffsetsDo "ContextCompilationTest new testVariablesAndOffsetsDo" | contextClasses | contextClasses := ContextPart withAllSuperclasses, ContextPart allSubclasses asArray. contextClasses do: [:class| class variablesAndOffsetsDo: [:var :offset| self assert: offset < 0. self assert: (class instVarNameForIndex: offset negated) == var]]. InstructionStream withAllSuperclasses, InstructionStream allSubclasses asArray do: [:class| (contextClasses includes: class) ifFalse: [class variablesAndOffsetsDo: [:var :offset| (InstructionStream instVarNames includes: var) ifFalse: [self assert: offset > 0. self assert: (class instVarNameForIndex: offset) == var]]]]! ! InstructionStream subclass: #ContextPart instanceVariableNames: 'stackp' classVariableNames: 'PrimitiveFailToken QuickStep' poolDictionaries: '' category: 'Kernel-Methods'! !ContextPart commentStamp: '' prior: 0! To the instruction parsing ability of InstructionStream I add the actual semantics for execution. The execution state is stored in the indexable fields of my subclasses. This includes temporary variables and a stack of values used in evaluating expressions. The actual semantics of execution can be found in my category "system simulation" and "instruction decode". These methods exactly parallel the operation of the Smalltalk machine itself. The simulator is a group of my methods that do what the Smalltalk interpreter does: execute Smalltalk bytecodes. By adding code to the simulator, you may take statistics on the running of Smalltalk methods. For example, Transcript show: (ContextPart runSimulated: [3 factorial]) printString.! !ContextPart methodsFor: 'accessing' stamp: 'stephane.ducasse 3/1/2009 08:41'! arguments "returns the arguments of a message invocation" | arguments numargs | numargs := self method numArgs. arguments := Array new: numargs. 1 to: numargs do: [:i | arguments at: i put: (self tempAt: i) ]. ^ arguments! ! !ContextPart methodsFor: 'accessing' stamp: 'eem 6/27/2008 15:55'! at: index "Primitive. Assumes receiver is indexable. Answer the value of an indexable element in the receiver. Fail if the argument index is not an Integer or is out of bounds. Essential. See Object documentation whatIsAPrimitive. Override the default primitive to give latitude to the VM in context management." index isInteger ifTrue: [self errorSubscriptBounds: index]. index isNumber ifTrue: [^self at: index asInteger] ifFalse: [self errorNonIntegerIndex]! ! !ContextPart methodsFor: 'accessing' stamp: 'eem 6/27/2008 15:57'! at: index put: value "Primitive. Assumes receiver is indexable. Answer the value of an indexable element in the receiver. Fail if the argument index is not an Integer or is out of bounds. Essential. See Object documentation whatIsAPrimitive. Override the default primitive to give latitude to the VM in context management." index isInteger ifTrue: [self errorSubscriptBounds: index]. index isNumber ifTrue: [^self at: index asInteger put: value] ifFalse: [self errorNonIntegerIndex]! ! !ContextPart methodsFor: 'accessing' stamp: 'eem 6/27/2008 15:56'! basicAt: index "Primitive. Assumes receiver is indexable. Answer the value of an indexable element in the receiver. Fail if the argument index is not an Integer or is out of bounds. Essential. See Object documentation whatIsAPrimitive. Override the default primitive to give latitude to the VM in context management." index isInteger ifTrue: [self errorSubscriptBounds: index]. index isNumber ifTrue: [^self at: index asInteger] ifFalse: [self errorNonIntegerIndex]! ! !ContextPart methodsFor: 'accessing' stamp: 'eem 6/27/2008 15:57'! basicAt: index put: value "Primitive. Assumes receiver is indexable. Answer the value of an indexable element in the receiver. Fail if the argument index is not an Integer or is out of bounds. Essential. See Object documentation whatIsAPrimitive. Override the default primitive to give latitude to the VM in context management." index isInteger ifTrue: [self errorSubscriptBounds: index]. index isNumber ifTrue: [^self at: index asInteger put: value] ifFalse: [self errorNonIntegerIndex]! ! !ContextPart methodsFor: 'accessing' stamp: 'eem 6/27/2008 10:45'! basicSize "Primitive. Answer the number of indexable variables in the receiver. This value is the same as the largest legal subscript. Essential. Do not override in any subclass. See Object documentation whatIsAPrimitive. Override the default primitive to give latitude to the VM in context management." "The number of indexable fields of fixed-length objects is 0" ^self primitiveFail! ! !ContextPart methodsFor: 'accessing'! client "Answer the client, that is, the object that sent the message that created this context." ^sender receiver! ! !ContextPart methodsFor: 'accessing' stamp: 'eem 6/15/2008 11:31'! contextForLocalVariables "Answer the context in which local variables (temporaries) are stored." self subclassResponsibility! ! !ContextPart methodsFor: 'accessing'! home "Answer the context in which the receiver was defined." self subclassResponsibility! ! !ContextPart methodsFor: 'accessing'! method "Answer the method of this context." self subclassResponsibility! ! !ContextPart methodsFor: 'accessing' stamp: 'ar 4/11/2006 01:49'! methodNode ^ self method methodNode.! ! !ContextPart methodsFor: 'accessing' stamp: 'eem 6/15/2008 11:27'! methodReturnContext "Answer the context from which an ^-return should return from." self subclassResponsibility! ! !ContextPart methodsFor: 'accessing' stamp: 'lr 3/22/2009 19:15'! methodSelector ^ self method selector! ! !ContextPart methodsFor: 'accessing'! receiver "Answer the receiver of the message that created this context." self subclassResponsibility! ! !ContextPart methodsFor: 'accessing' stamp: 'eem 6/27/2008 10:46'! size "Primitive. Answer the number of indexable variables in the receiver. This value is the same as the largest legal subscript. Essential. See Object documentation whatIsAPrimitive. Override the default primitive to give latitude to the VM in context management." "The number of indexable fields of fixed-length objects is 0" ^self primitiveFail! ! !ContextPart methodsFor: 'accessing'! tempAt: index "Answer the value of the temporary variable whose index is the argument, index." self subclassResponsibility! ! !ContextPart methodsFor: 'accessing'! tempAt: index put: value "Store the argument, value, as the temporary variable whose index is the argument, index." self subclassResponsibility! ! !ContextPart methodsFor: 'accessing' stamp: 'md 2/9/2007 17:34'! tempNamed: aName "Answer the value of the temporary variable whose name is the argument, aName." self subclassResponsibility! ! !ContextPart methodsFor: 'accessing' stamp: 'md 2/9/2007 17:34'! tempNamed: aName put: value "Store the argument, value, as the temporary variable whose name is the argument, aName." self subclassResponsibility! ! !ContextPart methodsFor: 'controlling'! activateMethod: newMethod withArgs: args receiver: rcvr class: class "Answer a ContextPart initialized with the arguments." ^MethodContext sender: self receiver: rcvr method: newMethod arguments: args! ! !ContextPart methodsFor: 'controlling' stamp: 'eem 6/14/2008 19:17'! blockCopy: numArgs "Primitive. Distinguish a block of code from its enclosing method by creating a new BlockContext for that block. The compiler inserts into all methods that contain blocks the bytecodes to send the message blockCopy:. Do not use blockCopy: in code that you write!! Only the compiler can decide to send the message blockCopy:. Fail if numArgs is not a SmallInteger. Optional. No Lookup. See Object documentation whatIsAPrimitive." ^ (BlockContext newForMethod: self method) home: self home startpc: pc + 2 nargs: numArgs! ! !ContextPart methodsFor: 'controlling' stamp: 'eem 8/29/2008 06:27'! closureCopy: numArgs copiedValues: anArray "Distinguish a block of code from its enclosing method by creating a BlockClosure for that block. The compiler inserts into all methods that contain blocks the bytecodes to send the message closureCopy:copiedValues:. Do not use closureCopy:copiedValues: in code that you write!! Only the compiler can decide to send the message closureCopy:copiedValues:. Fail if numArgs is not a SmallInteger. Optional. No Lookup. See Object documentation whatIsAPrimitive." ^BlockClosure outerContext: self startpc: pc + 2 numArgs: numArgs copiedValues: anArray! ! !ContextPart methodsFor: 'controlling'! hasSender: context "Answer whether the receiver is strictly above context on the stack." | s | self == context ifTrue: [^false]. s := sender. [s == nil] whileFalse: [s == context ifTrue: [^true]. s := s sender]. ^false! ! !ContextPart methodsFor: 'controlling' stamp: 'ajh 3/25/2004 00:07'! jump "Abandon thisContext and resume self instead (using the same current process). You may want to save thisContext's sender before calling this so you can jump back to it. Self MUST BE a top context (ie. a suspended context or a abandoned context that was jumped out of). A top context already has its return value on its stack (see Interpreter>>primitiveSuspend and other suspending primitives). thisContext's sender is converted to a top context (by pushing a nil return value on its stack) so it can be jump back to." | top | "Make abandoned context a top context (has return value (nil)) so it can be jumped back to" thisContext sender push: nil. "Pop self return value then return it to self (since we jump to self by returning to it)" stackp = 0 ifTrue: [self stepToSendOrReturn]. stackp = 0 ifTrue: [self push: nil]. "must be quick return self/constant" top := self pop. thisContext privSender: self. ^ top! ! !ContextPart methodsFor: 'controlling' stamp: 'di 1/11/1999 22:40'! pop "Answer the top of the receiver's stack and remove the top of the stack." | val | val := self at: stackp. self stackp: stackp - 1. ^ val! ! !ContextPart methodsFor: 'controlling' stamp: 'di 1/11/1999 22:39'! push: val "Push val on the receiver's stack." self stackp: stackp + 1. self at: stackp put: val! ! !ContextPart methodsFor: 'controlling' stamp: 'hmm 7/17/2001 20:57'! quickSend: selector to: receiver with: arguments super: superFlag "Send the given selector with arguments in an environment which closely resembles the non-simulating environment, with an interjected unwind-protected block to catch nonlocal returns. Attention: don't get lost!!" | oldSender contextToReturnTo result lookupClass | contextToReturnTo := self. lookupClass := superFlag ifTrue: [(self method literalAt: self method numLiterals) value superclass] ifFalse: [receiver class]. [oldSender := thisContext sender swapSender: self. result := receiver perform: selector withArguments: arguments inSuperclass: lookupClass. thisContext sender swapSender: oldSender] ifCurtailed: [ contextToReturnTo := thisContext sender receiver. "The block context returning nonlocally" contextToReturnTo jump: -1. "skip to front of return bytecode causing this unwind" contextToReturnTo nextByte = 16r7C ifTrue: [ "If it was a returnTop, push the value to be returned. Otherwise the value is implicit in the bytecode" contextToReturnTo push: (thisContext sender tempAt: 1)]. thisContext swapSender: thisContext home sender. "Make this block return to the method's sender" contextToReturnTo]. contextToReturnTo push: result. ^contextToReturnTo! ! !ContextPart methodsFor: 'controlling' stamp: 'ajh 5/20/2004 17:32'! restart "Unwind thisContext to self and resume from beginning. Execute unwind blocks when unwinding. ASSUMES self is a sender of thisContext" | ctxt unwindBlock | self isDead ifTrue: [self cannotReturn: nil to: self]. self privRefresh. ctxt := thisContext. [ ctxt := ctxt findNextUnwindContextUpTo: self. ctxt isNil ] whileFalse: [ unwindBlock := ctxt tempAt: 1. unwindBlock ifNotNil: [ ctxt tempAt: 1 put: nil. thisContext terminateTo: ctxt. unwindBlock value]. ]. thisContext terminateTo: self. self jump. ! ! !ContextPart methodsFor: 'controlling' stamp: 'ajh 6/27/2003 22:17'! resume "Roll back thisContext to self and resume. Execute unwind blocks when rolling back. ASSUMES self is a sender of thisContext" self resume: nil! ! !ContextPart methodsFor: 'controlling' stamp: 'ajh 5/20/2004 17:32'! resume: value "Unwind thisContext to self and resume with value as result of last send. Execute unwind blocks when unwinding. ASSUMES self is a sender of thisContext" | ctxt unwindBlock | self isDead ifTrue: [self cannotReturn: value to: self]. ctxt := thisContext. [ ctxt := ctxt findNextUnwindContextUpTo: self. ctxt isNil ] whileFalse: [ unwindBlock := ctxt tempAt: 1. unwindBlock ifNotNil: [ ctxt tempAt: 1 put: nil. thisContext terminateTo: ctxt. unwindBlock value]. ]. thisContext terminateTo: self. ^ value ! ! !ContextPart methodsFor: 'controlling' stamp: 'ajh 1/21/2003 19:27'! return "Unwind until my sender is on top" self return: self receiver! ! !ContextPart methodsFor: 'controlling' stamp: 'ajh 5/20/2004 17:27'! return: value "Unwind thisContext to self and return value to self's sender. Execute any unwind blocks while unwinding. ASSUMES self is a sender of thisContext" sender ifNil: [self cannotReturn: value to: sender]. sender resume: value! ! !ContextPart methodsFor: 'controlling' stamp: 'ajh 1/24/2003 15:30'! return: value to: sendr "Simulate the return of value to sendr." self releaseTo: sendr. sendr ifNil: [^ nil]. ^ sendr push: value! ! !ContextPart methodsFor: 'controlling' stamp: 'ajh 5/20/2004 17:20'! runUntilErrorOrReturnFrom: aSender "ASSUMES aSender is a sender of self. Execute self's stack until aSender returns or an unhandled exception is raised. Return a pair containing the new top context and a possibly nil exception. The exception is not nil if it was raised before aSender returned and it was not handled. The exception is returned rather than openning the debugger, giving the caller the choice of how to handle it." "Self is run by jumping directly to it (the active process abandons thisContext and executes self). However, before jumping to self we insert an ensure block under aSender that jumps back to thisContext when evaluated. We also insert an exception handler under aSender that jumps back to thisContext when an unhandled exception is raised. In either case, the inserted ensure and exception handler are removed once control jumps back to thisContext." | error ctxt here topContext | here := thisContext. "Insert ensure and exception handler contexts under aSender" error := nil. ctxt := aSender insertSender: (ContextPart contextOn: UnhandledError do: [:ex | error ifNil: [ error := ex exception. topContext := thisContext. ex resumeUnchecked: here jump] ifNotNil: [ex pass] ]). ctxt := ctxt insertSender: (ContextPart contextEnsure: [error ifNil: [ topContext := thisContext. here jump] ]). self jump. "Control jumps to self" "Control resumes here once above ensure block or exception handler is executed" ^ error ifNil: [ "No error was raised, remove ensure context by stepping until popped" [ctxt isDead] whileFalse: [topContext := topContext stepToCallee]. {topContext. nil} ] ifNotNil: [ "Error was raised, remove inserted above contexts then return signaler context" aSender terminateTo: ctxt sender. "remove above ensure and handler contexts" {topContext. error} ]. ! ! !ContextPart methodsFor: 'controlling' stamp: 'di 11/26/1999 19:34'! send: selector to: rcvr with: args super: superFlag "Simulate the action of sending a message with selector, selector, and arguments, args, to receiver. The argument, superFlag, tells whether the receiver of the message was specified with 'super' in the source method." | class meth val | class := superFlag ifTrue: [(self method literalAt: self method numLiterals) value superclass] ifFalse: [rcvr class]. meth := class lookupSelector: selector. meth == nil ifTrue: [^ self send: #doesNotUnderstand: to: rcvr with: (Array with: (Message selector: selector arguments: args)) super: superFlag] ifFalse: [val := self tryPrimitiveFor: meth receiver: rcvr args: args. val == PrimitiveFailToken ifFalse: [^ val]. (selector == #doesNotUnderstand: and: [class == ProtoObject]) ifTrue: [^ self error: 'Simulated message ' , (args at: 1) selector , ' not understood']. ^ self activateMethod: meth withArgs: args receiver: rcvr class: class]! ! !ContextPart methodsFor: 'controlling' stamp: 'ajh 1/24/2003 00:56'! terminate "Make myself unresumable." sender := nil. pc := nil. ! ! !ContextPart methodsFor: 'controlling' stamp: 'ar 3/6/2001 14:26'! terminateTo: previousContext "Terminate all the Contexts between me and previousContext, if previousContext is on my Context stack. Make previousContext my sender." | currentContext sendingContext | (self hasSender: previousContext) ifTrue: [ currentContext := sender. [currentContext == previousContext] whileFalse: [ sendingContext := currentContext sender. currentContext terminate. currentContext := sendingContext]]. sender := previousContext! ! !ContextPart methodsFor: 'controlling'! top "Answer the top of the receiver's stack." ^self at: stackp! ! !ContextPart methodsFor: 'debugger access' stamp: 'ajh 9/25/2001 00:12'! contextStack "Answer an Array of the contexts on the receiver's sender chain." ^self stackOfSize: 100000! ! !ContextPart methodsFor: 'debugger access'! depthBelow: aContext "Answer how many calls there are between this and aContext." | this depth | this := self. depth := 0. [this == aContext or: [this == nil]] whileFalse: [this := this sender. depth := depth + 1]. ^depth! ! !ContextPart methodsFor: 'debugger access' stamp: 'stephane.ducasse 5/2/2009 14:58'! errorReportOn: strm "Write a detailed error report on the stack (above me) on a stream. For both the error file, and emailing a bug report. Suppress any errors while getting printStrings. Limit the length." | cnt aContext startPos | strm print: Date today; space; print: Time now; cr. strm cr. strm nextPutAll: 'VM: '; nextPutAll: SmalltalkImage current platformName asString; nextPutAll: ' - '; nextPutAll: SmalltalkImage current platformSubtype asString; nextPutAll: ' - '; nextPutAll: SmalltalkImage current osVersion asString; nextPutAll: ' - '; nextPutAll: SmalltalkImage current vmVersion asString; cr. strm nextPutAll: 'Image: '; nextPutAll: SystemVersion current version asString; nextPutAll: ' ['; nextPutAll: SmalltalkImage current lastUpdateString asString; nextPutAll: ']'; cr. strm cr. SecurityManager default printStateOn: strm. "Note: The following is an open-coded version of ContextPart>>stackOfSize: since this method may be called during a low space condition and we might run out of space for allocating the full stack." cnt := 0. startPos := strm position. aContext := self. [aContext notNil and: [(cnt := cnt + 1) < 40]] whileTrue: [aContext printDetails: strm. "variable values" strm cr. aContext := aContext sender]. strm cr; nextPutAll: '--- The full stack ---'; cr. aContext := self. cnt := 0. [aContext == nil] whileFalse: [cnt := cnt + 1. cnt = 40 ifTrue: [strm nextPutAll: ' - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -'; cr]. strm print: aContext; cr. "just class>>selector" strm position > (startPos+150000) ifTrue: [strm nextPutAll: '...etc...'. ^ self]. "exit early" cnt > 200 ifTrue: [strm nextPutAll: '-- and more not shown --'. ^ self]. aContext := aContext sender].! ! !ContextPart methodsFor: 'debugger access' stamp: 'RAA 5/16/2000 12:14'! longStack "Answer a String showing the top 100 contexts on my sender chain." ^ String streamContents: [:strm | (self stackOfSize: 100) do: [:item | strm print: item; cr]]! ! !ContextPart methodsFor: 'debugger access' stamp: 'md 2/17/2006 18:41'! methodClass "Answer the class in which the receiver's method was found." ^self method methodClass ifNil:[self receiver class].! ! !ContextPart methodsFor: 'debugger access' stamp: 'eem 7/17/2008 14:49'! namedTempAt: index "Answer the value of the temp at index in the receiver's sequence of tempNames." ^self debuggerMap namedTempAt: index in: self! ! !ContextPart methodsFor: 'debugger access' stamp: 'eem 6/24/2008 12:24'! namedTempAt: index put: aValue "Set the value of the temp at index in the receiver's sequence of tempNames. (Note that if the value is a copied value it is also set out along the lexical chain, but alas not in along the lexical chain.)." ^self debuggerMap namedTempAt: index put: aValue in: self! ! !ContextPart methodsFor: 'debugger access' stamp: 'ar 7/13/2007 16:52'! print: anObject on: aStream "Safely print anObject in the face of direct ProtoObject subclasses" | title | (anObject class canUnderstand: #printOn:) ifTrue:[^anObject printOn: aStream]. title := anObject class name. aStream nextPutAll: (title first isVowel ifTrue: ['an '] ifFalse: ['a ']); nextPutAll: title! ! !ContextPart methodsFor: 'debugger access'! release "Remove information from the receiver and all of the contexts on its sender chain in order to break circularities." self releaseTo: nil! ! !ContextPart methodsFor: 'debugger access'! releaseTo: caller "Remove information from the receiver and the contexts on its sender chain up to caller in order to break circularities." | c s | c := self. [c == nil or: [c == caller]] whileFalse: [s := c sender. c singleRelease. c := s]! ! !ContextPart methodsFor: 'debugger access' stamp: 'md 2/17/2006 18:47'! selector "Answer the selector of the method that created the receiver." ^self method selector ifNil: [self method defaultSelector].! ! !ContextPart methodsFor: 'debugger access'! sender "Answer the context that sent the message that created the receiver." ^sender! ! !ContextPart methodsFor: 'debugger access' stamp: 'di 8/31/1999 09:42'! shortStack "Answer a String showing the top ten contexts on my sender chain." ^ String streamContents: [:strm | (self stackOfSize: 10) do: [:item | strm print: item; cr]]! ! !ContextPart methodsFor: 'debugger access' stamp: 'ajh 1/24/2003 00:03'! singleRelease "Remove information from the receiver in order to break circularities." stackp == nil ifFalse: [1 to: stackp do: [:i | self at: i put: nil]]. sender := nil. pc := nil. ! ! !ContextPart methodsFor: 'debugger access' stamp: 'md 2/22/2006 16:58'! sourceCode ^self method getSource. "Note: The above is a bit safer than ^ methodClass sourceCodeAt: selector which may fail if the receiver's method has been changed in the debugger (e.g., the method is no longer in the methodDict and thus the above selector is something like #Doit:with:with:with:) but the source code is still available."! ! !ContextPart methodsFor: 'debugger access'! stack "Answer an Array of the contexts on the receiver's sender chain." ^self stackOfSize: 9999! ! !ContextPart methodsFor: 'debugger access' stamp: 'eem 6/1/2008 09:43'! stackOfSize: limit "Answer an OrderedCollection of the top 'limit' contexts on the receiver's sender chain." | stack ctxt | stack := OrderedCollection new. stack addLast: (ctxt := self). [(ctxt := ctxt sender) ~~ nil and: [stack size < limit]] whileTrue: [stack addLast: ctxt]. ^stack! ! !ContextPart methodsFor: 'debugger access'! swapSender: coroutine "Replace the receiver's sender with coroutine and answer the receiver's previous sender. For use in coroutining." | oldSender | oldSender := sender. sender := coroutine. ^oldSender! ! !ContextPart methodsFor: 'debugger access' stamp: 'eem 6/10/2008 09:42'! tempNames "Answer a SequenceableCollection of the names of the receiver's temporary variables, which are strings." ^ self debuggerMap tempNamesForContext: self! ! !ContextPart methodsFor: 'debugger access' stamp: 'JorgeRessia 10/18/2009 12:42'! tempScopedNames "Answer a SequenceableCollection of the names of the receiver's temporary variables, which are strings." ^ self debuggerMap tempNamesScopedForContext: self! ! !ContextPart methodsFor: 'debugger access' stamp: 'eem 6/10/2008 09:47'! tempsAndValues "Return a string of the temporary variabls and their current values" ^self debuggerMap tempsAndValuesForContext: self! ! !ContextPart methodsFor: 'debugger access' stamp: 'JorgeRessia 10/18/2009 12:42'! tempsAndValuesLimitedTo: sizeLimit indent: indent "Return a string of the temporary variabls and their current values" | aStream | aStream := (String new: 100) writeStream. self tempScopedNames doWithIndex: [:title :index | indent timesRepeat: [aStream tab]. aStream nextPutAll: title; nextPut: $:; space; tab. aStream nextPutAll: ((self tempAt: index) printStringLimitedTo: (sizeLimit -3 -title size max: 1)). aStream cr]. ^aStream contents! ! !ContextPart methodsFor: 'instruction decoding'! doDup "Simulate the action of a 'duplicate top of stack' bytecode." self push: self top! ! !ContextPart methodsFor: 'instruction decoding'! doPop "Simulate the action of a 'remove top of stack' bytecode." self pop! ! !ContextPart methodsFor: 'instruction decoding'! jump: distance "Simulate the action of a 'unconditional jump' bytecode whose offset is the argument, distance." pc := pc + distance! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'ajh 7/6/2003 20:38'! jump: distance if: condition "Simulate the action of a 'conditional jump' bytecode whose offset is the argument, distance, and whose condition is the argument, condition." | bool | bool := self pop. (bool == true or: [bool == false]) ifFalse: [ ^self send: #mustBeBooleanIn: to: bool with: {self} super: false]. (bool eqv: condition) ifTrue: [self jump: distance]! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 6/15/2008 11:27'! methodReturnConstant: value "Simulate the action of a 'return constant' bytecode whose value is the argument, value. This corresponds to a source expression like '^0'." ^self return: value from: self methodReturnContext! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 6/15/2008 11:27'! methodReturnReceiver "Simulate the action of a 'return receiver' bytecode. This corresponds to the source expression '^self'." ^self return: self receiver from: self methodReturnContext! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 6/15/2008 11:27'! methodReturnTop "Simulate the action of a 'return top of stack' bytecode. This corresponds to source expressions like '^something'." ^self return: self pop from: self methodReturnContext! ! !ContextPart methodsFor: 'instruction decoding'! popIntoLiteralVariable: value "Simulate the action of bytecode that removes the top of the stack and stores it into a literal variable of my method." value value: self pop! ! !ContextPart methodsFor: 'instruction decoding'! popIntoReceiverVariable: offset "Simulate the action of bytecode that removes the top of the stack and stores it into an instance variable of my receiver." self receiver instVarAt: offset + 1 put: self pop! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 5/27/2008 11:38'! popIntoRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex "Simulate the action of bytecode that removes the top of the stack and stores it into an offset in one of my local variables being used as a remote temp vector." (self at: tempVectorIndex + 1) at: remoteTempIndex + 1 put: self pop! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 6/15/2008 11:34'! popIntoTemporaryVariable: offset "Simulate the action of bytecode that removes the top of the stack and stores it into one of my temporary variables." self contextForLocalVariables at: offset + 1 put: self pop! ! !ContextPart methodsFor: 'instruction decoding'! pushActiveContext "Simulate the action of bytecode that pushes the the active context on the top of its own stack." self push: self! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 8/29/2008 06:28'! pushClosureCopyNumCopiedValues: numCopied numArgs: numArgs blockSize: blockSize "Simulate the action of a 'closure copy' bytecode whose result is the new BlockClosure for the following code" | copiedValues | numCopied > 0 ifTrue: [copiedValues := Array new: numCopied. numCopied to: 1 by: -1 do: [:i| copiedValues at: i put: self pop]] ifFalse: [copiedValues := nil]. self push: (BlockClosure outerContext: self startpc: pc numArgs: numArgs copiedValues: copiedValues). self jump: blockSize! ! !ContextPart methodsFor: 'instruction decoding'! pushConstant: value "Simulate the action of bytecode that pushes the constant, value, on the top of the stack." self push: value! ! !ContextPart methodsFor: 'instruction decoding'! pushLiteralVariable: value "Simulate the action of bytecode that pushes the contents of the literal variable whose index is the argument, index, on the top of the stack." self push: value value! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 5/27/2008 11:32'! pushNewArrayOfSize: arraySize self push: (Array new: arraySize)! ! !ContextPart methodsFor: 'instruction decoding'! pushReceiver "Simulate the action of bytecode that pushes the active context's receiver on the top of the stack." self push: self receiver! ! !ContextPart methodsFor: 'instruction decoding'! pushReceiverVariable: offset "Simulate the action of bytecode that pushes the contents of the receiver's instance variable whose index is the argument, index, on the top of the stack." self push: (self receiver instVarAt: offset + 1)! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 5/27/2008 11:44'! pushRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex "Simulate the action of bytecode that pushes the value at remoteTempIndex in one of my local variables being used as a remote temp vector." self push: ((self at: tempVectorIndex + 1) at: remoteTempIndex + 1)! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 6/15/2008 11:34'! pushTemporaryVariable: offset "Simulate the action of bytecode that pushes the contents of the temporary variable whose index is the argument, index, on the top of the stack." self push: (self contextForLocalVariables at: offset + 1)! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'ajh 3/5/2004 03:44'! return: value from: aSender "For simulation. Roll back self to aSender and return value from it. Execute any unwind blocks on the way. ASSUMES aSender is a sender of self" | newTop ctxt | aSender isDead ifTrue: [ ^ self send: #cannotReturn: to: self with: {value} super: false]. newTop := aSender sender. ctxt := self findNextUnwindContextUpTo: newTop. ctxt ifNotNil: [ ^ self send: #aboutToReturn:through: to: self with: {value. ctxt} super: false]. self releaseTo: newTop. newTop ifNotNil: [newTop push: value]. ^ newTop ! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'hmm 7/17/2001 20:52'! send: selector super: superFlag numArgs: numArgs "Simulate the action of bytecodes that send a message with selector, selector. The argument, superFlag, tells whether the receiver of the message was specified with 'super' in the source method. The arguments of the message are found in the top numArgs locations on the stack and the receiver just below them." | receiver arguments answer | arguments := Array new: numArgs. numArgs to: 1 by: -1 do: [ :i | arguments at: i put: self pop]. receiver := self pop. selector == #doPrimitive:method:receiver:args: ifTrue: [answer := receiver doPrimitive: (arguments at: 1) method: (arguments at: 2) receiver: (arguments at: 3) args: (arguments at: 4). self push: answer. ^self]. QuickStep == self ifTrue: [ QuickStep := nil. ^self quickSend: selector to: receiver with: arguments super: superFlag]. ^self send: selector to: receiver with: arguments super: superFlag! ! !ContextPart methodsFor: 'instruction decoding'! storeIntoLiteralVariable: value "Simulate the action of bytecode that stores the top of the stack into a literal variable of my method." value value: self top! ! !ContextPart methodsFor: 'instruction decoding'! storeIntoReceiverVariable: offset "Simulate the action of bytecode that stores the top of the stack into an instance variable of my receiver." self receiver instVarAt: offset + 1 put: self top! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 5/27/2008 11:53'! storeIntoRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex "Simulate the action of bytecode that stores the top of the stack at an offset in one of my local variables being used as a remote temp vector." (self at: tempVectorIndex + 1) at: remoteTempIndex + 1 put: self top! ! !ContextPart methodsFor: 'instruction decoding' stamp: 'eem 6/15/2008 11:34'! storeIntoTemporaryVariable: offset "Simulate the action of bytecode that stores the top of the stack into one of my temporary variables." self contextForLocalVariables at: offset + 1 put: self top! ! !ContextPart methodsFor: 'objects from disk' stamp: 'tk 9/28/2000 22:54'! storeDataOn: aDataStream "Contexts are not allowed go to out in DataStreams. They must be included inside an ImageSegment." aDataStream insideASegment ifTrue: [^ super storeDataOn: aDataStream]. self error: 'This Context was not included in the ImageSegment'. "or perhaps ImageSegments were not used at all" ^ nil! ! !ContextPart methodsFor: 'printing' stamp: 'tk 10/19/2001 11:24'! printDetails: strm "Put my class>>selector and arguments and temporaries on the stream. Protect against errors during printing." | str | self printOn: strm. strm cr; tab; nextPutAll: 'Arguments and temporary variables: '; cr. str := [self tempsAndValuesLimitedTo: 80 indent: 2] ifError: [:err :rcvr | '<>']. strm nextPutAll: str. strm peekLast == Character cr ifFalse: [strm cr].! ! !ContextPart methodsFor: 'printing' stamp: 'md 2/17/2006 15:41'! printOn: aStream | selector class mclass | self method == nil ifTrue: [^ super printOn: aStream]. class := self receiver class. mclass := self methodClass. selector := self selector ifNil:[self method defaultSelector]. aStream nextPutAll: class name. mclass == class ifFalse: [aStream nextPut: $(. aStream nextPutAll: mclass name. aStream nextPut: $)]. aStream nextPutAll: '>>'. aStream nextPutAll: selector. selector = #doesNotUnderstand: ifTrue: [ aStream space. (self tempAt: 1) selector printOn: aStream. ]. ! ! !ContextPart methodsFor: 'query' stamp: 'ajh 7/21/2003 09:59'! bottomContext "Return the last context (the first context invoked) in my sender chain" ^ self findContextSuchThat: [:c | c sender isNil]! ! !ContextPart methodsFor: 'query' stamp: 'ajh 1/27/2003 18:35'! copyStack ^ self copyTo: nil! ! !ContextPart methodsFor: 'query' stamp: 'ajh 1/27/2003 21:20'! copyTo: aContext "Copy self and my sender chain down to, but not including, aContext. End of copied chain will have nil sender. BlockContexts whose home is also copied will point to the copy. However, blockContexts that are not on the stack but may be later will not have their home pointing in the new copied thread. So an error will be raised if one of these tries to return directly to its home. It is best to use BlockClosures instead. They only hold a ContextTag, which will work for all copies of the original home context." ^ self copyTo: aContext blocks: IdentityDictionary new! ! !ContextPart methodsFor: 'query' stamp: 'ajh 1/24/2003 00:12'! findContextSuchThat: testBlock "Search self and my sender chain for first one that satisfies testBlock. Return nil if none satisfy" | ctxt | ctxt := self. [ctxt isNil] whileFalse: [ (testBlock value: ctxt) ifTrue: [^ ctxt]. ctxt := ctxt sender. ]. ^ nil! ! !ContextPart methodsFor: 'query' stamp: 'md 1/20/2006 16:15'! findSecondToOldestSimilarSender "Search the stack for the second-to-oldest occurance of self's method. Very useful for an infinite recursion. Gets back to the second call so you can see one complete recursion cycle, and how it was called at the beginning." | sec ctxt bot | sec := self. ctxt := self. [ bot := ctxt findSimilarSender. bot isNil ] whileFalse: [ sec := ctxt. ctxt := bot. ]. ^ sec ! ! !ContextPart methodsFor: 'query' stamp: 'md 1/20/2006 16:14'! findSimilarSender "Return the closest sender with the same method, return nil if none found" | meth | meth := self method. ^ self sender findContextSuchThat: [:c | c method == meth]! ! !ContextPart methodsFor: 'query' stamp: 'ajh 1/24/2003 19:42'! hasContext: aContext "Answer whether aContext is me or one of my senders" ^ (self findContextSuchThat: [:c | c == aContext]) notNil! ! !ContextPart methodsFor: 'query' stamp: 'eem 12/31/2008 11:28'! isBottomContext "Answer if this is the last context (the first context invoked) in my sender chain" ^sender isNil! ! !ContextPart methodsFor: 'query' stamp: 'md 1/20/2006 16:14'! isClosureContext ^ false! ! !ContextPart methodsFor: 'query' stamp: 'eem 11/26/2008 20:21'! isContext ^true! ! !ContextPart methodsFor: 'query' stamp: 'ajh 1/24/2003 00:04'! isDead "Has self finished" ^ pc isNil! ! !ContextPart methodsFor: 'query' stamp: 'ajh 1/24/2003 22:28'! secondFromBottom "Return the second from bottom of my sender chain" self sender ifNil: [^ nil]. ^ self findContextSuchThat: [:c | c sender sender isNil]! ! !ContextPart methodsFor: 'system simulation' stamp: 'hmm 7/30/2001 20:43'! completeCallee: aContext "Simulate the execution of bytecodes until a return to the receiver." | ctxt current ctxt1 | ctxt := aContext. [ctxt == current or: [ctxt hasSender: self]] whileTrue: [current := ctxt. ctxt1 := ctxt quickStep. ctxt1 ifNil: [self halt]. ctxt := ctxt1]. ^self stepToSendOrReturn! ! !ContextPart methodsFor: 'system simulation' stamp: 'hmm 7/15/2001 20:58'! quickStep "If the next instruction is a send, just perform it. Otherwise, do a normal step." self willReallySend ifTrue: [QuickStep := self]. ^self step! ! !ContextPart methodsFor: 'system simulation' stamp: 'eem 6/16/2008 15:39'! runSimulated: aBlock contextAtEachStep: block2 "Simulate the execution of the argument, aBlock, until it ends. aBlock MUST NOT contain an '^'. Evaluate block2 with the current context prior to each instruction executed. Answer the simulated value of aBlock." | current | aBlock hasMethodReturn ifTrue: [self error: 'simulation of blocks with ^ can run loose']. current := aBlock asContext. current pushArgs: Array new from: self. [current == self] whileFalse: [block2 value: current. current := current step]. ^self pop! ! !ContextPart methodsFor: 'system simulation'! step "Simulate the execution of the receiver's next bytecode. Answer the context that would be the active context after this bytecode." ^self interpretNextInstructionFor: self! ! !ContextPart methodsFor: 'system simulation' stamp: 'ajh 1/24/2003 22:54'! stepToCallee "Step to callee or sender" | ctxt | ctxt := self. [(ctxt := ctxt step) == self] whileTrue. ^ ctxt! ! !ContextPart methodsFor: 'system simulation' stamp: 'hmm 7/30/2001 20:48'! stepToSendOrReturn "Simulate the execution of bytecodes until either sending a message or returning a value to the receiver (that is, until switching contexts)." | ctxt | [self willReallySend | self willReturn | self willStore] whileFalse: [ ctxt := self step. ctxt == self ifFalse: [self halt. "Caused by mustBeBoolean handling" ^ctxt]]! ! !ContextPart methodsFor: 'private' stamp: 'ajh 5/20/2004 16:27'! activateReturn: aContext value: value "Activate 'aContext return: value' in place of self, so execution will return to aContext's sender" ^ self activateMethod: ContextPart theReturnMethod withArgs: {value} receiver: aContext class: aContext class! ! !ContextPart methodsFor: 'private' stamp: 'ajh 6/29/2003 15:32'! cannotReturn: result to: homeContext "The receiver tried to return result to homeContext that no longer exists." ^ BlockCannotReturn new result: result; deadHome: homeContext; signal! ! !ContextPart methodsFor: 'private' stamp: 'ajh 1/27/2003 21:18'! copyTo: aContext blocks: dict "Copy self and my sender chain down to, but not including, aContext. End of copied chain will have nil sender. BlockContexts whose home is also copied will point to the copy. However, blockContexts that are not on the stack but may be later will not have their home pointing in the new copied thread. So an error will be raised if one of these tries to return directly to its home." | copy | self == aContext ifTrue: [^ nil]. copy := self copy. dict at: self ifPresent: [:blocks | blocks do: [:b | b privHome: copy]]. self sender ifNotNil: [ copy privSender: (self sender copyTo: aContext blocks: dict)]. ^ copy! ! !ContextPart methodsFor: 'private' stamp: 'ajh 1/24/2003 00:50'! cut: aContext "Cut aContext and its senders from my sender chain" | ctxt callee | ctxt := self. [ctxt == aContext] whileFalse: [ callee := ctxt. ctxt := ctxt sender. ctxt ifNil: [aContext ifNotNil: [self error: 'aContext not a sender']]. ]. callee privSender: nil. ! ! !ContextPart methodsFor: 'private' stamp: 'MMP 8/3/2009 13:12'! doPrimitive: primitiveIndex method: meth receiver: receiver args: arguments "Simulate a primitive method whose index is primitiveIndex. The simulated receiver and arguments are given as arguments to this message. Any primitive which provikes execution needs to be intercepted and simulated to avoid execution running away." | value | "Simulation guard" "If successful, push result and return resuming context, else ^ PrimitiveFailToken" (primitiveIndex = 19) ifTrue: [ToolSet debugContext: self label:'Code simulation error' contents: nil]. "ContextPart>>blockCopy:; simulated to get startpc right" (primitiveIndex = 80 and: [receiver isKindOf: ContextPart]) ifTrue: [^self push: ((BlockContext newForMethod: receiver method) home: receiver home startpc: pc + 2 nargs: (arguments at: 1))]. (primitiveIndex = 81 and: [receiver isMemberOf: BlockContext]) "BlockContext>>value[:value:...]" ifTrue: [^receiver pushArgs: arguments from: self]. (primitiveIndex = 82 and: [receiver isMemberOf: BlockContext]) "BlockContext>>valueWithArguments:" ifTrue: [^receiver pushArgs: arguments first from: self]. primitiveIndex = 83 "afr 9/11/1998 19:50" "Object>>perform:[with:...]" ifTrue: [^self send: arguments first to: receiver with: arguments allButFirst super: false]. primitiveIndex = 84 "afr 9/11/1998 19:50" "Object>>perform:withArguments:" ifTrue: [^self send: arguments first to: receiver with: (arguments at: 2) super: false]. primitiveIndex = 188 ifTrue: "eem 5/27/2008 11:10 Object>>withArgs:executeMethod:" [^MethodContext sender: self receiver: receiver method: (arguments at: 2) arguments: (arguments at: 1)]. "Closure primitives" (primitiveIndex = 200 and: [receiver == self]) ifTrue: "ContextPart>>closureCopy:copiedValues:; simulated to get startpc right" [^self push: (BlockClosure outerContext: receiver startpc: pc + 2 numArgs: arguments first copiedValues: arguments last)]. ((primitiveIndex between: 201 and: 205) "BlockClosure>>value[:value:...]" or: [primitiveIndex between: 221 and: 222]) ifTrue: "BlockClosure>>valueNoContextSwitch[:]" [^receiver simulateValueWithArguments: arguments caller: self]. primitiveIndex = 206 ifTrue: "BlockClosure>>valueWithArguments:" [^receiver simulateValueWithArguments: arguments first caller: self]. primitiveIndex = 120 ifTrue:[ "FFI method" value := meth literals first tryInvokeWithArguments: arguments. ] ifFalse:[ arguments size > 6 ifTrue: [^PrimitiveFailToken]. value := primitiveIndex = 117 "named primitives" ifTrue:[self tryNamedPrimitiveIn: meth for: receiver withArgs: arguments] ifFalse:[receiver tryPrimitive: primitiveIndex withArgs: arguments]. ]. ^value == PrimitiveFailToken ifTrue: [PrimitiveFailToken] ifFalse: [self push: value]! ! !ContextPart methodsFor: 'private' stamp: 'ajh 7/21/2003 09:59'! insertSender: aContext "Insert aContext and its sender chain between me and my sender. Return new callee of my original sender." | ctxt | ctxt := aContext bottomContext. ctxt privSender: self sender. self privSender: aContext. ^ ctxt! ! !ContextPart methodsFor: 'private' stamp: 'ajh 1/23/2003 22:35'! privSender: aContext sender := aContext! ! !ContextPart methodsFor: 'private' stamp: 'di 1/11/1999 10:12'! push: numObjects fromIndexable: anIndexableCollection "Push the elements of anIndexableCollection onto the receiver's stack. Do not call directly. Called indirectly by {1. 2. 3} constructs." 1 to: numObjects do: [:i | self push: (anIndexableCollection at: i)]! ! !ContextPart methodsFor: 'private' stamp: 'eem 1/19/2009 10:23'! stackPtr "For use only by the SystemTracer and the Debugger, Inspectors etc" ^ stackp! ! !ContextPart methodsFor: 'private' stamp: 'di 10/23/1999 17:31'! stackp: newStackp "Storing into the stack pointer is a potentially dangerous thing. This primitive stores nil into any cells that become accessible as a result, and it performs the entire operation atomically." "Once this primitive is implemented, failure code should cause an error" self error: 'stackp store failure'. " stackp == nil ifTrue: [stackp := 0]. newStackp > stackp 'effectively checks that it is a number' ifTrue: [oldStackp := stackp. stackp := newStackp. 'Nil any newly accessible cells' oldStackp + 1 to: stackp do: [:i | self at: i put: nil]] ifFalse: [stackp := newStackp] "! ! !ContextPart methodsFor: 'private' stamp: 'ar 5/25/2000 20:41'! tryNamedPrimitiveIn: aCompiledMethod for: aReceiver withArgs: arguments "Hack. Attempt to execute the named primitive from the given compiled method" | selector theMethod spec | arguments size > 8 ifTrue:[^PrimitiveFailToken]. selector := #( tryNamedPrimitive tryNamedPrimitive: tryNamedPrimitive:with: tryNamedPrimitive:with:with: tryNamedPrimitive:with:with:with: tryNamedPrimitive:with:with:with:with: tryNamedPrimitive:with:with:with:with:with: tryNamedPrimitive:with:with:with:with:with:with: tryNamedPrimitive:with:with:with:with:with:with:with:) at: arguments size+1. theMethod := aReceiver class lookupSelector: selector. theMethod == nil ifTrue:[^PrimitiveFailToken]. spec := theMethod literalAt: 1. spec replaceFrom: 1 to: spec size with: (aCompiledMethod literalAt: 1) startingAt: 1. ^aReceiver perform: selector withArguments: arguments! ! !ContextPart methodsFor: 'private' stamp: 'ar 5/25/2000 20:45'! tryPrimitiveFor: method receiver: receiver args: arguments "If this method has a primitive index, then run the primitive and return its result. Otherwise (and also if the primitive fails) return PrimitiveFailToken, as an indication that the method should be activated and run as bytecodes." | primIndex | (primIndex := method primitive) = 0 ifTrue: [^ PrimitiveFailToken]. ^ self doPrimitive: primIndex method: method receiver: receiver args: arguments! ! !ContextPart methodsFor: 'private-exceptions' stamp: 'ajh 2/1/2003 01:30'! canHandleSignal: exception "Sent to handler (on:do:) contexts only. If my exception class (first arg) handles exception then return true, otherwise forward this message to the next handler context. If none left, return false (see nil>>canHandleSignal:)" ^ (((self tempAt: 1) handles: exception) and: [self tempAt: 3]) or: [self nextHandlerContext canHandleSignal: exception]. ! ! !ContextPart methodsFor: 'private-exceptions' stamp: 'TPR 8/28/2000 19:27'! findNextHandlerContextStarting "Return the next handler marked context, returning nil if there is none. Search starts with self and proceeds up to nil." | ctx | ctx := self. [ctx isHandlerContext ifTrue:[^ctx]. (ctx := ctx sender) == nil ] whileFalse. ^nil! ! !ContextPart methodsFor: 'private-exceptions' stamp: 'TPR 8/23/2000 16:37'! findNextUnwindContextUpTo: aContext "Return the next unwind marked above the receiver, returning nil if there is none. Search proceeds up to but not including aContext." | ctx | ctx := self. [(ctx := ctx sender) == nil or: [ctx == aContext]] whileFalse: [ ctx isUnwindContext ifTrue: [^ctx]]. ^nil! ! !ContextPart methodsFor: 'private-exceptions' stamp: 'ajh 6/27/2003 20:47'! handleSignal: exception "Sent to handler (on:do:) contexts only. If my exception class (first arg) handles exception then execute my handle block (second arg), otherwise forward this message to the next handler context. If none left, execute exception's defaultAction (see nil>>handleSignal:)." | val | (((self tempAt: 1) handles: exception) and: [self tempAt: 3]) ifFalse: [ ^ self nextHandlerContext handleSignal: exception]. exception privHandlerContext: self contextTag. self tempAt: 3 put: false. "disable self while executing handle block" val := [(self tempAt: 2) valueWithPossibleArgs: {exception}] ensure: [self tempAt: 3 put: true]. self return: val. "return from self if not otherwise directed in handle block" ! ! !ContextPart methodsFor: 'private-exceptions' stamp: 'tpr 2/24/2001 21:29'! isHandlerContext ^false! ! !ContextPart methodsFor: 'private-exceptions' stamp: 'TPR 8/28/2000 15:45'! isUnwindContext ^false! ! !ContextPart methodsFor: 'private-exceptions' stamp: 'ajh 2/1/2003 00:20'! nextHandlerContext ^ self sender findNextHandlerContextStarting! ! !ContextPart methodsFor: 'private-exceptions' stamp: 'ajh 1/21/2003 17:59'! unwindTo: aContext | ctx unwindBlock | ctx := self. [(ctx := ctx findNextUnwindContextUpTo: aContext) isNil] whileFalse: [ unwindBlock := ctx tempAt: 1. unwindBlock == nil ifFalse: [ ctx tempAt: 1 put: nil. unwindBlock value] ]. ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ContextPart class instanceVariableNames: ''! !ContextPart class methodsFor: 'examples'! tallyInstructions: aBlock "This method uses the simulator to count the number of occurrences of each of the Smalltalk instructions executed during evaluation of aBlock. Results appear in order of the byteCode set." | tallies | tallies := Bag new. thisContext sender runSimulated: aBlock contextAtEachStep: [:current | tallies add: current nextByte]. ^tallies sortedElements "ContextPart tallyInstructions: [3.14159 printString]"! ! !ContextPart class methodsFor: 'examples'! tallyMethods: aBlock "This method uses the simulator to count the number of calls on each method invoked in evaluating aBlock. Results are given in order of decreasing counts." | prev tallies | tallies := Bag new. prev := aBlock. thisContext sender runSimulated: aBlock contextAtEachStep: [:current | current == prev ifFalse: "call or return" [prev sender == nil ifFalse: "call only" [tallies add: current printString]. prev := current]]. ^tallies sortedCounts "ContextPart tallyMethods: [3.14159 printString]"! ! !ContextPart class methodsFor: 'examples' stamp: 'sma 4/22/2000 17:03'! trace: aBlock "ContextPart trace: [3 factorial]" "This method uses the simulator to print calls and returned values in the Transcript." Transcript clear. ^ self trace: aBlock on: Transcript! ! !ContextPart class methodsFor: 'examples' stamp: 'AdrianLienhard 10/11/2009 19:39'! trace: aBlock on: aStream "ContextPart trace: [3 factorial]" "This method uses the simulator to print calls to a file." | prev | prev := aBlock. ^ thisContext sender runSimulated: aBlock contextAtEachStep: [:current | Sensor anyButtonPressed ifTrue: [^ nil]. current == prev ifFalse: [prev sender ifNil: [ "Following does not work anymore due to closures?" " aStream space; nextPut: $^. self carefullyPrint: current top on: aStream "]. aStream cr. (current depthBelow: aBlock) timesRepeat: [aStream space]. self carefullyPrint: current receiver on: aStream. aStream space; nextPutAll: current selector; flush. prev := current]]! ! !ContextPart class methodsFor: 'examples' stamp: 'sma 4/22/2000 17:05'! trace: aBlock onFileNamed: fileName "ContextPart trace: [3 factorial] onFileNamed: 'trace'" "This method uses the simulator to print calls to a file." | aStream | ^ [aStream := FileStream fileNamed: fileName. self trace: aBlock on: aStream] ensure: [aStream close]! ! !ContextPart class methodsFor: 'instance creation' stamp: 'di 10/23/1999 17:09'! basicNew: size self error: 'Contexts must only be created with newForMethod:'! ! !ContextPart class methodsFor: 'instance creation' stamp: 'sw 5/5/2000 00:30'! initializedInstance ^ nil! ! !ContextPart class methodsFor: 'instance creation' stamp: 'di 10/23/1999 17:09'! new self error: 'Contexts must only be created with newForMethod:'! ! !ContextPart class methodsFor: 'instance creation' stamp: 'di 10/23/1999 17:09'! new: size self error: 'Contexts must only be created with newForMethod:'! ! !ContextPart class methodsFor: 'instance creation' stamp: 'di 10/23/1999 17:55'! newForMethod: aMethod "This is the only method for creating new contexts, other than primitive cloning. Any other attempts, such as inherited methods like shallowCopy, should be avoided or must at least be rewritten to determine the proper size from the method being activated. This is because asking a context its size (even basicSize!!) will not return the real object size but only the number of fields currently accessible, as determined by stackp." ^ super basicNew: aMethod frameSize! ! !ContextPart class methodsFor: 'simulation' stamp: 'di 2/10/1999 22:15'! initialize "A unique object to be returned when a primitive fails during simulation" PrimitiveFailToken := Object new ! ! !ContextPart class methodsFor: 'simulation' stamp: 'di 2/10/1999 22:15'! primitiveFailToken ^ PrimitiveFailToken! ! !ContextPart class methodsFor: 'simulation'! runSimulated: aBlock "Simulate the execution of the argument, current. Answer the result it returns." ^ thisContext sender runSimulated: aBlock contextAtEachStep: [:ignored] "ContextPart runSimulated: [Pen new defaultNib: 5; go: 100]"! ! !ContextPart class methodsFor: 'special context creation' stamp: 'ajh 1/24/2003 14:31'! contextEnsure: block "Create an #ensure: context that is ready to return from executing its receiver" | ctxt chain | ctxt := thisContext. [chain := thisContext sender cut: ctxt. ctxt jump] ensure: block. "jump above will resume here without unwinding chain" ^ chain! ! !ContextPart class methodsFor: 'special context creation' stamp: 'ajh 1/24/2003 14:31'! contextOn: exceptionClass do: block "Create an #on:do: context that is ready to return from executing its receiver" | ctxt chain | ctxt := thisContext. [chain := thisContext sender cut: ctxt. ctxt jump] on: exceptionClass do: block. "jump above will resume here without unwinding chain" ^ chain! ! !ContextPart class methodsFor: 'special context creation' stamp: 'ajh 5/20/2004 16:25'! theReturnMethod | meth | meth := self lookupSelector: #return:. meth primitive = 0 ifFalse: [^ self error: 'expected #return: to not be a primitive']. ^ meth! ! !ContextPart class methodsFor: 'private' stamp: 'sma 4/22/2000 17:01'! carefullyPrint: anObject on: aStream aStream nextPutAll: ([anObject printString] on: Error do: ['unprintable ' , anObject class name])! ! !ContextPart class methodsFor: 'private' stamp: 'eem 6/19/2008 10:00'! isContextClass ^true! ! Inspector subclass: #ContextVariablesInspector instanceVariableNames: 'fieldList' classVariableNames: '' poolDictionaries: '' category: 'Tools-Debugger'! !ContextVariablesInspector commentStamp: '' prior: 0! I represent a query path into the internal representation of a ContextPart. Typically this is a context at a point in the query path of a Debugger. As a StringHolder, the string I represent is the value of the currently selected variable of the observed temporary variable of the context.! !ContextVariablesInspector methodsFor: 'accessing' stamp: 'HenrikSperreJohansen 10/17/2009 10:25'! contents ^super contents! ! !ContextVariablesInspector methodsFor: 'accessing' stamp: 'eem 5/21/2008 12:31'! fieldList "Refer to the comment in Inspector|fieldList." object == nil ifTrue: [^Array with: 'thisContext']. ^fieldList ifNil:[fieldList := (Array with: 'thisContext' with: 'stack top' with: 'all temp vars') , object tempNames]! ! !ContextVariablesInspector methodsFor: 'accessing' stamp: 'ar 4/11/2006 02:33'! inspect: anObject "Initialize the receiver so that it is inspecting anObject. There is no current selection. Because no object's inspectorClass method answers this class, it is OK for this method to override Inspector >> inspect: " fieldList := nil. object := anObject. self initialize. ! ! !ContextVariablesInspector methodsFor: 'code'! doItContext ^object! ! !ContextVariablesInspector methodsFor: 'code'! doItReceiver ^object receiver! ! !ContextVariablesInspector methodsFor: 'selecting' stamp: 'eem 7/18/2008 11:18'! replaceSelectionValue: anObject "Refer to the comment in Inspector|replaceSelectionValue:." ^selectionIndex = 1 ifTrue: [object] ifFalse: [object namedTempAt: selectionIndex - 3 put: anObject]! ! !ContextVariablesInspector methodsFor: 'selecting' stamp: 'eem 6/10/2008 09:37'! selection "Refer to the comment in Inspector|selection." selectionIndex = 0 ifTrue:[^'']. selectionIndex = 1 ifTrue: [^object]. selectionIndex = 2 ifTrue: [^object stackPtr > 0 ifTrue: [object top]]. selectionIndex = 3 ifTrue: [^object tempsAndValues]. ^object debuggerMap namedTempAt: selectionIndex - 3 in: object! ! !ContextVariablesInspector methodsFor: 'nil' stamp: 'HenrikSperreJohansen 10/17/2009 10:39'! contentsIsString "Hacked so contents empty when deselected" ^ #(0 3) includes: selectionIndex! ! PluggableButtonMorphPlus subclass: #ControlButtonMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !ControlButtonMorph commentStamp: 'gvc 9/23/2008 12:04' prior: 0! Specially themed "control" button. Used for drop-lists, expanders etc.! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:23'! disabledBorderStyle "Return the disabled borderStyle of the receiver." ^self theme controlButtonDisabledBorderStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:24'! disabledFillStyle "Return the disabled fillStyle of the receiver." ^self theme controlButtonDisabledFillStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/5/2008 14:58'! initialize "Initialize the receiver." super initialize. self layoutInset: (self theme controlButtonLabelInsetFor: self)! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/28/2009 17:12'! minWidth "Consult the theme also." ^self perform: #minWidth withArguments: #() inSuperclass: Morph! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:23'! mouseOverBorderStyle "Return the mouse over borderStyle of the receiver." ^self theme controlButtonMouseOverBorderStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:23'! mouseOverFillStyle "Return the mouse over fillStyle of the receiver." ^self theme controlButtonMouseOverFillStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:23'! normalBorderStyle "Return the normal borderStyle of the receiver." ^self theme controlButtonNormalBorderStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/28/2007 16:52'! normalFillStyle "Return the normal fillStyle of the receiver." ^self theme controlButtonNormalFillStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:58'! pressedBorderStyle "Return the pressed borderStyle of the receiver." ^self theme controlButtonPressedBorderStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:59'! pressedFillStyle "Return the pressed fillStyle of the receiver." ^self theme controlButtonPressedFillStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:25'! selectedDisabledBorderStyle "Return the selected disabled borderStyle of the receiver." ^self theme controlButtonSelectedDisabledBorderStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:25'! selectedDisabledFillStyle "Return the selected disabled fillStyle of the receiver." ^self theme controlButtonSelectedDisabledFillStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/9/2008 13:04'! selectedFillStyle "Return the selected fillStyle of the receiver." ^self theme controlButtonSelectedFillStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:24'! selectedMouseOverBorderStyle "Return the selected mouse over borderStyle of the receiver." ^self theme controlButtonSelectedMouseOverBorderStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:24'! selectedMouseOverFillStyle "Return the selected mouse over fillStyle of the receiver." ^self theme controlButtonSelectedMouseOverFillStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:24'! selectedPressedBorderStyle "Return the selected pressed borderStyle of the receiver." ^self theme controlButtonSelectedPressedBorderStyleFor: self! ! !ControlButtonMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/13/2007 11:25'! selectedPressedFillStyle "Return the selected pressed fillStyle of the receiver." ^self theme controlButtonSelectedPressedFillStyleFor: self! ! Object subclass: #Controller instanceVariableNames: 'model sensor' classVariableNames: '' poolDictionaries: '' category: 'ST80-Kernel-Remnants'! !Controller commentStamp: '' prior: 0! A Controller coordinates a View, its model, and user actions. It provides scheduling (control) behavior to determine when the user wants to communicate with the model or view.! !Controller methodsFor: 'basic control sequence'! controlInitialize "Sent by Controller|startUp as part of the standard control sequence, it provides a place in the standard control sequence for initializing the receiver (taking into account the current state of its model and view). It should be redefined in subclasses to perform some specific action." ^self! ! !Controller methodsFor: 'basic control sequence'! controlTerminate "Provide a place in the standard control sequence for terminating the receiver (taking into account the current state of its model and view). It should be redefined in subclasses to perform some specific action." ^self! ! !Controller methodsFor: 'basic control sequence'! terminateAndInitializeAround: aBlock "1/12/96 sw" self controlTerminate. aBlock value. self controlInitialize! ! !Controller methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:49'! initialize "Initialize the state of the receiver. Subclasses should include 'super initialize' when redefining this message to insure proper initialization." super initialize. sensor := InputSensor default! ! !Controller methodsFor: 'initialization' stamp: 'alain.plantec 6/11/2008 12:02'! release "Breaks the cycle between the receiver and its view. It is usually not necessary to send release provided the receiver's view has been properly released independently." model := nil. ! ! !Controller methodsFor: 'model access'! model "Answer the receiver's model which is the same as the model of the receiver's view." ^model! ! !Controller methodsFor: 'model access' stamp: 'alain.plantec 6/11/2008 12:18'! model: aModel "Controller|model: and Controller|view: are sent by View|controller: in order to coordinate the links between the model, view, and controller. In ordinary usage, the receiver is created and passed as the parameter to View|controller: so that the receiver's model and view links can be set up by the view." model := aModel! ! !Controller methodsFor: 'sensor access'! sensor "Answer the receiver's sensor. Subclasses may use other objects that are not instances of Sensor or its subclasses if more general kinds of input/output functions are required." ^sensor! ! !Controller methodsFor: 'sensor access' stamp: 'alain.plantec 6/11/2008 12:18'! sensor: aSensor "Set the receiver's sensor to aSensor." sensor := aSensor! ! AbstractResizerMorph subclass: #CornerGripMorph instanceVariableNames: 'target' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Windows'! !CornerGripMorph commentStamp: 'jmv 1/29/2006 17:15' prior: 0! I am the superclass of a hierarchy of morph specialized in allowing the user to resize windows.! !CornerGripMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 7/30/2009 14:06'! mouseDown: anEvent "Remember the receiver and target offsets too." |cp| cp := anEvent cursorPoint. lastMouse := {cp. cp - self position. cp - self targetPoint}! ! !CornerGripMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 2/12/2007 16:28'! target "Answer the target." ^target! ! !CornerGripMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 2/12/2007 16:36'! targetPoint "Answer the reference point of the target." ^self target bounds pointAtSideOrCorner: self ptName! ! !CornerGripMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 7/30/2009 14:07'! targetPoint: aPoint "Set the reference point of the target." |minExt rect| rect := self target bounds withSideOrCorner: self ptName setToPoint: aPoint. minExt := self target minimumExtent. rect width <= minExt x ifTrue: [ (self ptName = #topLeft or: [self ptName = #bottomLeft]) ifTrue: [rect := rect withSideOrCorner: #left setToPoint: self target bounds bottomRight - minExt] ifFalse: [rect := rect withSideOrCorner: #right setToPoint: self target bounds topLeft + minExt]]. rect height <= minExt y ifTrue: [ (self ptName = #topLeft or: [self ptName = #topRight]) ifTrue: [rect := rect withSideOrCorner: #top setToPoint: self target bounds bottomRight - minExt] ifFalse: [rect := rect withSideOrCorner: #bottom setToPoint: self target bounds topLeft + minExt]]. self target bounds: rect! ! !CornerGripMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 4/26/2007 12:08'! initialize super initialize. self extent: self defaultWidth @ self defaultHeight. self layoutFrame: self gripLayoutFrame! ! !CornerGripMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 2/12/2007 16:36'! mouseMove: anEvent "Track the mouse for resizing." target ifNil: [^ self]. target fastFramingOn ifTrue: [target doFastWindowReframe: self ptName] ifFalse: [ lastMouse at: 1 put: anEvent cursorPoint. self targetPoint: lastMouse first - lastMouse last. self position: (lastMouse first - lastMouse second)].! ! !CornerGripMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 3/27/2008 21:50'! target: aMorph target := aMorph. aMorph ifNotNil: [ self fillStyle: (aMorph theme resizerGripNormalFillStyleFor: self)]! ! !CornerGripMorph methodsFor: 'accessing' stamp: 'jmv 2/2/2006 14:24'! defaultHeight ^ 22! ! !CornerGripMorph methodsFor: 'accessing' stamp: 'jmv 2/2/2006 14:24'! defaultWidth ^ 22! ! Object subclass: #CornerRounder instanceVariableNames: 'cornerMasks cornerOverlays underBits' classVariableNames: 'CR0 CR1 CR2' poolDictionaries: '' category: 'Graphics-Display Objects'! !CornerRounder commentStamp: '' prior: 0! This class is a quick hack to support rounded corners in morphic. Rather than produce rounded rectangles, it tweaks the display of corners. Rather than work for any radius, it only supports a radius of 6. Rather than work for any border width, it only supports widths 0, 1 and 2. The corners, while apparently transparent, still behave opaquely to mouse clicks. Worse than this, the approach relies on the ability to extract underlying bits from the canvas prior to display. This ran afoul of top-down display, it seems, in SystemWindow spawnReframeHandle: (qv). It will also make a postscript printer very unhappy. But, hey, it's cute.! !CornerRounder methodsFor: 'all' stamp: 'di 6/24/1999 09:35'! masterMask: maskForm masterOverlay: overlayForm cornerMasks := #(none left pi right) collect: [:dir | (maskForm rotateBy: dir centerAt: 0@0) offset: 0@0]. cornerOverlays := #(none left pi right) collect: [:dir | (overlayForm rotateBy: dir centerAt: 0@0) offset: 0@0]. ! ! !CornerRounder methodsFor: 'all' stamp: 'ar 1/5/2002 17:26'! saveBitsUnderCornersOf: aMorph on: aCanvas in: bounds corners: cornerList | offset corner mask form corners rect | underBits := Array new: 4. corners := bounds corners. cornerList do:[:i| mask := cornerMasks at: i. corner := corners at: i. i = 1 ifTrue: [offset := 0@0]. i = 2 ifTrue: [offset := 0@mask height negated]. i = 3 ifTrue: [offset := mask extent negated]. i = 4 ifTrue: [offset := mask width negated@0]. rect := corner + offset extent: mask extent. (aCanvas isVisible: rect) ifTrue:[ form := aCanvas contentsOfArea: rect. form copyBits: form boundingBox from: mask at: 0@0 clippingBox: form boundingBox rule: Form and fillColor: nil map: (Bitmap with: 16rFFFFFFFF with: 0). underBits at: i put: form]]. ! ! !CornerRounder methodsFor: 'all' stamp: 'kfr 8/4/2003 23:28'! tweakCornersOf: aMorph on: aCanvas in: bounds borderWidth: w corners: cornerList "This variant has a cornerList argument, to allow some corners to be rounded and others not" | offset corner saveBits fourColors mask outBits shadowColor corners | shadowColor := aCanvas shadowColor. aCanvas shadowColor: nil. "for tweaking it's essential" w > 0 ifTrue:[ fourColors := shadowColor ifNil:[aMorph borderStyle colorsAtCorners] ifNotNil:[Array new: 4 withAll: Color transparent]]. mask := Form extent: cornerMasks first extent depth: aCanvas depth. corners := bounds corners. cornerList do:[:i| corner := corners at: i. saveBits := underBits at: i. saveBits ifNotNil:[ i = 1 ifTrue: [offset := 0@0]. i = 2 ifTrue: [offset := 0@saveBits height negated]. i = 3 ifTrue: [offset := saveBits extent negated]. i = 4 ifTrue: [offset := saveBits width negated@0]. "Mask out corner area (painting saveBits won't clear if transparent)." mask copyBits: mask boundingBox from: (cornerMasks at: i) at: 0@0 clippingBox: mask boundingBox rule: Form over fillColor: nil map: (Bitmap with: 0 with: 16rFFFFFFFF). outBits := aCanvas contentsOfArea: (corner + offset extent: mask extent). mask displayOn: outBits at: 0@0 rule: Form and. "Paint back corner bits." saveBits displayOn: outBits at: 0@0 rule: Form paint. "Paint back corner bits." aCanvas drawImage: outBits at: corner + offset. w > 0 ifTrue:[ aCanvas stencil: (cornerOverlays at: i) at: corner + offset color: (fourColors at: i)]]]. aCanvas shadowColor: shadowColor. "restore shadow color" ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CornerRounder class instanceVariableNames: ''! !CornerRounder class methodsFor: 'all' stamp: 'di 6/28/1999 15:51'! initialize "CornerRounder initialize" CR0 := CR1 := self new masterMask: (Form extent: 6@6 fromArray: #(2r1e26 2r111e26 2r1111e26 2r11111e26 2r11111e26 2r111111e26) offset: 0@0) masterOverlay: (Form extent: 6@6 fromArray: #(2r1e26 2r110e26 2r1000e26 2r10000e26 2r10000e26 2r100000e26) offset: 0@0). CR2 := self new masterMask: (Form extent: 6@6 fromArray: #(2r1e26 2r111e26 2r1111e26 2r11111e26 2r11111e26 2r111111e26) offset: 0@0) masterOverlay: (Form extent: 6@6 fromArray: #(2r1e26 2r111e26 2r1111e26 2r11100e26 2r11000e26 2r111000e26) offset: 0@0). ! ! !CornerRounder class methodsFor: 'all' stamp: 'di 3/25/2000 11:12'! rectWithinCornersOf: aRectangle "Return a single sub-rectangle that lies entirely inside corners that are made by me. Used to identify large regions of window that do not need to be redrawn." ^ aRectangle insetBy: 0@6! ! !CornerRounder class methodsFor: 'all' stamp: 'ar 1/5/2002 17:24'! roundCornersOf: aMorph on: aCanvas in: bounds displayBlock: displayBlock borderWidth: w corners: aList | rounder | rounder := CR0. w = 1 ifTrue: [rounder := CR1]. w = 2 ifTrue: [rounder := CR2]. rounder := rounder copy. rounder saveBitsUnderCornersOf: aMorph on: aCanvas in: bounds corners: aList. displayBlock value. rounder tweakCornersOf: aMorph on: aCanvas in: bounds borderWidth: w corners: aList! ! StandardFileStream subclass: #CrLfFileStream instanceVariableNames: 'lineEndConvention' classVariableNames: 'Cr CrLf Lf LineEndDefault LineEndStrings LookAheadCount' poolDictionaries: '' category: 'Files-Kernel'! !CrLfFileStream commentStamp: 'ls 11/10/2002 13:32' prior: 0! I am the same as a regular file stream, except that when I am in text mode, I will automatically convert line endings between the underlying platform's convention, and Squeak's convention of carriage-return only. The goal is that Squeak text files can be treated as OS text files, and vice versa. In binary mode, I behave identically to a StandardFileStream. To enable CrLfFileStream as the default file stream class for an entire image, modify FileStream class concreteStream . There are two caveats on programming with CrLfFileStream. First, the choice of text mode versus binary mode affects which characters are visible in Squeak, and no longer just affects whether those characters are returned as Character's or as Integer's. Thus the choice of mode needs to be made very carefully, and must be based on intent instead of convenience of representation. The methods asString, asByteArray, asCharacter, and asInteger can be used to convert between character and integer representations. (Arguably, file streams should accept either strings or characters in nextPut: and nextPutAll:, but that is not the case right now.) Second, arithmetic on positions no longer works, because one character that Squeak sees (carriage return) could map to two characters in the underlying file (carriage return plus line feed, on MS Windows and MS DOS). Comparison between positions still works. (This caveat could perhaps be fixed by maintaining a map between Squeak positions and positions in the underlying file, but it is complicated. Consider, for example, updates to the middle of the file. Also, consider that text files are rarely updated in the middle of the file, and that general random access to a text file is rarely very useful. If general random access with specific file counts is desired, then the file is starting to sound like a binary file instead of a text file.) ! !CrLfFileStream methodsFor: '*monticello' stamp: 'stephaneducasse 2/4/2006 20:47'! lineEndingConvention: aSymbol lineEndConvention := aSymbol! ! !CrLfFileStream methodsFor: 'access' stamp: 'ar 1/20/98 16:16'! ascii super ascii. self detectLineEndConvention! ! !CrLfFileStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! binary super binary. lineEndConvention := nil! ! !CrLfFileStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! detectLineEndConvention "Detect the line end convention used in this stream. The result may be either #cr, #lf or #crlf." | char numRead pos | self isBinary ifTrue: [^ self error: 'Line end conventions are not used on binary streams']. lineEndConvention := LineEndDefault. "Default if nothing else found" numRead := 0. pos := super position. [super atEnd not and: [numRead < LookAheadCount]] whileTrue: [char := super next. char = Lf ifTrue: [super position: pos. ^ lineEndConvention := #lf]. char = Cr ifTrue: [super peek = Lf ifTrue: [lineEndConvention := #crlf] ifFalse: [lineEndConvention := #cr]. super position: pos. ^ lineEndConvention]. numRead := numRead + 1]. super position: pos. ^ lineEndConvention! ! !CrLfFileStream methodsFor: 'access' stamp: 'nk 9/5/2004 12:58'! lineEndConvention ^lineEndConvention! ! !CrLfFileStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! next | char secondChar | char := super next. self isBinary ifTrue: [^char]. char == Cr ifTrue: [secondChar := super next. secondChar ifNotNil: [secondChar == Lf ifFalse: [self skip: -1]]. ^Cr]. char == Lf ifTrue: [^Cr]. ^char! ! !CrLfFileStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! next: n | string peekChar | string := super next: n. string size = 0 ifTrue: [ ^string ]. self isBinary ifTrue: [ ^string ]. "if we just read a CR, and the next character is an LF, then skip the LF" ( string last = Character cr ) ifTrue: [ peekChar := super next. "super peek doesn't work because it relies on #next" peekChar ~= Character lf ifTrue: [ super position: (super position - 1) ]. ]. string := string withSqueakLineEndings. string size = n ifTrue: [ ^string ]. "string shrunk due to embedded crlfs; make up the difference" ^string, (self next: n - string size)! ! !CrLfFileStream methodsFor: 'access' stamp: 'ar 1/20/98 16:18'! nextPut: char (lineEndConvention notNil and: [char = Cr]) ifTrue: [super nextPutAll: (LineEndStrings at: lineEndConvention)] ifFalse: [super nextPut: char]. ^ char! ! !CrLfFileStream methodsFor: 'access' stamp: 'ar 1/20/98 16:18'! nextPutAll: aString super nextPutAll: (self convertStringFromCr: aString). ^ aString ! ! !CrLfFileStream methodsFor: 'access' stamp: 'stephaneducasse 2/4/2006 20:31'! peek "Answer what would be returned if the message next were sent to the receiver. If the receiver is at the end, answer nil. " | next pos | self atEnd ifTrue: [^ nil]. pos := self position. next := self next. self position: pos. ^ next! ! !CrLfFileStream methodsFor: 'access' stamp: 'PeterHugossonMiller 9/3/2009 01:05'! upTo: aCharacter | newStream char | newStream := (String new: 100) writeStream. [(char := self next) isNil or: [char == aCharacter]] whileFalse: [newStream nextPut: char]. ^ newStream contents ! ! !CrLfFileStream methodsFor: 'access' stamp: 'ar 1/20/98 16:18'! verbatim: aString super verbatim: (self convertStringFromCr: aString). ^ aString! ! !CrLfFileStream methodsFor: 'open/close' stamp: 'stephaneducasse 2/4/2006 20:31'! open: aFileName forWrite: writeMode "Open the receiver. If writeMode is true, allow write, else access will be read-only. " | result | result := super open: aFileName forWrite: writeMode. result ifNotNil: [self detectLineEndConvention]. ^ result! ! !CrLfFileStream methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:04'! convertStringFromCr: aString | inStream outStream | lineEndConvention ifNil: [^ aString]. lineEndConvention == #cr ifTrue: [^ aString]. lineEndConvention == #lf ifTrue: [^ aString copy replaceAll: Cr with: Lf]. "lineEndConvention == #crlf" inStream := aString readStream. outStream := (String new: aString size) writeStream. [inStream atEnd] whileFalse: [outStream nextPutAll: (inStream upTo: Cr). (inStream atEnd not or: [aString last = Cr]) ifTrue: [outStream nextPutAll: CrLf]]. ^ outStream contents! ! !CrLfFileStream methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:04'! convertStringToCr: aString | inStream outStream | lineEndConvention ifNil: [^ aString]. lineEndConvention == #cr ifTrue: [^ aString]. lineEndConvention == #lf ifTrue: [^ aString copy replaceAll: Lf with: Cr]. "lineEndConvention == #crlf" inStream := aString readStream. outStream := (String new: aString size) writeStream. [inStream atEnd] whileFalse: [outStream nextPutAll: (inStream upTo: Cr). (inStream atEnd not or: [aString last = Cr]) ifTrue: [outStream nextPut: Cr. inStream peek = Lf ifTrue: [inStream next]]]. ^ outStream contents! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CrLfFileStream class instanceVariableNames: ''! !CrLfFileStream class methodsFor: 'initialization' stamp: 'ar 1/20/98 16:10'! defaultToCR "CrLfFileStream defaultToCR" LineEndDefault := #cr.! ! !CrLfFileStream class methodsFor: 'initialization' stamp: 'ar 1/20/98 16:10'! defaultToCRLF "CrLfFileStream defaultToCRLF" LineEndDefault := #crlf.! ! !CrLfFileStream class methodsFor: 'initialization' stamp: 'ar 1/20/98 16:10'! defaultToLF "CrLfFileStream defaultToLF" LineEndDefault := #lf.! ! !CrLfFileStream class methodsFor: 'initialization' stamp: 'norbert_hartl 6/13/2009 10:57'! guessDefaultLineEndConvention "Lets try to guess the line end convention from what we know about the path name delimiter from FileDirectory." FileDirectory pathNameDelimiter = $: ifTrue:[^self defaultToCR]. FileDirectory pathNameDelimiter = $/ ifTrue:[((SmalltalkImage current getSystemAttribute: 1002) beginsWith: 'darwin') ifTrue: [^ self defaultToCR] ifFalse: [^ self defaultToLF]]. FileDirectory pathNameDelimiter = $\ ifTrue:[^self defaultToCRLF]. "in case we don't know" ^self defaultToCR! ! !CrLfFileStream class methodsFor: 'initialization' stamp: 'di 2/4/1999 09:16'! initialize "CrLfFileStream initialize" Cr := Character cr. Lf := Character lf. CrLf := String with: Cr with: Lf. LineEndStrings := Dictionary new. LineEndStrings at: #cr put: (String with: Character cr). LineEndStrings at: #lf put: (String with: Character lf). LineEndStrings at: #crlf put: (String with: Character cr with: Character lf). LookAheadCount := 2048. Smalltalk addToStartUpList: self. self startUp.! ! !CrLfFileStream class methodsFor: 'initialization' stamp: 'yo 2/21/2004 04:46'! new ^ (MultiByteFileStream new) wantsLineEndConversion: true; yourself. ! ! !CrLfFileStream class methodsFor: 'initialization' stamp: 'djp 1/28/1999 22:08'! startUp self guessDefaultLineEndConvention! ! Array variableSubclass: #Cubic instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Collections-Arrayed'! !Cubic commentStamp: 'wiz 6/17/2004 20:31' prior: 0! I am a segment between to points. In the form of a cubic polynomial that can be evaluated between 0..1 to obtain the end points and intermediate values. ! !Cubic methodsFor: 'cubic support' stamp: 'wiz 6/17/2004 22:32'! bestSegments "Return the smallest integer number of segments that give the best curve." ^ self honeIn: self calcEnoughSegments! ! !Cubic methodsFor: 'cubic support' stamp: 'wiz 6/18/2004 23:12'! calcEnoughSegments "Find the power of two that represents a sufficient number of segments for this cubic. The measure is the sum of distances for the segments. We want this to be close enough not affect the straightness of the drawn lines. Which means within one pixel." "^ self enough: 2 withMeasure: (self measureFor: 1) withIn: self leeway This ran into a problem when the curve was an s-curve with inflections. Besides honeIn will check to see if 1 is better than two so we lose nothing by starting a little higher." ^ self enough: 4 withMeasure: (self measureFor: 2) withIn: self leeway! ! !Cubic methodsFor: 'cubic support' stamp: 'wiz 7/18/2004 22:50'! enough: nTry withMeasure: lastMeasure withIn: closeEnough "See comment in calcEnoughSegments for which I am a helper" | measure | measure := self measureFor: nTry. measure > (lastMeasure + closeEnough) ifFalse: [^ nTry // 2]. ^ self enough: 2 * nTry withMeasure: measure withIn: closeEnough! ! !Cubic methodsFor: 'cubic support' stamp: 'wiz 6/17/2004 23:51'! honeIn: enough "Find if there is a smaller n than enough that give the same measure for n." self assert: [enough isPowerOfTwo]. enough < 2 ifTrue: [^ enough]. ^ self honeIn: enough step: enough // 2 measure: (self measureFor: enough) withIn: self leeway! ! !Cubic methodsFor: 'cubic support' stamp: 'wiz 6/17/2004 23:45'! honeIn: centerN step: step measure: measure withIn: closeEnough "Pick the best n by binary search." | nTry | step < 1 ifTrue: [^ centerN]. nTry := centerN - step. ^ measure > (closeEnough + (self measureFor: nTry)) ifTrue: [self honeIn: centerN step: step // 2 measure: measure withIn: closeEnough] ifFalse: [self honeIn: nTry step: step // 2 measure: measure withIn: closeEnough]! ! !Cubic methodsFor: 'cubic support' stamp: 'wiz 6/19/2004 00:00'! leeway "How close can measure be" ^ 0.1! ! !Cubic methodsFor: 'cubic support' stamp: 'wiz 1/30/2005 20:59'! measureFor: n "Return a distance measure for cubic curve with n segments. For convienence and accuracy we use the sum of the distances. " "first point is poly of 0." | p1 p2 measure | p1 := self first. measure := 0. (1 to: n) do: [:i | p2 := self polynomialEval: i / n asFloat. measure := measure + (p2 dist: p1). p1 := p2]. ^ measure! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Cubic class instanceVariableNames: ''! !Cubic class methodsFor: 'instance creation' stamp: 'stephane.ducasse 12/21/2008 11:00'! with: pt1 with: pt2 with: pt3 with: pt4 "a cubic object is composed of 4 points" ^ self withAll: {pt1 . pt2 . pt3 . pt4}! ! Form subclass: #Cursor instanceVariableNames: '' classVariableNames: 'BlankCursor BottomLeftCursor BottomRightCursor CornerCursor CrossHairCursor CurrentCursor DownCursor MarkerCursor MenuCursor MoveCursor NormalCursor OriginCursor ReadCursor ResizeLeftCursor ResizeTopCursor ResizeTopLeftCursor ResizeTopRightCursor RightArrowCursor SquareCursor TargetCursor TopLeftCursor TopRightCursor UpCursor WaitCursor WebLinkCursor WriteCursor XeqCursor' poolDictionaries: '' category: 'Graphics-Display Objects'! !Cursor commentStamp: '' prior: 0! I am a Form that is a possible appearance for a mouse cursor. My size is always 16x16, ever since the original implementation on the Alto. There are many examples available in the "current cursor" category of class methods. For example, "Cursor normal" and "Cursor wait". For example: Cursor wait show ! !Cursor methodsFor: 'converting' stamp: 'RAA 8/14/2000 10:14'! asCursorForm | form | form := StaticForm extent: self extent depth: 8. form fillShape: self fillColor: Color black at: offset negated. ^ form offset: offset! ! !Cursor methodsFor: 'converting' stamp: 'bf 2/2/1999 19:32'! withMask ^CursorWithMask derivedFrom: self! ! !Cursor methodsFor: 'displaying' stamp: 'ls 6/17/2002 11:56'! show "Make the hardware's mouse cursor look like the receiver" Sensor currentCursor: self! ! !Cursor methodsFor: 'displaying'! showGridded: gridPoint "Make the current cursor shape be the receiver, forcing the location of the cursor to the point nearest gridPoint." Sensor cursorPoint: (Sensor cursorPoint grid: gridPoint). Sensor currentCursor: self! ! !Cursor methodsFor: 'displaying' stamp: 'bf 10/13/1999 13:05'! showWhile: aBlock "While evaluating the argument, aBlock, make the receiver be the cursor shape." | oldcursor | oldcursor := Sensor currentCursor. self show. ^aBlock ensure: [oldcursor show] ! ! !Cursor methodsFor: 'primitives'! beCursor "Primitive. Tell the interpreter to use the receiver as the current cursor image. Fail if the receiver does not match the size expected by the hardware. Essential. See Object documentation whatIsAPrimitive." self primitiveFailed! ! !Cursor methodsFor: 'primitives' stamp: 'jm 9/22/1998 23:33'! beCursorWithMask: maskForm "Primitive. Tell the interpreter to use the receiver as the current cursor image with the given mask Form. Both the receiver and the mask should have extent 16@16 and a depth of one. The mask and cursor bits are combined as follow: mask cursor effect 0 0 transparent (underlying pixel shows through) 1 1 opaque black 1 0 opaque white 0 1 invert the underlying pixel" "Essential. See Object documentation whatIsAPrimitive." self primitiveFailed ! ! !Cursor methodsFor: 'printing'! printOn: aStream self storeOn: aStream base: 2! ! !Cursor methodsFor: 'testing' stamp: 'bf 2/2/1999 19:34'! hasMask ^false! ! !Cursor methodsFor: 'updating' stamp: 'ls 6/17/2002 12:00'! changed: aParameter "overriden to reinstall the cursor if it is the active cursor, in case the appearance has changed. (Is this used anywhere? Do cursors really change in place these days?)" self == CurrentCursor ifTrue: [self beCursor]. super changed: aParameter! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Cursor class instanceVariableNames: ''! !Cursor class methodsFor: 'constants'! blank "Answer the instance of me that is all white." ^BlankCursor! ! !Cursor class methodsFor: 'constants' stamp: 'JMM 10/21/2003 19:13'! bottomLeft "Cursor bottomLeft showWhile: [Sensor waitButton]" ^BottomLeftCursor ! ! !Cursor class methodsFor: 'constants' stamp: 'JMM 10/21/2003 19:13'! bottomRight "Cursor bottomRight showWhile: [Sensor waitButton]" ^BottomRightCursor ! ! !Cursor class methodsFor: 'constants'! corner "Answer the instance of me that is the shape of the bottom right corner of a rectangle." ^CornerCursor! ! !Cursor class methodsFor: 'constants'! crossHair "Answer the instance of me that is the shape of a cross." ^CrossHairCursor! ! !Cursor class methodsFor: 'constants'! down "Answer the instance of me that is the shape of an arrow facing downward." ^DownCursor! ! !Cursor class methodsFor: 'constants'! execute "Answer the instance of me that is the shape of an arrow slanted left with a star next to it." ^XeqCursor! ! !Cursor class methodsFor: 'constants'! marker "Answer the instance of me that is the shape of a small ball." ^MarkerCursor! ! !Cursor class methodsFor: 'constants'! menu "Answer the instance of me that is the shape of a menu." ^MenuCursor! ! !Cursor class methodsFor: 'constants'! move "Answer the instance of me that is the shape of a cross inside a square." ^MoveCursor! ! !Cursor class methodsFor: 'constants'! normal "Answer the instance of me that is the shape of an arrow slanted left." ^NormalCursor! ! !Cursor class methodsFor: 'constants'! origin "Answer the instance of me that is the shape of the top left corner of a rectangle." ^OriginCursor! ! !Cursor class methodsFor: 'constants'! read "Answer the instance of me that is the shape of eyeglasses." ^ReadCursor! ! !Cursor class methodsFor: 'constants' stamp: 'ar 8/16/2001 14:48'! resizeBottom "Cursor resizeBottom showWhile: [Sensor waitButton]" ^self resizeTop! ! !Cursor class methodsFor: 'constants' stamp: 'ar 8/16/2001 14:46'! resizeBottomLeft "Cursor resizeBottomLeft showWhile: [Sensor waitButton]" ^self resizeTopRight! ! !Cursor class methodsFor: 'constants' stamp: 'ar 8/16/2001 14:45'! resizeBottomRight "Cursor resizeBottomRight showWhile: [Sensor waitButton]" ^self resizeTopLeft! ! !Cursor class methodsFor: 'constants' stamp: 'JMM 10/21/2003 18:58'! resizeLeft "Cursor resizeLeft showWhile: [Sensor waitButton]" ^ResizeLeftCursor! ! !Cursor class methodsFor: 'constants' stamp: 'ar 8/16/2001 14:45'! resizeRight "Cursor resizeRight showWhile: [Sensor waitButton]" ^self resizeLeft! ! !Cursor class methodsFor: 'constants' stamp: 'JMM 10/21/2003 19:19'! resizeTop "Cursor resizeTop showWhile: [Sensor waitButton]" ^ResizeTopCursor! ! !Cursor class methodsFor: 'constants' stamp: 'JMM 10/21/2003 19:00'! resizeTopLeft "Cursor resizeTopLeft showWhile: [Sensor waitButton]" ^ ResizeTopLeftCursor! ! !Cursor class methodsFor: 'constants' stamp: 'JMM 10/21/2003 19:00'! resizeTopRight "Cursor resizeTopRight showWhile: [Sensor waitButton]" ^ResizeTopRightCursor! ! !Cursor class methodsFor: 'constants'! rightArrow "Answer the instance of me that is the shape of an arrow pointing to the right." ^RightArrowCursor! ! !Cursor class methodsFor: 'constants'! square "Answer the instance of me that is the shape of a square." ^SquareCursor! ! !Cursor class methodsFor: 'constants' stamp: 'ar 3/1/2006 22:42'! target "Answer the instance of me that is the shape of a gunsight." "Cursor target show" ^TargetCursor ifNil:[self initTarget]! ! !Cursor class methodsFor: 'constants' stamp: 'JMM 10/21/2003 19:01'! topLeft "Cursor topLeft showWhile: [Sensor waitButton]" ^ TopLeftCursor! ! !Cursor class methodsFor: 'constants' stamp: 'JMM 10/21/2003 19:02'! topRight "Cursor topRight showWhile: [Sensor waitButton]" ^ TopRightCursor! ! !Cursor class methodsFor: 'constants'! up "Answer the instance of me that is the shape of an arrow facing upward." ^UpCursor! ! !Cursor class methodsFor: 'constants' stamp: 'sw 8/15/97 13:28'! wait "Answer the instance of me that is the shape of an Hourglass (was in the shape of three small balls)." ^WaitCursor! ! !Cursor class methodsFor: 'constants' stamp: 'ar 9/26/2001 22:37'! webLink "Return a cursor that can be used for emphasizing web links" "Cursor webLink showWhile: [Sensor waitButton]" ^WebLinkCursor ifNil:[ WebLinkCursor := (CursorWithMask extent: 16@16 fromArray: #(3072 4608 4608 4608 4608 5046 4681 29257 37449 37449 32769 32769 49155 16386 24582 16380 ) offset: -5@0) setMaskForm: (Form extent: 16@16 fromArray: (#(3072 7680 7680 7680 7680 8118 8191 32767 65535 65535 65535 65535 65535 32766 32766 16380 ) collect: [:bits | bits bitShift: 16]) offset: 0@0)].! ! !Cursor class methodsFor: 'constants'! write "Answer the instance of me that is the shape of a pen writing." ^WriteCursor! ! !Cursor class methodsFor: 'current cursor'! currentCursor "Answer the instance of Cursor that is the one currently displayed." ^CurrentCursor! ! !Cursor class methodsFor: 'current cursor' stamp: 'marcus.denker 8/17/2008 21:19'! currentCursor: aCursor "Make the instance of cursor, aCursor, be the current cursor. Display it. Create an error if the argument is not a Cursor." (aCursor isKindOf: self) ifTrue: [CurrentCursor := aCursor. aCursor beCursor] ifFalse: [self error: 'The new cursor must be an instance of class Cursor']! ! !Cursor class methodsFor: 'initialization' stamp: 'JMM 10/21/2003 18:57'! initBottomLeft BottomLeftCursor := (Cursor extent: 16@16 fromArray: #( 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1111111111111111 2r1111111111111111) offset: 0@-16). ! ! !Cursor class methodsFor: 'initialization' stamp: 'JMM 10/21/2003 18:57'! initBottomRight BottomRightCursor := (Cursor extent: 16@16 fromArray: #( 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r1111111111111111 2r1111111111111111) offset: -16@-16). ! ! !Cursor class methodsFor: 'initialization'! initCorner CornerCursor := (Cursor extent: 16@16 fromArray: #( 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r1111111111111111 2r1111111111111111) offset: -16@-16). ! ! !Cursor class methodsFor: 'initialization' stamp: 'kfr 7/12/2003 21:02'! initCrossHair CrossHairCursor := (Cursor extent: 16@16 fromArray: #( 2r0000000000000000 2r0000000100000000 2r0000000100000000 2r0000000100000000 2r0000000100000000 2r0000000100000000 2r0000000100000000 2r0111111111111100 2r0000000100000000 2r0000000100000000 2r0000000100000000 2r0000000100000000 2r0000000100000000 2r0000000100000000 2r0000000000000000 2r0) offset: -7@-7). ! ! !Cursor class methodsFor: 'initialization'! initDown DownCursor := (Cursor extent: 16@16 fromArray: #( 2r11000000000000 2r11000000000000 2r11000000000000 2r11000000000000 2r11000000000000 2r11000000000000 2r11000000000000 2r1111110000000000 2r111100000000000 2r11000000000000 2r0 2r0 2r0 2r0 2r0 2r0) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization'! initMarker MarkerCursor := Cursor extent: 16@16 fromArray: #( 2r0111000000000000 2r1111100000000000 2r1111100000000000 2r0111000000000000 2r0 2r0 2r0 2r0 2r0 2r0 2r0 2r0 2r0 2r0 2r0 2r0) offset: 0@0. ! ! !Cursor class methodsFor: 'initialization' stamp: 'di 7/30/2001 10:32'! initMenu MenuCursor := (Cursor extent: 16@16 fromArray: #( 2r1111111111100000 2r1000000000100000 2r1010011000100000 2r1000000000100000 2r1101001101100000 2r1111111111100000 2r1000000000100000 2r1011001010100000 2r1000000000100000 2r1010110010100000 2r1000000000100000 2r1010010100100000 2r1000000000100000 2r1111111111100000 0) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization' stamp: 'kfr 7/12/2003 21:10'! initMove MoveCursor := Cursor extent: 16@16 fromArray: #( 2r1111111111111100 2r1111111111111100 2r1100001100001100 2r1100001100001100 2r1100001100001100 2r1100001100001100 2r1111111111111100 2r1111111111111100 2r1100001100001100 2r1100001100001100 2r1100001100001100 2r1100001100001100 2r1111111111111100 2r1111111111111100 0) offset: 0@0. ! ! !Cursor class methodsFor: 'initialization'! initNormal NormalCursor := (Cursor extent: 16@16 fromArray: #( 2r1000000000000000 2r1100000000000000 2r1110000000000000 2r1111000000000000 2r1111100000000000 2r1111110000000000 2r1111111000000000 2r1111100000000000 2r1111100000000000 2r1001100000000000 2r0000110000000000 2r0000110000000000 2r0000011000000000 2r0000011000000000 2r0000001100000000 2r0000001100000000) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization' stamp: 'di 10/8/1998 17:04'! initNormalWithMask "Cursor initNormalWithMask. Cursor normal show" "Next two lines work simply for any cursor..." self initNormal. NormalCursor := CursorWithMask derivedFrom: NormalCursor. "But for a good looking cursor, you have to tweak things..." NormalCursor := (CursorWithMask extent: 16@16 depth: 1 fromArray: #( 0 1073741824 1610612736 1879048192 2013265920 2080374784 2113929216 2130706432 2080374784 2080374784 1275068416 100663296 100663296 50331648 50331648 0) offset: -1@-1) setMaskForm: (Form extent: 16@16 depth: 1 fromArray: #( 3221225472 3758096384 4026531840 4160749568 4227858432 4261412864 4278190080 4286578688 4278190080 4261412864 4261412864 3472883712 251658240 125829120 125829120 50331648) offset: 0@0).! ! !Cursor class methodsFor: 'initialization'! initOrigin OriginCursor := (Cursor extent: 16@16 fromArray: #( 2r1111111111111111 2r1111111111111111 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization' stamp: 'kfr 7/12/2003 22:55'! initRead ReadCursor := (Cursor extent: 16@16 fromArray: #( 2r0000000000000000 2r0000000000000000 2r0001000000001000 2r0010100000010100 2r0100000000100000 2r1111101111100000 2r1000010000100000 2r1000010000100000 2r1011010110100000 2r0111101111000000 2r0 2r0 2r0 2r0 2r0 2r0) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization' stamp: 'jrp 8/6/2005 22:50'! initResizeLeft ResizeLeftCursor := (Cursor extent: 16@16 fromArray: #( 2r0000000000000000 2r0000000000000000 2r0000000000000000 2r0000000000000000 2r0000100000010000 2r0001100000011000 2r0011100000011100 2r0111111111111110 2r0011100000011100 2r0001100000011000 2r0000100000010000 2r0000000000000000 2r0000000000000000 2r0000000000000000 2r0000000000000000 2r0000000000000000 ) offset: -7@-7 ) withMask! ! !Cursor class methodsFor: 'initialization' stamp: 'jrp 8/6/2005 22:54'! initResizeTop "Cursor initResizeTop" ResizeTopCursor := (Cursor extent: 16@16 fromArray: #( 2r000000100000000 2r000001110000000 2r000011111000000 2r000111111100000 2r000000100000000 2r000000100000000 2r000000100000000 2r000000100000000 2r000000100000000 2r000000100000000 2r000111111100000 2r000011111000000 2r000001110000000 2r000000100000000 2r000000000000000) offset: -7@-7) withMask! ! !Cursor class methodsFor: 'initialization' stamp: 'jrp 8/6/2005 22:55'! initResizeTopLeft ResizeTopLeftCursor := (Cursor extent: 16@16 fromArray: #( 2r0000000000000000 2r0111110000000000 2r0111100000000000 2r0111000000000000 2r0110100000000000 2r0100010000000000 2r0000001000000000 2r0000000100000000 2r0000000010000000 2r0000000001000100 2r0000000000101100 2r0000000000011100 2r0000000000111100 2r0000000001111100 2r0000000000000000 2r0000000000000000) offset: -7@-7) withMask! ! !Cursor class methodsFor: 'initialization' stamp: 'jrp 8/7/2005 07:54'! initResizeTopRight ResizeTopRightCursor := (Cursor extent: 16@16 fromArray: #( 2r0000000000000000 2r0000000001111100 2r0000000000111100 2r0000000000011100 2r0000000000101100 2r0000000001000100 2r0000000010000000 2r0000000100000000 2r0000001000000000 2r0100010000000000 2r0110100000000000 2r0111000000000000 2r0111100000000000 2r0111110000000000 2r0000000000000000 2r0000000000000000) offset: -7@-7) withMask! ! !Cursor class methodsFor: 'initialization'! initRightArrow RightArrowCursor := (Cursor extent: 16@16 fromArray: #( 2r100000000000 2r111000000000 2r1111111110000000 2r111000000000 2r100000000000 2r0 2r0 2r0 2r0 2r0 2r0 2r0 2r0 2r0 2r0 2r0) offset: 0@0). "Cursor initRightArrow"! ! !Cursor class methodsFor: 'initialization'! initSquare SquareCursor := (Cursor extent: 16@16 fromArray: #( 2r0 2r0 2r0 2r0 2r0 2r0000001111000000 2r0000001111000000 2r0000001111000000 2r0000001111000000 2r0 2r0 2r0 2r0 2r0 2r0 2r0) offset: -8@-8). ! ! !Cursor class methodsFor: 'initialization' stamp: 'ar 3/1/2006 22:42'! initTarget ^TargetCursor := Cursor extent: 16 @ 16 fromArray: #(1984 6448 8456 16644 17284 33026 35106 65278 35106 33026 17284 16644 8456 6448 1984 0) offset: -7 @ -7! ! !Cursor class methodsFor: 'initialization' stamp: 'JMM 10/21/2003 19:01'! initTopLeft TopLeftCursor := (Cursor extent: 16@16 fromArray: #( 2r1111111111111111 2r1111111111111111 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000 2r1100000000000000) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization' stamp: 'JMM 10/21/2003 19:02'! initTopRight TopRightCursor := (Cursor extent: 16@16 fromArray: #( 2r1111111111111111 2r1111111111111111 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011 2r0000000000000011) offset: -16@0). ! ! !Cursor class methodsFor: 'initialization'! initUp UpCursor := (Cursor extent: 16@16 fromArray: #( 2r11000000000000 2r111100000000000 2r1111110000000000 2r11000000000000 2r11000000000000 2r11000000000000 2r11000000000000 2r11000000000000 2r11000000000000 2r11000000000000 2r0 2r0 2r0 2r0 2r0 2r0) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization' stamp: 'kfr 7/12/2003 21:27'! initWait WaitCursor := (Cursor extent: 16@16 fromArray: #( 2r1111111111111100 2r1000000000000100 2r0100000000001000 2r0010000000010000 2r0001110011100000 2r0000111111000000 2r0000011110000000 2r0000011110000000 2r0000100101000000 2r0001000100100000 2r0010000110010000 2r0100001111001000 2r1000111111110100 2r1111111111111100 0) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization' stamp: 'kfr 7/12/2003 22:52'! initWrite WriteCursor := (Cursor extent: 16@16 fromArray: #( 2r0000000000011000 2r0000000000111100 2r0000000001001000 2r0000000010010000 2r0000000100100000 2r0000001001000100 2r0000010010000100 2r0000100100001100 2r0001001000010000 2r0010010000010000 2r0111100000001000 2r0101000011111000 2r1110000110000000 2r0111111100000000 2r0 2r0) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization'! initXeq XeqCursor := (Cursor extent: 16@16 fromArray: #( 2r1000000000010000 2r1100000000010000 2r1110000000111000 2r1111000111111111 2r1111100011000110 2r1111110001000100 2r1111111001111100 2r1111000001101100 2r1101100011000110 2r1001100010000010 2r0000110000000000 2r0000110000000000 2r0000011000000000 2r0000011000000000 2r0000001100000000 2r0000001100000000) offset: 0@0). ! ! !Cursor class methodsFor: 'initialization' stamp: 'stephane.ducasse 7/3/2009 22:32'! initialize "Create all the standard cursors..." self initOrigin. self initRightArrow. self initMenu. self initCorner. self initRead. self initWrite. self initWait. BlankCursor := Cursor new. self initXeq. self initSquare. self initNormalWithMask. self initCrossHair. self initMarker. self initUp. self initDown. self initMove. self initBottomLeft. self initBottomRight. self initResizeLeft. self initResizeTop. self initResizeTopLeft. self initResizeTopRight. self initTopLeft. self initTopRight. self initTarget. self makeCursorsWithMask. "Cursor initialize" ! ! !Cursor class methodsFor: 'initialization' stamp: 'bf 2/2/1999 19:33'! makeCursorsWithMask "Cursor initialize;makeCursorsWithMask" self classPool associationsDo: [:var | var value hasMask ifFalse: [var value: var value withMask]] ! ! !Cursor class methodsFor: 'initialization'! startUp self currentCursor: self currentCursor! ! !Cursor class methodsFor: 'instance creation'! extent: extentPoint fromArray: anArray offset: offsetPoint "Answer a new instance of me with width and height specified by extentPoint, offset by offsetPoint, and bits from anArray. NOTE: This has been kluged to take an array of 16-bit constants, and shift them over so they are left-justified in a 32-bit bitmap" extentPoint = (16 @ 16) ifTrue: [^ super extent: extentPoint fromArray: (anArray collect: [:bits | bits bitShift: 16]) offset: offsetPoint] ifFalse: [self error: 'cursors must be 16@16']! ! !Cursor class methodsFor: 'instance creation' stamp: 'di 10/6/1998 13:53'! new ^ self extent: 16 @ 16 fromArray: (Array new: 16 withAll: 0) offset: 0 @ 0 "Cursor new bitEdit show"! ! !Cursor class methodsFor: 'instance creation' stamp: 'ar 8/16/2001 15:52'! resizeForEdge: aSymbol "Cursor resizeForEdge: #top" "Cursor resizeForEdge: #bottomLeft" ^self perform: ('resize', aSymbol first asString asUppercase, (aSymbol copyFrom: 2 to: aSymbol size)) asSymbol.! ! Cursor subclass: #CursorWithMask instanceVariableNames: 'maskForm' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Display Objects'! !CursorWithMask commentStamp: '' prior: 0! A Cursor which additionally has a 16x16 transparency bitmap called a "mask". See the comment of beCursorWithMask: for details on how the mask is treated.! ]style[(97 17 40)f3,f3LCursor beCursorWithMask:;,f3! !CursorWithMask methodsFor: 'converting' stamp: 'RAA 8/14/2000 10:14'! asCursorForm | form | form := StaticForm extent: self extent depth: 8. form fillShape: maskForm fillColor: Color white. form fillShape: self fillColor: Color black at: offset negated. ^ form offset: offset! ! !CursorWithMask methodsFor: 'mask' stamp: 'bf 2/2/1999 19:34'! hasMask ^true! ! !CursorWithMask methodsFor: 'mask' stamp: 'di 10/8/1998 16:46'! maskForm ^ maskForm! ! !CursorWithMask methodsFor: 'mask' stamp: 'di 10/8/1998 16:46'! setMaskForm: aForm maskForm := aForm! ! !CursorWithMask methodsFor: 'mask' stamp: 'bf 2/2/1999 19:30'! storeOn: aStream base: anInteger aStream nextPut: $(. super storeOn: aStream base: anInteger. aStream nextPutAll: ' setMaskForm: '. maskForm storeOn: aStream base: anInteger. aStream nextPut: $)! ! !CursorWithMask methodsFor: 'mask' stamp: 'bf 2/2/1999 19:31'! withMask ^self! ! !CursorWithMask methodsFor: 'primitives' stamp: 'di 10/6/1998 15:16'! beCursor maskForm unhibernate. ^ self beCursorWithMask: maskForm! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CursorWithMask class instanceVariableNames: ''! !CursorWithMask class methodsFor: 'as yet unclassified' stamp: 'di 2/18/1999 08:56'! derivedFrom: aForm "Cursor initNormalWithMask. Cursor normal show" "aForm is presumably a cursor" | cursor mask ext | ext := aForm extent. cursor := self extent: ext. cursor copy: (1@1 extent: ext) from: 0@0 in: aForm rule: Form over. mask := Form extent: ext. (1@1) eightNeighbors do: [:p | mask copy: (p extent: ext) from: 0@0 in: aForm rule: Form under]. cursor setMaskForm: mask. cursor offset: ((aForm offset - (1@1)) max: ext negated). ^ cursor! ! Path subclass: #CurveFitter instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ST80-Paths'! !CurveFitter commentStamp: '' prior: 0! I represent a conic section determined by three points p1, p2 and p3. I interpolate p1 and p3 and am tangent to line p1, p2 at p1 and line p3, p2 at p3.! !CurveFitter methodsFor: 'displaying'! displayOn: aDisplayMedium at: aPoint clippingBox: clipRect rule: anInteger fillColor: aForm | pa pb k s p1 p2 p3 line | line := Line new. line form: self form. collectionOfPoints size < 3 ifTrue: [self error: 'Curve must have three points']. p1 := self firstPoint. p2 := self secondPoint. p3 := self thirdPoint. s := Path new. s add: p1. pa := p2 - p1. pb := p3 - p2. k := 5 max: pa x abs + pa y abs + pb x abs + pb y abs // 20. "k is a guess as to how many line segments to use to approximate the curve." 1 to: k do: [:i | s add: pa * i // k + p1 * (k - i) + (pb * (i - 1) // k + p2 * (i - 1)) // (k - 1)]. s add: p3. 1 to: s size - 1 do: [:i | line beginPoint: (s at: i). line endPoint: (s at: i + 1). line displayOn: aDisplayMedium at: aPoint clippingBox: clipRect rule: anInteger fillColor: aForm]! ! !CurveFitter methodsFor: 'displaying' stamp: '6/9/97 10:16 di'! displayOn: aDisplayMedium transformation: aTransformation clippingBox: clipRect rule: anInteger fillColor: aForm | transformedPath newCurveFitter | transformedPath := aTransformation applyTo: self. newCurveFitter := CurveFitter new. newCurveFitter firstPoint: transformedPath firstPoint. newCurveFitter secondPoint: transformedPath secondPoint. newCurveFitter thirdPoint: transformedPath thirdPoint. newCurveFitter form: self form. newCurveFitter displayOn: aDisplayMedium at: 0 @ 0 clippingBox: clipRect rule: anInteger fillColor: aForm! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CurveFitter class instanceVariableNames: ''! !CurveFitter class methodsFor: 'examples' stamp: '6/9/97 10:16 di'! example "Designate three locations on the screen by clicking any button. The curve determined by the points will be displayed with a long black form." | aCurveFitter aForm | aForm := Form extent: 1@30. "make a long thin Form for display " aForm fillBlack. "turn it black" aCurveFitter := CurveFitter new. aCurveFitter form: aForm. "set the form for display" "collect three Points and show them on the dispaly" aCurveFitter firstPoint: Sensor waitButton. Sensor waitNoButton. aForm displayOn: Display at: aCurveFitter firstPoint. aCurveFitter secondPoint: Sensor waitButton. Sensor waitNoButton. aForm displayOn: Display at: aCurveFitter secondPoint. aCurveFitter thirdPoint: Sensor waitButton. Sensor waitNoButton. aForm displayOn: Display at: aCurveFitter thirdPoint. aCurveFitter displayOn: Display "display the CurveFitter" "CurveFitter example"! ! !CurveFitter class methodsFor: 'instance creation'! new | newSelf | newSelf := super new: 3. newSelf add: 0@0. newSelf add: 0@0. newSelf add: 0@0. ^newSelf! ! PolygonMorph subclass: #CurveMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Basic'! !CurveMorph commentStamp: '' prior: 0! This is really only a shell for creating Shapes with smooth outlines.! !CurveMorph methodsFor: 'initialization' stamp: 'di 9/10/2000 14:28'! initialize super initialize. self beSmoothCurve. ! ! !CurveMorph methodsFor: 'parts bin' stamp: 'sw 6/28/2001 11:32'! initializeToStandAlone super initializeToStandAlone. self beSmoothCurve. ! ! !CurveMorph methodsFor: 'testing' stamp: 'wiz 1/7/2005 20:02'! isCurvier "Test used by smoothing routines. If true use true closed curve splines for closed curves. If not mimic old stodgy curveMorph curves with one sharp bend. Curve overrides this test for backward compatability.." ^ (false)! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CurveMorph class instanceVariableNames: ''! !CurveMorph class methodsFor: 'instance creation' stamp: 'tk 11/14/2001 17:47'! arrowPrototype | aa | aa := PolygonMorph vertices: (Array with: 5@40 with: 5@8 with: 35@8 with: 35@40) color: Color black borderWidth: 2 borderColor: Color black. aa beSmoothCurve; makeOpen; makeForwardArrow. "is already open" aa dashedBorder: {10. 10. Color red}. "A dash spec is a 3- or 5-element array with { length of normal border color. length of alternate border color. alternate border color}" aa computeBounds. ^ aa! ! PolygonMorph subclass: #CurvierMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Basic-NewCurve'! !CurvierMorph commentStamp: '' prior: 0! I want to be merged into PolygonMorph. I implement Closed Cubic Curves and restructured routines to ease maintence and development. New way to calculate curves. cVariables SlopeConstantsCache anArray size 2 indexed by nVerts \\2 . Each element is an array of integers. The integers represent the constants for calculating slopes for closed cubic curves from the vertices. Class Variable SlopeConstantsCache holds a pair of arrays for even and odd number of vertices( aka knots). Each array holds a series of constants in Integer form. This allows slopes to be calculated directly from the array of knots. Wonderfully it turns out that only two arrays are needed. By matching up the knots equidistant from the point in question; Summing the weighted differences of the pairs the unscaled slope can be arrived at. The scale needed to get the slopes needed is trice the reciprical of the next integer in the series. We leave the division til last to get the full benifit of the integer arithmetic. Rounding the vertices before calculation is recommended. Instead of calculating the number of curve subsegments in lineSegDo we add a ninth array to curve state to allow the number to be precalculated. Getting better looking curves motivates finding a better way of guessing n. So this provides a framework for trying. For the first pass we just used the constant 12 for every thing. In the second pass we judge the number of segments by starting with two and doubling the number until the distance of the curve no longer increases. Then we hone in using a binary search to find the smallest number of segments with that same curve length. We have changed some assumptions. Previously curves were figured by solving for the second derivative first and using the results to determine the slope and the third derivative. So lineSegDo counted on the last second deriv being a number it could use in its calculation of the number of subsegments. Currently we just solve for slopes and the second and third derivs are derived from that. Also the derivation for the second and third derivs only assume C(1) (first derivitive continuity). The calculations for the slopes are the only calcs using C(2) continuity. Therefore the slopes can alternately be chosen to fit some other chriteria and the resulting curves will still be smooth to the first degree. A useful variant of closed slopes is to scale them by a constant. Also the last of each element of curvestate always reflects a closing segment. And we don't add an extra row for closed curves anymore. That is now lineSegDo's responsibility to be aware of as it was already doing with segmented curves. So the last n does not track its old value. Preferences: A Preference has been added to toggle between the old (ugly) closed curves based on natural cubic slopes and the new smooth algorythim. This doesn't make much difference while newcurves are a subclass of polygons but the ambition is for newcurves to supercede polygons. This will allow backwards compatibility. Shapes: With closed curves a smooth oval results from rectagular or diamond vertices. So two menuitems have been added (to PolygonMorph) that allow the vertices to be set to these shapes using the current bounds of the polygon. The former state of vertices will be lost but it seems useful to lose a complicated shape and start fresh with a simple symmetrical one. Furthur on: Modify curveState to only contain slope and higher deriv information. Let the information about the knots only be held only in the vertices of the polygon. Once that is done curvestate will not have to be recalcutaled each time the polygon is moved but only when its shape changes. There is also some possible speed up to be had by refining or experimenting with other number of segment calculating schemes but not as much as preserving curvestate over a move. Furthur furthur on: Figure out how to combine straight and curved segments into a single shape in a pleasing way. ! !CurvierMorph methodsFor: 'initialization' stamp: 'wiz 11/16/2004 21:35'! initialize "We use an oval shape because we wear it well." super initialize. self beSmoothCurve. self diamondOval! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CurvierMorph class instanceVariableNames: ''! !CurvierMorph class methodsFor: 'initialization' stamp: 'wiz 11/6/2004 23:16'! initialize "CurvierMorph initialize" Preferences preferenceAt: #Curvier ifAbsent: [Preferences addPreference: #Curvier category: #morphic default: true balloonHelp: 'if true, closed CurvierMorphs will be smoother and more symmetrical all about. If false they will mimic the old curve shapes with the one sharp bend.']. self registerInFlapsRegistry! ! !CurvierMorph class methodsFor: 'initialization' stamp: 'wiz 11/6/2004 23:17'! registerInFlapsRegistry "Register the receiver in the system's flaps registry" self environment at: #Flaps ifPresent: [:cl | cl registerQuad: #(#CurvierMorph #authoringPrototype 'Curvier' 'A curve' ) forFlapNamed: 'PlugIn Supplies'. cl registerQuad: #(#CurvierMorph #authoringPrototype 'Curvier' 'A curve' ) forFlapNamed: 'Supplies']! ! SelectionMenu subclass: #CustomMenu instanceVariableNames: 'labels dividers lastDivider title targets arguments' classVariableNames: '' poolDictionaries: '' category: 'ST80-Menus'! !CustomMenu commentStamp: '' prior: 0! I am used to build menus on-the-fly. I maintain lists of menu items, actions (usually symbols to be sent as messages), and menu section dividing lines to which my clients may append new entries and lines by sending me the messages: add: aString action: anAction addLine After the menu is constructed, it may be invoked with one of the following messages: startUp: initialSelection startUp I am a subclass of ActionMenu, so I inherit a number of instance variables. The ones I am particularly concerned with are: items _ an OrderedCollection of strings to appear in the menu selectors _ an OrderedCollection of Symbols to be used as message selectors lineArray _ an OrderedCollection of line positions lastLine _ used to keep track of the last line to avoid making duplicate entries in lineArray! !CustomMenu methodsFor: '*morphic-invocation' stamp: 'wiz 7/20/2004 12:18'! startUp: initialSelection withCaption: caption at: aPoint "Build and invoke this menu with the given initial selection and caption. Answer the selection associated with the menu item chosen by the user or nil if none is chosen." self build. initialSelection notNil ifTrue: [self preSelect: initialSelection]. ^ super startUpWithCaption: caption at: aPoint! ! !CustomMenu methodsFor: '*morphic-invocation' stamp: 'wiz 7/20/2004 12:20'! startUpWithCaption: caption at: aPoint "Build and invoke this menu with no initial selection. Answer the selection associated with the menu item chosen by the user or nil if none is chosen; use the provided caption" ^ self startUp: nil withCaption: caption at: aPoint! ! !CustomMenu methodsFor: 'compatibility' stamp: 'ads 2/20/2003 08:59'! add: aString subMenu: aMenu target: target selector: aSymbol argumentList: argList "Create a sub-menu with the given label. This isn't really a sub-menu the way Morphic does it; it'll just pop up another menu." self add: aString target: aMenu selector: #invokeOn: argumentList: argList asArray.! ! !CustomMenu methodsFor: 'compatibility' stamp: 'sumim 2/10/2002 01:23'! add: aString target: target selector: aSymbol argument: arg "Append a menu item with the given label. If the item is selected, it will send the given selector to the target object with the given argument." self add: aString target: target selector: aSymbol argumentList: (Array with: arg)! ! !CustomMenu methodsFor: 'compatibility' stamp: 'sumim 2/10/2002 01:18'! add: aString target: target selector: aSymbol argumentList: argList "Append a menu item with the given label. If the item is selected, it will send the given selector to the target object with the given arguments. If the selector takes one more argument than the number of arguments in the given list, then the triggering event is supplied as as the last argument." self add: aString action: aSymbol. targets addLast: target. arguments addLast: argList asArray ! ! !CustomMenu methodsFor: 'compatibility' stamp: 'nk 2/15/2004 16:19'! addService: aService for: serviceUser "Append a menu item with the given service. If the item is selected, it will perform the given service." aService addServiceFor: serviceUser toMenu: self.! ! !CustomMenu methodsFor: 'compatibility' stamp: 'nk 2/15/2004 16:02'! addServices2: services for: served extraLines: linesArray services withIndexDo: [:service :i | service addServiceFor: served toMenu: self. (linesArray includes: i) ifTrue: [self addLine] ]! ! !CustomMenu methodsFor: 'compatibility' stamp: 'sumim 2/10/2002 01:20'! addServices: services for: served extraLines: linesArray services withIndexDo: [:service :i | self addService: service for: served. (linesArray includes: i) | service useLineAfter ifTrue: [self addLine]]! ! !CustomMenu methodsFor: 'compatibility' stamp: 'sw 2/16/2002 00:57'! arguments "Answer my arguments, initializing them to an empty collection if they're found to be nil." ^ arguments ifNil: [arguments := OrderedCollection new]! ! !CustomMenu methodsFor: 'compatibility' stamp: 'sw 2/16/2002 00:57'! targets "Answer my targets, initializing them to an empty collection if found to be nil" ^ targets ifNil: [targets := OrderedCollection new]! ! !CustomMenu methodsFor: 'construction' stamp: 'dhhi 9/14/2000 22:39'! add: aString action: actionItem "Add the given string as the next menu item. If it is selected, the given action (usually but not necessarily a symbol) will be returned to the client." | s | aString ifNil: [^ self addLine]. s := String new: aString size + 2. s at: 1 put: Character space. s replaceFrom: 2 to: s size - 1 with: aString. s at: s size put: Character space. labels addLast: s. selections addLast: actionItem.! ! !CustomMenu methodsFor: 'construction'! addLine "Append a line to the menu after the last entry. Suppress duplicate lines." (lastDivider ~= selections size) ifTrue: [ lastDivider := selections size. dividers addLast: lastDivider].! ! !CustomMenu methodsFor: 'construction' stamp: 'sd 3/1/2008 21:35'! addList: listOfTuplesAndDashes "Add a menu item to the receiver for each tuple in the given list of the form ( ). Add a line for each dash (-) in the list. The tuples may have an optional third element, providing balloon help for the item, but such an element is ignored in mvc." listOfTuplesAndDashes do: [:aTuple | aTuple == #- ifTrue: [self addLine] ifFalse: [self add: aTuple first capitalized action: aTuple second]] "CustomMenu new addList: #( ('apples' buyApples) ('oranges' buyOranges) - ('milk' buyMilk)); startUp" ! ! !CustomMenu methodsFor: 'construction' stamp: 'sw 8/12/2002 17:14'! addStayUpItem "For compatibility with MenuMorph. Here it is a no-op"! ! !CustomMenu methodsFor: 'construction' stamp: 'nk 11/25/2003 10:00'! addTranslatedList: listOfTuplesAndDashes "Add a menu item to the receiver for each tuple in the given list of the form ( ). Add a line for each dash (-) in the list. The tuples may have an optional third element, providing balloon help for the item, but such an element is ignored in mvc. The first element will be translated." listOfTuplesAndDashes do: [:aTuple | aTuple == #- ifTrue: [self addLine] ifFalse: [self add: aTuple first translated action: aTuple second]] "CustomMenu new addTranslatedList: #( ('apples' buyApples) ('oranges' buyOranges) - ('milk' buyMilk)); startUp" ! ! !CustomMenu methodsFor: 'construction' stamp: 'sw 7/20/1999 18:47'! balloonTextForLastItem: aString "Vacuous backstop provided for compatibility with MorphicMenu"! ! !CustomMenu methodsFor: 'construction' stamp: 'jm 8/20/1998 08:34'! labels: aString font: aFont lines: anArrayOrNil "This method allows the receiver to accept old-style SelectionMenu creation messages. It should be used only for backward compatibility during the MVC-to-Morphic transition. New code should be written using the other menu construction protocol such as addList:." | labelList linesArray | labelList := (aString findTokens: String cr) asArray. anArrayOrNil ifNil: [linesArray := #()] ifNotNil: [linesArray := anArrayOrNil]. 1 to: labelList size do: [:i | self add: (labelList at: i) action: (labelList at: i). (linesArray includes: i) ifTrue: [self addLine]]. font ifNotNil: [font := aFont]. ! ! !CustomMenu methodsFor: 'construction' stamp: 'yo 8/28/2002 22:34'! labels: labelList lines: linesArray selections: selectionsArray "This method allows the receiver to accept old-style SelectionMenu creation messages. It should be used only for backward compatibility during the MVC-to-Morphic transition. New code should be written using the other menu construction protocol such as addList:." "Labels can be either a sting with embedded crs, or a collection of strings." | labelArray | labelList isString ifTrue: [labelArray := labelList findTokens: String cr] ifFalse: [labelArray := labelList]. 1 to: labelArray size do: [:i | self add: (labelArray at: i) action: (selectionsArray at: i). (linesArray includes: i) ifTrue: [self addLine]]. ! ! !CustomMenu methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:50'! initialize super initialize. labels := OrderedCollection new. selections := OrderedCollection new. dividers := OrderedCollection new. lastDivider := 0. targets := OrderedCollection new. arguments := OrderedCollection new ! ! !CustomMenu methodsFor: 'initialization' stamp: 'sw 8/18/1998 12:01'! title: aTitle title := aTitle! ! !CustomMenu methodsFor: 'invocation' stamp: 'sw 2/17/2002 04:48'! invokeOn: targetObject "Pop up this menu and return the result of sending to the target object the selector corresponding to the menu item selected by the user. Return nil if no item is selected. If the chosen selector has arguments, obtain them from my arguments" ^ self invokeOn: targetObject orSendTo: nil! ! !CustomMenu methodsFor: 'invocation' stamp: 'marcus.denker 9/14/2008 21:15'! invokeOn: targetObject defaultSelection: defaultSelection "Invoke the menu with the given default selection (i.e. one of my 'action' symbols). Answer the 'action' selector associated with the menu item chosen by the user or nil if none is chosen." | sel | sel := self startUp: defaultSelection. sel ifNotNil: [ sel numArgs = 0 ifTrue: [^ targetObject perform: sel] ifFalse: [^ targetObject perform: sel with: nil]]. ^ nil ! ! !CustomMenu methodsFor: 'invocation' stamp: 'sw 11/16/2002 23:45'! invokeOn: targetObject orSendTo: anObject "Pop up this menu and return the result of sending to the target object the selector corresponding to the menu item selected by the user. Return nil if no item is selected. If the chosen selector has arguments, obtain appropriately. If the recipient does not respond to the resulting message, send it to the alternate object provided" | aSelector anIndex recipient | ^ (aSelector := self startUp) ifNotNil: [anIndex := self selection. recipient := ((targets := self targets) isEmptyOrNil or: [anIndex > targets size]) ifTrue: [targetObject] ifFalse: [targets at: anIndex]. aSelector numArgs == 0 ifTrue: [recipient perform: aSelector orSendTo: anObject] ifFalse: [recipient perform: aSelector withArguments: (self arguments at: anIndex)]]! ! !CustomMenu methodsFor: 'invocation'! startUp "Build and invoke this menu with no initial selection. Answer the selection associated with the menu item chosen by the user or nil if none is chosen." ^ self startUp: nil! ! !CustomMenu methodsFor: 'invocation' stamp: 'sw 8/18/1998 12:01'! startUp: initialSelection "Build and invoke this menu with the given initial selection. Answer the selection associated with the menu item chosen by the user or nil if none is chosen." ^ self startUp: initialSelection withCaption: title! ! !CustomMenu methodsFor: 'invocation'! startUp: initialSelection withCaption: caption "Build and invoke this menu with the given initial selection and caption. Answer the selection associated with the menu item chosen by the user or nil if none is chosen." self build. (initialSelection notNil) ifTrue: [self preSelect: initialSelection]. ^ super startUpWithCaption: caption! ! !CustomMenu methodsFor: 'invocation' stamp: 'sw 7/31/97 19:31'! startUpWithCaption: caption "Build and invoke this menu with no initial selection. Answer the selection associated with the menu item chosen by the user or nil if none is chosen; use the provided caption" ^ self startUp: nil withCaption: caption! ! !CustomMenu methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:05'! build "Turn myself into an invokable ActionMenu." | stream | stream := (String new) writeStream. labels do: [:label | stream nextPutAll: label; cr]. (labels isEmpty) ifFalse: [stream skip: -1]. "remove final cr" super labels: stream contents font: MenuStyle defaultFont lines: dividers! ! !CustomMenu methodsFor: 'private' stamp: 'di 4/14/1999 21:28'! preSelect: action "Pre-select and highlight the menu item associated with the given action." | i | i := selections indexOf: action ifAbsent: [^ self]. marker ifNil: [self computeForm]. marker := marker align: marker topLeft with: (marker left)@(frame inside top + (marker height * (i - 1))). selection := i.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CustomMenu class instanceVariableNames: ''! !CustomMenu class methodsFor: 'example' stamp: 'sw 11/8/1999 17:27'! example "CustomMenu example" | menu | menu := CustomMenu new. menu add: 'apples' action: #apples. menu add: 'oranges' action: #oranges. menu addLine. menu addLine. "extra lines ignored" menu add: 'peaches' action: #peaches. menu addLine. menu add: 'pears' action: #pears. menu addLine. ^ menu startUp: #apples "NB: The following is equivalent to the above, but uses the compact #fromArray: consruct: (CustomMenu fromArray: #( ('apples' apples) ('oranges' oranges) - - ('peaches' peaches) - ('pears' pears) -)) startUp: #apples"! ! QuestionWithoutCancelDialogWindow subclass: #CustomQuestionDialogWindow instanceVariableNames: 'yesButton noButton' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !CustomQuestionDialogWindow commentStamp: 'gvc 9/23/2008 11:59' prior: 0! QuestionDialog supporting custom text/buttons for yes/no choices.! !CustomQuestionDialogWindow methodsFor: 'accessing' stamp: 'gvc 1/10/2008 11:30'! noButton "Answer the value of noButton" ^ noButton! ! !CustomQuestionDialogWindow methodsFor: 'accessing' stamp: 'gvc 1/10/2008 11:30'! noButton: anObject "Set the value of noButton" noButton := anObject! ! !CustomQuestionDialogWindow methodsFor: 'accessing' stamp: 'gvc 1/10/2008 11:30'! yesButton "Answer the value of yesButton" ^ yesButton! ! !CustomQuestionDialogWindow methodsFor: 'accessing' stamp: 'gvc 1/10/2008 11:30'! yesButton: anObject "Set the value of yesButton" yesButton := anObject! ! !CustomQuestionDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/10/2008 11:31'! defaultNoButton "Answer a default no button." ^self newNoButton! ! !CustomQuestionDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/23/2008 12:02'! defaultYesButton "Answer a default yes button." ^self newYesButton isDefault: true! ! !CustomQuestionDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/10/2008 11:42'! initialize "Initialize the receiver." self yesButton: self defaultYesButton; noButton: self defaultNoButton. super initialize! ! !CustomQuestionDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/23/2008 12:02'! newButtons "Answer new buttons as appropriate." ^{self yesButton. self noButton}! ! !CustomQuestionDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/10/2008 11:47'! noText: aStringOrText help: helpString "Set the no button label." self noButton hResizing: #shrinkWrap; label: aStringOrText; setBalloonText: helpString! ! !CustomQuestionDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/10/2008 11:47'! yesText: aStringOrText help: helpString "Set the yes button label." self yesButton hResizing: #shrinkWrap; label: aStringOrText; setBalloonText: helpString! ! Object subclass: #DamageRecorder instanceVariableNames: 'invalidRects totalRepaint' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'! !DamageRecorder methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 9/27/2006 12:26'! recordInvalidRect: newRect "Record the given rectangle in my damage list, a list of rectangular areas of the display that should be redraw on the next display cycle." "Details: Damaged rectangles are often identical or overlap significantly. In these cases, we merge them to reduce the number of damage rectangles that must be processed when the display is updated. Moreover, above a certain threshold, we ignore the individual rectangles completely, and simply do a complete repaint on the next cycle." | mergeRect a | totalRepaint ifTrue: [^ self]. "planning full repaint; don't bother collecting damage" invalidRects do: [:rect | ((a := (rect intersect: newRect) area) > 40 and: ["Avoid combining a vertical and horizontal rects. Can make a big diff and we only test when likely." a > (newRect area // 4) or: [a > (rect area // 4)]]) ifTrue: ["merge rectangle in place (see note below) if there is significant overlap" rect setOrigin: (rect origin min: newRect origin) truncated corner: (rect corner max: newRect corner) truncated. ^ self]]. invalidRects size >= 50 ifTrue: ["if there are too many separate areas, merge them all" mergeRect := Rectangle merging: invalidRects. self reset. invalidRects addLast: mergeRect]. "add the given rectangle to the damage list" "Note: We make a deep copy of all rectangles added to the damage list, since rectangles in this list may be extended in place." invalidRects addLast: (newRect topLeft truncated corner: newRect bottomRight truncated). ! ! !DamageRecorder methodsFor: 'initialization' stamp: 'sma 6/5/2000 11:55'! reset "Clear the damage list." invalidRects := OrderedCollection new: 15. totalRepaint := false ! ! !DamageRecorder methodsFor: 'recording'! doFullRepaint "Record that a full redisplay is needed. No further damage rectangles will be recorded until after the next reset." ^ totalRepaint := true. ! ! !DamageRecorder methodsFor: 'recording'! invalidRectsFullBounds: aRectangle "Return a collection of damaged rectangles for the given canvas. If a total repaint has been requested, return the given rectangle." totalRepaint ifTrue: [^ Array with: aRectangle] ifFalse: [^ invalidRects copy]. ! ! !DamageRecorder methodsFor: 'testing' stamp: 'dgd 2/22/2003 14:43'! updateIsNeeded "Return true if the display needs to be updated." ^totalRepaint or: [invalidRects notEmpty]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DamageRecorder class instanceVariableNames: ''! !DamageRecorder class methodsFor: 'instance creation'! new ^ super new reset ! ! SimpleBorder subclass: #DashedBorder instanceVariableNames: 'dashColors dashLengths' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Borders'! !DashedBorder commentStamp: 'gvc 5/18/2007 13:28' prior: 0! Border style supporting dashed lines of configurable patterns and colours.! !DashedBorder methodsFor: 'accessing' stamp: 'gvc 4/24/2007 15:48'! dashColors "Answer the value of dashColors" ^ dashColors! ! !DashedBorder methodsFor: 'accessing' stamp: 'gvc 4/24/2007 15:48'! dashColors: anObject "Set the value of dashColors" dashColors := anObject! ! !DashedBorder methodsFor: 'accessing' stamp: 'gvc 4/24/2007 15:59'! dashColors: cols dashLengths: lens "Set the colours and lengths." cols size = lens size ifFalse: [self error: 'Colors and Lengths must have the same size']. self dashColors: cols; dashLengths: lens! ! !DashedBorder methodsFor: 'accessing' stamp: 'gvc 4/24/2007 15:48'! dashLengths "Answer the value of dashLengths" ^ dashLengths! ! !DashedBorder methodsFor: 'accessing' stamp: 'gvc 4/24/2007 15:48'! dashLengths: anObject "Set the value of dashLengths" dashLengths := anObject! ! !DashedBorder methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 15:51'! frameRectangle: aRectangle on: aCanvas "Frame the given rectangle on aCanvas" (aRectangle width < self width or: [aRectangle height < self width]) ifTrue: [^self]." don't do if too small" aCanvas frameRectangle: aRectangle width: self width colors: self dashColors dashes: self dashLengths! ! !DashedBorder methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 15:50'! initialize "Initialize the receiver." super initialize. self dashColors: {Color black. Color white}; dashLengths: #(1 1)! ! !DashedBorder methodsFor: 'as yet unclassified' stamp: 'gvc 8/8/2007 17:21'! style "Answer #dashed." ^#dashed! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DashedBorder class instanceVariableNames: ''! !DashedBorder class methodsFor: 'as yet unclassified' stamp: 'gvc 8/8/2007 16:39'! width: width dashColors: cols dashLengths: lens "Answer a new instance of the receiver with the given width, colours and lengths." ^self new width: width; dashColors: cols dashLengths: lens! ! Stream subclass: #DataStream instanceVariableNames: 'byteStream topCall basePos' classVariableNames: 'TypeMap' poolDictionaries: '' category: 'System-Object Storage'! !DataStream commentStamp: '' prior: 0! This is the save-to-disk facility. A DataStream can store one or more objects in a persistent form. To handle objects with sharing and cycles, you must use a ReferenceStream instead of a DataStream. (Or SmartRefStream.) ReferenceStream is typically faster and produces smaller files because it doesn't repeatedly write the same Symbols. Here is the way to use DataStream and ReferenceStream: rr _ ReferenceStream fileNamed: 'test.obj'. rr nextPut: . rr close. To get it back: rr _ ReferenceStream fileNamed: 'test.obj'. _ rr next. rr close. Each object to be stored has two opportunities to control what gets stored. On the high level, objectToStoreOnDataStream allows you to substitute another object on the way out. The low level hook is storeDataOn:. The read-in counterparts to these messages are comeFullyUpOnReload and (class) readDataFrom:size:. See these methods, and the class DiskProxy, for more information about externalizing and internalizing. NOTE: A DataStream should be treated as a write-stream for writing. It is a read-stream for reading. It is not a ReadWriteStream. ! !DataStream methodsFor: 'other'! atEnd "Answer true if the stream is at the end." ^ byteStream atEnd! ! !DataStream methodsFor: 'other'! byteStream ^ byteStream! ! !DataStream methodsFor: 'other'! close "Close the stream." | bytes | byteStream closed ifFalse: [ bytes := byteStream position. byteStream close] ifTrue: [bytes := 'unknown']. ^ bytes! ! !DataStream methodsFor: 'other' stamp: 'nk 3/12/2004 21:56'! contents ^byteStream contents! ! !DataStream methodsFor: 'other' stamp: 'yo 12/3/2004 17:14'! errorWriteReference: anInteger "PRIVATE -- Raise an error because this case of nextPut:'s perform: shouldn't be called. -- 11/15/92 jhm" self error: 'This should never be called'! ! !DataStream methodsFor: 'other'! flush "Guarantee that any writes to me are actually recorded on disk. -- 11/17/92 jhm" ^ byteStream flush! ! !DataStream methodsFor: 'other'! next: anInteger "Answer an Array of the next anInteger objects in the stream." | array | array := Array new: anInteger. 1 to: anInteger do: [:i | array at: i put: self next]. ^ array! ! !DataStream methodsFor: 'other' stamp: 'tk 3/5/2002 09:51'! nextAndClose "Speedy way to grab one object. Only use when we are inside an object binary file. Do not use for the start of a SmartRefStream mixed code-and-object file." | obj | obj := self next. self close. ^ obj! ! !DataStream methodsFor: 'other' stamp: 'ar 2/24/2001 22:45'! project ^nil! ! !DataStream methodsFor: 'other'! reset "Reset the stream." byteStream reset! ! !DataStream methodsFor: 'other' stamp: 'tk 5/29/97'! rootObject "Return the object at the root of the tree we are filing out. " ^ topCall! ! !DataStream methodsFor: 'other' stamp: 'tk 5/29/97'! rootObject: anObject "Return the object at the root of the tree we are filing out. " topCall := anObject! ! !DataStream methodsFor: 'other' stamp: '6/9/97 08:03 di'! setStream: aStream "PRIVATE -- Initialization method." aStream binary. basePos := aStream position. "Remember where we start. Earlier part of file contains a class or method file-in. Allow that to be edited. We don't deal in absolute file locations." byteStream := aStream.! ! !DataStream methodsFor: 'other' stamp: 'tk 8/18/1998 08:59'! setStream: aStream reading: isReading "PRIVATE -- Initialization method." aStream binary. basePos := aStream position. "Remember where we start. Earlier part of file contains a class or method file-in. Allow that to be edited. We don't deal in absolute file locations." byteStream := aStream.! ! !DataStream methodsFor: 'other'! size "Answer the stream's size." ^ byteStream size! ! !DataStream methodsFor: 'other' stamp: 'tk 7/12/1998 13:16'! vacantRef "Answer the magic 32-bit constant we use ***ON DISK*** as a stream 'reference position' to identify a reference that's not yet filled in. This must be a value that won't be used as an ordinary reference. Cf. outputReference: and readReference. -- NOTE: We could use a different type ID for vacant-refs rather than writing object-references with a magic value. (The type ID and value are overwritten by ordinary object-references when weak refs are fullfilled.)" ^ SmallInteger maxVal! ! !DataStream methodsFor: 'write and read' stamp: '6/9/97 08:14 tk'! beginInstance: aClass size: anInteger "This is for use by storeDataOn: methods. Cf. Object>>storeDataOn:." "Addition of 1 seems to make extra work, since readInstance has to compensate. Here for historical reasons dating back to Kent Beck's original implementation in late 1988. In ReferenceStream, class is just 5 bytes for shared symbol. SmartRefStream puts out the names and number of class's instances variables for checking." byteStream nextNumber: 4 put: anInteger + 1. self nextPut: aClass name! ! !DataStream methodsFor: 'write and read' stamp: 'yo 12/3/2004 17:12'! beginReference: anObject "We're starting to read anObject. Remember it and its reference position (if we care; ReferenceStream cares). Answer the reference position." ^ 0! ! !DataStream methodsFor: 'write and read'! getCurrentReference "PRIVATE -- Return the currentReference posn. Overridden by ReferenceStream." ^ 0! ! !DataStream methodsFor: 'write and read' stamp: 'tk 4/8/1999 13:11'! maybeBeginReference: internalObject "Do nothing. See ReferenceStream|maybeBeginReference:" ^ internalObject! ! !DataStream methodsFor: 'write and read' stamp: 'ar 4/10/2005 20:31'! next "Answer the next object in the stream." | type selector anObject isARefType pos internalObject | type := byteStream next. type ifNil: [pos := byteStream position. "absolute!!!!" byteStream close. "clean up" byteStream position = 0 ifTrue: [self error: 'The file did not exist in this directory'] ifFalse: [self error: 'Unexpected end of object file']. pos. "so can see it in debugger" ^ nil]. type = 0 ifTrue: [pos := byteStream position. "absolute!!!!" byteStream close. "clean up" self error: 'Expected start of object, but found 0'. ^ nil]. isARefType := self noteCurrentReference: type. selector := #(readNil readTrue readFalse readInteger "<-4" readStringOld readSymbol readByteArray "<-7" readArray readInstance readReference readBitmap "<-11" readClass readUser readFloat readRectangle readShortInst "<-16" readString readWordArray readWordArrayForSegment "<-19" readWordLike readMethod "<-21") at: type. selector == 0 ifTrue: [pos := byteStream position. "absolute!!!!" byteStream close. self error: 'file is more recent than this system'. ^ nil]. anObject := self perform: selector. "A method that recursively calls next (readArray, readInstance, objectAt:) must save & restore the current reference position." isARefType ifTrue: [self beginReference: anObject]. "After reading the externalObject, internalize it. #readReference is a special case. Either: (1) We actually have to read the object, recursively calling next, which internalizes the object. (2) We just read a reference to an object already read and thus already interalized. Either way, we must not re-internalize the object here." selector == #readReference ifTrue: [^ anObject]. internalObject := anObject comeFullyUpOnReload: self. internalObject == String ifTrue:[ "This is a hack to figure out if we're loading a String class that really should be a ByteString. Note that these days this will no longer be necessary since we use #withClassVersion: for constructing the global thus using a different classVersion will perfectly do the trick." ((anObject isKindOf: DiskProxy) and:[anObject globalObjectName == #String and:[anObject constructorSelector == #yourself]]) ifTrue:[ internalObject := ByteString]]. ^ self maybeBeginReference: internalObject! ! !DataStream methodsFor: 'write and read' stamp: 'tk 10/4/2000 10:35'! nextPut: anObject "Write anObject to the receiver stream. Answer anObject." | typeID selector objectToStore | typeID := self typeIDFor: anObject. (self tryToPutReference: anObject typeID: typeID) ifTrue: [^ anObject]. objectToStore := (self objectIfBlocked: anObject) objectForDataStream: self. objectToStore == anObject ifFalse: [typeID := self typeIDFor: objectToStore]. byteStream nextPut: typeID. selector := #(writeNil: writeTrue: writeFalse: writeInteger: writeStringOld: writeSymbol: writeByteArray: writeArray: writeInstance: errorWriteReference: writeBitmap: writeClass: writeUser: writeFloat: writeRectangle: == "<-16 short inst" writeString: writeBitmap: writeBitmap: writeWordLike: writeInstance: "CompiledMethod") at: typeID. self perform: selector with: objectToStore. ^ anObject "NOTE: If anObject is a reference type (one that we write cross-references to) but its externalized form (result of objectForDataStream:) isn't (e.g. CompiledMethod and ViewState), then we should remember its externalized form but not add to 'references'. Putting that object again should just put its external form again. That's more compact and avoids seeks when reading. But we just do the simple thing here, allowing backward-references for non-reference types like nil. So objectAt: has to compensate. Objects that externalize nicely won't contain the likes of ViewStates, so this shouldn't hurt much. writeReference: -> errorWriteReference:."! ! !DataStream methodsFor: 'write and read'! nextPutAll: aCollection "Write each of the objects in aCollection to the receiver stream. Answer aCollection." ^ aCollection do: [:each | self nextPut: each]! ! !DataStream methodsFor: 'write and read' stamp: 'yo 12/3/2004 17:25'! noteCurrentReference: typeID "PRIVATE -- If we support references for type typeID, remember the current byteStream position so we can add the next object to the 'objects' dictionary, and return true. Else return false. This method is here to be overridden by ReferenceStream" ^ false! ! !DataStream methodsFor: 'write and read' stamp: ' 6/9/97'! objectAt: anInteger "PRIVATE -- Read & return the object at a given stream position. 08:18 tk anInteger is a relative file position. " | savedPosn anObject refPosn | savedPosn := byteStream position. "absolute" refPosn := self getCurrentReference. "relative position" byteStream position: anInteger + basePos. "was relative" anObject := self next. self setCurrentReference: refPosn. "relative position" byteStream position: savedPosn. "absolute" ^ anObject! ! !DataStream methodsFor: 'write and read' stamp: 'tk 3/13/98 22:16'! objectIfBlocked: anObject "We don't do any blocking" ^ anObject! ! !DataStream methodsFor: 'write and read' stamp: '6/9/97 08:46 tk'! outputReference: referencePosn "PRIVATE -- Output a reference to the object at integer stream position referencePosn (relative to basePos). To output a weak reference to an object not yet written, supply (self vacantRef) for referencePosn." byteStream nextPut: 10. "reference typeID" byteStream nextNumber: 4 put: referencePosn "relative position"! ! !DataStream methodsFor: 'write and read' stamp: '6/9/97 08:32 tk'! readArray "PRIVATE -- Read the contents of an Array. We must do beginReference: here after instantiating the Array but before reading its contents, in case the contents reference the Array. beginReference: will be sent again when we return to next, but that's ok as long as we save and restore the current reference position over recursive calls to next." | count array refPosn | count := byteStream nextNumber: 4. refPosn := self beginReference: (array := Array new: count). "relative pos" 1 to: count do: [:i | array at: i put: self next]. self setCurrentReference: refPosn. "relative pos" ^ array! ! !DataStream methodsFor: 'write and read'! readBitmap "PRIVATE -- Read the contents of a Bitmap." ^ Bitmap newFromStream: byteStream "Note that the reader knows that the size is in long words, but the data is in bytes."! ! !DataStream methodsFor: 'write and read'! readBoolean "PRIVATE -- Read the contents of a Boolean. This is here only for compatibility with old data files." ^ byteStream next ~= 0! ! !DataStream methodsFor: 'write and read' stamp: 'jm 8/19/1998 17:00'! readByteArray "PRIVATE -- Read the contents of a ByteArray." | count | count := byteStream nextNumber: 4. ^ byteStream next: count "assume stream is in binary mode" ! ! !DataStream methodsFor: 'write and read' stamp: 'tk 3/24/98 10:29'! readClass "Should never be executed because a DiskProxy, not a clas comes in." ^ self error: 'Classes should be filed in'! ! !DataStream methodsFor: 'write and read'! readFalse "PRIVATE -- Read the contents of a False." ^ false! ! !DataStream methodsFor: 'write and read'! readFloat "PRIVATE -- Read the contents of a Float. This is the fast way to read a Float. We support 8-byte Floats here. Non-IEEE" | new | new := Float new: 2. "To get an instance" new at: 1 put: (byteStream nextNumber: 4). new at: 2 put: (byteStream nextNumber: 4). ^ new! ! !DataStream methodsFor: 'write and read' stamp: 'yo 12/3/2004 17:12'! readFloatString "PRIVATE -- Read the contents of a Float string. This is the slow way to read a Float--via its string rep'n. It's here for compatibility with old data files." ^ Float readFrom: (byteStream next: (byteStream nextNumber: 4))! ! !DataStream methodsFor: 'write and read' stamp: 'tk 1/8/97'! readInstance "PRIVATE -- Read the contents of an arbitrary instance. ASSUMES: readDataFrom:size: sends me beginReference: after it instantiates the new object but before reading nested objects. NOTE: We must restore the current reference position after recursive calls to next. Let the instance, not the class read the data. " | instSize aSymbol refPosn anObject newClass | instSize := (byteStream nextNumber: 4) - 1. refPosn := self getCurrentReference. aSymbol := self next. newClass := Smalltalk at: aSymbol asSymbol. anObject := newClass isVariable "Create object here" ifFalse: [newClass basicNew] ifTrue: [newClass basicNew: instSize - (newClass instSize)]. self setCurrentReference: refPosn. "before readDataFrom:size:" anObject := anObject readDataFrom: self size: instSize. self setCurrentReference: refPosn. "before returning to next" ^ anObject! ! !DataStream methodsFor: 'write and read'! readInteger "PRIVATE -- Read the contents of a SmallInteger." ^ byteStream nextInt32 "signed!!!!!!"! ! !DataStream methodsFor: 'write and read' stamp: 'tk 10/6/2000 14:36'! readMethod "PRIVATE -- Read the contents of an arbitrary instance. ASSUMES: readDataFrom:size: sends me beginReference: after it instantiates the new object but before reading nested objects. NOTE: We must restore the current reference position after recursive calls to next. Let the instance, not the class read the data. " | instSize refPosn newClass className xxHeader nLits byteCodeSizePlusTrailer newMethod lits | instSize := (byteStream nextNumber: 4) - 1. refPosn := self getCurrentReference. className := self next. newClass := Smalltalk at: className asSymbol. xxHeader := self next. "nArgs := (xxHeader >> 24) bitAnd: 16rF." "nTemps := (xxHeader >> 18) bitAnd: 16r3F." "largeBit := (xxHeader >> 17) bitAnd: 1." nLits := (xxHeader >> 9) bitAnd: 16rFF. "primBits := ((xxHeader >> 19) bitAnd: 16r600) + (xxHeader bitAnd: 16r1FF)." byteCodeSizePlusTrailer := instSize - (newClass instSize "0") - (nLits + 1 * 4). newMethod := newClass newMethod: byteCodeSizePlusTrailer header: xxHeader. self setCurrentReference: refPosn. "before readDataFrom:size:" self beginReference: newMethod. lits := newMethod numLiterals + 1. "counting header" 2 to: lits do: [:ii | newMethod objectAt: ii put: self next]. lits*4+1 to: newMethod basicSize do: [:ii | newMethod basicAt: ii put: byteStream next]. "Get raw bytes directly from the file" self setCurrentReference: refPosn. "before returning to next" ^ newMethod! ! !DataStream methodsFor: 'write and read'! readNil "PRIVATE -- Read the contents of an UndefinedObject." ^ nil! ! !DataStream methodsFor: 'write and read' stamp: ' 6/9/97'! readRectangle "Read a compact Rectangle. Rectangles with values outside +/- 2047 were stored as normal objects (type=9). They will not come here. 17:22 tk" "Encoding is four 12-bit signed numbers. 48 bits in next 6 bytes. 17:24 tk" | acc left top right bottom | acc := byteStream nextNumber: 3. left := acc bitShift: -12. (left bitAnd: 16r800) ~= 0 ifTrue: [left := left - 16r1000]. "sign" top := acc bitAnd: 16rFFF. (top bitAnd: 16r800) ~= 0 ifTrue: [top := top - 16r1000]. "sign" acc := byteStream nextNumber: 3. right := acc bitShift: -12. (right bitAnd: 16r800) ~= 0 ifTrue: [right := right - 16r1000]. "sign" bottom := acc bitAnd: 16rFFF. (bottom bitAnd: 16r800) ~= 0 ifTrue: [bottom := bottom - 16r1000]. "sign" ^ Rectangle left: left right: right top: top bottom: bottom ! ! !DataStream methodsFor: 'write and read' stamp: 'tk 1/5/2000 11:47'! readReference "Read the contents of an object reference. (Cf. outputReference:) File is not now positioned at this object." | referencePosition | ^ (referencePosition := (byteStream nextNumber: 4)) = self vacantRef "relative" ifTrue: [nil] ifFalse: [self objectAt: referencePosition] "relative pos"! ! !DataStream methodsFor: 'write and read' stamp: 'tk 1/8/97'! readShortInst "Read the contents of an arbitrary instance that has a short header. ASSUMES: readDataFrom:size: sends me beginReference: after it instantiates the new object but before reading nested objects. NOTE: We must restore the current reference position after recursive calls to next. Let the instance, not the class read the data. " | instSize aSymbol refPosn anObject newClass | instSize := (byteStream next) - 1. "one byte of size" refPosn := self getCurrentReference. aSymbol := self readShortRef. "class symbol in two bytes of file pos" newClass := Smalltalk at: aSymbol asSymbol. anObject := newClass isVariable "Create object here" ifFalse: [newClass basicNew] ifTrue: [newClass basicNew: instSize - (newClass instSize)]. self setCurrentReference: refPosn. "before readDataFrom:size:" anObject := anObject readDataFrom: self size: instSize. self setCurrentReference: refPosn. "before returning to next" ^ anObject! ! !DataStream methodsFor: 'write and read' stamp: 'tk 7/12/1998 13:32'! readShortRef "Read an object reference from two bytes only. Original object must be in first 65536 bytes of the file. Relative to start of data. vacantRef not a possibility." ^ self objectAt: (byteStream nextNumber: 2)! ! !DataStream methodsFor: 'write and read' stamp: 'tk 6/8/1998 21:03'! readString | str | byteStream ascii. str := byteStream nextString. byteStream binary. ^ str ! ! !DataStream methodsFor: 'write and read' stamp: 'tk 6/8/1998 21:27'! readStringOld ^ byteStream nextStringOld! ! !DataStream methodsFor: 'write and read'! readSymbol "PRIVATE -- Read the contents of a Symbol." ^ self readString asSymbol! ! !DataStream methodsFor: 'write and read'! readTrue "PRIVATE -- Read the contents of a True." ^ true! ! !DataStream methodsFor: 'write and read' stamp: 'tk 3/4/1999 22:58'! readUser "Reconstruct both the private class and the instance. Still used??" ^ self readInstance. "Will create new unique class" ! ! !DataStream methodsFor: 'write and read' stamp: 'tk 1/24/2000 23:20'! readWordArray "PRIVATE -- Read the contents of a WordArray." ^ WordArray newFromStream: byteStream "Size is number of long words."! ! !DataStream methodsFor: 'write and read' stamp: 'tk 1/24/2000 23:23'! readWordArrayForSegment "Read the contents of a WordArray ignoring endianness." ^ WordArrayForSegment newFromStream: byteStream "Size is number of long words."! ! !DataStream methodsFor: 'write and read' stamp: 'tk 2/3/2000 21:11'! readWordLike | refPosn aSymbol newClass anObject | "Can be used by any class that is bits and not bytes (WordArray, Bitmap, SoundBuffer, etc)." refPosn := self getCurrentReference. aSymbol := self next. newClass := Smalltalk at: aSymbol asSymbol. anObject := newClass newFromStream: byteStream. "Size is number of long words." self setCurrentReference: refPosn. "before returning to next" ^ anObject ! ! !DataStream methodsFor: 'write and read' stamp: 'tk 9/24/2000 15:39'! replace: original with: proxy "We may wish to remember that in some field, the original object is being replaced by the proxy. For the hybred scheme that collects with a DummyStream and writes an ImageSegment, it needs to hold onto the originals so they will appear in outPointers, and be replaced." "do nothing"! ! !DataStream methodsFor: 'write and read'! setCurrentReference: refPosn "PRIVATE -- Set currentReference to refPosn. Noop here. Cf. ReferenceStream."! ! !DataStream methodsFor: 'write and read' stamp: 'yo 12/3/2004 16:59'! tryToPutReference: anObject typeID: typeID "PRIVATE -- If we support references for type typeID, and if anObject already appears in my output stream, then put a reference to the place where anObject already appears. If we support references for typeID but didn't already put anObject, then associate the current stream position with anObject in case one wants to nextPut: it again. Return true after putting a reference; false if the object still needs to be put. For DataStream this is trivial. ReferenceStream overrides this." ^ false! ! !DataStream methodsFor: 'write and read' stamp: 'tk 2/20/1999 23:02'! typeIDFor: anObject "Return the typeID for anObject's class. This is where the tangle of objects is clipped to stop everything from going out. Classes can control their instance variables by defining objectToStoreOnDataStream. Any object in blockers is not written out. See ReferenceStream.objectIfBlocked: and DataStream nextPut:. Morphs do not write their owners. See Morph.storeDataOn: Each morph tells itself to 'prepareToBeSaved' before writing out." ^ TypeMap at: anObject class ifAbsent: [9 "instance of any normal class"] "See DataStream initialize. nil=1. true=2. false=3. a SmallInteger=4. (a String was 5). a Symbol=6. a ByteArray=7. an Array=8. other = 9. a Bitmap=11. a Metaclass=12. a Float=14. a Rectangle=15. any instance that can have a short header=16. a String=17 (new format). a WordArray=18."! ! !DataStream methodsFor: 'write and read'! writeArray: anArray "PRIVATE -- Write the contents of an Array." byteStream nextNumber: 4 put: anArray size. self nextPutAll: anArray.! ! !DataStream methodsFor: 'write and read' stamp: 'tk 6/8/1998 21:07'! writeBitmap: aBitmap "PRIVATE -- Write the contents of a Bitmap." aBitmap writeOn: byteStream "Note that this calls (byteStream nextPutAll: aBitmap) which knows enough to put 4-byte quantities on the stream!! Reader must know that size is in long words."! ! !DataStream methodsFor: 'write and read'! writeBoolean: aBoolean "PRIVATE -- Write the contents of a Boolean. This method is now obsolete." byteStream nextPut: (aBoolean ifTrue: [1] ifFalse: [0])! ! !DataStream methodsFor: 'write and read' stamp: 'tk 6/8/1998 21:06'! writeByteArray: aByteArray "PRIVATE -- Write the contents of a ByteArray." byteStream nextNumber: 4 put: aByteArray size. "May have to convert types here..." byteStream nextPutAll: aByteArray.! ! !DataStream methodsFor: 'write and read' stamp: 'tk 3/24/98 10:27'! writeClass: aClass "Write out a DiskProxy for the class. It will look up the class's name in Smalltalk in the new sustem. Never write classes or methodDictionaries as objects. For novel classes, front part of file is a fileIn of the new class." "This method never executed because objectToStoreOnDataStream returns a DiskProxy. See DataStream.nextPut:" ^ self error: 'Write a DiskProxy instead'! ! !DataStream methodsFor: 'write and read'! writeFalse: aFalse "PRIVATE -- Write the contents of a False."! ! !DataStream methodsFor: 'write and read'! writeFloat: aFloat "PRIVATE -- Write the contents of a Float. We support 8-byte Floats here." byteStream nextNumber: 4 put: (aFloat at: 1). byteStream nextNumber: 4 put: (aFloat at: 2). ! ! !DataStream methodsFor: 'write and read' stamp: 'yo 12/3/2004 17:07'! writeFloatString: aFloat "PRIVATE -- Write the contents of a Float string. This is the slow way to write a Float--via its string rep'n." self writeByteArray: (aFloat printString)! ! !DataStream methodsFor: 'write and read'! writeInstance: anObject "PRIVATE -- Write the contents of an arbitrary instance." ^ anObject storeDataOn: self! ! !DataStream methodsFor: 'write and read'! writeInteger: anInteger "PRIVATE -- Write the contents of a SmallInteger." byteStream nextInt32Put: anInteger "signed!!!!!!!!!!"! ! !DataStream methodsFor: 'write and read'! writeNil: anUndefinedObject "PRIVATE -- Write the contents of an UndefinedObject."! ! !DataStream methodsFor: 'write and read' stamp: 'jm 7/31/97 16:16'! writeRectangle: anObject "Write the contents of a Rectangle. See if it can be a compact Rectangle (type=15). Rectangles with values outside +/- 2047 were stored as normal objects (type=9). 17:22 tk" | ok right bottom top left acc | ok := true. (right := anObject right) > 2047 ifTrue: [ok := false]. right < -2048 ifTrue: [ok := false]. (bottom := anObject bottom) > 2047 ifTrue: [ok := false]. bottom < -2048 ifTrue: [ok := false]. (top := anObject top) > 2047 ifTrue: [ok := false]. top < -2048 ifTrue: [ok := false]. (left := anObject left) > 2047 ifTrue: [ok := false]. left < -2048 ifTrue: [ok := false]. ok := ok & left isInteger & right isInteger & top isInteger & bottom isInteger. ok ifFalse: [ byteStream skip: -1; nextPut: 9; skip: 0. "rewrite type to be normal instance" ^ anObject storeDataOn: self]. acc := ((left bitAnd: 16rFFF) bitShift: 12) + (top bitAnd: 16rFFF). byteStream nextNumber: 3 put: acc. acc := ((right bitAnd: 16rFFF) bitShift: 12) + (bottom bitAnd: 16rFFF). byteStream nextNumber: 3 put: acc.! ! !DataStream methodsFor: 'write and read' stamp: 'tk 6/8/1998 20:57'! writeString: aString "PRIVATE -- Write the contents of a String." byteStream nextStringPut: aString.! ! !DataStream methodsFor: 'write and read' stamp: 'tk 6/8/1998 21:23'! writeStringOld: aString "PRIVATE -- Write the contents of a String." | length | aString size < 16384 ifTrue: [ (length := aString size) < 192 ifTrue: [byteStream nextPut: length] ifFalse: [byteStream nextPut: (length // 256 + 192). byteStream nextPut: (length \\ 256)]. aString do: [:char | byteStream nextPut: char asciiValue]] ifFalse: [self writeByteArray: aString]. "takes more space"! ! !DataStream methodsFor: 'write and read'! writeSymbol: aSymbol "PRIVATE -- Write the contents of a Symbol." self writeString: aSymbol! ! !DataStream methodsFor: 'write and read'! writeTrue: aTrue "PRIVATE -- Write the contents of a True."! ! !DataStream methodsFor: 'write and read'! writeUser: anObject "Write the contents of an arbitrary User instance (and its devoted class)." " 7/29/96 tk" "If anObject is an instance of a unique user class, will lie and say it has a generic class" ^ anObject storeDataOn: self! ! !DataStream methodsFor: 'write and read' stamp: 'tk 2/5/2000 21:53'! writeWordLike: aWordArray "Note that we put the class name before the size." self nextPut: aWordArray class name. aWordArray writeOn: byteStream "Note that this calls (byteStream nextPutAll: aBitmap) which knows enough to put 4-byte quantities on the stream!! Reader must know that size is in long words or double-bytes."! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DataStream class instanceVariableNames: ''! !DataStream class methodsFor: 'as yet unclassified'! example "An example and test of DataStream/ReferenceStream. 11/19/92 jhm: Use self testWith:." "DataStream example" "ReferenceStream example" | input sharedPoint | "Construct the test data." input := Array new: 9. input at: 1 put: nil. input at: 2 put: true. input at: 3 put: (Form extent: 63 @ 50 depth: 8). (input at: 3) fillWithColor: Color lightBlue. input at: 4 put: #(3 3.0 'three'). input at: 5 put: false. input at: 6 put: 1024 @ -2048. input at: 7 put: #x. input at: 8 put: (Array with: (sharedPoint := 0 @ -30000)). input at: 9 put: sharedPoint. "Write it out, read it back, and return it for inspection." ^ self testWith: input! ! !DataStream class methodsFor: 'as yet unclassified'! exampleWithPictures "DataStream exampleWithPictures" | file result | file := FileStream fileNamed: 'Test-Picture'. file binary. (DataStream on: file) nextPut: (Form fromUser). file close. file := FileStream fileNamed: 'Test-Picture'. file binary. result := (DataStream on: file) next. file close. result display. ^ result! ! !DataStream class methodsFor: 'as yet unclassified'! fileNamed: aString "Here is the way to use DataStream and ReferenceStream: rr := ReferenceStream fileNamed: 'test.obj'. rr nextPut: . rr close. " | strm | strm := self on: (FileStream fileNamed: aString). "will be binary" strm byteStream setFileTypeToObject. "Type and Creator not to be text, so can attach correctly to an email msg" ^ strm! ! !DataStream class methodsFor: 'as yet unclassified' stamp: 'adrian_lienhard 7/27/2009 20:11'! initialize "TypeMap maps Smalltalk classes to type ID numbers which identify the data stream primitive formats. nextPut: writes these IDs to the data stream. NOTE: Changing these type ID numbers will invalidate all extant data stream files. Adding new ones is OK. Classes named here have special formats in the file. If such a class has a subclass, it will use type 9 and write correctly. It will just be slow. (Later write the class name in the special format, then subclasses can use the type also.) See nextPut:, next, typeIDFor:, & ReferenceStream>>isAReferenceType:" "DataStream initialize" | refTypes t | refTypes := OrderedCollection new. t := TypeMap := Dictionary new: 80. "sparse for fast hashing" t at: UndefinedObject put: 1. refTypes add: 0. t at: True put: 2. refTypes add: 0. t at: False put: 3. refTypes add: 0. t at: SmallInteger put: 4. refTypes add: 0. t at: ByteString put: 5. refTypes add: 1. t at: ByteSymbol put: 6. refTypes add: 1. t at: ByteArray put: 7. refTypes add: 1. t at: Array put: 8. refTypes add: 1. "(type ID 9 is for arbitrary instances of any class, cf. typeIDFor:)" refTypes add: 1. "(type ID 10 is for references, cf. ReferenceStream>>tryToPutReference:)" refTypes add: 0. t at: Bitmap put: 11. refTypes add: 1. t at: Metaclass put: 12. refTypes add: 0. "Type ID 13 is used for HyperSqueak User classes that must be reconstructed." refTypes add: 1. t at: Float put: 14. refTypes add: 1. t at: Rectangle put: 15. refTypes add: 1. "Allow compact Rects." "type ID 16 is an instance with short header. See beginInstance:size:" refTypes add: 1. self flag: #ByteArray. t at: ByteString put: 17. refTypes add: 1. "new String format, 1 or 4 bytes of length" t at: WordArray put: 18. refTypes add: 1. "bitmap-like" t at: WordArrayForSegment put: 19. refTypes add: 1. "bitmap-like" Smalltalk at: #SoundBuffer ifPresent: [ :class | t at: class put: 20. refTypes add: 1. "And all other word arrays, both 16-bit and 32-bit. See methods in ArrayedCollection. Overridden in SoundBuffer." ]. t at: CompiledMethod put: 21. refTypes add: 1. "special creation method" "t at: put: 22. refTypes add: 0." ReferenceStream refTypes: refTypes. "save it" "For all classes that are like WordArrays, store them the way ColorArray is stored. As bits, and able to change endianness." Smalltalk do: [:cls | cls isInMemory ifTrue: [ cls isBehavior ifTrue: [ cls isPointers not & cls isVariable & cls isWords ifTrue: [ (t includesKey: cls) ifFalse: [t at: cls put: 20]]]]].! ! !DataStream class methodsFor: 'as yet unclassified' stamp: 'di 2/15/98 14:03'! new ^ self basicNew! ! !DataStream class methodsFor: 'as yet unclassified'! newFileNamed: aString "Here is the way to use DataStream and ReferenceStream: rr := ReferenceStream fileNamed: 'test.obj'. rr nextPut: . rr close. " | strm | strm := self on: (FileStream newFileNamed: aString). "will be binary" strm byteStream setFileTypeToObject. "Type and Creator not to be text, so can attach correctly to an email msg" ^ strm! ! !DataStream class methodsFor: 'as yet unclassified'! oldFileNamed: aString "Here is the way to use DataStream and ReferenceStream: rr := ReferenceStream oldFileNamed: 'test.obj'. ^ rr nextAndClose. " | strm ff | ff := FileStream oldFileOrNoneNamed: aString. ff ifNil: [^ nil]. strm := self on: (ff binary). ^ strm! ! !DataStream class methodsFor: 'as yet unclassified' stamp: 'di 6/24/97 00:18'! on: aStream "Open a new DataStream onto a low-level I/O stream." ^ self basicNew setStream: aStream "aStream binary is in setStream:" ! ! !DataStream class methodsFor: 'as yet unclassified' stamp: 'RAA 7/28/2000 08:38'! streamedRepresentationOf: anObject | file | file := (RWBinaryOrTextStream on: (ByteArray new: 5000)). file binary. (self on: file) nextPut: anObject. ^file contents! ! !DataStream class methodsFor: 'as yet unclassified' stamp: 'jm 12/3/97 19:36'! testWith: anObject "As a test of DataStream/ReferenceStream, write out anObject and read it back. 11/19/92 jhm: Set the file type. More informative file name." "DataStream testWith: 'hi'" "ReferenceStream testWith: 'hi'" | file result | file := FileStream fileNamed: (self name, ' test'). file binary. (self on: file) nextPut: anObject. file close. file := FileStream fileNamed: (self name, ' test'). file binary. result := (self on: file) next. file close. ^ result! ! !DataStream class methodsFor: 'as yet unclassified' stamp: 'RAA 7/28/2000 08:33'! unStream: aString ^(self on: ((RWBinaryOrTextStream with: aString) reset; binary)) next! ! Timespan subclass: #Date instanceVariableNames: '' classVariableNames: '' poolDictionaries: 'ChronologyConstants' category: 'Kernel-Chronology'! !Date commentStamp: '' prior: 0! Instances of Date are Timespans with duration of 1 day. Their default creation assumes a start of midnight in the local time zone.! !Date methodsFor: 'printing' stamp: 'sd 3/16/2008 14:43'! mmddyyyy "Answer the receiver rendered in standard U.S.A format mm/dd/yyyy. Note that the name here is slightly misleading -- the month and day numbers don't show leading zeros, so that for example February 1 1996 is 2/1/96" ^ self printFormat: #(2 1 3 $/ 1 1)! ! !Date methodsFor: 'printing' stamp: 'PeterHugossonMiller 9/3/2009 01:05'! printFormat: formatArray "Answer a String describing the receiver using the argument formatArray." | aStream | aStream := (String new: 16) writeStream. self printOn: aStream format: formatArray. ^ aStream contents! ! !Date methodsFor: 'printing' stamp: 'BP 3/23/2001 12:27'! printOn: aStream self printOn: aStream format: #(1 2 3 $ 3 1 )! ! !Date methodsFor: 'printing' stamp: 'brp 7/27/2003 16:05'! printOn: aStream format: formatArray "Print a description of the receiver on aStream using the format denoted the argument, formatArray: #(item item item sep monthfmt yearfmt twoDigits) items: 1=day 2=month 3=year will appear in the order given, separated by sep which is eaither an ascii code or character. monthFmt: 1=09 2=Sep 3=September yearFmt: 1=1996 2=96 digits: (missing or)1=9 2=09. See the examples in printOn: and mmddyy" | gregorian twoDigits element monthFormat | gregorian := self dayMonthYearDo: [ :d :m :y | {d. m. y} ]. twoDigits := formatArray size > 6 and: [(formatArray at: 7) > 1]. 1 to: 3 do: [ :i | element := formatArray at: i. element = 1 ifTrue: [twoDigits ifTrue: [aStream nextPutAll: (gregorian first asString padded: #left to: 2 with: $0)] ifFalse: [gregorian first printOn: aStream]]. element = 2 ifTrue: [monthFormat := formatArray at: 5. monthFormat = 1 ifTrue: [twoDigits ifTrue: [aStream nextPutAll: (gregorian middle asString padded: #left to: 2 with: $0)] ifFalse: [gregorian middle printOn: aStream]]. monthFormat = 2 ifTrue: [aStream nextPutAll: ((Month nameOfMonth: gregorian middle) copyFrom: 1 to: 3)]. monthFormat = 3 ifTrue: [aStream nextPutAll: (Month nameOfMonth: gregorian middle)]]. element = 3 ifTrue: [(formatArray at: 6) = 1 ifTrue: [gregorian last printOn: aStream] ifFalse: [aStream nextPutAll: ((gregorian last \\ 100) asString padded: #left to: 2 with: $0)]]. i < 3 ifTrue: [(formatArray at: 4) ~= 0 ifTrue: [aStream nextPut: (formatArray at: 4) asCharacter]]] ! ! !Date methodsFor: 'printing' stamp: 'BP 3/23/2001 12:27'! storeOn: aStream aStream print: self printString; nextPutAll: ' asDate'! ! !Date methodsFor: 'printing' stamp: 'brp 7/27/2003 16:04'! yyyymmdd "Format the date in ISO 8601 standard like '2002-10-22'." ^ self printFormat: #(3 2 1 $- 1 1 2)! ! !Date methodsFor: 'smalltalk-80' stamp: 'brp 8/23/2003 22:09'! addDays: dayCount ^ (self asDateAndTime + (dayCount days)) asDate! ! !Date methodsFor: 'smalltalk-80' stamp: 'brp 7/27/2003 16:08'! asSeconds "Answer the seconds since the Squeak epoch: 1 January 1901" ^ start asSeconds! ! !Date methodsFor: 'smalltalk-80' stamp: 'brp 7/27/2003 16:08'! leap "Answer whether the receiver's year is a leap year." ^ start isLeapYear ifTrue: [1] ifFalse: [0].! ! !Date methodsFor: 'smalltalk-80' stamp: 'brp 1/16/2004 14:30'! previous: dayName "Answer the previous date whose weekday name is dayName." | days | days := 7 + self weekdayIndex - (self class dayOfWeek: dayName) \\ 7. days = 0 ifTrue: [ days := 7 ]. ^ self subtractDays: days ! ! !Date methodsFor: 'smalltalk-80' stamp: 'brp 7/27/2003 16:09'! subtractDate: aDate "Answer the number of days between self and aDate" ^ (self start - aDate asDateAndTime) days! ! !Date methodsFor: 'smalltalk-80' stamp: 'brp 8/23/2003 22:05'! subtractDays: dayCount ^ (self asDateAndTime - (dayCount days)) asDate! ! !Date methodsFor: 'smalltalk-80' stamp: 'brp 8/24/2003 12:04'! weekday "Answer the name of the day of the week on which the receiver falls." ^ self dayOfWeekName! ! !Date methodsFor: 'smalltalk-80' stamp: 'brp 8/24/2003 12:04'! weekdayIndex "Sunday=1, ... , Saturday=7" ^ self dayOfWeek! ! !Date methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 14:43'! asDate ^ self! ! !Date methodsFor: 'squeak protocol' stamp: 'brp 7/27/2003 16:10'! dayMonthYearDo: aBlock "Supply integers for day, month and year to aBlock and return the result" ^ start dayMonthYearDo: aBlock! ! !Date methodsFor: 'squeak protocol' stamp: 'avi 2/21/2004 18:12'! month ^ self asMonth! ! !Date methodsFor: 'squeak protocol' stamp: 'avi 2/29/2004 13:10'! monthIndex ^ super month! ! !Date methodsFor: 'utils' stamp: 'tbn 7/11/2006 10:30'! addMonths: monthCount |year month maxDaysInMonth day | year := self year + (monthCount + self monthIndex - 1 // 12). month := self monthIndex + monthCount - 1 \\ 12 + 1. maxDaysInMonth := Month daysInMonth: month forYear: year. day := self dayOfMonth > maxDaysInMonth ifTrue: [maxDaysInMonth] ifFalse: [self dayOfMonth]. ^ Date newDay: day month: month year: year! ! !Date methodsFor: 'utils' stamp: 'spfa 3/8/2004 13:52'! onNextMonth ^ self addMonths: 1 ! ! !Date methodsFor: 'utils' stamp: 'spfa 3/8/2004 13:52'! onPreviousMonth ^ self addMonths: -1 ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Date class instanceVariableNames: ''! !Date class methodsFor: 'general inquiries' stamp: 'BG 3/16/2005 14:57'! easterDateFor: year " compute the easter date. source: Physikalisch-Technische Bundesanstalt Braunschweig. Lichtenberg, H.: Zur Interpretation der Gaussschen Osterformel und ihrer Ausnahmeregeln, Historia Mathematica 24 (1997), pp. 441-444 http://www.ptb.de/de/org/4/44/441/oste.htm " | k m s a d r og sz oe day | k := year // 100. m := 15 + (3*k + 3//4) - (8*k + 13//25). s := 2 - (3*k + 3// 4). a := year \\ 19. d := 19*a + m \\ 30. r := d//29 + ((d//28) - (d//29)* (a// 11)). og := 21 + d - r. sz := 7 - (year//4 + year + s\\7). oe := 7 - (og - sz\\7). day := og + oe. ^day <= 31 ifTrue: [Date newDay: day month: 3 year: year ] ifFalse: [Date newDay: day - 31 month: 4 year: year].! ! !Date class methodsFor: 'general inquiries' stamp: 'BG 3/16/2005 14:48'! orthodoxEasterDateFor: year " compute the easter date according to the rules of the orthodox calendar. source: http://www.smart.net/~mmontes/ortheast.html " | r1 r2 r3 r4 ra rb r5 rc date | r1 := year \\ 19. r2 := year \\ 4. r3 := year \\ 7. ra := 19*r1 + 16. r4 := ra \\ 30. rb := r2 + r2 + (4*r3) + (6*r4). r5 := rb \\ 7. rc := r4 + r5. date := Date newDay: 3 month: 4 year: year. ^date addDays: rc.! ! !Date class methodsFor: 'smalltalk-80' stamp: 'sd 3/16/2008 14:57'! dateAndTimeNow "Answer an Array whose with Date today and Time now." ^ Time dateAndTimeNow! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 13:35'! dayOfWeek: dayName ^ Week indexOfDay: dayName! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 13:59'! daysInMonth: monthName forYear: yearInteger ^ Month daysInMonth: monthName forYear: yearInteger. ! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 13:53'! daysInYear: yearInteger ^ Year daysInYear: yearInteger.! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 1/16/2004 14:35'! firstWeekdayOfMonth: month year: year "Answer the weekday index of the first day in in the ." ^ (self newDay: 1 month: month year: year) weekdayIndex ! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 7/27/2003 16:01'! fromDays: dayCount "Days since 1 January 1901" ^ self julianDayNumber: dayCount + SqueakEpoch! ! !Date class methodsFor: 'smalltalk-80' stamp: 'sd 3/16/2008 14:57'! fromSeconds: seconds "Answer an instance of me which is 'seconds' seconds after January 1, 1901." ^ self fromDays: ((Duration seconds: seconds) days)! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 13:39'! indexOfMonth: aMonthName ^ Month indexOfMonth: aMonthName. ! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 13:56'! leapYear: yearInteger ^ Year leapYear: yearInteger! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 13:37'! nameOfDay: dayIndex ^ Week nameOfDay: dayIndex ! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 13:40'! nameOfMonth: anIndex ^ Month nameOfMonth: anIndex. ! ! !Date class methodsFor: 'smalltalk-80' stamp: 'sd 3/16/2008 14:57'! newDay: day month: month year: year ^ self year: year month: month day: day! ! !Date class methodsFor: 'smalltalk-80' stamp: 'brp 7/27/2003 16:01'! newDay: dayCount year: yearInteger ^ self year: yearInteger day: dayCount! ! !Date class methodsFor: 'smalltalk-80' stamp: 'sd 3/16/2008 14:57'! today ^ self current! ! !Date class methodsFor: 'squeak protocol' stamp: 'md 7/15/2006 18:06'! fromString: aString "Answer an instance of created from a string with format mm.dd.yyyy." ^ self readFrom: aString readStream.! ! !Date class methodsFor: 'squeak protocol' stamp: 'brp 7/27/2003 18:25'! julianDayNumber: aJulianDayNumber ^ self starting: (DateAndTime julianDayNumber: aJulianDayNumber)! ! !Date class methodsFor: 'squeak protocol' stamp: 'PeterHugossonMiller 9/3/2009 01:06'! readFrom: aStream "Read a Date from the stream in any of the forms: (5 April 1982; 5-APR-82) (April 5, 1982) (4/5/82) (5APR82)" | day month year | aStream peek isDigit ifTrue: [day := Integer readFrom: aStream]. [aStream peek isAlphaNumeric] whileFalse: [aStream skip: 1]. aStream peek isLetter ifTrue: ["number/name... or name..." month := (String new: 10) writeStream. [aStream peek isLetter] whileTrue: [month nextPut: aStream next]. month := month contents. day isNil ifTrue: ["name/number..." [aStream peek isAlphaNumeric] whileFalse: [aStream skip: 1]. day := Integer readFrom: aStream]] ifFalse: ["number/number..." month := Month nameOfMonth: day. day := Integer readFrom: aStream]. [aStream peek isAlphaNumeric] whileFalse: [aStream skip: 1]. year := Integer readFrom: aStream. year < 10 ifTrue: [year := 2000 + year] ifFalse: [ year < 1900 ifTrue: [ year := 1900 + year]]. ^ self year: year month: month day: day! ! !Date class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 14:58'! starting: aDateAndTime ^ super starting: (aDateAndTime midnight) duration: (Duration days: 1) ! ! !Date class methodsFor: 'squeak protocol' stamp: 'brp 7/1/2003 18:09'! tomorrow ^ self today next! ! !Date class methodsFor: 'squeak protocol' stamp: 'brp 7/27/2003 22:03'! year: year day: dayOfYear ^ self starting: (DateAndTime year: year day: dayOfYear) ! ! !Date class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 14:58'! year: year month: month day: day ^ self starting: (DateAndTime year: year month: month day: day) ! ! !Date class methodsFor: 'squeak protocol' stamp: 'brp 7/1/2003 18:09'! yesterday ^ self today previous! ! Magnitude subclass: #DateAndTime instanceVariableNames: 'seconds offset jdn nanos' classVariableNames: 'LocalTimeZone' poolDictionaries: 'ChronologyConstants' category: 'Kernel-Chronology'! !DateAndTime commentStamp: 'sd 3/16/2008 14:58' prior: 0! I represent a point in UTC time as defined by ISO 8601. I have zero duration. My implementation uses three SmallIntegers and a Duration: jdn - julian day number. seconds - number of seconds since midnight. nanos - the number of nanoseconds since the second. offset - duration from UTC. The nanosecond attribute is almost always zero but it defined for full ISO compliance and is suitable for timestamping. ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'brp 7/9/2005 08:45'! + operand "operand conforms to protocol Duration" | ticks | ticks := self ticks + (operand asDuration ticks) . ^ self class basicNew ticks: ticks offset: self offset; yourself. ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'brp 1/9/2004 05:39'! - operand "operand conforms to protocol DateAndTime or protocol Duration" ^ (operand respondsTo: #asDateAndTime) ifTrue: [ | lticks rticks | lticks := self asLocal ticks. rticks := operand asDateAndTime asLocal ticks. Duration seconds: (SecondsInDay *(lticks first - rticks first)) + (lticks second - rticks second) nanoSeconds: (lticks third - rticks third) ] ifFalse: [ self + (operand negated) ]. ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'nk 3/30/2004 09:09'! < comparand "comparand conforms to protocol DateAndTime, or can be converted into something that conforms." | lticks rticks comparandAsDateAndTime | comparandAsDateAndTime := comparand asDateAndTime. offset = comparandAsDateAndTime offset ifTrue: [lticks := self ticks. rticks := comparandAsDateAndTime ticks] ifFalse: [lticks := self asUTC ticks. rticks := comparandAsDateAndTime asUTC ticks]. ^ lticks first < rticks first or: [lticks first > rticks first ifTrue: [false] ifFalse: [lticks second < rticks second or: [lticks second > rticks second ifTrue: [false] ifFalse: [lticks third < rticks third]]]] ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'brp 7/28/2004 16:14'! = comparand "comparand conforms to protocol DateAndTime, or can be converted into something that conforms." | comparandAsDateAndTime | self == comparand ifTrue: [^ true]. [comparandAsDateAndTime := comparand asDateAndTime] on: MessageNotUnderstood do: [^ false]. ^ self offset = comparandAsDateAndTime offset ifTrue: [self hasEqualTicks: comparandAsDateAndTime ] ifFalse: [self asUTC ticks = comparandAsDateAndTime asUTC ticks] ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:04'! asLocal ^ (self offset = self class localOffset) ifTrue: [self] ifFalse: [self utcOffset: self class localOffset] ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'brp 4/13/2006 10:21'! asUTC ^ offset isZero ifTrue: [self] ifFalse: [self utcOffset: 0] ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:04'! dayOfMonth "Answer which day of the month is represented by the receiver." ^ self dayMonthYearDo: [ :d :m :y | d ]! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:04'! dayOfWeek "Sunday=1, ... , Saturday=7" ^ (jdn + 1 rem: 7) + 1! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:04'! dayOfWeekAbbreviation ^ self dayOfWeekName copyFrom: 1 to: 3! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:04'! dayOfWeekName ^ Week nameOfDay: self dayOfWeek ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'adrian_lienhard 1/7/2009 18:23'! dayOfYear "This code was contributed by Dan Ingalls. It is equivalent to the terser ^ jdn - (Year year: self year) start julianDayNumber + 1 but much quicker." | monthStart | ^ self dayMonthYearDo: [ :d :m :y | monthStart := #(1 32 60 91 121 152 182 213 244 274 305 335) at: m. (m > 2 and: [ Year isLeapYear: y ]) ifTrue: [ monthStart + d ] ifFalse: [ monthStart + d - 1 ]]! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:04'! hash ^ self asUTC ticks hash ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:04'! hour ^ self hour24 ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:05'! hour12 "Answer an between 1 and 12, inclusive, representing the hour of the day in the 12-hour clock of the local time of the receiver." ^ self hour24 - 1 \\ 12 + 1! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:05'! hour24 ^ (Duration seconds: seconds) hours! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:05'! isLeapYear ^ Year isLeapYear: self year. ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:05'! meridianAbbreviation ^ self asTime meridianAbbreviation! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:05'! minute ^ (Duration seconds: seconds) minutes ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:05'! month ^ self dayMonthYearDo: [ :d :m :y | m ].! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:05'! monthAbbreviation ^ self monthName copyFrom: 1 to: 3 ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:05'! monthName ^ Month nameOfMonth: self month ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:06'! offset ^ offset ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:06'! offset: anOffset "Answer a equivalent to the receiver but with its local time being offset from UTC by offset." ^ self class basicNew ticks: self ticks offset: anOffset asDuration; yourself ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:06'! second ^ (Duration seconds: seconds) seconds ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:06'! timeZoneAbbreviation ^ self class localTimeZone abbreviation ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:06'! timeZoneName ^ self class localTimeZone name ! ! !DateAndTime methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:06'! year ^ self dayMonthYearDo: [:d :m :y | y ]! ! !DateAndTime methodsFor: 'converting' stamp: 'pc 2/20/2009 15:35'! asUnixTime ^ self asTimeStamp asSeconds - 2177452800! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 8/23/2003 21:03'! asSeconds "Return the number of seconds since the Squeak epoch" ^ (self - (self class epoch)) asSeconds ! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 17:53'! day ^ self dayOfYear! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 5/13/2003 07:48'! daysInMonth "Answer the number of days in the month represented by the receiver." ^ self asMonth daysInMonth! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 5/13/2003 07:48'! daysInYear "Answer the number of days in the year represented by the receiver." ^ self asYear daysInYear ! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 7/27/2003 15:44'! daysLeftInYear "Answer the number of days in the year after the date of the receiver." ^ self daysInYear - self dayOfYear ! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 7/27/2003 15:44'! firstDayOfMonth ^ self asMonth start day! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 18:30'! hours ^ self hour! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 1/7/2004 15:45'! minutes ^ self minute! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 5/13/2003 07:50'! monthIndex ^ self month ! ! !DateAndTime methodsFor: 'smalltalk-80' stamp: 'brp 7/1/2003 18:31'! seconds ^ self second! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:00'! asDate ^ Date starting: self! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:00'! asDateAndTime ^ self ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'gk 8/31/2006 00:55'! asDuration "Answer the duration since midnight." ^ Duration seconds: seconds nanoSeconds: nanos ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:01'! asMonth ^ Month starting: self ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:01'! asNanoSeconds "Answer the number of nanoseconds since midnight" ^ self asDuration asNanoSeconds ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:01'! asTime ^ Time seconds: seconds nanoSeconds: nanos! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'brp 8/24/2003 00:02'! asTimeStamp ^ self as: TimeStamp! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:01'! asWeek ^ Week starting: self ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:01'! asYear ^ Year starting: self! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:01'! dayMonthYearDo: aBlock "Evaluation the block with three arguments: day month, year." | l n i j dd mm yyyy | l := jdn + 68569. n := 4 * l // 146097. l := l - (146097 * n + 3 // 4). i := 4000 * (l + 1) // 1461001. l := l - (1461 * i // 4) + 31. j := 80 * l // 2447. dd := l - (2447 * j // 80). l := j // 11. mm := j + 2 - (12 * l). yyyy := 100 * (n - 49) + i + l. ^ aBlock value: dd value: mm value: yyyy.! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:01'! duration ^ Duration zero! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:02'! julianDayNumber ^ jdn! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:02'! middleOf: aDuration "Return a Timespan where the receiver is the middle of the Duration" | duration | duration := aDuration asDuration. ^ Timespan starting: (self - (duration / 2)) duration: duration. ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'HenrikSperreJohansen 10/15/2009 14:42'! midnight "Answer a DateAndTime starting at midnight local time" ^self class basicNew setJdn: jdn seconds: 0 nano: 0 offset: self class localOffset! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:02'! nanoSecond ^ nanos ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:02'! noon "Answer a DateAndTime starting at noon" ^ self dayMonthYearDo: [ :d :m :y | self class year: y month: m day: d hour: 12 minute: 0 second: 0 ]! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'nk 3/12/2004 10:03'! printHMSOn: aStream "Print just hh:mm:ss" aStream nextPutAll: (self hour asString padded: #left to: 2 with: $0); nextPut: $:; nextPutAll: (self minute asString padded: #left to: 2 with: $0); nextPut: $:; nextPutAll: (self second asString padded: #left to: 2 with: $0). ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'nk 3/12/2004 10:38'! printOn: aStream "Print as per ISO 8601 sections 5.3.3 and 5.4.1. Prints either: 'YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years)" ^self printOn: aStream withLeadingSpace: false ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'dtl 10/31/2004 01:20'! printOn: aStream withLeadingSpace: printLeadingSpaceToo "Print as per ISO 8601 sections 5.3.3 and 5.4.1. If printLeadingSpaceToo is false, prints either: 'YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years) If printLeadingSpaceToo is true, prints either: ' YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for positive years) or '-YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z' (for negative years) " self printYMDOn: aStream withLeadingSpace: printLeadingSpaceToo. aStream nextPut: $T. self printHMSOn: aStream. self nanoSecond ~= 0 ifTrue: [ | z ps | ps := self nanoSecond printString padded: #left to: 9 with: $0. z := ps findLast: [ :c | c asciiValue > $0 asciiValue ]. (z > 0) ifTrue: [aStream nextPut: $.]. ps from: 1 to: z do: [ :c | aStream nextPut: c ] ]. aStream nextPut: (offset positive ifTrue: [$+] ifFalse: [$-]); nextPutAll: (offset hours abs asString padded: #left to: 2 with: $0); nextPut: $:; nextPutAll: (offset minutes abs asString padded: #left to: 2 with: $0). offset seconds = 0 ifFalse: [ aStream nextPut: $:; nextPutAll: (offset seconds abs truncated asString) ]. ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'nk 3/12/2004 10:29'! printYMDOn: aStream "Print just YYYY-MM-DD part. If the year is negative, prints out '-YYYY-MM-DD'." ^self printYMDOn: aStream withLeadingSpace: false. ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'nk 3/12/2004 10:29'! printYMDOn: aStream withLeadingSpace: printLeadingSpaceToo "Print just the year, month, and day on aStream. If printLeadingSpaceToo is true, then print as: ' YYYY-MM-DD' (if the year is positive) or '-YYYY-MM-DD' (if the year is negative) otherwise print as: 'YYYY-MM-DD' or '-YYYY-MM-DD' " | year month day | self dayMonthYearDo: [ :d :m :y | year := y. month := m. day := d ]. year negative ifTrue: [ aStream nextPut: $- ] ifFalse: [ printLeadingSpaceToo ifTrue: [ aStream space ]]. aStream nextPutAll: (year abs asString padded: #left to: 4 with: $0); nextPut: $-; nextPutAll: (month asString padded: #left to: 2 with: $0); nextPut: $-; nextPutAll: (day asString padded: #left to: 2 with: $0) ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:03'! to: anEnd "Answer a Timespan. anEnd conforms to protocol DateAndTime or protocol Timespan" ^ Timespan starting: self ending: (anEnd asDateAndTime). ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:03'! to: anEnd by: aDuration "Answer a Timespan. anEnd conforms to protocol DateAndTime or protocol Timespan" ^ (Schedule starting: self ending: (anEnd asDateAndTime)) schedule: (Array with: aDuration asDuration); yourself. ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:03'! to: anEnd by: aDuration do: aBlock "Answer a Timespan. anEnd conforms to protocol DateAndTime or protocol Timespan" ^ (self to: anEnd by: aDuration) scheduleDo: aBlock ! ! !DateAndTime methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:03'! utcOffset: anOffset "Answer a equivalent to the receiver but offset from UTC by anOffset" | equiv | equiv := self + (anOffset asDuration - self offset). ^ equiv ticks: (equiv ticks) offset: anOffset asDuration; yourself ! ! !DateAndTime methodsFor: 'private' stamp: 'brp 7/28/2004 16:22'! hasEqualTicks: aDateAndTime ^ (jdn = aDateAndTime julianDayNumber) and: [ (seconds = aDateAndTime secondsSinceMidnight) and: [ nanos = aDateAndTime nanoSecond ] ] ! ! !DateAndTime methodsFor: 'private' stamp: 'gk 8/30/2006 22:59'! normalize: i ticks: ticks base: base | tick div quo rem | tick := ticks at: i. div := tick digitDiv: base neg: tick negative. quo := (div at: 1) normalize. rem := (div at: 2) normalize. rem < 0 ifTrue: [ quo := quo - 1. rem := base + rem ]. ticks at: (i-1) put: ((ticks at: i-1) + quo). ticks at: i put: rem ! ! !DateAndTime methodsFor: 'private' stamp: 'brp 7/28/2004 16:20'! secondsSinceMidnight ^ seconds! ! !DateAndTime methodsFor: 'private' stamp: 'HenrikSperreJohansen 10/15/2009 14:36'! setJdn: julDays seconds: secs nano: nanoSecs offset: anOffset jdn := julDays. seconds := secs. nanos := nanoSecs. offset := anOffset.! ! !DateAndTime methodsFor: 'private' stamp: 'sd 3/16/2008 15:03'! ticks "Private - answer an array with our instance variables. Assumed to be UTC " ^ Array with: jdn with: seconds with: nanos.! ! !DateAndTime methodsFor: 'private' stamp: 'adrian_lienhard 1/7/2009 18:23'! ticks: ticks offset: utcOffset "ticks is {julianDayNumber. secondCount. nanoSeconds}" self normalize: 3 ticks: ticks base: NanosInSecond. self normalize: 2 ticks: ticks base: SecondsInDay. jdn := ticks at: 1. seconds := ticks at: 2. nanos := ticks at: 3. offset := utcOffset! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DateAndTime class instanceVariableNames: ''! !DateAndTime class methodsFor: 'ansi protocol' stamp: 'gk 8/31/2006 00:49'! clockPrecision "One nanosecond precision" ^ Duration seconds: 0 nanoSeconds: 1 ! ! !DateAndTime class methodsFor: 'ansi protocol' stamp: 'gk 8/30/2006 23:01'! now ^ self basicNew ticks: (Array with: SqueakEpoch with: Time totalSeconds with: 0) offset: self localTimeZone offset ! ! !DateAndTime class methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 14:59'! year: year day: dayOfYear hour: hour minute: minute second: second ^ self year: year day: dayOfYear hour: hour minute: minute second: second offset: self localOffset. ! ! !DateAndTime class methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 14:59'! year: year day: dayOfYear hour: hour minute: minute second: second offset: offset "Return a DataAndTime" | y d | y := self year: year month: 1 day: 1 hour: hour minute: minute second: second nanoSecond: 0 offset: offset. d := Duration days: (dayOfYear - 1). ^ y + d! ! !DateAndTime class methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 14:59'! year: year month: month day: day hour: hour minute: minute second: second "Return a DateAndTime" ^ self year: year month: month day: day hour: hour minute: minute second: second offset: self localOffset ! ! !DateAndTime class methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:00'! year: year month: month day: day hour: hour minute: minute second: second offset: offset ^ self year: year month: month day: day hour: hour minute: minute second: second nanoSecond: 0 offset: offset ! ! !DateAndTime class methodsFor: 'creation' stamp: 'pc 2/20/2009 15:34'! fromUnixTime: anInteger ^ self fromSeconds: anInteger + 2177452800 "unix epoch constant"! ! !DateAndTime class methodsFor: 'smalltalk-80' stamp: 'dtl 6/21/2009 23:37'! fromSeconds: seconds "Answer a DateAndTime since the Squeak epoch: 1 January 1901" | integerSeconds nanos | integerSeconds := seconds truncated. integerSeconds = seconds ifTrue: [nanos := 0] ifFalse: [nanos := (seconds - integerSeconds * NanosInSecond) asInteger]. ^ self basicNew ticks: (Array with: SqueakEpoch with: integerSeconds with: nanos) offset: self localOffset! ! !DateAndTime class methodsFor: 'smalltalk-80' stamp: 'brp 8/24/2003 00:00'! millisecondClockValue ^ Time millisecondClockValue! ! !DateAndTime class methodsFor: 'smalltalk-80' stamp: 'brp 8/24/2003 00:01'! totalSeconds ^ Time totalSeconds! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:07'! current ^ self now ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:07'! date: aDate time: aTime ^ self year: aDate year day: aDate dayOfYear hour: aTime hour minute: aTime minute second: aTime second ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:07'! epoch "Answer a DateAndTime representing the Squeak epoch: 1 January 1901" ^ self julianDayNumber: SqueakEpoch ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'damiencassou 5/30/2008 10:56'! fromString: aString ^ self readFrom: aString readStream! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:07'! julianDayNumber: aJulianDayNumber ^ self basicNew ticks: aJulianDayNumber days ticks offset: self localOffset; yourself! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:07'! localOffset "Answer the duration we are offset from UTC" ^ self localTimeZone offset ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'brp 9/4/2003 06:39'! localTimeZone "Answer the local time zone" ^ LocalTimeZone ifNil: [ LocalTimeZone := TimeZone default ] ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'nk 3/30/2004 09:53'! localTimeZone: aTimeZone "Set the local time zone" " DateAndTime localTimeZone: (TimeZone offset: 0 hours name: 'Universal Time' abbreviation: 'UTC'). DateAndTime localTimeZone: (TimeZone offset: -8 hours name: 'Pacific Standard Time' abbreviation: 'PST'). " LocalTimeZone := aTimeZone ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:07'! midnight ^ self now midnight ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:07'! new "Answer a DateAndTime representing the Squeak epoch: 1 January 1901" ^ self epoch ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:08'! noon ^ self now noon! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'PeterHugossonMiller 9/3/2009 01:10'! readFrom: aStream | bc year month day hour minute second nanos offset buffer ch | aStream peek = $- ifTrue: [ aStream next. bc := -1] ifFalse: [bc := 1]. year := (aStream upTo: $-) asInteger * bc. month := (aStream upTo: $-) asInteger ifNil: [1]. day := (aStream upTo: $T) asInteger ifNil: [1]. hour := (aStream upTo: $:) asInteger ifNil: [0]. buffer := '00:' copy. ch := nil. minute := buffer writeStream. [ aStream atEnd | (ch = $:) | (ch = $+) | (ch = $-) ] whileFalse: [ ch := minute nextPut: aStream next. ]. (ch isNil or: [ch isDigit]) ifTrue: [ ch := $: ]. minute := (buffer readStream upTo: ch) asInteger. buffer := '00.' copy. second := buffer writeStream. [ aStream atEnd | (ch = $.) | (ch = $+) | (ch = $-) ] whileFalse: [ ch := second nextPut: aStream next. ]. (ch isNil or: [ch isDigit]) ifTrue: [ ch := $. ]. second := (buffer readStream upTo: ch) asInteger. buffer := '000000000' copy. (ch = $.) ifTrue: [ nanos := buffer writeStream. [ aStream atEnd | ((ch := aStream next) = $+) | (ch = $-) ] whileFalse: [ nanos nextPut: ch. ]. (ch isNil or: [ch isDigit]) ifTrue: [ ch := $+ ]. ]. nanos := buffer asInteger. aStream atEnd ifTrue: [ offset := self localOffset ] ifFalse: [offset := Duration fromString: (ch asString, '0:', aStream upToEnd). (offset = self localOffset) ifTrue: [ offset := self localOffset ]]. ^ self year: year month: month day: day hour: hour minute: minute second: second nanoSecond: nanos offset: offset. " '-1199-01-05T20:33:14.321-05:00' asDateAndTime ' 2002-05-16T17:20:45.1+01:01' asDateAndTime ' 2002-05-16T17:20:45.02+01:01' asDateAndTime ' 2002-05-16T17:20:45.003+01:01' asDateAndTime ' 2002-05-16T17:20:45.0004+01:01' asDateAndTime ' 2002-05-16T17:20:45.00005' asDateAndTime ' 2002-05-16T17:20:45.000006+01:01' asDateAndTime ' 2002-05-16T17:20:45.0000007+01:01' asDateAndTime ' 2002-05-16T17:20:45.00000008-01:01' asDateAndTime ' 2002-05-16T17:20:45.000000009+01:01' asDateAndTime ' 2002-05-16T17:20:45.0000000001+01:01' asDateAndTime ' 2002-05-16T17:20' asDateAndTime ' 2002-05-16T17:20:45' asDateAndTime ' 2002-05-16T17:20:45+01:57' asDateAndTime ' 2002-05-16T17:20:45-02:34' asDateAndTime ' 2002-05-16T17:20:45+00:00' asDateAndTime ' 1997-04-26T01:02:03+01:02:3' asDateAndTime " ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:08'! today ^ self midnight ! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:08'! tomorrow ^ self today asDate next asDateAndTime! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:08'! year: year day: dayOfYear "Return a DateAndTime" ^ self year: year day: dayOfYear hour: 0 minute: 0 second: 0! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'HenrikSperreJohansen 10/15/2009 14:44'! year: year month: month day: day "Return a DateAndTime, midnight local time" ^ self year: year month: month day: day hour: 0 minute: 0! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'HenrikSperreJohansen 10/15/2009 14:44'! year: year month: month day: day hour: hour minute: minute "Return a DateAndTime" ^ self year: year month: month day: day hour: hour minute: minute second: 0! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'HenrikSperreJohansen 10/15/2009 14:42'! year: year month: month day: day hour: hour minute: minute second: second nanoSecond: nanoCount offset: offset "Return a DateAndTime" | monthIndex daysInMonth p q r s julianDayNumber | monthIndex := month isInteger ifTrue: [month] ifFalse: [Month indexOfMonth: month]. daysInMonth := Month daysInMonth: monthIndex forYear: year. day < 1 ifTrue: [self error: 'day may not be zero or negative']. day > daysInMonth ifTrue: [self error: 'day is after month ends']. p := (monthIndex - 14) quo: 12. q := year + 4800 + p. r := monthIndex - 2 - (12 * p). s := (year + 4900 + p) quo: 100. julianDayNumber := ((1461 * q) quo: 4) + ((367 * r) quo: 12) - ((3 * s) quo: 4) + (day - 32075). ^self basicNew setJdn: julianDayNumber seconds: hour * 60 + minute * 60 + second nano: nanoCount offset: offset; yourself! ! !DateAndTime class methodsFor: 'squeak protocol' stamp: 'sd 3/16/2008 15:09'! yesterday ^ self today asDate previous asDateAndTime ! ! TestCase subclass: #DateAndTimeEpochTest instanceVariableNames: 'aDateAndTime aDuration aTimeZone localTimeZoneToRestore' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Chronology'! !DateAndTimeEpochTest commentStamp: 'tlk 1/6/2004 18:27' prior: 0! I represent one of several Sunit test Cases intentended to provide complete coverage for the Chronology set of classes as part of the external testing. The other Chronology sunit test cases are: DateTestCase DateAndTimeLeapTestCase, DurationTestCase, ScheduleTestCase TimeStampTestCase TimespanDoTestCase, TimespanDoSpanAYearTestCase, TimespanTestCase, YearMonthWeekTestCase. These tests attempt to exercise all public and private methods. Except, they do not explicitly depreciated methods. tlk My fixtures are: aDateAndTime = January 01, 1901 midnight (the start of the Squeak epoch) with localTimeZone = Grenwhich Meridian (local offset = 0 hours) aDuration = 1 day, 2 hours, 3, minutes, 4 seconds and 5 nano seconds. aTimeZone = 'Epoch Test Time Zone', 'ETZ' , offset: 12 hours, 15 minutes. ! !DateAndTimeEpochTest methodsFor: 'running' stamp: 'tlk 1/2/2004 10:58'! setUp localTimeZoneToRestore := DateAndTime localTimeZone. aDateAndTime := DateAndTime localTimeZone: TimeZone default; epoch. aTimeZone := TimeZone offset: (Duration minutes: 135) name: 'Epoch Test Time Zone' abbreviation: 'ETZ'. aDuration := Duration days: 1 hours: 2 minutes: 3 seconds: 4 nanoSeconds: 5 ! ! !DateAndTimeEpochTest methodsFor: 'running' stamp: 'tlk 1/2/2004 11:04'! tearDown DateAndTime localTimeZone: localTimeZoneToRestore. "wish I could remove the time zones I added earlier, tut there is no method for that" ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:01'! testAsDate self assert: aDateAndTime asDate = 'January 1, 1901' asDate. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 13:31'! testAsDateAndTime self assert: aDateAndTime asDateAndTime = aDateAndTime ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 13:34'! testAsDuration self assert: aDateAndTime asDuration = 0 asDuration ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 11:06'! testAsLocal self assert: aDateAndTime asLocal = aDateAndTime. self assert: aDateAndTime asLocal = (aDateAndTime utcOffset: aDateAndTime class localOffset) ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 09:27'! testAsMonth self assert: aDateAndTime asMonth = (Month month: 'January' year: 1901). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 13:59'! testAsNanoSeconds self assert: aDateAndTime asNanoSeconds = 0 asDuration asNanoSeconds ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 14:01'! testAsSeconds self assert: aDateAndTime asSeconds = 0 asDuration asSeconds ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 09:32'! testAsTime self assert: aDateAndTime asTime = Time midnight. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 14:51'! testAsTimeStamp self assert: aDateAndTime asTimeStamp = TimeStamp new. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 11:07'! testAsUTC self assert: aDateAndTime asUTC = aDateAndTime ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'brp 1/16/2004 13:43'! testAsWeek self assert: aDateAndTime asWeek = (Week starting: '12-31-1900' asDate). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 09:43'! testAsYear self assert: aDateAndTime asYear = (Year starting: '01-01-1901' asDate). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:28'! testCurrent self deny: aDateAndTime = (DateAndTime current). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 09:46'! testDateTime self assert: aDateAndTime = (DateAndTime date: '01-01-1901' asDate time: '00:00:00' asTime) ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:01'! testDay self assert: aDateAndTime day = DateAndTime new day ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 11:08'! testDayMonthYearDo |iterations| iterations := 0. self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear | iterations := iterations + 1]) = 1. self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear | eachYear]) = 1901. self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear | eachMonth]) = 1. self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear | eachDay]) = 1. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 15:45'! testDayOfMonth self assert: aDateAndTime dayOfMonth = 1. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 10:47'! testDayOfWeek self assert: aDateAndTime dayOfWeek = 3. self assert: aDateAndTime dayOfWeekAbbreviation = 'Tue'. self assert: aDateAndTime dayOfWeekName = 'Tuesday'. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:01'! testDayOfYear self assert: aDateAndTime dayOfYear = 1. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:02'! testDaysInMonth self assert: aDateAndTime daysInMonth = 31. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:02'! testDaysInYear self assert: aDateAndTime daysInYear = 365. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:02'! testDaysLeftInYear self assert: aDateAndTime daysLeftInYear = 364. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 16:24'! testDuration self assert: aDateAndTime duration = 0 asDuration. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:25'! testEpoch self assert: aDateAndTime = '1901-01-01T00:00:00+00:00'. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 10:44'! testFirstDayOfMonth self assert: aDateAndTime firstDayOfMonth = 1 ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:25'! testFromSeconds self assert: aDateAndTime = (DateAndTime fromSeconds: 0). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:26'! testFromString self assert: aDateAndTime = (DateAndTime fromString: ' 1901-01-01T00:00:00+00:00'). self assert: aDateAndTime = (DateAndTime fromString: ' 1901-01-01T00:00:00'). self assert: aDateAndTime = (DateAndTime fromString: ' 1901-01-01T00:00'). self assert: aDateAndTime = (DateAndTime fromString: ' 1901-01-01T00:00:00+00:00'). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'al 6/12/2008 21:56'! testHash self assert: aDateAndTime hash = DateAndTime new hash! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 16:59'! testHour self assert: aDateAndTime hour = aDateAndTime hour24. self assert: aDateAndTime hour = 0. self assert: aDateAndTime hour = aDateAndTime hours ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'brp 3/12/2004 15:21'! testHour12 self assert: aDateAndTime hour12 = DateAndTime new hour12. self assert: aDateAndTime hour12 = 12 ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:02'! testIsLeapYear self deny: aDateAndTime isLeapYear ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 17:18'! testJulianDayNumber self assert: aDateAndTime = (DateAndTime julianDayNumber: 2415386). self assert: aDateAndTime julianDayNumber = 2415386.! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 13:20'! testLessThan self assert: aDateAndTime < (aDateAndTime + '1:00:00:00'). self assert: aDateAndTime + -1 < aDateAndTime. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 10:40'! testMeridianAbbreviation self assert: aDateAndTime meridianAbbreviation = 'AM'. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 12:37'! testMiddleOf self assert: (aDateAndTime middleOf: '2:00:00:00' asDuration) = (Timespan starting: '12-31-1900' asDate duration: 2 days). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 17:39'! testMidnight self assert: aDateAndTime midnight = aDateAndTime ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:03'! testMinus self assert: aDateAndTime - aDateAndTime = '0:00:00:00' asDuration. self assert: aDateAndTime - '0:00:00:00' asDuration = aDateAndTime. self assert: aDateAndTime - aDuration = (DateAndTime year: 1900 month: 12 day: 30 hour: 21 minute: 56 second: 55 nanoSecond: 999999995 offset: 0 hours ). " I believe this Failure is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)" ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 19:35'! testMinute self assert: aDateAndTime minute = 0 ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'brp 1/16/2004 13:41'! testMinutes self assert: aDateAndTime minutes = 0 ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 19:46'! testMonth self assert: aDateAndTime month = 1. self assert: aDateAndTime monthAbbreviation = 'Jan'. self assert: aDateAndTime monthName = 'January'. self assert: aDateAndTime monthIndex = 1.! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 19:47'! testNanoSecond self assert: aDateAndTime nanoSecond = 0 ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:27'! testNew self assert: aDateAndTime = (DateAndTime new). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 19:49'! testNoon self assert: aDateAndTime noon = '1901-01-01T12:00:00+00:00'. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:28'! testNow self deny: aDateAndTime = (DateAndTime now). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:41'! testOffset self assert: aDateAndTime offset = '0:00:00:00' asDuration. self assert: (aDateAndTime offset: '0:12:00:00') = '1901-01-01T00:00:00+12:00'. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 11:03'! testPlus self assert: aDateAndTime + '0:00:00:00' = aDateAndTime. self assert: aDateAndTime + 0 = aDateAndTime. self assert: aDateAndTime + aDuration = (DateAndTime year: 1901 month: 1 day: 2 hour: 2 minute: 3 second: 4 nanoSecond: 5 offset: 0 hours ) " I believe this is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)" ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'damiencassou 5/30/2008 11:09'! testPrintOn | cs rw | cs := '1901-01-01T00:00:00+00:00' readStream. rw := ReadWriteStream on: ''. aDateAndTime printOn: rw. self assert: rw contents = cs contents. cs := 'a TimeZone(ETZ)' readStream. rw := ReadWriteStream on: ''. aTimeZone printOn: rw. self assert: rw contents = cs contents! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 20:22'! testSecond self assert: aDateAndTime second = 0 ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 20:22'! testSeconds self assert: aDateAndTime seconds = 0 ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 20:25'! testTicks self assert: aDateAndTime ticks = (DateAndTime julianDayNumber: 2415386) ticks. self assert: aDateAndTime ticks = #(2415386 0 0)! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 20:31'! testTicksOffset self assert: aDateAndTime = (aDateAndTime ticks: #(2415386 0 0) offset: DateAndTime localOffset). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:42'! testTo self assert: (aDateAndTime to: aDateAndTime) = (DateAndTime new to: DateAndTime new) "MessageNotUnderstood: UndefinedObject>>starting:ending: where UndefinedObject is Timespan "! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:43'! testToBy self assert: (aDateAndTime to: aDateAndTime + 10 days by: 5 days) = (DateAndTime new to: DateAndTime new + 10 days by: 5 days ) "MessageNotUnderstood: UndefinedObject>>starting:ending: where UndefinedObject is Timespan "! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 20:53'! testToByDo "self assert: (aDateAndTime to: aDateAndTime + 10 days by: 5 days do: []) = " "MessageNotUnderstood: UndefinedObject>>starting:ending: where UndefinedObject is Timespan "! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 17:35'! testToday self deny: aDateAndTime = (DateAndTime today). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:45'! testTommorrow self assert: (DateAndTime today + 24 hours) = (DateAndTime tomorrow). self deny: aDateAndTime = (DateAndTime tomorrow). "MessageNotUnderstood: Date class>>starting:"! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 20:58'! testUtcOffset self assert: (aDateAndTime utcOffset: '0:12:00:00') = '1901-01-01T12:00:00+12:00'. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 21:00'! testYear self assert: aDateAndTime year = 1901. ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:30'! testYearDay self assert: aDateAndTime = (DateAndTime year: 1901 day: 1). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:31'! testYearDayHourMinuteSecond self assert: aDateAndTime = (DateAndTime year: 1901 day: 1 hour: 0 minute: 0 second: 0). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:31'! testYearMonthDay self assert: aDateAndTime = (DateAndTime year: 1901 month: 1 day: 1). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/1/2004 12:31'! testYearMonthDayHourMinuteSecond self assert: aDateAndTime = (DateAndTime year: 1901 month: 1 day: 1 hour: 0 minute: 0 second: 0). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 12:23'! testYearMonthDayHourMinuteSecondNanosSecondOffset self assert: aDateAndTime = (DateAndTime year: 1901 month: 1 day: 1 hour: 0 minute: 0 second: 0 nanoSecond: 0 offset:0 hours ). self assert: ((DateAndTime year: 1 month: 1 day: 1 hour: 0 minute: 0 second: 0 nanoSecond: 0 offset: 0 hours ) + (Duration days: 1 hours: 2 minutes: 3 seconds: 4 nanoSeconds: 5) ) = (DateAndTime year: 1 month: 1 day: 2 hour: 2 minute: 3 second: 4 nanoSecond: 5 offset: 0 hours ) " I believe this is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)"" I believe this is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)" ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 09:47'! testYesterday self deny: aDateAndTime = (DateAndTime yesterday). ! ! !DateAndTimeEpochTest methodsFor: 'testing' stamp: 'nk 3/12/2004 11:26'! testtimeZone self assert: aDateAndTime timeZoneName = 'Universal Time'. self assert: aDateAndTime timeZoneAbbreviation = 'UTC' ! ! TestCase subclass: #DateAndTimeLeapTest instanceVariableNames: 'aDateAndTime aDuration aTimeZone localTimeZoneToRestore' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Chronology'! !DateAndTimeLeapTest commentStamp: 'tlk 1/6/2004 17:54' prior: 0! I represent one of several Sunit test Cases intentended to provide complete coverage for the Chronology set of classes as part of the external testing. tlk. My fixtures are: aDateAndTime = February 29, 2004 1:33 PM with offset: 2 hours aDuration = 15 days, 14 hours, 13 minutes, 12 seconds and 11 nano seconds. aTimeZone = Grenwhich Meridian (local offset = 0 hours) ! !DateAndTimeLeapTest methodsFor: 'running' stamp: 'nk 3/12/2004 11:00'! setUp localTimeZoneToRestore := DateAndTime localTimeZone. DateAndTime localTimeZone: TimeZone default. aDateAndTime := (DateAndTime year: 2004 month: 2 day: 29 hour: 13 minute: 33 second: 0 offset: 2 hours). aTimeZone := TimeZone default. aDuration := Duration days: 0 hours: 13 minutes: 33 seconds: 0 nanoSeconds: 0 ! ! !DateAndTimeLeapTest methodsFor: 'running' stamp: 'tlk 1/2/2004 21:30'! tearDown DateAndTime localTimeZone: localTimeZoneToRestore. "wish I could remove the time zones I added earlier, tut there is no method for that" ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:00'! testAsDate self assert: aDateAndTime asDate = 'February 29, 2004' asDate. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 21:55'! testAsDuration self assert: aDateAndTime asDuration = aDuration ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 14:00'! testAsLocal self assert: aDateAndTime asLocal = aDateAndTime. self assert: aDateAndTime asLocal = (aDateAndTime utcOffset: aDateAndTime class localOffset) ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 12:24'! testAsMonth self assert: aDateAndTime asMonth = (Month month: 'February' year: 2004). ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 21:59'! testAsNanoSeconds self assert: aDateAndTime asNanoSeconds = aDuration asNanoSeconds. self assert: aDateAndTime asNanoSeconds = 48780000000000 ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 22:05'! testAsSeconds self assert: aDuration asSeconds = 48780. self assert: aDateAndTime asSeconds = 3255507180 ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 12:26'! testAsTime self assert: aDateAndTime asTime = (Time hour: 13 minute: 33 second: 0) ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:31'! testAsTimeStamp self assert: aDateAndTime asTimeStamp = ((TimeStamp readFrom: '2-29-2004 1:33 pm' readStream) offset: 2 hours). ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:59'! testAsUTC self assert: aDateAndTime asUTC = aDateAndTime ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 12:30'! testAsWeek self assert: aDateAndTime asWeek = (Week starting: '02-29-2004' asDate). ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 12:36'! testAsYear self assert: aDateAndTime asYear = (Year starting: '02-29-2004' asDate). self deny: aDateAndTime asYear = (Year starting: '01-01-2004' asDate) ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:23'! testDay self assert: aDateAndTime day = 60. self deny: aDateAndTime day = 29 ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 22:16'! testDayMonthYearDo self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear | eachYear]) = 2004. self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear | eachMonth]) = 2. self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear | eachDay]) = 29. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 22:17'! testDayOfMonth self assert: aDateAndTime dayOfMonth = 29. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:34'! testDayOfWeek self assert: aDateAndTime dayOfWeek = 1. self assert: aDateAndTime dayOfWeekAbbreviation = 'Sun'. self assert: aDateAndTime dayOfWeekName = 'Sunday'. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:59'! testDayOfYear self assert: aDateAndTime dayOfYear = 60. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:58'! testDaysInMonth self assert: aDateAndTime daysInMonth = 29. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:58'! testDaysInYear self assert: aDateAndTime daysInYear = 366. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:58'! testDaysLeftInYear self assert: aDateAndTime daysLeftInYear = 306. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:38'! testFirstDayOfMonth self deny: aDateAndTime firstDayOfMonth = 1. self assert: aDateAndTime firstDayOfMonth = 32 ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 10:43'! testFromString self assert: aDateAndTime = (DateAndTime fromString: ' 2004-02-29T13:33:00+02:00'). ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 10:48'! testHour self assert: aDateAndTime hour = aDateAndTime hour24. self assert: aDateAndTime hour = 13. self assert: aDateAndTime hour = aDateAndTime hours ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'brp 3/12/2004 15:19'! testHour12 self assert: aDateAndTime hour12 = 1. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:35'! testIsLeapYear self assert: aDateAndTime isLeapYear ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 21:30'! testLessThan self assert: aDateAndTime < (aDateAndTime + '1:00:00:00'). self assert: aDateAndTime + -1 < aDateAndTime. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 10:42'! testMeridianAbbreviation self assert: aDateAndTime meridianAbbreviation = 'PM'. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:12'! testMiddleOf self assert: (aDateAndTime middleOf: aDuration) = (Timespan starting: (DateAndTime year: 2004 month: 2 day: 29 hour: 6 minute: 46 second: 30 offset: 2 hours) duration: (Duration days: 0 hours: 13 minutes: 33 seconds: 0 nanoSeconds: 0 )) ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:57'! testMidnight self assert: aDateAndTime midnight = '2004-02-29T00:00:00+00:00'. self deny: aDateAndTime midnight = '2004-02-29T00:00:00+02:00' ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:00'! testMinute self assert: aDateAndTime minute = 33 ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'brp 1/16/2004 13:44'! testMinutes self assert: aDateAndTime minutes = 33 ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:02'! testMonth self assert: aDateAndTime month = 2. self assert: aDateAndTime monthAbbreviation = 'Feb'. self assert: aDateAndTime monthName = 'February'. self assert: aDateAndTime monthIndex = 2.! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 21:30'! testNanoSecond self assert: aDateAndTime nanoSecond = 0 ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:03'! testNoon self assert: aDateAndTime noon = '2004-02-29T12:00:00+00:00'. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:07'! testOffset self assert: aDateAndTime offset = '0:02:00:00' asDuration. self assert: (aDateAndTime offset: '0:12:00:00') = '2004-02-29T13:33:00+12:00'. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'damiencassou 5/30/2008 11:09'! testPrintOn | cs rw | cs := '2004-02-29T13:33:00+02:00' readStream. rw := ReadWriteStream on: ''. aDateAndTime printOn: rw. self assert: rw contents = cs contents. cs := 'a TimeZone(UTC)' readStream. rw := ReadWriteStream on: ''. aTimeZone printOn: rw. self assert: rw contents = cs contents! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 21:30'! testSecond self assert: aDateAndTime second = 0 ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/2/2004 21:30'! testSeconds self assert: aDateAndTime seconds = 0 ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:12'! testTicks self assert: aDateAndTime ticks = ((DateAndTime julianDayNumber: 2453065) + 48780 seconds) ticks. self assert: aDateAndTime ticks = #(2453065 48780 0)! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:52'! testTicksOffset self assert: aDateAndTime = (aDateAndTime ticks: #(2453065 48780 0) offset: DateAndTime localOffset). ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/4/2004 13:51'! testUtcOffset self assert: (aDateAndTime utcOffset: '0:02:00:00') = '2004-02-29T13:33:00+02:00'. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:17'! testYear self assert: aDateAndTime year = 2004. ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:21'! testYearDayHourMinuteSecond self assert: aDateAndTime = ((DateAndTime year: 2004 day: 60 hour: 13 minute: 33 second: 0) offset: 2 hours). ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'tlk 1/3/2004 11:23'! testYearMonthDayHourMinuteSecond self assert: aDateAndTime = ((DateAndTime year: 2004 month: 2 day: 29 hour: 13 minute: 33 second: 0) offset: 2 hours). ! ! !DateAndTimeLeapTest methodsFor: 'testing' stamp: 'nk 3/12/2004 11:26'! testtimeZone self assert: aDateAndTime timeZoneName = 'Universal Time'. self assert: aDateAndTime timeZoneAbbreviation = 'UTC' ! ! ClassTestCase subclass: #DateAndTimeTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Chronology'! !DateAndTimeTest methodsFor: 'Coverage' stamp: 'brp 9/25/2003 09:25'! classToBeTested ^ DateAndTime ! ! !DateAndTimeTest methodsFor: 'Coverage' stamp: 'brp 9/25/2003 09:25'! selectorsToBeIgnored | private | private := #( #printOn: ). ^ super selectorsToBeIgnored, private ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'brp 1/7/2004 17:00'! testArithmeticAcrossDateBoundary | t1 t2 | t1 := '2004-01-07T11:55:00+00:00' asDateAndTime. t2 := t1 - ( (42900+1) seconds). self assert: t2 = ('2004-01-06T23:59:59+00:00' asDateAndTime) ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'dtl 11/7/2004 13:00'! testDateTimeDenotation1 "DateAndTimeTest new testDateTimeDenotation1" " Detroit is 5 hours behind UTC, this offset to UTC is therefore written with a minus sign. This example tests the correct interpretation of the DateAndTime denotation. " | twoPmInLondon twoPmUTCInLocalTimeOfDetroit nineAmInDetroit | twoPmInLondon := DateAndTime year: 2004 month: 11 day: 2 hour: 14 minute: 0 second: 0 offset: 0 hours. twoPmUTCInLocalTimeOfDetroit := twoPmInLondon utcOffset: -5 hours. nineAmInDetroit := '2004-11-02T09:00:00-05:00' asDateAndTime. self assert: twoPmUTCInLocalTimeOfDetroit = nineAmInDetroit. ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'dtl 11/7/2004 13:01'! testDateTimeDenotation2 "DateAndTimeTest new testDateTimeDenotation2" " Moscow is 3 hours ahead UTC, this offset to UTC is therefore positive. This example tests the correct interpretation of the DateAndTime denotation. " | lateEveningInLondon lateEveningInLocalTimeOfMoscow localMoscowTimeFromDenotation | lateEveningInLondon := DateAndTime year: 2004 month: 11 day: 30 hour: 23 minute: 30 second: 0 offset: 0 hours. lateEveningInLocalTimeOfMoscow := lateEveningInLondon utcOffset: 3 hours. localMoscowTimeFromDenotation := '2004-12-01T02:30:00+03:00' asDateAndTime. self assert: lateEveningInLocalTimeOfMoscow = localMoscowTimeFromDenotation. ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'bvs 9/29/2004 16:22'! testErrorWhenDayIsAfterMonthEnd self should: [DateAndTime year: 2004 month: 2 day: 30] raise: Error. self shouldnt: [DateAndTime year: 2004 month: 2 day: 29] raise: Error. ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'bvs 9/29/2004 16:29'! testErrorWhenDayIsBeforeMonthStart self should: [DateAndTime year: 2004 month: 2 day: -1] raise: Error. self should: [DateAndTime year: 2004 month: 2 day: 0] raise: Error. self shouldnt: [DateAndTime year: 2004 month: 2 day: 1] raise: Error. ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'brp 1/7/2004 15:37'! testInstanceCreation | t | t := DateAndTime year: 1 month: 1 day: 2 hour: 2 minute: 3 second: 4 nanoSecond: 5 offset: 6 hours. self assert: (t julianDayNumber = 1721427); assert: (t offset = 6 hours); assert: (t hour = 2); assert: (t minute = 3); assert: (t second = 4); assert: (t nanoSecond = 5). ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'nk 3/12/2004 11:06'! testMonotonicity | t1 t2 t3 t4 | t1 := DateAndTime now. t2 := DateAndTime now. (Delay forMilliseconds: 1000) wait. t3 := DateAndTime now. t4 := DateAndTime now. self assert: ( t1 <= t2); assert: ( t2 < t3); assert: ( t3 <= t4). ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'dtl 11/5/2004 05:45'! testPrintString "(self new setTestSelector: #testPrintString) debug" | dt | dt :=DateAndTime year: 2004 month: 11 day: 2 hour: 14 minute: 3 second: 5 nanoSecond: 12345 offset: (Duration seconds: (5 * 3600)). self assert: dt printString = '2004-11-02T14:03:05.000012345+05:00' ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'stephane.ducasse 5/21/2009 14:25'! testReadFromFoolProofExtension "Convenient extension without a time, only a date" "self debug: #testReadFromFoolProofExtension" self assert: ('2008' asDateAndTime printString = '2008-01-01T00:00:00+00:00'). self assert: ('2008-08' asDateAndTime printString = '2008-08-01T00:00:00+00:00'). self assert: ('2006-08-28' asDateAndTime printString = '2006-08-28T00:00:00+00:00'). "Regular nanoseconds" self assert: ('2006-08-28T00:00:00.123456789' asDateAndTime printString = '2006-08-28T00:00:00.123456789+00:00'). "Extra picoseconds precision should not spoil the DateAndTime" self assert: ('2006-08-28T00:00:00.123456789000' asDateAndTime printString = '2006-08-28T00:00:00.123456789+00:00').! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'brp 1/7/2004 15:43'! testSmalltalk80Accessors | t | t := DateAndTime year: 1 month: 1 day: 2 hour: 2 minute: 3 second: 4 nanoSecond: 5 offset: 6 hours. self assert: (t hours = t hours); assert: (t minutes = t minute); assert: (t seconds = t second). ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'BG 11/7/2004 12:18'! testTimeZoneEquivalence "DateAndTimeTest new testTimeZoneEquivalence" "When the clock on the wall in Detroit says 9:00am, the clock on the wall in London says 2:00pm. The Duration difference between the corresponding DateAndTime values should be zero." " Detroit is 5 hours behind UTC, this offset to UTC is therefore written with a minus sign. This example tests both the correct interpretation of the DateAndTime denotation and correct DateAndTime arithmetics. " | twoPmInLondon nineAmInDetroit durationDifference | twoPmInLondon := '2004-11-02T14:00:00+00:00' asDateAndTime. nineAmInDetroit := '2004-11-02T09:00:00-05:00' asDateAndTime. durationDifference := twoPmInLondon - nineAmInDetroit. self assert: durationDifference asSeconds = 0. self assert: twoPmInLondon = nineAmInDetroit ! ! !DateAndTimeTest methodsFor: 'Tests' stamp: 'BG 11/7/2004 12:17'! testTimeZoneEquivalence2 "DateAndTimeTest new testTimeZoneEquivalence2" "This example demonstates the fact that 2004-05-24T22:40:00 UTC is 2004-05-25T01:40:00 in Moscow (Moscow is 3 hours ahead of UTC) " | thisMoment thisMomentInMoscow | thisMoment := DateAndTime year: 2004 month: 5 day: 24 hour: 22 minute: 40. thisMomentInMoscow := thisMoment utcOffset: 3 hours. self assert: (thisMoment - thisMomentInMoscow) asSeconds = 0. self assert: thisMoment = thisMomentInMoscow ! ! ClassTestCase subclass: #DateTest instanceVariableNames: 'date aDate aTime' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Chronology'! !DateTest commentStamp: 'brp 7/26/2003 16:58' prior: 0! This is the unit test for the class Date. ! !DateTest methodsFor: 'Coverage' stamp: 'brp 7/27/2003 13:01'! classToBeTested ^ self dateClass! ! !DateTest methodsFor: 'Coverage' stamp: 'brp 1/30/2005 09:03'! selectorsToBeIgnored | deprecated private special | deprecated := #(). private := #(). special := #( #< #= #new #next #previous #printOn: #printOn:format: #storeOn: #fromString: ). ^ super selectorsToBeIgnored, deprecated, private, special! ! !DateTest methodsFor: 'Running' stamp: 'brp 1/21/2004 18:46'! setUp date := self dateClass newDay: 153 year: 1973. "2 June 1973" aDate := Date readFrom: '01-23-2004' readStream. aTime := Time readFrom: '12:34:56 pm' readStream! ! !DateTest methodsFor: 'Tests' stamp: 'brp 8/23/2003 16:07'! testAccessing self assert: date day = 153; assert: date julianDayNumber = 2441836; assert: date leap = 0; assert: date monthIndex = 6; assert: date monthName = #June; assert: date weekday = #Saturday; assert: date weekdayIndex = 7; assert: date year = 1973. ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:10'! testArithmetic | d | d := date addDays: 32. "4 July 1973" self assert: d year = 1973; assert: d monthIndex = 7; assert: d dayOfMonth = 4. self assert: (d subtractDate: date) = 32; assert: (date subtractDate: d) = -32. self assert: (d subtractDays: 32) = date. ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:54'! testComparing | d1 d2 d3 | d1 := self dateClass newDay: 2 month: #June year: 1973. d2 := self dateClass newDay: 97 year: 2003. "7 April 2003" d3 := self dateClass newDay: 250 year: 1865. "7 September 1865" self assert: date = d1; assert: date = date copy; assert: date hash = d1 hash. self assert: date < d2; deny: date < d3. ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:15'! testConverting self assert: date asDate = date; assert: '2 June 1973' asDate = date; assert: date asSeconds = 2285280000. date dayMonthYearDo: [ :d :m :y | self assert: d = 2; assert: m = 6; assert: y = 1973 ].! ! !DateTest methodsFor: 'Tests' stamp: 'brp 1/21/2004 18:47'! testFromDays | epoch d0 d1 d2 | epoch := self dateClass newDay: 1 year: 1901. d0 := self dateClass fromDays: 0. "1 January 1901" self assert: d0 = epoch. d1 := self dateClass fromDays: 26450. "2 June 1973" self assert: d1 = date. d2 := self dateClass fromDays: -100000. "18 March 1627" self assert: d2 julianDayNumber = 2315386. self assert: aDate = (Date fromDays: 37642). self assert: aDate = (Date fromDays: 103*365 + 22 + 25 "leap days") . ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:17'! testFromSeconds | d | d := self dateClass fromSeconds: 2285280000. self assert: d = date. ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 1/7/2004 16:37'! testGeneralInquiries | shuffled indices names now | shuffled := #(#January #February #March #April #May #June #July #August #September #October #November #December) shuffled. indices := shuffled collect: [ :m | self dateClass indexOfMonth: m ]. names := indices collect: [ :i | self dateClass nameOfMonth: i ]. self assert: names = shuffled. shuffled := #(#Monday #Tuesday #Wednesday #Thursday #Friday #Saturday #Sunday) shuffled. indices := shuffled collect: [ :m | self dateClass dayOfWeek: m ]. names := indices collect: [ :i | self dateClass nameOfDay: i ]. self assert: names = shuffled. now := self dateClass dateAndTimeNow. self assert: now size = 2; assert: now first = self dateClass today. self assert: (self dateClass firstWeekdayOfMonth: #June year: 1973) = 6. self assert: (self dateClass leapYear: 1973) = 0; assert: (self dateClass leapYear: 1972) = 1; assert: (self dateClass daysInYear: 1973) = 365; assert: (self dateClass daysInYear: 1972) = 366; assert: (self dateClass daysInMonth: #February forYear: 1973) = 28; assert: (self dateClass daysInMonth: #February forYear: 1972) = 29. ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:17'! testInitialization self should: [ self dateClass initialize. true ]. ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:18'! testInquiries self assert: date dayOfMonth = 2; assert: date dayOfYear = 153; assert: date daysInMonth = 30; assert: date daysInYear = 365; assert: date daysLeftInYear = (365 - 153); assert: date firstDayOfMonth = 152. ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:05'! testNew | epoch | epoch := self dateClass newDay: 1 year: 1901. self assert: (self dateClass new = epoch).! ! !DateTest methodsFor: 'Tests' stamp: 'brp 1/9/2004 16:33'! testPreviousNext | n p pt ps | n := date next. p := date previous. self assert: n year = 1973; assert: n dayOfYear = 154; assert: p year = 1973; assert: p dayOfYear = 152. pt := date previous: #Thursday. "31 May 1973" self assert: pt year = 1973; assert: pt dayOfYear = 151. ps := date previous: #Saturday. " 26 May 1973" self assert: ps year = 1973; assert: ps dayOfYear = (153-7). ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:21'! testPrinting self assert: date mmddyyyy = '6/2/1973'; assert: date yyyymmdd = '1973-06-02'; assert: (date printFormat: #(3 1 2 $!! 2 1 1)) = '1973!!2!!Jun'. ! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:23'! testReadFrom | s1 s2 s3 s4 s5 | s1 := '2 June 1973'. s2 := '2-JUN-73'. s3 := 'June 2, 1973'. s4 := '6/2/73'. s5 := '2JUN73'. self assert: date = (self dateClass readFrom: s1 readStream); assert: date = (self dateClass readFrom: s2 readStream); assert: date = (self dateClass readFrom: s3 readStream); assert: date = (self dateClass readFrom: s4 readStream); assert: date = (self dateClass readFrom: s5 readStream).! ! !DateTest methodsFor: 'Tests' stamp: 'brp 7/27/2003 13:05'! testStoring self assert: date storeString = '''2 June 1973'' asDate'; assert: date = ('2 June 1973' asDate). ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testAddDays self assert: (aDate addDays: 00) yyyymmdd = '2004-01-23'. self assert: (aDate addDays: 30) yyyymmdd = '2004-02-22'. self assert: (aDate addDays: 60) yyyymmdd = '2004-03-23'. self assert: (aDate addDays: 90) yyyymmdd = '2004-04-22'. self assert: (aDate addDays:120) yyyymmdd = '2004-05-22'! ! !DateTest methodsFor: 'testing' stamp: 'tbn 7/11/2006 10:37'! testAddMonths self assert: (aDate addMonths: 0) yyyymmdd = '2004-01-23'. self assert: (aDate addMonths: 1) yyyymmdd = '2004-02-23'. self assert: (aDate addMonths: 2) yyyymmdd = '2004-03-23'. self assert: (aDate addMonths: 3) yyyymmdd = '2004-04-23'. self assert: (aDate addMonths: 12) yyyymmdd = '2005-01-23'. self assert: ((Date readFrom: '05-31-2017' readStream) addMonths: 1) yyyymmdd = '2017-06-30'. self assert: ((Date readFrom: '02-29-2000' readStream) addMonths: 12) yyyymmdd = '2001-02-28'! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testAsDate self assert: (aDate asDate) = aDate ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testAsSeconds self assert: (aDate asSeconds) = 3252268800. self assert: (aDate asSeconds) = ((103*365*24*60*60) + (22+25"leap days"*24*60*60)) . self assert: aDate = (Date fromSeconds: 3252268800).! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testDateAndTimeNow "Not a great test: could falsely fail if midnight come in between the two executions and doesnt catch time errors" self assert: Date dateAndTimeNow first = Date today ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testDayMonthYearDo self assert: (aDate dayMonthYearDo: [:day :month :year | day asString , month asString, year asString]) = '2312004' ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testDaysInMonthForYear self assert: (Date daysInMonth: 'February' forYear: 2008) = 29. self assert: (Date daysInMonth: 'February' forYear: 2000) = 29. self assert: (Date daysInMonth: 'February' forYear: 2100) = 28. self assert: (Date daysInMonth: 'July' forYear: 2100) = 31. ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testDaysInYear self assert: (Date daysInYear: 2008) = 366. self assert: (Date daysInYear: 2000) = 366. self assert: (Date daysInYear: 2100) = 365 ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testDuration self assert: aDate duration = 24 hours! ! !DateTest methodsFor: 'testing' stamp: 'damiencassou 5/30/2008 11:09'! testEqual self assert: aDate = (Date readFrom: 'January 23, 2004' readStream)! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testFirstWeekdayOfMonthYear self assert: (Date firstWeekdayOfMonth: 'January' year: 2004) = 5. ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testIndexOfMonth self assert: (Date indexOfMonth: 'January') = 1. self assert: (Date indexOfMonth: 'December') = 12. ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testJulianDayNumber self assert: aDate = (Date julianDayNumber: ((4713+2004)*365 +1323) ). ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testLeap self assert: aDate leap = 1. ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testLeapNot self assert: (aDate addDays: 365) leap = 0 ! ! !DateTest methodsFor: 'testing' stamp: 'damiencassou 5/30/2008 11:09'! testLessThan self assert: aDate < (Date readFrom: '01-24-2004' readStream)! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testMmddyyyy self assert: aDate mmddyyyy = '1/23/2004'! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testNameOfMonth self assert: (Date nameOfMonth: 5) = 'May'. self assert: (Date nameOfMonth: 8) = 'August' ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testNewDayMonthYear self assert: aDate = (Date newDay: 23 month: 1 year: 2004) ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testNewDayYear self assert: aDate = (Date newDay: 23 year: 2004) ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testPreviousFriday self assert: (aDate previous: 'Friday') yyyymmdd = '2004-01-16' ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testPreviousThursday self assert: (aDate previous: 'Thursday') yyyymmdd = '2004-01-22' ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testPrintFormat self assert: (aDate printFormat: #(1 2 3 $? 2 2)) = '23?Jan?04'! ! !DateTest methodsFor: 'testing' stamp: 'damiencassou 5/30/2008 11:09'! testPrintOn | cs rw | cs := '23 January 2004' readStream. rw := ReadWriteStream on: ''. aDate printOn: rw. self assert: rw contents = cs contents! ! !DateTest methodsFor: 'testing' stamp: 'damiencassou 5/30/2008 11:09'! testPrintOnFormat | cs rw | cs := '04*Jan*23' readStream. rw := ReadWriteStream on: ''. aDate printOn: rw format: #(3 2 1 $* 2 2 ). self assert: rw contents = cs contents! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testStarting self assert: aDate = (Date starting: (DateAndTime fromString: '2004-01-23T12:12')). ! ! !DateTest methodsFor: 'testing' stamp: 'damiencassou 5/30/2008 11:09'! testStoreOn | cs rw | cs := '''23 January 2004'' asDate' readStream. rw := ReadWriteStream on: ''. aDate storeOn: rw. self assert: rw contents = cs contents! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testSubtractDate self assert: (aDate subtractDate:(aDate addDays: 30)) = -30. self assert: (aDate subtractDate:(aDate subtractDays: 00)) = 0. self assert: (aDate subtractDate:(aDate subtractDays: 30)) = 30. ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testSubtractDays self assert: (aDate subtractDays: 00) yyyymmdd = '2004-01-23'. self assert: (aDate subtractDays: 30) yyyymmdd = '2003-12-24'. self assert: (aDate subtractDays: 60) yyyymmdd = '2003-11-24' ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testTomorrow "Not a great test: could falsely fail if midnight come in between the two executions and doesnt catch many errors" self assert: Date tomorrow > Date today ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testWeekday self assert: aDate weekday = 'Friday'. self assert: aDate weekdayIndex = 6. self assert: (Date dayOfWeek: aDate weekday ) =6. self assert: (Date nameOfDay: 6 ) = 'Friday' ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testYesterday "Not a great test: doesnt catch many errors" self assert: Date yesterday < Date today ! ! !DateTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:48'! testYyyymmdd self assert: aDate yyyymmdd = '2004-01-23'! ! !DateTest methodsFor: 'Private' stamp: 'brp 8/24/2003 00:10'! dateClass ^ Date! ! CodeHolder subclass: #Debugger instanceVariableNames: 'interruptedProcess interruptedController contextStack contextStackTop contextStackIndex contextStackList receiverInspector contextVariablesInspector externalInterrupt proceedValue selectingPC debuggerMap savedCursor isolationHead failedProject errorWasInUIProcess labelString' classVariableNames: 'ContextStackKeystrokes ErrorRecursion' poolDictionaries: '' category: 'Tools-Debugger'! !Debugger commentStamp: '' prior: 0! I represent the machine state at the time of an interrupted process. I also represent a query path into the state of the process. The debugger is typically viewed through a window that views the stack of suspended contexts, the code for, and execution point in, the currently selected message, and inspectors on both the receiver of the currently selected message, and the variables in the current context. Special note on recursive errors: Some errors affect Squeak's ability to present a debugger. This is normally an unrecoverable situation. However, if such an error occurs in an isolation layer, Squeak will attempt to exit from the isolation layer and then present a debugger. Here is the chain of events in such a recovery. * A recursive error is detected. * The current project is queried for an isolationHead * Changes in the isolationHead are revoked * The parent project of isolated project is returned to * The debugger is opened there and execution resumes. If the user closes that debugger, execution continues in the outer project and layer. If, after repairing some damage, the user proceeds from the debugger, then the isolationHead is re-invoked, the failed project is re-entered, and execution resumes in that world. ! !Debugger methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 1/27/2009 12:59'! addOptionalButtonsTo: window at: fractions plus: verticalOffset "Add button panes to the window. A row of custom debugger-specific buttons (Proceed, Restart, etc.) is always added, and if optionalButtons is in force, then the standard code-tool buttons are also added. Answer the verticalOffset plus the height added." | delta buttons anOffset | anOffset := (Preferences optionalButtons and: [Preferences extraDebuggerButtons]) ifTrue: [super addOptionalButtonsTo: window at: fractions plus: verticalOffset] ifFalse: [verticalOffset]. buttons := self customButtonRow. delta := self defaultButtonPaneHeight max: (buttons minExtent y + 1). buttons color: Color white; borderWidth: 0. window addMorph: buttons fullFrame: (LayoutFrame fractions: fractions offsets: (0 @ anOffset corner: 0 @ (anOffset + delta - 1))). ^ anOffset + delta! ! !Debugger methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 12/5/2008 15:11'! buildMorphicNotifierLabelled: label message: messageString | notifyPane window extentToUse row| self expandStack. window := (PreDebugWindow labelled: label) model: self. extentToUse := 450 @ 156. "nice and wide to show plenty of the error msg" window addMorph: (row := self buttonRowForPreDebugWindow: window) fullFrame: (LayoutFrame fractions: (0@0 corner: 1@0) offsets: (0@0 corner: 0@row minExtent y)). row color: Color transparent. Preferences eToyFriendly | messageString notNil ifFalse: [notifyPane := PluggableListMorph on: self list: #contextStackList selected: #contextStackIndex changeSelected: #debugAt: menu: nil keystroke: nil] ifTrue: [notifyPane := PluggableTextMorph on: self text: nil accept: nil readSelection: nil menu: #debugProceedMenu:. notifyPane editString: (self preDebugNotifierContentsFrom: messageString); askBeforeDiscardingEdits: false]. window addMorph: notifyPane fullFrame: (LayoutFrame fractions: (0@0 corner: 1@1) offsets: (0@24 corner: 0@0)). window setBalloonTextForCloseBox. window openInWorldExtent: extentToUse. window currentWorld displayWorld. "helps with interrupt not working somehow." ^window! ! !Debugger methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 1/27/2009 13:06'! buttonRowForPreDebugWindow: aDebugWindow "Answer a row of button for a pre-debug notifier." | buttons quads | buttons := OrderedCollection with: (AlignmentMorph newVariableTransparentSpacer). quads := OrderedCollection withAll: self preDebugButtonQuads. (self interruptedContext selector == #doesNotUnderstand:) ifTrue: [ quads add: { 'Create'. #createMethod. #magenta. 'create the missing method' }]. quads do: [:quad | buttons add: ((PluggableButtonMorph on: aDebugWindow getState: nil action: quad second) label: quad first; setBalloonText: quad fourth; useSquareCorners; hResizing: #shrinkWrap; vResizing: #spaceFill). buttons add: AlignmentMorph newVariableTransparentSpacer]. ^(UITheme builder newRow: buttons) cellInset: 2! ! !Debugger methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 1/27/2009 12:58'! customButtonRow "Answer a button pane affording the user one-touch access to certain functions; the pane is given the formal name 'customButtonPane' by which it can be retrieved by code wishing to send messages to widgets residing on the pane" | buttons aLabel | buttons := OrderedCollection new. self customButtonSpecs do: [:tuple | aLabel := Preferences abbreviatedBrowserButtons ifTrue: [self abbreviatedWordingFor: tuple second]. buttons add: ((PluggableButtonMorph on: self getState: nil action: tuple second) hResizing: #spaceFill; vResizing: #spaceFill; askBeforeChanging: (#(proceed restart send doStep stepIntoBlock fullStack where) includes: tuple second); label: (aLabel ifNil: [tuple first asString]); setBalloonText: (tuple size > 2 ifTrue: [tuple third]))]. ^(UITheme builder newRow: buttons) layoutInset: (0@0 corner: 0@1); cellInset: 2! ! !Debugger methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 1/27/2009 12:55'! optionalButtonRow "Answer a button pane affording the user one-touch access to certain functions; the pane is given the formal name 'buttonPane' by which it can be retrieved by code wishing to send messages to widgets residing on the pane" | buttons aLabel | buttons := OrderedCollection new. self optionalButtonPairs do: [:tuple | aLabel := Preferences abbreviatedBrowserButtons ifTrue: [self abbreviatedWordingFor: tuple second]. buttons add: ((PluggableButtonMorph on: self getState: nil action: tuple second) hResizing: #spaceFill; vResizing: #spaceFill; askBeforeChanging: (#(proceed restart send doStep stepIntoBlock fullStack where) includes: tuple second); label: (aLabel ifNil: [tuple first asString]); setBalloonText: (tuple size > 2 ifTrue: [tuple third]))]. ^(UITheme builder newRow: buttons) cellInset: 2! ! !Debugger methodsFor: 'accessing' stamp: 'di 10/9/1998 17:15'! contents "Depending on the current selection, different information is retrieved. Answer a string description of that information. This information is the method in the currently selected context." contents == nil ifTrue: [^ String new]. ^ contents copy! ! !Debugger methodsFor: 'accessing' stamp: 'hfm 9/30/2009 03:57'! contents: aText notifying: aController "The retrieved information has changed and its source must now be updated. In this case, the retrieved information is the method of the selected context." | result selector classOfMethod category h ctxt newMethod | contextStackIndex = 0 ifTrue: [^false]. self selectedContext isExecutingBlock ifTrue: [h := self selectedContext activeHome. h ifNil: [self inform: 'Method for block not found on stack, can''t edit and continue'. ^false]. (self confirm: 'I will have to revert to the method from\which this block originated. Is that OK?' withCRs) ifFalse: [^false]. self resetContext: h. result := self contents: aText notifying: aController. self contentsChanged. ^result]. classOfMethod := self selectedClass. category := self selectedMessageCategoryName. selector := self selectedClass parserClass new parseSelector: aText. (selector == self selectedMessageName or: [(self selectedMessageName beginsWith: 'DoIt') and: [selector numArgs = self selectedMessageName numArgs]]) ifFalse: [self inform: 'can''t change selector'. ^false]. selector := classOfMethod compile: aText classified: category notifying: aController. selector ifNil: [^false]. "compile cancelled" contents := aText. newMethod := classOfMethod compiledMethodAt: selector. newMethod isQuick ifTrue: [self down. self selectedContext jump: (self selectedContext previousPc - self selectedContext pc)]. ctxt := interruptedProcess popTo: self selectedContext. ctxt == self selectedContext ifFalse: [self inform: 'Method saved, but current context unchanged\because of unwind error. Click OK to see error' withCRs] ifTrue: [newMethod isQuick ifFalse: [interruptedProcess restartTopWith: newMethod; stepToSendOrReturn]. contextVariablesInspector object: nil]. self resetContext: ctxt. World addAlarm: #changed: withArguments: #(contentsSelection) for: self at: (Time millisecondClockValue + 200). ^true! ! !Debugger methodsFor: 'accessing'! contextVariablesInspector "Answer the instance of Inspector that is providing a view of the variables of the selected context." ^contextVariablesInspector! ! !Debugger methodsFor: 'accessing'! interruptedContext "Answer the suspended context of the interrupted process." ^contextStackTop! ! !Debugger methodsFor: 'accessing'! interruptedProcess "Answer the interrupted process." ^interruptedProcess! ! !Debugger methodsFor: 'accessing' stamp: 'tk 4/16/1998 15:47'! isNotifier "Return true if this debugger has not been expanded into a full sized window" ^ receiverInspector == nil! ! !Debugger methodsFor: 'accessing' stamp: 'hmm 7/16/2001 21:54'! labelString ^labelString! ! !Debugger methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'! labelString: aString labelString := aString. self changed: #relabel! ! !Debugger methodsFor: 'accessing'! proceedValue "Answer the value to return to the selected context when the interrupted process proceeds." ^proceedValue! ! !Debugger methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'! proceedValue: anObject "Set the value to be returned to the selected context when the interrupted process proceeds." proceedValue := anObject! ! !Debugger methodsFor: 'accessing'! receiver "Answer the receiver of the selected context, if any. Answer nil otherwise." contextStackIndex = 0 ifTrue: [^nil] ifFalse: [^self selectedContext receiver]! ! !Debugger methodsFor: 'accessing'! receiverInspector "Answer the instance of Inspector that is providing a view of the variables of the selected context's receiver." ^receiverInspector! ! !Debugger methodsFor: 'accessing' stamp: 'md 2/20/2006 18:52'! receiverInspectorObject: obj context: ctxt "set context before object so it can refer to context when building field list" receiverInspector context: ctxt. receiverInspector object: obj. ! ! !Debugger methodsFor: 'as yet unclassified' stamp: 'hfm 12/21/2008 22:57'! runToSelection | currentContext selectionInterval | selectionInterval := self codeTextMorph selectionInterval. self pc first >= selectionInterval first ifTrue: [ ^self ]. currentContext := self selectedContext. [ currentContext == self selectedContext and: [ self pc first < selectionInterval first ] ] whileTrue: [ self doStep ].! ! !Debugger methodsFor: 'breakpoints' stamp: 'marcus.denker 10/9/2008 20:32'! toggleBreakOnEntry "Install or uninstall a halt-on-entry breakpoint" | selectedMethod | self selectedClassOrMetaClass isNil ifTrue:[^self]. selectedMethod := self selectedClassOrMetaClass >> self selectedMessageName. selectedMethod hasBreakpoint ifTrue: [BreakpointManager unInstall: selectedMethod] ifFalse: [BreakpointManager installInClass: self selectedClassOrMetaClass selector: self selectedMessageName].! ! !Debugger methodsFor: 'class list' stamp: 'md 2/17/2006 09:32'! selectedClass "Answer the class in which the currently selected context's method was found." ^self selectedContext methodClass! ! !Debugger methodsFor: 'code pane' stamp: 'tk 4/15/1998 18:31'! contentsSelection ^ self pcRange! ! !Debugger methodsFor: 'code pane'! doItContext "Answer the context in which a text selection can be evaluated." contextStackIndex = 0 ifTrue: [^super doItContext] ifFalse: [^self selectedContext]! ! !Debugger methodsFor: 'code pane'! doItReceiver "Answer the object that should be informed of the result of evaluating a text selection." ^self receiver! ! !Debugger methodsFor: 'code pane' stamp: 'tk 5/2/1998 10:04'! pc ^ self pcRange! ! !Debugger methodsFor: 'code pane' stamp: 'eem 3/12/2009 14:54'! pcRange "Answer the indices in the source code for the method corresponding to the selected context's program counter value." (selectingPC and: [contextStackIndex ~= 0]) ifFalse: [^1 to: 0]. self selectedContext isDead ifTrue: [^1 to: 0]. ^self selectedContext debuggerMap rangeForPC: self selectedContext pc contextIsActiveContext: contextStackIndex = 1! ! !Debugger methodsFor: 'code pane menu' stamp: 'nk 8/6/2003 13:52'! codePaneMenu: aMenu shifted: shifted aMenu add: 'run to here' target: self selector: #runToSelection: argument: thisContext sender receiver selectionInterval. aMenu addLine. super codePaneMenu: aMenu shifted: shifted. ^aMenu.! ! !Debugger methodsFor: 'code pane menu' stamp: 'sd 11/20/2005 21:27'! perform: selector orSendTo: otherTarget "Selector was just chosen from a menu by a user. If can respond, then perform it on myself. If not, send it to otherTarget, presumably the editPane from which the menu was invoked." | result | (#(debug proceed) includes: selector) "When I am a notifier window" ifTrue: [^ self perform: selector] ifFalse: [result := super perform: selector orSendTo: otherTarget. selector == #doIt ifTrue: [ result ~~ #failedDoit ifTrue: [self proceedValue: result]]. ^ result]! ! !Debugger methodsFor: 'code pane menu' stamp: 'sd 11/20/2005 21:27'! runToSelection: selectionInterval | currentContext | self pc first >= selectionInterval first ifTrue: [ ^self ]. currentContext := self selectedContext. [ currentContext == self selectedContext and: [ self pc first < selectionInterval first ] ] whileTrue: [ self doStep ].! ! !Debugger methodsFor: 'context stack (message list)'! contextStackIndex "Answer the index of the selected context." ^contextStackIndex! ! !Debugger methodsFor: 'context stack (message list)'! contextStackList "Answer the array of contexts." ^contextStackList! ! !Debugger methodsFor: 'context stack (message list)' stamp: 'sd 11/20/2005 21:27'! expandStack "A Notifier is being turned into a full debugger. Show a substantial amount of stack in the context pane." self newStack: (contextStackTop stackOfSize: 20). contextStackIndex := 0. receiverInspector := Inspector inspect: nil. contextVariablesInspector := ContextVariablesInspector inspect: nil. proceedValue := nil! ! !Debugger methodsFor: 'context stack (message list)' stamp: 'ajh 9/25/2001 00:14'! fullyExpandStack "Expand the stack to include all of it, rather than the first four or five contexts." self okToChange ifFalse: [^ self]. self newStack: contextStackTop contextStack. self changed: #contextStackList! ! !Debugger methodsFor: 'context stack (message list)'! messageListIndex "Answer the index of the currently selected context." ^contextStackIndex! ! !Debugger methodsFor: 'context stack (message list)' stamp: 'eem 3/12/2009 14:54'! selectedMessage "Answer the source code of the currently selected context." ^contents := self selectedContext debuggerMap sourceText asText makeSelectorBold! ! !Debugger methodsFor: 'context stack (message list)' stamp: 'eem 9/5/2008 13:57'! selectedMessageName "Answer the message selector of the currently selected context. If the method is unbound we can still usefully answer its old selector." | selector | selector := self selectedContext methodSelector. ^(selector ~~ self selectedContext method selector and: [selector beginsWith: 'DoIt']) ifTrue: [self selectedContext method selector] ifFalse: [selector]! ! !Debugger methodsFor: 'context stack (message list)'! toggleContextStackIndex: anInteger "If anInteger is the same as the index of the selected context, deselect it. Otherwise, the context whose index is anInteger becomes the selected context." self contextStackIndex: (contextStackIndex = anInteger ifTrue: [0] ifFalse: [anInteger]) oldContextWas: (contextStackIndex = 0 ifTrue: [nil] ifFalse: [contextStack at: contextStackIndex])! ! !Debugger methodsFor: 'context stack menu' stamp: 'DamienCassou 9/23/2009 08:33'! askForCategoryIn: aClass default: aString | categories index category | categories := OrderedCollection with: 'new ...'. categories addAll: (aClass allMethodCategoriesIntegratedThrough: Object). index := UIManager default chooseFrom: categories title: 'Please provide a good category for the new method!!' translated. index = 0 ifTrue: [^ aString]. category := index = 1 ifTrue: [UIManager default request: 'Enter category name:'] ifFalse: [categories at: index]. ^ category isEmptyOrNil ifTrue: [^ aString] ifFalse: [category]! ! !Debugger methodsFor: 'context stack menu' stamp: 'wod 5/15/1998 00:24'! browseMessages "Present a menu of all messages sent by the currently selected message. Open a message set browser of all implementors of the message chosen. Do nothing if no message is chosen." contextStackIndex = 0 ifTrue: [^ self]. super browseMessages.! ! !Debugger methodsFor: 'context stack menu' stamp: 'wod 5/15/1998 00:23'! browseSendersOfMessages "Present a menu of the currently selected message, as well as all messages sent by it. Open a message set browser of all implementors of the message chosen." contextStackIndex = 0 ifTrue: [^ self]. super browseSendersOfMessages! ! !Debugger methodsFor: 'context stack menu' stamp: 'sd 11/20/2005 21:27'! browseVersions "Create and schedule a message set browser on all versions of the currently selected message selector." | class selector | class := self selectedClassOrMetaClass. selector := self selectedMessageName. VersionsBrowser browseVersionsOf: (class compiledMethodAt: selector) class: self selectedClass theNonMetaClass meta: class isMeta category: self selectedMessageCategoryName selector: selector! ! !Debugger methodsFor: 'context stack menu' stamp: 'tk 4/6/98 23:00'! buildMessageBrowser "Create and schedule a message browser on the current method." contextStackIndex = 0 ifTrue: [^ self]. ^ Browser openMessageBrowserForClass: self selectedClassOrMetaClass selector: self selectedMessageName editString: nil! ! !Debugger methodsFor: 'context stack menu'! close: aScheduledController "The argument is a controller on a view of the receiver. That view is closed." aScheduledController close ! ! !Debugger methodsFor: 'context stack menu' stamp: 'sd 11/20/2005 21:27'! contextStackKey: aChar from: view "Respond to a keystroke in the context list" | selector | selector := ContextStackKeystrokes at: aChar ifAbsent: [nil]. selector ifNil: [self messageListKey: aChar from: view] ifNotNil: [self perform: selector]! ! !Debugger methodsFor: 'context stack menu' stamp: 'alain.plantec 5/30/2008 11:42'! contextStackMenu: aMenu shifted: shifted "Set up the menu appropriately for the context-stack-list, either shifted or unshifted as per the parameter provided" ^ shifted ifTrue: [aMenu labels: 'browse class hierarchy browse class browse method (O) implementors of sent messages change sets with this method inspect instances inspect subinstances revert to previous version remove from current change set revert & remove from changes more...' lines: #(5 7 10 ) selections: #(#classHierarchy #browseClass #openSingleMessageBrowser #browseAllMessages #findMethodInChangeSets #inspectInstances #inspectSubInstances #revertToPreviousVersion #removeFromCurrentChanges #revertAndForget #unshiftedYellowButtonActivity )] ifFalse: [self selectedContext selector = #doesNotUnderstand: ifTrue: [aMenu add: 'implement in...' subMenu: (self populateImplementInMenu: (MenuMorph new defaultTarget: self)) target: nil selector: nil argumentList: #(nil )]. aMenu labels: 'fullStack (f) restart (r) proceed (p) step (t) step through (T) send (e) where (w) peel to first like this return entered value toggle break on entry senders of... (n) implementors of... (m) inheritance (i) versions (v) inst var refs... inst var defs... class var refs... class variables class refs (N) browse full (b) file out mail out bug report more...' lines: #(8 9 13 15 18 21 ) selections: #(#fullStack #restart #proceed #doStep #stepIntoBlock #send #where #peelToFirst #returnValue #toggleBreakOnEntry #browseSendersOfMessages #browseMessages #methodHierarchy #browseVersions #browseInstVarRefs #browseInstVarDefs #browseClassVarRefs #browseClassVariables #browseClassRefs #browseMethodFull #fileOutMessage #mailOutBugReport #shiftedYellowButtonActivity )]! ! !Debugger methodsFor: 'context stack menu' stamp: 'tk 4/16/1998 12:19'! debugProceedMenu: aMenu ^ aMenu labels: 'proceed debug' lines: #() selections: #(proceed debug ) ! ! !Debugger methodsFor: 'context stack menu' stamp: 'sd 11/20/2005 21:27'! doStep "Send the selected message in the accessed method, and regain control after the invoked method returns." | currentContext newContext | self okToChange ifFalse: [^ self]. self checkContextSelection. currentContext := self selectedContext. newContext := interruptedProcess completeStep: currentContext. newContext == currentContext ifTrue: [ newContext := interruptedProcess stepToSendOrReturn]. self contextStackIndex > 1 ifTrue: [self resetContext: newContext] ifFalse: [newContext == currentContext ifTrue: [self changed: #contentsSelection. self updateInspectors] ifFalse: [self resetContext: newContext]]. ! ! !Debugger methodsFor: 'context stack menu' stamp: 'tk 4/15/1998 16:55'! down "move down the context stack to the previous (enclosing) context" self toggleContextStackIndex: contextStackIndex+1! ! !Debugger methodsFor: 'context stack menu' stamp: 'tk 4/17/1998 18:06'! fullStack "Change from displaying the minimal stack to a full one." self contextStackList size > 20 "Already expanded" ifTrue: [self changed: #flash] ifFalse: [self contextStackIndex = 0 ifFalse: [ self toggleContextStackIndex: self contextStackIndex]. self fullyExpandStack]! ! !Debugger methodsFor: 'context stack menu' stamp: 'eem 5/21/2008 10:39'! implement: aMessage inClass: aClass aClass compile: aMessage createStubMethod classified: (self askForCategoryIn: aClass default: 'as yet unclassified'). self setContentsToForceRefetch. self selectedContext privRefreshWith: (aClass lookupSelector: aMessage selector). self selectedContext method numArgs > 0 ifTrue: [(self selectedContext tempAt: 1) arguments withIndexDo: [:arg :index| self selectedContext tempAt: index put: arg]]. self resetContext: self selectedContext. self debug. ! ! !Debugger methodsFor: 'context stack menu' stamp: 'PeterHugossonMiller 9/3/2009 01:11'! mailOutBugReport "Compose a useful bug report showing the state of the process as well as vital image statistics as suggested by Chris Norton - 'Squeak could pre-fill the bug form with lots of vital, but oft-repeated, information like what is the image version, last update number, VM version, platform, available RAM, author...' and address it to the list with the appropriate subject prefix." | messageStrm | MailSender default ifNil: [^self]. Cursor write showWhile: ["Prepare the message" messageStrm := (String new: 1500) writeStream. messageStrm nextPutAll: 'From: '; nextPutAll: MailSender userName; cr; nextPutAll: 'To: Pharo-project@lists.gforge.inria.fr'; cr; nextPutAll: 'Subject: '; nextPutAll: '[BUG]'; nextPutAll: self interruptedContext printString; cr;cr; nextPutAll: 'here insert explanation of what you were doing, suspect changes you''ve made and so forth.';cr;cr. self interruptedContext errorReportOn: messageStrm. MailSender sendMessage: (MailMessage from: messageStrm contents)]. ! ! !Debugger methodsFor: 'context stack menu' stamp: 'sw 3/16/2001 17:20'! messageListMenu: aMenu shifted: shifted "The context-stack menu takes the place of the message-list menu in the debugger, so pass it on" ^ self contextStackMenu: aMenu shifted: shifted! ! !Debugger methodsFor: 'context stack menu' stamp: 'md 2/20/2006 20:23'! peelToFirst "Peel the stack back to the second occurance of the currently selected message. Very useful for an infinite recursion. Gets back to the second call so you can see one complete recursion cycle, and how it was called at the beginning. Also frees a lot of space!!" | ctxt | contextStackIndex = 0 ifTrue: [^ Beeper beep]. "self okToChange ifFalse: [^ self]." ctxt := interruptedProcess popTo: self selectedContext findSecondToOldestSimilarSender. self resetContext: ctxt. ! ! !Debugger methodsFor: 'context stack menu' stamp: 'sd 11/20/2005 21:27'! populateImplementInMenu: aMenu | msg | msg := self selectedContext at: 1. self selectedContext receiver class withAllSuperclasses do: [:each | aMenu add: each name target: self selector: #implement:inClass: argumentList: (Array with: msg with: each)]. ^ aMenu ! ! !Debugger methodsFor: 'context stack menu' stamp: 'di 5/5/1998 00:07'! proceed "Proceed execution of the receiver's model, starting after the expression at which an interruption occurred." Smalltalk okayToProceedEvenIfSpaceIsLow ifTrue: [ self proceed: self topView]. ! ! !Debugger methodsFor: 'context stack menu' stamp: 'ajh 1/24/2003 12:29'! proceed: aTopView "Proceed from the interrupted state of the currently selected context. The argument is the topView of the receiver. That view is closed." self okToChange ifFalse: [^ self]. self checkContextSelection. self resumeProcess: aTopView! ! !Debugger methodsFor: 'context stack menu' stamp: 'sd 11/20/2005 21:27'! restart "Proceed from the initial state of the currently selected context. The argument is a controller on a view of the receiver. That view is closed." "Closing now depends on a preference #restartAlsoProceeds - hmm 9/7/2001 16:46" | ctxt noUnwindError | self okToChange ifFalse: [^ self]. self checkContextSelection. ctxt := interruptedProcess popTo: self selectedContext. noUnwindError := false. ctxt == self selectedContext ifTrue: [ noUnwindError := true. interruptedProcess restartTop; stepToSendOrReturn]. self resetContext: ctxt. (Preferences restartAlsoProceeds and: [noUnwindError]) ifTrue: [self proceed]. ! ! !Debugger methodsFor: 'context stack menu' stamp: 'rbb 3/1/2005 10:50'! returnValue "Force a return of a given value to the previous context!!" | previous selectedContext expression value | contextStackIndex = 0 ifTrue: [^Beeper beep]. selectedContext := self selectedContext. expression := UIManager default request: 'Enter expression for return value:'. value := Compiler new evaluate: expression in: selectedContext to: selectedContext receiver. previous := selectedContext sender. self resetContext: previous. interruptedProcess popTo: previous value: value! ! !Debugger methodsFor: 'context stack menu' stamp: 'sd 11/20/2005 21:27'! selectPC "Toggle the flag telling whether to automatically select the expression currently being executed by the selected context." selectingPC := selectingPC not! ! !Debugger methodsFor: 'context stack menu' stamp: 'ajh 1/24/2003 12:29'! send "Send the selected message in the accessed method, and take control in the method invoked to allow further step or send." self okToChange ifFalse: [^ self]. self checkContextSelection. interruptedProcess step: self selectedContext. self resetContext: interruptedProcess stepToSendOrReturn. ! ! !Debugger methodsFor: 'context stack menu' stamp: 'ajh 1/24/2003 12:46'! stepIntoBlock "Send messages until you return to the present method context. Used to step into a block in the method." interruptedProcess stepToHome: self selectedContext. self resetContext: interruptedProcess stepToSendOrReturn.! ! !Debugger methodsFor: 'context stack menu' stamp: 'tk 4/15/1998 16:55'! up "move up the context stack to the next (enclosed) context" contextStackIndex > 1 ifTrue: [self toggleContextStackIndex: contextStackIndex-1]! ! !Debugger methodsFor: 'context stack menu' stamp: 'sd 11/20/2005 21:27'! where "Select the expression whose evaluation was interrupted." selectingPC := true. self contextStackIndex: contextStackIndex oldContextWas: self selectedContext ! ! !Debugger methodsFor: 'dependents access' stamp: 'di 1/14/1999 09:28'! step "Update the inspectors." receiverInspector ifNotNil: [receiverInspector step]. contextVariablesInspector ifNotNil: [contextVariablesInspector step]. ! ! !Debugger methodsFor: 'dependents access' stamp: 'hmm 7/15/2001 19:48'! updateInspectors "Update the inspectors on the receiver's variables." receiverInspector == nil ifFalse: [receiverInspector update]. contextVariablesInspector == nil ifFalse: [contextVariablesInspector update]! ! !Debugger methodsFor: 'dependents access' stamp: 'di 1/14/1999 09:25'! wantsSteps ^ true! ! !Debugger methodsFor: 'initialize' stamp: 'stephane.ducasse 10/26/2008 15:42'! buildNotifierLabelled: label message: messageString | notifyPane window contentTop extentToUse | self expandStack. window := (PreDebugWindow labelled: label) model: self. contentTop := 0.25. extentToUse := 450 @ 156. "nice and wide to show plenty of the error msg" window addMorph: (self buttonRowForPreDebugWindow: window) frame: (0@0 corner: 1 @ contentTop). messageString notNil ifFalse: [notifyPane := PluggableListMorph on: self list: #contextStackList selected: #contextStackIndex changeSelected: #debugAt: menu: nil keystroke: nil] ifTrue: [notifyPane := PluggableTextMorph on: self text: nil accept: nil readSelection: nil menu: #debugProceedMenu:. notifyPane editString: (self preDebugNotifierContentsFrom: messageString); askBeforeDiscardingEdits: false]. window addMorph: notifyPane frame: (0@contentTop corner: 1@1). "window deleteCloseBox. chickened out by commenting the above line out, sw 8/14/2000 12:54" window setBalloonTextForCloseBox. ^ window openInWorldExtent: extentToUse! ! !Debugger methodsFor: 'initialize' stamp: 'hfm 12/21/2008 22:44'! customButtonSpecs "Answer an array of elements of the form wording, selector, help-message, that characterize the custom button row of a debugger." | list | list := #(('Proceed' proceed 'close the debugger and proceed.') ('Restart' restart 'reset this context to its start.') ('Into' send 'step Into message sends') ('Over' doStep 'step Over message sends') ('Through' stepIntoBlock 'step into a block') ('Full Stack' fullStack 'show full stack') ('Run to Here' runToSelection 'run to selection') ('Where' where 'select current pc range')). Preferences restartAlsoProceeds ifTrue: [list := list collect: [:each | each second == #restart ifTrue: [each copy at: 3 put: 'proceed from the beginning of this context.'; yourself] ifFalse: [each]]]. ^ list! ! !Debugger methodsFor: 'initialize' stamp: 'kfr 10/4/2000 22:13'! debugAt: anInteger self toggleContextStackIndex: anInteger. ^ self debug.! ! !Debugger methodsFor: 'initialize' stamp: 'sd 11/20/2005 21:27'! errorWasInUIProcess: boolean errorWasInUIProcess := boolean! ! !Debugger methodsFor: 'initialize' stamp: 'tk 5/9/2003 11:20'! initialExtent "Make the full debugger longer!!" dependents size < 9 ifTrue: [^ super initialExtent]. "Pre debug window" RealEstateAgent standardWindowExtent y < 400 "a tiny screen" ifTrue: [^ super initialExtent]. ^ 600@700 ! ! !Debugger methodsFor: 'initialize' stamp: 'sw 12/28/1999 13:07'! notifierButtonHeight ^ 18! ! !Debugger methodsFor: 'initialize' stamp: 'wiz 2/25/2006 20:22'! openFullMorphicLabel: aLabelString "Open a full morphic debugger with the given label" | window aListMorph oldContextStackIndex | oldContextStackIndex := contextStackIndex. self expandStack. "Sets contextStackIndex to zero." window := (SystemWindow labelled: aLabelString) model: self. aListMorph := PluggableListMorph on: self list: #contextStackList selected: #contextStackIndex changeSelected: #toggleContextStackIndex: menu: #contextStackMenu:shifted: keystroke: #contextStackKey:from:. aListMorph menuTitleSelector: #messageListSelectorTitle. window addMorph: aListMorph frame: (0@0 corner: 1@0.25). self addLowerPanesTo: window at: (0@0.25 corner: 1@0.8) with: nil. window addMorph: (( PluggableListMorph new doubleClickSelector: #inspectSelection; on: self receiverInspector list: #fieldList selected: #selectionIndex changeSelected: #toggleIndex: menu: #fieldListMenu: keystroke: #inspectorKey:from:) autoDeselect: false) "For doubleClick to work best disable autoDeselect" frame: (0@0.8 corner: 0.2@1). window addMorph: (PluggableTextMorph on: self receiverInspector text: #contents accept: #accept: readSelection: #contentsSelection menu: #codePaneMenu:shifted:) frame: (0.2@0.8 corner: 0.5@1). window addMorph: ( PluggableListMorph new doubleClickSelector: #inspectSelection; on: self contextVariablesInspector list: #fieldList selected: #selectionIndex changeSelected: #toggleIndex: menu: #fieldListMenu: keystroke: #inspectorKey:from:) frame: (0.5@0.8 corner: 0.7@1). window addMorph: (PluggableTextMorph on: self contextVariablesInspector text: #contents accept: #accept: readSelection: #contentsSelection menu: #codePaneMenu:shifted:) frame: (0.7@0.8 corner: 1@1). window openInWorld. self toggleContextStackIndex: oldContextStackIndex. ^ window ! ! !Debugger methodsFor: 'initialize' stamp: 'alain.plantec 5/30/2008 11:45'! openFullNoSuspendLabel: aString "Create and schedule a full debugger with the given label. Do not terminate the current active process." self openFullMorphicLabel: aString. errorWasInUIProcess := Project spawnNewProcessIfThisIsUI: interruptedProcess! ! !Debugger methodsFor: 'initialize' stamp: 'alain.plantec 5/30/2008 11:51'! openNotifierContents: msgString label: label "Create and schedule a notifier view with the given label and message. A notifier view shows just the message or the first several lines of the stack, with a menu that allows the user to open a full debugger if so desired. " "NOTE: When this method returns, a new process has been scheduled to run the windows, and thus this notifier, but the previous active porcess has not been suspended. The sender will do this." | msg | Sensor flushKeyboard. savedCursor := Sensor currentCursor. Sensor currentCursor: Cursor normal. (label beginsWith: 'Space is low') ifTrue: [msg := self lowSpaceChoices , (msgString ifNil: [''])] ifFalse: [msg := msgString]. isolationHead ifNotNil: ["We have already revoked the isolation layer -- now jump to the parent project." msg := self isolationRecoveryAdvice , msgString. failedProject := Project current. isolationHead parent enterForEmergencyRecovery]. self buildNotifierLabelled: label message: msg. errorWasInUIProcess := Project spawnNewProcessIfThisIsUI: interruptedProcess! ! !Debugger methodsFor: 'initialize' stamp: 'sbw 12/23/1999 09:50'! optionalAnnotationHeight ^ 10! ! !Debugger methodsFor: 'initialize' stamp: 'stephane.ducasse 10/26/2008 15:32'! preDebugButtonQuads ^ { {'Proceed' translated. #proceed. #blue. 'continue execution' translated}. {'Abandon' translated. #abandon. #black. 'abandon this execution by closing this window' translated}. {'Debug' translated. #debug. #red. 'bring up a debugger' translated} } ! ! !Debugger methodsFor: 'initialize' stamp: 'stephane.ducasse 10/26/2008 15:33'! preDebugNotifierContentsFrom: messageString ^ messageString ! ! !Debugger methodsFor: 'initialize' stamp: 'jm 8/20/1998 18:31'! release self windowIsClosing. super release. ! ! !Debugger methodsFor: 'initialize' stamp: 'sw 1/24/2001 21:22'! wantsOptionalButtons "The debugger benefits so majorly from the optional buttons that we put them up regardless of the global setting. Some traditionalists will want to change this method manually!!" ^ true! ! !Debugger methodsFor: 'initialize' stamp: 'sd 11/20/2005 21:27'! windowIsClosing "My window is being closed; clean up. Restart the low space watcher." interruptedProcess == nil ifTrue: [^ self]. interruptedProcess terminate. interruptedProcess := nil. interruptedController := nil. contextStack := nil. contextStackTop := nil. receiverInspector := nil. contextVariablesInspector := nil. Smalltalk installLowSpaceWatcher. "restart low space handler" ! ! !Debugger methodsFor: 'notifier menu' stamp: 'alain.plantec 5/30/2008 11:43'! debug "Open a full DebuggerView." | topView | topView := self topView. topView model: nil. "so close won't release me." self breakDependents. topView delete. ^ self openFullMorphicLabel: topView label! ! !Debugger methodsFor: 'notifier menu' stamp: 'adrian_lienhard 7/18/2009 15:54'! storeLog | logFileName | logFileName := Preferences debugLogTimestamp ifTrue: ['PharoDebug-' , Time totalSeconds printString , '.log'] ifFalse: ['PharoDebug.log']. Smalltalk logError: labelString printString inContext: contextStackTop to: logFileName ! ! !Debugger methodsFor: 'tally support' stamp: 'ab 3/23/2005 16:43'! getSelectedText | m interval text | m := self getTextMorph. interval := m selectionInterval. text := m text. ^ text copyFrom: interval first to: interval last ! ! !Debugger methodsFor: 'tally support' stamp: 'ab 3/23/2005 16:43'! getTextMorph ^ (self dependents select: [:m| m class == PluggableTextMorph]) first! ! !Debugger methodsFor: 'tally support' stamp: 'ab 3/23/2005 16:42'! tally self getTextMorph tallyIt. ! ! !Debugger methodsFor: 'toolbuilder' stamp: 'ar 2/12/2005 18:30'! buildFullWith: builder | windowSpec listSpec textSpec panelSpec extent | windowSpec := builder pluggableWindowSpec new. windowSpec model: self. windowSpec label: 'Debugger'. Display height < 800 "a small screen" ifTrue:[extent := RealEstateAgent standardWindowExtent] ifFalse:[extent := 600@700]. windowSpec extent: extent. windowSpec children: OrderedCollection new. listSpec := builder pluggableListSpec new. listSpec model: self; list: #contextStackList; getIndex: #contextStackIndex; setIndex: #toggleContextStackIndex:; menu: #contextStackMenu:shifted:; keyPress: #contextStackKey:from:; frame: (0@0 corner: 1@0.25). windowSpec children add: listSpec. panelSpec := self buildOptionalButtonsWith: builder. panelSpec frame: (0@0.25 corner: 1@0.3). windowSpec children add: panelSpec. textSpec := builder pluggableTextSpec new. textSpec model: self; getText: #contents; setText: #contents:notifying:; selection: #contentsSelection; menu: #codePaneMenu:shifted:; frame: (0@0.3corner: 1@0.8). windowSpec children add: textSpec. listSpec := builder pluggableListSpec new. listSpec model: self receiverInspector; list: #fieldList; getIndex: #selectionIndex; setIndex: #toggleIndex:; menu: #fieldListMenu:; keyPress: #inspectorKey:from:; frame: (0@0.8 corner: 0.2@1). windowSpec children add: listSpec. textSpec := builder pluggableTextSpec new. textSpec model: self receiverInspector; getText: #contents; setText: #accept:; selection: #contentsSelection; menu: #codePaneMenu:shifted:; frame: (0.2@0.8 corner: 0.5@1). windowSpec children add: textSpec. listSpec := builder pluggableListSpec new. listSpec model: self contextVariablesInspector; list: #fieldList; getIndex: #selectionIndex; setIndex: #toggleIndex:; menu: #fieldListMenu:; keyPress: #inspectorKey:from:; frame: (0.5@0.8 corner: 0.7@1). windowSpec children add: listSpec. textSpec := builder pluggableTextSpec new. textSpec model: self contextVariablesInspector; getText: #contents; setText: #accept:; selection: #contentsSelection; menu: #codePaneMenu:shifted:; frame: (0.7@0.8 corner: 1@1). windowSpec children add: textSpec. ^builder build: windowSpec! ! !Debugger methodsFor: 'toolbuilder' stamp: 'stephane.ducasse 10/26/2008 15:42'! buildNotifierWith: builder label: label message: messageString | windowSpec listSpec textSpec panelSpec buttonSpec | windowSpec := builder pluggableWindowSpec new. windowSpec model: self. windowSpec extent: 450 @ 156. "nice and wide to show plenty of the error msg" windowSpec label: label. windowSpec children: OrderedCollection new. panelSpec := builder pluggablePanelSpec new. panelSpec children: OrderedCollection new. self preDebugButtonQuads do:[:spec| buttonSpec := builder pluggableButtonSpec new. buttonSpec model: self. buttonSpec label: spec first. buttonSpec action: spec second. buttonSpec help: spec fourth. panelSpec children add: buttonSpec. ]. panelSpec layout: #horizontal. "buttons" panelSpec frame: (0@0 corner: 1@0.2). windowSpec children add: panelSpec. messageString notNil ifTrue:[ listSpec := builder pluggableListSpec new. listSpec model: self; list: #contextStackList; getIndex: #contextStackIndex; setIndex: #debugAt:; frame: (0@0.2 corner: 1@1). windowSpec children add: listSpec. ] ifFalse:[ textSpec := builder pluggableTextSpec new. textSpec model: self; getText: #preDebugMessageString; setText: nil; selection: nil; menu: #debugProceedMenu:; frame: (0@0.2corner: 1@1). windowSpec children add: textSpec. ]. ^windowSpec! ! !Debugger methodsFor: 'toolbuilder' stamp: 'ar 2/11/2005 16:24'! buildWith: aBuilder ^self buildFullWith: aBuilder! ! !Debugger methodsFor: 'toolbuilder' stamp: 'ar 2/11/2005 16:25'! preDebugMessageString ^'An error has occurred; you should probably just hit ''abandon''. Sorry!!'! ! !Debugger methodsFor: 'private' stamp: 'sd 11/20/2005 21:27'! askForSuperclassOf: aClass toImplement: aSelector ifCancel: cancelBlock | classes chosenClassIndex | classes := aClass withAllSuperclasses. chosenClassIndex := UIManager default chooseFrom: (classes collect: [:c | c name]) title: 'Define #', aSelector, ' in which class?'. chosenClassIndex = 0 ifTrue: [^ cancelBlock value]. ^ classes at: chosenClassIndex! ! !Debugger methodsFor: 'private' stamp: 'yo 8/12/2003 16:34'! checkContextSelection contextStackIndex = 0 ifTrue: [self contextStackIndex: 1 oldContextWas: nil]. ! ! !Debugger methodsFor: 'private' stamp: 'eem 3/12/2009 14:55'! contextStackIndex: anInteger oldContextWas: oldContext "Change the context stack index to anInteger, perhaps in response to user selection." | isNewMethod selectedContextSlotName index | contextStackIndex := anInteger. anInteger = 0 ifTrue: [currentCompiledMethod := contents := nil. self changed: #contextStackIndex. self decorateButtons. self contentsChanged. contextVariablesInspector object: nil. receiverInspector object: self receiver. ^self]. selectedContextSlotName := contextVariablesInspector selectedSlotName. isNewMethod := oldContext == nil or: [oldContext method ~~ (currentCompiledMethod := self selectedContext method)]. isNewMethod ifTrue: [contents := self selectedMessage. self contentsChanged. self pcRange]. self changed: #contextStackIndex. self decorateButtons. contextVariablesInspector object: self selectedContext. ((index := contextVariablesInspector fieldList indexOf: selectedContextSlotName) ~= 0 and: [index ~= contextVariablesInspector selectionIndex]) ifTrue: [contextVariablesInspector toggleIndex: index]. receiverInspector object: self receiver. isNewMethod ifFalse: [self changed: #contentsSelection]! ! !Debugger methodsFor: 'private' stamp: 'sd 11/20/2005 21:27'! createMethod "Should only be called when this Debugger was created in response to a MessageNotUnderstood exception. Create a stub for the method that was missing and proceed into it." | msg chosenClass | msg := contextStackTop tempAt: 1. chosenClass := self askForSuperclassOf: contextStackTop receiver class toImplement: msg selector ifCancel: [^self]. self implement: msg inClass: chosenClass. ! ! !Debugger methodsFor: 'private' stamp: 'sd 11/20/2005 21:27'! externalInterrupt: aBoolean externalInterrupt := aBoolean ! ! !Debugger methodsFor: 'private' stamp: 'tk 8/17/2000 15:36'! isolationRecoveryAdvice "Return a notifier message string to be presented in case of recovery from recursive error by revoking the changes in an isolation layer. This surely ranks as one of Squeak's longer help messages." ^ 'Warning!! You have encountered a recursive error situation. Don''t panic, but do read the following advice. If you were just fooling around, the simplest thing to do is to quit and NOT save, and restart Squeak. If you care about recovery, then read on... In the process of diagnosing one error, further errors occurred, making it impossible to give you a debugger to work with. Squeak has jumped to an outer project where many of the objects and code changes that might have caused this problem are not involved in normal operation. If you are looking at this window, chances are that this first level of recovery was successful. If there are changes you care a lot about, try to save them now. Then, hopefully, from the state in this debugger, you can determine what the problem was and fix it. Do not save this image until you are confident of its recovery. You are no longer in the world that is damaged. The two most likely causes of recursive errors are malformed objects (for instance a corrupt value encountered in any display of the desktop) and recurring code errors (such as a change that causes errors in any attempt to display the desktop). In the case of malformed objects, you can attempt to repair them by altering various bindings in the corrupted environment. Open this debugger and examine the state of the objects closest to the error. In the case of code errors, note that you are no longer in a world where the erroneous code is in effect. The only simple option available is for you to browse to the changeSet for the project in distress, and remove one or more of the changes (later it will be possible to edit the code remotely from here). If you feel you have repaired the problem, then you may proceed from this debugger. This will put you back in the project that failed with the changes that failed for another try. Note that the debugger from which you are proceeding is the second one that occurred; you will likely find the first one waiting for you when you reenter the failed project!! Also note that if your error occurred while displaying a morph, it may now be flagged as undisplayable (red with yellow cross); if so, use the morph debug menu to choose ''start drawing again''. If you have not repaired the problem, you should close this debugger and delete the failed project after retrieving whatever may be of value in it. Good luck. - The Squeak Fairy Godmother PS: If you feel you need the help of a quantum mechanic, do NOT close this window. Instead, the best thing to do (after saving anything that seems safe to save) would be to use the ''save as...'' command in the world menu, and give it a new image name, such as OOPS. There is a good chance that someone who knows their way around Squeak can help you out. '! ! !Debugger methodsFor: 'private' stamp: 'adrian_lienhard 7/18/2009 15:53'! lowSpaceChoices "Return a notifier message string to be presented when space is running low." ^ 'Warning!! Pharo is almost out of memory!! Low space detection is now disabled. It will be restored when you close or proceed from this error notifier. Don''t panic, but do proceed with caution. Here are some suggestions: If you suspect an infinite recursion (the same methods calling each other again and again), then close this debugger, and fix the problem. If you want this computation to finish, then make more space available (read on) and choose "proceed" in this debugger. Here are some ways to make more space available... > Close any windows that are not needed. > Get rid of some large objects (e.g., images). > Leave this window on the screen, choose "save as..." from the screen menu, quit, restart the Pharo VM with a larger memory allocation, then restart the image you just saved, and choose "proceed" in this window. If you want to investigate further, choose "debug" in this window. Do not use the debugger "fullStack" command unless you are certain that the stack is not very deep. (Trying to show the full stack will definitely use up all remaining memory if the low-space problem is caused by an infinite recursion!!). ' ! ! !Debugger methodsFor: 'private' stamp: 'sd 11/20/2005 21:27'! newStack: stack | oldStack diff | oldStack := contextStack. contextStack := stack. (oldStack == nil or: [oldStack last ~~ stack last]) ifTrue: [contextStackList := contextStack collect: [:ctx | ctx printString]. ^ self]. "May be able to re-use some of previous list" diff := stack size - oldStack size. contextStackList := diff <= 0 ifTrue: [contextStackList copyFrom: 1-diff to: oldStack size] ifFalse: [diff > 1 ifTrue: [contextStack collect: [:ctx | ctx printString]] ifFalse: [(Array with: stack first printString) , contextStackList]]! ! !Debugger methodsFor: 'private' stamp: 'di 4/14/2000 16:24'! process: aProcess controller: aController context: aContext ^ self process: aProcess controller: aController context: aContext isolationHead: nil! ! !Debugger methodsFor: 'private' stamp: 'alain.plantec 5/30/2008 11:59'! process: aProcess controller: aController context: aContext isolationHead: projectOrNil super initialize. Smalltalk at: #MessageTally ifPresentAndInMemory: [:c | c new close]. contents := nil. interruptedProcess := aProcess. interruptedController := aController. contextStackTop := aContext. self newStack: (contextStackTop stackOfSize: 1). contextStackIndex := 1. externalInterrupt := false. selectingPC := true. isolationHead := projectOrNil. errorWasInUIProcess := false! ! !Debugger methodsFor: 'private' stamp: 'sd 11/20/2005 21:27'! resetContext: aContext "Used when a new context becomes top-of-stack, for instance when the method of the selected context is re-compiled, or the simulator steps or returns to a new method. There is room for much optimization here, first to save recomputing the whole stack list (and text), and secondly to avoid recomposing all that text (by editing the paragraph instead of recreating it)." | oldContext | oldContext := self selectedContext. contextStackTop := aContext. self newStack: contextStackTop contextStack. self changed: #contextStackList. self contextStackIndex: 1 oldContextWas: oldContext. self contentsChanged. ! ! !Debugger methodsFor: 'private' stamp: 'alain.plantec 5/30/2008 12:04'! resumeProcess: aTopView savedCursor ifNotNil: [Sensor currentCursor: savedCursor]. isolationHead ifNotNil: [failedProject enterForEmergencyRecovery. isolationHead invoke. isolationHead := nil]. interruptedProcess isTerminated ifFalse: [errorWasInUIProcess ifTrue: [Project resumeProcess: interruptedProcess] ifFalse: [interruptedProcess resume]]. "if old process was terminated, just terminate current one" interruptedProcess := nil. "Before delete, so release doesn't terminate it" aTopView delete. World displayWorld. Smalltalk installLowSpaceWatcher. "restart low space handler" errorWasInUIProcess == false ifFalse: [Processor terminateActive]! ! !Debugger methodsFor: 'private'! selectedContext contextStackIndex = 0 ifTrue: [^contextStackTop] ifFalse: [^contextStack at: contextStackIndex]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Debugger class instanceVariableNames: ''! !Debugger class methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:28'! initialize ErrorRecursion := false. ContextStackKeystrokes := Dictionary new at: $e put: #send; at: $t put: #doStep; at: $T put: #stepIntoBlock; at: $p put: #proceed; at: $r put: #restart; at: $f put: #fullStack; at: $w put: #where; yourself. "Debugger initialize"! ! !Debugger class methodsFor: 'initialization' stamp: 'adrian_lienhard 7/18/2009 15:54'! openContext: aContext label: aString contents: contentsStringOrNil | isolationHead | "Open a notifier in response to an error, halt, or notify. A notifier view just shows a short view of the sender stack and provides a menu that lets the user open a full debugger." "Simulation guard" ErrorRecursion not & Preferences logDebuggerStackToFile ifTrue: [Smalltalk logError: aString inContext: aContext to: 'PharoDebug.log']. ErrorRecursion ifTrue: [ErrorRecursion := false. (isolationHead := Project current isolationHead) ifNil: [self primitiveError: aString] ifNotNil: [isolationHead revoke]]. ErrorRecursion := true. self informExistingDebugger: aContext label: aString. (Debugger context: aContext isolationHead: isolationHead) openNotifierContents: contentsStringOrNil label: aString. ErrorRecursion := false. Processor activeProcess suspend. ! ! !Debugger class methodsFor: 'instance creation' stamp: 'di 4/14/2000 16:29'! context: aContext "Answer an instance of me for debugging the active process starting with the given context." ^ self context: aContext isolationHead: nil! ! !Debugger class methodsFor: 'instance creation' stamp: 'alain.plantec 5/30/2008 12:06'! context: aContext isolationHead: isolationHead "Answer an instance of me for debugging the active process starting with the given context." ^ self new process: Processor activeProcess controller: nil context: aContext isolationHead: isolationHead ! ! !Debugger class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! informExistingDebugger: aContext label: aString "Walking the context chain, we try to find out if we're in a debugger stepping situation. If we find the relevant contexts, we must rearrange them so they look just like they would if the methods were excuted outside of the debugger." | ctx quickStepMethod oldSender baseContext | ctx := thisContext. quickStepMethod := ContextPart compiledMethodAt: #quickSend:to:with:super:. [ctx sender == nil or: [ctx sender method == quickStepMethod]] whileFalse: [ctx := ctx sender]. ctx sender == nil ifTrue: [^self]. baseContext := ctx. "baseContext is now the context created by the #quickSend... method." oldSender := ctx := ctx sender home sender. "oldSender is the context which originally sent the #quickSend... method" [ctx == nil or: [ctx receiver isKindOf: self]] whileFalse: [ctx := ctx sender]. ctx == nil ifTrue: [^self]. "ctx is the context of the Debugger method #doStep" ctx receiver labelString: aString. ctx receiver externalInterrupt: false; proceedValue: aContext receiver. baseContext swapSender: baseContext sender sender sender. "remove intervening contexts" thisContext swapSender: oldSender. "make myself return to debugger" ErrorRecursion := false. ^aContext! ! !Debugger class methodsFor: 'opening' stamp: 'stephane.ducasse 10/26/2008 15:30'! openInterrupt: aString onProcess: interruptedProcess "Open a notifier in response to an interrupt. An interrupt occurs when the user types the interrupt key (cmd-. on Macs, ctrl-c or alt-. on other systems) or when the low-space watcher detects that memory is low." | debugger | "Simulation guard" debugger := self new. debugger process: interruptedProcess controller: nil context: interruptedProcess suspendedContext. debugger externalInterrupt: true. Preferences logDebuggerStackToFile ifTrue: [(aString includesSubString: 'Space') & (aString includesSubString: 'low') ifTrue: [Smalltalk logError: aString inContext: debugger interruptedContext to: 'LowSpaceDebug.log']]. ^ debugger openNotifierContents: nil label: aString! ! !Debugger class methodsFor: 'opening' stamp: 'adrian_lienhard 7/18/2009 15:54'! openOn: process context: context label: title contents: contentsStringOrNil fullView: bool "Open a notifier in response to an error, halt, or notify. A notifier view just shows a short view of the sender stack and provides a menu that lets the user open a full debugger." | errorWasInUIProcess | errorWasInUIProcess := Project spawnNewProcessIfThisIsUI: process. WorldState addDeferredUIMessage: [[| debugger | debugger := self new process: process controller: nil context: context. "schedule debugger in deferred UI message to address redraw problems after opening a debugger e.g. from the testrunner." "WorldState addDeferredUIMessage: [" bool ifTrue: [debugger openFullNoSuspendLabel: title] ifFalse: [debugger openNotifierContents: contentsStringOrNil label: title]. debugger errorWasInUIProcess: errorWasInUIProcess. Preferences logDebuggerStackToFile ifTrue: [Smalltalk logError: title inContext: context to: 'PharoDebug.log']] on: Error do: [:ex | self primitiveError: 'Orginal error: ' , title asString , '. Debugger error: ' , ([ex description] on: Error do: ['a ' , ex class printString]) , ':']]. process suspend! ! !Debugger class methodsFor: 'window color' stamp: 'sw 2/26/2002 14:10'! windowColorSpecification "Answer a WindowColorSpec object that declares my preference" ^ WindowColorSpec classSymbol: self name wording: 'Debugger' brightColor: #lightRed pastelColor: #veryPaleRed helpMessage: 'The system debugger.'! ! Object subclass: #DebuggerMethodMap instanceVariableNames: 'timestamp methodReference methodNode abstractSourceRanges sortedSourceMap' classVariableNames: 'MapCache MapCacheEntries' poolDictionaries: '' category: 'Tools-Debugger'! !DebuggerMethodMap commentStamp: '' prior: 0! I am a place-holder for information needed by the Debugger to inspect method activations. I insulate the debugger from details of code generation such as exact bytecode offsets and temporary variable locations. I have two concreate subclasses, one for methods compiled using BlueBook blocks and one for methods compiled using Closures. These classes deal with temporary variable access. My function is to abstract the source map away from actual bytecode pcs to abstract bytecode pcs. To reduce compilation time I try and defer as much computation to access time as possible as instances of me will be created after each compilation. I maintain a WeakIdentityDictionary of method to DebuggerMethodMap to cache maps. I refer to my method through a WeakArray to keep the map cache functional. If the reference from a DebuggerMethodMap to its method were strong then the method would never be dropped from the cache because the reference from its map would keep it alive.! ]style[(974)i! !DebuggerMethodMap methodsFor: 'accessing' stamp: 'eem 6/3/2008 12:21'! markRecentlyUsed timestamp := Time totalSeconds! ! !DebuggerMethodMap methodsFor: 'accessing' stamp: 'eem 6/5/2008 09:21'! method ^methodReference at: 1! ! !DebuggerMethodMap methodsFor: 'accessing' stamp: 'eem 6/10/2008 09:44'! namedTempAt: index in: aContext "Answer the value of the temp at index in aContext where index is relative to the array of temp names answered by tempNamesForContext:" self subclassResponsibility! ! !DebuggerMethodMap methodsFor: 'accessing' stamp: 'eem 6/10/2008 09:44'! namedTempAt: index put: aValue in: aContext "Assign the value of the temp at index in aContext where index is relative to the array of temp names answered by tempNamesForContext:" self subclassResponsibility! ! !DebuggerMethodMap methodsFor: 'accessing' stamp: 'eem 6/10/2008 09:45'! tempNamesForContext: aContext "Answer an Array of all the temp names in scope in aContext starting with the home's first local (the first argument or first temporary if no arguments)." self subclassResponsibility! ! !DebuggerMethodMap methodsFor: 'accessing' stamp: 'PeterHugossonMiller 9/3/2009 01:12'! tempsAndValuesForContext: aContext "Return a string of the temporary variabls and their current values" | aStream | aStream := (String new: 100) writeStream. (self tempNamesForContext: aContext) doWithIndex: [:title :index | aStream nextPutAll: title; nextPut: $:; space; tab. aContext print: (self namedTempAt: index in: aContext) on: aStream. aStream cr]. ^aStream contents! ! !DebuggerMethodMap methodsFor: 'accessing' stamp: 'eem 6/2/2008 18:32'! timestamp ^timestamp! ! !DebuggerMethodMap methodsFor: 'initialize-release' stamp: 'eem 6/5/2008 09:21'! forMethod: aMethod "" methodNode: theMethodNode "" methodReference := WeakArray with: aMethod. methodNode := theMethodNode. self markRecentlyUsed! ! !DebuggerMethodMap methodsFor: 'source mapping' stamp: 'eem 7/29/2008 17:12'! abstractSourceMap "Answer with a Dictionary of abstractPC to sourceRange ." | theMethodToScan rawSourceRanges concreteSourceRanges abstractPC scanner client | abstractSourceRanges ifNotNil: [^abstractSourceRanges]. "If the methodNode hasn't had a method generated it doesn't have pcs set in its nodes so we must generate a new method and might as well use it for scanning." methodNode rawSourceRangesAndMethodDo: [:ranges :method| rawSourceRanges := ranges. theMethodToScan := method]. concreteSourceRanges := Dictionary new. rawSourceRanges keysAndValuesDo: [:node :range| node pc ~= 0 ifTrue: [concreteSourceRanges at: node pc put: range]]. abstractPC := 1. abstractSourceRanges := Dictionary new. scanner := InstructionStream on: theMethodToScan. client := InstructionClient new. [(concreteSourceRanges includesKey: scanner pc) ifTrue: [abstractSourceRanges at: abstractPC put: (concreteSourceRanges at: scanner pc)]. abstractPC := abstractPC + 1. scanner interpretNextInstructionFor: client. scanner atEnd] whileFalse. ^abstractSourceRanges! ! !DebuggerMethodMap methodsFor: 'source mapping' stamp: 'eem 6/5/2008 16:43'! rangeForPC: contextsConcretePC contextIsActiveContext: contextIsActiveContext "Answer the indices in the source code for the supplied pc. If the context is the actve context (is at the hot end of the stack) then its pc is the current pc. But if the context isn't, because it is suspended sending a message, then its current pc is the previous pc." | pc i end | pc := self method abstractPCForConcretePC: (contextIsActiveContext ifTrue: [contextsConcretePC] ifFalse: [(self method pcPreviousTo: contextsConcretePC) ifNotNil: [:prevpc| prevpc] ifNil: [contextsConcretePC]]). (self abstractSourceMap includesKey: pc) ifTrue: [^self abstractSourceMap at: pc]. sortedSourceMap ifNil: [sortedSourceMap := self abstractSourceMap. sortedSourceMap := (sortedSourceMap keys collect: [:key| key -> (sortedSourceMap at: key)]) asSortedCollection]. (sortedSourceMap isNil or: [sortedSourceMap isEmpty]) ifTrue: [^1 to: 0]. i := sortedSourceMap indexForInserting: (pc -> nil). i < 1 ifTrue: [^1 to: 0]. i > sortedSourceMap size ifTrue: [end := sortedSourceMap inject: 0 into: [:prev :this | prev max: this value last]. ^end+1 to: end]. ^(sortedSourceMap at: i) value "| method source scanner map | method := DebuggerMethodMap compiledMethodAt: #rangeForPC:contextIsActiveContext:. source := method getSourceFromFile asString. scanner := InstructionStream on: method. map := method debuggerMap. Array streamContents: [:ranges| [scanner atEnd] whileFalse: [| range | range := map rangeForPC: scanner pc contextIsActiveContext: true. ((map abstractSourceMap includesKey: scanner abstractPC) and: [range first ~= 0]) ifTrue: [ranges nextPut: (source copyFrom: range first to: range last)]. scanner interpretNextInstructionFor: InstructionClient new]]"! ! !DebuggerMethodMap methodsFor: 'source mapping' stamp: 'eem 7/6/2009 10:13'! sourceText self method ifNotNil: [:method| method holdsTempNames ifTrue: [^method getSourceFor: (method selector ifNil: [method defaultSelector]) in: method methodClass]]. ^methodNode sourceText! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DebuggerMethodMap class instanceVariableNames: ''! !DebuggerMethodMap class methodsFor: 'class initialization' stamp: 'eem 6/5/2008 09:14'! initialize "DebuggerMethodMap initialize" self voidMapCache! ! !DebuggerMethodMap class methodsFor: 'class initialization' stamp: 'eem 6/5/2008 09:14'! voidMapCache MapCache := WeakIdentityKeyDictionary new. MapCacheEntries := 16! ! !DebuggerMethodMap class methodsFor: 'debugger support' stamp: 'eem 6/26/2008 22:59'! cacheDebugMap: aDebuggerMethodMap forMethod: aCompiledMethod MapCache finalizeValues. [MapCache size >= MapCacheEntries] whileTrue: [| mapsByAge | mapsByAge := MapCache keys asSortedCollection: [:m1 :m2| (MapCache at: m1) timestamp < (MapCache at: m2) timestamp]. mapsByAge notEmpty ifTrue: "There be race conditions and reentrancy issues here" [MapCache removeKey: mapsByAge last]]. ^MapCache at: aCompiledMethod put: aDebuggerMethodMap! ! !DebuggerMethodMap class methodsFor: 'instance creation' stamp: 'eem 6/5/2008 09:19'! forMethod: aMethod "" "Answer a DebuggerMethodMap suitable for debugging activations of aMethod. Answer an existing instance from the cache if it exists, cacheing a new one if required." ^MapCache at: aMethod ifAbsent: [self cacheDebugMap: (self forMethod: aMethod methodNode: aMethod methodNode) forMethod: aMethod]! ! !DebuggerMethodMap class methodsFor: 'instance creation' stamp: 'eem 7/29/2008 16:54'! forMethod: aMethod "" methodNode: methodNode "" "Uncached instance creation method for private use or for tests. Please consider using forMethod: instead." ^(aMethod isBlueBookCompiled ifTrue: [DebuggerMethodMapForBlueBookMethods] ifFalse: [DebuggerMethodMapForClosureCompiledMethods]) new forMethod: aMethod methodNode: methodNode! ! DebuggerMethodMap subclass: #DebuggerMethodMapForBlueBookMethods instanceVariableNames: 'tempNames' classVariableNames: '' poolDictionaries: '' category: 'Tools-Debugger'! !DebuggerMethodMapForBlueBookMethods commentStamp: '' prior: 0! I am a place-holder for information needed by the Debugger to inspect method activations. See my superclass's comment. I map methods compiled using Closures.! ]style[(158)i! !DebuggerMethodMapForBlueBookMethods methodsFor: 'accessing' stamp: 'eem 6/3/2008 11:43'! namedTempAt: index in: aContext "Answer the value of the temp at index in aContext where index is relative to the array of temp names answered by tempNamesForContext:" ^aContext tempAt: index! ! !DebuggerMethodMapForBlueBookMethods methodsFor: 'accessing' stamp: 'eem 6/3/2008 11:43'! namedTempAt: index put: aValue in: aContext "Assign the value of the temp at index in aContext where index is relative to the array of temp names answered by tempNamesForContext:" ^aContext tempAt: index put: aValue! ! !DebuggerMethodMapForBlueBookMethods methodsFor: 'accessing' stamp: 'eem 6/3/2008 11:42'! tempNamesForContext: aContext "Answer an Array of all the temp names in scope in aContext starting with the home's first local (the first argument or first temporary if no arguments)." ^tempNames! ! !DebuggerMethodMapForBlueBookMethods methodsFor: 'initialize-release' stamp: 'eem 6/5/2008 10:34'! forMethod: aMethod "" methodNode: aMethodNode "" super forMethod: aMethod methodNode: aMethodNode. tempNames := methodNode encoder tempNames! ! DebuggerMethodMap subclass: #DebuggerMethodMapForClosureCompiledMethods instanceVariableNames: 'blockExtentsToTempRefs startpcsToTempRefs' classVariableNames: 'FirstTime' poolDictionaries: '' category: 'Tools-Debugger'! !DebuggerMethodMapForClosureCompiledMethods commentStamp: '' prior: 0! I am a place-holder for information needed by the Debugger to inspect method activations. See my superclass's comment. I map methods compiled using BlueBook blocks. Instance variables blockExtentsToTempsRefs Array of: (Array with: String with: (Integer | (Array with: Integer with: Integer)))> maps a block extent to an Array of temp references for that block/method. Each reference is a pair of temp name and index, where the index can itself be a pair for a remote temp. startpcsToTempRefs Array of: (Array with: String with: temp reference)> where temp reference ::= Integer | (Array with: Integer with: Integer) | (Array with: #outer with: temp reference)! ]style[(167 569)i,cblack;! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'accessing' stamp: 'eem 7/29/2008 19:28'! namedTempAt: index in: aContext "Answer the value of the temp at index in aContext where index is relative to the array of temp names answered by tempNamesForContext:" ^self privateTempAt: index in: aContext startpcsToBlockExtents: aContext method startpcsToBlockExtents! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'accessing' stamp: 'eem 7/29/2008 19:33'! namedTempAt: index put: aValue in: aContext "Assign the value of the temp at index in aContext where index is relative to the array of temp names answered by tempNamesForContext:. If the value is a copied value we also need to set it along the lexical chain." ^self privateTempAt: index in: aContext put: aValue startpcsToBlockExtents: aContext method startpcsToBlockExtents! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'accessing' stamp: 'eem 7/29/2008 18:26'! tempNamesForContext: aContext "Answer an Array of all the temp names in scope in aContext starting with the home's first local (the first argument or first temporary if no arguments)." ^(self privateTempRefsForContext: aContext startpcsToBlockExtents: aContext method startpcsToBlockExtents) collect: [:pair| pair first]! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'accessing' stamp: 'JorgeRessia 10/18/2009 12:41'! tempNamesScopedForContext: aContext "Answer an Array of all the temp names in scope in aContext starting with the home's first local (the first argument or first temporary if no arguments)." ^((self privateTempRefsForContext: aContext startpcsToBlockExtents: aContext method startpcsToBlockExtents) reject: [:pair | self privateIsOuter: pair] ) collect: [:pair| pair first]! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'private' stamp: 'eem 7/29/2008 20:09'! ensureExtentsMapsInitialized | encoderTempRefs " >>>" | blockExtentsToTempRefs ifNotNil: [^self]. blockExtentsToTempRefs := Dictionary new. startpcsToTempRefs := Dictionary new. encoderTempRefs := methodNode blockExtentsToTempRefs. encoderTempRefs keysAndValuesDo: [:blockExtent :tempVector| blockExtentsToTempRefs at: blockExtent put: (Array streamContents: [:stream| tempVector withIndexDo: [:nameOrSequence :index| nameOrSequence isString ifTrue: [stream nextPut: {nameOrSequence. index}] ifFalse: [nameOrSequence withIndexDo: [:name :indirectIndex| stream nextPut: { name. { index. indirectIndex }}]]]])]! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'private' stamp: 'eem 7/29/2008 19:26'! privateDereference: tempReference in: aContext "Fetch the temporary with reference tempReference in aContext. tempReference can be integer - direct temp reference #( indirectionVectorIndex tempIndex ) - remote temp in indirectionVector at index #( outer. temp reference ) - a temp reference in an outer context." ^tempReference isInteger ifTrue: [aContext tempAt: tempReference] ifFalse: [tempReference first == #outer ifTrue: [self privateDereference: tempReference last in: aContext outerContext] ifFalse: [(aContext tempAt: tempReference first) at: tempReference second]]! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'private' stamp: 'eem 7/29/2008 19:26'! privateDereference: tempReference in: aContext put: aValue "Assign the temporary with reference tempReference in aContext. tempReference can be integer - direct temp reference #( indirectionVectorIndex tempIndex ) - remote temp in indirectionVector at index #( outer. temp reference ) - a temp reference in an outer context." ^tempReference isInteger ifTrue: [aContext tempAt: tempReference put: aValue] ifFalse: [tempReference first == #outer ifTrue: [self privateDereference: tempReference last in: aContext outerContext put: aValue] ifFalse: [(aContext tempAt: tempReference first) at: tempReference second put: aValue]]! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'private' stamp: 'JorgeRessia 10/17/2009 18:32'! privateIsOuter: anObject ^anObject last isArray and: [anObject last first == #outer]! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'private' stamp: 'eem 7/29/2008 20:03'! privateTempAt: index in: aContext put: aValue startpcsToBlockExtents: theContextsStartpcsToBlockExtents | nameRefPair | nameRefPair := (self privateTempRefsForContext: aContext startpcsToBlockExtents: theContextsStartpcsToBlockExtents) at: index ifAbsent: [aContext errorSubscriptBounds: index]. ^self privateDereference: nameRefPair last in: aContext put: aValue! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'private' stamp: 'eem 7/29/2008 20:02'! privateTempAt: index in: aContext startpcsToBlockExtents: theContextsStartpcsToBlockExtents | nameRefPair | nameRefPair := (self privateTempRefsForContext: aContext startpcsToBlockExtents: theContextsStartpcsToBlockExtents) at: index ifAbsent: [aContext errorSubscriptBounds: index]. ^self privateDereference: nameRefPair last in: aContext! ! !DebuggerMethodMapForClosureCompiledMethods methodsFor: 'private' stamp: 'eem 7/6/2009 10:14'! privateTempRefsForContext: aContext startpcsToBlockExtents: theContextsStartpcsToBlockExtents "Answer the sequence of temps in scope in aContext in the natural order, outermost arguments and temporaries first, innermost last. Each temp is a pair of the temp's name followed by a reference. The reference can be integer - index of temp in aContext #( indirectionVectorIndex tempIndex ) - remote temp in indirectionVector at index in aContext #( outer. temp reference ) - a temp reference in an outer context." blockExtentsToTempRefs ifNil: [blockExtentsToTempRefs := (aContext method holdsTempNames ifTrue: [aContext method] ifFalse: [methodNode]) blockExtentsToTempsMap. startpcsToTempRefs := Dictionary new]. ^startpcsToTempRefs at: aContext startpc ifAbsentPut: [| localRefs | localRefs := blockExtentsToTempRefs at: (theContextsStartpcsToBlockExtents at: aContext startpc). aContext outerContext ifNil: [localRefs] ifNotNil: [:outer| | outerTemps | "Present temps in the order outermost to innermost left-to-right, but replace copied outermost temps with their innermost copies" outerTemps := (self privateTempRefsForContext: outer startpcsToBlockExtents: theContextsStartpcsToBlockExtents) collect: [:outerPair| localRefs detect: [:localPair| outerPair first = localPair first] ifNone: [{ outerPair first. { #outer. outerPair last } }]]. outerTemps, (localRefs reject: [:localPair| outerTemps anySatisfy: [:outerPair| localPair first = outerPair first]])]]! ! TestCase subclass: #DebuggerUnwindBug instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Tools'! !DebuggerUnwindBug methodsFor: 'as yet unclassified' stamp: 'al 7/14/2008 18:15'! expectedFailures "See thread http://lists.squeakfoundation.org/pipermail/squeak-dev/2008-June/129360.html" ^ #(testUnwindDebuggerWithStep)! ! !DebuggerUnwindBug methodsFor: 'as yet unclassified' stamp: 'ar 3/7/2003 01:38'! testUnwindBlock "test if unwind blocks work properly" | sema process | sema := Semaphore forMutualExclusion. self assert: sema isSignaled. "deadlock on the semaphore" process := [sema critical:[sema wait]] forkAt: Processor userInterruptPriority. self deny: sema isSignaled. "terminate process" process terminate. self assert: sema isSignaled. ! ! !DebuggerUnwindBug methodsFor: 'as yet unclassified' stamp: 'ar 3/7/2003 01:41'! testUnwindDebugger "test if unwind blocks work properly when a debugger is closed" | sema process debugger top | sema := Semaphore forMutualExclusion. self assert: sema isSignaled. process := [sema critical:[sema wait]] forkAt: Processor userInterruptPriority. self deny: sema isSignaled. "everything set up here - open a debug notifier" debugger := Debugger openInterrupt: 'test' onProcess: process. "get into the debugger" debugger debug. top := debugger topView. "set top context" debugger toggleContextStackIndex: 1. "close debugger" top delete. "and see if unwind protection worked" self assert: sema isSignaled.! ! !DebuggerUnwindBug methodsFor: 'as yet unclassified' stamp: 'stephane.ducasse 5/25/2008 18:53'! testUnwindDebuggerWithStep "test if unwind blocks work properly when a debugger is closed" "self debug:#testUnwindDebuggerWithStep" | sema process debugger top | sema := Semaphore forMutualExclusion. self assert: sema isSignaled. process := [sema critical:[sema wait]] forkAt: Processor userInterruptPriority. self deny: sema isSignaled. "everything set up here - open a debug notifier" debugger := Debugger openInterrupt: 'test' onProcess: process. "get into the debugger" debugger debug. top := debugger topView. "set top context" debugger toggleContextStackIndex: 1. "do single step" debugger doStep. "close debugger" top delete. "and see if unwind protection worked" self assert: sema isSignaled.! ! InstructionStream subclass: #Decompiler instanceVariableNames: 'constructor method instVars tempVars constTable stack statements lastPc exit caseExits lastJumpPc lastReturnPc limit hasValue blockStackBase numLocalTemps blockStartsToTempVars tempVarCount' classVariableNames: 'ArgumentFlag CascadeFlag CaseFlag IfNilFlag' poolDictionaries: '' category: 'Compiler-Kernel'! !Decompiler commentStamp: '' prior: 0! I decompile a method in three phases: Reverser: postfix byte codes -> prefix symbolic codes (nodes and atoms) Parser: prefix symbolic codes -> node tree (same as the compiler) Printer: node tree -> text (done by the nodes) instance vars: constructor method instVars tempVars constTable stack statements lastPc exit caseExits - stack of exit addresses that have been seen in the branches of caseOf:'s lastJumpPc lastReturnPc limit hasValue blockStackBase numLocaltemps - number of temps local to a block; also a flag indicating decompiling a block! !Decompiler methodsFor: 'control' stamp: 'tao 8/20/97 22:51'! blockForCaseTo: end "Decompile a range of code as in statementsForCaseTo:, but return a block node." | exprs block oldBase | oldBase := blockStackBase. blockStackBase := stack size. exprs := self statementsForCaseTo: end. block := constructor codeBlock: exprs returns: lastReturnPc = lastPc. blockStackBase := oldBase. lastReturnPc := -1. "So as not to mislead outer calls" ^block! ! !Decompiler methodsFor: 'control'! blockTo: end "Decompile a range of code as in statementsTo:, but return a block node." | exprs block oldBase | oldBase := blockStackBase. blockStackBase := stack size. exprs := self statementsTo: end. block := constructor codeBlock: exprs returns: lastReturnPc = lastPc. blockStackBase := oldBase. lastReturnPc := -1. "So as not to mislead outer calls" ^block! ! !Decompiler methodsFor: 'control' stamp: 'eem 5/29/2008 13:16'! checkForBlock: receiver selector: selector arguments: arguments selector == #blockCopy: ifTrue: [^self checkForBlockCopy: receiver]. self assert: selector == #closureCopy:copiedValues:. ^self checkForClosureCopy: receiver arguments: arguments! ! !Decompiler methodsFor: 'control' stamp: 'eem 7/29/2008 17:42'! checkForBlockCopy: receiver "We just saw a blockCopy: message. Check for a following block." | savePc jump args argPos block | receiver == constructor codeThisContext ifFalse: [^false]. savePc := pc. (jump := self interpretJump) ifNil: [pc := savePc. ^false]. self sawBlueBookBlock. "Definitely a block" jump := jump + pc. argPos := statements size. [self willStorePop] whileTrue: [stack addLast: ArgumentFlag. "Flag for doStore:" self interpretNextInstructionFor: self]. args := Array new: statements size - argPos. 1 to: args size do: "Retrieve args" [:i | args at: i put: statements removeLast. (args at: i) scope: -1 "flag args as block temps"]. block := self blockTo: jump. stack addLast: (constructor codeArguments: args block: block). ^true! ! !Decompiler methodsFor: 'control' stamp: 'eem 5/29/2008 17:02'! checkForClosureCopy: receiver arguments: arguments "We just saw a closureCopy:copiedValues: message. Check for and construct a following block." | savePc jump | receiver == constructor codeThisContext ifFalse: [^false]. savePc := pc. (jump := self interpretJump) notNil ifFalse: [pc := savePc. ^nil]. "Definitely a block" self doClosureCopyCopiedValues: arguments last "" elements numArgs: arguments first key blockSize: jump. ^true! ! !Decompiler methodsFor: 'control' stamp: 'eem 7/1/2009 14:37'! doClosureCopyCopiedValues: blockCopiedValues numArgs: numArgs blockSize: blockSize | savedTemps savedTempVarCount savedNumLocalTemps jump blockArgs blockTemps blockTempsOffset block | savedTemps := tempVars. savedTempVarCount := tempVarCount. savedNumLocalTemps := numLocalTemps. jump := blockSize + pc. numLocalTemps := BlockLocalTempCounter tempCountForBlockAt: pc - 4 in: method. blockTempsOffset := numArgs + blockCopiedValues size. (blockStartsToTempVars notNil "implies we were intialized with temp names." and: [blockStartsToTempVars includesKey: pc]) ifTrue: [tempVars := blockStartsToTempVars at: pc] ifFalse: [blockArgs := (1 to: numArgs) collect: [:i| (constructor codeTemp: i - 1 named: 't', (tempVarCount + i) printString) beBlockArg]. blockTemps := (1 to: numLocalTemps) collect: [:i| constructor codeTemp: i + blockTempsOffset - 1 named: 't', (tempVarCount + i + numArgs) printString]. tempVars := blockArgs, blockCopiedValues, blockTemps]. numLocalTemps timesRepeat: [self interpretNextInstructionFor: self. stack removeLast]. tempVarCount := tempVarCount + numArgs + numLocalTemps. block := self blockTo: jump. stack addLast: (constructor codeArguments: (tempVars copyFrom: 1 to: numArgs) temps: (tempVars copyFrom: blockTempsOffset + 1 to: blockTempsOffset + numLocalTemps) block: block). tempVars := savedTemps. tempVarCount := savedTempVarCount. numLocalTemps := savedNumLocalTemps! ! !Decompiler methodsFor: 'control' stamp: 'ls 1/28/2004 13:29'! statementsForCaseTo: end "Decompile the method from pc up to end and return an array of expressions. If at run time this block will leave a value on the stack, set hasValue to true. If the block ends with a jump or return, set exit to the destination of the jump, or the end of the method; otherwise, set exit = end. Leave pc = end. Note that stack initially contains a CaseFlag which will be removed by a subsequent Pop instruction, so adjust the StackPos accordingly." | blockPos stackPos | blockPos := statements size. stackPos := stack size - 1. "Adjust for CaseFlag" [pc < end] whileTrue: [lastPc := pc. limit := end. "for performs" self interpretNextInstructionFor: self]. "If there is an additional item on the stack, it will be the value of this block." (hasValue := stack size > stackPos) ifTrue: [stack last == CaseFlag ifFalse: [ statements addLast: stack removeLast] ]. lastJumpPc = lastPc ifFalse: [exit := pc]. caseExits add: exit. ^self popTo: blockPos! ! !Decompiler methodsFor: 'control'! statementsTo: end "Decompile the method from pc up to end and return an array of expressions. If at run time this block will leave a value on the stack, set hasValue to true. If the block ends with a jump or return, set exit to the destination of the jump, or the end of the method; otherwise, set exit = end. Leave pc = end." | blockPos stackPos t | blockPos := statements size. stackPos := stack size. [pc < end] whileTrue: [lastPc := pc. limit := end. "for performs" self interpretNextInstructionFor: self]. "If there is an additional item on the stack, it will be the value of this block." (hasValue := stack size > stackPos) ifTrue: [statements addLast: stack removeLast]. lastJumpPc = lastPc ifFalse: [exit := pc]. ^self popTo: blockPos! ! !Decompiler methodsFor: 'initialize-release' stamp: 'eem 7/1/2009 14:45'! initSymbols: aClass constructor method: method class: aClass literals: method literals. constTable := constructor codeConstants. instVars := Array new: aClass instSize. tempVarCount := method numTemps. "(tempVars isNil and: [method holdsTempNames]) ifTrue: [tempVars := method tempNamesString]." tempVars isString ifTrue: [blockStartsToTempVars := self mapFromBlockStartsIn: method toTempVarsFrom: tempVars constructor: constructor. tempVars := blockStartsToTempVars at: method initialPC] ifFalse: [| namedTemps | namedTemps := tempVars ifNil: [(1 to: tempVarCount) collect: [:i| 't', i printString]]. tempVars := (1 to: tempVarCount) collect: [:i | i <= namedTemps size ifTrue: [constructor codeTemp: i - 1 named: (namedTemps at: i)] ifFalse: [constructor codeTemp: i - 1]]]. 1 to: method numArgs do: [:i| (tempVars at: i) beMethodArg]! ! !Decompiler methodsFor: 'initialize-release' stamp: 'eem 6/30/2009 18:13'! mapFromBlockStartsIn: aMethod toTempVarsFrom: schematicTempNamesString constructor: aDecompilerConstructor | map | map := aMethod mapFromBlockKeys: aMethod startpcsToBlockExtents keys asSortedCollection toSchematicTemps: schematicTempNamesString. map keysAndValuesDo: [:startpc :tempNameTupleVector| tempNameTupleVector isEmpty ifFalse: [| subMap numTemps tempVector | subMap := Dictionary new. "Find how many temp slots there are (direct & indirect temp vectors) and for each indirect temp vector find how big it is." tempNameTupleVector do: [:tuple| tuple last isArray ifTrue: [subMap at: tuple last first put: tuple last last. numTemps := tuple last first] ifFalse: [numTemps := tuple last]]. "create the temp vector for this scope level." tempVector := Array new: numTemps. "fill it in with any indirect temp vectors" subMap keysAndValuesDo: [:index :size| tempVector at: index put: (Array new: size)]. "fill it in with temp nodes." tempNameTupleVector do: [:tuple| | itv | tuple last isArray ifTrue: [itv := tempVector at: tuple last first. itv at: tuple last last put: (aDecompilerConstructor codeTemp: tuple last last - 1 named: tuple first)] ifFalse: [tempVector at: tuple last put: (aDecompilerConstructor codeTemp: tuple last - 1 named: tuple first)]]. "replace any indirect temp vectors with proper RemoteTempVectorNodes" subMap keysAndValuesDo: [:index :size| tempVector at: index put: (aDecompilerConstructor codeRemoteTemp: index remoteTemps: (tempVector at: index))]. "and update the entry in the map" map at: startpc put: tempVector]]. ^map! ! !Decompiler methodsFor: 'initialize-release' stamp: 'eem 6/29/2009 09:41'! withTempNames: tempNames "" "Optionally initialize the temp names to be used when decompiling. For backward-copmpatibility, if tempNames is an Array it is a single vector of temp names, probably for a blue-book-compiled method. If tempNames is a string it is a schematic string that encodes the layout of temp vars in the method and any closures/blocks within it. Decoding encoded tempNames is done in decompile:in:method:using: which has the method from which to derive blockStarts. See e.g. BytecodeEncoder>>schematicTempNamesString for syntax." tempVars := tempNames! ! !Decompiler methodsFor: 'instruction decoding'! blockReturnTop "No action needed"! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'PeterHugossonMiller 9/2/2009 16:08'! case: dist "statements = keyStmts CascadeFlag keyValueBlock ... keyStmts" | nextCase thenJump stmtStream elements b node cases otherBlock myExits | nextCase := pc + dist. "Now add CascadeFlag & keyValueBlock to statements" statements addLast: stack removeLast. stack addLast: CaseFlag. "set for next pop" statements addLast: (self blockForCaseTo: nextCase). stack last == CaseFlag ifTrue: "Last case" ["ensure jump is within block (in case thenExpr returns wierdly I guess)" stack removeLast. "get rid of CaseFlag" stmtStream := (self popTo: stack removeLast) readStream. elements := OrderedCollection new. b := OrderedCollection new. [stmtStream atEnd] whileFalse: [(node := stmtStream next) == CascadeFlag ifTrue: [elements addLast: (constructor codeMessage: (constructor codeBlock: b returns: false) selector: (constructor codeSelector: #-> code: #macro) arguments: (Array with: stmtStream next)). b := OrderedCollection new] ifFalse: [b addLast: node]]. b size > 0 ifTrue: [self error: 'Bad cases']. cases := constructor codeBrace: elements. "try find the end of the case" myExits := caseExits removeLast: elements size. myExits := myExits reject: [ :e | e isNil or: [ e < 0 or: [ e > method endPC ] ] ]. thenJump := myExits isEmpty ifTrue: [ nextCase ] ifFalse: [ myExits max ]. otherBlock := self blockTo: thenJump. stack addLast: (constructor codeMessage: stack removeLast selector: (constructor codeSelector: #caseOf:otherwise: code: #macro) arguments: (Array with: cases with: otherBlock))].! ! !Decompiler methodsFor: 'instruction decoding'! doDup stack last == CascadeFlag ifFalse: ["Save position and mark cascade" stack addLast: statements size. stack addLast: CascadeFlag]. stack addLast: CascadeFlag! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'di 2/5/2000 09:34'! doPop stack isEmpty ifTrue: ["Ignore pop in first leg of ifNil for value" ^ self]. stack last == CaseFlag ifTrue: [stack removeLast] ifFalse: [statements addLast: stack removeLast].! ! !Decompiler methodsFor: 'instruction decoding'! doStore: stackOrBlock "Only called internally, not from InstructionStream. StackOrBlock is stack for store, statements for storePop." | var expr | var := stack removeLast. expr := stack removeLast. stackOrBlock addLast: (expr == ArgumentFlag ifTrue: [var] ifFalse: [constructor codeAssignTo: var value: expr])! ! !Decompiler methodsFor: 'instruction decoding'! jump: dist exit := pc + dist. lastJumpPc := lastPc! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 7/1/2009 10:35'! jump: dist if: condition | savePc sign elsePc elseStart end cond ifExpr thenBlock elseBlock thenJump elseJump condHasValue isIfNil saveStack blockBody | stack last == CascadeFlag ifTrue: [^ self case: dist]. elsePc := lastPc. elseStart := pc + dist. end := limit. "Check for bfp-jmp to invert condition. Don't be fooled by a loop with a null body." sign := condition. savePc := pc. self interpretJump ifNotNil: [:elseDist| (elseDist >= 0 and: [elseStart = pc]) ifTrue: [sign := sign not. elseStart := pc + elseDist]]. pc := savePc. ifExpr := stack removeLast. (isIfNil := stack size > 0 and: [stack last == IfNilFlag]) ifTrue: [stack removeLast]. saveStack := stack. stack := OrderedCollection new. thenBlock := self blockTo: elseStart. condHasValue := hasValue or: [isIfNil]. "ensure jump is within block (in case thenExpr returns)" thenJump := exit <= end ifTrue: [exit] ifFalse: [elseStart]. "if jump goes back, then it's a loop" thenJump < elseStart ifTrue: ["Must be a while loop... thenJump will jump to the beginning of the while expr. In the case of while's with a block in the condition, the while expr should include more than just the last expression: find all the statements needed by re-decompiling." stack := saveStack. pc := thenJump. blockBody := self statementsTo: elsePc. "discard unwanted statements from block" blockBody size - 1 timesRepeat: [statements removeLast]. statements addLast: (constructor codeMessage: (constructor codeBlock: blockBody returns: false) selector: (constructor codeSelector: (sign ifTrue: [#whileFalse:] ifFalse: [#whileTrue:]) code: #macro) arguments: { thenBlock }). pc := elseStart. self convertToDoLoop] ifFalse: ["Must be a conditional..." elseBlock := self blockTo: thenJump. elseJump := exit. "if elseJump is backwards, it is not part of the elseExpr" elseJump < elsePc ifTrue: [pc := lastPc]. cond := isIfNil ifTrue: [constructor codeMessage: ifExpr ifNilReceiver selector: (constructor codeSelector: (sign ifTrue: [#ifNotNil:] ifFalse: [#ifNil:]) code: #macro) arguments: (Array with: thenBlock)] ifFalse: [constructor codeMessage: ifExpr selector: (constructor codeSelector: #ifTrue:ifFalse: code: #macro) arguments: (sign ifTrue: [{elseBlock. thenBlock}] ifFalse: [{thenBlock. elseBlock}])]. stack := saveStack. condHasValue ifTrue: [stack addLast: cond] ifFalse: [statements addLast: cond]]! ! !Decompiler methodsFor: 'instruction decoding'! methodReturnConstant: value self pushConstant: value; methodReturnTop! ! !Decompiler methodsFor: 'instruction decoding'! methodReturnReceiver self pushReceiver; methodReturnTop! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 9/26/2008 15:43'! methodReturnTop | last | last := stack removeLast "test test" asReturnNode. stack size > blockStackBase "get effect of elided pop before return" ifTrue: [statements addLast: stack removeLast]. exit := pc. lastJumpPc := lastReturnPc := lastPc. statements addLast: last! ! !Decompiler methodsFor: 'instruction decoding'! popIntoLiteralVariable: value self pushLiteralVariable: value; doStore: statements! ! !Decompiler methodsFor: 'instruction decoding'! popIntoReceiverVariable: offset self pushReceiverVariable: offset; doStore: statements! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 6/4/2008 14:44'! popIntoRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex self sawClosureBytecode. self pushRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex; doStore: statements! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 8/4/2009 11:43'! popIntoTemporaryVariable: offset | maybeTVTag tempVector start | maybeTVTag := stack last. ((maybeTVTag isMemberOf: Association) and: [maybeTVTag key == #pushNewArray]) ifTrue: [blockStartsToTempVars notNil "implies we were intialized with temp names." ifTrue: "Use the provided temps" [self assert: ((tempVector := tempVars at: offset + 1 ifAbsent: [ParseNode basicNew]) isTemp and: [tempVector isIndirectTempVector and: [tempVector remoteTemps size = maybeTVTag value size]])] ifFalse: "Synthesize some remote temps" [tempVector := maybeTVTag value. offset + 1 <= tempVars size ifTrue: [start := 2. tempVector at: 1 put: (tempVars at: offset + 1)] ifFalse: [tempVars := (Array new: offset + 1) replaceFrom: 1 to: tempVars size with: tempVars. start := 1]. start to: tempVector size do: [:i| tempVector at: i put: (constructor codeTemp: numLocalTemps + offset + i - 1 named: 't', (tempVarCount + i) printString)]. tempVars at: offset + 1 put: (constructor codeRemoteTemp: offset + 1 remoteTemps: tempVector)]. tempVarCount := tempVarCount + maybeTVTag value size. stack removeLast. ^self]. self pushTemporaryVariable: offset; doStore: statements! ! !Decompiler methodsFor: 'instruction decoding'! pushActiveContext stack addLast: constructor codeThisContext! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 9/5/2008 14:27'! pushClosureCopyNumCopiedValues: numCopied numArgs: numArgs blockSize: blockSize | copiedValues | self sawClosureBytecode. numCopied > 0 ifTrue: [copiedValues := Array new: numCopied. numLocalTemps == #decompileBlock: ifTrue: "Hack fake temps for copied values" [1 to: numCopied do: [:i| stack addLast: (constructor codeTemp: i - 1)]]. numCopied to: 1 by: -1 do: [:i| copiedValues at: i put: stack removeLast]] ifFalse: [copiedValues := #()]. self doClosureCopyCopiedValues: copiedValues numArgs: numArgs blockSize: blockSize! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 6/4/2008 14:44'! pushConsArrayWithElements: numElements | array | self sawClosureBytecode. array := Array new: numElements. numElements to: 1 by: -1 do: [:i| array at: i put: stack removeLast]. stack addLast: (constructor codeBrace: array)! ! !Decompiler methodsFor: 'instruction decoding'! pushConstant: value | node | node := value == true ifTrue: [constTable at: 2] ifFalse: [value == false ifTrue: [constTable at: 3] ifFalse: [value == nil ifTrue: [constTable at: 4] ifFalse: [constructor codeAnyLiteral: value]]]. stack addLast: node! ! !Decompiler methodsFor: 'instruction decoding'! pushLiteralVariable: assoc stack addLast: (constructor codeAnyLitInd: assoc)! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 6/4/2008 14:45'! pushNewArrayOfSize: size self sawClosureBytecode. stack addLast: #pushNewArray -> (Array new: size)! ! !Decompiler methodsFor: 'instruction decoding'! pushReceiver stack addLast: (constTable at: 1)! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'nk 2/20/2004 11:56'! pushReceiverVariable: offset | var | (var := instVars at: offset + 1 ifAbsent: []) == nil ifTrue: ["Not set up yet" var := constructor codeInst: offset. instVars size < (offset + 1) ifTrue: [ instVars := (Array new: offset + 1) replaceFrom: 1 to: instVars size with: instVars; yourself ]. instVars at: offset + 1 put: var]. stack addLast: var! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 9/25/2008 09:48'! pushRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex self sawClosureBytecode. stack addLast: ((tempVars at: tempVectorIndex + 1) remoteTemps at: remoteTempIndex + 1)! ! !Decompiler methodsFor: 'instruction decoding'! pushTemporaryVariable: offset stack addLast: (tempVars at: offset + 1)! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 9/29/2008 19:23'! send: selector super: superFlag numArgs: numArgs | args rcvr selNode msgNode messages | args := Array new: numArgs. (numArgs to: 1 by: -1) do: [:i | args at: i put: stack removeLast]. rcvr := stack removeLast. superFlag ifTrue: [rcvr := constructor codeSuper]. ((#(blockCopy: closureCopy:copiedValues:) includes: selector) and: [self checkForBlock: rcvr selector: selector arguments: args]) ifFalse: [selNode := constructor codeAnySelector: selector. rcvr == CascadeFlag ifTrue: ["May actually be a cascade or an ifNil: for value." self willJumpIfFalse ifTrue: "= generated by a case macro" [selector == #= ifTrue: [" = signals a case statement..." statements addLast: args first. stack addLast: rcvr. "restore CascadeFlag" ^ self]. selector == #== ifTrue: [" == signals an ifNil: for value..." stack removeLast; removeLast. rcvr := stack removeLast. stack addLast: IfNilFlag; addLast: (constructor codeMessage: rcvr selector: selNode arguments: args). ^ self]] ifFalse: [(self willJumpIfTrue and: [selector == #==]) ifTrue: [" == signals an ifNotNil: for value..." stack removeLast; removeLast. rcvr := stack removeLast. stack addLast: IfNilFlag; addLast: (constructor codeMessage: rcvr selector: selNode arguments: args). ^ self]]. msgNode := constructor codeCascadedMessage: selNode arguments: args. stack last == CascadeFlag ifFalse: ["Last message of a cascade" statements addLast: msgNode. messages := self popTo: stack removeLast. "Depth saved by first dup" msgNode := constructor codeCascade: stack removeLast messages: messages]] ifFalse: [msgNode := constructor codeMessage: rcvr selector: selNode arguments: args]. stack addLast: msgNode]! ! !Decompiler methodsFor: 'instruction decoding'! storeIntoLiteralVariable: assoc self pushLiteralVariable: assoc; doStore: stack! ! !Decompiler methodsFor: 'instruction decoding'! storeIntoReceiverVariable: offset self pushReceiverVariable: offset; doStore: stack! ! !Decompiler methodsFor: 'instruction decoding' stamp: 'eem 6/4/2008 14:45'! storeIntoRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex self sawClosureBytecode. self pushRemoteTemp: remoteTempIndex inVectorAt: tempVectorIndex; doStore: stack! ! !Decompiler methodsFor: 'instruction decoding'! storeIntoTemporaryVariable: offset self pushTemporaryVariable: offset; doStore: stack! ! !Decompiler methodsFor: 'public access'! decompile: aSelector in: aClass "See Decompiler|decompile:in:method:. The method is found by looking up the message, aSelector, in the method dictionary of the class, aClass." ^self decompile: aSelector in: aClass method: (aClass compiledMethodAt: aSelector)! ! !Decompiler methodsFor: 'public access' stamp: 'eem 10/20/2008 14:09'! decompile: aSelector in: aClass method: aMethod "Answer a MethodNode that is the root of the parse tree for the argument, aMethod, which is the CompiledMethod associated with the message, aSelector. Variables are determined with respect to the argument, aClass." ^self decompile: aSelector in: aClass method: aMethod using: (self constructorForMethod: aMethod)! ! !Decompiler methodsFor: 'public access' stamp: 'eem 7/1/2009 14:45'! decompile: aSelector in: aClass method: aMethod using: aConstructor | block node | constructor := aConstructor. method := aMethod. self initSymbols: aClass. "create symbol tables" method isQuick ifTrue: [block := self quickMethod] ifFalse: [stack := OrderedCollection new: method frameSize. caseExits := OrderedCollection new. statements := OrderedCollection new: 20. numLocalTemps := 0. super method: method pc: method initialPC. "skip primitive error code store if necessary" (method primitive ~= 0 and: [self willStore]) ifTrue: [pc := pc + 2. tempVars := tempVars asOrderedCollection]. block := self blockTo: method endPC + 1. stack isEmpty ifFalse: [self error: 'stack not empty']]. node := constructor codeMethod: aSelector block: block tempVars: tempVars primitive: method primitive class: aClass. method primitive > 0 ifTrue: [node removeAndRenameLastTempIfErrorCode]. ^node! ! !Decompiler methodsFor: 'public access' stamp: 'AdrianLienhard 10/11/2009 19:18'! decompileBlock: aBlock "Decompile aBlock, returning the result as a BlockNode. Show temp names from source if available." "Decompiler new decompileBlock: [3 + 4]" | startpc end homeClass blockNode methodNode home source | (home := aBlock home) ifNil: [^ nil]. method := home method. (homeClass := home methodClass) ifNil: [^ nil]. constructor := self constructorForMethod: aBlock method. method fileIndex ~~ 0 ifTrue: "got any source code?" [source := [method getSourceFromFile] on: Error do: [:ex | ^ nil]. methodNode := [homeClass compilerClass new parse: source in: homeClass notifying: nil] on: (Smalltalk classNamed: 'SyntaxErrorNotification') do: [:ex | ^ nil]. self withTempNames: methodNode schematicTempNamesString]. self initSymbols: homeClass. startpc := aBlock startpc. end := aBlock isClosure ifTrue: [(method at: startpc - 2) * 256 + (method at: startpc - 1) + startpc - 1] ifFalse: [(method at: startpc - 2) \\ 16 - 4 * 256 + (method at: startpc - 1) + startpc - 1]. stack := OrderedCollection new: method frameSize. caseExits := OrderedCollection new. statements := OrderedCollection new: 20. super method: method pc: (aBlock isClosure ifTrue: [startpc - 4] ifFalse: [startpc - 5]). aBlock isClosure ifTrue: [numLocalTemps := #decompileBlock: "Get pushClosureCopy... to hack fake temps for copied values"]. blockNode := self blockTo: end. stack isEmpty ifFalse: [self error: 'stack not empty']. ^blockNode statements first! ! !Decompiler methodsFor: 'public access'! tempAt: offset "Needed by BraceConstructor 1]] ifFalse: [extension := 64 + offset. [:instr | (instr = 128 and: [scanner followingByte = extension]) ifTrue: [nRefs := nRefs + 1]. nRefs > 1]]. self scanBlockScopeFor: pc from: method initialPC to: method endPC with: scan scanner: scanner. ^nRefs = 1! ! !Decompiler methodsFor: 'private' stamp: 'eem 10/20/2008 15:49'! constructorForMethod: aMethod ^(aMethod isBlueBookCompiled ifTrue: [DecompilerConstructor] ifFalse: [DecompilerConstructorForClosures]) new! ! !Decompiler methodsFor: 'private' stamp: 'eem 9/5/2008 18:41'! convertToDoLoop "If statements contains the pattern var := startExpr. [var <= limit] whileTrue: [...statements... var := var + incConst] then replace this by startExpr to: limit by: incConst do: [:var | ...statements...]" | initStmt toDoStmt limitStmt | statements size < 2 ifTrue: [^ self]. initStmt := statements at: statements size-1. (toDoStmt := statements last toDoFromWhileWithInit: initStmt) == nil ifTrue: [^ self]. initStmt variable scope: -1. "Flag arg as block temp" statements removeLast; removeLast; addLast: toDoStmt. "Attempt further conversion of the pattern limitVar := limitExpr. startExpr to: limitVar by: incConst do: [:var | ...statements...] to startExpr to: limitExpr by: incConst do: [:var | ...statements...]" statements size < 2 ifTrue: [^ self]. limitStmt := statements at: statements size-1. ((limitStmt isMemberOf: AssignmentNode) and: [limitStmt variable isTemp and: [limitStmt variable == toDoStmt arguments first and: [self blockScopeRefersOnlyOnceToTemp: limitStmt variable fieldOffset]]]) ifFalse: [^ self]. toDoStmt arguments at: 1 put: limitStmt value. limitStmt variable scope: -2. "Flag limit var so it won't print" statements removeLast; removeLast; addLast: toDoStmt. ! ! !Decompiler methodsFor: 'private' stamp: 'eem 5/13/2008 15:41'! interpretNextInstructionFor: client | code varNames | "Change false here will trace all state in Transcript." true ifTrue: [^ super interpretNextInstructionFor: client]. varNames := self class allInstVarNames. code := (self method at: pc) radix: 16. Transcript cr; cr; print: pc; space; nextPutAll: '<' , (code copyFrom: 4 to: code size), '>'. 8 to: varNames size do: [:i | i <= 10 ifTrue: [Transcript cr] ifFalse: [Transcript space; space]. Transcript nextPutAll: (varNames at: i); nextPutAll: ': '; print: (self instVarAt: i)]. Transcript endEntry. ^ super interpretNextInstructionFor: client! ! !Decompiler methodsFor: 'private' stamp: 'di 2/6/2000 10:55'! methodRefersOnlyOnceToTemp: offset | nRefs byteCode extension scanner | nRefs := 0. offset <= 15 ifTrue: [byteCode := 16 + offset. (InstructionStream on: method) scanFor: [:instr | instr = byteCode ifTrue: [nRefs := nRefs + 1]. nRefs > 1]] ifFalse: [extension := 64 + offset. scanner := InstructionStream on: method. scanner scanFor: [:instr | (instr = 128 and: [scanner followingByte = extension]) ifTrue: [nRefs := nRefs + 1]. nRefs > 1]]. ^ nRefs = 1 ! ! !Decompiler methodsFor: 'private'! popTo: oldPos | t | t := Array new: statements size - oldPos. (t size to: 1 by: -1) do: [:i | t at: i put: statements removeLast]. ^t! ! !Decompiler methodsFor: 'private' stamp: 'di 12/26/1998 21:29'! quickMethod | | method isReturnSpecial ifTrue: [^ constructor codeBlock: (Array with: (constTable at: method primitive - 255)) returns: true]. method isReturnField ifTrue: [^ constructor codeBlock: (Array with: (constructor codeInst: method returnField)) returns: true]. self error: 'improper short method'! ! !Decompiler methodsFor: 'private' stamp: 'eem 7/29/2008 17:41'! sawBlueBookBlock constructor isForClosures ifTrue: [constructor primitiveChangeClassTo: DecompilerConstructor new]! ! !Decompiler methodsFor: 'private' stamp: 'eem 6/4/2008 14:43'! sawClosureBytecode constructor isForClosures ifFalse: [constructor primitiveChangeClassTo: DecompilerConstructorForClosures new]! ! !Decompiler methodsFor: 'private' stamp: 'eem 9/6/2008 09:27'! scanBlockScopeFor: refpc from: startpc to: endpc with: scan scanner: scanner | bsl maybeBlockSize | bsl := BlockStartLocator new. scanner pc: startpc. [scanner pc <= endpc] whileTrue: [refpc = scanner pc ifTrue: [scanner pc: startpc. [scanner pc <= endpc] whileTrue: [(scan value: scanner firstByte) ifTrue: [^endpc]. (maybeBlockSize := scanner interpretNextInstructionFor: bsl) isInteger ifTrue: [scanner pc: scanner pc + maybeBlockSize]]. ^self]. (maybeBlockSize := scanner interpretNextInstructionFor: bsl) isInteger ifTrue: [refpc <= (scanner pc + maybeBlockSize) ifTrue: [^self scanBlockScopeFor: refpc from: scanner pc to: scanner pc + maybeBlockSize with: scan scanner: scanner] ifFalse: [scanner pc: scanner pc + maybeBlockSize]]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Decompiler class instanceVariableNames: ''! !Decompiler class methodsFor: 'initialization' stamp: 'di 1/28/2000 22:21'! initialize CascadeFlag := 'cascade'. "A unique object" CaseFlag := 'case'. "Ditto" ArgumentFlag := 'argument'. "Ditto" IfNilFlag := 'ifNil'. "Ditto" "Decompiler initialize"! ! !Decompiler class methodsFor: 'testing' stamp: 'ls 1/29/2004 23:54'! recompileAllTest "[Decompiler recompileAllTest]" "decompile every method and compile it back; if the decompiler is correct then the system should keep running. :)" | decompiled ast compiled | SystemNavigation default allBehaviorsDo: [ :behavior | Utilities informUser: (behavior printString) during: [ behavior selectors do: [ :sel | decompiled := Decompiler new decompile: sel in: behavior. ast := Compiler new compile: decompiled in: behavior notifying: nil ifFail: [ self error: 'failed' ]. compiled := ast generate: (behavior compiledMethodAt: sel) trailer. behavior addSelector: sel withMethod: compiled. ] ] ]! ! ParseNode subclass: #DecompilerConstructor instanceVariableNames: 'method instVars nArgs literalValues tempVars' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Support'! !DecompilerConstructor commentStamp: '' prior: 0! I construct the node tree for a Decompiler.! !DecompilerConstructor methodsFor: 'constructor'! codeAnyLitInd: association ^VariableNode new name: association key key: association index: 0 type: LdLitIndType! ! !DecompilerConstructor methodsFor: 'constructor'! codeAnyLiteral: value ^LiteralNode new key: value index: 0 type: LdLitType! ! !DecompilerConstructor methodsFor: 'constructor'! codeAnySelector: selector ^SelectorNode new key: selector index: 0 type: SendType! ! !DecompilerConstructor methodsFor: 'constructor'! codeArguments: args block: block ^block arguments: args! ! !DecompilerConstructor methodsFor: 'constructor' stamp: 'eem 5/21/2008 13:28'! codeArguments: args temps: temps block: block block arguments: args; temporaries: temps. ^block! ! !DecompilerConstructor methodsFor: 'constructor'! codeAssignTo: variable value: expression ^AssignmentNode new variable: variable value: expression! ! !DecompilerConstructor methodsFor: 'constructor' stamp: 'sma 3/3/2000 13:34'! codeBlock: statements returns: returns ^ BlockNode statements: statements returns: returns! ! !DecompilerConstructor methodsFor: 'constructor'! codeBrace: elements ^BraceNode new elements: elements! ! !DecompilerConstructor methodsFor: 'constructor' stamp: 'di 11/19/1999 11:06'! codeCascade: receiver messages: messages ^ (BraceNode new matchBraceStreamReceiver: receiver messages: messages) ifNil: [CascadeNode new receiver: receiver messages: messages]! ! !DecompilerConstructor methodsFor: 'constructor'! codeCascadedMessage: selector arguments: arguments ^self codeMessage: nil selector: selector arguments: arguments! ! !DecompilerConstructor methodsFor: 'constructor'! codeConstants "Answer with an array of the objects representing self, true, false, nil, -1, 0, 1, 2." ^(Array with: NodeSelf with: NodeTrue with: NodeFalse with: NodeNil) , ((-1 to: 2) collect: [:i | LiteralNode new key: i code: LdMinus1 + i + 1])! ! !DecompilerConstructor methodsFor: 'constructor' stamp: 'sma 3/3/2000 13:35'! codeEmptyBlock ^ BlockNode withJust: NodeNil! ! !DecompilerConstructor methodsFor: 'constructor' stamp: 'eem 8/21/2008 14:02'! codeInst: index ^InstanceVariableNode new name: (instVars at: index + 1 ifAbsent: ['unknown', index asString]) index: index + 1! ! !DecompilerConstructor methodsFor: 'constructor' stamp: 'sma 2/5/2000 12:37'! codeMessage: receiver selector: selector arguments: arguments | symbol node | symbol := selector key. (node := BraceNode new matchBraceWithReceiver: receiver selector: symbol arguments: arguments) ifNotNil: [^ node]. (node := self decodeIfNilWithReceiver: receiver selector: symbol arguments: arguments) ifNotNil: [^ node]. ^ MessageNode new receiver: receiver selector: selector arguments: arguments precedence: symbol precedence! ! !DecompilerConstructor methodsFor: 'constructor' stamp: 'eem 9/23/2008 22:06'! codeMethod: selector block: block tempVars: vars primitive: primitive class: class | node methodTemps arguments temporaries | node := self codeSelector: selector code: nil. tempVars := vars. methodTemps := tempVars select: [:t | t scope >= 0]. arguments := methodTemps copyFrom: 1 to: nArgs. temporaries := methodTemps copyFrom: nArgs + 1 to: methodTemps size. block arguments: arguments; temporaries: temporaries. ^MethodNode new selector: node arguments: arguments precedence: selector precedence temporaries: temporaries block: block encoder: (Encoder new initScopeAndLiteralTables temps: tempVars literals: literalValues class: class) primitive: primitive! ! !DecompilerConstructor methodsFor: 'constructor'! codeSelector: sel code: code ^SelectorNode new key: sel code: code! ! !DecompilerConstructor methodsFor: 'constructor'! codeSuper ^NodeSuper! ! !DecompilerConstructor methodsFor: 'constructor'! codeTemp: index ^ TempVariableNode new name: 't' , (index + 1) printString index: index type: LdTempType scope: 0! ! !DecompilerConstructor methodsFor: 'constructor'! codeTemp: index named: tempName ^ TempVariableNode new name: tempName index: index type: LdTempType scope: 0! ! !DecompilerConstructor methodsFor: 'constructor'! codeThisContext ^NodeThisContext! ! !DecompilerConstructor methodsFor: 'constructor' stamp: 'di 1/28/2000 21:23'! decodeIfNilWithReceiver: receiver selector: selector arguments: arguments selector == #ifTrue:ifFalse: ifFalse: [^ nil]. (receiver isMessage: #== receiver: nil arguments: [:argNode | argNode == NodeNil]) ifFalse: [^ nil]. ^ (MessageNode new receiver: receiver selector: (SelectorNode new key: #ifTrue:ifFalse: code: #macro) arguments: arguments precedence: 3) noteSpecialSelector: #ifNil:ifNotNil:! ! !DecompilerConstructor methodsFor: 'initialize-release'! method: aMethod class: aClass literals: literals method := aMethod. instVars := aClass allInstVarNames. nArgs := method numArgs. literalValues := literals! ! !DecompilerConstructor methodsFor: 'testing' stamp: 'eem 6/4/2008 14:41'! isForClosures ^false! ! !DecompilerConstructor methodsFor: 'visiting' stamp: 'eem 5/30/2008 09:44'! accept: aVisitor "I am not really a ParseNode. Only here to access constants defined in parseNode." self shouldNotImplement! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DecompilerConstructor class instanceVariableNames: ''! DecompilerConstructor subclass: #DecompilerConstructorForClosures instanceVariableNames: 'tempNameCounter' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Support'! !DecompilerConstructorForClosures methodsFor: 'constructor' stamp: 'eem 6/11/2009 17:04'! codeMethod: selector block: block tempVars: vars primitive: primitive class: class | blockNode selectorNode visibleTemps invisibleTemps arguments temporaries | selectorNode := self codeSelector: selector code: nil. tempVars := vars. visibleTemps := OrderedCollection new. invisibleTemps := OrderedCollection new. tempVars do: [:t| ((t isIndirectTempVector or: [t scope >= 0]) ifTrue: [visibleTemps] ifFalse: [invisibleTemps]) addLast: t]. arguments := visibleTemps copyFrom: 1 to: nArgs. temporaries := visibleTemps copyFrom: nArgs + 1 to: visibleTemps size. block arguments: arguments; temporaries: temporaries. blockNode := BytecodeAgnosticMethodNode new selector: selectorNode arguments: arguments precedence: selector precedence temporaries: temporaries block: block encoder: (EncoderForV3PlusClosures new initScopeAndLiteralTables temps: visibleTemps, invisibleTemps literals: literalValues class: class) primitive: primitive properties: method properties copy. blockNode properties method: blockNode. ^blockNode! ! !DecompilerConstructorForClosures methodsFor: 'constructor' stamp: 'eem 10/20/2008 13:01'! codeRemoteTemp: index remoteTemps: tempVector ^(RemoteTempVectorNode new name: '_r', index printString index: index type: LdTempType scope: 0) remoteTemps: tempVector; yourself! ! !DecompilerConstructorForClosures methodsFor: 'testing' stamp: 'eem 6/4/2008 14:41'! isForClosures ^true! ! DecompilerTests subclass: #DecompilerTestFailuresCollector instanceVariableNames: 'failures' classVariableNames: '' poolDictionaries: '' category: 'Tests-Compiler'! !DecompilerTestFailuresCollector commentStamp: '' prior: 0! (| dtfc | dtfc := DecompilerTestFailuresCollector new. (dtfc class superclass organization listAtCategoryNamed: #tests) do: [:s| dtfc perform: s]. dtfc failures) (Transcript nextPut: ${. self do: [:mr| Transcript print: mr actualClass; nextPut: $.; space; store: mr methodSymbol; nextPut: $.; cr; flush]. Transcript nextPut: $}; flush) eem 7/1/2009 16:13 {AdditionalMethodState. #keysAndValuesDo:. AdditionalMethodState. #propertyKeysAndValuesDo:. AdditionalMethodState. #at:ifAbsent:. AdditionalMethodState. #removeKey:ifAbsent:. AdditionalMethodState. #at:ifAbsentPut:. AdditionalMethodState. #setMethod:. AdditionalMethodState. #at:put:. AdditionalMethodState. #pragmas. AdditionalMethodState. #includesProperty:. AdditionalMethodState. #properties. AdditionalMethodState. #hasLiteralSuchThat:. AdditionalMethodState. #propertyValueAt:ifAbsent:. AdditionalMethodState. #hasLiteralThorough:. Array. #hasLiteralSuchThat:. BitBltSimulation. #initDither8Lookup. BlockNode. #sizeCodeExceptLast:. BlockNode. #emitCodeExceptLast:encoder:. Categorizer. #changeFromCategorySpecs:. Categorizer. #elementCategoryDict. CColorPicker. #colors:. CCustomDrawListCostume. #drawListOn:in:. ChangeList. #browseCurrentVersionsOfSelections. ClosureTests. #testToDoInsideTemp. Cogit. #computeMaximumSizes. Cogit. #outputInstructionsAt:. Cogit. #generateMapAt:start:. CogVMSimulator. #printFrameThing:at:. CogVMSimulator. #str:n:cmp:. CoInterpreter. #validStackPageBaseFrames. CoInterpreter. #markAndTraceTraceLog. CoInterpreter. #mapTraceLog. CoInterpreter. #checkStackIntegrity. CoInterpreter. #mapStackPages. CoInterpreter. #updateStackZoneReferencesToCompiledCodePreCompaction. CoInterpreter. #ceActivateFailingPrimitiveMethod:. CoInterpreterStackPages. #initializeStack:numSlots:pageSize:stackLimitOffset:stackPageHeadroom:. CompiledMethod. #=. CompiledMethod. #getPreambleFrom:at:. CompiledMethod. #hasLiteralThorough:. CompiledMethod. #hasLiteralSuchThat:. CPopUpMenuCostume. #drawMenu:on:in:. CroquetParticipant. #dropFiles:. CTextParagraph. #selectionRectsFrom:to:. CWheelWidgetCostume. #drawOn:in:. Dictionary. #scanFor:. Float. #printPaddedWith:to:. FMSound. #mixSampleCount:into:startingAt:leftVol:rightVol:. Form. #transformColors:. FTPClient. #getDataInto:. GIFReadWriter. #nextImageWithPlugin. GraphMorph. #drawDataOn:. GZipReadStream. #on:from:to:. HTTPServiceDispatcher. #errorReportFor:stack:on:. HttpUrl. #checkAuthorization:retry:. Integer. #benchSwitch:. Interpreter. #primitiveClosureValueWithArgs. Interpreter. #primitivePerformAt:. Interpreter. #primitiveDoPrimitiveWithArgs. Interpreter. #primitiveNewMethod. InterpreterStackPages. #initializeStack:numSlots:pageSize:stackLimitOffset:stackPageHeadroom:. JPEGReadWriter. #decodeBlockInto:component:dcTable:acTable:. KeyedIdentitySet. #scanFor:. KeyedSet. #scanFor:. LargeIntegersPlugin. #isNormalized:. LargeIntegersPlugin. #cBytesCopyFrom:to:len:. LargeIntegersPlugin. #cDigitMultiply:len:with:len:into:. LiteralDictionary. #scanFor:. LoopedSampledSound. #mixSampleCount:into:startingAt:leftVol:rightVol:. MethodDictionary. #scanFor:. MP4BoxInfoParser. #parseMP4BoxOutput:. MP4BoxNHMLTrack. #computeDTSDeltas. MultiByteBinaryOrTextStream. #next:. MultiByteFileStream. #next:. MViewPane. #reconstructEnabledDocuments. MViewPane. #reconstructOpenDocuments. MViewPane. #reconstructSelectionList. NewParagraph. #selectionRectsFrom:to:. Object. #instanceFields. OldSocket. #getResponseNoLF. PasteUpMorph. #dropFiles:. PlotMorphGrid. #bestStep:. PluckedSound. #reset. PluggableDictionary. #scanFor:. PluggableSet. #scanFor:. PluggableTabButtonMorph. #calculateArcLengths. PluggableTabButtonMorph. #drawTabOn:. PNGReadWriter. #copyPixelsGray:. PNMReadWriter. #readPlainRGB. PNMReadWriter. #readBWreverse:. PNMReadWriter. #nextPutRGB:. PNMReadWriter. #nextPutBW:reverse:. PopUpMenu. #readKeyboard. QFloorFan. #initialize. QMinimalForum. #demoDesksUnused. QNetVidReorderingBuffer. #popFramesForCTS:. QNetVidTrackStreamer. #sampleIndexWithCTS:. QServiceProvider. #statusReport. QServicesPane. #forumMenuInto:. QUserListItem. #drawOn:in:. QVMProfiler. #computeHistograms:. QVMProfiler. #selectSymbolsInRange. QwaqParticipantUI. #onDropFiles:. RelativeInstructionPrinter. #print:. RemoteHandMorph. #appendNewDataToReceiveBuffer. SchizophrenicClosureFormatStackInterpreter. #primitiveClosureValueWithArgs. Set. #do:. Set. #scanFor:. SHParserST80. #isBinary. ShootoutMall. #processVisitors. ShortIntegerArray. #writeOn:. SparseLargeArray. #analyzeSpaceSaving. StackInterpreter. #validStackPageBaseFrames. StackInterpreter. #divorceAllFrames. StackInterpreter. #checkStackIntegrity. StackInterpreter. #primitiveDoPrimitiveWithArgs. StackInterpreter. #reverseDisplayFrom:to:. StackInterpreter. #printOop:. StackInterpreter. #mapStackPages. StackInterpreter. #primitiveNewMethod. StackInterpreter. #primitiveClosureValueWithArgs. StrikeFontSet. #displayStringR2L:on:from:to:at:kern:. String. #howManyMatch:. Text. #asHtmlFragmentTextStyle:useBreaks:. TextURL. #actOnClickFor:. TFractalTerrain. #heightAt:. TFractalTerrain. #makeFaces. TFractalTerrain. #makeVertices. TFractalTerrain. #makeTextureUV. TFractalTerrain. #makeVertexNormals. TFrame. #computeUnionSphere. TMethod. #emitCCommentOn:. TRFBStreamOutput. #handleRequest:. TTCFontReader. #processCharacterMappingTable:. TTContourConstruction. #segmentsDo:. TTensor. #projectionIntegrate:. TTFontReader. #processHorizontalMetricsTable:length:. TTFontReader. #processCharacterMappingTable:. TWaves. #step. Vector. #copyFrom:. Vector. #asVector3. VectorColor. #copyFrom:. WeakKeyDictionary. #scanForNil:. WeakKeyDictionary. #scanFor:. WeakSet. #scanFor:. WeakSet. #scanForLoadedSymbol:. }! !DecompilerTestFailuresCollector methodsFor: 'accessing' stamp: 'eem 11/10/2008 15:46'! assert: aBoolean description: aString resumable: resumableBoolean aBoolean ifFalse: [failures isNil ifTrue: [failures := OrderedCollection new]. failures addLast: (thisContext sender tempAt: 1) methodReference]! ! !DecompilerTestFailuresCollector methodsFor: 'accessing' stamp: 'eem 11/10/2008 15:47'! failures ^failures! ! Object subclass: #DecompilerTests instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Compiler'! !DecompilerTests commentStamp: 'AdrianLienhard 10/11/2009 19:11' prior: 0! AdrianLienhard 10/11/2009 19:08: Since many of tests are expected to fail, the super class is temporarily changed to Object so that these tests are not run anymore. Using the expected failures mechanism does not work since the tests depend on the source code loaded in the image and hence may or may not fail depending on what is loaded. Apparently the decompiler does not really work totally. Here are a bunch of methods that can help improving the decompiler: - blockingClasses return class for which it is impossible to decompile methods - failures are problems that lead to a DNU - decompilerDiscrepancies are the results of running decompileTestHelper..as you see the pattern is quite present.! !DecompilerTests methodsFor: 'utilities' stamp: 'sd 9/25/2004 15:30'! blockingClasses ^ #(CompiledMethod)! ! !DecompilerTests methodsFor: 'utilities' stamp: 'eem 6/11/2009 17:24'! checkDecompileMethod: oldMethod | cls selector oldMethodNode methodNode newMethod oldCodeString newCodeString | cls := oldMethod methodClass. selector := oldMethod selector. oldMethodNode := cls decompilerClass new decompile: selector in: cls method: oldMethod. [oldMethodNode properties includesKey: #warning] whileTrue: [oldMethodNode properties removeKey: #warning]. oldCodeString := oldMethodNode decompileString. methodNode := [cls compilerClass new compile: oldCodeString in: cls notifying: nil ifFail: []] on: SyntaxErrorNotification do: [:ex| ex errorMessage = 'Cannot store into' ifTrue: [ex return: #badStore]. ex pass]. "Ignore cannot store into block arg errors; they're not our issue." methodNode ~~ #badStore ifTrue: [newMethod := methodNode generate: #(0 0 0 0). newCodeString := (cls decompilerClass new decompile: selector in: cls method: newMethod) decompileString. "(StringHolder new textContents: (TextDiffBuilder buildDisplayPatchFrom: oldCodeString to: newCodeString)) openLabel: 'Decompilation Differences for ', cls name,'>>',selector" "(StringHolder new textContents: (TextDiffBuilder buildDisplayPatchFrom: oldMethod abstractSymbolic to: newMethod abstractSymbolic)) openLabel: 'Bytecode Differences for ', cls name,'>>',selector" self assert: oldCodeString = newCodeString description: cls name asString, ' ', selector asString resumable: true]! ! !DecompilerTests methodsFor: 'utilities' stamp: 'eem 9/29/2008 15:07'! decompileClassesSelect: aBlock (Smalltalk classNames select: aBlock) do: [:cn | | cls | cls := Smalltalk at: cn. Smalltalk garbageCollect. Transcript cr; show: cn. cls selectors do: [:selector | | methodNode oldMethod newMethod oldCodeString newCodeString | (self isFailure: cls sel: selector) ifFalse: [" to help making progress (self isStoredProblems: cls theNonMetaClass sel: selector meta: cls isMeta) ifFalse: [ " Transcript nextPut: $.; flush. self checkDecompileMethod: (cls compiledMethodAt: selector)]]]! ! !DecompilerTests methodsFor: 'utilities' stamp: 'DamienCassou 10/6/2009 09:37'! decompilerDiscrepancies "classnames, method selector, isMeta" ^ #(#(#AIFFFileReader #readExtendedFloat false) #(#AbstractFont #emphasisStringFor: false) #(#AbstractString #asSmalltalkComment false) #(#AbstractString #compressWithTable: false) #(#AbstractString #howManyMatch: false) #(#Archive #addTree:removingFirstCharacters: false) #(#ArchiveViewer #createButtonBar false) #(#ArchiveViewer #extractAllPossibleInDirectory: false) #(#BMPReadWriter #nextPutImage: false) #(#Bitmap #readCompressedFrom: false) #(#BitmapStreamTests #testOtherClasses false) #(#BlobMorph #mergeSelfWithBlob:atPoint: false) #(#BookMorph #fromRemoteStream: false) #(#BookMorph #saveIndexOfOnly: false) #(#Browser #categorizeAllUncategorizedMethods false) #(#Browser #highlightMessageList:with: false) #(#Categorizer #elementCategoryDict false) #(#ChangeList #selectConflicts: false) #(#ChangeSet #containsMethodAtPosition: false) #(#ChangeSorter #removeContainedInClassCategories false) #(#CodeHolder #getSelectorAndSendQuery:to:with: false) #(#Color #initializeGrayToIndexMap false) #(#ColorForm #maskingMap false) #(#CompiledMethodInspector #fieldList false) #(#ComplexBorder #drawLineFrom:to:on: false) #(#DateAndTime #ticks:offset: false) #(#Dictionary #scanFor: false) #(#DockingBarMorph #example3 false) #(#Envelope #storeOn: false) #(#FFT #transformDataFrom:startingAt: false) #(#FMSound #mixSampleCount:into:startingAt:leftVol:rightVol: false) #(#FTPClient #getDataInto: false) #(#FWT #samples: false) #(#FWT #setAlpha:beta: false) #(#FileList #selectEncoding false) #(#FileList2 #endingSpecs false) #(#FilePackage #conflictsWithUpdatedMethods false) #(#FishEyeMorph #calculateTransform false) #(#FlapsTest #testRegisteredFlapsQuads false) #(#Float #absByteEncode:base: false) #(#Float #absPrintExactlyOn:base: false) #(#Float #absPrintOn:base: false) #(#Float #initialize false) #(#Form #dotOfSize: false) #(#Form #readNativeResourceFrom: false) #(#GIFReadWriter #exampleAnim false) #(#GZipReadStream #on:from:to: false) #(#GraphMorph #drawDataOn: false) #(#HttpUrl #checkAuthorization:retry: false) #(#ImageSegment #verify:matches:knowing: false) #(#Imports #importImageDirectory: false) #(#Integer #digitDiv:neg: false) #(#Integer #take: false) #(#Interval #valuesInclude: false) #(#JPEGHuffmanTable #makeDerivedTables false) #(#JPEGReadWriter #decodeBlockInto:component:dcTable:acTable: false) #(#KeyedIdentitySet #scanFor: false) #(#KeyedSet #scanFor: false) #(#LiteralDictionary #scanFor: false) #(#LoopedSampledSound #mixSampleCount:into:startingAt:leftVol:rightVol: false) #(#MIDIInputParser #processByte: false) #(#MIDIScore #insertEvents:at: false) #(#MPEGMoviePlayerMorph #guessVolumeSlider false) #(#MailMessage #bodyTextFormatted false) #(#MenuIcons #createIconMethodsFromDirectory: false) #(#MenuIcons #decorateMenu: false) #(#MenuMorph #addTitle:icon:updatingSelector:updateTarget: false) #(#MethodDictionary #scanFor: false) #(#MethodFinder #load: false) #(#Morph #addNestedYellowButtonItemsTo:event: false) #(#Morph #addToggleItemsToHaloMenu: false) #(#Morph #duplicateMorphCollection: false) #(#Morph #layoutMenuPropertyString:from: false) #(#Morph #printConstructorOn:indent:nodeDict: false) #(#Morph #privateAddAllMorphs:atIndex: false) #(#Morph #specialNameInModel false) #(#MultiByteBinaryOrTextStream #next: false) #(#MultiByteFileStream #next: false) #(#MultiString #indexOfAscii:inMultiString:startingAt: false) #(#MultiString #findMultiSubstring:in:startingAt:matchTable: false) #(#MultiString #multiStringCompare:with:collated: false) #(#MulticolumnLazyListMorph #setColumnWidthsFor: false) #(#NaturalLanguageTranslator #loadAvailableExternalLocales false) #(#NewParagraph #OLDcomposeLinesFrom:to:delta:into:priorLines:atY: false) #(#NewParagraph #selectionRectsFrom:to: false) #(#Object #copyFrom: false) #(#Object #storeOn: false) #(#ObjectExplorer #step false) #(#ObjectOut #xxxFixup false) #(#OrderedCollection #copyReplaceFrom:to:with: false) #(#PNGReadWriter #copyPixelsGray: false) #(#PNGReadWriter #copyPixelsGrayAlpha: false) #(#PNMReadWriter #nextPutBW:reverse: false) #(#PNMReadWriter #nextPutRGB: false) #(#PNMReadWriter #readBWreverse: false) #(#PNMReadWriter #readPlainRGB false) #(#PRServerDirectory #getPostArgsFromThingsToSearchFor: false) #(#PRServerDirectory #putSmalltalkInfoInto: false) #(#PackageInfo #foreignClasses false) #(#ParagraphEditor #cursorEnd: false) #(#ParagraphEditor #explainDelimitor: false) #(#ParseNode #nodePrintOn:indent: false) #(#ParseTreeRewriter #acceptCascadeNode: false) #(#ParseTreeSearcher #messages false) #(#PartsBin #translatedQuads: false) #(#PasteUpMorph #dropFiles: false) #(#PasteUpMorph #mouseDown: false) #(#PhonemeRecord #prunedAverageFeatures: false) #(#PluckedSound #reset false) #(#PluggableDictionary #scanFor: false) #(#PluggableListMorph #list: false) #(#PluggableMultiColumnListMorph #calculateColumnOffsetsFrom: false) #(#PluggableMultiColumnListMorph #calculateColumnWidthsFrom: false) #(#PluggableMultiColumnListMorph #layoutMorphicLists: false) #(#PluggableSet #scanFor: false) #(#PointerFinder #buildList false) #(#PointerFinder #followObject: false) #(#PolygonMorph #derivs:first:second:third: false) #(#PopUpMenu #readKeyboard false) #(#PostscriptCanvas #convertFontName: false) #(#PostscriptCanvas #fontSampler false) #(#PostscriptCanvas #postscriptFontInfoForFont: false) #(#PostscriptCanvas #postscriptFontMappingSummary false) #(#PostscriptCanvas #drawGeneralBezierShape:color:borderWidth:borderColor: false) #(#PostscriptCanvas #outlineQuadraticBezierShape: false) #(#Preferences #keihanna false) #(#Preferences #printStandardSystemFonts false) #(#Preferences #refreshFontSettings false) #(#Preferences #setDefaultFonts: false) #(#Preferences #smallLand false) #(#ProcessBrowser #dumpTallyOnTranscript: false) #(#ProcessBrowser #processNameList false) #(#ProcessorScheduler #highestPriority: false) #(#ProcessorScheduler #nextReadyProcess false) #(#Project #setFlaps false) #(#ProtoObject #pointsTo: false) #(#RBAssignmentNode #bestNodeFor: false) #(#RBFormatter #formatMessage:cascade: false) #(#RBFormatter #formatStatementCommentFor: false) #(#RBMessageNode #bestNodeFor: false) #(#RBPatternMessageNode #receiver:selectorParts:arguments: false) #(#RBPatternVariableNode #initializePatternVariables false) #(#RBProgramNode #copyList:inContext: false) #(#RBSequenceNode #= false) #(#RBSequenceNode #replaceNode:withNodes: false) #(#RemoteHandMorph #appendNewDataToReceiveBuffer false) #(#RunArray #rangeOf:startingAt: false) #(#SARInstaller #ensurePackageWithId: false) #(#SARInstaller #fileIntoChangeSetNamed:fromStream: false) #(#SARInstaller #memberNameForProjectNamed: false) #(#SMLoader #cachePackageReleaseAndOfferToCopy false) #(#SMLoader #downloadPackageRelease false) #(#SMLoader #installPackageRelease: false) #(#SMSqueakMap #accountForName: false) #(#SMSqueakMap #mapInitialsFromMinnow false) #(#SampledSound #convert8bitSignedFrom:to16Bit: false) #(#ScaledDecimalTest #testConvertFromFloat false) #(#ScrollBar #arrowSamples false) #(#ScrollBar #boxSamples false) #(#ScrollBar #doScrollDown false) #(#ScrollBar #doScrollUp false) #(#ScrollBar #scrollDown: false) #(#ScrollBar #scrollUp: false) #(#SecurityManager #flushSecurityKey: false) #(#SelectionMorph #extendByHand: false) #(#SelectorBrowser #markMatchingClasses false) #(#Set #do: false) #(#Set #scanFor: false) #(#ShortIntegerArray #writeOn: false) #(#SimpleMIDIPort #closeAllPorts false) #(#SmaCCParser #errorHandlerStates false) #(#SmaCCParser #findErrorHandlerIfNoneUseErrorNumber: false) #(#SmalltalkImage #saveImageSegments false) #(#SmartRefStream #uniClassInstVarsRefs: false) #(#SoundBuffer #normalized: false) #(#SparseLargeTable #zapDefaultOnlyEntries false) #(#Spline #derivs:first:second:third: false) #(#StrikeFont #bonk:with: false) #(#StrikeFont #buildfontNamed:fromForms:startingAtAscii:ascent:descent:maxWid: false) #(#StrikeFont #makeItalicGlyphs false) #(#StrikeFont #readFromBitFont: false) #(#StrikeFontSet #bonk:with:at: false) #(#StrikeFontSet #displayStringR2L:on:from:to:at:kern: false) #(#StrikeFontSet #makeItalicGlyphs false) #(#String #indexOfAscii:inString:startingAt: false) #(#StringTest #testAsSmalltalkComment false) #(#SymbolTest #testWithFirstCharacterDownshifted false) #(#SyntaxMorph #rename: false) #(#SystemDictionary #makeSqueaklandReleasePhaseFinalSettings false) #(#SystemDictionary #saveImageSegments false) #(#TTCFont #reorganizeForNewFontArray:name: false) #(#TTCFontReader #processCharacterMappingTable: false) #(#TTContourConstruction #segmentsDo: false) #(#TTFontReader #getGlyphFlagsFrom:size: false) #(#TTFontReader #processCharMap: false) #(#TTFontReader #processCharacterMappingTable: false) #(#TTFontReader #processHorizontalMetricsTable:length: false) #(#TestsForTextAndTextStreams #testExampleRunArray5 false) #(#TestsForTextAndTextStreams #testRangeDetection1 false) #(#TestsForTextAndTextStreams #testRangeDetection2 false) #(#TestsForTextAndTextStreams #testRangeDetection3 false) #(#TestsForTextAndTextStreams #testRangeDetection4 false) #(#Text #initTextConstants false) #(#TextConverter #allEncodingNames false) #(#TextStyle #decodeStyleName: false) #(#TextStyle #fontMenuForStyle:target:selector:highlight: false) #(#TextStyle #modalMVCStyleSelectorWithTitle: false) #(#TextStyle #modalStyleSelectorWithTitle: false) #(#TextURL #actOnClickFor: false) #(#ThreePhaseButtonMorph #initialize false) #(#TickIndicatorMorph #drawOn: false) #(#TimeProfileBrowser #setClassAndSelectorIn: false) #(#UCSTable #initializeGB2312Table false) #(#UCSTable #initializeJISX0208Table false) #(#UCSTable #initializeKSX1001Table false) #(#Utilities #decimalPlacesForFloatPrecision: false) #(#Utilities #floatPrecisionForDecimalPlaces: false) #(#WaveEditor #showEnvelope false) #(#WaveletCodec #decodeFrames:from:at:into:at: false) #(#WaveletCodec #encodeFrames:from:at:into:at: false) #(#WeakKeyDictionary #scanFor: false) #(#WeakKeyDictionary #scanForNil: false) #(#WeakSet #scanFor: false) #(#WeakSet #scanForLoadedSymbol: false) #(#WorldState #displayWorldSafely: false) #(#ZLibWriteStream #updateAdler32:from:to:in: false) #(#ZipConstants #initializeDistanceCodes false) #(#ZipWriteStream #dynamicBlockSizeFor:and:using:and: false) #(#ZipWriteStream #fixedBlockSizeFor:and: false) (SimpleMIDIPort closeAllPorts true) (Float initialize true) (FileList2 endingSpec true) (ProcessBrowser dumpTallyOnTranscript: true) (SARInstaller ensurePackageWithId: true) (SARInstaller fileIntoChangeSetNamed:fromStream: true) (Color initializeGrayToIndexMap true) (GIFReadWriter exampleAnim true) (Text initTextConstants true) (String indexOfAscii:inString:startingAt: true)(MultiString indexOfAscii:inString:startingAt: true) (ZLibWriteStream updateAdler32:from:to:in: true) (SampledSound convert8bitSignedFrom:to16Bit: true) (Form dotOfSize: true) (Preferences setDefaultFonts true)(Preferences refreshFontSettings true) (Preferences keihanna true) (Preferences smallLand true) (Preferences printStandardSystemFonts true) (ThreePhaseButtonMorph initialize true)(ScrollBar arrowSamples true) (ScrollBar boxSamples true) (DockingBarMorph example3)(PartsBin translatedQuads: true)(Utilities decimlaPlacesForFloatPrecision: true) (Utilities floatPrecisionForDecimalPlaces: true) (PostcriptCanvas postscriptFontMappingSummary true) (PostscriptCanvas convertFontName: true) (PostscriptCanvas fontSampler true) (PostScriptCanvas postscriptFontInfoForFont: true) (TextStyle decodeStyleName true) (TestStyle fontMenuForStyle:target:selector:highlight: true) (TextStyle modalMVCStyleSelectorWithTitle: true)(TextStyle modalStyleSelectorWithTitle: true) (AbstractFont emphasisStringFor: true) (TTCFonr reorganizeForNewFontArray:name: true) (ZipConstants initializeDistanceCodes true) (MenuIcons createIconMethodsFromDirectory: true) (MenuIcons decorateMenu: true) (UCSTable initializeJISX0208Table true)(UCSTable initializeBG3212Table true)(UCSTable initializeKSX1001Table true) (TextConverter allEncodingNames true))! ! !DecompilerTests methodsFor: 'utilities' stamp: 'eem 11/10/2008 15:30'! decompilerFailures "here is the list of failures: DNU resulting in trying to decompile the following methods" ^ #((BalloonEngineSimulation circleCosTable "-0.3826834323650903 => -0.38268343236509 or -0.3826834323650902") (BalloonEngineSimulation circleSinTable "-0.3826834323650903 => -0.38268343236509 or -0.3826834323650902") (GeniePlugin primSameClassAbsoluteStrokeDistanceMyPoints:otherPoints:myVectors:otherVectors:mySquaredLengths:otherSquaredLengths:myAngles:otherAngles:maxSizeAndReferenceFlag:rowBase:rowInsertRemove:rowInsertRemoveCount: "Cannot compile -- stack including temps is too deep") (QPickable2D pick:) "foo ifTrue: [^bar] ifFalse: [^baz]. ^huh?" (QUsersPane userEntryCompare:to:) "foo ifTrue: [^bar] ifFalse: [^baz]. ^huh?" (TShaderProgram vertexStrings) "foo ifTrue: []. => foo. => ." (TShaderProgram fragmentStrings) "foo ifTrue: []. => foo. => ." (TWindow zoomWindow:) "foo ifTrue: [^bar] ifFalse: [^baz]. ^huh?" "(PNMReadWriter nextImage) (Collection #ifEmpty:ifNotEmpty:) (Collection #ifEmpty:) (Collection #ifNotEmpty:ifEmpty:) (Text #alignmentAt:ifAbsent:) (ObjectWithDocumentation propertyAt:ifAbsent:)")! ! !DecompilerTests methodsFor: 'utilities' stamp: 'sd 9/25/2004 15:36'! decompilerTestHelper "Decompiles the source for every method in the system, and then compiles that source and verifies that it generates (and decompiles to) identical code. This currently fails in a number of places because some different patterns (esp involving conditionals where the first branch returns) decompile the same. " "self new decompilerTestHelper" | methodNode oldMethod newMethod badOnes oldCodeString n | badOnes := OrderedCollection new. Smalltalk forgetDoIts. 'Decompiling all classes...' displayProgressAt: Sensor cursorPoint from: 0 to: CompiledMethod instanceCount during: [:bar | n := 0. self systemNavigation allBehaviorsDo: [:cls | (self isBlockingClass: cls) ifFalse: [ Smalltalk garbageCollect. Transcript cr; show: cls name. cls selectors do: [:selector | (n := n + 1) \\ 100 = 0 ifTrue: [bar value: n]. (self isFailure: cls sel: selector) ifFalse: [oldMethod := cls compiledMethodAt: selector. oldCodeString := (cls decompilerClass new decompile: selector in: cls method: oldMethod) decompileString. methodNode := cls compilerClass new compile: oldCodeString in: cls notifying: nil ifFail: []. newMethod := methodNode generate: #(0 0 0 0 ). oldCodeString = (cls decompilerClass new decompile: selector in: cls method: newMethod) decompileString ifFalse: [Transcript cr; show: '***' , cls name , ' ' , selector. badOnes add: cls name , ' ' , selector]]]]]]. self systemNavigation browseMessageList: badOnes asSortedCollection name: 'Decompiler Discrepancies'! ! !DecompilerTests methodsFor: 'utilities' stamp: 'sd 9/25/2004 15:30'! isBlockingClass: cls "self new isBlockingClass: PNMReaderWriter" ^ self blockingClasses includes: cls name asSymbol ! ! !DecompilerTests methodsFor: 'utilities' stamp: 'eem 11/10/2008 16:52'! isFailure: cls sel: selector "self new isKnowProblem: PNMReaderWriter sel: #nextImage" "#((PNMReadWriter nextImage)) includes: {PNMReadWriter name asSymbol . #nextImage}." ^(#(#DoIt #DoItIn:) includes: selector) or: [self decompilerFailures includes: {cls name asSymbol. selector}]! ! !DecompilerTests methodsFor: 'utilities' stamp: 'sd 9/25/2004 21:28'! isStoredProblems: cls sel: selector meta: aBoolean "self new isKnowProblem: PNMReaderWriter sel: #nextImage" ^ self decompilerDiscrepancies includes: {cls name asSymbol. selector . aBoolean}! ! !DecompilerTests methodsFor: 'testing' stamp: 'sd 9/26/2004 13:26'! testDecompiler "self run: #testDecompiler" "self debug: #testDecompiler" | methodNode oldMethod newMethod oldCodeString | Smalltalk forgetDoIts. self systemNavigation allBehaviorsDo: [:cls | (self isBlockingClass: cls) ifFalse: [Smalltalk garbageCollect. cls selectors do: [:selector | (self isFailure: cls sel: selector) ifFalse: [" to help making progress (self isStoredProblems: cls theNonMetaClass sel: selector meta: cls isMeta) ifFalse: [ " Transcript cr; show: cls name. oldMethod := cls compiledMethodAt: selector. oldCodeString := (cls decompilerClass new decompile: selector in: cls method: oldMethod) decompileString. methodNode := cls compilerClass new compile: oldCodeString in: cls notifying: nil ifFail: []. newMethod := methodNode generate: #(0 0 0 0 ). self assert: oldCodeString = (cls decompilerClass new decompile: selector in: cls method: newMethod) decompileString description: cls name asString, ' ', selector asString resumable: true. ]]]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesAAtoAM self decompileClassesSelect: [:cn| cn first = $A and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesANtoAZ self decompileClassesSelect: [:cn| cn first = $A and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesBAtoBM self decompileClassesSelect: [:cn| cn first = $B and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesBNtoBZ self decompileClassesSelect: [:cn| cn first = $B and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesCAtoCM self decompileClassesSelect: [:cn| cn first = $C and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesCNtoCZ self decompileClassesSelect: [:cn| cn first = $C and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesDAtoDM self decompileClassesSelect: [:cn| cn first = $D and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesDNtoDZ self decompileClassesSelect: [:cn| cn first = $D and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesEAtoEM self decompileClassesSelect: [:cn| cn first = $E and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesENtoEZ self decompileClassesSelect: [:cn| cn first = $E and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesFAtoFM self decompileClassesSelect: [:cn| cn first = $F and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesFNtoFZ self decompileClassesSelect: [:cn| cn first = $F and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesGAtoGM self decompileClassesSelect: [:cn| cn first = $G and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesGNtoGZ self decompileClassesSelect: [:cn| cn first = $G and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesHAtoHM self decompileClassesSelect: [:cn| cn first = $H and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesHNtoHZ self decompileClassesSelect: [:cn| cn first = $H and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesIAtoIM self decompileClassesSelect: [:cn| cn first = $I and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesINtoIZ self decompileClassesSelect: [:cn| cn first = $I and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesJAtoJM self decompileClassesSelect: [:cn| cn first = $J and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesJNtoJZ self decompileClassesSelect: [:cn| cn first = $J and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesKAtoKM self decompileClassesSelect: [:cn| cn first = $K and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesKNtoKZ self decompileClassesSelect: [:cn| cn first = $K and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesLAtoLM self decompileClassesSelect: [:cn| cn first = $L and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesLNtoLZ self decompileClassesSelect: [:cn| cn first = $L and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesMAtoMM self decompileClassesSelect: [:cn| cn first = $M and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesMNtoMZ self decompileClassesSelect: [:cn| cn first = $M and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesNAtoNM self decompileClassesSelect: [:cn| cn first = $N and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesNNtoNZ self decompileClassesSelect: [:cn| cn first = $N and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesOAtoOM self decompileClassesSelect: [:cn| cn first = $O and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesONtoOZ self decompileClassesSelect: [:cn| cn first = $O and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesPAtoPM self decompileClassesSelect: [:cn| cn first = $P and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesPNtoPZ self decompileClassesSelect: [:cn| cn first = $P and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesQAtoQM self decompileClassesSelect: [:cn| cn first = $Q and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesQNtoQZ self decompileClassesSelect: [:cn| cn first = $Q and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesRAtoRM self decompileClassesSelect: [:cn| cn first = $R and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesRNtoRZ self decompileClassesSelect: [:cn| cn first = $R and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesSAtoSM self decompileClassesSelect: [:cn| cn first = $S and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesSNtoSZ self decompileClassesSelect: [:cn| cn first = $S and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesTAtoTM self decompileClassesSelect: [:cn| cn first = $T and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesTNtoTZ self decompileClassesSelect: [:cn| cn first = $T and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesUAtoUM self decompileClassesSelect: [:cn| cn first = $U and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesUNtoUZ self decompileClassesSelect: [:cn| cn first = $U and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesVAtoVM self decompileClassesSelect: [:cn| cn first = $V and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesVNtoVZ self decompileClassesSelect: [:cn| cn first = $V and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesWAtoWM self decompileClassesSelect: [:cn| cn first = $W and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesWNtoWZ self decompileClassesSelect: [:cn| cn first = $W and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesXAtoXM self decompileClassesSelect: [:cn| cn first = $X and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesXNtoXZ self decompileClassesSelect: [:cn| cn first = $X and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesYAtoYM self decompileClassesSelect: [:cn| cn first = $Y and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesYNtoYZ self decompileClassesSelect: [:cn| cn first = $Y and: [cn second asUppercase > $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesZAtoZM self decompileClassesSelect: [:cn| cn first = $Z and: [cn second asUppercase <= $M]]! ! !DecompilerTests methodsFor: 'tests' stamp: 'eem 9/23/2008 11:16'! testDecompilerInClassesZNtoZZ self decompileClassesSelect: [:cn| cn first = $Z and: [cn second asUppercase > $M]]! ! Object subclass: #DeepCopier instanceVariableNames: 'references' classVariableNames: 'NextVariableCheckTime' poolDictionaries: '' category: 'System-Object Storage'! !DeepCopier commentStamp: 'stephane.ducasse 9/25/2008 17:47' prior: 0! DeepCopier does a veryDeepCopy. It is a complete tree copy using a dictionary. Any object that is in the tree twice is only copied once. All references to the object in the copy of the tree will point to the new copy. See Object|veryDeepCopy which calls (self veryDeepCopyWith: aDeepCopier). When a tree of morphs points at a morph outside of itself, that morph should not be copied. Use our own kind of weak pointers for the 'potentially outside' morphs. Default is that any new class will have all of its fields deeply copied. If a field needs to be weakly copied, define veryDeepInner: and veryDeepFixupWith:. veryDeepInner: has the loop that actually copies the fields. If a class defines its own copy of veryDeepInner: (to leave some fields out), then veryDeepFixupWith: will be called on that object at the end. veryDeepInner: can compute an alternate object to put in a field. (Object veryDeepCopyWith: discovers which superclasses did not define veryDeepInner:, and very deeply copies the variables defined in those classes). To decide if a class needs veryDeepInner: and veryDeepFixupWith:, ask this about an instance: If I duplicate this object, does that mean that I also want to make duplicates of the things it holds onto? If yes, (i.e. a Paragraph does want a new copy of its Text) then do nothing. If no, (i.e. an undo command does not want to copy the objects it acts upon), then define veryDeepInner: and veryDeepFixupWith:. Here is an analysis for the specific case of a morph being held by another morph. Does field X contain a morph (or a Player whose costume is a morph)? If not, no action needed. Is the morph in field X already a submorph of the object? Is it down lower in the submorph tree? If so, no action needed. Could the morph in field X every appear on the screen (be a submorph of some other morph)? If not, no action needed. If it could, you must write the methods veryDeepFixupWith: and veryDeepInner:, and in them, refrain from sending veryDeepCopyWith: to the contents of field X. ----- Things Ted is still considering ----- Rule: If a morph stores a uniClass class (Player 57) as an object in a field, the new uniClass will not be stored there. Each uniClass instance does have a new class created for it. (fix this by putting the old class in references and allow lookup? Wrong if encounter it before seeing an instance?) Rule: If object A has object C in a field, and A says (^ C) for the copy, but object B has A in a normal field and it gets deepCopied, and A in encountered first, then there will be two copies of C. (just be aware of it) Dependents are now fixed up. Suppose a model has a dependent view. In the DependentFields dictionary, model -> (view ...). If only the model is copied, no dependents are created (no one knows about the new model). If only the view is copied, it is inserted into DependentFields on the right side. model -> (view copiedView ...). If both are copied, the new model has the new view as its dependent. If additional things depend on a model that is copied, the caller must add them to its dependents. ! !DeepCopier methodsFor: 'like fullCopy' stamp: 'eem 6/11/2008 17:21'! checkDeep "Write exceptions in the Transcript. Every class that implements veryDeepInner: must copy all its inst vars. Danger is that a user will add a new instance variable and forget to copy it. This check is only run by hand once in a while to make sure nothing was forgotten. (Please do not remove this method.) DeepCopier new checkDeep " Transcript cr; show: 'Instance variables shared with the original object when it is copied'. (self systemNavigation allClassesImplementing: #veryDeepInner:) do: [:aClass | | mm | (mm := aClass instVarNames size) > 0 ifTrue: [aClass instSize - mm + 1 to: aClass instSize do: [:index | ((aClass compiledMethodAt: #veryDeepInner:) writesField: index) ifFalse: [Transcript cr; show: aClass name; space; show: (aClass allInstVarNames at: index)]]]]! ! !DeepCopier methodsFor: 'like fullCopy' stamp: 'eem 6/11/2008 17:21'! checkVariables "Check that no indexes of instance vars have changed in certain classes. If you get an error in this method, an implementation of veryDeepCopyWith: needs to be updated. The idea is to catch a change while it is still in the system of the programmer who made it. DeepCopier new checkVariables " self checkBasicClasses. "Every class that implements veryDeepInner: must copy all its inst vars. Danger is that a user will add a new instance variable and forget to copy it. So check that the last one is mentioned in the copy method." (self systemNavigation allClassesImplementing: #veryDeepInner:) do: [:aClass | ((aClass compiledMethodAt: #veryDeepInner:) writesField: aClass instSize) ifFalse: [aClass instSize > 0 ifTrue: [self warnIverNotCopiedIn: aClass sel: #veryDeepInner:]]]. (self systemNavigation allClassesImplementing: #veryDeepCopyWith:) do: [:aClass | | meth | meth := aClass compiledMethodAt: #veryDeepCopyWith:. meth size > 20 & (meth literals includes: #veryDeepCopyWith:) not ifTrue: [(meth writesField: aClass instSize) ifFalse: [self warnIverNotCopiedIn: aClass sel: #veryDeepCopyWith:]]]! ! !DeepCopier methodsFor: 'like fullCopy' stamp: 'eem 6/11/2008 17:22'! fixDependents "They are not used much, but need to be right" DependentsFields associationsDo: [:pair | pair value do: [:dep | (references at: dep ifAbsent: [nil]) ifNotNil: [:newDep| | newModel | newModel := references at: pair key ifAbsent: [pair key]. newModel addDependent: newDep]]]. ! ! !DeepCopier methodsFor: 'like fullcopy' stamp: 'stephane.ducasse 1/30/2009 21:52'! checkBasicClasses "Check that no indexes of instance vars have changed in certain classes. If you get an error in this method, an implementation of veryDeepCopyWith: needs to be updated. The idea is to catch a change while it is still in the system of the programmer who made it. DeepCopier new checkVariables " | str objCls morphCls | str := '|veryDeepCopyWith: or veryDeepInner: is out of date.'. (objCls := self objInMemory: #Object) ifNotNil: [ objCls instSize = 0 ifFalse: [self error: 'Many implementers of veryDeepCopyWith: are out of date']]. (morphCls := self objInMemory: #Morph) ifNotNil: [ morphCls superclass == Object ifFalse: [self error: 'Morph', str]. (morphCls instVarNames copyFrom: 1 to: 6) = #('bounds' 'owner' 'submorphs' 'fullBounds' 'color' 'extension') ifFalse: [self error: 'Morph', str]]. "added ones are OK" ! ! !DeepCopier methodsFor: 'like fullcopy' stamp: 'tk 3/7/2001 15:42'! checkClass: aClass | meth | "Check that no indexes of instance vars have changed in certain classes. If you get an error in this method, an implementation of veryDeepCopyWith: needs to be updated. The idea is to catch a change while it is still in the system of the programmer who made it." self checkBasicClasses. "Unlikely, but important to catch when it does happen." "Every class that implements veryDeepInner: must copy all its inst vars. Danger is that a user will add a new instance variable and forget to copy it. So check that the last one is mentioned in the copy method." (aClass includesSelector: #veryDeepInner:) ifTrue: [ ((aClass compiledMethodAt: #veryDeepInner:) writesField: aClass instSize) ifFalse: [ aClass instSize > 0 ifTrue: [ self warnIverNotCopiedIn: aClass sel: #veryDeepInner:]]]. (aClass includesSelector: #veryDeepCopyWith:) ifTrue: [ meth := aClass compiledMethodAt: #veryDeepCopyWith:. (meth size > 20) & (meth literals includes: #veryDeepCopyWith:) not ifTrue: [ (meth writesField: aClass instSize) ifFalse: [ self warnIverNotCopiedIn: aClass sel: #veryDeepCopyWith:]]]. ! ! !DeepCopier methodsFor: 'like fullcopy' stamp: 'alain.plantec 5/28/2009 09:50'! initialize super initialize. self initialize: 4096. ! ! !DeepCopier methodsFor: 'like fullcopy' stamp: 'stephane.ducasse 9/25/2008 17:46'! initialize: size references := IdentityDictionary new: size. ! ! !DeepCopier methodsFor: 'like fullcopy' stamp: 'tk 11/24/1999 17:53'! intervalForChecks "set delay interval for checking for new instance variables to 10 minutes. hg 11/23/1999" ^600 ! ! !DeepCopier methodsFor: 'like fullcopy' stamp: 'tk 11/25/1999 14:37'! isItTimeToCheckVariables | now isIt | NextVariableCheckTime ifNil: [ NextVariableCheckTime := Time totalSeconds. ^ true]. now := Time totalSeconds. isIt := NextVariableCheckTime < now. isIt ifTrue: ["update time for next check" NextVariableCheckTime := now + self intervalForChecks]. ^isIt ! ! !DeepCopier methodsFor: 'like fullcopy' stamp: 'tk 3/7/2001 15:29'! objInMemory: ClassSymbol | cls | "Test if this global is in memory and return it if so." cls := Smalltalk at: ClassSymbol ifAbsent: [^ nil]. ^ cls isInMemory ifTrue: [cls] ifFalse: [nil].! ! !DeepCopier methodsFor: 'like fullcopy' stamp: 'tk 8/20/1998 22:13'! references ^ references! ! !DeepCopier methodsFor: 'like fullcopy' stamp: 'ar 9/27/2005 20:27'! warnIverNotCopiedIn: aClass sel: sel "Warn the user to update veryDeepCopyWith: or veryDeepInner:" self inform: ('An instance variable was added to to class ', aClass name, ',\and it is not copied in the method ', sel, '.\Please rewrite it to handle all instance variables.\See DeepCopier class comment.') withCRs. ToolSet browse: aClass selector: sel! ! Object subclass: #DefaultExternalDropHandler instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Support'! !DefaultExternalDropHandler commentStamp: 'dgd 4/5/2004 19:07' prior: 0! An alternative default handler that uses the file-list services to process files. ! !DefaultExternalDropHandler methodsFor: 'event handling' stamp: 'bf 9/21/2004 18:44'! handle: dropStream in: pasteUp dropEvent: anEvent "the file was just droped, let's do our job" | fileName services theOne | fileName := dropStream name. "" services := self servicesForFileNamed: fileName. "" "no service, default behavior" services isEmpty ifTrue: ["" dropStream edit. ^ self]. "" theOne := self chooseServiceFrom: services. theOne isNil ifFalse: [theOne performServiceFor: dropStream]! ! !DefaultExternalDropHandler methodsFor: 'private' stamp: 'alain.plantec 2/8/2009 22:02'! chooseServiceFrom: aCollection "private - choose a service from aCollection asking the user if needed" aCollection size = 1 ifTrue: [^ aCollection anyOne]. ^ UIManager default chooseFrom: (aCollection collect: [:each | each label]) values: aCollection. ! ! !DefaultExternalDropHandler methodsFor: 'private' stamp: 'dgd 4/5/2004 19:23'! servicesForFileNamed: aString "private - answer a collection of file-services for the file named aString" | allServices | allServices := FileList itemsForFile: aString. ^ allServices reject: [:svc | self unwantedSelectors includes: svc selector]! ! !DefaultExternalDropHandler methodsFor: 'private' stamp: 'dgd 4/5/2004 19:23'! unwantedSelectors "private - answer a collection well known unwanted selectors " ^ #(#removeLineFeeds: #addFileToNewZip: #compressFile: #putUpdate: )! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DefaultExternalDropHandler class instanceVariableNames: ''! !DefaultExternalDropHandler class methodsFor: 'initialization' stamp: 'dgd 4/5/2004 19:10'! initialize "initialize the receiver" ExternalDropHandler defaultHandler: self new! ! !DefaultExternalDropHandler class methodsFor: 'initialization' stamp: 'dgd 4/5/2004 19:09'! unload "initialize the receiver" ExternalDropHandler defaultHandler: nil! ! WriteStream subclass: #DeflateStream instanceVariableNames: 'hashHead hashTail hashValue blockPosition blockStart' classVariableNames: '' poolDictionaries: 'ZipConstants' category: 'Compression-Streams'! !DeflateStream methodsFor: 'accessing' stamp: 'ar 12/29/1999 20:00'! goodMatchLength "Return the length that is considered to be a 'good' match. Higher values will result in better compression but take more time." ^MaxMatch "Best compression"! ! !DeflateStream methodsFor: 'accessing' stamp: 'ar 12/29/1999 20:00'! hashChainLength "Return the max. number of hash chains to traverse. Higher values will result in better compression but take more time." ^4096 "Best compression"! ! !DeflateStream methodsFor: 'accessing' stamp: 'ar 2/19/2004 00:34'! next: bytes putAll: aCollection startingAt: startPos (startPos = 1 and:[bytes = aCollection size]) ifTrue:[^self nextPutAll: aCollection]. ^self nextPutAll: (aCollection copyFrom: startPos to: startPos + bytes - 1)! ! !DeflateStream methodsFor: 'accessing' stamp: 'ar 12/29/1999 17:33'! nextPutAll: aCollection | start count max | aCollection species = collection species ifFalse:[ aCollection do:[:ch| self nextPut: ch]. ^aCollection]. start := 1. count := aCollection size. [count = 0] whileFalse:[ position = writeLimit ifTrue:[self deflateBlock]. max := writeLimit - position. max > count ifTrue:[max := count]. collection replaceFrom: position+1 to: position+max with: aCollection startingAt: start. start := start + max. count := count - max. position := position + max]. ^aCollection! ! !DeflateStream methodsFor: 'accessing' stamp: 'ar 12/28/1999 17:35'! pastEndPut: anObject self deflateBlock. ^self nextPut: anObject! ! !DeflateStream methodsFor: 'deflating' stamp: 'ar 12/29/1999 20:24'! compare: here with: matchPos min: minLength "Compare the two strings and return the length of matching characters. minLength is a lower bound for match lengths that will be accepted. Note: here and matchPos are zero based." | length | "First test if we can actually get longer than minLength" (collection at: here+minLength+1) = (collection at: matchPos+minLength+1) ifFalse:[^0]. (collection at: here+minLength) = (collection at: matchPos+minLength) ifFalse:[^0]. "Then test if we have an initial match at all" (collection at: here+1) = (collection at: matchPos+1) ifFalse:[^0]. (collection at: here+2) = (collection at: matchPos+2) ifFalse:[^1]. "Finally do the real comparison" length := 3. [length <= MaxMatch and:[ (collection at: here+length) = (collection at: matchPos+length)]] whileTrue:[length := length + 1]. ^length - 1! ! !DeflateStream methodsFor: 'deflating' stamp: 'ar 12/31/1999 18:00'! deflateBlock "Deflate the current contents of the stream" | flushNeeded lastIndex | (blockStart == nil) ifTrue:[ "One time initialization for the first block" 1 to: MinMatch-1 do:[:i| self updateHashAt: i]. blockStart := 0]. [blockPosition < position] whileTrue:[ (position + MaxMatch > writeLimit) ifTrue:[lastIndex := writeLimit - MaxMatch] ifFalse:[lastIndex := position]. flushNeeded := self deflateBlock: lastIndex-1 chainLength: self hashChainLength goodMatch: self goodMatchLength. flushNeeded ifTrue:[ self flushBlock. blockStart := blockPosition]. "Make room for more data" self moveContentsToFront]. ! ! !DeflateStream methodsFor: 'deflating' stamp: 'ar 12/29/1999 18:05'! deflateBlock: lastIndex chainLength: chainLength goodMatch: goodMatch "Continue deflating the receiver's collection from blockPosition to lastIndex. Note that lastIndex must be at least MaxMatch away from the end of collection" | here matchResult flushNeeded hereMatch hereLength newMatch newLength hasMatch | blockPosition > lastIndex ifTrue:[^false]. "Nothing to deflate" hasMatch := false. here := blockPosition. [here <= lastIndex] whileTrue:[ hasMatch ifFalse:[ "Find the first match" matchResult := self findMatch: here lastLength: MinMatch-1 lastMatch: here chainLength: chainLength goodMatch: goodMatch. self insertStringAt: here. "update hash table" hereMatch := matchResult bitAnd: 16rFFFF. hereLength := matchResult bitShift: -16]. "Look ahead if there is a better match at the next position" matchResult := self findMatch: here+1 lastLength: hereLength lastMatch: hereMatch chainLength: chainLength goodMatch: goodMatch. newMatch := matchResult bitAnd: 16rFFFF. newLength := matchResult bitShift: -16. "Now check if the next match is better than the current one. If not, output the current match (provided that the current match is at least MinMatch long)" (hereLength >= newLength and:[hereLength >= MinMatch]) ifTrue:[ self assert:[self validateMatchAt: here from: hereMatch to: hereMatch + hereLength - 1]. "Encode the current match" flushNeeded := self encodeMatch: hereLength distance: here - hereMatch. "Insert all strings up to the end of the current match. Note: The first string has already been inserted." 1 to: hereLength-1 do:[:i| self insertStringAt: (here := here + 1)]. hasMatch := false. here := here + 1. ] ifFalse:[ "Either the next match is better than the current one or we didn't have a good match after all (e.g., current match length < MinMatch). Output a single literal." flushNeeded := self encodeLiteral: (collection byteAt: (here + 1)). here := here + 1. (here <= lastIndex and:[flushNeeded not]) ifTrue:[ "Cache the results for the next round" self insertStringAt: here. hasMatch := true. hereMatch := newMatch. hereLength := newLength]. ]. flushNeeded ifTrue:[blockPosition := here. ^true]. ]. blockPosition := here. ^false! ! !DeflateStream methodsFor: 'deflating' stamp: 'ar 12/29/1999 17:45'! findMatch: here lastLength: lastLength lastMatch: lastMatch chainLength: maxChainLength goodMatch: goodMatch "Find the longest match for the string starting at here. If there is no match longer than lastLength return lastMatch/lastLength. Traverse at most maxChainLength entries in the hash table. Stop if a match of at least goodMatch size has been found." | matchResult matchPos distance chainLength limit bestLength length | "Compute the default match result" matchResult := (lastLength bitShift: 16) bitOr: lastMatch. "There is no way to find a better match than MaxMatch" lastLength >= MaxMatch ifTrue:[^matchResult]. "Start position for searches" matchPos := hashHead at: (self updateHashAt: here + MinMatch) + 1. "Compute the distance to the (possible) match" distance := here - matchPos. "Note: It is required that 0 < distance < MaxDistance" (distance > 0 and:[distance < MaxDistance]) ifFalse:[^matchResult]. chainLength := maxChainLength. "Max. nr of match chain to search" here > MaxDistance "Limit for matches that are too old" ifTrue:[limit := here - MaxDistance] ifFalse:[limit := 0]. "Best match length so far (current match must be larger to take effect)" bestLength := lastLength. ["Compare the current string with the string at match position" length := self compare: here with: matchPos min: bestLength. "Truncate accidental matches beyound stream position" (here + length > position) ifTrue:[length := position - here]. "Ignore very small matches if they are too far away" (length = MinMatch and:[(here - matchPos) > (MaxDistance // 4)]) ifTrue:[length := MinMatch - 1]. length > bestLength ifTrue:["We have a new (better) match than before" "Compute the new match result" matchResult := (length bitShift: 16) bitOr: matchPos. bestLength := length. "There is no way to find a better match than MaxMatch" bestLength >= MaxMatch ifTrue:[^matchResult]. "But we may have a good, fast match" bestLength > goodMatch ifTrue:[^matchResult]. ]. (chainLength := chainLength - 1) > 0] whileTrue:[ "Compare with previous entry in hash chain" matchPos := hashTail at: (matchPos bitAnd: WindowMask) + 1. matchPos <= limit ifTrue:[^matchResult]. "Match position is too old" ]. ^matchResult! ! !DeflateStream methodsFor: 'deflating' stamp: 'ar 12/28/1999 17:37'! flushBlock "Flush a deflated block"! ! !DeflateStream methodsFor: 'deflating' stamp: 'ar 12/29/1999 17:46'! insertStringAt: here "Insert the string at the given start position into the hash table. Note: The hash value is updated starting at MinMatch-1 since all strings before have already been inserted into the hash table (and the hash value is updated as well)." | prevEntry | hashValue := self updateHashAt: (here + MinMatch). prevEntry := hashHead at: hashValue+1. hashHead at: hashValue+1 put: here. hashTail at: (here bitAnd: WindowMask)+1 put: prevEntry.! ! !DeflateStream methodsFor: 'deflating' stamp: 'ar 12/29/1999 17:48'! updateHash: nextValue "Update the running hash value based on the next input byte. Return the new updated hash value." ^((hashValue bitShift: HashShift) bitXor: nextValue) bitAnd: HashMask.! ! !DeflateStream methodsFor: 'deflating' stamp: 'ar 12/29/1999 17:47'! updateHashAt: here "Update the hash value at position here (one based)" ^self updateHash: (collection byteAt: here)! ! !DeflateStream methodsFor: 'deflating' stamp: 'ar 12/28/1999 17:43'! validateMatchAt: pos from: startPos to: endPos | here | here := pos. startPos+1 to: endPos+1 do:[:i| (collection at: i) = (collection at: (here := here + 1)) ifFalse:[^self error:'Not a match']]. ^true! ! !DeflateStream methodsFor: 'encoding' stamp: 'ar 12/29/1999 18:04'! encodeLiteral: literal "Encode the given literal. Return true if the current block needs to be flushed." ^false! ! !DeflateStream methodsFor: 'encoding' stamp: 'ar 12/29/1999 18:04'! encodeMatch: matchLength distance: matchDistance "Encode a match of the given length and distance. Return true if the current block should be flushed." ^false! ! !DeflateStream methodsFor: 'initialization' stamp: 'ar 12/29/1999 17:30'! flush "Force compression" self deflateBlock.! ! !DeflateStream methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:51'! initialize super initialize. blockStart := nil. blockPosition := 0. hashValue := 0. self initializeHashTables.! ! !DeflateStream methodsFor: 'initialization' stamp: 'ar 12/29/1999 17:32'! initializeHashTables hashHead := WordArray new: 1 << HashBits. hashTail := WordArray new: WindowSize. ! ! !DeflateStream methodsFor: 'initialization' stamp: 'ar 12/29/1999 17:33'! on: aCollection self initialize. super on: (aCollection species new: WindowSize * 2).! ! !DeflateStream methodsFor: 'initialization' stamp: 'ar 12/28/1999 17:34'! on: aCollection from: firstIndex to: lastIndex "Not for DeflateStreams please" ^self shouldNotImplement! ! !DeflateStream methodsFor: 'private' stamp: 'ar 12/29/1999 17:50'! moveContentsToFront "Move the contents of the receiver to the front" | delta | delta := (blockPosition - WindowSize). delta <= 0 ifTrue:[^self]. "Move collection" collection replaceFrom: 1 to: collection size - delta with: collection startingAt: delta+1. position := position - delta. "Move hash table entries" blockPosition := blockPosition - delta. blockStart := blockStart - delta. self updateHashTable: hashHead delta: delta. self updateHashTable: hashTail delta: delta.! ! !DeflateStream methodsFor: 'private' stamp: 'ar 2/2/2001 15:47'! updateHashTable: table delta: delta | pos | 1 to: table size do:[:i| "Discard entries that are out of range" (pos := table at: i) >= delta ifTrue:[table at: i put: pos - delta] ifFalse:[table at: i put: 0]].! ! Object subclass: #Delay instanceVariableNames: 'delayDuration resumptionTime delaySemaphore beingWaitedOn' classVariableNames: 'AccessProtect ActiveDelay ActiveDelayStartTime DelaySuspended FinishedDelay RunTimerEventLoop ScheduledDelay SuspendedDelays TimerEventLoop TimingSemaphore' poolDictionaries: '' category: 'Kernel-Processes'! !Delay commentStamp: 'stephaneducasse 10/1/2005 21:07' prior: 0! I am the main way that a process may pause for some amount of time. The simplest usage is like this: (Delay forSeconds: 5) wait. An instance of Delay responds to the message 'wait' by suspending the caller's process for a certain amount of time. The duration of the pause is specified when the Delay is created with the message forMilliseconds: or forSeconds:. A Delay can be used again when the current wait has finished. For example, a clock process might repeatedly wait on a one-second Delay. The maximum delay is (SmallInteger maxVal // 2) milliseconds, or about six days. A delay in progress when an image snapshot is saved is resumed when the snapshot is re-started. Delays work across millisecond clock roll-overs. For a more complex example, see #testDelayOf:for:rect: . A word of advice: This is THE highest priority code which is run in Squeak, in other words it is time-critical. The speed of this code is critical for accurate responses, it is critical for network services, it affects every last part of the system. In short: Don't fix it if it ain't broken!! This code isn't supposed to be beautiful, it's supposed to be fast!! The reason for duplicating code is to make it fast. The reason for not using ifNil:[]ifNotNil:[] is that the compiler may not inline those. Since the effect of changes are VERY hard to predict it is best to leave things as they are for now unless there is an actual need to change anything! !Delay methodsFor: 'delaying' stamp: 'nk 3/14/2001 08:52'! isExpired ^delaySemaphore isSignaled. ! ! !Delay methodsFor: 'delaying' stamp: 'ar 8/30/2007 19:32'! wait "Schedule this Delay, then wait on its semaphore. The current process will be suspended for the amount of time specified when this Delay was created." self schedule. [delaySemaphore wait] ifCurtailed:[self unschedule]. ! ! !Delay methodsFor: 'printing' stamp: 'ar 7/10/2007 22:12'! printOn: aStream super printOn: aStream. aStream nextPutAll: '('; print: delayDuration; nextPutAll: ' msecs'. beingWaitedOn ifTrue:[ aStream nextPutAll: '; '; print: resumptionTime - Time millisecondClockValue; nextPutAll: ' msecs remaining'. ]. aStream nextPutAll: ')'.! ! !Delay methodsFor: 'public' stamp: 'ar 7/10/2007 21:49'! beingWaitedOn "Answer whether this delay is currently scheduled, e.g., being waited on" ^beingWaitedOn! ! !Delay methodsFor: 'public' stamp: 'ar 7/10/2007 21:49'! beingWaitedOn: aBool "Indicate whether this delay is currently scheduled, e.g., being waited on" beingWaitedOn := aBool! ! !Delay methodsFor: 'public' stamp: 'ar 7/10/2007 20:56'! delayDuration ^delayDuration! ! !Delay methodsFor: 'public' stamp: 'brp 10/21/2004 16:05'! delaySemaphore ^ delaySemaphore! ! !Delay methodsFor: 'private' stamp: 'jm 9/11/97 14:49'! adjustResumptionTimeOldBase: oldBaseTime newBase: newBaseTime "Private!! Adjust the value of the system's millisecond clock at which this Delay will be awoken. Used to adjust resumption times after a snapshot or clock roll-over." resumptionTime := newBaseTime + (resumptionTime - oldBaseTime). ! ! !Delay methodsFor: 'private' stamp: 'jm 9/11/97 11:54'! resumptionTime "Answer the value of the system's millisecondClock at which the receiver's suspended Process will resume." ^ resumptionTime ! ! !Delay methodsFor: 'private' stamp: 'ar 9/21/2009 22:19'! schedule "Schedule this delay" beingWaitedOn ifTrue: [^self error: 'This Delay has already been scheduled.']. resumptionTime := Time millisecondClockValue + delayDuration. AccessProtect critical:[ ScheduledDelay := self. TimingSemaphore signal. ].! ! !Delay methodsFor: 'private' stamp: 'nice 4/19/2009 21:18'! setDelay: milliseconds forSemaphore: aSemaphore "Private!! Initialize this delay to signal the given semaphore after the given number of milliseconds." delayDuration := milliseconds asInteger. delayDuration < 0 ifTrue: [self error: 'delay times cannot be negative']. delaySemaphore := aSemaphore. beingWaitedOn := false.! ! !Delay methodsFor: 'private' stamp: 'jm 9/11/97 11:54'! signalWaitingProcess "The delay time has elapsed; signal the waiting process." beingWaitedOn := false. delaySemaphore signal. ! ! !Delay methodsFor: 'private' stamp: 'ar 3/2/2009 14:42'! unschedule AccessProtect critical:[ FinishedDelay := self. TimingSemaphore signal. ].! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Delay class instanceVariableNames: ''! !Delay class methodsFor: 'class initialization' stamp: 'ar 7/11/2007 18:16'! initialize "Delay initialize" self startTimerEventLoop.! ! !Delay class methodsFor: 'example' stamp: 'jm 9/11/97 11:23'! testDelayOf: delay for: testCount rect: r "Delay testDelayOf: 100 for: 20 rect: (10@10 extent: 30@30). Delay testDelayOf: 400 for: 20 rect: (50@10 extent: 30@30)." | onDelay offDelay | onDelay := Delay forMilliseconds: 50. offDelay := Delay forMilliseconds: delay - 50. Display fillBlack: r. [1 to: testCount do: [:i | Display fillWhite: r. onDelay wait. Display reverse: r. offDelay wait]. ] forkAt: Processor userInterruptPriority. ! ! !Delay class methodsFor: 'instance creation' stamp: 'brp 9/25/2003 13:43'! forDuration: aDuration ^ self forMilliseconds: aDuration asMilliSeconds ! ! !Delay class methodsFor: 'instance creation' stamp: 'laza 1/30/2005 22:10'! forMilliseconds: aNumber "Return a new Delay for the given number of milliseconds. Sending 'wait' to this Delay will cause the sender's process to be suspended for approximately that length of time." ^ self new setDelay: aNumber forSemaphore: Semaphore new ! ! !Delay class methodsFor: 'instance creation' stamp: 'laza 1/30/2005 22:11'! forSeconds: aNumber ^ self forMilliseconds: aNumber * 1000 ! ! !Delay class methodsFor: 'instance creation' stamp: 'laza 1/6/2008 06:35'! timeoutSemaphore: aSemaphore afterMSecs: anInteger "Create and schedule a Delay to signal the given semaphore when the given number of milliseconds has elapsed. Return the scheduled Delay. The timeout can be cancelled by sending 'unschedule' to this Delay." "Details: This mechanism is used to provide a timeout when waiting for an external event, such as arrival of data over a network connection, to signal a semaphore. The timeout ensures that the semaphore will be signalled within a reasonable period of time even if the event fails to occur. Typically, the waiting process cancels the timeout request when awoken, then determines if the awaited event has actually occurred." ^ (self new setDelay: anInteger forSemaphore: aSemaphore) schedule ! ! !Delay class methodsFor: 'primitives' stamp: 'ar 3/2/2009 14:43'! primSignal: aSemaphore atMilliseconds: aSmallInteger "Signal the semaphore when the millisecond clock reaches the value of the second argument. Fail if the first argument is neither a Semaphore nor nil. Essential. See Object documentation whatIsAPrimitive." ^self primitiveFailed! ! !Delay class methodsFor: 'snapshotting' stamp: 'ar 3/2/2009 14:44'! restoreResumptionTimes "Private!! Restore the resumption times of all scheduled Delays after a snapshot or clock roll-over. This method should be called only while the AccessProtect semaphore is held." | newBaseTime | newBaseTime := Time millisecondClockValue. SuspendedDelays do: [:d | d adjustResumptionTimeOldBase: 0 newBase: newBaseTime]. ActiveDelay == nil ifFalse: [ ActiveDelay adjustResumptionTimeOldBase: 0 newBase: newBaseTime. ]. ! ! !Delay class methodsFor: 'snapshotting' stamp: 'jm 9/11/97 15:15'! saveResumptionTimes "Private!! Record the resumption times of all Delays relative to a base time of zero. This is done prior to snapshotting or adjusting the resumption times after a clock roll-over. This method should be called only while the AccessProtect semaphore is held." | oldBaseTime | oldBaseTime := Time millisecondClockValue. ActiveDelay == nil ifFalse: [ oldBaseTime < ActiveDelayStartTime ifTrue: [oldBaseTime := ActiveDelayStartTime]. "clock rolled over" ActiveDelay adjustResumptionTimeOldBase: oldBaseTime newBase: 0]. SuspendedDelays do: [:d | d adjustResumptionTimeOldBase: oldBaseTime newBase: 0]. ! ! !Delay class methodsFor: 'snapshotting' stamp: 'ar 9/30/2007 12:46'! shutDown "Suspend the active delay, if any, before snapshotting. It will be reactived when the snapshot is resumed." "Details: This prevents a timer interrupt from waking up the active delay in the midst snapshoting, since the active delay will be restarted when resuming the snapshot and we don't want to process the delay twice." AccessProtect wait. self primSignal: nil atMilliseconds: 0. self saveResumptionTimes. DelaySuspended := true.! ! !Delay class methodsFor: 'snapshotting' stamp: 'ar 3/2/2009 14:44'! startUp "Restart active delay, if any, when resuming a snapshot." DelaySuspended ifFalse:[^self error: 'Trying to activate Delay twice']. DelaySuspended := false. self restoreResumptionTimes. AccessProtect signal. ! ! !Delay class methodsFor: 'testing' stamp: 'ar 9/6/1999 17:05'! anyActive "Return true if there is any delay currently active" ^ActiveDelay notNil! ! !Delay class methodsFor: 'testing'! nextWakeUpTime ^ AccessProtect critical: [ActiveDelay isNil ifTrue: [0] ifFalse: [ActiveDelay resumptionTime]]! ! !Delay class methodsFor: 'timer process' stamp: 'ar 8/24/2007 12:36'! handleTimerEvent "Handle a timer event; which can be either: - a schedule request (ScheduledDelay notNil) - an unschedule request (FinishedDelay notNil) - a timer signal (not explicitly specified) We check for timer expiry every time we get a signal." | nowTick nextTick | "Wait until there is work to do." TimingSemaphore wait. "Process any schedule requests" ScheduledDelay ifNotNil:[ "Schedule the given delay" self scheduleDelay: ScheduledDelay. ScheduledDelay := nil. ]. "Process any unschedule requests" FinishedDelay ifNotNil:[ self unscheduleDelay: FinishedDelay. FinishedDelay := nil. ]. "Check for clock wrap-around." nowTick := Time millisecondClockValue. nowTick < ActiveDelayStartTime ifTrue: [ "clock wrapped" self saveResumptionTimes. self restoreResumptionTimes. ]. ActiveDelayStartTime := nowTick. "Signal any expired delays" [ActiveDelay notNil and:[nowTick >= ActiveDelay resumptionTime]] whileTrue:[ ActiveDelay signalWaitingProcess. SuspendedDelays isEmpty ifTrue: [ActiveDelay := nil] ifFalse:[ActiveDelay := SuspendedDelays removeFirst]. ]. "And signal when the next request is due. We sleep at most 1sec here as a soft busy-loop so that we don't accidentally miss signals." nextTick := nowTick + 1000. ActiveDelay ifNotNil:[nextTick := nextTick min: ActiveDelay resumptionTime]. nextTick := nextTick min: SmallInteger maxVal. "Since we have processed all outstanding requests, reset the timing semaphore so that only new work will wake us up again. Do this RIGHT BEFORE setting the next wakeup call from the VM because it is only signaled once so we mustn't miss it." TimingSemaphore initSignals. Delay primSignal: TimingSemaphore atMilliseconds: nextTick. "This last test is necessary for the obscure case that the msecs clock rolls over after nowTick has been computed (unlikely but not impossible). In this case we'd wait for MillisecondClockMask msecs (roughly six days) or until another delay gets scheduled (which may not be any time soon). In any case, since handling the condition is easy, let's just deal with it" Time millisecondClockValue < nowTick ifTrue:[TimingSemaphore signal]. "retry" ! ! !Delay class methodsFor: 'timer process' stamp: 'ar 3/2/2009 14:40'! runTimerEventLoop "Run the timer event loop." [RunTimerEventLoop] whileTrue: [self handleTimerEvent]! ! !Delay class methodsFor: 'timer process' stamp: 'ar 7/10/2007 22:32'! scheduleDelay: aDelay "Private. Schedule this Delay." aDelay beingWaitedOn: true. ActiveDelay ifNil:[ ActiveDelay := aDelay ] ifNotNil:[ aDelay resumptionTime < ActiveDelay resumptionTime ifTrue:[ SuspendedDelays add: ActiveDelay. ActiveDelay := aDelay. ] ifFalse: [SuspendedDelays add: aDelay]. ]. ! ! !Delay class methodsFor: 'timer process' stamp: 'ar 3/2/2009 14:40'! startTimerEventLoop "Start the timer event loop" "Delay startTimerEventLoop" self stopTimerEventLoop. AccessProtect := Semaphore forMutualExclusion. ActiveDelayStartTime := Time millisecondClockValue. SuspendedDelays := Heap withAll: (SuspendedDelays ifNil:[#()]) sortBlock: [:d1 :d2 | d1 resumptionTime <= d2 resumptionTime]. TimingSemaphore := Semaphore new. RunTimerEventLoop := true. TimerEventLoop := [self runTimerEventLoop] newProcess. TimerEventLoop priority: Processor timingPriority. TimerEventLoop resume. TimingSemaphore signal. "get going" ! ! !Delay class methodsFor: 'timer process' stamp: 'ar 7/10/2007 21:26'! stopTimerEventLoop "Stop the timer event loop" RunTimerEventLoop := false. TimingSemaphore signal. TimerEventLoop := nil.! ! !Delay class methodsFor: 'timer process' stamp: 'ar 8/30/2007 19:59'! unscheduleDelay: aDelay "Private. Unschedule this Delay." aDelay beingWaitedOn ifFalse:[^self]. ActiveDelay == aDelay ifTrue: [ SuspendedDelays isEmpty ifTrue:[ ActiveDelay := nil. ] ifFalse: [ ActiveDelay := SuspendedDelays removeFirst. ] ] ifFalse:[ SuspendedDelays remove: aDelay ifAbsent: []. ]. aDelay beingWaitedOn: false.! ! TestCase subclass: #DelayTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Processes'! !DelayTest methodsFor: 'testing' stamp: 'nice 4/19/2009 21:21'! testBounds "self run: #testBounds" self should: [Delay forMilliseconds: -1] raise: Error. self shouldnt: [Delay forMilliseconds: SmallInteger maxVal // 2 + 1] raise: Error. self shouldnt: [Delay forMilliseconds: SmallInteger maxVal + 1] raise: Error. self shouldnt: [(Delay forMilliseconds: Float pi) wait] raise: Error. "Wait 3ms" ! ! !DelayTest methodsFor: 'testing' stamp: 'laza 1/6/2008 06:46'! testSemaphore "When we provide our own semaphore for a Delay, it should be used" "See http://bugs.squeak.org/view.php?id=6834" "self run: #testSemaphore" | sem process | sem := Semaphore new. [ process := [Delay timeoutSemaphore: sem afterMSecs: 0. sem wait] newProcess. process priority: Processor highIOPriority. process resume. self assert: process isTerminated. ] ensure: [sem signal]! ! !DelayTest methodsFor: 'testing-limits' stamp: 'ar 9/21/2009 22:14'! testMultiProcessWaitOnSameDelay "Ensure that waiting on the same delay from multiple processes raises an error" | delay p1 p2 wasRun | delay := Delay forSeconds: 1. wasRun := false. p1 := [delay wait] forkAt: Processor activePriority+1. p2 := [ self should:[delay wait] raise: Error. wasRun := true. ] forkAt: Processor activePriority+1. p1 terminate. p2 terminate. self assert: wasRun. ! ! !DelayTest methodsFor: 'testing-limits' stamp: 'ar 9/21/2009 22:12'! testMultiSchedule "Ensure that scheduling the same delay twice raises an error" | delay | delay := Delay forSeconds: 1. delay schedule. self should:[delay schedule] raise: Error. ! ! Delay subclass: #DelayWaitTimeout instanceVariableNames: 'process expired' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Processes'! !DelayWaitTimeout commentStamp: '' prior: 0! DelayWaitTimeout is a special kind of Delay used in waitTimeoutMSecs: to avoid signaling the underlying semaphore when the wait times out.! !DelayWaitTimeout methodsFor: 'signaling' stamp: 'ar 3/24/2009 23:24'! signalWaitingProcess "Release the given process from the semaphore it is waiting on. This method relies on running at highest priority so that it cannot be preempted by the process being released." beingWaitedOn := false. "Release the process but only if it is still waiting on its original list" process suspendingList == delaySemaphore ifTrue:[ expired := true. process suspend; resume. ]. ! ! !DelayWaitTimeout methodsFor: 'testing' stamp: 'ar 3/23/2009 16:37'! isExpired "Did this timeout fire before the associated semaphore was signaled?" ^expired! ! !DelayWaitTimeout methodsFor: 'waiting' stamp: 'ar 3/27/2009 22:26'! wait "Wait until either the semaphore is signaled or the delay times out" [self schedule. "It is critical that the following has no suspension point so that the test and the wait primitive are atomic. In addition, if the delay is no longer being waited on while entering the way we know that it is expired because the delay has already fired." beingWaitedOn ifTrue:[delaySemaphore wait] ifFalse:[expired := true]] ensure:[self unschedule]. ^self isExpired ! ! !DelayWaitTimeout methodsFor: 'private' stamp: 'ar 3/23/2009 16:38'! setDelay: anInteger forSemaphore: aSemaphore super setDelay: anInteger forSemaphore: aSemaphore. process := Processor activeProcess. expired := false.! ! MessageDialogWindow subclass: #DenyDialogWindow instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !DenyDialogWindow commentStamp: 'gvc 5/18/2007 13:27' prior: 0! Dialog window displaying a message with a single OK button. Escape/return will close. Icon is a themed lock icon.! !DenyDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/18/2007 10:27'! icon "Answer an icon for the receiver." ^self theme lockIcon! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DenyDialogWindow class instanceVariableNames: ''! !DenyDialogWindow class methodsFor: 'as yet unclassified' stamp: 'gvc 5/22/2007 11:52'! taskbarIcon "Answer the icon for the receiver in a task bar." ^self theme smallLockIcon! ! Array weakSubclass: #DependentsArray instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Objects'! !DependentsArray commentStamp: '' prior: 0! An array of (weak) dependents of some object.! !DependentsArray methodsFor: 'copying' stamp: 'bf 7/21/2006 17:04'! copyWith: newElement "Re-implemented to not copy any niled out dependents." | copy i | copy := self class new: self size + 1. i := 0. self do: [:item | copy at: (i:=i+1) put: item]. copy at: (i:=i+1) put: newElement. ^copy! ! !DependentsArray methodsFor: 'copying' stamp: 'GabrielOmarCotelli 5/25/2009 16:22'! size "No nil verification required. See do: implementation that only evaluates not nil objects" ^self inject: 0 into: [:size :anObject | size + 1]! ! !DependentsArray methodsFor: 'enumerating' stamp: 'nk 3/11/2004 09:34'! do: aBlock "Refer to the comment in Collection|do:." | dep | 1 to: self basicSize do:[:i| (dep := self at: i) ifNotNil:[aBlock value: dep]].! ! !DependentsArray methodsFor: 'enumerating' stamp: 'PeterHugossonMiller 9/3/2009 01:12'! select: aBlock "Refer to the comment in Collection|select:." | aStream | aStream := (self species new: self size) writeStream. self do:[:obj| (aBlock value: obj) ifTrue: [aStream nextPut: obj]]. ^ aStream contents! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DependentsArray class instanceVariableNames: ''! TestCase subclass: #DependentsArrayTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Objects'! !DependentsArrayTest methodsFor: 'test' stamp: 'GabrielOmarCotelli 5/25/2009 16:16'! testSize self assert: (DependentsArray with: nil) size = 0; assert: (DependentsArray with: nil with: 1 with: nil) size = 1; assert: (DependentsArray with: 1 with: 3) size = 2; assert: (DependentsArray with: nil with: nil with: nil) size = 0! ! Warning subclass: #Deprecation instanceVariableNames: 'methodReference explanationString deprecationDate versionString' classVariableNames: 'Log' poolDictionaries: '' category: 'Exceptions-Kernel'! !Deprecation commentStamp: 'dew 5/21/2003 17:46' prior: 0! This Warning is signalled by methods which are deprecated. The use of Object>>#deprecatedExplanation: aString and Object>>#deprecated: aBlock explanation: aString is recommended. Idiom: Imagine I want to deprecate the message #foo. foo ^ 'foo' I can replace it with: foo self deprecatedExplanation: 'The method #foo was not good. Use Bar>>newFoo instead.' ^ 'foo' Or, for certain cases such as when #foo implements a primitive, #foo can be renamed to #fooDeprecated. fooDeprecated ^ foo ^ self deprecated: [self fooDeprecated] explanation: 'The method #foo was not good. Use Bar>>newFoo instead.' ! !Deprecation methodsFor: 'accessing' stamp: 'eem 7/3/2009 19:07'! deprecationDate "Answer the value of deprecationDate" ^ deprecationDate! ! !Deprecation methodsFor: 'accessing' stamp: 'eem 7/3/2009 19:07'! explanationString "Answer the value of explanationString" ^ explanationString! ! !Deprecation methodsFor: 'accessing' stamp: 'AndrewBlack 8/31/2009 03:15'! messageText "Return an exception's message text." ^ 'The method ', methodReference stringVersion, ' has been deprecated. ', explanationString! ! !Deprecation methodsFor: 'accessing' stamp: 'eem 7/3/2009 19:07'! methodReference "Answer the value of methodReference" ^ methodReference! ! !Deprecation methodsFor: 'accessing' stamp: 'eem 7/3/2009 19:07'! versionString "Answer the value of versionString" ^ versionString! ! !Deprecation methodsFor: 'comparing' stamp: 'eem 7/3/2009 19:10'! = anObject ^self class == anObject class and: [methodReference = anObject methodReference and: [methodReference ifNil: [explanationString = anObject explanationString] ifNotNil: [true]]]! ! !Deprecation methodsFor: 'comparing' stamp: 'eem 7/3/2009 19:08'! hash ^(methodReference ifNil: [explanationString]) hash! ! !Deprecation methodsFor: 'handling' stamp: 'AndrewBlack 9/1/2009 07:45'! defaultAction Log ifNotNil: [:log| log add: self]. Preferences showDeprecationWarnings ifTrue: [Transcript nextPutAll: self messageText; cr; flush]. Preferences raiseDeprecatedWarnings ifTrue: [super defaultAction]! ! !Deprecation methodsFor: 'initialize-release' stamp: 'eem 7/3/2009 18:57'! method: aCompiledMethod explanation: anExplanationString on: dateString in: aVersionString methodReference := aCompiledMethod methodReference. explanationString := anExplanationString. deprecationDate := dateString. versionString := aVersionString ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Deprecation class instanceVariableNames: ''! !Deprecation class methodsFor: 'class initialization' stamp: 'eem 7/3/2009 19:11'! initialize "Deprecation initialize" Preferences addBooleanPreference: #showDeprecationWarnings category: #general "programming?" default: true balloonHelp: 'If enabled, use of deprecated APIs is reported to the transcript.'. Preferences addBooleanPreference: #raiseDeprecatedWarnings category: #general "programming?" default: true balloonHelp: 'If enabled, use of a deprecated API raises a Deprecated warning.'.! ! !Deprecation class methodsFor: 'instance creation' stamp: 'eem 7/3/2009 19:15'! method: aCompiledMethod explanation: anExplanationString on: dateString in: aVersionString ^self new method: aCompiledMethod explanation: anExplanationString on: dateString in: aVersionString! ! !Deprecation class methodsFor: 'logging' stamp: 'eem 7/3/2009 19:13'! deprecationsWhile: aBlock | oldLog result | oldLog := Log. Log := Set new. aBlock value. result := Log. oldLog ifNotNil: [oldLog addAll: result]. Log := oldLog. ^result! ! StandardWindow subclass: #DialogWindow instanceVariableNames: 'cancelled' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !DialogWindow commentStamp: 'gvc 5/18/2007 13:26' prior: 0! Dialog style window with no window controls (expand, collapse etc). Usually opened modally (the morph that is used to modally open determines the modal scope, use of World implies "system modal"). Designed to be subclassed with content. Supports Escape key for cancel and Enter key for default button.! !DialogWindow methodsFor: 'accessing' stamp: 'gvc 8/14/2006 14:12'! cancelled "Answer the value of cancelled" ^ cancelled! ! !DialogWindow methodsFor: 'accessing' stamp: 'gvc 8/14/2006 14:12'! cancelled: anObject "Set the value of cancelled" cancelled := anObject! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/27/2006 11:15'! acceptTextMorphs "Accept any text morphs except for those that have no edits." self allMorphs do: [:p | ((p respondsTo: #accept) and: [ (p respondsTo: #hasUnacceptedEdits) and: [ p hasUnacceptedEdits]]) ifTrue: [p accept]]! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/25/2006 10:25'! addInitialPanel "Add the panel." self addMainPanel! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/9/2007 16:52'! addMainPanel "Add the main panel." self addMorph: self newMainPanel frame: (0@0 corner: 1@1)! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/27/2006 11:11'! applyChanges "Apply the changes." self acceptTextMorphs! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/12/2009 18:14'! buttons "Answer the buttons in the button row" ^self paneMorphs last lastSubmorph submorphs! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2009 11:16'! canBeMaximized "Answer whether we are not we can be maximised." ^self isResizeable ifTrue: [super canBeMaximized] ifFalse: [false]! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/25/2006 10:10'! cancel "Cancel and close." self close! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/25/2006 10:10'! close "Close the window." self delete! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/10/2007 13:23'! defaultButton "Answer the default button." ^self findDeepSubmorphThat: [:m | (m isKindOf: PluggableButtonMorph) and: [m isDefault]] ifAbsent: [] ! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/14/2006 12:40'! defaultLabel "Answer the default label for the receiver." ^'Dialog' translated! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/10/2007 13:42'! escapePressed "Default is to cancel." self cancel! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2009 11:14'! isResizeable "Answer whether we are not we can be resized." ^false! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 2/2/2009 13:15'! mainPanel "Anwer the main panel morph or nil if not yet present." ^self paneMorphs isEmpty ifFalse: [self paneMorphs first]! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 12/3/2008 17:35'! newButtonRow "Answer a new ok/cancel button row." |answer buttons e| buttons := self newButtons. e := 0@0. buttons do: [:b | e := e max: b minExtent]. buttons do: [:b | b extent: e]. answer := Morph new color: Color transparent; changeTableLayout; cellInset: 8; listDirection: #leftToRight; listCentering: #bottomRight; hResizing: #spaceFill; vResizing: #shrinkWrap. buttons do: [:b | answer addMorphBack: b]. ^answer! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/10/2007 13:50'! newButtons "Answer new buttons as appropriate." ^{self newOKButton isDefault: true. self newCancelButton}! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/14/2006 11:58'! newContentMorph "Answer a new content morph." ^Morph new color: Color transparent; hResizing: #spaceFill; vResizing: #spaceFill! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/15/2007 17:40'! newMainPanel "Answer a new main panel." ^self newDialogPanel addMorphBack: self newContentMorph; addMorphBack: self newButtonRow; yourself! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/14/2006 14:12'! ok "Apply the changes and close." self cancelled: false; applyChanges; delete! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/10/2007 13:48'! returnPressed "Default is to do the default button." (self defaultButton ifNil: [^self]) performAction! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/12/2009 18:13'! setButtonFont: aFont "Set the font for the buttons." |buttons e hRes vRes| buttons := self buttons. e := 0@0. buttons do: [:b | hRes := b hResizing. vRes := b vResizing. b hResizing: #shrinkWrap; vResizing: #shrinkWrap. b label: b label font: aFont. e := e max: b minExtent. b hResizing: hRes; vResizing: vRes]. buttons do: [:b | b extent: e]! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 10/26/2007 21:31'! setLabelWidgetAllowance "Set the extra space required, in general, apart from the label. No extra needed for dialogs." ^labelWidgetAllowance := 0! ! !DialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2009 11:16'! wantsGrips "Answer whether the window wants edge and corner grips." ^self isResizeable! ! !DialogWindow methodsFor: 'controls' stamp: 'gvc 1/15/2007 17:14'! title: aString "Set the window title." super title: aString. label fitContents. self minimumExtent: ((label width + 20 min: (Display width // 2))@ self minimumExtent y)! ! !DialogWindow methodsFor: 'event handling' stamp: 'gvc 9/22/2009 11:17'! doubleClick: event "Handle a double click. Maximize/restore the window. Not for dialogs if not resizeable..." self isResizeable ifTrue: [super doubleClick: event]! ! !DialogWindow methodsFor: 'event handling' stamp: 'gvc 7/30/2009 12:21'! handlesKeyboard: evt "Return true if the receiver wishes to handle the given keyboard event" (super handlesKeyboard: evt) ifTrue: [^true]. ^evt keyCharacter = Character escape or: [ (self defaultButton notNil and: [ evt keyCharacter = Character cr])] ! ! !DialogWindow methodsFor: 'event handling' stamp: 'gvc 7/30/2009 12:32'! keyStroke: evt "Check for return and escape keys." super keyStroke: evt. (self defaultButton notNil and: [evt keyCharacter = Character cr]) ifTrue: [self returnPressed. ^true]. evt keyCharacter = Character escape ifTrue: [self escapePressed. ^true]. ^false! ! !DialogWindow methodsFor: 'event handling' stamp: 'gvc 9/21/2007 14:36'! keyboardFocusChange: aBoolean "Set the focus to the default button." aBoolean ifTrue: [ self defaultFocusMorph ifNotNilDo: [:b | b takeKeyboardFocus]]! ! !DialogWindow methodsFor: 'focus handling' stamp: 'gvc 4/25/2007 16:03'! defaultFocusMorph "Answer the morph that should have the keyboard focus by default when the dialog is opened." ^self defaultButton ifNil: [(self respondsTo: #nextMorphWantingFocus) ifTrue: [ self nextMorphWantingFocus]] ifNotNilDo: [:b | b enabled ifTrue: [b]]! ! !DialogWindow methodsFor: 'initialization' stamp: 'gvc 4/3/2008 11:52'! initialize "Initialize the receiver." super initialize. self cancelled: true; addInitialPanel! ! !DialogWindow methodsFor: 'initialization' stamp: 'gvc 10/25/2007 16:45'! initializeLabelArea "Initialize the label area (titlebar) for the window." super initializeLabelArea. self removeBoxes. self replaceBoxes! ! !DialogWindow methodsFor: 'initialization' stamp: 'gvc 6/1/2009 12:21'! setFramesForLabelArea "Delegate to theme." self theme configureDialogWindowLabelAreaFrameFor: self! ! !DialogWindow methodsFor: 'open/close' stamp: 'gvc 9/22/2009 11:15'! initialExtent "Answer the default extent for the receiver." |rl paneExt ext| rl := self getRawLabel. paneExt := self mainPanel ifNil: [0@0] ifNotNilDo: [:pane | pane minExtent]. ext := paneExt + (2@ self labelHeight) + (2 * self class borderWidth) max: rl extent + 20. self isResizeable ifTrue: [ self title: self title "adjust minimumExtent". self minimumExtent: (ext x max: self minimumExtent x)@(ext y max: self minimumExtent y)]. ^ext! ! !DialogWindow methodsFor: 'theme' stamp: 'gvc 5/24/2007 11:35'! activeFillStyle "Return the active fillStyle for the receiver." ^self theme dialogWindowActiveFillStyleFor: self! ! !DialogWindow methodsFor: 'theme' stamp: 'gvc 4/24/2007 16:19'! animateClose "Animate closing."! ! !DialogWindow methodsFor: 'theme' stamp: 'gvc 5/24/2007 11:36'! inactiveFillStyle "Return the active fillStyle for the receiver." ^self theme dialogWindowInactiveFillStyleFor: self! ! !DialogWindow methodsFor: 'theme' stamp: 'gvc 6/2/2009 10:26'! preferredCornerStyle "Answer the preferred corner style." ^self theme dialogWindowPreferredCornerStyleFor: self! ! !DialogWindow methodsFor: 'theme' stamp: 'gvc 6/2/2009 10:36'! wantsRoundedCorners "Answer whether rounded corners are wanted." ^(self theme dialogWindowPreferredCornerStyleFor: self) == #rounded! ! !DialogWindow methodsFor: 'top window' stamp: 'gvc 12/4/2007 16:32'! activate "Set the default focus for now, will want to remember it at some point." super activate. self world ifNil: [^self]. self rememberedKeyboardFocus ifNil: [self defaultFocusMorph ifNotNilDo: [:m | m takeKeyboardFocus]]! ! Set subclass: #Dictionary instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Collections-Unordered'! !Dictionary commentStamp: '' prior: 0! I represent a set of elements that can be viewed from one of two perspectives: a set of associations, or a container of values that are externally named where the name can be any object that responds to =. The external name is referred to as the key. I inherit many operations from Set.! !Dictionary methodsFor: '*compiler' stamp: 'ar 5/17/2003 14:07'! bindingOf: varName ^self associationAt: varName ifAbsent:[nil]! ! !Dictionary methodsFor: '*compiler' stamp: 'ar 5/18/2003 20:33'! bindingsDo: aBlock ^self associationsDo: aBlock! ! !Dictionary methodsFor: '*tools-inspector' stamp: 'ar 9/27/2005 18:32'! inspectorClass "Answer the class of the inspector to be used on the receiver. Called by inspect; use basicInspect to get a normal (less useful) type of inspector." ^ DictionaryInspector! ! !Dictionary methodsFor: 'accessing'! associationAt: key ^ self associationAt: key ifAbsent: [self errorKeyNotFound]! ! !Dictionary methodsFor: 'accessing'! associationAt: key ifAbsent: aBlock "Answer the association with the given key. If key is not found, return the result of evaluating aBlock." | index assoc | index := self findElementOrNil: key. assoc := array at: index. nil == assoc ifTrue: [ ^ aBlock value ]. ^ assoc! ! !Dictionary methodsFor: 'accessing' stamp: 'eem 6/11/2008 17:25'! associationDeclareAt: aKey "Return an existing association, or create and return a new one. Needed as a single message by ImageSegment.prepareToBeSaved." ^ self associationAt: aKey ifAbsent: [| existing | (Undeclared includesKey: aKey) ifTrue: [existing := Undeclared associationAt: aKey. Undeclared removeKey: aKey. self add: existing] ifFalse: [self add: aKey -> false]]! ! !Dictionary methodsFor: 'accessing' stamp: 'PeterHugossonMiller 9/3/2009 01:12'! associations "Answer a Collection containing the receiver's associations." | out | out := (Array new: self size) writeStream. self associationsDo: [:value | out nextPut: value]. ^ out contents! ! !Dictionary methodsFor: 'accessing'! at: key "Answer the value associated with the key." ^ self at: key ifAbsent: [self errorKeyNotFound]! ! !Dictionary methodsFor: 'accessing' stamp: 'sma 5/12/2000 15:01'! at: key ifAbsentPut: aBlock "Return the value at the given key. If key is not included in the receiver store the result of evaluating aBlock as new value." ^ self at: key ifAbsent: [self at: key put: aBlock value]! ! !Dictionary methodsFor: 'accessing' stamp: 'sma 5/12/2000 14:59'! at: key ifAbsent: aBlock "Answer the value associated with the key or, if key isn't found, answer the result of evaluating aBlock." | assoc | assoc := array at: (self findElementOrNil: key). assoc ifNil: [^ aBlock value]. ^ assoc value! ! !Dictionary methodsFor: 'accessing' stamp: 'di 3/7/2001 15:29'! at: key ifPresentAndInMemory: aBlock "Lookup the given key in the receiver. If it is present, answer the value of evaluating the given block with the value associated with the key. Otherwise, answer nil." | v | v := self at: key ifAbsent: [^ nil]. v isInMemory ifFalse: [^ nil]. ^ aBlock value: v ! ! !Dictionary methodsFor: 'accessing' stamp: 'jm 5/15/1998 07:20'! at: key ifPresent: aBlock "Lookup the given key in the receiver. If it is present, answer the value of evaluating the given block with the value associated with the key. Otherwise, answer nil." | v | v := self at: key ifAbsent: [^ nil]. ^ aBlock value: v ! ! !Dictionary methodsFor: 'accessing' stamp: 'sma 5/12/2000 15:00'! at: key put: anObject "Set the value at key to be anObject. If key is not found, create a new entry for key and set is value to anObject. Answer anObject." | index assoc | index := self findElementOrNil: key. assoc := array at: index. assoc ifNil: [self atNewIndex: index put: (Association key: key value: anObject)] ifNotNil: [assoc value: anObject]. ^ anObject! ! !Dictionary methodsFor: 'accessing' stamp: 'yo 8/27/2008 23:16'! customizeExplorerContents ^ true. ! ! !Dictionary methodsFor: 'accessing' stamp: 'ar 2/13/1999 21:16'! keyAtIdentityValue: value "Answer the key that is the external name for the argument, value. If there is none, answer nil. Note: There can be multiple keys with the same value. Only one is returned." ^self keyAtIdentityValue: value ifAbsent: [self errorValueNotFound]! ! !Dictionary methodsFor: 'accessing' stamp: 'ar 2/13/1999 21:16'! keyAtIdentityValue: value ifAbsent: exceptionBlock "Answer the key that is the external name for the argument, value. If there is none, answer the result of evaluating exceptionBlock. Note: There can be multiple keys with the same value. Only one is returned." self associationsDo: [:association | value == association value ifTrue: [^association key]]. ^exceptionBlock value! ! !Dictionary methodsFor: 'accessing' stamp: 'pmm 7/4/2009 18:01'! keyAtValue: value "Answer the key that is the external name for the argument, value. If there is none, signal an error." ^self keyAtValue: value ifAbsent: [self errorValueNotFound]! ! !Dictionary methodsFor: 'accessing' stamp: 'tk 2/18/97'! keyAtValue: value ifAbsent: exceptionBlock "Answer the key that is the external name for the argument, value. If there is none, answer the result of evaluating exceptionBlock. : Use =, not ==, so stings like 'this' can be found. Note that MethodDictionary continues to use == so it will be fast." self associationsDo: [:association | value = association value ifTrue: [^association key]]. ^exceptionBlock value! ! !Dictionary methodsFor: 'accessing'! keys "Answer a Set containing the receiver's keys." | aSet | aSet := Set new: self size. self keysDo: [:key | aSet add: key]. ^ aSet! ! !Dictionary methodsFor: 'accessing' stamp: 'sma 6/18/2000 12:56'! keysSortedSafely "Answer a SortedCollection containing the receiver's keys." | sortedKeys | sortedKeys := SortedCollection new: self size. sortedKeys sortBlock: [:x :y | "Should really be use compareSafely..." ((x isString and: [y isString]) or: [x isNumber and: [y isNumber]]) ifTrue: [x < y] ifFalse: [x class == y class ifTrue: [x printString < y printString] ifFalse: [x class name < y class name]]]. self keysDo: [:each | sortedKeys addLast: each]. ^ sortedKeys reSort! ! !Dictionary methodsFor: 'accessing' stamp: 'PeterHugossonMiller 9/3/2009 01:13'! values "Answer a Collection containing the receiver's values." | out | out := (Array new: self size) writeStream. self valuesDo: [:value | out nextPut: value]. ^ out contents! ! !Dictionary methodsFor: 'adding' stamp: 'raok 12/17/2003 16:01'! addAll: aKeyedCollection aKeyedCollection == self ifFalse: [ aKeyedCollection keysAndValuesDo: [:key :value | self at: key put: value]]. ^aKeyedCollection! ! !Dictionary methodsFor: 'adding'! add: anAssociation | index element | index := self findElementOrNil: anAssociation key. element := array at: index. element == nil ifTrue: [self atNewIndex: index put: anAssociation] ifFalse: [element value: anAssociation value]. ^ anAssociation! ! !Dictionary methodsFor: 'adding'! declare: key from: aDictionary "Add key to the receiver. If key already exists, do nothing. If aDictionary includes key, then remove it from aDictionary and use its association as the element of the receiver." (self includesKey: key) ifTrue: [^ self]. (aDictionary includesKey: key) ifTrue: [self add: (aDictionary associationAt: key). aDictionary removeKey: key] ifFalse: [self add: key -> nil]! ! !Dictionary methodsFor: 'comparing' stamp: 'cyrille.delaunay 7/17/2009 15:45'! = aDictionary "Two dictionaries are equal if (a) they are the same 'kind' of thing. (b) they have the same set of keys. (c) for each (common) key, they have the same value" self == aDictionary ifTrue: [ ^ true ]. (aDictionary isDictionary) ifFalse: [^false]. self size = aDictionary size ifFalse: [^false]. self associationsDo: [:assoc| (aDictionary at: assoc key ifAbsent: [^false]) = assoc value ifFalse: [^false]]. ^true ! ! !Dictionary methodsFor: 'enumerating'! associationsDo: aBlock "Evaluate aBlock for each of the receiver's elements (key/value associations)." super do: aBlock! ! !Dictionary methodsFor: 'enumerating' stamp: 'dtl 2/17/2003 09:40'! associationsSelect: aBlock "Evaluate aBlock with each of my associations as the argument. Collect into a new dictionary, only those associations for which aBlock evaluates to true." | newCollection | newCollection := self species new. self associationsDo: [:each | (aBlock value: each) ifTrue: [newCollection add: each]]. ^newCollection! ! !Dictionary methodsFor: 'enumerating' stamp: 'ar 6/13/2008 00:16'! collect: aBlock "Evaluate aBlock with each of my values as the argument. Collect the resulting values into a collection that is like me. Answer with the new collection." | newCollection | newCollection := self species new. self associationsDo:[:each | newCollection at: each key put: (aBlock value: each value). ]. ^newCollection! ! !Dictionary methodsFor: 'enumerating'! do: aBlock super do: [:assoc | aBlock value: assoc value]! ! !Dictionary methodsFor: 'enumerating' stamp: 'ar 7/11/1999 08:04'! keysAndValuesDo: aBlock ^self associationsDo:[:assoc| aBlock value: assoc key value: assoc value].! ! !Dictionary methodsFor: 'enumerating'! keysDo: aBlock "Evaluate aBlock for each of the receiver's keys." self associationsDo: [:association | aBlock value: association key]! ! !Dictionary methodsFor: 'enumerating' stamp: 'nice 5/22/2008 14:30'! select: aBlock "Evaluate aBlock with each of my values as the argument. Collect into a new dictionary, only those associations for which aBlock evaluates to true." | newCollection | newCollection := self copyEmpty. self associationsDo: [:each | (aBlock value: each value) ifTrue: [newCollection add: each]]. ^newCollection! ! !Dictionary methodsFor: 'enumerating' stamp: 'dtl 2/17/2003 09:48'! valuesDo: aBlock "Evaluate aBlock for each of the receiver's values." self associationsDo: [:association | aBlock value: association value]! ! !Dictionary methodsFor: 'printing' stamp: 'MPW 1/4/1901 08:33'! flattenOnStream:aStream ^aStream writeDictionary:self. ! ! !Dictionary methodsFor: 'printing' stamp: 'apb 7/14/2004 12:48'! printElementsOn: aStream aStream nextPut: $(. self size > 100 ifTrue: [aStream nextPutAll: 'size '. self size printOn: aStream] ifFalse: [self keysSortedSafely do: [:key | aStream print: key; nextPutAll: '->'; print: (self at: key); space]]. aStream nextPut: $)! ! !Dictionary methodsFor: 'printing'! storeOn: aStream | noneYet | aStream nextPutAll: '(('. aStream nextPutAll: self class name. aStream nextPutAll: ' new)'. noneYet := true. self associationsDo: [:each | noneYet ifTrue: [noneYet := false] ifFalse: [aStream nextPut: $;]. aStream nextPutAll: ' add: '. aStream store: each]. noneYet ifFalse: [aStream nextPutAll: '; yourself']. aStream nextPut: $)! ! !Dictionary methodsFor: 'removing' stamp: 'di 4/4/2000 11:47'! keysAndValuesRemove: keyValueBlock "Removes all entries for which keyValueBlock returns true." "When removing many items, you must not do it while iterating over the dictionary, since it may be changing. This method takes care of tallying the removals in a first pass, and then performing all the deletions afterward. Many places in the sytem could be simplified by using this method." | removals | removals := OrderedCollection new. self associationsDo: [:assoc | (keyValueBlock value: assoc key value: assoc value) ifTrue: [removals add: assoc key]]. removals do: [:aKey | self removeKey: aKey]! ! !Dictionary methodsFor: 'removing'! removeKey: key "Remove key from the receiver. If key is not in the receiver, notify an error." ^ self removeKey: key ifAbsent: [self errorKeyNotFound]! ! !Dictionary methodsFor: 'removing'! removeKey: key ifAbsent: aBlock "Remove key (and its associated value) from the receiver. If key is not in the receiver, answer the result of evaluating aBlock. Otherwise, answer the value externally named by key." | index assoc | index := self findElementOrNil: key. assoc := array at: index. assoc == nil ifTrue: [ ^ aBlock value ]. array at: index put: nil. tally := tally - 1. self fixCollisionsFrom: index. ^ assoc value! ! !Dictionary methodsFor: 'removing'! removeUnreferencedKeys "Undeclared removeUnreferencedKeys" ^ self unreferencedKeys do: [:key | self removeKey: key].! ! !Dictionary methodsFor: 'removing'! remove: anObject self shouldNotImplement! ! !Dictionary methodsFor: 'removing'! remove: anObject ifAbsent: exceptionBlock self shouldNotImplement! ! !Dictionary methodsFor: 'removing' stamp: 'dvf 8/23/2003 11:51'! unreferencedKeys "TextConstants unreferencedKeys" | n | ^'Scanning for references . . .' displayProgressAt: Sensor cursorPoint from: 0 to: self size during: [:bar | n := 0. self keys select: [:key | bar value: (n := n + 1). (self systemNavigation allCallsOn: (self associationAt: key)) isEmpty]]! ! !Dictionary methodsFor: 'testing' stamp: 'tween 9/13/2004 10:11'! hasBindingThatBeginsWith: aString "Answer true if the receiver has a key that begins with aString, false otherwise" self keysDo:[:each | (each beginsWith: aString) ifTrue:[^true]]. ^false! ! !Dictionary methodsFor: 'testing' stamp: 'ab 9/17/2004 00:39'! includesAssociation: anAssociation ^ (self associationAt: anAssociation key ifAbsent: [ ^ false ]) value = anAssociation value ! ! !Dictionary methodsFor: 'testing' stamp: 'sw 2/14/2000 14:34'! includesIdentity: anObject "Answer whether anObject is one of the values of the receiver. Contrast #includes: in which there is only an equality check, here there is an identity check" self do: [:each | anObject == each ifTrue: [^ true]]. ^ false! ! !Dictionary methodsFor: 'testing' stamp: 'RAA 8/23/2001 12:56'! includesKey: key "Answer whether the receiver has a key equal to the argument, key." self at: key ifAbsent: [^false]. ^true! ! !Dictionary methodsFor: 'testing'! includes: anObject self do: [:each | anObject = each ifTrue: [^true]]. ^false! ! !Dictionary methodsFor: 'testing' stamp: 'md 8/11/2005 16:49'! isDictionary ^true! ! !Dictionary methodsFor: 'testing' stamp: 'sw 3/23/2000 01:12'! keyForIdentity: anObject "If anObject is one of the values of the receive, return its key, else return nil. Contrast #keyAtValue: in which there is only an equality check, here there is an identity check" self associationsDo: [:assoc | assoc value == anObject ifTrue: [^ assoc key]]. ^ nil! ! !Dictionary methodsFor: 'testing'! occurrencesOf: anObject "Answer how many of the receiver's elements are equal to anObject." | count | count := 0. self do: [:each | anObject = each ifTrue: [count := count + 1]]. ^count! ! !Dictionary methodsFor: 'user interface' stamp: 'yo 8/27/2008 23:44'! explorerContentsWithIndexCollect: twoArgBlock | sortedKeys | sortedKeys := self keys asSortedCollection: [:x :y | ((x isString and: [y isString]) or: [x isNumber and: [y isNumber]]) ifTrue: [x < y] ifFalse: [x class == y class ifTrue: [x printString < y printString] ifFalse: [x class name < y class name]]]. ^ sortedKeys collect: [:k | twoArgBlock value: (self at: k) value: k]. ! ! !Dictionary methodsFor: 'private' stamp: 'raok 4/22/2002 12:09'! copy "Must copy the associations, or later store will affect both the original and the copy" ^ self shallowCopy withArray: (array collect: [:assoc | assoc ifNil: [nil] ifNotNil: [Association key: assoc key value: assoc value]])! ! !Dictionary methodsFor: 'private'! errorKeyNotFound self error: 'key not found'! ! !Dictionary methodsFor: 'private'! errorValueNotFound self error: 'value not found'! ! !Dictionary methodsFor: 'private'! keyAt: index "May be overridden by subclasses so that fixCollisions will work" | assn | assn := array at: index. assn == nil ifTrue: [^ nil] ifFalse: [^ assn key]! ! !Dictionary methodsFor: 'private'! noCheckAdd: anObject "Must be defined separately for Dictionary because (self findElementOrNil:) expects a key, not an association. 9/7/96 tk" array at: (self findElementOrNil: anObject key) put: anObject. tally := tally + 1! ! !Dictionary methodsFor: 'private'! rehash "Smalltalk rehash." | newSelf | newSelf := self species new: self size. self associationsDo: [:each | newSelf noCheckAdd: each]. array := newSelf array! ! !Dictionary methodsFor: 'private' stamp: 'md 10/5/2005 15:42'! scanFor: anObject "Scan the key array for the first slot containing either a nil (indicating an empty slot) or an element that matches anObject. Answer the index of that slot or zero if no slot is found. This method will be overridden in various subclasses that have different interpretations for matching elements." | element start finish | finish := array size. start := (anObject hash \\ finish) + 1. "Search from (hash mod size) to the end." start to: finish do: [:index | ((element := array at: index) == nil or: [element key = anObject]) ifTrue: [^ index ]]. "Search from 1 to where we started." 1 to: start-1 do: [:index | ((element := array at: index) == nil or: [element key = anObject]) ifTrue: [^ index ]]. ^ 0 "No match AND no empty slot"! ! !Dictionary methodsFor: 'private'! valueAtNewKey: aKey put: anObject atIndex: index declareFrom: aDictionary "Support for coordinating class variable and global declarations with variables that have been put in Undeclared so as to redirect all references to the undeclared variable." (aDictionary includesKey: aKey) ifTrue: [self atNewIndex: index put: ((aDictionary associationAt: aKey) value: anObject). aDictionary removeKey: aKey] ifFalse: [self atNewIndex: index put: (Association key: aKey value: anObject)]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Dictionary class instanceVariableNames: ''! !Dictionary class methodsFor: 'instance creation'! newFrom: aDict "Answer an instance of me containing the same associations as aDict. Error if any key appears twice." | newDictionary | newDictionary := self new: aDict size. aDict associationsDo: [:x | (newDictionary includesKey: x key) ifTrue: [self error: 'Duplicate key: ', x key printString] ifFalse: [newDictionary add: x]]. ^ newDictionary " NewDictionary newFrom: {1->#a. 2->#b. 3->#c} {1->#a. 2->#b. 3->#c} as: NewDictionary NewDictionary newFrom: {1->#a. 2->#b. 1->#c} {1->#a. 2->#b. 1->#c} as: NewDictionary "! ! !Dictionary class methodsFor: 'instance creation' stamp: 'bgf 10/25/2006 17:08'! newFromPairs: anArray "Answer an instance of me associating (anArray at:i) to (anArray at: i+i) for each odd i. anArray must have an even number of entries." | newDictionary | newDictionary := self new: (anArray size/2). 1 to: (anArray size-1) by: 2 do: [ :i| newDictionary at: (anArray at: i) put: (anArray at: i+1). ]. ^ newDictionary " Dictionary newFromPairs: {'Red' . Color red . 'Blue' . Color blue . 'Green' . Color green}. "! ! Inspector subclass: #DictionaryInspector instanceVariableNames: 'keyArray' classVariableNames: '' poolDictionaries: '' category: 'Tools-Inspector'! !DictionaryInspector methodsFor: 'accessing' stamp: 'apb 8/20/2004 23:06'! fieldList ^ self baseFieldList , (keyArray collect: [:key | key printString])! ! !DictionaryInspector methodsFor: 'initialization' stamp: 'PHK 7/21/2004 18:00'! initialize super initialize. self calculateKeyArray! ! !DictionaryInspector methodsFor: 'menu' stamp: 'rbb 3/1/2005 10:51'! addEntry | newKey aKey | newKey := UIManager default request: 'Enter new key, then type RETURN. (Expression will be evaluated for value.) Examples: #Fred ''a string'' 3+4'. aKey := Compiler evaluate: newKey. object at: aKey put: nil. self calculateKeyArray. selectionIndex := self numberOfFixedFields + (keyArray indexOf: aKey). self changed: #inspectObject. self changed: #selectionIndex. self changed: #fieldList. self update! ! !DictionaryInspector methodsFor: 'menu' stamp: 'apb 8/20/2004 21:19'! copyName "Copy the name of the current variable, so the user can paste it into the window below and work with is. If collection, do (xxx at: 1)." | sel | self selectionIndex <= self numberOfFixedFields ifTrue: [super copyName] ifFalse: [sel := String streamContents: [:strm | strm nextPutAll: '(self at: '. (keyArray at: selectionIndex - self numberOfFixedFields) storeOn: strm. strm nextPutAll: ')']. Clipboard clipboardText: sel asText "no undo allowed"]! ! !DictionaryInspector methodsFor: 'menu' stamp: 'ar 10/31/2004 17:25'! fieldListMenu: aMenu ^ aMenu labels: 'inspect copy name references objects pointing to this value senders of this key refresh view add key rename key remove basic inspect' lines: #(6 9) selections: #(inspectSelection copyName selectionReferences objectReferencesToSelection sendersOfSelectedKey refreshView addEntry renameEntry removeSelection inspectBasic) ! ! !DictionaryInspector methodsFor: 'menu' stamp: 'sd 11/20/2005 21:27'! removeSelection selectionIndex = 0 ifTrue: [^ self changed: #flash]. object removeKey: (keyArray at: selectionIndex - self numberOfFixedFields). selectionIndex := 0. contents := ''. self calculateKeyArray. self changed: #inspectObject. self changed: #selectionIndex. self changed: #fieldList. self changed: #selection.! ! !DictionaryInspector methodsFor: 'menu' stamp: 'rbb 3/1/2005 10:51'! renameEntry | newKey aKey value | value := object at: (keyArray at: selectionIndex - self numberOfFixedFields). newKey := UIManager default request: 'Enter new key, then type RETURN. (Expression will be evaluated for value.) Examples: #Fred ''a string'' 3+4' initialAnswer: (keyArray at: selectionIndex - self numberOfFixedFields) printString. aKey := Compiler evaluate: newKey. object removeKey: (keyArray at: selectionIndex - self numberOfFixedFields). object at: aKey put: value. self calculateKeyArray. selectionIndex := self numberOfFixedFields + (keyArray indexOf: aKey). self changed: #selectionIndex. self changed: #inspectObject. self changed: #fieldList. self update! ! !DictionaryInspector methodsFor: 'menu' stamp: 'ar 10/31/2004 17:26'! selectionReferences "Create a browser on all references to the association of the current selection." self selectionIndex = 0 ifTrue: [^ self changed: #flash]. object class == MethodDictionary ifTrue: [^ self changed: #flash]. self systemNavigation browseAllCallsOn: (object associationAt: (keyArray at: selectionIndex - self numberOfFixedFields)). ! ! !DictionaryInspector methodsFor: 'menu' stamp: 'ar 4/10/2005 22:17'! sendersOfSelectedKey "Create a browser on all senders of the selected key" | aKey | self selectionIndex = 0 ifTrue: [^ self changed: #flash]. ((aKey := keyArray at: selectionIndex - self numberOfFixedFields) isSymbol) ifFalse: [^ self changed: #flash]. SystemNavigation default browseAllCallsOn: aKey! ! !DictionaryInspector methodsFor: 'selecting' stamp: 'sd 11/20/2005 21:27'! addEntry: aKey object at: aKey put: nil. self calculateKeyArray. selectionIndex := self numberOfFixedFields + (keyArray indexOf: aKey). self changed: #inspectObject. self changed: #selectionIndex. self changed: #fieldList. self update! ! !DictionaryInspector methodsFor: 'selecting' stamp: 'sd 11/20/2005 21:27'! calculateKeyArray "Recalculate the KeyArray from the object being inspected" keyArray := object keysSortedSafely asArray. selectionIndex := 0. ! ! !DictionaryInspector methodsFor: 'selecting' stamp: 'di 9/22/1998 21:25'! contentsIsString "Hacked so contents empty when deselected" ^ (selectionIndex = 0)! ! !DictionaryInspector methodsFor: 'selecting' stamp: 'sd 11/20/2005 21:27'! refreshView | i | i := selectionIndex. self calculateKeyArray. selectionIndex := i. self changed: #fieldList. self changed: #contents.! ! !DictionaryInspector methodsFor: 'selecting' stamp: 'apb 8/20/2004 22:37'! replaceSelectionValue: anObject selectionIndex <= self numberOfFixedFields ifTrue: [^ super replaceSelectionValue: anObject]. ^ object at: (keyArray at: selectionIndex - self numberOfFixedFields) put: anObject! ! !DictionaryInspector methodsFor: 'selecting' stamp: 'apb 8/20/2004 21:55'! selection selectionIndex <= (self numberOfFixedFields) ifTrue: [^ super selection]. ^ object at: (keyArray at: selectionIndex - self numberOfFixedFields) ifAbsent:[nil]! ! !DictionaryInspector methodsFor: 'private' stamp: 'apb 8/20/2004 21:15'! numberOfFixedFields ^ 2 + object class instSize! ! CollectionRootTest subclass: #DictionaryTest uses: TIncludesTest + TDictionaryAddingTest + TDictionaryComparingTest + TDictionaryCopyingTest + TDictionaryEnumeratingTest + TDictionaryPrintingTest - {#testPrintElementsOn. #testStoreOn} + TDictionaryRemovingTest + TPutBasicTest - {#testAtPutOutOfBounds} + TAsStringCommaAndDelimiterTest + TPrintTest + TConvertTest + TConvertAsSortedTest + TCopyTest - {#testCopyEmptyWithout. #testCopyNonEmptyWithout. #testCopyNonEmptyWithoutNotIncluded} + TSetArithmetic + TDictionaryIncludesWithIdentityCheckTest + TDictionaryValueAccessTest + TDictionaryKeysValuesAssociationsAccess + TDictionaryKeyAccessTest + TDictionaryAssociationAccessTest + TStructuralEqualityTest + TOccurrencesForMultiplinessTest instanceVariableNames: 'emptyDict nonEmptyDict nonEmpty5ElementsNoDuplicates indexArray valueArray nonEmpty1Element collectionNotIncluded collectionIncluded associationNotIn valueNotIn keyNotIn dictionaryNotIncluded nonEmptyWithFloat dictionaryWithDuplicateValues duplicateValue' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Unordered'! !DictionaryTest methodsFor: 'helpers' stamp: 'stephane.ducasse 1/12/2009 17:24'! aValue ^ 33! ! !DictionaryTest methodsFor: 'helpers' stamp: 'stephane.ducasse 1/12/2009 17:25'! anIndex ^ #GG! ! !DictionaryTest methodsFor: 'helpers' stamp: 'stephane.ducasse 1/12/2009 17:25'! anotherValue ^ 66! ! !DictionaryTest methodsFor: 'requirement' stamp: 'stephane.ducasse 11/21/2008 15:05'! anotherElementNotIn ^ 42! ! !DictionaryTest methodsFor: 'requirement' stamp: 'delaunay 5/5/2009 14:16'! associationWithKeyAlreadyInToAdd " return an association that will be used to add to nonEmptyDict (the key of this association is already included in nonEmptyDict)" ^ (self nonEmptyDict keys anyOne)->valueNotIn .! ! !DictionaryTest methodsFor: 'requirement' stamp: 'delaunay 5/5/2009 14:15'! associationWithKeyNotInToAdd " return an association that will be used to add to nonEmptyDict" ^ associationNotIn ! ! !DictionaryTest methodsFor: 'requirement' stamp: 'damienpollet 1/13/2009 16:15'! collection ^ self nonEmptyDict! ! !DictionaryTest methodsFor: 'requirement' stamp: 'delaunay 4/2/2009 11:53'! elementNotInForOccurrences ^ 666! ! !DictionaryTest methodsFor: 'requirement' stamp: 'stephane.ducasse 11/21/2008 15:04'! empty ^ emptyDict! ! !DictionaryTest methodsFor: 'requirement' stamp: 'AlexandreBergel 1/6/2009 15:06'! emptyDict ^ emptyDict! ! !DictionaryTest methodsFor: 'requirement' stamp: 'damienpollet 1/21/2009 18:22'! expectedElementByDetect ^ 30! ! !DictionaryTest methodsFor: 'requirement' stamp: 'damienpollet 1/30/2009 17:44'! expectedSizeAfterReject self flag: 'what should this return?'! ! !DictionaryTest methodsFor: 'requirement' stamp: 'AlexandreBergel 1/6/2009 15:09'! newEmptyDict ^ self emptyDict copy! ! !DictionaryTest methodsFor: 'requirement' stamp: 'AlexandreBergel 1/6/2009 15:06'! nonEmptyDict ^ nonEmptyDict ! ! !DictionaryTest methodsFor: 'requirement' stamp: 'damienpollet 1/13/2009 16:35'! result ^ Dictionary newFromPairs: { #a . SmallInteger . #b . SmallInteger . #c . SmallInteger . #d . SmallInteger }! ! !DictionaryTest methodsFor: 'requirement' stamp: 'damienpollet 1/13/2009 16:55'! sizeCollection ^ nonEmptyDict! ! !DictionaryTest methodsFor: 'requirement' stamp: 'damienpollet 1/21/2009 18:04'! speciesClass ^ Dictionary! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 11:56'! anotherElementOrAssociationIn " return an element (or an association for Dictionary ) present in 'collection' " ^ self collection associations anyOne.! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 11:56'! anotherElementOrAssociationNotIn " return an element (or an association for Dictionary )not present in 'collection' " ^ associationNotIn ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 11:32'! collectionClass " return the class to be used to create instances of the class tested" ^ Dictionary! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 10:16'! collectionNotIncluded " return a collection for wich each element is not included in 'nonEmpty' " ^collectionNotIncluded ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 16:05'! collectionWithElement "Returns a collection that already includes what is returned by #element." ^ nonEmpty5ElementsNoDuplicates add: self element ;yourself.! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 11:09'! collectionWithElementsToRemove " return a collection of elements included in 'nonEmpty' " ^ collectionIncluded ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 5/13/2009 15:54'! collectionWithEqualElements " return a collecition including atLeast two elements equal" ^ dictionaryWithDuplicateValues ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 10:45'! collectionWithSortableElements " return a collection elements that can be sorte ( understanding message ' < ' or ' > ')" ^ nonEmpty5ElementsNoDuplicates ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 15:52'! collectionWithoutEqualElements " return a collection without equal elements" ^ nonEmpty5ElementsNoDuplicates ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 15:19'! collectionWithoutNilElements " return a collection that doesn't includes a nil element and that doesn't includes equal elements'" ^nonEmpty5ElementsNoDuplicates ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 16:08'! element ^ 30! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 14:51'! elementNotIn "return an element not included in 'nonEmpty' " ^ valueNotIn! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 10:17'! elementToAdd " return an element of type 'nonEmpy' elements'type'" ^ #u->5.! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 5/13/2009 15:54'! elementTwiceInForOccurrences " return an element included exactly two time in # collectionWithEqualElements" ^ duplicateValue ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 10:12'! indexInNonEmpty " return an index between bounds of 'nonEmpty' " ^ #a! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 15:52'! integerCollectionWithoutEqualElements " return a collection of integer without equal elements" ^ nonEmpty5ElementsNoDuplicates ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 5/4/2009 16:05'! keyNotIn " return a key not included in nonEmpty" ^ keyNotIn ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 15:00'! keyNotInNonEmpty " return a key not included in nonEmpty" ^ keyNotIn ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 5/5/2009 15:21'! keyNotInNonEmptyDict " return a key not included in nonEmptyDict" ^ keyNotIn ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'stephane.ducasse 11/21/2008 15:04'! nonEmpty ^ nonEmptyDict! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 15:24'! nonEmpty1Element " return a collection of size 1 including one element" ^ nonEmpty1Element ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 5/6/2009 10:09'! nonEmptyDifferentFromNonEmptyDict " return a dictionary for which all keys are not included in nonEmptyDict" ^ dictionaryNotIncluded ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 5/12/2009 11:07'! nonEmptyWithCopyNonIdentical. " return a collection including elements for wich copy is not identical to the initial element ( this is not the cas of Integer )" ^nonEmptyWithFloat ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 5/5/2009 10:41'! nonEmptyWithoutEqualsValues " return a dictionary that doesn't include equal values'" ^nonEmpty5ElementsNoDuplicates ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/28/2009 16:04'! otherCollection "Returns a collection that does not include what is returned by #element." ^ nonEmpty5ElementsNoDuplicates ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 5/5/2009 10:41'! valueNotIn " return a value not included in nonEmpty " ^valueNotIn ! ! !DictionaryTest methodsFor: 'requirements' stamp: 'delaunay 4/29/2009 15:00'! valueNotInNonEmpty " return a value not included in nonEmpty" ^ valueNotIn ! ! !DictionaryTest methodsFor: 'setup' stamp: 'AlexandreBergel 1/14/2009 15:14'! classToBeTested ^ Dictionary! ! !DictionaryTest methodsFor: 'setup' stamp: 'delaunay 5/13/2009 15:54'! setUp emptyDict := self classToBeTested new. nonEmptyDict := self classToBeTested new. nonEmptyDict at: #a put: self elementTwiceIn; at: #b put: 30; at: #c put: self elementTwiceIn; at: #d put: -2. nonEmpty5ElementsNoDuplicates := self classToBeTested new at: #a put: 5; at: #b put: 4; at: #c put: 7; at: #d put: 6; at: #e put: 9; yourself. valueNotIn := 666. keyNotIn := #z . associationNotIn := keyNotIn->valueNotIn. dictionaryNotIncluded := Dictionary new add: associationNotIn ;yourself. collectionNotIncluded := { valueNotIn. valueNotIn }. collectionIncluded := { (self elementTwiceIn) }. indexArray := #(2 3 1 ). valueArray := #(5 5 5 ). nonEmpty1Element := self classToBeTested new at: #a put: 5; yourself. nonEmptyWithFloat := Dictionary new add: #A->2.5; add: #b->3.5 ; yourself. duplicateValue := 2.5. dictionaryWithDuplicateValues := Dictionary new add: #A->duplicateValue ; add: #b->3.5 ; add: #C->duplicateValue ; yourself. ! ! !DictionaryTest methodsFor: 'test - adding' stamp: 'delaunay 5/5/2009 12:08'! testAdd "| dict | dict := self emptyDict. dict add: #a -> 1. dict add: #b -> 2. self assert: (dict at: #a) = 1. self assert: (dict at: #b) = 2" | dictionary result | dictionary := self nonEmptyDict. result := dictionary add: self associationWithKeyNotInToAdd. self assert: result = self associationWithKeyNotInToAdd! ! !DictionaryTest methodsFor: 'test - adding'! testAddAll | collectionToAdd collection result oldSize | collection := self nonEmptyDict . oldSize := collection size. collectionToAdd := Dictionary new add: self associationWithKeyAlreadyInToAdd ; add: self associationWithKeyNotInToAdd ; yourself. result := collection addAll: collectionToAdd . self assert: result = collectionToAdd . " the association with the key already in should have replaced the oldest :" self assert: collection size = (oldSize + 1). result associationsDo: [:assoc | self assert: (collection at: (assoc key) ) = assoc value].! ! !DictionaryTest methodsFor: 'test - adding' stamp: 'delaunay 5/5/2009 12:08'! testAddWithKeyAlreadyIn | dictionary result association | dictionary := self nonEmptyDict. association := self associationWithKeyNotInToAdd. result := dictionary add: association. self assert: result = association. self assert: (dictionary at: association key) = association value! ! !DictionaryTest methodsFor: 'test - adding' stamp: 'delaunay 5/5/2009 12:08'! testAddWithKeyNotIn | dictionary result association | dictionary := self nonEmptyDict. association := self associationWithKeyNotInToAdd. result := dictionary add: association. self assert: result = association. self assert: (dictionary at: association key) = association value! ! !DictionaryTest methodsFor: 'test - adding'! testDeclareFrom | newDict v dictionary keyIn associationKeyNotIn | dictionary := self nonEmptyDict. keyIn := dictionary keys anyOne. associationKeyNotIn := self associationWithKeyNotInToAdd . newDict := Dictionary new add: associationKeyNotIn ; yourself. "if the key already exist, nothing changes" v := dictionary at: keyIn. dictionary declare: keyIn from: newDict. self assert: (dictionary at: keyIn ) = v. "if the key does not exist, then it gets removed from newDict and is added to the receiver" self nonEmptyDict declare: associationKeyNotIn key from: newDict. self assert: (dictionary at: associationKeyNotIn key) = associationKeyNotIn value. self assert: (newDict size = 0)! ! !DictionaryTest methodsFor: 'test - comparing'! testEquality | nonEmptyDict2 | nonEmptyDict2 := self nonEmpty class new. self nonEmpty keysAndValuesDo: [ :key :value | nonEmptyDict2 at: key put: value ]. self assert: (self nonEmptyDict = nonEmptyDict2)! ! !DictionaryTest methodsFor: 'test - copying'! testDictionaryConcatenationWithCommonKeys | dictionary1 dictionary2 result | dictionary1 := self nonEmptyDict. dictionary2 := self nonEmptyDict. result := dictionary1 , dictionary2. self assert: result size = ( dictionary2 size). dictionary2 associationsDo: [ :assoc | self assert: (result at: assoc key) = assoc value ]! ! !DictionaryTest methodsFor: 'test - copying'! testDictionaryConcatenationWithCommonKeysDifferentValues | dictionary1 dictionary2 result value | dictionary1 := self nonEmptyDict. value := self nonEmptyDifferentFromNonEmptyDict values anyOne. dictionary2 := dictionary1 copy. dictionary2 keys do: [ :key | dictionary2 at: key put: value ]. result := dictionary1 , dictionary2. self assert: result size = ( dictionary2 size). dictionary2 associationsDo: [ :assoc | self assert: (result at: assoc key) = assoc value ]! ! !DictionaryTest methodsFor: 'test - copying' stamp: 'delaunay 5/6/2009 10:12'! testDictionaryConcatenationWithoutCommonKeys "self run: #testDictionaryConcatenation" "| dict1 dict2 dict3 | dict1 := self emptyDict. dict1 at: #a put: 'Nicolas' ; at: #b put: 'Damien'. dict2 := self emptyDict. dict2 at: #a put: 'Christophe' ; at: #c put: 'Anthony'. dict3 := dict1, dict2. self assert: (dict3 at: #a) = 'Christophe'. self assert: (dict3 at: #b) = 'Damien'. self assert: (dict3 at: #c) = 'Anthony'. " | dictionary1 dictionary2 result | dictionary1 := self nonEmptyDict. dictionary2 := self nonEmptyDifferentFromNonEmptyDict. result := dictionary1 , dictionary2. self assert: result size = (dictionary1 size + dictionary2 size). dictionary1 associationsDo: [ :assoc | self assert: (result at: assoc key) = assoc value ]. dictionary2 associationsDo: [ :assoc | self assert: (result at: assoc key) = assoc value ]! ! !DictionaryTest methodsFor: 'test - equality'! testEqualSign "self debug: #testEqualSign" self deny: (self empty = self nonEmpty).! ! !DictionaryTest methodsFor: 'test - equality'! testEqualSignIsTrueForNonIdenticalButEqualCollections "self debug: #testEqualSignIsTrueForNonIdenticalButEqualCollections" self assert: (self empty = self empty copy). self assert: (self empty copy = self empty). self assert: (self empty copy = self empty copy). self assert: (self nonEmpty = self nonEmpty copy). self assert: (self nonEmpty copy = self nonEmpty). self assert: (self nonEmpty copy = self nonEmpty copy).! ! !DictionaryTest methodsFor: 'test - equality'! testEqualSignOfIdenticalCollectionObjects "self debug: #testEqualSignOfIdenticalCollectionObjects" self assert: (self empty = self empty). self assert: (self nonEmpty = self nonEmpty). ! ! !DictionaryTest methodsFor: 'test - new' stamp: 'delaunay 5/4/2009 14:24'! testNew | d | d := self classToBeTested new: 10. self assert: d size = 0. "Why 14? Mysterious" "self assert: d capacity = 14"! ! !DictionaryTest methodsFor: 'test - removing'! testKeysAndValuesRemove | oldSize collection keyIn | collection := self nonEmptyDict . oldSize := collection size. keyIn := collection keys anyOne. collection keysAndValuesRemove: [:key :value | key == self keyNotInNonEmptyDict ]. self assert: (collection size = (oldSize )). collection keysAndValuesRemove: [:key :value | key == keyIn ]. self assert: (collection size = (oldSize - 1)). self should: [ collection at: keyIn ] raise: Error.! ! !DictionaryTest methodsFor: 'test - removing'! testRemove self should: [self nonEmptyDict remove: nil] raise: Error. self should: [self nonEmptyDict remove: nil ifAbsent: ['What ever here']] raise: Error.! ! !DictionaryTest methodsFor: 'test - removing'! testRemoveKey "self debug: #testRemoveKey" | collection oldSize keyIn | collection := self nonEmptyDict . oldSize := collection size. keyIn := collection keys anyOne. collection removeKey: keyIn . self assert: (collection size = (oldSize - 1)). self should: [ (collection at: keyIn )] raise: Error. self should: [collection removeKey: self keyNotInNonEmptyDict ] raise: Error! ! !DictionaryTest methodsFor: 'test - removing'! testRemoveKeyIfAbsent | collection oldSize keyIn value result | collection := self nonEmptyDict . oldSize := collection size. keyIn := collection keys anyOne. value := collection at: keyIn . result := collection removeKey: keyIn ifAbsent: [888]. self assert: result = value. self assert: (collection size = (oldSize - 1)). self should: [ (collection at: keyIn )] raise: Error. self assert: (collection removeKey: self keyNotInNonEmptyDict ifAbsent: [888] ) = 888.! ! !DictionaryTest methodsFor: 'test - testing' stamp: 'AlexandreBergel 1/6/2009 11:56'! testHasBindingThatBeginsWith | newDict | newDict := Dictionary new at: #abc put: 10; at: #abcd put: 100; at: #def put: 20; yourself. self assert: (newDict hasBindingThatBeginsWith: 'ab'). self assert: (newDict hasBindingThatBeginsWith: 'def'). self deny: (newDict hasBindingThatBeginsWith: 'defg').! ! !DictionaryTest methodsFor: 'test - testing' stamp: 'damienpollet 1/30/2009 17:55'! testIncludeAssociation self assert: (nonEmptyDict includesAssociation: #a -> self elementTwiceIn). self assert: (nonEmptyDict includesAssociation: (nonEmptyDict associations first)). ! ! !DictionaryTest methodsFor: 'test - testing' stamp: 'damienpollet 1/30/2009 17:57'! testIncludes | o1 o2 newDict | self assert: (nonEmptyDict includes: self element). o1 := 2 @ 3. o2 := 2 @ 3. self deny: (o1 == o2). self assert: (o1 = o2). newDict := Dictionary new. newDict at: #a put: o1. self assert: (newDict includes: o2). ! ! !DictionaryTest methodsFor: 'test - testing' stamp: 'GabrielOmarCotelli 6/6/2009 19:07'! testIncludesAssociationNoValue | association dictionary | association := Association key: #key. self assert: association value isNil. dictionary := Dictionary new. dictionary add: association. self assert: (dictionary at: #key) isNil ! ! !DictionaryTest methodsFor: 'test - testing' stamp: 'GabrielOmarCotelli 6/6/2009 19:08'! testIncludesAssociationWithValue | association dictionary | association := Association key: #key value: 1. dictionary := Dictionary new. dictionary add: association. self assert: (dictionary at: #key) = 1 ! ! !DictionaryTest methodsFor: 'test - testing' stamp: 'AlexandreBergel 1/6/2009 13:48'! testIsDictionary self deny: Object new isDictionary. self assert: nonEmptyDict isDictionary. self assert: emptyDict isDictionary.! ! !DictionaryTest methodsFor: 'test - testing' stamp: 'damienpollet 1/30/2009 17:57'! testKeyForIdentity self assert: (nonEmptyDict keyForIdentity: 30) = #b. "The value 20 is associated to two different associations" self assert: (#(a c) includes: (nonEmptyDict keyForIdentity: self elementTwiceIn))! ! !DictionaryTest methodsFor: 'test - testing' stamp: 'stephane.ducasse 5/20/2009 18:08'! testOccurrencesOf "self run:#testOccurrencesOf" | dict | dict := Dictionary new. dict at: #a put: 1. dict at: #b put: 2. dict at: #c put: 1. dict at: #d put: 3. dict at: nil put: nil. dict at: #z put: nil. self assert: (dict occurrencesOf: 1 ) = 2. self assert: (dict occurrencesOf: nil ) = 2. ! ! !DictionaryTest methodsFor: 'tests - Dictionary keys values associations access'! testAssociations | collection result | collection := self nonEmpty . result := collection associations. self assert: result size = collection size. result do: [:assoc | self assert: (assoc value) = (collection at: assoc key) ]. "keys do: [ :key | self assert: ( result at: key ) = ( collection at: key )] ." ! ! !DictionaryTest methodsFor: 'tests - Dictionary keys values associations access'! testKeys | collection result | collection := self nonEmpty. result := collection keys. result do: [ :key | self shouldnt: [collection at: key ] raise:Error ]. self assert: result size = collection size . self should: [result detect: [:each | (result occurrencesOf: each ) > 1] ] raise: Error. ! ! !DictionaryTest methodsFor: 'tests - Dictionary keys values associations access'! testKeysSortedSafely | collection result | collection := self nonEmpty. result := collection keysSortedSafely . result do: [ :key | self shouldnt: [collection at: key ] raise:Error ]. self assert: result size = collection size . self should: [result detect: [:each | (result occurrencesOf: each ) > 1] ] raise: Error. self assert: result asArray isSorted.! ! !DictionaryTest methodsFor: 'tests - Dictionary keys values associations access'! testValues | collection result | collection := self nonEmpty . result := collection values. self assert: result size = collection size. result do: [:each | self assert: (collection occurrencesOf:each ) = (result occurrencesOf: each) ]. ! ! !DictionaryTest methodsFor: 'tests - DictionaryIndexAccessing'! testAt | collection association | collection := self nonEmpty . association := collection associations anyOne. self assert: (collection at: association key) = association value.! ! !DictionaryTest methodsFor: 'tests - DictionaryIndexAccessing'! testAtError "self run: #testAtError" | dict keyNotIn keyIn | dict := self nonEmpty . keyNotIn := self keyNotIn . keyIn := dict keys anyOne. self shouldnt: [ dict at: keyIn ] raise: Error. self should: [ dict at: keyNotIn ] raise: Error. ! ! !DictionaryTest methodsFor: 'tests - DictionaryIndexAccessing'! testAtIfAbsent | collection association | collection := self nonEmpty . association := collection associations anyOne. self assert: (collection at: association key ifAbsent: [ 888 ]) = association value. self assert: (collection at: self keyNotIn ifAbsent: [ 888 ]) = 888.! ! !DictionaryTest methodsFor: 'tests - DictionaryIndexAccessing'! testAtIfAbsentPut | collection association | collection := self nonEmpty . association := collection associations anyOne. collection at: association key ifAbsentPut: [ 888 ]. self assert: (collection at: association key) = association value. collection at: self keyNotIn ifAbsentPut: [ 888 ]. self assert: ( collection at: self keyNotIn ) = 888.! ! !DictionaryTest methodsFor: 'tests - DictionaryIndexAccessing'! testAtIfPresent "self run: #testAtIfAbsent" | t collection association keyNotIn | collection := self nonEmpty . association := collection associations anyOne. keyNotIn := self keyNotIn . t := false. self nonEmptyDict at: association key ifPresent: [:x | t := (x = association value)]. self assert: t. self assert: (self nonEmptyDict at: association key ifPresent: [:x | 'ABCDEF']) = 'ABCDEF'. self assert: (self nonEmptyDict at: keyNotIn ifPresent: [:x | Error signal]) isNil ! ! !DictionaryTest methodsFor: 'tests - DictionaryIndexAccessing'! testAtPutDict "self run: #testAtPutDict" "self debug: #testAtPutDict" | adictionary keyIn | adictionary := self nonEmpty . keyIn := adictionary keys anyOne. adictionary at: keyIn put: 'new'. self assert: (adictionary at: keyIn ) = 'new'. adictionary at: keyIn put: 'newnew'. self assert: (adictionary at: keyIn ) = 'newnew'. adictionary at: self keyNotIn put: 666. self assert: (adictionary at: self keyNotIn ) = 666.! ! !DictionaryTest methodsFor: 'tests - DictionaryIndexAccessing'! testAtPutNil "self run: #testAtPut" "self debug: #testAtPut" | dict keyIn | dict := self nonEmpty . keyIn := dict keys anyOne. dict at: nil put: 'new'. self assert: (dict at: nil) = 'new'. dict at: keyIn put: nil. self assert: (dict at: keyIn ) isNil. dict at: self keyNotIn put: nil. self assert: ( dict at: self keyNotIn ) isNil. dict at: nil put: nil. self assert: (dict at: nil) isNil.! ! !DictionaryTest methodsFor: 'tests - as sorted collection'! testAsSortedArray | result collection | collection := self collectionWithSortableElements . result := collection asSortedArray. self assert: (result class includesBehavior: Array). self assert: result isSorted. self assert: result size = collection size! ! !DictionaryTest methodsFor: 'tests - as sorted collection'! testAsSortedCollection | aCollection result | aCollection := self collectionWithSortableElements . result := aCollection asSortedCollection. self assert: (result class includesBehavior: SortedCollection). result do: [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. self assert: result size = aCollection size.! ! !DictionaryTest methodsFor: 'tests - as sorted collection'! testAsSortedCollectionWithSortBlock | result tmp | result := self collectionWithSortableElements asSortedCollection: [:a :b | a > b]. self assert: (result class includesBehavior: SortedCollection). result do: [ :each | self assert: (self collectionWithSortableElements occurrencesOf: each) = (result occurrencesOf: each) ]. self assert: result size = self collectionWithSortableElements size. tmp:=result at: 1. result do: [:each| self assert: tmp>=each. tmp:=each]. ! ! !DictionaryTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsCommaStringEmpty self assert: self empty asCommaString = ''. self assert: self empty asCommaStringAnd = ''. ! ! !DictionaryTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsCommaStringMore | result resultAnd index allElementsAsString tmp | result:= self nonEmpty asCommaString . resultAnd:= self nonEmpty asCommaStringAnd . tmp :=OrderedCollection new. self nonEmpty do: [ :each | tmp add: each asString]. "verifying result :" index := 1. allElementsAsString := (result findBetweenSubStrs: ', ' ). allElementsAsString do: [:each | self assert: (tmp occurrencesOf: each)=(allElementsAsString occurrencesOf: each). ]. "verifying esultAnd :" allElementsAsString:=(resultAnd findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) | i= allElementsAsString size ifTrue: [self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i))]. i=(allElementsAsString size-1) ifTrue:[ self assert: (allElementsAsString at:i)=('and')]. ].! ! !DictionaryTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsCommaStringOne self nonEmpty1Element do: [:each | self assert: each asString =self nonEmpty1Element asCommaString. self assert: each asString=self nonEmpty1Element asCommaStringAnd.]. ! ! !DictionaryTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterEmpty | delim emptyStream | delim := ', '. emptyStream := ReadWriteStream on: ''. self empty asStringOn: emptyStream delimiter: delim. self assert: emptyStream contents = ''. ! ! !DictionaryTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterLastEmpty | delim emptyStream | delim := ', '. emptyStream := ReadWriteStream on: ''. self empty asStringOn: emptyStream delimiter: delim last:'and'. self assert: emptyStream contents = ''. ! ! !DictionaryTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterLastMore | delim multiItemStream result last allElementsAsString tmp | delim := ', '. last := 'and'. result:=''. tmp := self nonEmpty collect: [:each | each asString]. multiItemStream := ReadWriteStream on:result. self nonEmpty asStringOn: multiItemStream delimiter: ', ' last: last. allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) | i= allElementsAsString size ifTrue: [self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i))]. i=(allElementsAsString size-1) ifTrue:[ self assert: (allElementsAsString at:i)=('and')]. ]. ! ! !DictionaryTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterLastOne | delim oneItemStream result | delim := ', '. result:=''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim last: 'and'. oneItemStream do: [:each1 | self nonEmpty1Element do: [:each2 |self assert: each1 = (each2 asString) ] ]. ! ! !DictionaryTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterMore | delim multiItemStream result allElementsAsString tmp | delim := ', '. result:=''. tmp:= self nonEmpty collect:[:each | each asString]. multiItemStream := ReadWriteStream on:result. self nonEmpty asStringOn: multiItemStream delimiter: ', '. allElementsAsString := (result findBetweenSubStrs: ', ' ). allElementsAsString do: [:each | self assert: (tmp occurrencesOf: each)=(allElementsAsString occurrencesOf: each). ].! ! !DictionaryTest methodsFor: 'tests - as string comma delimiter sequenceable'! testAsStringOnDelimiterOne | delim oneItemStream result | delim := ', '. result:=''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim. oneItemStream do: [:each1 | self nonEmpty1Element do: [:each2 |self assert: each1 = (each2 asString) ] ]. ! ! !DictionaryTest methodsFor: 'tests - at put'! testAtPut "self debug: #testAtPut" self nonEmpty at: self anIndex put: self aValue. self assert: (self nonEmpty at: self anIndex) = self aValue. ! ! !DictionaryTest methodsFor: 'tests - at put'! testAtPutTwoValues "self debug: #testAtPutTwoValues" self nonEmpty at: self anIndex put: self aValue. self nonEmpty at: self anIndex put: self anotherValue. self assert: (self nonEmpty at: self anIndex) = self anotherValue.! ! !DictionaryTest methodsFor: 'tests - converting'! assertNoDuplicates: aCollection whenConvertedTo: aClass | result | result := self collectionWithEqualElements asIdentitySet. self assert: (result class includesBehavior: IdentitySet). self collectionWithEqualElements do: [ :initial | self assert: (result occurrencesOf: initial) = 1 ]! ! !DictionaryTest methodsFor: 'tests - converting'! assertNonDuplicatedContents: aCollection whenConvertedTo: aClass | result | result := aCollection perform: ('as' , aClass name) asSymbol. self assert: (result class includesBehavior: aClass). result do: [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. ^ result! ! !DictionaryTest methodsFor: 'tests - converting'! assertSameContents: aCollection whenConvertedTo: aClass | result | result := self assertNonDuplicatedContents: aCollection whenConvertedTo: aClass. self assert: result size = aCollection size! ! !DictionaryTest methodsFor: 'tests - converting'! testAsArray "self debug: #testAsArray3" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Array! ! !DictionaryTest methodsFor: 'tests - converting'! testAsBag self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Bag! ! !DictionaryTest methodsFor: 'tests - converting'! testAsByteArray | res | self shouldnt: [self integerCollectionWithoutEqualElements ] raise: Error. self integerCollectionWithoutEqualElements do: [ :each | self assert: each class = SmallInteger] . res := true. self integerCollectionWithoutEqualElements detect: [ :each | (self integerCollectionWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false. self assertSameContents: self integerCollectionWithoutEqualElements whenConvertedTo: ByteArray! ! !DictionaryTest methodsFor: 'tests - converting'! testAsIdentitySet "test with a collection without equal elements :" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: IdentitySet. ! ! !DictionaryTest methodsFor: 'tests - converting'! testAsOrderedCollection self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: OrderedCollection! ! !DictionaryTest methodsFor: 'tests - converting'! testAsSet | | "test with a collection without equal elements :" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Set. ! ! !DictionaryTest methodsFor: 'tests - copy'! testCopyEmptyWith "self debug: #testCopyWith" | res element | element := self elementToAdd. res := self empty copyWith: element. self assert: res size = (self empty size + 1). self assert: (res includes: (element value))! ! !DictionaryTest methodsFor: 'tests - copy'! testCopyEmptyWithoutAll "self debug: #testCopyEmptyWithoutAll" | res | res := self empty copyWithoutAll: self collectionWithElementsToRemove. self assert: res size = self empty size. self collectionWithElementsToRemove do: [ :each | self deny: (res includes: each) ]! ! !DictionaryTest methodsFor: 'tests - copy'! testCopyNonEmptyWith "self debug: #testCopyNonEmptyWith" | res element | element := self elementToAdd . res := self nonEmpty copyWith: element. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self assert: (res includes: (element value)). self nonEmpty do: [ :each | res includes: each ]! ! !DictionaryTest methodsFor: 'tests - copy'! testCopyNonEmptyWithoutAll "self debug: #testCopyNonEmptyWithoutAll" | res | res := self nonEmpty copyWithoutAll: self collectionWithElementsToRemove. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self collectionWithElementsToRemove do: [ :each | self deny: (res includes: (each)) ]. self nonEmpty do: [ :each | (self collectionWithElementsToRemove includes: each) ifFalse: [ self assert: (res includes: each) ] ]! ! !DictionaryTest methodsFor: 'tests - copy'! testCopyNonEmptyWithoutAllNotIncluded "self debug: #testCopyNonEmptyWithoutAllNotIncluded" | res | res := self nonEmpty copyWithoutAll: self collectionNotIncluded. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self nonEmpty do: [ :each | self assert: (res includes: each) ]! ! !DictionaryTest methodsFor: 'tests - copy - clone'! testCopyCreatesNewObject "self debug: #testCopyCreatesNewObject" | copy | copy := self nonEmpty copy. self deny: self nonEmpty == copy. ! ! !DictionaryTest methodsFor: 'tests - copy - clone'! testCopyEmpty "self debug: #testCopyEmpty" | copy | copy := self empty copy. self assert: copy isEmpty.! ! !DictionaryTest methodsFor: 'tests - copy - clone'! testCopyNonEmpty "self debug: #testCopyNonEmpty" | copy | copy := self nonEmpty copy. self deny: copy isEmpty. self assert: copy size = self nonEmpty size. self nonEmpty do: [:each | copy includes: each]! ! !DictionaryTest methodsFor: 'tests - dictionary assocition access'! testAssociationAt | collection keyIn result | collection := self nonEmpty. keyIn := collection keys anyOne. result := collection associationAt: keyIn. self assert: (result key) = keyIn. self assert: (result value ) = (collection at: keyIn ).! ! !DictionaryTest methodsFor: 'tests - dictionary assocition access'! testAssociationAtError | collection keyNotIn | collection := self nonEmpty. keyNotIn := self keyNotIn . self should: [collection associationAt: keyNotIn] raise: Error. ! ! !DictionaryTest methodsFor: 'tests - dictionary assocition access'! testAssociationAtIfAbsent | collection keyIn result | collection := self nonEmpty. keyIn := collection keys anyOne. result := collection associationAt: keyIn ifAbsent: [888]. self assert: (result key) = keyIn. self assert: (result value ) = (collection at: keyIn ). self assert: (collection associationAt: self keyNotIn ifAbsent: [888] ) = 888! ! !DictionaryTest methodsFor: 'tests - dictionary assocition access'! testAssociationDeclareAt | collection keyIn result | collection := self nonEmpty. keyIn := collection keys anyOne. result := collection associationDeclareAt: keyIn . self assert: (result key) = keyIn. self assert: (result value ) = (collection at: keyIn ). result := collection associationDeclareAt: self keyNotIn . self shouldnt: [collection at: self keyNotIn ] raise: Error. self assert: (collection at: self keyNotIn ) = false.! ! !DictionaryTest methodsFor: 'tests - dictionary including'! testIncludesAssociation | associationNotIn associationIn keyIn valueIn | keyIn := self nonEmpty keys anyOne. valueIn := self nonEmpty values anyOne. associationNotIn := self keyNotInNonEmpty -> self valueNotInNonEmpty . associationIn := self nonEmpty associations anyOne. self assert: (self nonEmpty includesAssociation: associationIn ). self deny: (self nonEmpty includesAssociation: associationNotIn ). " testing the case where key is included but not with the same value :" self deny: (self nonEmpty includesAssociation: (keyIn-> self valueNotInNonEmpty )). " testing the case where value is included but not corresponding key :" self deny: (self nonEmpty includesAssociation: (self keyNotInNonEmpty -> valueIn )). ! ! !DictionaryTest methodsFor: 'tests - dictionary including'! testIncludesComportementForDictionnary | valueIn collection keyIn | collection := self nonEmpty. valueIn := collection values anyOne. keyIn := collection keys anyOne. self assert: (collection includes: valueIn). self deny: (collection includes: self valueNotInNonEmpty). " testing that includes take only care of values :" self deny: (collection includes: keyIn)! ! !DictionaryTest methodsFor: 'tests - dictionary including'! testIncludesIdentityBasicComportement | valueIn collection | collection := self nonEmpty . valueIn := collection values anyOne. self assert: (collection includesIdentity: valueIn ) . self deny: (collection includesIdentity: self valueNotInNonEmpty ).! ! !DictionaryTest methodsFor: 'tests - dictionary including'! testIncludesIdentitySpecificComportement | valueIn collection | collection := self nonEmptyWithCopyNonIdentical . valueIn := collection values anyOne. self assert: (collection includesIdentity: valueIn ) . self deny: (collection includesIdentity: valueIn copy ) . ! ! !DictionaryTest methodsFor: 'tests - dictionary including'! testIncludesKey | collection keyIn keyNotIn | collection := self nonEmpty . keyIn := collection keys anyOne. keyNotIn := self keyNotInNonEmpty. self assert: ( collection includesKey: keyIn ). self deny: ( collection includesKey: keyNotIn ).! ! !DictionaryTest methodsFor: 'tests - dictionary key access'! testKeyAtIdentityValue | dict value result | dict := self nonEmpty . value := dict values anyOne. result := dict keyAtIdentityValue: value. self assert: (dict at: result) = value. self should: [dict keyAtIdentityValue: self valueNotIn ] raise: Error ! ! !DictionaryTest methodsFor: 'tests - dictionary key access'! testKeyAtIdentityValueIfAbsent "self run: #testKeyAtValue" "self debug: #testKeyAtValue" | dict value result | dict := self nonEmpty . value := dict values anyOne. result := dict keyAtIdentityValue: value ifAbsent: [nil]. self assert: (dict at: result) = value. self assert: (dict keyAtIdentityValue: self valueNotIn ifAbsent: [nil] ) = nil. ! ! !DictionaryTest methodsFor: 'tests - dictionary key access'! testKeyAtValue "self run: #testKeyAtValue" "self debug: #testKeyAtValue" | dict value result | dict := self nonEmpty . value := dict values anyOne. result := dict keyAtValue: value. self assert: (dict at: result) = value. self should: [dict keyAtValue: self valueNotIn ] raise: Error ! ! !DictionaryTest methodsFor: 'tests - dictionary key access'! testKeyAtValueIfAbsent "self run: #testKeyAtValue" "self debug: #testKeyAtValue" | dict value result | dict := self nonEmpty . value := dict values anyOne. result := dict keyAtValue: value ifAbsent: [nil]. self assert: (dict at: result) = value. self assert: (dict keyAtValue: self valueNotIn ifAbsent: [nil] ) = nil. ! ! !DictionaryTest methodsFor: 'tests - dictionnary enumerating'! testAssociationsDo | collection keys | collection := self nonEmptyDict . keys := OrderedCollection new. collection associationsDo: [ :assoc | keys add: assoc key. self assert: ( collection at: assoc key ) = assoc value. ]. collection keys do: [:key | self assert: ( keys occurrencesOf: key ) = (collection keys occurrencesOf: key)].! ! !DictionaryTest methodsFor: 'tests - dictionnary enumerating'! testAssociationsSelect | collection keys result | collection := self nonEmptyDict . keys := OrderedCollection new. result := collection associationsSelect: [ :assoc | keys add: assoc key. true]. collection keys do: [ :key | self assert: (collection keys occurrencesOf: key) = (keys occurrencesOf: key)]. self assert: result = collection.! ! !DictionaryTest methodsFor: 'tests - dictionnary enumerating'! testCollect | collection values result | collection := self nonEmptyDict . values := OrderedCollection new. result := collection collect: [ :value | values add: value. ]. collection values do: [ :value | self assert: (collection values occurrencesOf: value) = (values occurrencesOf: value)]. self assert: result = collection.! ! !DictionaryTest methodsFor: 'tests - dictionnary enumerating'! testDo | t collection | collection := self nonEmptyDict . t := OrderedCollection new. collection do: [: value | t add: value ]. t do: [ :each | self assert: (t occurrencesOf: each ) = ( collection values occurrencesOf: each) ].! ! !DictionaryTest methodsFor: 'tests - dictionnary enumerating'! testKeysAndValuesDo | collection keys | collection := self nonEmptyDict . keys := OrderedCollection new. collection keysAndValuesDo: [ :key :value | keys add: key. self assert: (collection at: key) = value ]. collection keys do: [ :key | self assert: (collection keys occurrencesOf: key) = (keys occurrencesOf: key)]! ! !DictionaryTest methodsFor: 'tests - dictionnary enumerating'! testKeysDo | collection keys | collection := self nonEmptyDict . keys := OrderedCollection new. collection keysDo: [ :key | keys add: key. ]. collection keys do: [ :key | self assert: (collection keys occurrencesOf: key) = (keys occurrencesOf: key)]! ! !DictionaryTest methodsFor: 'tests - dictionnary enumerating'! testReject "Ensure that Dictionary>>reject: answers a dictionary not something else" | collection result | collection := self nonEmptyDict . result := collection reject: [ :each | false]. self assert: result = collection. ! ! !DictionaryTest methodsFor: 'tests - dictionnary enumerating'! testSelect | collection values result | collection := self nonEmptyDict . values := OrderedCollection new. result := collection select: [ :value | values add: value. true]. collection values do: [ :value| self assert: (collection values occurrencesOf: value) = (values occurrencesOf: value)]. self assert: result = collection.! ! !DictionaryTest methodsFor: 'tests - dictionnary enumerating'! testValuesDo | collection values | collection := self nonEmptyDict . values := OrderedCollection new. collection valuesDo: [ :value | values add: value. ]. collection values do: [ :value | self assert: (collection values occurrencesOf: value) = (values occurrencesOf: value)]! ! !DictionaryTest methodsFor: 'tests - fixture'! test0CopyTest self shouldnt: [ self empty ]raise: Error. self assert: self empty size = 0. self shouldnt: [ self nonEmpty ]raise: Error. self assert: (self nonEmpty size = 0) not. self shouldnt: [ self collectionWithElementsToRemove ]raise: Error. self assert: (self collectionWithElementsToRemove size = 0) not. self collectionWithElementsToRemove do: [:each | self assert: ( self nonEmpty includes: each)]. self shouldnt: [ self elementToAdd ]raise: Error. self deny: (self nonEmpty includes: self elementToAdd ). self shouldnt: [ self collectionNotIncluded ]raise: Error. self collectionNotIncluded do: [ :each | self deny: (self nonEmpty includes: each) ]! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureAsStringCommaAndDelimiterTest self shouldnt: [self nonEmpty] raise:Error . self deny: self nonEmpty isEmpty. self shouldnt: [self empty] raise:Error . self assert: self empty isEmpty. self shouldnt: [self nonEmpty1Element ] raise:Error . self assert: self nonEmpty1Element size=1.! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureCloneTest self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty. ! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureConverAsSortedTest self shouldnt: [self collectionWithSortableElements ] raise: Error. self deny: self collectionWithSortableElements isEmpty .! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryAddingTest self shouldnt: [ self nonEmptyDict ]raise: Error. self deny: self nonEmptyDict isEmpty. self shouldnt: [ self associationWithKeyNotInToAdd ]raise: Error. self deny: (self nonEmptyDict keys includes: self associationWithKeyNotInToAdd key ). self shouldnt: [ self associationWithKeyAlreadyInToAdd ]raise: Error. self assert: (self nonEmptyDict keys includes: self associationWithKeyAlreadyInToAdd key ). ! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryAssocitionAccess self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [self keyNotIn ] raise: Error. self deny: ( self nonEmpty keys includes: self keyNotIn ).! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryCopyingTest | duplicateKey | self shouldnt: [ self nonEmptyDict ] raise: Error. self deny: self nonEmptyDict isEmpty. self shouldnt: [ self nonEmptyDifferentFromNonEmptyDict ] raise: Error. self deny: self nonEmptyDifferentFromNonEmptyDict isEmpty. duplicateKey := true. self nonEmptyDict keys detect: [ :key | self nonEmptyDifferentFromNonEmptyDict includes: key ] ifNone: [ duplicateKey := false ] . self assert: duplicateKey = false. ! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryElementAccess | in | self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self keyNotIn ] raise: Error. in := true. self nonEmpty keys detect: [ :key | key = self keyNotIn ] ifNone: [ in := false]. self assert: in = false.! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryEnumeratingTest self shouldnt: [ self nonEmptyDict ] raise: Error. self deny: self nonEmptyDict isEmpty.! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryIncludes | in | self shouldnt: [ self nonEmpty ]raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self valueNotInNonEmpty ] raise: Error. in := false. self nonEmpty valuesDo: [ :assoc | assoc = self valueNotInNonEmpty ifTrue: [ in := true ] ]. self assert: in = false. self shouldnt: [ self keyNotInNonEmpty ] raise: Error. in := false. self nonEmpty keysDo: [ :assoc | assoc = self keyNotInNonEmpty ifTrue: [ in := true ] ]. self assert: in = false! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryIncludesIdentity | | self shouldnt: [ self nonEmptyWithCopyNonIdentical ]raise: Error. self deny: self nonEmptyWithCopyNonIdentical isEmpty. self nonEmptyWithCopyNonIdentical do: [ :each | self deny: each == each copy ]. ! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryKeyAccess | collection equals | self shouldnt: [ self nonEmptyWithoutEqualsValues ] raise: Error. self deny: self nonEmptyWithoutEqualsValues isEmpty. equals := true. collection := self nonEmptyWithoutEqualsValues values. collection detect: [:each | (collection occurrencesOf: each) > 1 ] ifNone: [ equals := false]. self assert: equals = false. self shouldnt: [ self valueNotIn ] raise: Error. self deny: (self nonEmptyWithoutEqualsValues values includes: self valueNotIn )! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryKeysValuesAssociationsAccess self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty .! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureDictionaryRemovingTest self shouldnt: [self nonEmptyDict ] raise: Error. self deny: self nonEmptyDict isEmpty. self shouldnt: [self keyNotInNonEmptyDict ] raise: Error. self deny: (self nonEmptyDict keys includes: self keyNotInNonEmptyDict ).! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureIncludeTest | elementIn | self shouldnt: [ self nonEmpty ]raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self elementNotIn ]raise: Error. elementIn := true. self nonEmpty detect: [ :each | each = self elementNotIn ] ifNone: [ elementIn := false ]. self assert: elementIn = false. self shouldnt: [ self anotherElementNotIn ]raise: Error. elementIn := true. self nonEmpty detect: [ :each | each = self anotherElementNotIn ] ifNone: [ elementIn := false ]. self assert: elementIn = false. self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty. ! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureOccurrencesForMultiplinessTest | cpt element collection | self shouldnt: [self collectionWithEqualElements ]raise: Error. self shouldnt: [self collectionWithEqualElements ]raise: Error. self shouldnt: [ self elementTwiceInForOccurrences ] raise: Error. element := self elementTwiceInForOccurrences . collection := self collectionWithEqualElements . cpt := 0 . " testing with identity check ( == ) so that identy collections can use this trait : " self collectionWithEqualElements do: [ :each | each == self elementTwiceInForOccurrences ifTrue: [ cpt := cpt + 1 ] ]. self assert: cpt = 2.! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureOccurrencesTest | tmp | self shouldnt: [self empty ]raise: Error. self assert: self empty isEmpty. self shouldnt: [ self collectionWithoutEqualElements ] raise: Error. self deny: self collectionWithoutEqualElements isEmpty. tmp := OrderedCollection new. self collectionWithoutEqualElements do: [ :each | self deny: (tmp includes: each). tmp add: each. ]. self shouldnt: [ self elementNotInForOccurrences ] raise: Error. self deny: (self collectionWithoutEqualElements includes: self elementNotInForOccurrences)! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixturePrintTest self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty.! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixturePutTest self shouldnt: self aValue raise: Error. self shouldnt: self anotherValue raise: Error. self shouldnt: self anIndex raise: Error. self nonEmpty isDictionary ifFalse:[self assert: (self anIndex >=1 & self anIndex <= self nonEmpty size).]. self shouldnt: self empty raise: Error. self assert: self empty isEmpty . self shouldnt: self nonEmpty raise: Error. self deny: self nonEmpty isEmpty.! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureSetAritmeticTest self shouldnt: [ self collection ] raise: Error. self deny: self collection isEmpty. self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self anotherElementOrAssociationNotIn ] raise: Error. self collection isDictionary ifTrue: [ self deny: (self collection associations includes: self anotherElementOrAssociationNotIn key) ] ifFalse: [ self deny: (self collection includes: self anotherElementOrAssociationNotIn) ]. self shouldnt: [ self collectionClass ] raise: Error! ! !DictionaryTest methodsFor: 'tests - fixture'! test0FixtureTConvertTest "a collection of number without equal elements:" | res | self shouldnt: [ self collectionWithoutEqualElements ]raise: Error. res := true. self collectionWithoutEqualElements detect: [ :each | (self collectionWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false. ! ! !DictionaryTest methodsFor: 'tests - fixture'! test0TStructuralEqualityTest self shouldnt: [self empty] raise: Error. self shouldnt: [self nonEmpty] raise: Error. self assert: self empty isEmpty. self deny: self nonEmpty isEmpty.! ! !DictionaryTest methodsFor: 'tests - includes'! testIdentityIncludesNonSpecificComportement " test the same comportement than 'includes: ' " | collection | collection := self nonEmpty . self deny: (collection identityIncludes: self elementNotIn ). self assert:(collection identityIncludes: collection anyOne) ! ! !DictionaryTest methodsFor: 'tests - includes'! testIncludesAllOfAllThere "self debug: #testIncludesAllOfAllThere'" self assert: (self empty includesAllOf: self empty). self assert: (self nonEmpty includesAllOf: { self nonEmpty anyOne }). self assert: (self nonEmpty includesAllOf: self nonEmpty).! ! !DictionaryTest methodsFor: 'tests - includes' stamp: 'delaunay 4/2/2009 11:53'! testIncludesAllOfNoneThere "self debug: #testIncludesAllOfNoneThere'" self deny: (self empty includesAllOf: self collection). self deny: (self nonEmpty includesAllOf: { (self elementNotIn). (self anotherElementNotIn) })! ! !DictionaryTest methodsFor: 'tests - includes'! testIncludesAnyOfAllThere "self debug: #testIncludesAnyOfAllThere'" self deny: (self nonEmpty includesAnyOf: self empty). self assert: (self nonEmpty includesAnyOf: { self nonEmpty anyOne }). self assert: (self nonEmpty includesAnyOf: self nonEmpty).! ! !DictionaryTest methodsFor: 'tests - includes' stamp: 'delaunay 4/2/2009 11:53'! testIncludesAnyOfNoneThere "self debug: #testIncludesAnyOfNoneThere'" self deny: (self nonEmpty includesAnyOf: self empty). self deny: (self nonEmpty includesAnyOf: { (self elementNotIn). (self anotherElementNotIn) })! ! !DictionaryTest methodsFor: 'tests - includes' stamp: 'delaunay 4/2/2009 11:53'! testIncludesElementIsNotThere "self debug: #testIncludesElementIsNotThere" self deny: (self nonEmpty includes: self elementNotInForOccurrences). self assert: (self nonEmpty includes: self nonEmpty anyOne). self deny: (self empty includes: self elementNotInForOccurrences)! ! !DictionaryTest methodsFor: 'tests - includes'! testIncludesElementIsThere "self debug: #testIncludesElementIsThere" self assert: (self nonEmpty includes: self nonEmpty anyOne).! ! !DictionaryTest methodsFor: 'tests - includes' stamp: 'delaunay 4/9/2009 10:44'! testIncludesSubstringAnywhere "self debug: #testIncludesSubstringAnywher'" self assert: (self empty includesAllOf: self empty). self assert: (self nonEmpty includesAllOf: { (self nonEmpty anyOne) }). self assert: (self nonEmpty includesAllOf: self nonEmpty)! ! !DictionaryTest methodsFor: 'tests - occurrencesOf'! testOccurrencesOfEmpty | result | result := self empty occurrencesOf: (self collectionWithoutEqualElements anyOne). self assert: result = 0! ! !DictionaryTest methodsFor: 'tests - occurrencesOf'! testOccurrencesOfNotIn | result | result := self collectionWithoutEqualElements occurrencesOf: self elementNotInForOccurrences. self assert: result = 0! ! !DictionaryTest methodsFor: 'tests - occurrencesOf for multipliness'! testOccurrencesOfForMultipliness | collection element | collection := self collectionWithEqualElements . element := self elementTwiceInForOccurrences . self assert: (collection occurrencesOf: element ) = 2. ! ! !DictionaryTest methodsFor: 'tests - printing'! testPrintElementsOn | aStream result allElementsAsString tmp | result:=''. aStream:= ReadWriteStream on: result. tmp:= OrderedCollection new. self nonEmpty do: [:each | tmp add: each asString]. self nonEmpty printElementsOn: aStream . allElementsAsString:=(result findBetweenSubStrs: ' ' ). 1 to: allElementsAsString size do: [:i | self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i)). ].! ! !DictionaryTest methodsFor: 'tests - printing'! testPrintNameOn | aStream result | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printNameOn: aStream . Transcript show: result asString. self nonEmpty class name first isVowel ifTrue:[ self assert: aStream contents =('an ',self nonEmpty class name ) ] ifFalse:[self assert: aStream contents =('a ',self nonEmpty class name)].! ! !DictionaryTest methodsFor: 'tests - printing'! testPrintOn | aStream result allElementsAsString tmp | result:=''. aStream:= ReadWriteStream on: result. tmp:= OrderedCollection new. self nonEmpty do: [:each | tmp add: each asString]. self nonEmpty printOn: aStream . allElementsAsString:=(result findBetweenSubStrs: ' ' ). 1 to: allElementsAsString size do: [:i | i=1 ifTrue:[ self accessCollection class name first isVowel ifTrue:[self assert: (allElementsAsString at:i)='an' ] ifFalse:[self assert: (allElementsAsString at:i)='a'].]. i=2 ifTrue:[self assert: (allElementsAsString at:i)=self accessCollection class name]. i>2 ifTrue:[self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i)).]. ].! ! !DictionaryTest methodsFor: 'tests - printing'! testPrintOnDelimiter | aStream result allElementsAsString tmp | result:=''. aStream:= ReadWriteStream on: result. tmp:= OrderedCollection new. self nonEmpty do: [:each | tmp add: each asString]. self nonEmpty printOn: aStream delimiter: ', ' . allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | self assert: (tmp occurrencesOf:(allElementsAsString at:i))=(allElementsAsString occurrencesOf:(allElementsAsString at:i)) ].! ! !DictionaryTest methodsFor: 'tests - printing'! testPrintOnDelimiterLast | aStream result allElementsAsString tmp | result:=''. aStream:= ReadWriteStream on: result. tmp:= OrderedCollection new. self nonEmpty do: [:each | tmp add: each asString]. self nonEmpty printOn: aStream delimiter: ', ' last: 'and'. allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) ifTrue: [self assert: (tmp occurrencesOf: (allElementsAsString at:i))=(allElementsAsString occurrencesOf: (allElementsAsString at:i))]. i=(allElementsAsString size-1) ifTrue:[ self deny: (allElementsAsString at:i)=('and')asString]. i=(allElementsAsString size) ifTrue: [self assert: (tmp occurrencesOf: (allElementsAsString at:i))=(allElementsAsString occurrencesOf: (allElementsAsString at:i))]. ].! ! !DictionaryTest methodsFor: 'tests - printing'! testStoreOn " for the moment work only for collection that include simple elements such that Integer" "| string str result cuttedResult index elementsAsStringExpected elementsAsStringObtained tmp | string := ''. str := ReadWriteStream on: string. elementsAsStringExpected := OrderedCollection new. elementsAsStringObtained := OrderedCollection new. self nonEmpty do: [ :each | elementsAsStringExpected add: each asString]. self nonEmpty storeOn: str. result := str contents . cuttedResult := ( result findBetweenSubStrs: ';' ). index := 1. cuttedResult do: [ :each | index = 1 ifTrue: [ self assert: (each beginsWith: ( tmp := '((' , self nonEmpty class asString , ' new) add: ' )). tmp := each copyFrom: ( tmp size + 1) to: ( each size ). elementsAsStringObtained add: tmp. index := index + 1. ] ifFalse: [ index < cuttedResult size ifTrue:[self assert: (each beginsWith: ( tmp:= ' add: ' )). tmp := each copyFrom: ( tmp size + 1) to: ( each size ). elementsAsStringObtained add: tmp. index := index + 1.] ifFalse: [self assert: ( each = ' yourself)' ) ]. ] ]. elementsAsStringExpected do: [ :each | self assert: (elementsAsStringExpected occurrencesOf: each ) = ( elementsAsStringObtained occurrencesOf: each) ]" ! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! containsAll: union of: one andOf: another self assert: (one allSatisfy: [:each | union includes: each]). self assert: (another allSatisfy: [:each | union includes: each])! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! numberOfSimilarElementsInIntersection ^ self collection occurrencesOf: self anotherElementOrAssociationIn! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! testDifference "Answer the set theoretic difference of two collections." "self debug: #testDifference" self assert: (self collection difference: self collection) isEmpty. self assert: (self empty difference: self collection) isEmpty. self assert: (self collection difference: self empty) = self collection ! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! testDifferenceWithNonNullIntersection "Answer the set theoretic difference of two collections." "self debug: #testDifferenceWithNonNullIntersection" " #(1 2 3) difference: #(2 4) -> #(1 3)" | res overlapping | overlapping := self collectionClass with: self anotherElementOrAssociationNotIn with: self anotherElementOrAssociationIn. res := self collection difference: overlapping. self deny: (res includes: self anotherElementOrAssociationIn). overlapping do: [ :each | self deny: (res includes: each) ]! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! testDifferenceWithSeparateCollection "Answer the set theoretic difference of two collections." "self debug: #testDifferenceWithSeparateCollection" | res separateCol | separateCol := self collectionClass with: self anotherElementOrAssociationNotIn. res := self collection difference: separateCol. self deny: (res includes: self anotherElementOrAssociationNotIn). self assert: res = self collection. res := separateCol difference: self collection. self deny: (res includes: self collection anyOne). self assert: res = separateCol! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! testIntersectionBasic "self debug: #testIntersectionBasic" | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). self deny: inter isEmpty. self assert: (inter includes: self anotherElementOrAssociationIn value)! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! testIntersectionEmpty "self debug: #testIntersectionEmpty" | inter | inter := self empty intersection: self empty. self assert: inter isEmpty. inter := self empty intersection: self collection . self assert: inter = self empty. ! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! testIntersectionItself "self debug: #testIntersectionItself" self assert: (self collection intersection: self collection) = self collection. ! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! testIntersectionTwoSimilarElementsInIntersection "self debug: #testIntersectionBasic" | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). self assert: (self collection occurrencesOf: self anotherElementOrAssociationIn) = self numberOfSimilarElementsInIntersection. self assert: (inter includes: self anotherElementOrAssociationIn value)! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! testUnion "self debug: #testUnionOfEmpties" | union | union := self empty union: self nonEmpty. self containsAll: union of: self empty andOf: self nonEmpty. union := self nonEmpty union: self empty. self containsAll: union of: self empty andOf: self nonEmpty. union := self collection union: self nonEmpty. self containsAll: union of: self collection andOf: self nonEmpty.! ! !DictionaryTest methodsFor: 'tests - set arithmetic'! testUnionOfEmpties "self debug: #testUnionOfEmpties" self assert: (self empty union: self empty) isEmpty. ! ! !DictionaryTest methodsFor: 'tests' stamp: 'nice 9/14/2009 21:07'! testRemoveAll "Allows one to remove all elements of a collection" | dict1 dict2 s2 | dict1 := Dictionary new. dict1 at: #a put:1 ; at: #b put: 2. dict2 := dict1 copy. s2 := dict2 size. dict1 removeAll. self assert: dict1 size = 0. self assert: dict2 size = s2 description: 'the copy has not been modified'.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DictionaryTest class uses: TIncludesTest classTrait + TDictionaryAddingTest classTrait + TDictionaryComparingTest classTrait + TDictionaryCopyingTest classTrait + TDictionaryEnumeratingTest classTrait + TDictionaryPrintingTest classTrait + TDictionaryRemovingTest classTrait + TPutBasicTest classTrait + TAsStringCommaAndDelimiterTest classTrait + TPrintTest classTrait + TConvertTest classTrait + TConvertAsSortedTest classTrait + TCopyTest classTrait + TSetArithmetic classTrait + TDictionaryValueAccessTest classTrait + TDictionaryKeysValuesAssociationsAccess classTrait + TDictionaryKeyAccessTest classTrait + TDictionaryAssociationAccessTest classTrait + TDictionaryIncludesWithIdentityCheckTest classTrait + TStructuralEqualityTest classTrait + TOccurrencesForMultiplinessTest classTrait instanceVariableNames: 'testToto pt1'! ProportionalSplitterMorph subclass: #DiffJoinMorph instanceVariableNames: 'srcOffset dstOffset mappings' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Tools-Diff'! !DiffJoinMorph methodsFor: 'accessing' stamp: 'gvc 10/24/2006 16:02'! dstOffset "Answer the value of dstOffset" ^ dstOffset! ! !DiffJoinMorph methodsFor: 'accessing' stamp: 'gvc 10/31/2006 11:33'! dstOffset: anInteger "Set the dstOffset." dstOffset := anInteger. self mappings do: [:j | j dstOffset: anInteger]! ! !DiffJoinMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 11:50'! mappings "Answer the value of mappings" ^ mappings! ! !DiffJoinMorph methodsFor: 'accessing' stamp: 'gvc 10/31/2006 13:19'! mappings: anObject "Set the value of mappings" mappings := anObject. self updateMappings. self changed! ! !DiffJoinMorph methodsFor: 'accessing' stamp: 'gvc 10/24/2006 16:02'! srcOffset "Answer the value of srcOffset" ^ srcOffset! ! !DiffJoinMorph methodsFor: 'accessing' stamp: 'gvc 10/31/2006 11:33'! srcOffset: anInteger "Set the srcOffset." srcOffset := anInteger. self mappings do: [:j | j srcOffset: anInteger]! ! !DiffJoinMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/30/2009 13:43'! compositeText "Answer the composite text based on the selection state of the joins." |t| t := Text new. self mappings do: [:j | j appendToCompositeText: t]. ^t! ! !DiffJoinMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/20/2006 14:21'! defaultColor "Answer the default color for the receiver." ^Color transparent! ! !DiffJoinMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/31/2006 12:08'! drawOn: aCanvas "Draw the indicators for the mappings." super drawOn: aCanvas. aCanvas translateBy: self topLeft clippingTo: self clippingBounds during: [:c | self mappings do: [:j | j drawOn: c]]! ! !DiffJoinMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/31/2006 13:18'! extent: aPoint "Update the shapes of the joins." super extent: aPoint. self updateMappings! ! !DiffJoinMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/31/2006 11:44'! initialize "Initialize the receiver." super initialize. self mappings: OrderedCollection new; srcOffset: 0@0; dstOffset: 0@0! ! !DiffJoinMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/31/2006 13:18'! layoutBounds: aRectangle "Set the bounds for laying out children of the receiver." super layoutBounds: aRectangle. self updateMappings! ! !DiffJoinMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/1/2006 12:00'! mouseDown: evt "Check for a click." |cj| cj := self mappings detect: [:j | j containsPoint: evt position - self topLeft] ifNone: []. cj ifNotNil: [ cj clicked. self triggerEvent: #joinClicked]. super mouseDown: evt! ! !DiffJoinMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/31/2006 13:18'! updateMappings "Update the shapes of the joins." self mappings do: [:j | j width: self width]! ! BorderedMorph subclass: #DiffMapMorph instanceVariableNames: 'mappings' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Tools-Diff'! !DiffMapMorph methodsFor: 'accessing' stamp: 'gvc 10/26/2006 15:11'! adoptPaneColor: paneColor "Change our border color too." |c| super adoptPaneColor: paneColor. paneColor ifNil: [^self]. c := paneColor alphaMixed: 0.1 with: Color white. self fillStyle: ((GradientFillStyle ramp: (self gradientRampForColor: c)) origin: self bounds topLeft; direction: 0@ self height). self borderStyle baseColor: paneColor! ! !DiffMapMorph methodsFor: 'accessing' stamp: 'gvc 10/26/2006 14:10'! defaultColor "Answer the default color for the receiver." ^Color white! ! !DiffMapMorph methodsFor: 'accessing' stamp: 'gvc 3/21/2008 17:14'! extent: newExtent "Update the gradient." super extent: newExtent. (self fillStyle notNil and: [self fillStyle isOrientedFill]) ifTrue: [self fillStyle direction: 0@self height]! ! !DiffMapMorph methodsFor: 'accessing' stamp: 'gvc 10/26/2006 15:12'! gradientRampForColor: c "Answer the background gradient ramp to use." ^{0.0->c darker duller. 0.1-> c lighter. 0.9->c twiceLighter. 1.0->c darker}! ! !DiffMapMorph methodsFor: 'accessing' stamp: 'gvc 10/26/2006 14:08'! initialize "Initialize the receiver." super initialize. self mappings: #()! ! !DiffMapMorph methodsFor: 'accessing' stamp: 'gvc 10/26/2006 13:57'! mappings "Answer the value of mappings" ^ mappings! ! !DiffMapMorph methodsFor: 'accessing' stamp: 'gvc 10/26/2006 14:15'! mappings: anObject "Set the value of mappings" mappings := anObject. self changed! ! !DiffMapMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/1/2006 10:51'! mappingsHeight "Answer the maximum y of all the mappings." self mappings ifEmpty: [^0]. ^self mappings last dst range last ! ! !DiffMapMorph methodsFor: 'nil' stamp: 'gvc 10/26/2006 15:05'! drawOn: aCanvas "Draw the indicators for the mappings." |b f| b := self innerBounds insetBy: 2. super drawOn: aCanvas. b height < 1 ifTrue: [^self]. f := self mappingsHeight. f < 1 ifTrue: [^self]. f := b height / f. aCanvas clipBy: self clippingBounds during: [:c | self mappings do: [:j | j drawMapOn: c in: b scale: f]]! ! ComposableMorph subclass: #DiffMorph instanceVariableNames: 'srcText dstText prettyPrint contextClass srcMorph dstMorph scrollbarMorph mapMorph joinMorph difference joinMappings' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Tools-Diff'! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 9/2/2008 15:38'! contextClass "Answer the value of contextClass" ^ contextClass! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 9/2/2008 15:38'! contextClass: anObject "Set the value of contextClass" contextClass := anObject! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 11:27'! difference "Answer the value of difference" ^ difference! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 11:27'! difference: anObject "Set the value of difference" difference := anObject! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 10:46'! dstMorph "Answer the value of dstMorph" ^ dstMorph! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 10:46'! dstMorph: anObject "Set the value of dstMorph" dstMorph := anObject! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 9/2/2008 15:21'! dstText "Answer the value of dstText" ^ dstText! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 9/2/2008 15:21'! dstText: anObject "Set the value of dstText" dstText := anObject! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/24/2006 15:55'! joinMappings "Answer the join parameters between src and dst." ^joinMappings ifNil: [self calculateJoinMappings]! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 7/30/2009 13:42'! joinMappings: aCollection "Set the join parameters between src and dst." joinMappings := aCollection! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 10:46'! joinMorph "Answer the value of joinMorph" ^ joinMorph! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 10:46'! joinMorph: anObject "Set the value of joinMorph" joinMorph := anObject! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 10:46'! mapMorph "Answer the value of mapMorph" ^ mapMorph! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 10:46'! mapMorph: anObject "Set the value of mapMorph" mapMorph := anObject! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 9/2/2008 15:21'! prettyPrint "Answer the value of prettyPrint" ^ prettyPrint! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 9/2/2008 15:22'! prettyPrint: aBoolean "Set the value of prettyPrint" prettyPrint == aBoolean ifTrue: [^self]. prettyPrint := aBoolean. self updateText ! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/23/2006 15:47'! scrollbarMorph "Answer the value of scrollbarMorph" ^ scrollbarMorph! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/23/2006 15:47'! scrollbarMorph: anObject "Set the value of scrollbarMorph" scrollbarMorph := anObject! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 10:46'! srcMorph "Answer the value of srcMorph" ^ srcMorph! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 10/20/2006 10:46'! srcMorph: anObject "Set the value of srcMorph" srcMorph := anObject! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 9/2/2008 15:21'! srcText "Answer the value of srcText" ^ srcText! ! !DiffMorph methodsFor: 'accessing' stamp: 'gvc 9/2/2008 15:21'! srcText: anObject "Set the value of srcText" srcText := anObject! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/24/2006 12:34'! additionColor "Answer the color used to show additions." ^Color paleGreen alpha: 0.5! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/29/2006 18:23'! adoptPaneColor: paneColor "Change our border color too." super adoptPaneColor: paneColor. paneColor ifNil: [^self]. self borderStyle baseColor: paneColor! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/1/2006 10:52'! applyHighlights "Apply the relevant highlights to src and dst." self srcMorph highlights: (self joinMappings gather: [:j | j src highlights]). self dstMorph highlights: (self joinMappings gather: [:j | j dst highlights])! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/24/2006 11:11'! applyJoin "Apply the join mappings to the join morph." self joinMorph mappings: self joinMappings! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/26/2006 14:11'! applyMap "Apply the join mappings to the map morph." self mapMorph mappings: self joinMappings! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/20/2006 13:11'! calculateDifference "Calculate the difference of the src and dst." self difference: ((TextDiffBuilder from: self oldText asString to: self newText asString) buildPatchSequence)! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/24/2006 15:56'! calculateJoinMappings "Calculate the join parameters between src and dst and store in joinMappings." self joinMappings: self calculatedJoinMappings! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/31/2006 11:51'! calculatedJoinMappings "Calculate the join parameters between src and dst and answer. sl = src line, dl = dst line, j = joins, ds = dst run start, ss = src run start de = dst run end, se = dst run end, mds = match dst start, mss = match src start" |sl dl j ds ss de se mds mss| sl := dl := 0. j := OrderedCollection new. ds := de:= ss := se := mss := mds := 0. self difference do: [:p | p key = #match ifTrue: [ sl := sl + 1. dl := dl + 1. mss = 0 ifTrue: [mss := sl. mds := dl]. (ds > 0 or: [ss > 0]) ifTrue: [ ss = 0 ifTrue: [ss := sl]. ds = 0 ifTrue: [ds := dl]. se = 0 ifTrue: [se := ss - 1]. de = 0 ifTrue: [de := ds - 1]. j add: (self newJoinSectionFrom: (ss to: se) to: (ds to: de)). ds := de := ss := se := 0]]. p key = #remove ifTrue: [ mss > 0 ifTrue: [ j add: (self newMatchJoinSectionFrom: (mss to: sl) to: (mds to: dl)). mss := mds := 0]. sl := sl + 1. ss = 0 ifTrue: [ss := sl]. se := sl]. p key = #insert ifTrue: [ mss > 0 ifTrue: [ j add: (self newMatchJoinSectionFrom: (mss to: sl) to: (mds to: dl)). mss := mds := 0]. dl := dl + 1. ss > 0 ifTrue: [ se = 0 ifTrue: [se := ss]. de = 0 ifTrue: [de := ds]. j add: (self newJoinSectionFrom: (ss to: se) to: (ds to: de)). ds := de := ss := se := 0]. ds = 0 ifTrue: [ds := dl]. de := dl]]. sl := sl + 1. dl := dl + 1. (ds > 0 or: [ss > 0]) ifTrue: [ ss = 0 ifTrue: [ss := sl ]. ds = 0 ifTrue: [ds := dl]. se = 0 ifTrue: [se := ss - 1]. de = 0 ifTrue: [de := ds - 1]. j add: (self newJoinSectionFrom: (ss to: se) to: (ds to: de))]. mss > 0 ifTrue: [ j add: (self newMatchJoinSectionFrom: (mss to: sl - 1) to: (mds to: dl - 1))]. ^j! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/23/2006 16:29'! calibrateScrollbar "Set the scrollbar parameters to match the texts." |maxY range delta innerH| self fullBounds. maxY := self srcMorph textExtent y max: self dstMorph textExtent y. innerH := self dstMorph innerBounds height. delta := self dstMorph textMorph defaultLineHeight. range := maxY - innerH max: 0. range = 0 ifTrue: [^self scrollbarMorph scrollDelta: 0.02 pageDelta: 0.2; interval: 1.0; setValue: 0.0]. self scrollbarMorph scrollDelta: (delta / range) asFloat pageDelta: ((innerH - delta) / range) asFloat; interval: (innerH / maxY) asFloat; setValue: ((self srcMorph scroller offset y max: self dstMorph scroller offset y) / range min: 1.0) asFloat! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/26/2006 14:29'! colorForType: type "Anwser the color to use for the given change type." ^{self matchColor. self additionColor. self removalColor. self modificationColor} at: (#(match addition removal modification) indexOf: type)! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/26/2006 14:10'! defaultColor "Answer the default color for the receiver." ^Color white! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/1/2006 11:04'! defaultTitle "Answer the default title label for the receiver." ^'Diff' translated! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 18:22'! dstScroll: scrollValue "Called from dst when scrolled by keyboard etc." self scrollbarMorph value: scrollValue. self srcMorph vScrollBarValue: scrollValue. self updateJoinOffsets! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/24/2006 12:35'! edgeColor "Answer the color used to show the border of the changes." ^Color gray alpha: 0.5! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/23/2006 16:27'! extent: newExtent "Update the scrollbar." super extent: newExtent. self calibrateScrollbar! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/31/2006 13:23'! font: aFont "Set the font on the src and dst morphs." self srcMorph font: aFont. self dstMorph font: aFont! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/2/2008 15:24'! from: old to: new "Set the old (src) and new (dst) text." self srcText: old; dstText: new. self setText; calculateDifference; calculateJoinMappings; calibrateScrollbar; applyHighlights; applyJoin; applyMap! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/2/2008 15:45'! from: old to: new contextClass: aClass "Set the old (src) and new (dst) text." self contextClass: aClass; srcText: old; dstText: new. self setText; calculateDifference; calculateJoinMappings; calibrateScrollbar; applyHighlights; applyJoin; applyMap! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/23/2006 16:12'! hideOrShowScrollBar "Do nothing" ! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 17:55'! join: aJoin selected: aBoolean "Set the selection for the given join and update the src dst and join morphs." aJoin selected: aBoolean. self srcMorph changed. self joinMorph changed. self dstMorph changed! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/24/2006 12:08'! joinColor "Answer the color used for the join bar." ^Color paleBlue duller! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/1/2006 14:12'! joinSectionClass "Answer the class to use for a new join section." ^JoinSection! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/26/2006 14:29'! matchColor "Answer the color used to show matches." ^Color transparent! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/24/2006 12:34'! modificationColor "Answer the color used to show changes." ^Color paleYellow alpha: 0.5! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/26/2006 13:52'! newDstMorph "Answer a new dst text morph." ^self newSrcMorph! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 12:54'! newHighlight "Anewser a new highlight." ^TextHighlight new color: self modificationColor; borderWidth: 1; borderColor: self edgeColor! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 13:39'! newHighlight: type "Anewser a new highlight." ^TextHighlight new color: (self colorForType: type); borderWidth: 1; borderColor: self edgeColor; fillWidth: true! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/1/2006 14:15'! newJoinMorph "Answer a new join morph." ^DiffJoinMorph new hResizing: #shrinkWrap; vResizing: #spaceFill; extent: 30@4; minWidth: 30; color: self joinColor! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/1/2006 14:11'! newJoinSection "Answer a new join section." ^self joinSectionClass new srcColor: self modificationColor; dstColor: self modificationColor; borderWidth: 1; borderColor: self edgeColor; addDependent: self; yourself! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/31/2006 14:08'! newJoinSectionFrom: srcRange to: dstRange "Answer a new join section." |spl dpl sy1 sy2 dy1 dy2 t c| spl := self srcMorph textMorph paragraph lines. dpl := self dstMorph textMorph paragraph lines. t := #modification. sy1 := srcRange first > spl size ifTrue: [t := #addition. spl last bottom truncated - 1] ifFalse: [(spl at: srcRange first) top truncated - 1]. sy2 := srcRange size < 1 ifTrue: [t := #addition. sy1 + 3] ifFalse: [srcRange last > spl size ifTrue: [spl last bottom truncated + 3] ifFalse: [(spl at: srcRange last) bottom truncated - 1]]. dy1 := dstRange first > dpl size ifTrue: [t := #removal. dpl last bottom truncated - 1] ifFalse: [(dpl at: dstRange first) top truncated - 1]. dy2 := dstRange size < 1 ifTrue: [t := #removal. dy1 + 3] ifFalse: [dstRange last > dpl size ifTrue: [dpl last bottom truncated + 3] ifFalse: [(dpl at: dstRange last) bottom truncated - 1]]. c := self colorForType: t. ^self newJoinSection type: t; srcColor: c; dstColor: c; srcLineRange: srcRange; dstLineRange: dstRange; srcRange: (sy1 to: sy2); dstRange: (dy1 to: dy2); createHighlightsFrom: self srcMorph textMorph paragraph to: self dstMorph textMorph paragraph! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/26/2006 14:16'! newMapMorph "Answer a new map morph." ^DiffMapMorph new hResizing: #shrinkWrap; vResizing: #spaceFill; extent: 20@4; minWidth: 20; borderStyle: (BorderStyle inset width: 1)! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 11/1/2006 11:07'! newMatchJoinSectionFrom: srcRange to: dstRange "Answer a new match join section." |spl dpl sy1 sy2 dy1 dy2 c| spl := self srcMorph textMorph paragraph lines. dpl := self dstMorph textMorph paragraph lines. sy1 := (spl at: srcRange first) top truncated. sy2 := (spl at: srcRange last) bottom truncated. dy1 := (dpl at: dstRange first) top truncated. dy2 := (dpl at: dstRange last) bottom truncated. c := self colorForType: #match. ^self newJoinSection type: #match; borderWidth: 0; srcColor: c; dstColor: c; srcLineRange: srcRange; dstLineRange: dstRange; srcRange: (sy1 to: sy2); dstRange: (dy1 to: dy2); createHighlightsFrom: self srcMorph textMorph paragraph to: self dstMorph textMorph paragraph! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/2/2008 15:56'! newPrettyPrintCheckboxMorph "Answer a new checkbox for specifying whether to use pretty printing for the diff texts." ^self newCheckboxFor: self getSelected: #prettyPrint setSelected: #prettyPrint: getEnabled: nil label: 'Pretty print' translated help: 'If selected, pretty print will be applied to any displayed method source (eliminates trivial formatting changes)' translated! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/1/2008 11:48'! newScrollbarMorph "Answer a new scrollbar morph." ^ScrollBar new model: self; setValueSelector: #vScroll:; vResizing: #spaceFill; width: self theme scrollbarThickness! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/26/2006 13:52'! newSrcMorph "Answer a new src text morph." ^(self newTextEditorFor: nil getText: nil setText: nil getEnabled: nil) hideVScrollBarIndefinitely: true; borderWidth: 0; enabled: false; wrapFlag: false; selectionColor: self textSelectionColor; setText: ''! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/20/2006 11:26'! newText "Answer the new (dst) text." ^self dstMorph text! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/20/2006 11:26'! oldText "Answer the old (src) text." ^self srcMorph text! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/24/2006 12:34'! removalColor "Answer the color used to show removals." ^Color paleRed alpha: 0.5! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'alain.plantec 5/18/2009 15:54'! setText "Set the src and dst text in the morphs applying prettyPrint if required." |src dst ctx| src := self srcText. dst := self dstText. ctx := self contextClass. (self prettyPrint and: [ctx notNil]) ifTrue: [src isEmpty ifFalse: [ src := ctx prettyPrinterClass format: src in: ctx notifying: nil]. dst isEmpty ifFalse: [ dst := ctx prettyPrinterClass format: dst in: ctx notifying: nil]]. self srcMorph setText: src; font: self theme textFont. self dstMorph setText: dst; font: self theme textFont! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 18:22'! srcScroll: scrollValue "Called from src when scrolled by keyboard etc.." self scrollbarMorph value: scrollValue. self dstMorph vScrollBarValue: scrollValue. self updateJoinOffsets! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/24/2006 16:11'! textSelectionColor "Answer the color used for thew text selection." ^Preferences textHighlightColor alpha: 0.5! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/1/2008 12:27'! themeChanged "Update the scrollbar width/frame." |offset| super themeChanged. self scrollbarMorph width: self theme scrollbarThickness. offset := self scrollbarMorph width negated - self mapMorph width. self scrollbarMorph layoutFrame leftOffset: offset. self dstMorph layoutFrame rightOffset: offset! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/24/2006 16:09'! updateJoinOffsets "Update the src and dst offsets in the join morph to match the src and dst tex scroll offsets." self joinMorph srcOffset: 0 @ self srcMorph scroller offset y negated; dstOffset: 0 @ self dstMorph scroller offset y negated; changed! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/2/2008 15:23'! updateText "Reset the text if we have some." (self srcText notNil and: [self dstText notNil]) ifTrue: [ self from: self srcText to: self dstText]! ! !DiffMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 18:22'! vScroll: scrollValue "Called from standalone scroolbar. Scroll the srcMorph and redo the join." self srcMorph vScrollBarValue: scrollValue. self dstMorph vScrollBarValue: scrollValue. self updateJoinOffsets! ! !DiffMorph methodsFor: 'initialization' stamp: 'gvc 9/2/2008 16:21'! initialize "Initialize the receiver." |exv exh opts ppCheckbox| super initialize. self prettyPrint: Preferences diffsWithPrettyPrint. ppCheckbox := self newPrettyPrintCheckboxMorph. opts := self newPanel addMorph: ((self newRow: {ppCheckbox}) listCentering: #bottomRight). opts vResizing: #shrinkWrap. opts extent: opts minExtent. self srcMorph: self newSrcMorph; joinMorph: self newJoinMorph; dstMorph: self newDstMorph; scrollbarMorph: self newScrollbarMorph; mapMorph: self newMapMorph; changeProportionalLayout; addMorph: self srcMorph fullFrame: (LayoutFrame fractions: (0@0 corner: 0.5@1) offsets: (0@0 corner: self joinMorph width negated@opts height negated)); addMorph: self joinMorph fullFrame: (LayoutFrame fractions: (0.5@0 corner: 0.5@1) offsets: (self joinMorph width negated@0 corner: 0@opts height negated)); addMorph: self dstMorph fullFrame: (LayoutFrame fractions: (0.5@0 corner: 1@1) offsets: (0@0 corner: self scrollbarMorph width negated - self mapMorph width@opts height negated)); addMorph: self scrollbarMorph fullFrame: (LayoutFrame fractions: (1@0 corner: 1@1) offsets: (self scrollbarMorph width negated - self mapMorph width@0 corner: self mapMorph width negated@opts height negated)); addMorph: self mapMorph fullFrame: (LayoutFrame fractions: (1@0 corner: 1@1) offsets: (self mapMorph width negated@0 corner: 0@opts height negated)); addMorph: opts fullFrame: (LayoutFrame fractions: (0@1 corner: 1@1) offsets: (0@opts height negated corner: 0@0)). exv := ExclusiveWeakMessageSend newSharedState. exh := ExclusiveWeakMessageSend newSharedState. self srcMorph when: #vScroll send: #srcScroll: to: self exclusive: exv; when: #hScroll send: #hScrollValue: to: self dstMorph exclusive: exh. self dstMorph when: #vScroll send: #dstScroll: to: self exclusive: exv; when: #hScroll send: #hScrollValue: to: self srcMorph exclusive: exh. self linkSubmorphsToSplitters; extent: self initialExtent! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DiffMorph class instanceVariableNames: ''! !DiffMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 10/20/2006 11:26'! from: old to: new "Answer a new instance of the receiver with the given old and new text." ^self new from: old to: new! ! !DiffMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 9/2/2008 15:46'! from: old to: new contextClass: aClass "Answer a new instance of the receiver with the given old and new text." ^self new from: old to: new contextClass: aClass! ! Object subclass: #DigitalSignatureAlgorithm instanceVariableNames: 'randKey randSeed' classVariableNames: 'HighBitOfByte SmallPrimes' poolDictionaries: '' category: 'System-Digital Signatures'! !DigitalSignatureAlgorithm commentStamp: '' prior: 0! This class implements the Digital Signature Algorithm (DSA) of the U.S. government's "Digital Signature Standard" (DSS). The DSA algorithm was proposed in 1991 and became a standard in May 1994. The official description is available as a Federal Information Processing Standards Publication (FIPS PUB 186, May 19, 1994). A companion standard, the Secure Hash Standard, or SHS (FIPS PUB 180-1, April 17, 1995), describes a 160-bit message digest algorithm known as the Secure Hash Algorithm (SHA). This message digest is used to compute the document signature. Here's how to use it: 1. The "signer" creates a pair of keys. One of these must be kept private. The other may be freely distributed. For example, it could be built into the signature checking code of an application. 2. When the signer wishes to sign a packet of data (a "message") , he uses the secure hash algorithm to create a 160-bit message digest (hash) which is used as the input to DSA. The result of this is a pair of large numbers called a "signature" that is attached to the original message. 3. When someone receives a signed message purported to have come from the signer, they compute the 160-bit hash of the message and pass that, along with the message signature and the signer's public key, to the signature verification algorithm. If the signature checks, then it is virtually guaranteed that the message originated from someone who had the signer's private key. That is, the message is not a forgery and has not been modified since it was signed. For example, if the message contains a program, and the recipient trusts the signer, then the recipient can run the program with the assurance that it won't do anything harmful. (At least, not intentionally. A digital signature is no guarantee against bugs!! :->) The signer must keep the private key secure, since anyone who has the private key can forge the signer's signature on any message they like. As long as the secret key is not stolen, cryptographers believe it to be virtually impossible either to forge a signature, to find a message that matches an existing sigature, or to discover the signer's private key by analyzing message signatures. Knowing the public key (which, for example, could be recovered from an application that had it built in), does not weaken the security at all. An excellent reference work on digital signatures and cryptography in general is: Schneier, Bruce "Applied Cryptography: Protocols, Algorithms, and Source Code in C" John Wiley and Sons, 1996. I used this book as a guide to implementing many of the numerical algorithms required by DSA. Patents and Export Restrictions: Many digital signature technologies are patented. DSA is also patented, but the patent is owned by the U.S. government which has made DSA available royalty-free. There is a claim that the government patent infringes on an earlier patent by Schnorr, but the government is requiring the use of DSA, so they apparently believe this claim is not strong enough to be a serious threat to their own patent. Most cryptography technology, including digital signature technology, requires an export license for it to be distributed outside the U.S. Recent legislation may have relaxed the export license requirements, but it would be prudent to check the current regulations before exporting this code.! !DigitalSignatureAlgorithm methodsFor: 'initialization' stamp: 'jm 1/11/2000 00:25'! initRandom: randomInteger "Initialize the the secure random number generator with the given value. The argument should be a positive integer of up to 512 bits chosen randomly to avoid someone being able to predict the sequence of random values generated." "Note: The random generator must be initialized before generating a key set or signature. Signature verification does not require initialization of the random generator." randSeed := 16rEFCDAB8998BADCFE10325476C3D2E1F067452301. "initial seed" randKey := randomInteger. Transcript show: 'Random seed: ', randomInteger printString; cr. ! ! !DigitalSignatureAlgorithm methodsFor: 'initialization' stamp: 'ar 2/1/2001 20:18'! initRandomFromString: aString "Ask the user to type a long random string and use the result to seed the secure random number generator." | s k srcIndex | s := aString. k := LargePositiveInteger new: (s size min: 64). srcIndex := 0. k digitLength to: 1 by: -1 do: [:i | k digitAt: i put: (s at: (srcIndex := srcIndex + 1)) asciiValue]. k := k + (Random new next * 16r7FFFFFFF) asInteger. "a few additional bits randomness" k highBit > 512 ifTrue: [k := k bitShift: k highBit - 512]. self initRandom: k. ! ! !DigitalSignatureAlgorithm methodsFor: 'initialization' stamp: 'DamienCassou 9/23/2009 08:37'! initRandomFromUser "Ask the user to type a long random string and use the result to seed the secure random number generator." | s k srcIndex | s := UIManager default request: 'Enter a long random string to seed the random generator.'. s isNil ifTrue: [s := '']. k := LargePositiveInteger new: (s size min: 64). srcIndex := 0. k digitLength to: 1 by: -1 do: [:i | k digitAt: i put: (s at: (srcIndex := srcIndex + 1)) asciiValue]. k := k + (Random new next * 16r7FFFFFFF) asInteger. "a few additional bits randomness" k highBit > 512 ifTrue: [k := k bitShift: k highBit - 512]. self initRandom: k. ! ! !DigitalSignatureAlgorithm methodsFor: 'initialization' stamp: 'gk 2/26/2004 09:52'! initRandomNonInteractively [self initRandom: (SoundService default randomBitsFromSoundInput: 512)] ifError: [self initRandomFromString: Time millisecondClockValue printString, Date today printString, SmalltalkImage current platformName printString].! ! !DigitalSignatureAlgorithm methodsFor: 'large integer arithmetic' stamp: 'jm 12/9/1999 21:49'! inverseOf: x mod: n "Answer the inverse of x modulus n. That is, the integer y such that (x * y) \\ n is 1. Both x and n must be positive, and it is assumed that x < n and that x and n are integers." "Details: Use the extended Euclidean algorithm, Schneier, p. 247." | v u k u1 u2 u3 t1 t2 t3 tmp | ((x <= 0) or: [n <= 0]) ifTrue: [self error: 'x and n must be greater than zero']. x >= n ifTrue: [self error: 'x must be < n']. v := x. u := n. k := 0. [x even and: [n even and: [u > 0]]] whileTrue: [ "eliminate common factors of two" k := k + 1. u := u bitShift: -1. v := v bitShift: -1]. u1 := 1. u2 := 0. u3 := u. t1 := v. t2 := u - 1. t3 := v. [ [u3 even ifTrue: [ ((u1 odd) or: [u2 odd]) ifTrue: [ u1 := u1 + v. u2 := u2 + u]. u1 := u1 bitShift: -1. u2 := u2 bitShift: -1. u3 := u3 bitShift: -1]. ((t3 even) or: [u3 < t3]) ifTrue: [ tmp := u1. u1 := t1. t1 := tmp. tmp := u2. u2 := t2. t2 := tmp. tmp := u3. u3 := t3. t3 := tmp]. u3 even and: [u3 > 0]] whileTrue: ["loop while u3 is even"]. [((u1 < t1) or: [u2 < t2]) and: [u1 > 0]] whileTrue: [ u1 := u1 + v. u2 := u2 + u]. u1 := u1 - t1. u2 := u2 - t2. u3 := u3 - t3. t3 > 0] whileTrue: ["loop while t3 > 0"]. [u1 >= v and: [u2 >= u]] whileTrue: [ u1 := u1 - v. u2 := u2 - u]. u1 := u1 bitShift: k. u2 := u2 bitShift: k. u3 := u3 bitShift: k. u3 = 1 ifFalse: [self error: 'no inverse']. ^ u - u2 ! ! !DigitalSignatureAlgorithm methodsFor: 'large integer arithmetic' stamp: 'adrian-lienhard 5/18/2009 21:08'! isProbablyPrime: p "Answer true if p is prime with very high probability. Such a number is sometimes called an 'industrial grade prime'--a large number that is so extremely likely to be prime that it can assumed that it actually is prime for all practical purposes. This implementation uses the Rabin-Miller algorithm (Schneier, p. 159)." | iterations factor pMinusOne b m r a j z couldBePrime | iterations := 50. "Note: The DSA spec requires >50 iterations; Schneier says 5 are enough (p. 260)" "quick elimination: check for p divisible by a small prime" SmallPrimes ifNil: [ "generate list of small primes > 2" SmallPrimes := Integer primesUpTo: 2000. SmallPrimes := SmallPrimes copyFrom: 2 to: SmallPrimes size]. factor := SmallPrimes detect: [:f | (p \\ f) = 0] ifNone: [nil]. factor ifNotNil: [^ p = factor]. pMinusOne := p - 1. b := self logOfLargestPowerOfTwoDividing: pMinusOne. m := pMinusOne // (2 raisedTo: b). "Assert: pMinusOne = m * (2 raisedTo: b) and m is odd" Transcript show: ' Prime test pass '. r := Random new. 1 to: iterations do: [:i | Transcript show: i printString; space. a := (r next * 16rFFFFFF) truncated. j := 0. z := (a raisedTo: m modulo: p) normalize. couldBePrime := z = 1. [couldBePrime] whileFalse: [ z = 1 ifTrue: [Transcript show: 'failed!!'; cr. ^ false]. "not prime" z = pMinusOne ifTrue: [couldBePrime := true] ifFalse: [ (j := j + 1) < b ifTrue: [z := (z * z) \\ p] ifFalse: [Transcript show: 'failed!!'; cr. ^ false]]]]. "not prime" Transcript show: 'passed!!'; cr. ^ true "passed all tests; probably prime." ! ! !DigitalSignatureAlgorithm methodsFor: 'public' stamp: 'adrian-lienhard 5/18/2009 21:07'! computeSignatureForMessageHash: hash privateKey: privateKey "Answer the digital signature of the given message hash using the given private key. A signature is a pair of large integers. The private key is an array of four large integers: (p, q, g, x)." | p q g x r s k tmp | p := privateKey first. q := privateKey second. g := privateKey third. x := privateKey fourth. r := s := 0. [r = 0 or: [s = 0]] whileTrue: [ k := self nextRandom160 \\ q. r := (g raisedTo: k modulo: p) \\ q. tmp := (hash + (x * r)) \\ q. s := ((self inverseOf: k mod: q) * tmp) \\ q]. ^ Array with: r with: s. ! ! !DigitalSignatureAlgorithm methodsFor: 'public' stamp: 'adrian-lienhard 5/18/2009 21:08'! generateKeySet "Generate and answer a key set for DSA. The result is a pair (). Each key is an array of four large integers. The private key is (p, q, g, x); the public one is (p, q, g, y). The signer must be sure to record (p, q, g, x), and must keep x secret to prevent someone from forging their signature." "Note: Key generation can take some time. Open a transcript so you can see what's happening and take a coffee break!!" | qAndPandS q p exp g h x y | qAndPandS := self generateQandP. Transcript show: 'Computing g...'. q := qAndPandS first. p := qAndPandS second. exp := (p - 1) / q. h := 2. [g := h raisedTo: exp modulo: p. g = 1] whileTrue: [h := h + 1]. Transcript show: 'done.'; cr. Transcript show: 'Computing x and y...'. x := self nextRandom160. y := g raisedTo: x modulo: p. Transcript show: 'done.'; cr. Transcript show: 'Key generation complete!!'; cr. ^ Array with: (Array with: p with: q with: g with: x) with: (Array with: p with: q with: g with: y). ! ! !DigitalSignatureAlgorithm methodsFor: 'public' stamp: 'PeterHugossonMiller 9/3/2009 01:13'! signatureToString: aSignature "Answer a string representation of the given signature. This string can be parsed using the stringToSignature: method." | s | s := (String new: 2000) writeStream. s nextPutAll: '[DSA digital signature '. s nextPutAll: aSignature first printStringHex. s space. s nextPutAll: aSignature second printStringHex. s nextPutAll: ']'. ^ s contents ! ! !DigitalSignatureAlgorithm methodsFor: 'public' stamp: 'dc 5/30/2008 10:17'! stringToSignature: aString "Answer the signature stored in the given string. A signature string has the format: '[DSA digital signature ]' where and are large positive integers represented by strings of hexidecimal digits." | prefix stream r s | prefix := '[DSA digital signature '. (aString beginsWith: prefix) ifFalse: [ self error: 'bad signature prefix' ]. stream := aString readStream. stream position: prefix size. r := Integer readFrom: stream base: 16. stream next. s := Integer readFrom: stream base: 16. ^ Array with: r with: s! ! !DigitalSignatureAlgorithm methodsFor: 'public' stamp: 'adrian-lienhard 5/18/2009 21:08'! verifySignature: aSignature ofMessageHash: hash publicKey: publicKey "Answer true if the given signature is the authentic signature of the given message hash. That is, if the signature must have been computed using the private key set corresponding to the given public key. The public key is an array of four large integers: (p, q, g, y)." | p q g y r s w u1 u2 v0 v | p := publicKey first. q := publicKey second. g := publicKey third. y := publicKey fourth. r := aSignature first. s := aSignature last. ((r > 0) and: [r < q]) ifFalse: [^ false]. "reject" ((s > 0) and: [s < q]) ifFalse: [^ false]. "reject" w := self inverseOf: s mod: q. u1 := (hash * w) \\ q. u2 := (r * w) \\ q. v0 := (g raisedTo: u1 modulo: p) * (y raisedTo: u2 modulo: p). v := ( v0 \\ p) \\ q. ^ v = r. ! ! !DigitalSignatureAlgorithm methodsFor: 'private' stamp: 'raa 5/30/2000 15:47'! generateQandP "Generate the two industrial-grade primes, q (160-bits) and p (512-bit) needed to build a key set. Answer the array (q, p, s), where s is the seed that from which q and p were created. This seed is normally discarded, but can be used to verify the key generation process if desired." | pBits halfTwoToTheP chunkCount sAndq q twoQ n c w x p s | pBits := 512. "desired size of p in bits" halfTwoToTheP := 2 raisedTo: (pBits - 1). chunkCount := pBits // 160. Transcript show: 'Searching for primes q and p...'; cr. [true] whileTrue: [ sAndq := self generateSandQ. Transcript show: ' Found a candidate q.'; cr. s := sAndq first. q := sAndq last. twoQ := q bitShift: 1. n := 2. c := 0. [c < 4096] whileTrue: [ w := self generateRandomLength: pBits s: s n: n. x := w + halfTwoToTheP. p := (x - ( x \\ twoQ)) + 1. p highBit = pBits ifTrue: [ Transcript show: ' Testing potential p ', (c + 1) printString, '...'; cr. (self isProbablyPrime: p) ifTrue: [ Transcript show: ' Found p!!'; cr. ^ Array with: q with: p with: s]]. n := n + chunkCount + 1. c := c + 1]]. ! ! !DigitalSignatureAlgorithm methodsFor: 'private' stamp: 'jm 12/13/1999 16:36'! generateRandomLength: bitLength s: s n: n "Answer a random number of bitLength bits generated using the secure hash algorithm." | sha out count extraBits v | sha := SecureHashAlgorithm new. out := 0. count := (bitLength // 160). extraBits := bitLength - (count * 160). 0 to: count do: [:k | v := sha hashInteger: (s + n + k). k = count ifTrue: [ v := v - ((v >> extraBits) << extraBits)]. out := out bitOr: (v bitShift: (160 * k))]. ^ out ! ! !DigitalSignatureAlgorithm methodsFor: 'private' stamp: 'raa 5/30/2000 15:46'! generateSandQ "Generate a 160-bit random seed s and an industrial grade prime q." | hasher s sPlusOne u q | hasher := SecureHashAlgorithm new. [true] whileTrue: [ s := self nextRandom160. sPlusOne := s + 1. sPlusOne highBit > 160 ifTrue: [sPlusOne := sPlusOne \\ (2 raisedTo: 160)]. u := (hasher hashInteger: s) bitXor: (hasher hashInteger: sPlusOne). q := u bitOr: ((1 bitShift: 159) bitOr: 1). (self isProbablyPrime: q) ifTrue: [^ Array with: s with: q]]. ! ! !DigitalSignatureAlgorithm methodsFor: 'private' stamp: 'jm 12/13/1999 11:12'! logOfLargestPowerOfTwoDividing: aPositiveInteger "Answer the base-2 log of the largest power of two that divides the given integer. For example, the largest power of two that divides 24 is 8, whose log base-2 is 3. Do this efficiently even when the given number is a large integer. Assume that the given integer is > 0." "DigitalSignatureAlgorithm new largestPowerOfTwoDividing: (32 * 3)" | digitIndex power d | digitIndex := (1 to: aPositiveInteger digitLength) detect: [:i | (aPositiveInteger digitAt: i) ~= 0]. power := (digitIndex - 1) * 8. d := aPositiveInteger digitAt: digitIndex. [d odd] whileFalse: [ power := power + 1. d := d bitShift: -1]. ^ power ! ! !DigitalSignatureAlgorithm methodsFor: 'private' stamp: 'jm 12/13/1999 14:39'! nextRandom160 "Answer a newly generated 160-bit random number in the range [1..(2^160 - 1)]." "Details: Try again in the extremely unlikely chance that zero is encountered." | result | result := 0. [result = 0] whileTrue: [ result := SecureHashAlgorithm new hashInteger: randKey seed: randSeed. randKey := randKey + result + 1]. ^ result ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DigitalSignatureAlgorithm class instanceVariableNames: ''! !DigitalSignatureAlgorithm class methodsFor: 'examples' stamp: 'jm 12/22/1999 11:23'! example "Example of signing a message and verifying its signature." "Note: Secure random numbers are needed for key generation and message signing, but not for signature verification. There is no need to call initRandomFromUser if you are merely checking a signature." "DigitalSignatureAlgorithm example" | msg keys sig | msg := 'This is a test...'. keys := self testKeySet. sig := self sign: msg privateKey: keys first. self inform: 'Signature created'. (self verify: sig isSignatureOf: msg publicKey: keys last) ifTrue: [self inform: 'Signature verified.'] ifFalse: [self error: 'ERROR!! Signature verification failed']. ! ! !DigitalSignatureAlgorithm class methodsFor: 'examples' stamp: 'mdr 8/31/2000 18:43'! testExamplesFromDisk "verify messages from file on disk" "Note: Secure random numbers are needed for key generation and message signing, but not for signature verification. There is no need to call initRandomFromUser if you are merely checking a signature." "DigitalSignatureAlgorithm testExamplesFromDisk" | msg sig file publicKey | file := FileStream readOnlyFileNamed: 'dsa.test.out'. [ [file atEnd] whileFalse: [ sig := file nextChunk. msg := file nextChunk. publicKey := Compiler evaluate: file nextChunk. (self verify: sig isSignatureOf: msg publicKey: publicKey) ifTrue: [ Transcript show: 'SUCCESS: ',msg; cr. ] ifFalse: [ self error: 'ERROR!! Signature verification failed' ]. ]. ] ensure: [file close] ! ! !DigitalSignatureAlgorithm class methodsFor: 'examples' stamp: 'jm 12/22/1999 11:28'! testKeySet "Answer a pair of keys for testing. The first key is the private key, the second one is the public key." "WARNING: This test key set is public should be used only for testing!! In a real application, the user would create a set of keys using generateKeySet and would keep the private key secret." ^ #( (8343811888543852523216773185009428259187948644369498021763210776677854991854533186365944349987509452133156416880596803846631577352387751880552969116768071 1197175832754339660404549606408619548226315875117 1433467472198821951822151391684734233265646022897503720591270330985699984763922266163182803556189497900262038518780931942996381297743579119123094520048965 957348690772296812) (8343811888543852523216773185009428259187948644369498021763210776677854991854533186365944349987509452133156416880596803846631577352387751880552969116768071 1197175832754339660404549606408619548226315875117 1433467472198821951822151391684734233265646022897503720591270330985699984763922266163182803556189497900262038518780931942996381297743579119123094520048965 4645213122572190617807944614677917601101008235397095646475699959851618402406173485853587185431290863173614335452934961425661774118334228449202337038283799)) ! ! !DigitalSignatureAlgorithm class methodsFor: 'examples' stamp: 'RAA 5/31/2000 08:46'! timeDecode: count "Example of signing a message and verifying its signature." "Note: Secure random numbers are needed for key generation and message signing, but not for signature verification. There is no need to call initRandomFromUser if you are merely checking a signature." "DigitalSignatureAlgorithm timeDecode: 20" | msg keys sig s dsa | dsa := DigitalSignatureAlgorithm new. dsa initRandomFromUser. #(1 10 100 1000 10000 100000) do: [ :extraLen | s := String new: extraLen. 1 to: s size do: [ :i | s at: i put: (Character value: 200 atRandom)]. msg := 'This is a test...',s. keys := self testKeySet. sig := self sign: msg privateKey: keys first dsa: dsa. "self inform: 'Signature created'." self timeDirect: [ count timesRepeat: [ (self verify: sig isSignatureOf: msg publicKey: keys last) ifFalse: [self error: 'ERROR!! Signature verification failed']. ]. ] as: 'verify msgLen = ',msg size printString count: count ]. ! ! !DigitalSignatureAlgorithm class methodsFor: 'examples' stamp: 'RAA 5/31/2000 13:13'! writeExamplesToDisk "Example of signing a message and verifying its signature. Used to create samples from one implementation that could later be tested with a different implementation" "Note: Secure random numbers are needed for key generation and message signing, but not for signature verification. There is no need to call initRandomFromUser if you are merely checking a signature." "DigitalSignatureAlgorithm writeExamplesToDisk" | sig file keyList dsa msgList | dsa := DigitalSignatureAlgorithm new. dsa initRandomFromUser. self inform: 'About to generate 5 key sets. Will take a while'. keyList := {self testKeySet},((1 to: 5) collect: [ :ignore | self generateKeySet]). msgList := {'This is a test...'. 'This is the second test period.'. 'And finally, a third message'}. file := FileStream newFileNamed: 'dsa.test.out'. [ msgList do: [ :msg | keyList do: [ :keys | sig := self sign: msg privateKey: keys first dsa: dsa. (self verify: sig isSignatureOf: msg publicKey: keys last) ifTrue: [ file nextChunkPut: sig; nextChunkPut: msg; nextChunkPut: keys last storeString. ] ifFalse: [ self error: 'ERROR!! Signature verification failed' ]. ]. ]. ] ensure: [file close] ! ! !DigitalSignatureAlgorithm class methodsFor: 'initialization' stamp: 'NorbertHartl 6/13/2008 11:38'! initialize "DigitalSignatureAlgorithm initialize" "SmallPrimes is a list of small primes greater than two." SmallPrimes := Integer primesUpTo: 2000. SmallPrimes := SmallPrimes copyFrom: 2 to: SmallPrimes size. "HighBitOfByte maps a byte to the index of its top non-zero bit." HighBitOfByte := (0 to: 255) collect: [:byte | byte highBit]. ! ! !DigitalSignatureAlgorithm class methodsFor: 'public' stamp: 'ads 7/31/2003 14:01'! generateKeySet "Generate and answer a key set for code signing. The result is a pair (). Each key is an array of four large integers. The signer must be sure to record this keys set and must keep the private key secret to prevent someone from forging their signature." "Note: Key generation can take some time. Open a transcript so you can see what's happening and take a coffee break!!" "Note: Unguessable random numbers are needed for key generation. The user will be prompted to type a really long random string (two or three lines) to initialize the random number generator before generating a key set. A different random string should be typed for every session; it is not a password and we wish to produce different random number streams." "DigitalSignatureAlgorithm generateKeySet" | dsa | dsa := DigitalSignatureAlgorithm new. (self confirm: 'Shall I seed the random generator from the current sound input?') ifTrue: [dsa initRandomNonInteractively] ifFalse: [dsa initRandomFromUser]. ^ dsa generateKeySet ! ! !DigitalSignatureAlgorithm class methodsFor: 'public' stamp: 'stephane.ducasse 5/25/2008 15:23'! sign: aStringOrStream privateKey: privateKey "Sign the given message (a stream or string) and answer a signature string." "Note: Unguessable random numbers are needed for message signing. The user will be prompted to type a really long random string (two or three lines) to initialize the random number generator before signing a message. A different random string should be typed for every session; it is not a password and we wish to produce different random number streams." | dsa hasher h sig | dsa := DigitalSignatureAlgorithm new. dsa initRandomFromUser. hasher := SecureHashAlgorithm new. h := aStringOrStream class isBytes ifTrue: [ hasher hashMessage: aStringOrStream ] ifFalse: [ hasher hashStream: aStringOrStream ]. sig := dsa computeSignatureForMessageHash: h privateKey: privateKey. ^ dsa signatureToString: sig! ! !DigitalSignatureAlgorithm class methodsFor: 'public' stamp: 'stephane.ducasse 5/25/2008 15:23'! sign: aStringOrStream privateKey: privateKey dsa: dsa "Sign the given message (a stream or string) and answer a signature string." "Note: Unguessable random numbers are needed for message signing. The user will be prompted to type a really long random string (two or three lines) to initialize the random number generator before signing a message. A different random string should be typed for every session; it is not a password and we wish to produce different random number streams." | hasher h sig | hasher := SecureHashAlgorithm new. h := aStringOrStream class isBytes ifTrue: [ hasher hashMessage: aStringOrStream ] ifFalse: [ hasher hashStream: aStringOrStream ]. sig := dsa computeSignatureForMessageHash: h privateKey: privateKey. ^ dsa signatureToString: sig! ! !DigitalSignatureAlgorithm class methodsFor: 'public' stamp: 'stephane.ducasse 5/25/2008 15:23'! verify: signatureString isSignatureOf: aStringOrStream publicKey: publicKey "Answer true if the given signature string signs the given message (a stream or string)." "Note: Random numbers are not needed for signature verification; thus, there is no need to call initRandomFromUser before verifying a signature." | dsa hasher h sig | dsa := DigitalSignatureAlgorithm new. hasher := SecureHashAlgorithm new. h := aStringOrStream class isBytes ifTrue: [ hasher hashMessage: aStringOrStream ] ifFalse: [ hasher hashStream: aStringOrStream ]. sig := dsa stringToSignature: signatureString. ^ dsa verifySignature: sig ofMessageHash: h publicKey: publicKey! ! !DigitalSignatureAlgorithm class methodsFor: 'testing' stamp: 'RAA 5/31/2000 08:21'! time: aBlock as: aString count: anInteger ^{anInteger. aString. (Time millisecondsToRun: aBlock)}! ! !DigitalSignatureAlgorithm class methodsFor: 'testing' stamp: 'RAA 5/31/2000 08:40'! timeDirect: aBlock as: aString count: anInteger Transcript show: anInteger asStringWithCommas,' ', aString ,' took ', (Time millisecondsToRun: aBlock) asStringWithCommas,' ms'; cr ! ! ArrayedCollection subclass: #DirectoryEntry instanceVariableNames: 'name creationTime modificationTime dirFlag fileSize' classVariableNames: '' poolDictionaries: '' category: 'Files-Directories'! !DirectoryEntry commentStamp: '' prior: 0! an entry in a directory; a reference to either a file or a directory.! !DirectoryEntry methodsFor: 'access' stamp: 'ls 7/15/1998 21:37'! creationTime "time the entry was created. (what's its type?)" ^creationTime! ! !DirectoryEntry methodsFor: 'access' stamp: 'ls 7/15/1998 21:38'! fileSize "size of the entry, if it's a file" ^fileSize! ! !DirectoryEntry methodsFor: 'access' stamp: 'ls 7/15/1998 21:38'! isDirectory "whether this entry represents a directory" ^dirFlag! ! !DirectoryEntry methodsFor: 'access' stamp: 'ls 7/15/1998 21:37'! modificationTime "time the entry was last modified" ^modificationTime! ! !DirectoryEntry methodsFor: 'access' stamp: 'ls 7/15/1998 21:37'! name "name of the entry" ^name! ! !DirectoryEntry methodsFor: 'access-compatibility' stamp: 'ls 7/15/1998 22:29'! at: index "compatibility interface" "self halt: 'old-style access to DirectoryEntry'" index = 1 ifTrue: [ ^self name ]. index = 2 ifTrue: [ ^self creationTime ]. index = 3 ifTrue: [ ^self modificationTime ]. index = 4 ifTrue:[ ^self isDirectory ]. index = 5 ifTrue:[ ^self fileSize ]. self error: 'invalid index specified'.! ! !DirectoryEntry methodsFor: 'access-compatibility' stamp: 'ls 7/15/1998 22:16'! size ^5! ! !DirectoryEntry methodsFor: 'multilingual system' stamp: 'stephaneducasse 2/4/2006 20:31'! convertFromSystemName name := (FilePath pathName: name isEncoded: true) asSqueakPathName! ! !DirectoryEntry methodsFor: 'private-initialization' stamp: 'stephaneducasse 2/4/2006 20:31'! privateName: name0 creationTime: creationTime0 modificationTime: modificationTime0 isDirectory: isDirectory0 fileSize: fileSize0 name := name0. creationTime := creationTime0. modificationTime := modificationTime0. dirFlag := isDirectory0. fileSize := fileSize0.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DirectoryEntry class instanceVariableNames: ''! !DirectoryEntry class methodsFor: 'instance creation' stamp: 'ls 7/15/1998 21:42'! fromArray: array ^self name: (array at: 1) creationTime: (array at: 2) modificationTime: (array at: 3) isDirectory: (array at: 4) fileSize: (array at: 5) ! ! !DirectoryEntry class methodsFor: 'instance creation' stamp: 'ls 7/15/1998 21:41'! name: name0 creationTime: creationTime modificationTime: modificationTime isDirectory: isDirectory fileSize: fileSize ^self new privateName: name0 creationTime: creationTime modificationTime: modificationTime isDirectory: isDirectory fileSize: fileSize! ! HierarchicalURI subclass: #DirectoryURI instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Network-URI'! Object subclass: #DiskProxy instanceVariableNames: 'globalObjectName preSelector constructorSelector constructorArgs' classVariableNames: '' poolDictionaries: '' category: 'System-Object Storage'! !DiskProxy commentStamp: '' prior: 0! A DiskProxy is an externalized form of an object to write on a DataStream. It contains a "constructor" message to regenerate the object, in context, when sent a comeFullyUpOnReload message (i.e. "internalize"). We are now using DiskProxy for shared system objects like StrikeFonts. The idea is to define, for each kind of object that needs special externalization, a class method that will internalize the object by reconstructing it from its defining state. We call this a "constructor" method. Then externalize such an object as a frozen message that invokes this method--a DiskProxy. (Here is the old comment: Constructing a new object is good for any object that (1) can not be externalized simply by snapshotting and reloading its instance variables (like a CompiledMethod or a Picture), or (2) wants to be free to evolve its internal representation without making stored instances obsolete (and dangerous). Snapshotting and reloading an object"s instance variables is a dangerous breach of encapsulation. The internal structure of the class is then free to evolve. All externalized instances will be useful as long as the constructor methods are maintained with the same semantics. There may be several constructor methods for a particular class. This is useful for (1) instances with characteristically different defining state, and (2) newer, evolved forms of an object and its constructors, with the old constructor methods kept around so old data can still be properly loaded.) Create one like this example from class Picture DiskProxy global: #Picture selector: #fromByteArray: args: (Array with: self storage asByteArray) * See also subclass DiskProxyQ that will construct an object in the above manner and then send it a sequence of messages. This may save creating a wide variety of constructor methods. It is also useful because the newly read-in DiskProxyQ can catch messages like #objectContainedIn: (via #doesNotUnderstand:) and add them to the queue of messages to send to the new object. * We may also want a subclass of DiskProxy that evaluates a string expression to compute the receiver of the constructor message. My instance variables: * globalObjectName -- the Symbol name of a global object in the System dictionary (usually a class). * constructorSelector -- the constructor message selector Symbol to send to the global object (perform:withArguments:), typically a variation on newFrom:. * constructorArgs -- the Array of arguments to pass in the constructor message. -- 11/9/92 Jerry Morrison ! !DiskProxy methodsFor: 'accessing' stamp: 'tk 3/10/2000 23:50'! constructorArgs ^ constructorArgs! ! !DiskProxy methodsFor: 'accessing' stamp: 'tk 11/6/2000 22:38'! constructorSelector ^ constructorSelector! ! !DiskProxy methodsFor: 'accessing' stamp: 'tk 11/6/2000 22:38'! globalObjectName ^ globalObjectName! ! !DiskProxy methodsFor: 'accessing' stamp: 'tk 11/6/2000 22:35'! preSelector ^ preSelector! ! !DiskProxy methodsFor: 'accessing' stamp: 'tk 4/8/1999 12:54'! preSelector: aSelector preSelector := aSelector! ! !DiskProxy methodsFor: 'accessing' stamp: 'tk 10/6/2000 15:18'! simpleGlobalOrNil "Return the object I refer to if it is a simple global in Smalltalk." preSelector ifNotNil: [^ nil]. constructorSelector == #yourself ifFalse: [^ nil]. ^ Smalltalk at: globalObjectName ifAbsent: [nil]. ! ! !DiskProxy methodsFor: 'exceptions' stamp: 'tk 3/14/2000 16:27'! enter "Enter the new project" self enter: false revert: false saveForRevert: false.! ! !DiskProxy methodsFor: 'exceptions' stamp: 'RAA 5/17/2000 11:51'! loadFromServer "In support of check for newer version in ProjectViewMorph menu" self enter ! ! !DiskProxy methodsFor: 'i/o' stamp: 'stephane.ducasse 7/10/2009 17:44'! comeFullyUpOnReload: smartRefStream "Internalize myself into a fully alive object after raw loading from a DataStream. (See my class comment.) DataStream will substitute the object from this eval for the DiskProxy." | globalObj symbol arrayIndex | symbol := globalObjectName. "See if class is mapped to another name" (smartRefStream respondsTo: #renamed) ifTrue: ["If in outPointers in an ImageSegment, remember original class name. See mapClass:installIn:. Would be lost otherwise." (thisContext sender sender sender sender sender sender sender sender receiver class == ImageSegment and: [thisContext sender sender sender sender method == (DataStream compiledMethodAt: #readArray)]) ifTrue: [arrayIndex := thisContext sender sender sender sender tempAt: 4. "index var in readArray. Later safer to find i on stack of context." smartRefStream renamedConv at: arrayIndex put: symbol]. "save original name" symbol := smartRefStream renamed at: symbol ifAbsent: [symbol]]. "map" globalObj := Smalltalk at: symbol ifAbsent: [preSelector == nil & (constructorSelector = #yourself) ifTrue: [Transcript cr; show: symbol , ' is undeclared.'. (Undeclared includesKey: symbol) ifTrue: [^ Undeclared at: symbol]. Undeclared at: symbol put: nil. ^ nil]. ^ self error: 'Global "' , symbol , '" not found']. preSelector ifNotNil: [Symbol hasInterned: preSelector ifTrue: [:selector | [globalObj := globalObj perform: selector] on: Error do: [:ex | ex messageText = 'key not found' ifTrue: [^ nil]. ^ ex signal]]]. "keep the Proxy if Project does not exist" constructorSelector ifNil: [^ globalObj]. Symbol hasInterned: constructorSelector ifTrue: [:selector | [^ globalObj perform: selector withArguments: constructorArgs] on: Error do: [:ex | ex messageText = 'key not found' ifTrue: [^ nil]. ^ ex signal]]. "args not checked against Renamed" ^ nil! ! !DiskProxy methodsFor: 'i/o' stamp: 'tk 3/26/98 11:17'! storeDataOn: aDataStream "Besides just storing, get me inserted into references, so structures will know about class DiskProxy." super storeDataOn: aDataStream. aDataStream references at: self put: #none. "just so instVarInfo: will find it and put it into structures"! ! !DiskProxy methodsFor: 'initialization' stamp: 'tk 4/8/1999 12:58'! global: globalNameSymbol preSelector: aSelector selector: selectorSymbol args: argArray "Initialize self as a DiskProxy constructor with the given globalNameSymbol, selectorSymbol, and argument Array. I will internalize by looking up the global object name in the SystemDictionary (Smalltalk) and sending it this message with these arguments." globalObjectName := globalNameSymbol asSymbol. preSelector := aSelector asSymbol. constructorSelector := selectorSymbol asSymbol. constructorArgs := argArray.! ! !DiskProxy methodsFor: 'initialization' stamp: 'tk 11/4/1999 19:28'! global: globalNameSymbol selector: selectorSymbol args: argArray "Initialize self as a DiskProxy constructor with the given globalNameSymbol, selectorSymbol, and argument Array. I will internalize by looking up the global object name in the SystemDictionary (Smalltalk) and sending it this message with these arguments." (globalNameSymbol beginsWith: 'AnObsolete') ifTrue: [ self error: 'Trying to write out, ', globalNameSymbol]. globalObjectName := globalNameSymbol asSymbol. constructorSelector := selectorSymbol asSymbol. constructorArgs := argArray.! ! !DiskProxy methodsFor: 'printing' stamp: 'ar 4/10/2005 18:46'! printOn: aStream "Try to report the name of the project" globalObjectName == #Project ifFalse: [^ super printOn: aStream]. constructorArgs size > 0 ifFalse: [^ super printOn: aStream]. constructorArgs first isString ifFalse: [^ super printOn: aStream]. aStream nextPutAll: constructorArgs first, ' (on server)'! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DiskProxy class instanceVariableNames: ''! !DiskProxy class methodsFor: 'instance creation'! global: globalNameSymbol selector: selectorSymbol args: argArray "Create a new DiskProxy constructor with the given globalNameSymbol, selectorSymbol, and argument Array. It will internalize itself by looking up the global object name in the SystemDictionary (Smalltalk) and sending it this message with these arguments." ^ self new global: globalNameSymbol selector: selectorSymbol args: argArray! ! DisplayScreen subclass: #DisplayHostWindow instanceVariableNames: 'windowProxy title windowType' classVariableNames: 'ActiveWindowIndex' poolDictionaries: '' category: 'Graphics-External-Ffenestri'! !DisplayHostWindow commentStamp: '' prior: 0! A subclass of DisplayScreen that uses a (platform appropriate) HostWindowProxy to do its displaying in a separate host OS window. This is just one example of a client for HostWindowProxy. See #test #test2 and HostWindowTests for example usage.! !DisplayHostWindow methodsFor: 'basic api' stamp: 'tpr 9/21/2004 16:57'! forceToScreen "update the area defined by my bounds" self forceToScreen: self boundingBox! ! !DisplayHostWindow methodsFor: 'basic api' stamp: 'tpr 10/7/2004 10:51'! forceToScreen: damageRectangle "update the area defined by damageRectangle" windowProxy ifNotNil:[ windowProxy forceToScreen: damageRectangle]! ! !DisplayHostWindow methodsFor: 'basic api' stamp: 'tpr 10/11/2004 16:56'! windowPosition "return the current position of the window" ^windowProxy ifNotNil:[ windowProxy windowPosition]! ! !DisplayHostWindow methodsFor: 'basic api' stamp: 'tpr 10/11/2004 16:56'! windowPosition: aPoint "set the position of the window and then return the new position" ^windowProxy ifNotNil:[ windowProxy windowPosition: aPoint]! ! !DisplayHostWindow methodsFor: 'basic api' stamp: 'tpr 10/11/2004 16:56'! windowSize "return the current size of the window - not neccessarily the same as my bitmap" ^windowProxy ifNotNil:[ windowProxy windowSize]! ! !DisplayHostWindow methodsFor: 'basic api' stamp: 'tpr 10/11/2004 16:56'! windowSize: aPoint "Set the size of the window and then return the current size of the window - not neccessarily the same " ^windowProxy ifNotNil:[ windowProxy windowSize: aPoint]! ! !DisplayHostWindow methodsFor: 'basic api' stamp: 'lr 7/4/2009 10:42'! windowTitle: titleString "set the label in the window titlebar to titleString" title := titleString. windowProxy ifNotNil: [ windowProxy windowTitle: title ]! ! !DisplayHostWindow methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! close "close this window" windowProxy ifNil: [ ^ self error: 'cannot close never opened window' ]. "We don't use 'self windowProxy close' here because if we've never setup the window why do it now only to close it immediately?" windowProxy close. windowProxy := nil! ! !DisplayHostWindow methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! open "open the host window" windowProxy ifNil: [ windowProxy := HostWindowProxy on: self ]. windowType ifNil: [ windowType := #defaultWindowType ]. windowProxy perform: windowType. ^ windowProxy open! ! !DisplayHostWindow methodsFor: 'snapshots' stamp: 'tpr 10/14/2004 16:13'! actualScreenSize "return the host window size as if it were 'the' screen" ^self windowSize! ! !DisplayHostWindow methodsFor: 'snapshots' stamp: 'lr 7/4/2009 10:42'! resetProxy "private - for use when resuming a snapshot file only. If the windowProxy had previously been created, nil it and reopen cleanly. IF you try to use this in a 'live' system it will NOT close the windows since startup conditions assume that proxies are invalid so we don't attempt to close them - since that could cause other problems" windowProxy ifNotNil: [ windowProxy := nil. self open ]! ! !DisplayHostWindow methodsFor: 'testing' stamp: 'lr 7/4/2009 10:42'! test "((DisplayHostWindow extent: 400@400 depth: 16 ) translateBy: 210@450) test" "Should a) open a window with the upper left portion of the current Display b) find the window size f) close the window" | size | self open. Display displayOn: self. self forceToScreen: self boundingBox. size := self windowSize. self close. ^ size! ! !DisplayHostWindow methodsFor: 'testing' stamp: 'tpr 10/6/2004 21:46'! test2 "((DisplayHostWindow extent: 400@400 depth: 16 ) translateBy: 210@450) test2" "Should a) open a window with the upper left portion of the current Display b) update the middle area with part of Display c) move the window from 210@450 to 300@300 d) change the window title e) change the window size from 400@400 to 600@400 f) wait 4 seconds so you can see the result g) close the window via the garbage collecttor finalizing it" self open. Display displayOn: self. self forceToScreen. Display displayOn: self at: -100@-200. self forceToScreen: (100@100 extent: 200@200). self windowPosition: 300@300. self windowTitle: 'YooHoo!! New title'. self windowSize: 600@400. (Delay forSeconds: 4) wait.! ! !DisplayHostWindow methodsFor: 'private' stamp: 'tpr 10/14/2004 16:12'! setExtent: extent depth: bitsPerPixel "reset the host window size to suit the extent chosen" self windowSize: extent. ^super setExtent: extent depth: bitsPerPixel ! ! DisplayObject subclass: #DisplayMedium instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Display Objects'! !DisplayMedium commentStamp: '' prior: 0! I am a display object which can both paint myself on a medium (displayOn: messages), and can act as a medium myself. My chief subclass is Form.! !DisplayMedium methodsFor: 'bordering'! border: aRectangle width: borderWidth "Paint a border whose rectangular area is defined by aRectangle. The width of the border of each side is borderWidth. Uses black for drawing the border." self border: aRectangle width: borderWidth fillColor: Color black. ! ! !DisplayMedium methodsFor: 'bordering'! border: aRectangle width: borderWidth fillColor: aHalfTone "Paint a border whose rectangular area is defined by aRectangle. The width of the border of each side is borderWidth. Uses aHalfTone for drawing the border." self border: aRectangle widthRectangle: (Rectangle left: borderWidth right: borderWidth top: borderWidth bottom: borderWidth) rule: Form over fillColor: aHalfTone! ! !DisplayMedium methodsFor: 'bordering'! border: aRectangle width: borderWidth rule: combinationRule fillColor: aHalfTone "Paint a border whose rectangular area is defined by aRectangle. The width of the border of each side is borderWidth. Uses aHalfTone for drawing the border." self border: aRectangle widthRectangle: (Rectangle left: borderWidth right: borderWidth top: borderWidth bottom: borderWidth) rule: combinationRule fillColor: aHalfTone! ! !DisplayMedium methodsFor: 'bordering'! border: aRectangle widthRectangle: insets rule: combinationRule fillColor: aHalfTone "Paint a border whose rectangular area is defined by aRectangle. The width of each edge of the border is determined by the four coordinates of insets. Uses aHalfTone and combinationRule for drawing the border." (aRectangle areasOutside: (aRectangle insetBy: insets)) do: [:edgeStrip | self fill: edgeStrip rule: combinationRule fillColor: aHalfTone]! ! !DisplayMedium methodsFor: 'coloring'! fill: aRectangle fillColor: aForm "Replace a rectangular area of the receiver with the pattern described by aForm according to the rule over." self fill: aRectangle rule: Form over fillColor: aForm! ! !DisplayMedium methodsFor: 'coloring'! fill: aRectangle rule: anInteger fillColor: aForm "Replace a rectangular area of the receiver with the pattern described by aForm according to the rule anInteger." self subclassResponsibility! ! !DisplayMedium methodsFor: 'coloring'! fillBlack "Set all bits in the receiver to black (ones)." self fill: self boundingBox fillColor: Color black! ! !DisplayMedium methodsFor: 'coloring'! fillBlack: aRectangle "Set all bits in the receiver's area defined by aRectangle to black (ones)." self fill: aRectangle rule: Form over fillColor: Color black! ! !DisplayMedium methodsFor: 'coloring'! fillColor: aColor "Set all pixels in the receiver to the color. Must be a correct color for this depth of medium. TK 1 Jun 96" self fill: self boundingBox fillColor: aColor! ! !DisplayMedium methodsFor: 'coloring'! fillGray "Set all bits in the receiver to gray." self fill: self boundingBox fillColor: Color gray! ! !DisplayMedium methodsFor: 'coloring'! fillGray: aRectangle "Set all bits in the receiver's area defined by aRectangle to the gray mask." self fill: aRectangle rule: Form over fillColor: Color gray! ! !DisplayMedium methodsFor: 'coloring'! fillShape: aShapeForm fillColor: aColor "Fill a region corresponding to 1 bits in aShapeForm with aColor" ^ self fillShape: aShapeForm fillColor: aColor at: 0@0! ! !DisplayMedium methodsFor: 'coloring' stamp: 'ar 5/28/2000 12:06'! fillShape: aShapeForm fillColor: aColor at: location "Fill a region corresponding to 1 bits in aShapeForm with aColor" ((BitBlt current destForm: self sourceForm: aShapeForm fillColor: aColor combinationRule: Form paint destOrigin: location + aShapeForm offset sourceOrigin: 0@0 extent: self extent clipRect: self boundingBox) colorMap: (Bitmap with: 0 with: 16rFFFFFFFF)) copyBits! ! !DisplayMedium methodsFor: 'coloring'! fillWhite "Set all bits in the form to white." self fill: self boundingBox fillColor: Color white. ! ! !DisplayMedium methodsFor: 'coloring'! fillWhite: aRectangle "Set all bits in the receiver's area defined by aRectangle to white." self fill: aRectangle rule: Form over fillColor: Color white. ! ! !DisplayMedium methodsFor: 'coloring'! fillWithColor: aColor "Fill the receiver's bounding box with the given color." self fill: self boundingBox fillColor: aColor. ! ! !DisplayMedium methodsFor: 'coloring' stamp: 'jm 6/18/1999 19:01'! reverse "Change all the bits in the receiver that are white to black, and the ones that are black to white." self fill: self boundingBox rule: Form reverse fillColor: (Color quickHighLight: self depth)! ! !DisplayMedium methodsFor: 'coloring' stamp: 'jm 6/18/1999 19:00'! reverse: aRectangle "Change all the bits in the receiver's area that intersects with aRectangle that are white to black, and the ones that are black to white." self fill: aRectangle rule: Form reverse fillColor: (Color quickHighLight: self depth)! ! !DisplayMedium methodsFor: 'coloring'! reverse: aRectangle fillColor: aMask "Change all the bits in the receiver's area that intersects with aRectangle according to the mask. Black does not necessarily turn to white, rather it changes with respect to the rule and the bit in a corresponding mask location. Bound to give a surprise." self fill: aRectangle rule: Form reverse fillColor: aMask! ! !DisplayMedium methodsFor: 'displaying'! copyBits: sourceRect from: sourceForm at: destOrigin clippingBox: clipRect rule: rule fillColor: aForm "Make up a BitBlt table and copy the bits." self subclassResponsibility! ! !DisplayMedium methodsFor: 'displaying' stamp: 'hmm 9/16/2000 21:27'! deferUpdatesIn: aRectangle while: aBlock "DisplayScreen overrides with something more involved..." ^aBlock value! ! !DisplayMedium methodsFor: 'displaying'! drawLine: sourceForm from: beginPoint to: endPoint clippingBox: clipRect rule: anInteger fillColor: aForm "Draw line by copying the argument, sourceForm, starting at location beginPoint and ending at endPoint, clipped by the rectangle, clipRect. The rule and mask for copying are the arguments anInteger and aForm." self subclassResponsibility! ! Object subclass: #DisplayObject instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Display Objects'! !DisplayObject commentStamp: '' prior: 0! The abstract protocol for most display primitives that are used by Views for presenting information on the screen.! !DisplayObject methodsFor: 'accessing'! extent "Answer the point that represents the width and height of the receiver's bounding box." ^self boundingBox extent! ! !DisplayObject methodsFor: 'accessing'! height "Answer the number that represents the height of the receiver's bounding box." ^self boundingBox height! ! !DisplayObject methodsFor: 'accessing'! offset "Answer the amount by which the receiver should be offset when it is displayed or its position is tested." self subclassResponsibility! ! !DisplayObject methodsFor: 'accessing'! offset: aPoint "Set the amount by which the receiver's position is offset." ^self! ! !DisplayObject methodsFor: 'accessing'! relativeRectangle "Answer a Rectangle whose top left corner is the receiver's offset position and whose width and height are the same as the receiver." ^Rectangle origin: self offset extent: self extent! ! !DisplayObject methodsFor: 'accessing'! width "Answer the number that represents the width of the receiver's bounding box." ^self boundingBox width! ! !DisplayObject methodsFor: 'display box access'! boundingBox "Answer the rectangular area that represents the boundaries of the receiver's space of information." ^self computeBoundingBox! ! !DisplayObject methodsFor: 'display box access'! center ^ self boundingBox center! ! !DisplayObject methodsFor: 'display box access'! computeBoundingBox "Answer the rectangular area that represents the boundaries of the receiver's area for displaying information. This is the primitive for computing the area if it is not already known." self subclassResponsibility! ! !DisplayObject methodsFor: 'display box access'! initialExtent "Included here for when a FormView is being opened as a window. (4@4) covers border widths." ^ self extent + (4@4) ! ! !DisplayObject methodsFor: 'displaying-display'! display "Display the receiver on the Display at location 0,0." self displayOn: Display! ! !DisplayObject methodsFor: 'displaying-display'! follow: locationBlock while: durationBlock "Move an image around on the Display. Restore the background continuously without causing flashing. The argument, locationBlock, supplies each new location, and the argument, durationBlock, supplies true to continue, and then false to stop. 8/20/96 sw: call follow:while:bitsBehind: to do the real work. Note that th method now returns the final bits behind as method value." | bitsBehind loc | bitsBehind := Form fromDisplay: ((loc := locationBlock value) extent: self extent). ^ self follow: locationBlock while: durationBlock bitsBehind: bitsBehind startingLoc: loc! ! !DisplayObject methodsFor: 'displaying-display' stamp: 'ar 5/28/2000 12:06'! follow: locationBlock while: durationBlock bitsBehind: initialBitsBehind startingLoc: loc "Move an image around on the Display. Restore the background continuously without causing flashing. The argument, locationBlock, supplies each new location, and the argument, durationBlock, supplies true to continue or false to stop. This variant takes the bitsBehind as an input argument, and returns the final saved saved bits as method value." | location rect1 save1 save1Blt buffer bufferBlt newLoc rect2 bothRects | location := loc. rect1 := location extent: self extent. save1 := initialBitsBehind. save1Blt := BitBlt current toForm: save1. buffer := Form extent: self extent*2 depth: Display depth. "Holds overlapping region" bufferBlt := BitBlt current toForm: buffer. Display deferUpdates: true. self displayOn: Display at: location rule: Form paint. Display deferUpdates: false; forceToScreen: (location extent: self extent). [durationBlock value] whileTrue: [ newLoc := locationBlock value. newLoc ~= location ifTrue: [ rect2 := newLoc extent: self extent. bothRects := rect1 merge: rect2. (rect1 intersects: rect2) ifTrue: [ "when overlap, buffer background for both rectangles" bufferBlt copyFrom: bothRects in: Display to: 0@0. bufferBlt copyFrom: save1 boundingBox in: save1 to: rect1 origin - bothRects origin. "now buffer is clean background; get new bits for save1" save1Blt copy: (0@0 extent: self extent) from: rect2 origin - bothRects origin in: buffer. self displayOnPort: bufferBlt at: rect2 origin - bothRects origin rule: Form paint. Display deferUpdates: true. Display copy: bothRects from: 0@0 in: buffer rule: Form over. Display deferUpdates: false; forceToScreen: bothRects] ifFalse: [ "when no overlap, do the simple thing (both rects might be too big)" Display deferUpdates: true. Display copy: (location extent: save1 extent) from: 0@0 in: save1 rule: Form over. save1Blt copyFrom: rect2 in: Display to: 0@0. self displayOn: Display at: newLoc rule: Form paint. Display deferUpdates: false; forceToScreen: (location extent: save1 extent); forceToScreen: (newLoc extent: self extent)]. location := newLoc. rect1 := rect2]]. ^ save1 displayOn: Display at: location ! ! !DisplayObject methodsFor: 'displaying-display' stamp: 'di 9/12/97 11:09'! isTransparent ^ false! ! !DisplayObject methodsFor: 'displaying-display'! slideFrom: startPoint to: stopPoint nSteps: nSteps "does not display at the first point, but does at the last" | i p delta | i:=0. p:= startPoint. delta := (stopPoint-startPoint) // nSteps. ^ self follow: [p:= p+delta] while: [(i:=i+1) < nSteps]! ! !DisplayObject methodsFor: 'displaying-display' stamp: 'jm 10/22/97 07:43'! slideFrom: startPoint to: stopPoint nSteps: nSteps delay: milliSecs "Slide this object across the display over the given number of steps, pausing for the given number of milliseconds after each step." "Note: Does not display at the first point, but does at the last." | i p delta | i := 0. p := startPoint. delta := (stopPoint - startPoint) / nSteps asFloat. ^ self follow: [(p := p + delta) truncated] while: [ (Delay forMilliseconds: milliSecs) wait. (i := i + 1) < nSteps] ! ! !DisplayObject methodsFor: 'displaying-display' stamp: 'di 10/19/97 12:05'! slideFrom: startPoint to: stopPoint nSteps: nSteps delay: milliSecs andStay: stayAtEnd "Does not display at the first point, but does at the last. Moreover, if stayAtEnd is true, it leaves the dragged image at the stopPoint" | i done | i := 0. ^ self follow: [startPoint + ((stopPoint-startPoint) * i // nSteps)] while: [milliSecs ifNotNil: [(Delay forMilliseconds: milliSecs) wait]. ((done := (i := i+1) > nSteps) and: [stayAtEnd]) ifTrue: [^ self "Return without clearing the image"]. done not]! ! !DisplayObject methodsFor: 'displaying-display' stamp: 'sr 6/6/2000 05:37'! slideWithFirstFrom: startPoint to: stopPoint nSteps: nSteps delay: milliSecs "Slide this object across the display over the given number of steps, pausing for the given number of milliseconds after each step." "Note: Does display at the first point and at the last." | i p delta | i := 0. delta := stopPoint - startPoint / nSteps asFloat. p := startPoint - delta. ^ self follow: [(p := p + delta) truncated] while: [(Delay forMilliseconds: milliSecs) wait. (i := i + 1) <= nSteps]! ! !DisplayObject methodsFor: 'displaying-generic'! displayAt: aDisplayPoint "Display the receiver located at aDisplayPoint with default settings for the displayMedium, rule and halftone." self displayOn: Display at: aDisplayPoint clippingBox: Display boundingBox rule: Form over fillColor: nil! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium "Simple default display in order to see the receiver in the upper left corner of screen." self displayOn: aDisplayMedium at: 0 @ 0! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium at: aDisplayPoint "Display the receiver located at aDisplayPoint with default settings for rule and halftone." self displayOn: aDisplayMedium at: aDisplayPoint clippingBox: aDisplayMedium boundingBox rule: Form over fillColor: nil! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle "Display the receiver located at aDisplayPoint with default settings for rule and halftone. Information to be displayed must be confined to the area that intersects with clipRectangle." self displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: Form over fillColor: nil! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: ruleInteger fillColor: aForm "This is the basic display primitive for graphic display objects. Display the receiver located at aDisplayPoint with rule, ruleInteger, and mask, aForm. Information to be displayed must be confined to the area that intersects with clipRectangle." self subclassResponsibility! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium at: aDisplayPoint rule: ruleInteger "Display the receiver located at aPoint with default setting for the halftone and clippingBox." self displayOn: aDisplayMedium at: aDisplayPoint clippingBox: aDisplayMedium boundingBox rule: ruleInteger fillColor: nil! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle "Display primitive for the receiver where a DisplayTransformation is provided as an argument. Alignment is defaulted to the receiver's rectangle. Information to be displayed must be confined to the area that intersects with clipRectangle." self displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: self relativeRectangle center with: self relativeRectangle center rule: Form over fillColor: nil! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: alignmentPoint with: relativePoint "Display primitive where a DisplayTransformation is provided as an argument, rule is over and mask is Form black. Information to be displayed must be confined to the area that intersects with clipRectangle." self displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: alignmentPoint with: relativePoint rule: Form over fillColor: nil! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: alignmentPoint with: relativePoint rule: ruleInteger fillColor: aForm "Display the receiver where a DisplayTransformation is provided as an argument, rule is ruleInteger and mask is aForm. Translate by relativePoint-alignmentPoint. Information to be displayed must be confined to the area that intersects with clipRectangle." | absolutePoint | absolutePoint := displayTransformation applyTo: relativePoint. self displayOn: aDisplayMedium at: (absolutePoint - alignmentPoint) clippingBox: clipRectangle rule: ruleInteger fillColor: aForm ! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle fixedPoint: aPoint "Display the receiver where a DisplayTransformation is provided as an argument, rule is over and mask is Form black. No translation. Information to be displayed must be confined to the area that intersects with clipRectangle." self displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: aPoint with: aPoint rule: Form over fillColor: nil! ! !DisplayObject methodsFor: 'displaying-generic'! displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle rule: ruleInteger fillColor: aForm "Display the receiver where a DisplayTransformation is provided as an argument, rule is ruleInteger and mask is aForm. No translation. Information to be displayed must be confined to the area that intersects with clipRectangle." self displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: self relativeRectangle origin with: self relativeRectangle origin rule: ruleInteger fillColor: aForm! ! !DisplayObject methodsFor: 'displaying-generic'! displayOnPort: aPort self displayOnPort: aPort at: 0@0! ! !DisplayObject methodsFor: 'displaying-generic' stamp: 'jm 10/21/97 16:56'! displayOnPort: port at: location rule: rule port copyForm: self to: location rule: rule. ! ! !DisplayObject methodsFor: 'displaying-generic'! followCursor "Just show the Form following the mouse. 6/21/96 tk" Cursor blank showWhile: [self follow: [Sensor cursorPoint] while: [Sensor noButtonPressed]] ! ! !DisplayObject methodsFor: 'filein/out'! writeOnFileNamed: fileName "Saves the receiver on the file fileName in the format: fileCode, depth, extent, offset, bits." | file | file := FileStream newFileNamed: fileName. file binary. file nextPut: 2. "file code = 2" self writeOn: file. file close " | f | [(f := Form fromUser) boundingBox area>25] whileTrue: [f writeOnFileNamed: 'test.form'. (Form newFromFileNamed: 'test.form') display]. "! ! !DisplayObject methodsFor: 'filein/out' stamp: 'tk 2/19/1999 07:20'! writeUncompressedOnFileNamed: fileName "Saves the receiver on the file fileName in the format: fileCode, depth, extent, offset, bits." | file | file := FileStream newFileNamed: fileName. file binary. file nextPut: 2. "file code = 2" self writeUncompressedOn: file. file close " | f | [(f := Form fromUser) boundingBox area>25] whileTrue: [f writeUncompressedOnFileNamed: 'test.form'. (Form fromBinaryStream: (FileStream oldFileNamed: 'test.form')) display]. "! ! !DisplayObject methodsFor: 'transforming'! align: alignmentPoint with: relativePoint "Translate the receiver's offset such that alignmentPoint aligns with relativePoint." self offset: (self offset translateBy: relativePoint - alignmentPoint)! ! !DisplayObject methodsFor: 'transforming'! scaleBy: aPoint "Scale the receiver's offset by aPoint." self offset: (self offset scaleBy: aPoint)! ! !DisplayObject methodsFor: 'transforming'! translateBy: aPoint "Translate the receiver's offset." self offset: (self offset translateBy: aPoint)! ! !DisplayObject methodsFor: 'truncation and round off'! rounded "Convert the offset of the receiver to integer coordinates." self offset: self offset rounded! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DisplayObject class instanceVariableNames: ''! !DisplayObject class methodsFor: 'filein/out' stamp: 'mdr 8/31/2000 19:11'! collectionFromFileNamed: fileName "Answer a collection of Forms read from the external file named fileName. The file format is: fileCode, {depth, extent, offset, bits}." | formList f fileCode | formList := OrderedCollection new. f := (FileStream readOnlyFileNamed: fileName) binary. fileCode := f next. fileCode = 1 ifTrue: [ [f atEnd] whileFalse: [formList add: (self new readFromOldFormat: f)]] ifFalse: [ fileCode = 2 ifFalse: [self error: 'unknown Form file format'. ^ formList]. [f atEnd] whileFalse: [formList add: (self new readFrom: f)]]. f close. ^ formList ! ! !DisplayObject class methodsFor: 'filein/out'! writeCollection: coll onFileNamed: fileName "Saves a collection of Forms on the file fileName in the format: fileCode, {depth, extent, offset, bits}." | file | file := FileStream newFileNamed: fileName. file binary. file nextPut: 2. "file code = 2" coll do: [:f | f writeOn: file]. file close " | f c | c := OrderedCollection new. [(f := Form fromUser) boundingBox area>25] whileTrue: [c add: f]. Form writeCollection: c onFileNamed: 'test.forms'. c := Form collectionFromFileNamed: 'test.forms'. 1 to: c size do: [:i | (c at: i) displayAt: 0@(i*100)]. "! ! CharacterScanner subclass: #DisplayScanner instanceVariableNames: 'bitBlt lineY runX foregroundColor backgroundColor fillBlt lineHeight paragraph paragraphColor morphicOffset ignoreColorChanges' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Text'! !DisplayScanner commentStamp: '' prior: 0! My instances are used to scan text and display it on the screen or in a hidden form.! !DisplayScanner methodsFor: '*FreeType-override' stamp: 'tween 4/6/2007 12:51'! paddedSpace "Each space is a stop condition when the alignment is right justified. Padding must be added to the base width of the space according to which space in the line this space is and according to the amount of space that remained at the end of the line when it was composed." spaceCount := spaceCount + 1. destX := destX + spaceWidth + (line justifiedPadFor: spaceCount font: font). lastIndex := lastIndex + 1. ^ false! ! !DisplayScanner methodsFor: 'mvc-compatibility' stamp: 'lr 7/4/2009 10:42'! displayLines: linesInterval in: aParagraph clippedBy: visibleRectangle "The central display routine. The call on the primitive (scanCharactersFrom:to:in:rightX:) will be interrupted according to an array of stop conditions passed to the scanner at which time the code to handle the stop condition is run and the call on the primitive continued until a stop condition returns true (which means the line has terminated)." "leftInRun is the # of characters left to scan in the current run; when 0, it is time to call 'self setStopConditions'" | runLength done stopCondition leftInRun startIndex string lastPos | morphicOffset := 0 @ 0. leftInRun := 0. self initializeFromParagraph: aParagraph clippedBy: visibleRectangle. ignoreColorChanges := false. paragraph := aParagraph. foregroundColor := paragraphColor := aParagraph foregroundColor. backgroundColor := aParagraph backgroundColor. aParagraph backgroundColor isTransparent ifTrue: [ fillBlt := nil ] ifFalse: [ fillBlt := bitBlt copy. "Blt to fill spaces, tabs, margins" fillBlt sourceForm: nil; sourceOrigin: 0 @ 0. fillBlt fillColor: aParagraph backgroundColor ]. rightMargin := aParagraph rightMarginForDisplay. lineY := aParagraph topAtLineIndex: linesInterval first. bitBlt destForm deferUpdatesIn: visibleRectangle while: [ linesInterval do: [ :lineIndex | line := aParagraph lines at: lineIndex. lastIndex := line first. self setStopConditions. " causes an assignment to inst var. alignment " leftMargin := aParagraph leftMarginForDisplayForLine: lineIndex alignment: (alignment ifNil: [ textStyle alignment ]). destX := runX := leftMargin. line := aParagraph lines at: lineIndex. lineHeight := line lineHeight. fillBlt == nil ifFalse: [ fillBlt destX: visibleRectangle left destY: lineY width: visibleRectangle width height: lineHeight; copyBits ]. lastIndex := line first. leftInRun <= 0 ifTrue: [ self setStopConditions. "also sets the font" leftInRun := text runLengthFor: line first ]. destY := lineY + line baseline - font ascent. "Should have happened in setFont" runLength := leftInRun. runStopIndex := lastIndex + (runLength - 1) min: line last. leftInRun := leftInRun - (runStopIndex - lastIndex + 1). spaceCount := 0. done := false. string := text string. self handleIndentation. [ done ] whileFalse: [ startIndex := lastIndex. lastPos := destX @ destY. stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex in: string rightX: rightMargin stopConditions: stopConditions kern: kern. lastIndex >= startIndex ifTrue: [ font displayString: string on: bitBlt from: startIndex to: lastIndex at: lastPos kern: kern ]. "see setStopConditions for stopping conditions for displaying." done := self perform: stopCondition ]. fillBlt == nil ifFalse: [ fillBlt destX: destX destY: lineY width: visibleRectangle right - destX height: lineHeight; copyBits ]. lineY := lineY + lineHeight ] ]! ! !DisplayScanner methodsFor: 'mvc-compatibility' stamp: 'pavel.krivanek 11/21/2008 16:52'! initializeFromParagraph: aParagraph clippedBy: clippingRectangle super initializeFromParagraph: aParagraph clippedBy: clippingRectangle. bitBlt := UIManager default grafPort toForm: aParagraph destinationForm. bitBlt sourceX: 0; width: 0. "Init BitBlt so that the first call to a primitive will not fail" bitBlt combinationRule: (Display depth = 1 ifTrue: [ aParagraph rule ] ifFalse: [ Form paint ]). bitBlt colorMap: (Bitmap with: 0 with: (bitBlt destForm pixelValueFor: aParagraph foregroundColor)). "Assumes 1-bit deep fonts" bitBlt clipRect: clippingRectangle! ! !DisplayScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! displayLine: textLine offset: offset leftInRun: leftInRun "The call on the primitive (scanCharactersFrom:to:in:rightX:) will be interrupted according to an array of stop conditions passed to the scanner at which time the code to handle the stop condition is run and the call on the primitive continued until a stop condition returns true (which means the line has terminated). leftInRun is the # of characters left to scan in the current run; when 0, it is time to call setStopConditions." | done stopCondition nowLeftInRun startIndex string lastPos | line := textLine. morphicOffset := offset. lineY := line top + offset y. lineHeight := line lineHeight. rightMargin := line rightMargin + offset x. lastIndex := line first. leftInRun <= 0 ifTrue: [ self setStopConditions ]. leftMargin := (line leftMarginForAlignment: alignment) + offset x. destX := runX := leftMargin. fillBlt == nil ifFalse: [ "Not right" fillBlt destX: line left destY: lineY width: line width left height: lineHeight; copyBits ]. lastIndex := line first. leftInRun <= 0 ifTrue: [ nowLeftInRun := text runLengthFor: lastIndex ] ifFalse: [ nowLeftInRun := leftInRun ]. destY := lineY + line baseline - font ascent. runStopIndex := lastIndex + (nowLeftInRun - 1) min: line last. spaceCount := 0. done := false. string := text string. [ done ] whileFalse: [ startIndex := lastIndex. lastPos := destX @ destY. stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex in: string rightX: rightMargin stopConditions: stopConditions kern: kern. lastIndex >= startIndex ifTrue: [ font displayString: string on: bitBlt from: startIndex to: lastIndex at: lastPos kern: kern ]. "see setStopConditions for stopping conditions for displaying." done := self perform: stopCondition. lastIndex > runStopIndex ifTrue: [ done := true ] ]. ^ runStopIndex - lastIndex "Number of characters remaining in the current run"! ! !DisplayScanner methodsFor: 'scanning' stamp: 'lr 7/4/2009 10:42'! placeEmbeddedObject: anchoredMorph anchoredMorph relativeTextAnchorPosition ifNotNil: [ anchoredMorph position: anchoredMorph relativeTextAnchorPosition + (anchoredMorph owner textBounds origin x @ 0) - (0 @ morphicOffset y) + (0 @ lineY). ^ true ]. (super placeEmbeddedObject: anchoredMorph) ifFalse: [ ^ false ]. anchoredMorph isMorph ifTrue: [ anchoredMorph position: (destX - anchoredMorph width) @ lineY - morphicOffset ] ifFalse: [ destY := lineY. runX := destX. anchoredMorph displayOn: bitBlt destForm at: (destX - anchoredMorph width) @ destY clippingBox: bitBlt clipRect ]. ^ true! ! !DisplayScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! cr "When a carriage return is encountered, simply increment the pointer into the paragraph." lastIndex := lastIndex + 1. ^ false! ! !DisplayScanner methodsFor: 'stop conditions' stamp: 'di 9/3/2000 16:24'! crossedX "This condition will sometimes be reached 'legally' during display, when, for instance the space that caused the line to wrap actually extends over the right boundary. This character is allowed to display, even though it is technically outside or straddling the clipping ectangle since it is in the normal case not visible and is in any case appropriately clipped by the scanner." ^ true ! ! !DisplayScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! endOfRun "The end of a run in the display case either means that there is actually a change in the style (run code) to be associated with the string or the end of this line has been reached." | runLength | lastIndex = line last ifTrue: [ ^ true ]. runX := destX. runLength := text runLengthFor: (lastIndex := lastIndex + 1). runStopIndex := lastIndex + (runLength - 1) min: line last. self setStopConditions. ^ false! ! !DisplayScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! plainTab | oldX | oldX := destX. super plainTab. fillBlt == nil ifFalse: [ fillBlt destX: oldX destY: destY width: destX - oldX height: font height; copyBits ]! ! !DisplayScanner methodsFor: 'stop conditions' stamp: 'yo 10/4/2002 20:43'! setStopConditions "Set the font and the stop conditions for the current run." self setFont. self setConditionArray: (alignment = Justified ifTrue: [#paddedSpace]). " alignment = Justified ifTrue: [ stopConditions == DefaultStopConditions ifTrue:[stopConditions _ stopConditions copy]. stopConditions at: Space asciiValue + 1 put: #paddedSpace] "! ! !DisplayScanner methodsFor: 'stop conditions' stamp: 'lr 7/4/2009 10:42'! tab self plainTab. lastIndex := lastIndex + 1. ^ false! ! !DisplayScanner methodsFor: 'private' stamp: 'ar 5/17/2000 19:26'! setDestForm: df bitBlt setDestForm: df.! ! !DisplayScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setFont foregroundColor := paragraphColor. super setFont. "Sets font and emphasis bits, and maybe foregroundColor" font installOn: bitBlt foregroundColor: foregroundColor backgroundColor: Color transparent. text ifNotNil: [ destY := lineY + line baseline - font ascent ]! ! !DisplayScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! setPort: aBitBlt "Install the BitBlt to use" bitBlt := aBitBlt. bitBlt sourceX: 0; width: 0. "Init BitBlt so that the first call to a primitive will not fail" bitBlt sourceForm: nil "Make sure font installation won't be confused"! ! !DisplayScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! text: t textStyle: ts foreground: foreColor background: backColor fillBlt: blt ignoreColorChanges: shadowMode text := t. textStyle := ts. foregroundColor := paragraphColor := foreColor. (backgroundColor := backColor) isTransparent ifFalse: [ fillBlt := blt. fillBlt fillColor: backgroundColor ]. ignoreColorChanges := shadowMode! ! !DisplayScanner methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! textColor: textColor ignoreColorChanges ifTrue: [ ^ self ]. foregroundColor := textColor! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DisplayScanner class instanceVariableNames: ''! !DisplayScanner class methodsFor: 'queries' stamp: 'ar 5/17/2000 17:39'! defaultFont ^ TextStyle defaultFont! ! Form subclass: #DisplayScreen instanceVariableNames: 'clippingBox extraRegions' classVariableNames: 'DeferringUpdates DisplayChangeSignature LastScreenModeSelected ScreenSave' poolDictionaries: '' category: 'Graphics-Display Objects'! !DisplayScreen commentStamp: '' prior: 0! There is only one instance of me, Display. It is a global and is used to handle general user requests to deal with the whole display screen. Although I offer no protocol, my name provides a way to distinguish this special instance from all other Forms. This is useful, for example, in dealing with saving and restoring the system. To change the depth of your Display... Display newDepth: 16. Display newDepth: 8. Display newDepth: 1. Valid display depths are 1, 2, 4, 8, 16 and 32. It is suggested that you run with your monitors setting the same, for better speed and color fidelity. Note that this can add up to 4Mb for the Display form. Finally, note that newDepth: ends by executing a 'ControlManager restore' which currently terminates the active process, so nothing that follows in the doit will get executed. Depths 1, 2, 4 and 8 bits go through a color map to put color on the screen, but 16 and 32-bit color use the pixel values directly for RGB color (5 and 8 bits per, respectivlely). The color choice an be observed by executing Color fromUser in whatever depth you are using. ! !DisplayScreen methodsFor: 'blitter defaults' stamp: 'ar 5/28/2000 12:01'! defaultBitBltClass "Return the BitBlt version to use when I am active" ^BitBlt! ! !DisplayScreen methodsFor: 'blitter defaults' stamp: 'ar 5/28/2000 12:02'! defaultCanvasClass "Return the WarpBlt version to use when I am active" ^FormCanvas! ! !DisplayScreen methodsFor: 'blitter defaults' stamp: 'ar 5/28/2000 12:01'! defaultWarpBltClass "Return the WarpBlt version to use when I am active" ^WarpBlt! ! !DisplayScreen methodsFor: 'disk i/o' stamp: 'tk 9/28/2000 15:41'! objectForDataStream: refStrm | dp | "I am about to be written on an object file. Write a reference to the Display in the other system instead. " "A path to me" dp := DiskProxy global: #Display selector: #yourself args: #(). refStrm replace: self with: dp. ^ dp ! ! !DisplayScreen methodsFor: 'displaying' stamp: 'ar 4/19/2001 05:44'! addExtraRegion: aRectangle for: regionDrawer "Register the given rectangle as a region which is drawn by the specified region drawer. The region will be excluded from any updates when #forceDamageToScreen: is called. Note that the rectangle is only valid for a single update cycle; once #forceDamageToScreen: has been called, the region drawer and its region are being removed from the list" extraRegions ifNil:[extraRegions := #()]. extraRegions := extraRegions copyWith: (Array with: regionDrawer with: aRectangle). ! ! !DisplayScreen methodsFor: 'displaying' stamp: 'ar 5/28/2000 12:07'! copyBits: rect from: sf at: destOrigin clippingBox: clipRect rule: cr fillColor: hf (BitBlt current destForm: self sourceForm: sf fillColor: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: rect origin extent: rect extent clipRect: (clipRect intersect: clippingBox)) copyBits! ! !DisplayScreen methodsFor: 'displaying' stamp: 'ar 5/28/2000 12:07'! copyBits: rect from: sf at: destOrigin clippingBox: clipRect rule: cr fillColor: hf map: map ((BitBlt current destForm: self sourceForm: sf fillColor: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: rect origin extent: rect extent clipRect: (clipRect intersect: clippingBox)) colorMap: map) copyBits! ! !DisplayScreen methodsFor: 'displaying' stamp: 'jm 5/22/1998 01:23'! flash: aRectangle "Flash the area of the screen defined by the given rectangle." self reverse: aRectangle. self forceDisplayUpdate. (Delay forMilliseconds: 100) wait. self reverse: aRectangle. self forceDisplayUpdate. ! ! !DisplayScreen methodsFor: 'displaying' stamp: 'RAA 6/2/2000 12:09'! flash: aRectangle andWait: msecs "Flash the area of the screen defined by the given rectangle." self reverse: aRectangle. self forceDisplayUpdate. (Delay forMilliseconds: msecs) wait. self reverse: aRectangle. self forceDisplayUpdate. (Delay forMilliseconds: msecs) wait. ! ! !DisplayScreen methodsFor: 'displaying' stamp: 'sw 1/1/2005 01:31'! flashAll: rectangleList andWait: msecs "Flash the areas of the screen defined by the given rectangles." rectangleList do: [:aRectangle | self reverse: aRectangle]. self forceDisplayUpdate. (Delay forMilliseconds: msecs) wait. rectangleList do: [:aRectangle | self reverse: aRectangle]. self forceDisplayUpdate. (Delay forMilliseconds: msecs) wait. ! ! !DisplayScreen methodsFor: 'displaying' stamp: 'PeterHugossonMiller 9/3/2009 01:14'! forceDamageToScreen: allDamage "Force all the damage rects to the screen." | rectList excluded remaining regions | rectList := allDamage. "Note: Reset extra regions at the beginning to prevent repeated errors" regions := extraRegions. extraRegions := nil. regions ifNotNil:[ "exclude extra regions" regions do:[:drawerAndRect| excluded := drawerAndRect at: 2. remaining := Array new writeStream. rectList do:[:r| remaining nextPutAll:(r areasOutside: excluded)]. rectList := remaining contents]. ]. rectList do:[:r| self forceToScreen: r]. regions ifNotNil:[ "Have the drawers paint what is needed" regions do:[:drawerAndRect| (drawerAndRect at: 1) forceToScreen]. ].! ! !DisplayScreen methodsFor: 'initialization' stamp: 'ar 5/26/2000 00:07'! release "I am no longer Display. Release any resources if necessary"! ! !DisplayScreen methodsFor: 'initialization' stamp: 'ar 5/28/2000 11:25'! shutDown "Minimize Display memory saved in image" self setExtent: 240@120 depth: depth! ! !DisplayScreen methodsFor: 'other'! boundingBox clippingBox == nil ifTrue: [clippingBox := super boundingBox]. ^ clippingBox! ! !DisplayScreen methodsFor: 'other' stamp: 'alain.plantec 6/10/2008 22:29'! clippingTo: aRect do: aBlock "Display clippingTo: Rectangle fromUser do:" | saveClip | saveClip := clippingBox. clippingBox := aRect. aBlock value. clippingBox := saveClip! ! !DisplayScreen methodsFor: 'other' stamp: 'hmm 6/18/2000 19:16'! deferUpdates: aBoolean | wasDeferred | "Set the deferUpdates flag in the virtual machine. When this flag is true, BitBlt operations on the Display are not automatically propagated to the screen. If this underlying platform does not support deferred updates, this primitive will fail. Answer whether updates were deferred before if the primitive succeeds, nil if it fails." wasDeferred := DeferringUpdates == true. DeferringUpdates := aBoolean. ^(self primitiveDeferUpdates: aBoolean) ifNotNil: [wasDeferred]! ! !DisplayScreen methodsFor: 'other' stamp: 'hmm 2/2/2001 10:14'! deferUpdatesIn: aRectangle while: aBlock | result | (self deferUpdates: true) ifTrue: [^aBlock value]. result := aBlock value. self deferUpdates: false. self forceToScreen: aRectangle. ^result! ! !DisplayScreen methodsFor: 'other' stamp: 'RAA 11/27/1999 15:48'! displayChangeSignature ^DisplayChangeSignature! ! !DisplayScreen methodsFor: 'other' stamp: 'jm 5/21/1998 23:48'! forceDisplayUpdate "On platforms that buffer screen updates, force the screen to be updated immediately. On other platforms, or if the primitive is not implemented, do nothing." "do nothing if primitive fails"! ! !DisplayScreen methodsFor: 'other' stamp: 'ar 2/11/1999 18:14'! forceToScreen "Force the entire display area to the screen" ^self forceToScreen: self boundingBox! ! !DisplayScreen methodsFor: 'other' stamp: 'jm 5/19/1998 17:50'! forceToScreen: aRectangle "Force the given rectangular section of the Display to be copied to the screen. The primitive call does nothing if the primitive is not implemented. Typically used when the deferUpdates flag in the virtual machine is on; see deferUpdates:." self primShowRectLeft: aRectangle left right: aRectangle right top: aRectangle top bottom: aRectangle bottom. ! ! !DisplayScreen methodsFor: 'other'! fullBoundingBox ^ super boundingBox! ! !DisplayScreen methodsFor: 'other'! fullScreen "Display fullScreen" ScreenSave notNil ifTrue: [Display := ScreenSave]. clippingBox := super boundingBox! ! !DisplayScreen methodsFor: 'other' stamp: 'sd 6/7/2003 19:46'! fullScreenMode: aBoolean "On platforms that support it, set full-screen mode to the value of the argument. (Note: you'll need to restore the Display after calling this primitive." "Display fullScreenMode: true. Display newDepth: Display depth" self primitiveFailed ! ! !DisplayScreen methodsFor: 'other'! height ^ self boundingBox height! ! !DisplayScreen methodsFor: 'other' stamp: 'alain.plantec 5/30/2008 12:43'! newDepth: pixelSize " Display newDepth: 8. Display newDepth: 1 " (self supportsDisplayDepth: pixelSize) ifFalse: [^ self inform: 'Display depth ' , pixelSize printString , ' is not supported on this system']. self newDepthNoRestore: pixelSize. self restore! ! !DisplayScreen methodsFor: 'other' stamp: 'hmm 6/18/2000 19:14'! primitiveDeferUpdates: aBoolean "Set the deferUpdates flag in the virtual machine. When this flag is true, BitBlt operations on the Display are not automatically propagated to the screen. If this underlying platform does not support deferred updates, this primitive will fail. Answer the receiver if the primitive succeeds, nil if it fails." ^ nil "answer nil if primitive fails" ! ! !DisplayScreen methodsFor: 'other'! replacedBy: aForm do: aBlock "Permits normal display to draw on aForm instead of the display." ScreenSave := self. Display := aForm. aBlock value. Display := self. ScreenSave := nil.! ! !DisplayScreen methodsFor: 'other' stamp: 'alain.plantec 5/30/2008 12:52'! restore World fullRepaintNeeded! ! !DisplayScreen methodsFor: 'other' stamp: 'alain.plantec 5/30/2008 12:55'! restoreAfter: aBlock "Evaluate the block, wait for a mouse click, and then restore the screen." aBlock value. Sensor waitButton. self restore! ! !DisplayScreen methodsFor: 'other' stamp: 'ar 5/17/2001 21:02'! supportedDisplayDepths "Return all pixel depths supported on the current host platform." ^#(1 2 4 8 16 32 -1 -2 -4 -8 -16 -32) select: [:d | self supportsDisplayDepth: d]! ! !DisplayScreen methodsFor: 'other' stamp: 'ar 5/5/1999 23:45'! supportsDisplayDepth: pixelDepth "Return true if this pixel depth is supported on the current host platform. Primitive. Optional." ^#(1 2 4 8 16 32) includes: pixelDepth! ! !DisplayScreen methodsFor: 'other'! usableArea "Answer the usable area of the receiver. 5/22/96 sw." ^ self boundingBox deepCopy! ! !DisplayScreen methodsFor: 'other'! width ^ self boundingBox width! ! !DisplayScreen methodsFor: 'screen managing' stamp: 'RobRothwell 2/23/2009 22:21'! fullScreen: aBoolean Display fullScreenMode: (LastScreenModeSelected := aBoolean). DisplayScreen checkForNewScreenSize. World restoreMorphicDisplay! ! !DisplayScreen methodsFor: 'screen managing' stamp: 'RobRothwell 2/23/2009 22:22'! fullScreenOff self fullScreen: false! ! !DisplayScreen methodsFor: 'screen managing' stamp: 'RobRothwell 2/23/2009 22:23'! fullScreenOn self fullScreen: true! ! !DisplayScreen methodsFor: 'screen managing' stamp: 'RobRothwell 2/23/2009 22:23'! isFullScreen ^ self lastScreenModeSelected.! ! !DisplayScreen methodsFor: 'screen managing' stamp: 'RobRothwell 2/23/2009 22:22'! lastScreenModeSelected ^ LastScreenModeSelected ifNil: [LastScreenModeSelected := false]! ! !DisplayScreen methodsFor: 'screen managing' stamp: 'RobRothwell 2/23/2009 22:23'! toggleFullScreen self fullScreen: self isFullScreen not! ! !DisplayScreen methodsFor: 'testing' stamp: 'ar 5/25/2000 23:34'! isDisplayScreen ^true! ! !DisplayScreen methodsFor: 'private'! beDisplay "Primitive. Tell the interpreter to use the receiver as the current display image. Fail if the form is too wide to fit on the physical display. Essential. See Object documentation whatIsAPrimitive." self primitiveFailed! ! !DisplayScreen methodsFor: 'private' stamp: 'di 3/3/1999 10:00'! copyFrom: aForm "Take on all state of aForm, with complete sharing" super copyFrom: aForm. clippingBox := super boundingBox! ! !DisplayScreen methodsFor: 'private' stamp: 'adrian_lienhard 7/18/2009 15:54'! findAnyDisplayDepth "Return any display depth that is supported on this system." ^self findAnyDisplayDepthIfNone:[ "Ugh .... now this is a biggie - a system that does not support any of the display depths at all." Smalltalk logError:'Fatal error: This system has no support for any display depth at all.' inContext: thisContext to: 'PharoDebug.log'. Smalltalk quitPrimitive. "There is no way to continue from here" ].! ! !DisplayScreen methodsFor: 'private' stamp: 'ar 5/17/2001 21:03'! findAnyDisplayDepthIfNone: aBlock "Return any display depth that is supported on this system. If there is none, evaluate aBlock." #(1 2 4 8 16 32 -1 -2 -4 -8 -16 -32) do:[:bpp| (self supportsDisplayDepth: bpp) ifTrue:[^bpp]. ]. ^aBlock value! ! !DisplayScreen methodsFor: 'private' stamp: 'alain.plantec 5/30/2008 12:42'! newDepthNoRestore: pixelSize "Change depths. Check if there is enough space!! , di" | area need | pixelSize = depth ifTrue: [^ self"no change"]. pixelSize abs < self depth ifFalse: ["Make sure there is enough space" area := Display boundingBox area. "pixels" need := area * (pixelSize abs - self depth) // 8 + Smalltalk lowSpaceThreshold. "new bytes needed" (Smalltalk garbageCollectMost <= need and: [Smalltalk garbageCollect <= need]) ifTrue: [self error: 'Insufficient free space']]. self setExtent: self extent depth: pixelSize. DisplayScreen startUp! ! !DisplayScreen methodsFor: 'private' stamp: 'jm 6/3/1998 13:00'! primRetryShowRectLeft: l right: r top: t bottom: b "Copy the given rectangular section of the Display to to the screen. This primitive is not implemented on all platforms. Do nothing if it fails. " "do nothing if primitive fails" ! ! !DisplayScreen methodsFor: 'private' stamp: 'jm 6/3/1998 13:02'! primShowRectLeft: l right: r top: t bottom: b "Copy the given rectangular section of the Display to to the screen. This primitive is not implemented on all platforms. If this fails, retry integer coordinates." "if this fails, coerce coordinates to integers and try again" self primRetryShowRectLeft: l truncated right: r rounded top: t truncated bottom: b rounded. ! ! !DisplayScreen methodsFor: 'private' stamp: 'bf 5/16/2006 11:35'! setExtent: aPoint depth: bitsPerPixel "DisplayScreen startUp" "This method is critical. If the setExtent fails, there will be no proper display on which to show the error condition..." "ar 5/1/1999: ... and that is exactly why we check for the available display depths first." "RAA 27 Nov 99 - if depth and extent are the same and acceptable, why go through this. also - record when we change so worlds can tell if it is time to repaint" (depth == bitsPerPixel and: [aPoint = self extent and: [self supportsDisplayDepth: bitsPerPixel]]) ifFalse: [ bits := nil. "Free up old bitmap in case space is low" DisplayChangeSignature := (DisplayChangeSignature ifNil: [0]) + 1. (self supportsDisplayDepth: bitsPerPixel) ifTrue:[super setExtent: aPoint depth: bitsPerPixel] ifFalse:[(self supportsDisplayDepth: bitsPerPixel negated) ifTrue:[super setExtent: aPoint depth: bitsPerPixel negated] ifFalse:["Search for a suitable depth" super setExtent: aPoint depth: self findAnyDisplayDepth]]. ]. clippingBox := super boundingBox! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DisplayScreen class instanceVariableNames: ''! !DisplayScreen class methodsFor: 'display box access'! boundingBox "Answer the bounding box for the form representing the current display screen." ^Display boundingBox! ! !DisplayScreen class methodsFor: 'display box access' stamp: 'marcus.denker 9/17/2008 20:46'! checkForNewScreenSize "Check whether the screen size has changed and if so take appropriate actions " Display extent = DisplayScreen actualScreenSize ifTrue: [^ self]. DisplayScreen startUp. World restoreMorphicDisplay. World repositionFlapsAfterScreenSizeChange! ! !DisplayScreen class methodsFor: 'display box access' stamp: 'pavel.krivanek 12/3/2008 21:00'! depth: depthInteger width: widthInteger height: heightInteger fullscreen: aBoolean "Force Squeak's window (if there's one) into a new size and depth." "DisplayScreen depth: 8 width: 1024 height: 768 fullscreen: false" self primitiveFailed ! ! !DisplayScreen class methodsFor: 'snapshots' stamp: 'ar 2/5/2001 17:24'! actualScreenDepth ^ Display depth! ! !DisplayScreen class methodsFor: 'snapshots'! actualScreenSize ^ 640@480! ! !DisplayScreen class methodsFor: 'snapshots' stamp: 'ar 5/28/2000 11:26'! shutDown "Minimize Display memory saved in image" Display shutDown.! ! !DisplayScreen class methodsFor: 'snapshots' stamp: 'ar 5/17/2001 15:50'! startUp "DisplayScreen startUp" Display setExtent: self actualScreenSize depth: Display nativeDepth. Display beDisplay! ! DisplayObject subclass: #DisplayText instanceVariableNames: 'text textStyle offset form foreColor backColor' classVariableNames: '' poolDictionaries: 'TextConstants' category: 'Graphics-Display Objects'! !DisplayText commentStamp: '' prior: 0! I represent Text whose emphasis changes are mapped to a set of fonts. My instances have an offset used in determining screen placement for displaying. They get used two different ways in the system. In the user interface, they mainly hold onto some text which is viewed by some form of ParagraphEditor. However, as a DisplayObject, they may need to display efficiently, so my instances have a cache for the bits.! !DisplayText methodsFor: 'accessing'! alignedTo: alignPointSelector "Return a copy with offset according to alignPointSelector which is one of... #(topLeft, topCenter, topRight, leftCenter, center, etc)" | boundingBox | boundingBox := 0@0 corner: self form extent. ^ self shallowCopy offset: (0@0) - (boundingBox perform: alignPointSelector)! ! !DisplayText methodsFor: 'accessing'! fontsUsed "Return a list of all fonts used currently in this text. 8/19/96 tk" ^ text runs values asSet collect: [:each | textStyle fontAt: each]! ! !DisplayText methodsFor: 'accessing'! form "Answer the form into which the receiver's display bits are cached." form == nil ifTrue: [self composeForm]. ^form! ! !DisplayText methodsFor: 'accessing' stamp: 'MarcusDenker 9/30/2009 11:53'! form: aForm form := aForm! ! !DisplayText methodsFor: 'accessing'! lineGrid "Answer the relative space between lines of the receiver's text." ^textStyle lineGrid! ! !DisplayText methodsFor: 'accessing'! numberOfLines "Answer the number of lines of text in the receiver." ^self height // text lineGrid! ! !DisplayText methodsFor: 'accessing'! offset "Refer to the comment in DisplayObject|offset." ^offset! ! !DisplayText methodsFor: 'accessing'! offset: aPoint "Refer to the comment in DisplayObject|offset:." offset := aPoint! ! !DisplayText methodsFor: 'accessing'! string "Answer the string of the characters displayed by the receiver." ^text string! ! !DisplayText methodsFor: 'accessing'! text "Answer the text displayed by the receiver." ^text! ! !DisplayText methodsFor: 'accessing'! text: aText "Set the receiver to display the argument, aText." text := aText. form := nil. self changed. ! ! !DisplayText methodsFor: 'accessing'! textStyle "Answer the style by which the receiver displays its text." ^textStyle! ! !DisplayText methodsFor: 'accessing'! textStyle: aTextStyle "Set the style by which the receiver should display its text." textStyle := aTextStyle. form := nil. self changed. ! ! !DisplayText methodsFor: 'color'! backgroundColor backColor == nil ifTrue: [^ Color transparent]. ^ backColor! ! !DisplayText methodsFor: 'color'! foregroundColor foreColor == nil ifTrue: [^ Color black]. ^ foreColor! ! !DisplayText methodsFor: 'color'! foregroundColor: cf backgroundColor: cb foreColor := cf. backColor := cb! ! !DisplayText methodsFor: 'converting' stamp: 'tk 10/21/97 12:28'! asParagraph "Answer a Paragraph whose text and style are identical to that of the receiver." | para | para := Paragraph withText: text style: textStyle. para foregroundColor: foreColor backgroundColor: backColor. backColor isTransparent ifTrue: [para rule: Form paint]. ^ para! ! !DisplayText methodsFor: 'display box access'! boundingBox "Refer to the comment in DisplayObject|boundingBox." ^self form boundingBox! ! !DisplayText methodsFor: 'display box access'! computeBoundingBox "Compute minimum enclosing rectangle around characters." | character font width carriageReturn lineWidth lineHeight | carriageReturn := Character cr. width := lineWidth := 0. font := textStyle defaultFont. lineHeight := textStyle lineGrid. 1 to: text size do: [:i | character := text at: i. character = carriageReturn ifTrue: [lineWidth := lineWidth max: width. lineHeight := lineHeight + textStyle lineGrid. width := 0] ifFalse: [width := width + (font widthOf: character)]]. lineWidth := lineWidth max: width. ^offset extent: lineWidth @ lineHeight! ! !DisplayText methodsFor: 'displaying' stamp: 'yo 6/23/2003 20:05'! displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: ruleInteger fillColor: aForm "For TT font, rule 34 is used if possible." "Refer to the comment in DisplayObject|displayOn:at:clippingBox:rule:mask:." | form1 rule | form1 := self form. rule := (ruleInteger = Form over and: [backColor isTransparent]) ifTrue: [form1 depth = 32 ifTrue: [rule := 34] ifFalse: [Form paint]] ifFalse: [ruleInteger]. form1 depth = 32 ifTrue: [rule := 34]. form1 displayOn: aDisplayMedium at: aDisplayPoint + offset clippingBox: clipRectangle rule: rule fillColor: aForm! ! !DisplayText methodsFor: 'displaying'! displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: alignmentPoint with: relativePoint rule: ruleInteger fillColor: aForm "Refer to the comment in DisplayObject|displayOn:transformation:clippingBox:align:with:rule:mask:." | absolutePoint | absolutePoint := displayTransformation applyTo: relativePoint. absolutePoint := absolutePoint x asInteger @ absolutePoint y asInteger. self displayOn: aDisplayMedium at: absolutePoint - alignmentPoint clippingBox: clipRectangle rule: ruleInteger fillColor: aForm! ! !DisplayText methodsFor: 'displaying'! displayOnPort: aPort at: location self form displayOnPort: aPort at: location + offset! ! !DisplayText methodsFor: 'private' stamp: 'pavel.krivanek 11/21/2008 16:52'! composeForm form := UIManager default composeFormFor: self. ^ form! ! !DisplayText methodsFor: 'private'! setText: aText textStyle: aTextStyle offset: aPoint text := aText. textStyle := aTextStyle. offset := aPoint. form := nil! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DisplayText class instanceVariableNames: ''! !DisplayText class methodsFor: 'examples' stamp: 'tk 11/28/2001 16:03'! example "Continually prints two lines of text wherever you point with the cursor. Terminate by pressing any button on the mouse." | tx | tx := 'this is a line of characters and this is the second line.' asDisplayText. tx foregroundColor: Color black backgroundColor: Color transparent. tx := tx alignedTo: #center. [Sensor anyButtonPressed] whileFalse: [tx displayOn: Display at: Sensor cursorPoint] "DisplayText example."! ! !DisplayText class methodsFor: 'instance creation'! text: aText "Answer an instance of me such that the text displayed is aText according to the system's default text style." ^self new setText: aText textStyle: DefaultTextStyle copy offset: 0 @ 0! ! !DisplayText class methodsFor: 'instance creation'! text: aText textStyle: aTextStyle "Answer an instance of me such that the text displayed is aText according to the style specified by aTextStyle." ^self new setText: aText textStyle: aTextStyle offset: 0 @ 0! ! !DisplayText class methodsFor: 'instance creation'! text: aText textStyle: aTextStyle offset: aPoint "Answer an instance of me such that the text displayed is aText according to the style specified by aTextStyle. The display of the information should be offset by the amount given as the argument, aPoint." ^self new setText: aText textStyle: aTextStyle offset: aPoint! ! Object subclass: #DisplayTransform instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Transformations'! !DisplayTransform commentStamp: '' prior: 0! This class represents a base for generic transformations of 2D points between different coordinate systems (including scaling and rotation). The transformations map objects between one coordinate system and another where it is assumed that a nested hierarchy of transformations can be defined. It is assumed that transformations deal with Integer points. All transformations should return Integer coordinates (even though float points may be passed in as argument). Compositions of transformations MUST work in the following order. A 'global' transformation (the argument in #composedWithGlobal:) is defined as a transformation that takes place between the receiver (the 'local') transformation and any 'global' point computations, whereas a 'local' transformation (e.g., the argument in #composedWithLocal:) takes place between the receiver ('global') and any 'local' points. For the transformation methods this means that combining a global and a local transformation will result in the following order: globalPointToLocal: globalPoint "globalPoint -> globalTransform -> localTransform -> locaPoint" ^localTransform globalPointToLocal: (globalTransform globalPointToLocal: globalPoint) localPointToGlobal: localPoint "localPoint -> localTransform -> globalTransform -> globalPoint" ^globalTransform localPointToGlobal: (localTransform localPointToGlobal: localPoint) ! !DisplayTransform methodsFor: 'accessing' stamp: 'ar 11/2/1998 19:43'! inverseTransformation "Return the inverse transformation of the receiver" ^self subclassResponsibility! ! !DisplayTransform methodsFor: 'composing' stamp: 'ar 11/2/1998 16:15'! composedWithGlobal: aTransformation "Return the composition of the receiver and the global transformation passed in. A 'global' transformation is defined as a transformation that takes place between the receiver (the 'local') transformation and any 'global' point computations, e.g., for the methods globalPointToLocal: globalPoint globalPoint -> globalTransform -> localTransform -> locaPoint localPointToGlobal: localPoint localPoint -> localTransform -> globalTransform -> globalPoint " ^aTransformation composedWithLocal: self! ! !DisplayTransform methodsFor: 'composing' stamp: 'ar 11/2/1998 16:41'! composedWithLocal: aTransformation "Return the composition of the receiver and the local transformation passed in. A 'local' transformation is defined as a transformation that takes place between the receiver (the 'global') transformation and any 'local' point computations, e.g., for the methods globalPointToLocal: globalPoint globalPoint -> globalTransform -> localTransform -> locaPoint localPointToGlobal: localPoint localPoint -> localTransform -> globalTransform -> globalPoint " self isIdentity ifTrue:[^ aTransformation]. aTransformation isIdentity ifTrue:[^ self]. ^ CompositeTransform new globalTransform: self localTransform: aTransformation! ! !DisplayTransform methodsFor: 'converting' stamp: 'ar 11/2/1998 19:59'! asCompositeTransform "Represent the receiver as a composite transformation" ^CompositeTransform new globalTransform: self localTransform: self species identity! ! !DisplayTransform methodsFor: 'converting' stamp: 'ar 11/2/1998 20:01'! asMatrixTransform2x3 "Represent the receiver as a 2x3 matrix transformation" ^self subclassResponsibility! ! !DisplayTransform methodsFor: 'initialize' stamp: 'ar 11/2/1998 23:18'! setIdentity "Initialize the receiver to the identity transformation (e.g., not affecting points)" ^self subclassResponsibility! ! !DisplayTransform methodsFor: 'testing' stamp: 'ar 11/2/1998 22:47'! isCompositeTransform "Return true if the receiver is a composite transformation. Composite transformations may have impact on the accuracy." ^false! ! !DisplayTransform methodsFor: 'testing' stamp: 'ar 11/2/1998 16:17'! isIdentity "Return true if the receiver is the identity transform; that is, if applying to a point returns the point itself." ^self subclassResponsibility! ! !DisplayTransform methodsFor: 'testing' stamp: 'ar 11/2/1998 22:48'! isMatrixTransform2x3 "Return true if the receiver is 2x3 matrix transformation" ^false! ! !DisplayTransform methodsFor: 'testing' stamp: 'ar 11/2/1998 22:48'! isMorphicTransform "Return true if the receiver is a MorphicTransform, that is specifies the transformation values explicitly." ^false! ! !DisplayTransform methodsFor: 'testing' stamp: 'ar 11/2/1998 16:16'! isPureTranslation "Return true if the receiver specifies no rotation or scaling." ^self subclassResponsibility! ! !DisplayTransform methodsFor: 'transforming points' stamp: 'ar 11/2/1998 16:17'! globalPointToLocal: aPoint "Transform aPoint from global coordinates into local coordinates" ^self subclassResponsibility! ! !DisplayTransform methodsFor: 'transforming points' stamp: 'ar 11/9/1998 14:35'! globalPointsToLocal: inArray "Transform all the points of inArray from global into local coordinates" ^inArray collect:[:pt| self globalPointToLocal: pt]! ! !DisplayTransform methodsFor: 'transforming points' stamp: 'gh 10/22/2001 13:24'! invertBoundsRect: aRectangle "Return a rectangle whose coordinates have been transformed from local back to global coordinates." ^self subclassResponsibility! ! !DisplayTransform methodsFor: 'transforming points' stamp: 'ar 11/2/1998 16:18'! localPointToGlobal: aPoint "Transform aPoint from local coordinates into global coordinates" ^self subclassResponsibility! ! !DisplayTransform methodsFor: 'transforming points' stamp: 'ar 11/9/1998 14:35'! localPointsToGlobal: inArray "Transform all the points of inArray from local into global coordinates" ^inArray collect:[:pt| self localPointToGlobal: pt]! ! !DisplayTransform methodsFor: 'transforming rects' stamp: 'ar 11/2/1998 16:19'! globalBoundsToLocal: aRectangle "Transform aRectangle from global coordinates into local coordinates" ^Rectangle encompassing: (self globalPointsToLocal: aRectangle corners)! ! !DisplayTransform methodsFor: 'transforming rects' stamp: 'ar 11/2/1998 16:19'! localBoundsToGlobal: aRectangle "Transform aRectangle from local coordinates into global coordinates" ^Rectangle encompassing: (self localPointsToGlobal: aRectangle corners)! ! !DisplayTransform methodsFor: 'transforming rects' stamp: 'di 10/25/1999 12:49'! sourceQuadFor: aRectangle ^ aRectangle innerCorners collect: [:p | self globalPointToLocal: p]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DisplayTransform class instanceVariableNames: ''! !DisplayTransform class methodsFor: 'instance creation' stamp: 'ar 11/2/1998 20:55'! identity ^self new setIdentity! ! AbstractEvent subclass: #DoItEvent instanceVariableNames: 'context' classVariableNames: '' poolDictionaries: '' category: 'System-Change Notification'! !DoItEvent methodsFor: 'accessing' stamp: 'rw 7/14/2003 11:29'! context ^context! ! !DoItEvent methodsFor: 'printing' stamp: 'rw 7/14/2003 10:15'! printEventKindOn: aStream aStream nextPutAll: 'DoIt'! ! !DoItEvent methodsFor: 'testing' stamp: 'rw 7/14/2003 10:15'! isDoIt ^true! ! !DoItEvent methodsFor: 'private-accessing' stamp: 'rw 7/14/2003 11:29'! context: aContext context := aContext! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DoItEvent class instanceVariableNames: ''! !DoItEvent class methodsFor: 'accessing' stamp: 'rw 7/14/2003 10:19'! changeKind ^#DoIt! ! !DoItEvent class methodsFor: 'accessing' stamp: 'NS 1/20/2004 12:23'! supportedKinds ^ Array with: self expressionKind! ! !DoItEvent class methodsFor: 'instance creation' stamp: 'NS 1/19/2004 09:47'! expression: stringOrStream context: aContext | instance | instance := self item: stringOrStream kind: AbstractEvent expressionKind. instance context: aContext. ^instance! ! AlignmentMorph subclass: #DockingBarMorph instanceVariableNames: 'originalColor gradientRamp fillsOwner avoidVisibleBordersAtEdge autoGradient selectedItem activeSubMenu' classVariableNames: '' poolDictionaries: '' category: 'Morphic-DockingBar'! !DockingBarMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/29/2007 15:31'! add: wordingString font: aFont icon: aForm help: helpString subMenu: aMenuMorph "Append the given submenu with the given label." | item | item := ToggleMenuItemMorph new. item font: aFont; contents: wordingString; subMenu: aMenuMorph; icon: aForm. helpString isNil ifFalse: [item setBalloonText: helpString]. self addMorphBack: item! ! !DockingBarMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 9/25/2006 13:37'! adoptPaneColor: paneColor "Change our color too." super adoptPaneColor: paneColor. paneColor ifNil: [^self]. originalColor := paneColor. self borderStyle baseColor: paneColor. self updateColor! ! !DockingBarMorph methodsFor: '*Polymorph-Widgets' stamp: 'gvc 4/26/2007 15:27'! originalColor "Answer the original color." ^originalColor! ! !DockingBarMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 7/30/2007 14:24'! extent: aPoint "Change the receiver's extent. optimized to not keep updating the (gradient) color!!" |old| old := self extent. super extent: aPoint. self extent = old ifTrue: [^self]. self updateColor! ! !DockingBarMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 11/14/2006 15:37'! updatePosition "private - update the receiver's position. Fixed so as not to keep changing position!! (called twice if adhereing)" | edgeSymbol margin | edgeSymbol := self edgeToAdhereTo. edgeSymbol == #none ifTrue: [self perform: (edgeSymbol , ':') asSymbol with: (self owner perform: edgeSymbol)]. "" margin := self avoidVisibleBordersAtEdge ifTrue: [self borderWidth asPoint] ifFalse: [0 asPoint]. "" self isAdheringToTop ifTrue: [| usedHeight | usedHeight := self usedHeightByPredominantDockingBarsOfChastes: #(#top ). self topLeft: self owner topLeft - margin + (0 @ usedHeight)]. self isAdheringToBottom ifTrue: [| usedHeight | usedHeight := self usedHeightByPredominantDockingBarsOfChastes: #(#bottom ). self bottomLeft: self owner bottomLeft + (-1 @ 1 * margin) - (0 @ usedHeight)]. "" self isAdheringToLeft ifTrue: [| usedHeight usedWidth | usedHeight := self usedHeightByPredominantDockingBarsOfChastes: #(#top ). usedWidth := self usedWidthByPredominantDockingBarsOfChastes: #(#left ). self topLeft: self owner topLeft - margin + (usedWidth @ usedHeight)]. self isAdheringToRight ifTrue: [| usedHeight usedWidth | usedHeight := self usedHeightByPredominantDockingBarsOfChastes: #(#top ). usedWidth := self usedWidthByPredominantDockingBarsOfChastes: #(#right ). self topRight: self owner topRight + (1 @ -1 * margin) + (usedWidth negated @ usedHeight)]! ! !DockingBarMorph methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 4/16/2007 14:41'! wantsYellowButtonMenu "Answer true if the receiver wants a yellow button menu. Fixed for when generalizedYellowButtonMenu pref is off" ^Preferences noviceMode not and: [Preferences generalizedYellowButtonMenu]! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 9/13/2004 19:59'! addBlankIconsIfNecessary: anIcon "If any of my items have an icon, ensure that all do by using anIcon for those that don't" self items reject: [:each | each hasIconOrMarker] thenDo: [:each | each icon: anIcon]! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 12:01'! adhereToBottom "Instract the receiver to adhere to bottom" self adhereTo:#bottom! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 12:01'! adhereToLeft "Instract the receiver to adhere to left" self adhereTo: #left! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 12:01'! adhereToRight "Instract the receiver to adhere to right" self adhereTo: #right! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 12:01'! adhereToTop "Instract the receiver to adhere to top" self adhereTo: #top! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 14:28'! autoGradient "Answer if the receiver is in autoGradient mode" ^ autoGradient! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 14:28'! autoGradient: aBoolean "Instruct the receiver to fill the owner or not" autoGradient := aBoolean. self updateColor! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 13:38'! avoidVisibleBordersAtEdge "Answer if the receiver is in avoidVisibleBordersAtEdge mode" ^ avoidVisibleBordersAtEdge! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 13:57'! avoidVisibleBordersAtEdge: aBoolean "Instruct the receiver to avoid showing the borders at edge" avoidVisibleBordersAtEdge := aBoolean. self updateLayoutProperties.! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 12:02'! beFloating "Instract the receiver to be floating" self adhereTo: #none! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 11/2/2004 12:00'! color: aColor "Set the receiver's color." super color: aColor. originalColor := aColor asColor. "" self updateColor! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 13:35'! fillsOwner "Answer if the receiver is in fillOwner mode" ^ fillsOwner! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 13:57'! fillsOwner: aBoolean "Instruct the receiver to fill the owner or not" fillsOwner := aBoolean. self updateLayoutProperties! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 11:57'! isAdheringToBottom "Answer true if the receiver is adhering to bottom" ^ self edgeToAdhereTo == #bottom! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 11:57'! isAdheringToLeft "Answer true if the receiver is adhering to left" ^ self edgeToAdhereTo == #left! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 11:57'! isAdheringToRight "Answer true if the receiver is adhering to right" ^ self edgeToAdhereTo == #right! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 11:57'! isAdheringToTop "Answer true if the receiver is adhering to top" ^ self edgeToAdhereTo == #top! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/30/2004 23:13'! isFloating "Answer true if the receiver has a float layout" ^ self isHorizontal not and: [self isVertical not]! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 11:58'! isHorizontal "Answer true if the receiver has a horizontal layout" ^ self isAdheringToTop or: [self isAdheringToBottom]! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 11:58'! isVertical "Answer true if the receiver has a vertical layout" ^ self isAdheringToLeft or: [self isAdheringToRight] ! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 9/9/2004 19:45'! rootMenu ^ self! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 9/1/2004 16:39'! stayUp ^ false! ! !DockingBarMorph methodsFor: 'accessing' stamp: 'dgd 8/31/2004 16:33'! wantsToBeTopmost "Answer if the receiver want to be one of the topmost objects in its owner" ^ true! ! !DockingBarMorph methodsFor: 'change reporting' stamp: 'dgd 9/1/2004 15:29'! ownerChanged "The receiver's owner has changed its layout. " self updateBounds. ^ super ownerChanged! ! !DockingBarMorph methodsFor: 'construction' stamp: 'dgd 7/28/2005 12:08'! addDefaultSpace "Add a new space of the given size to the receiver." ^ self addSpace: (Preferences tinyDisplay ifFalse:[10] ifTrue:[3])! ! !DockingBarMorph methodsFor: 'construction' stamp: 'dgd 9/1/2004 19:10'! addLine "Append a divider line to this menu. Suppress duplicate lines." submorphs isEmpty ifTrue: [^ self]. (self lastSubmorph isKindOf: MenuLineMorph) ifFalse: [self addMorphBack: MenuLineMorph new]. ! ! !DockingBarMorph methodsFor: 'construction' stamp: 'dgd 8/31/2004 11:34'! addSpacer "Add a new spacer to the receiver. Spacer are objects that try to use as much space as they can" self addMorphBack: (AlignmentMorph newSpacer: Color transparent)! ! !DockingBarMorph methodsFor: 'construction' stamp: 'dgd 8/31/2004 11:34'! addSpace: sizePointOrNumber "Add a new space of the given size to the receiver." | space | space := RectangleMorph new. space extent: sizePointOrNumber asPoint. space color: Color transparent. space borderWidth: 0. self addMorphBack: space! ! !DockingBarMorph methodsFor: 'construction' stamp: 'dgd 9/10/2004 16:48'! add: wordingString icon: aForm help: helpString subMenu: aMenuMorph "Append the given submenu with the given label." | item | item := MenuItemMorph new. item contents: wordingString. item subMenu: aMenuMorph. item icon: aForm. helpString isNil ifFalse: [item setBalloonText: helpString]. self addMorphBack: item! ! !DockingBarMorph methodsFor: 'construction' stamp: 'dgd 9/10/2004 16:48'! add: wordingString icon: aForm subMenu: aMenuMorph "Append the given submenu with the given label." ^ self add: wordingString icon: aForm help: nil subMenu: aMenuMorph ! ! !DockingBarMorph methodsFor: 'construction' stamp: 'dgd 9/1/2004 19:08'! add: aString subMenu: aMenuMorph "Append the given submenu with the given label." self add: aString icon: nil subMenu: aMenuMorph ! ! !DockingBarMorph methodsFor: 'control' stamp: 'dgd 9/9/2004 21:48'! activeSubmenu: aSubmenu activeSubMenu isNil ifFalse: [activeSubMenu delete]. activeSubMenu := aSubmenu. aSubmenu isNil ifTrue: [^ self]. "" activeSubMenu selectItem: nil event: nil. MenuIcons decorateMenu: activeSubMenu. activeSubMenu activatedFromDockingBar: self. activeSubMenu borderColor: self borderColor. activeSubMenu beSticky. activeSubMenu resistsRemoval: true. activeSubMenu removeMatchString.! ! !DockingBarMorph methodsFor: 'control' stamp: 'dgd 9/1/2004 16:48'! deleteIfPopUp: evt evt ifNotNil: [evt hand releaseMouseFocus: self]! ! !DockingBarMorph methodsFor: 'control' stamp: 'dgd 9/1/2004 16:40'! selectItem: aMenuItem event: anEvent selectedItem ifNotNil: [selectedItem deselect: anEvent]. selectedItem := aMenuItem. selectedItem ifNotNil: [selectedItem select: anEvent]! ! !DockingBarMorph methodsFor: 'dropping/grabbing' stamp: 'dgd 9/7/2004 14:47'! aboutToBeGrabbedBy: aHand "The morph is about to be grabbed, make it float" self beFloating. self updateBounds. self updateColor. (self bounds containsPoint: aHand position) ifFalse: [self center: aHand position]. self owner restoreFlapsDisplay! ! !DockingBarMorph methodsFor: 'dropping/grabbing' stamp: 'dgd 8/31/2004 14:37'! justDroppedInto: aMorph event: anEvent | ownerBounds leftRegion droppedPosition rightRegion topRegion bottomRegion | super justDroppedInto: aMorph event: anEvent. "" self owner isNil ifTrue: [^ self]. "" ownerBounds := aMorph bounds. topRegion := ownerBounds bottom: ownerBounds top + (ownerBounds height // 5). bottomRegion := ownerBounds top: ownerBounds bottom - (ownerBounds height // 5). "" leftRegion := ownerBounds right: ownerBounds left + (ownerBounds width // 5). leftRegion := leftRegion top: topRegion bottom. leftRegion := leftRegion bottom: bottomRegion top. "" rightRegion := ownerBounds left: ownerBounds right - (ownerBounds width // 5). rightRegion := rightRegion top: topRegion bottom. rightRegion := rightRegion bottom: bottomRegion top. "" droppedPosition := anEvent position. (topRegion containsPoint: droppedPosition) ifTrue: [ ^ self adhereToTop]. (bottomRegion containsPoint: droppedPosition) ifTrue: [ ^ self adhereToBottom]. (leftRegion containsPoint: droppedPosition) ifTrue: [ ^ self adhereToLeft]. (rightRegion containsPoint: droppedPosition) ifTrue: [ ^ self adhereToRight]. "" self beFloating! ! !DockingBarMorph methodsFor: 'events' stamp: 'dgd 9/1/2004 19:29'! activate: evt "Receiver should be activated; e.g., so that control passes correctly." evt hand newMouseFocus: self! ! !DockingBarMorph methodsFor: 'events-processing' stamp: 'dgd 9/9/2004 21:43'! handleFocusEvent: evt "Handle focus events. Valid menu transitions are determined based on the menu currently holding the focus after the mouse went down on one of its children." (evt isMouse and:[ evt isMouseUp ]) ifTrue:[^ self]. self processEvent: evt. "Need to handle keyboard input if we have the focus." evt isKeyboard ifTrue: [^ self handleEvent: evt]. "We need to handle button clicks outside and transitions to local popUps so throw away everything else" (evt isMouseOver or:[evt isMouse not]) ifTrue:[^self]. "What remains are mouse buttons and moves" evt isMove ifFalse:[^self handleEvent: evt]. "handle clicks outside by regular means" "Now it's getting tricky. On #mouseMove we might transfer control to *either* the currently active submenu or the pop up owner, if any. Since the active sub menu is always displayed upfront check it first." selectedItem ifNotNil:[(selectedItem activateSubmenu: evt) ifTrue:[^self]]. ! ! !DockingBarMorph methodsFor: 'initialization' stamp: 'dgd 9/2/2004 11:03'! initialize "initialize the receiver" super initialize. "" selectedItem := nil. activeSubMenu := nil. fillsOwner := true. avoidVisibleBordersAtEdge := true. autoGradient := Preferences gradientMenu. "" self setDefaultParameters. "" self beFloating. "" self layoutInset: 0. ! ! !DockingBarMorph methodsFor: 'initialization' stamp: 'dgd 8/30/2004 22:17'! setDefaultParameters "private - set the default parameter using Preferences as the inspiration source" | colorFromMenu worldColor menuColor menuBorderColor | colorFromMenu := Preferences menuColorFromWorld and: [Display depth > 4] and: [(worldColor := self currentWorld color) isColor]. "" menuColor := colorFromMenu ifTrue: [worldColor luminance > 0.7 ifTrue: [worldColor mixed: 0.85 with: Color black] ifFalse: [worldColor mixed: 0.4 with: Color white]] ifFalse: [Preferences menuColor]. "" menuBorderColor := Preferences menuAppearance3d ifTrue: [#raised] ifFalse: [colorFromMenu ifTrue: [worldColor muchDarker] ifFalse: [Preferences menuBorderColor]]. "" self setColor: menuColor borderWidth: Preferences menuBorderWidth borderColor: menuBorderColor! ! !DockingBarMorph methodsFor: 'menu' stamp: 'dgd 9/29/2004 20:31'! addCustomMenuItems: aMenu hand: aHandMorph "Populate aMenu with appropriate menu items for a yellow-button (context menu) click." super addCustomMenuItems: aMenu hand: aHandMorph. "" aMenu addLine. aMenu addUpdating: #autoGradientString action: #toggleAutoGradient. self isFloating ifFalse: ["" aMenu addUpdating: #fillsOwnerString action: #toggleFillsOwner. aMenu addUpdating: #avoidVisibleBordersAtEdgeString action: #toggleAvoidVisibleBordersAtEdge]! ! !DockingBarMorph methodsFor: 'menu' stamp: 'dgd 9/29/2004 20:25'! autoGradientString "Answer the string to be shown in a menu to represent the 'resistsRemoval' status" ^ (self autoGradient ifTrue: [''] ifFalse: ['']) , 'auto gradient' translated! ! !DockingBarMorph methodsFor: 'menu' stamp: 'dgd 9/29/2004 20:25'! avoidVisibleBordersAtEdgeString "Answer the string to be shown in a menu to represent the 'resistsRemoval' status" ^ (self avoidVisibleBordersAtEdge ifTrue: [''] ifFalse: ['']) , 'avoid visible borders at edge' translated! ! !DockingBarMorph methodsFor: 'menu' stamp: 'dgd 9/29/2004 20:23'! fillsOwnerString "Answer the string to be shown in a menu to represent the 'resistsRemoval' status" ^ (self fillsOwner ifTrue: [''] ifFalse: ['']) , 'fills owner' translated ! ! !DockingBarMorph methodsFor: 'menu' stamp: 'dgd 9/29/2004 20:27'! toggleAutoGradient self autoGradient: self autoGradient not! ! !DockingBarMorph methodsFor: 'menu' stamp: 'dgd 9/29/2004 20:26'! toggleAvoidVisibleBordersAtEdge self avoidVisibleBordersAtEdge: self avoidVisibleBordersAtEdge not! ! !DockingBarMorph methodsFor: 'menu' stamp: 'dgd 9/29/2004 20:24'! toggleFillsOwner self fillsOwner: self fillsOwner not! ! !DockingBarMorph methodsFor: 'menus' stamp: 'dgd 9/1/2004 15:29'! snapToEdgeIfAppropriate (self owner isNil or: [self owner isHandMorph]) ifTrue: [^ self]. "" self updateBounds! ! !DockingBarMorph methodsFor: 'rounding' stamp: 'dgd 8/31/2004 14:16'! roundedCorners "Return a list of those corners to round" self isAdheringToTop ifTrue: [^ #(2 3 )]. self isAdheringToBottom ifTrue: [^ #(1 4 )]. self isAdheringToLeft ifTrue: [^ #(3 4 )]. self isAdheringToRight ifTrue: [^ #(1 2 )]. ^ #(1 2 3 4 )! ! !DockingBarMorph methodsFor: 'submorphs-accessing' stamp: 'dgd 9/1/2004 18:41'! noteNewOwner: aMorph "I have just been added as a submorph of aMorph" super noteNewOwner: aMorph. self submorphs do: [:each | each adjustLayoutBounds]. ! ! !DockingBarMorph methodsFor: 'submorphs-add/remove' stamp: 'dgd 9/1/2004 19:26'! delete activeSubMenu ifNotNil: [activeSubMenu delete]. ^ super delete! ! !DockingBarMorph methodsFor: 'testing' stamp: 'dgd 8/31/2004 15:00'! isDockingBar "Return true if the receiver is a docking bar" ^ true! ! !DockingBarMorph methodsFor: 'wiw support' stamp: 'dgd 9/7/2004 19:25'! morphicLayerNumber "helpful for insuring some morphs always appear in front of or behind others. smaller numbers are in front" ^ 11! ! !DockingBarMorph methodsFor: 'private' stamp: 'dgd 9/9/2004 21:24'! selectedItem selectedItem isNil ifTrue: [^ nil]. ^ selectedItem isSelected ifTrue: [ selectedItem] ifFalse: [ nil]! ! !DockingBarMorph methodsFor: 'private - accessing' stamp: 'dgd 8/31/2004 14:35'! adhereTo: edgeSymbol "Private - Instruct the receiver to adhere to the given edge. Options: #left #top #right #bottom or #none" "" (#(#left #top #right #bottom #none ) includes: edgeSymbol) ifFalse: [^ self error: 'invalid option']. "" self setToAdhereToEdge: edgeSymbol. self updateLayoutProperties. self updateColor! ! !DockingBarMorph methodsFor: 'private - accessing' stamp: 'dgd 8/31/2004 13:56'! edgeToAdhereTo "private - answer the edge where the receiver is adhering to" ^ self valueOfProperty: #edgeToAdhereTo ifAbsent: [#none]! ! !DockingBarMorph methodsFor: 'private - accessing' stamp: 'dgd 9/1/2004 15:19'! predominantDockingBarsOfChastes: predominantChastes "Private - Answer a collection of the docking bar of my owner that are predominant to the receiver. By 'predominant' we mean docking bar that have the right to get a position before the receiver. The predominance of individual living in the same chaste is determinated by the arrival order. " | allDockingBars byChaste byArrival | (self owner isNil or: [self owner isHandMorph]) ifTrue: [^ #()]. "" allDockingBars := self owner dockingBars. "" byChaste := allDockingBars select: [:each | predominantChastes includes: each edgeToAdhereTo]. "" (predominantChastes includes: self edgeToAdhereTo) ifFalse: [^ byChaste]. "" byChaste := byChaste reject: [:each | each edgeToAdhereTo = self edgeToAdhereTo]. "" byArrival := allDockingBars select: [:each | each edgeToAdhereTo = self edgeToAdhereTo]. byArrival := byArrival copyAfter: self. "" ^ byChaste , byArrival! ! !DockingBarMorph methodsFor: 'private - accessing' stamp: 'dgd 9/1/2004 19:39'! usedHeightByPredominantDockingBarsOfChastes: predominantChastes "Private - convenience" | predominants | predominants := self predominantDockingBarsOfChastes: predominantChastes. ^ predominants isEmpty ifTrue: [0] ifFalse: [(predominants collect: [:each | each height]) sum]! ! !DockingBarMorph methodsFor: 'private - accessing' stamp: 'dgd 9/1/2004 19:38'! usedWidthByPredominantDockingBarsOfChastes: predominantChastes "Private - convenience" | predominants | predominants := self predominantDockingBarsOfChastes: predominantChastes. ^ predominants isEmpty ifTrue: [0] ifFalse: [(predominants collect: [:each | each width]) sum]! ! !DockingBarMorph methodsFor: 'private - layout' stamp: 'dgd 11/2/2004 11:59'! gradientRamp ^ gradientRamp ifNil:[{0.0 -> originalColor muchLighter. 1.0 -> originalColor twiceDarker}]! ! !DockingBarMorph methodsFor: 'private - layout' stamp: 'dgd 11/2/2004 12:00'! gradientRamp: colorRamp gradientRamp := colorRamp. "" self updateColor! ! !DockingBarMorph methodsFor: 'private - layout' stamp: 'dgd 9/1/2004 15:29'! updateBounds "private - update the receiver's bounds" self updateExtent. self isFloating ifFalse: [self updatePosition]! ! !DockingBarMorph methodsFor: 'private - layout' stamp: 'dgd 11/2/2004 11:55'! updateColor "private - update the receiver's color" | fill | self autoGradient ifFalse: [^ self]. "" fill := GradientFillStyle ramp: self gradientRamp. "" fill origin: self topLeft. self isVertical ifTrue: [fill direction: self width @ 0] ifFalse: [fill direction: 0 @ self height]. "" self fillStyle: fill! ! !DockingBarMorph methodsFor: 'private - layout' stamp: 'dgd 9/1/2004 15:20'! updateExtent "private - update the receiver's extent" | margin | self fullBounds. self fillsOwner ifFalse: [^ self]. "" margin := self avoidVisibleBordersAtEdge ifTrue: [self borderWidth * 2] ifFalse: [0]."" self isHorizontal ifTrue: [self width: self owner width + margin]."" self isVertical ifTrue: [| usedHeight | usedHeight := self usedHeightByPredominantDockingBarsOfChastes: #(#top #bottom ). self height: self owner height + margin - usedHeight]! ! !DockingBarMorph methodsFor: 'private - layout' stamp: 'dgd 8/31/2004 14:03'! updateLayoutProperties "private - update the layout properties based on adhering, fillsOwner and avoidVisibleBordersAtEdge preferencs" "" (self isHorizontal or: [self isFloating]) ifTrue: [self listDirection: #leftToRight] ifFalse: [self listDirection: #topToBottom]. "" self hResizing: #shrinkWrap. self vResizing: #shrinkWrap. self fillsOwner ifTrue: ["" self isHorizontal ifTrue: [self hResizing: #spaceFill]. self isVertical ifTrue: [self vResizing: #spaceFill]]. ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DockingBarMorph class instanceVariableNames: ''! !DockingBarMorph class methodsFor: 'samples' stamp: 'dgd 9/1/2004 20:12'! squeakMenu | menu | menu := MenuMorph new defaultTarget: self. menu add: 'Hello' target: self selector: #inform: argument: 'Hello World!!'. menu add: 'Long Hello' target: self selector: #inform: argument: 'Helloooo World!!'. menu add: 'A very long Hello' target: self selector: #inform: argument: 'Hellooooooooooooooo World!!'. menu add: 'An incredible long Hello' target: self selector: #inform: argument: 'Hellooooooooooooooooooooooo World!!'. ^ menu! ! !DockingBarMorph class methodsFor: 'scripting' stamp: 'dgd 8/31/2004 14:26'! defaultNameStemForInstances ^ 'DockingBar'! ! FileDirectory subclass: #DosFileDirectory instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Files-Directories'! !DosFileDirectory commentStamp: '' prior: 0! I represent a DOS or Windows FileDirectory. ! !DosFileDirectory methodsFor: 'as yet unclassified' stamp: 'stephaneducasse 2/4/2006 20:31'! checkName: aFileName fixErrors: fixing "Check if the file name contains any invalid characters" | fName badChars hasBadChars | fName := super checkName: aFileName fixErrors: fixing. badChars := #( $: $< $> $| $/ $\ $? $* $") asSet. hasBadChars := fName includesAnyOf: badChars. (hasBadChars and:[fixing not]) ifTrue:[^self error:'Invalid file name']. hasBadChars ifFalse:[^ fName]. ^ fName collect: [:char | (badChars includes: char) ifTrue:[$#] ifFalse:[char]]! ! !DosFileDirectory methodsFor: 'as yet unclassified' stamp: 'bf 3/21/2000 17:06'! setPathName: pathString "Ensure pathString is absolute - relative directories aren't supported on all platforms." (pathString isEmpty or: [pathString first = $\ or: [pathString size >= 2 and: [pathString second = $: and: [pathString first isLetter]]]]) ifTrue: [^ super setPathName: pathString]. self error: 'Fully qualified path expected'! ! !DosFileDirectory methodsFor: 'path access' stamp: 'stephaneducasse 2/4/2006 20:31'! driveName "return a possible drive letter and colon at the start of a Path name, empty string otherwise" | firstTwoChars | ( pathName asSqueakPathName size >= 2 ) ifTrue: [ firstTwoChars := (pathName asSqueakPathName copyFrom: 1 to: 2). (self class isDrive: firstTwoChars) ifTrue: [^firstTwoChars] ]. ^''! ! !DosFileDirectory methodsFor: 'path access' stamp: 'nk 7/18/2004 17:26'! fullNameFor: fileName "Return a corrected, fully-qualified name for the given file name. If the given name is already a full path (i.e., it contains a delimiter character), assume it is already a fully-qualified name. Otherwise, prefix it with the path to this directory. In either case, correct the local part of the file name." fileName ifNil:[^fileName]. "Check for fully qualified names" ((fileName size >= 2 and: [fileName first isLetter and: [fileName second = $:]]) or: [(fileName beginsWith: '\\') and: [(fileName occurrencesOf: $\) >= 2]]) ifTrue:[^fileName]. ^super fullNameFor: fileName! ! !DosFileDirectory methodsFor: 'path access' stamp: 'yo 12/19/2003 21:15'! fullPathFor: path "Return the fully-qualified path name for the given file." path isEmpty ifTrue:[^pathName asSqueakPathName]. (path at: 1) = $\ ifTrue:[ (path size >= 2 and:[(path at: 2) = $\]) ifTrue:[^path]. "e.g., \\pipe\" ^self driveName , path "e.g., \windows\"]. (path size >= 2 and:[(path at: 2) = $: and:[path first isLetter]]) ifTrue:[^path]. "e.g., c:" ^pathName asSqueakPathName, self slash, path! ! !DosFileDirectory methodsFor: 'path access' stamp: 'yo 12/19/2003 21:15'! relativeNameFor: path "Return the full name for path, assuming that path is a name relative to me." path isEmpty ifTrue:[^pathName asSqueakPathName]. (path at: 1) = $\ ifTrue:[ (path size >= 2 and:[(path at: 2) = $\]) ifTrue:[^super relativeNameFor: path allButFirst ]. "e.g., \\pipe\" ^super relativeNameFor: path "e.g., \windows\"]. (path size >= 2 and:[(path at: 2) = $: and:[path first isLetter]]) ifTrue:[^super relativeNameFor: (path copyFrom: 3 to: path size) ]. "e.g., c:" ^pathName asSqueakPathName, self slash, path! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DosFileDirectory class instanceVariableNames: ''! !DosFileDirectory class methodsFor: '*network-uri' stamp: 'pg 1/29/2006 15:37'! privateFullPathForURI: aURI | path | path := aURI path unescapePercents. "Check for drive notation (a: etc)" path size > 1 ifTrue: [ ((path at: 3) = $:) ifTrue: [path := path copyFrom: 2 to: path size] ifFalse: [ "All other cases should be network path names (\\xxx\sdsd etc)" path := '/' , path]]. ^path copyReplaceAll: '/' with: self slash! ! !DosFileDirectory class methodsFor: 'platform specific' stamp: 'ar 5/1/1999 01:48'! isCaseSensitive "Return true if file names are treated case sensitive" ^false! ! !DosFileDirectory class methodsFor: 'platform specific' stamp: 'ar 3/6/2004 03:46'! isDrive: fullName "Answer whether the given full name describes a 'drive', e.g., one of the root directories of a Win32 file system. We allow two forms here - the classic one where a drive is specified by a letter followed by a colon, e.g., 'C:', 'D:' etc. and the network share form starting with double-backslashes e.g., '\\server'." ^ (fullName size = 2 and: [fullName first isLetter and: [fullName last = $:]]) or: [(fullName beginsWith: '\\') and: [(fullName occurrencesOf: $\) = 2]]! ! !DosFileDirectory class methodsFor: 'platform specific' stamp: 'jm 5/8/1998 20:45'! maxFileNameLength ^ 255 ! ! !DosFileDirectory class methodsFor: 'platform specific' stamp: 'jm 12/4/97 22:57'! pathNameDelimiter ^ $\ ! ! !DosFileDirectory class methodsFor: 'platform specific' stamp: 'ar 3/6/2004 04:14'! splitName: fullName to: pathAndNameBlock "Take the file name and convert it to the path name of a directory and a local file name within that directory. IMPORTANT NOTE: For 'drives', e.g., roots of the file system on Windows we treat the full name of that 'drive' as the local name rather than the path. This is because conceptually, all of these 'drives' hang off the virtual root of the entire Squeak file system, specified by FileDirectory root. In order to be consistent with, e.g., DosFileDirectory localNameFor: 'C:\Windows' -> 'Windows' DosFileDirectory dirPathFor: 'C:\Windows' -> 'C:' we expect the following to be true: DosFileDirectory localNameFor: 'C:' -> 'C:' DosFileDirectory dirPathFor: 'C:'. -> '' DosFileDirectory localNameFor: '\\server' -> '\\server'. DosFileDirectory dirPathFor: '\\server' -> ''. so that in turn the following relations hold: | fd | fd := DosFileDirectory on: 'C:\Windows'. fd containingDirectory includes: fd localName. fd := DosFileDirectory on: 'C:'. fd containingDirectory includes: fd localName. fd := DosFileDirectory on: '\\server'. fd containingDirectory includes: fd localName. " (self isDrive: fullName) ifTrue: [^ pathAndNameBlock value:'' value: fullName]. ^ super splitName: fullName to: pathAndNameBlock! ! TestCase subclass: #DosFileDirectoryTests instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Files'! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 3/6/2004 04:03'! testFileDirectoryContainingDirectory "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: fd containingDirectory pathName = ''. ! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 3/6/2004 04:05'! testFileDirectoryContainingDirectoryExistence "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: (fd containingDirectory fileOrDirectoryExists: 'C:').! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 3/6/2004 04:04'! testFileDirectoryContainingEntry "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: (fd containingDirectory entryAt: fd localName) notNil. ! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 3/6/2004 04:04'! testFileDirectoryDirectoryEntry "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: fd directoryEntry notNil.! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 4/27/2004 23:28'! testFileDirectoryEntryFor "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory root directoryEntryFor: 'C:'. self assert: (fd name sameAs: 'C:').! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 4/27/2004 23:21'! testFileDirectoryExists "Hoping that you have 'C:' of course..." FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. self assert: (FileDirectory root directoryExists: 'C:').! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 3/6/2004 04:04'! testFileDirectoryLocalName "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: fd localName = 'C:'. ! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 4/27/2004 23:19'! testFileDirectoryNamed "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory root directoryNamed: 'C:'. self assert: fd pathName = 'C:'.! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'DF 5/26/2006 11:57'! testFileDirectoryNonExistence | inexistentFileName | "Hoping that you have 'C:' of course..." FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. inexistentFileName := DosFileDirectory default nextNameFor: 'DosFileDirectoryTest' extension: 'temp'. "This test can fail if another process creates a file with the same name as inexistentFileName (the probability of that is very very remote)" self deny: (DosFileDirectory default fileOrDirectoryExists: inexistentFileName)! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 3/6/2004 04:13'! testFileDirectoryRootExistence "Hoping that you have 'C:' of course..." FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. self assert: (FileDirectory root fileOrDirectoryExists: 'C:').! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 4/27/2004 23:28'! testFullNameFor "Hoping that you have 'C:' of course..." FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. self assert: (FileDirectory default fullNameFor: 'C:') = 'C:'. self assert: (FileDirectory default fullNameFor: 'C:\test') = 'C:\test'. self assert: (FileDirectory default fullNameFor: '\\share') = '\\share'. self assert: (FileDirectory default fullNameFor: '\\share\test') = '\\share\test'. self assert: (FileDirectory default fullNameFor: '\test') = (FileDirectory default pathParts first, '\test'). ! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 3/6/2004 04:17'! testIsDriveForDrive self assert: (DosFileDirectory isDrive: 'C:'). self deny: (DosFileDirectory isDrive: 'C:\'). self deny: (DosFileDirectory isDrive: 'C:\foo'). self deny: (DosFileDirectory isDrive: 'C:foo').! ! !DosFileDirectoryTests methodsFor: 'as yet unclassified' stamp: 'ar 3/6/2004 04:17'! testIsDriveForShare self assert: (DosFileDirectory isDrive: '\\server'). self deny: (DosFileDirectory isDrive: '\\server\'). self deny: (DosFileDirectory isDrive: '\\server\foo'). ! ! MorphicEvent subclass: #DropEvent instanceVariableNames: 'position contents wasHandled' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Events'! !DropEvent methodsFor: 'accessing' stamp: 'ar 9/13/2000 18:33'! contents ^contents! ! !DropEvent methodsFor: 'accessing' stamp: 'ar 9/13/2000 19:21'! cursorPoint "For compatibility with mouse events" ^position! ! !DropEvent methodsFor: 'accessing' stamp: 'ar 9/13/2000 18:33'! position ^position! ! !DropEvent methodsFor: 'accessing' stamp: 'ar 9/13/2000 18:33'! type ^#dropEvent! ! !DropEvent methodsFor: 'accessing' stamp: 'ar 9/13/2000 18:44'! wasHandled ^wasHandled! ! !DropEvent methodsFor: 'accessing' stamp: 'ar 9/13/2000 18:44'! wasHandled: aBool wasHandled := aBool.! ! !DropEvent methodsFor: 'dispatching' stamp: 'ar 1/10/2001 21:24'! sentTo: anObject "Dispatch the receiver into anObject" self type == #dropEvent ifTrue:[^anObject handleDropMorph: self].! ! !DropEvent methodsFor: 'initialize' stamp: 'ar 10/10/2000 01:19'! copyHandlerState: anEvent "Copy the handler state from anEvent. Used for quickly transferring handler information between transformed events." wasHandled := anEvent wasHandled.! ! !DropEvent methodsFor: 'initialize' stamp: 'ar 10/10/2000 01:18'! resetHandlerFields "Reset anything that is used to cross-communicate between two eventual handlers during event dispatch" wasHandled := false.! ! !DropEvent methodsFor: 'printing' stamp: 'JMM 9/29/2004 13:24'! printOn: aStream aStream nextPut: $[. aStream nextPutAll: self position printString; space. aStream nextPutAll: self type; space. aStream nextPutAll: self windowIndex printString. aStream nextPut: $].! ! !DropEvent methodsFor: 'testing' stamp: 'ar 9/13/2000 18:33'! isDropEvent ^true! ! !DropEvent methodsFor: 'transforming' stamp: 'ar 10/7/2000 18:28'! transformBy: aMorphicTransform "Transform the receiver into a local coordinate system." position := aMorphicTransform globalPointToLocal: position.! ! !DropEvent methodsFor: 'transforming' stamp: 'ar 10/7/2000 18:28'! transformedBy: aMorphicTransform "Return the receiver transformed by the given transform into a local coordinate system." ^self shallowCopy transformBy: aMorphicTransform! ! !DropEvent methodsFor: 'private' stamp: 'ar 9/13/2000 19:23'! setPosition: pos contents: aMorph hand: aHand position := pos. contents := aMorph. source := aHand. wasHandled := false.! ! DropEvent subclass: #DropFilesEvent instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Events'! !DropFilesEvent methodsFor: 'accessing' stamp: 'ar 1/10/2001 21:35'! type ^#dropFilesEvent! ! !DropFilesEvent methodsFor: 'dispatching' stamp: 'ar 1/10/2001 21:35'! sentTo: anObject "Dispatch the receiver into anObject" self type == #dropFilesEvent ifTrue:[^anObject handleDropFiles: self].! ! MorphicModel subclass: #DropListMorph uses: TEnableOnHaloMenu instanceVariableNames: 'contentMorph listMorph buttonMorph list listSelectionIndex getListSelector getIndexSelector setIndexSelector getEnabledSelector enabled useSelectionIndex' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !DropListMorph commentStamp: 'gvc 5/23/2007 14:12' prior: 0! Displays a selected item and a drop button. When pressed will popup a list to enable changing of the selection. Supports enablement.! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 8/22/2006 13:25'! buttonMorph "Answer the value of buttonMorph" ^ buttonMorph! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 8/22/2006 13:25'! buttonMorph: anObject "Set the value of buttonMorph" buttonMorph := anObject! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 6/17/2006 11:45'! contentMorph "Answer the value of contentMorph" ^ contentMorph! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 6/17/2006 11:45'! contentMorph: anObject "Set the value of contentMorph" contentMorph := anObject! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 8/14/2006 13:18'! enabled "Answer the value of enabled" ^ enabled! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 9/1/2006 15:57'! enabled: anObject "Set the value of enabled" enabled = anObject ifTrue: [^self]. enabled := anObject. anObject ifFalse: [self hideList]. self changed: #enabled. self adoptPaneColor: self paneColor; changed! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 8/14/2006 13:16'! getEnabledSelector "Answer the value of getEnabledSelector" ^ getEnabledSelector! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 8/14/2006 13:30'! getEnabledSelector: anObject "Set the value of getEnabledSelector" getEnabledSelector := anObject. self updateEnabled! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 7/17/2006 12:26'! getIndexSelector "Answer the value of getIndexSelector" ^ getIndexSelector! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 7/17/2006 12:26'! getIndexSelector: anObject "Set the value of getIndexSelector" getIndexSelector := anObject! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 7/17/2006 12:26'! getListSelector "Answer the value of getListSelector" ^ getListSelector! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 7/17/2006 12:26'! getListSelector: anObject "Set the value of getListSelector" getListSelector := anObject! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 6/17/2006 11:07'! listMorph "Answer the value of listMorph" ^ listMorph! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 6/17/2006 11:07'! listMorph: anObject "Set the value of listMorph" listMorph := anObject! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 7/17/2006 12:26'! setIndexSelector "Answer the value of setIndexSelector" ^ setIndexSelector! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 7/17/2006 12:26'! setIndexSelector: anObject "Set the value of setIndexSelector" setIndexSelector := anObject! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 8/8/2007 15:53'! useSelectionIndex "Answer the value of useSelectionIndex" ^ useSelectionIndex! ! !DropListMorph methodsFor: 'accessing' stamp: 'gvc 8/8/2007 15:53'! useSelectionIndex: anObject "Set the value of useSelectionIndex" useSelectionIndex := anObject! ! !DropListMorph methodsFor: 'as yet unclassified'! addToggleItemsToHaloMenu: aCustomMenu "Add toggle-items to the halo menu" super addToggleItemsToHaloMenu: aCustomMenu. aCustomMenu addUpdating: #enabledString target: self action: #toggleEnabled! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/22/2009 15:35'! adoptPaneColor: paneColor "Pass on to the list morph and border too." super adoptPaneColor: paneColor. paneColor ifNil: [^self]. self fillStyle: self fillStyleToUse. self borderWidth > 0 ifTrue: [ self borderStyle: self borderStyleToUse]. self buttonMorph cornerStyle: self cornerStyle. self updateContentColor: paneColor. self listPaneColor: paneColor. self changed: #buttonLabel! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 11:04'! borderStyleToUse "Answer the borderStyle that should be used for the receiver." ^self enabled ifTrue: [self theme dropListNormalBorderStyleFor: self] ifFalse: [self theme dropListDisabledBorderStyleFor: self]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/23/2009 13:12'! buttonExtent "Answer based on theme and preferences." ^self buttonWidth @ self buttonHeight! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/23/2009 13:12'! buttonHeight "Answer based on theme." ^self theme buttonMinHeight! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/1/2009 11:40'! buttonLabel "Answer the label for the button." ^self theme dropListButtonLabelFor: self! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/28/2009 17:08'! buttonWidth "Answer based on scrollbar size." ^(Preferences scrollBarsNarrow ifTrue: [12] ifFalse: [16]) max: self theme dropListControlButtonWidth! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/22/2006 13:31'! cornerStyle: aSymbol "Pass on to list and button too." super cornerStyle: aSymbol. self listMorph cornerStyle: aSymbol. self buttonMorph cornerStyle: aSymbol.! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/17/2006 11:17'! defaultColor "Answer the default color of the receiver." ^Color white! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/2/2007 12:18'! disable "Disable the receiver." self enabled: false! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/31/2007 15:16'! drawSubmorphsOn: aCanvas "Display submorphs back to front. Draw the focus here since we are using inset bounds for the focus rectangle." super drawSubmorphsOn: aCanvas. self hasKeyboardFocus ifTrue: [ self drawKeyboardFocusOn: aCanvas]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/2/2007 12:18'! enable "Enable the receiver." self enabled: true! ! !DropListMorph methodsFor: 'as yet unclassified'! enabledString "Answer the string to be shown in a menu to represent the 'enabled' status" ^ (self enabled ifTrue: [''] ifFalse: ['']), 'enabled' translated! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 11:04'! extent: newExtent "Update the gradient." super extent: newExtent. (self fillStyle notNil and: [self fillStyle isSolidFill not]) ifTrue: [self fillStyle: self fillStyleToUse]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 11:03'! fillStyleToUse "Answer the fillStyle that should be used for the receiver." ^self enabled ifTrue: [self theme dropListNormalFillStyleFor: self] ifFalse: [self theme dropListDisabledFillStyleFor: self]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/20/2009 16:38'! focusBounds "Answer the bounds for drawing the focus indication." ^self theme dropListFocusBoundsFor: self! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/20/2009 16:40'! focusIndicatorCornerRadius "Answer the corner radius preferred for the focus indicator for the receiver for themes that support this." ^self theme dropListFocusIndicatorCornerRadiusFor: self ! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/8/2006 15:07'! font "Answer the list font" ^self listMorph font! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/31/2007 12:34'! font: aFont "Set the list and content font" self listMorph font: aFont. self contentMorph beAllFont: aFont! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/30/2009 14:15'! getCurrentSelection "Answer the current selection from the model." |selection| selection := self model perform: self getIndexSelector. ^(self list includes: selection) ifTrue: [selection]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/17/2006 12:30'! getCurrentSelectionIndex "Answer the index of the current selection." self getIndexSelector ifNil: [^0]. ^self model perform: self getIndexSelector! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/8/2006 11:30'! handlesKeyboard: evt "Return true if the receiver wishes to handle the given keyboard event." ^true! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/13/2009 13:54'! hideList "Hide the list." self listMorph ifNil: [^self]. self listVisible ifFalse: [^self]. self listMorph delete. self listMorph selectionIndex = self listSelectionIndex ifFalse: [self listMorph changeModelSelection: self listMorph selectionIndex]. self roundedCorners: #(1 2 3 4). (self buttonMorph ifNil: [^self]) roundedCorners: (self roundedCorners copyWithoutAll: #(1 2)). self changed. self wantsKeyboardFocus ifTrue: [self takeKeyboardFocus]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/23/2009 12:20'! initialize "Initialize the receiver." super initialize. listSelectionIndex := 0. enabled := true. list := #(). self useSelectionIndex: true; clipSubmorphs: true; layoutPolicy: RowLayout new; layoutInset: (self theme dropListInsetFor: self); cellPositioning: #center; listMorph: self newListMorph; contentMorph: self newContentMorph; buttonMorph: self newButtonMorph; borderStyle: self borderStyleToUse; addMorphBack: self contentMorph; addMorphBack: (self addDependent: self buttonMorph); on: #mouseDown send: #popList to: self. self listMorph fillStyle: (self theme dropListNormalListFillStyleFor: self)! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/8/2007 13:31'! keyStroke: event "Pass on to the list." (self navigationKey: event) ifTrue: [^self]. self listMorph keyStroke: event ! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/6/2007 14:37'! keyboardFocusChange: aBoolean "The message is sent to a morph when its keyboard focus changes. Update for focus feedback." self focusChanged! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/17/2006 11:27'! list "Answer the list contents." ^list! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/17/2006 11:31'! list: aCollection "Set the list contents." list := aCollection. self changed: #list! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/29/2006 12:16'! listHeight "Answer the height for the list." ^(self listMorph listMorph height + 6 max: 38) min: 200! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/17/2006 11:42'! listMorphClass "Answer the class for a new list morph" ^PluggableListMorph! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/22/2006 15:44'! listMouseDown: evt "Click outside the list." (self listMorph fullContainsPoint: evt position) ifTrue: [self listMorph selectionIndex: (self listMorph rowAtLocation: evt position)] ifFalse: [self hideList]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/13/2009 14:01'! listPaneColor: paneColor "Set the pane color for the list." self listMorph ifNil: [^self]. self listMorph adoptPaneColor: paneColor; fillStyle: (self theme dropListNormalListFillStyleFor: self); borderStyle: (self theme dropListNormalListBorderStyleFor: self)! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/17/2006 11:28'! listSelectionIndex "Answer the list selection." ^listSelectionIndex! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/8/2007 16:08'! listSelectionIndex: anInteger "Set the list selection." self hideList. anInteger = 0 ifTrue: [^self]. listSelectionIndex := anInteger. self changed: #listSelectionIndex; updateContents; triggerEvent: #selectionIndex with: anInteger. self model ifNotNilDo: [:m | self setIndexSelector ifNotNilDo: [:s | self useSelectionIndex ifTrue: [m perform: s with: anInteger] ifFalse: [m perform: s with: self selectedItem]]]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/17/2006 12:26'! listVisible "Answer whether the list is visible." ^self listMorph owner notNil! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/17/2006 12:27'! morphicLayerNumber "Answer the layer number." ^self listVisible ifTrue: [10] ifFalse: [super morphicLayerNumber]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/23/2009 13:12'! newButtonMorph "Answer a new button morph" ^(ControlButtonMorph on: self getState: nil action: #popList label: #buttonLabel) roundedCorners: #(3 4); getEnabledSelector: #enabled; label: self buttonLabel; vResizing: #spaceFill; hResizing: #rigid; extent: self buttonExtent; setProperty: #wantsKeyboardFocusNavigation toValue: false; cornerStyle: self cornerStyle! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 6/5/2007 09:23'! newContentMorph "Answer a new content morph" ^TextMorphForFieldView new contents: ' '; margins: (2@0 corner: 2@1); vResizing: #shrinkWrap; hResizing: #spaceFill; autoFit: false; lock! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/13/2009 14:01'! newListMorph "Answer a new list morph" |m| m := (self listMorphClass on: self list: #list selected: #listSelectionIndex changeSelected: #listSelectionIndex: menu: nil keystroke: nil) roundedCorners: #(2 3); setProperty: #morphicLayerNumber toValue: 5; color: self color; borderStyle: (self theme dropListNormalListBorderStyleFor: self); on: #mouseDown send: #listMouseDown: to: self. ^m! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/8/2007 15:58'! on: anObject list: getListSel selected: getSelectionSel changeSelected: setSelectionSel "Set the receiver to the given model parameterized by the given message selectors." getListSel isSymbol ifTrue: [self getListSelector: getListSel] ifFalse: [self list: getListSel]. "allow direct list" self model: anObject; getIndexSelector: getSelectionSel; setIndexSelector: setSelectionSel; updateList; updateListSelectionIndex; updateContents! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/8/2006 10:13'! outOfWorld: aWorld "Get rid of the list if visible." self hideList. ^super outOfWorld: aWorld! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/22/2006 15:00'! popList "Hide / show the list." self enabled ifFalse: [^self]. self listMorph owner isNil ifTrue: [self showList] ifFalse: [self hideList]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/12/2009 18:15'! roundedCorners: anArray "Set the corners to round." super roundedCorners: anArray. self buttonMorph ifNotNilDo: [:b | b roundedCorners: (anArray copyWithoutAll: #(1 2))]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/12/2007 14:12'! selectedItem "Answer the selected list item." ^(self listSelectionIndex between: 1 and: self list size) ifTrue: [ self list at: self listSelectionIndex]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/12/2006 13:58'! selectionColor "Answer the selection color for the receiver." ^self listMorph selectionColor! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/12/2006 13:58'! selectionColor: aColor "Set the selection color for the receiver." self listMorph selectionColor: aColor! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 3/13/2009 12:07'! showList "Show the list." self listMorph owner isNil ifTrue: [self listMorph bounds: (self boundsInWorld bottomLeft extent: self width @ self listHeight). self listPaneColor: self paneColor. self world addMorphInLayer: self listMorph. self buttonMorph roundedCorners: (self roundedCorners copyWithoutAll: #(1 2 3)). self roundedCorners: (self roundedCorners copyWithoutAll: #(2 3)). self changed. self listMorph wantsKeyboardFocus ifTrue: [ self listMorph takeKeyboardFocus]. self activeHand newMouseFocus: self listMorph]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/21/2007 14:37'! step "Reset mouse focus to the list if it is showing." self listVisible ifTrue: [ self activeHand mouseFocus ifNil: [ self listMorph wantsKeyboardFocus ifTrue: [ self listMorph takeKeyboardFocus]. self activeHand newMouseFocus: self listMorph]]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/6/2006 12:48'! stepTime "Answer the desired time between steps in milliseconds." ^100! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/11/2007 12:30'! takesKeyboardFocus "Answer whether the receiver can normally take keyboard focus." ^true! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/23/2009 13:13'! themeChanged "Update the selection colour." self selectionColor ifNotNil: [ self selectionColor: self theme selectionColor]. self layoutInset: (self theme dropListInsetFor: self). self buttonMorph extent: self buttonExtent. super themeChanged! ! !DropListMorph methodsFor: 'as yet unclassified'! toggleEnabled "Toggle the enabled state." self enabled: self enabled not! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/14/2006 13:18'! update: aSymbol "Refer to the comment in View|update:." aSymbol == getListSelector ifTrue: [self updateList. ^ self]. aSymbol == getIndexSelector ifTrue: [self updateListSelectionIndex. ^ self]. aSymbol == getEnabledSelector ifTrue: [self updateEnabled. ^ self]. ! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 11:16'! updateContentColor: paneColor "Change the content text color." self enabled ifTrue: [self contentMorph textColor: Color black] ifFalse: [self contentMorph textColor: paneColor duller]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/8/2006 15:35'! updateContents "Update the contents." |sel| self contentMorph contents: (self listSelectionIndex > 0 ifTrue: [sel := self list at: self listSelectionIndex. sel isText ifTrue: [sel] ifFalse: [sel asString]] ifFalse: [' ']) "needs something to keep font"! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/8/2009 13:25'! updateEnabled "Update the enablement state." self model ifNotNil: [ self getEnabledSelector ifNotNil: [ self enabled: (self model perform: self getEnabledSelector)]]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/8/2007 15:57'! updateList "Refresh the list." self getListSelector isSymbol ifTrue: [ self list: (self model perform: self getListSelector). listSelectionIndex := 0]! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/17/2008 12:34'! updateListSelectionIndex "Update the list selection." |i| self useSelectionIndex ifTrue: [i := self getCurrentSelectionIndex. listSelectionIndex == i ifTrue: [^self]. listSelectionIndex := i] ifFalse: [i := self getCurrentSelection. listSelectionIndex := i isNil ifTrue: [0] ifFalse: [self list indexOf: i]]. self changed: #listSelectionIndex; updateContents; triggerEvent: #selectionIndex with: i! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/8/2007 15:53'! useIndex "Use the model as returning the selected index rather than item." self useSelectionIndex: true! ! !DropListMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/8/2007 15:53'! useSelection "Use the model as returning the selected item rather than index." self useSelectionIndex: false! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DropListMorph class uses: TEnableOnHaloMenu classTrait instanceVariableNames: ''! !DropListMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 7/17/2006 12:25'! on: anObject list: getListSel selected: getSelectionSel changeSelected: setSelectionSel "Answer a new instance of the receiver on the given model using the given selectors as the interface." ^self new on: anObject list: getListSel selected: getSelectionSel changeSelected: setSelectionSel! ! !DropListMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 8/8/2007 16:05'! on: anObject list: getListSel selected: getSelectionSel changeSelected: setSelectionSel useIndex: useIndex "Answer a new instance of the receiver on the given model using the given selectors as the interface." ^self new useSelectionIndex: useIndex; on: anObject list: getListSel selected: getSelectionSel changeSelected: setSelectionSel! ! Model subclass: #DualChangeSorter instanceVariableNames: 'leftCngSorter rightCngSorter' classVariableNames: '' poolDictionaries: '' category: 'Tools-Changes'! !DualChangeSorter commentStamp: '' prior: 0! This class presents a view of a two change sets at once, and supports copying changes between change sets. ! !DualChangeSorter methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 1/23/2009 16:31'! modelWakeUp "A window with me as model is being entered. Make sure I am up-to-date with the changeSets. Treat each side individually rather than going through the . Changed here to avoid endless confirm dialogs." leftCngSorter canDiscardEdits ifTrue: [leftCngSorter updateIfNecessary]. rightCngSorter canDiscardEdits ifTrue: [rightCngSorter updateIfNecessary]! ! !DualChangeSorter methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:27'! morphicWindow | window | leftCngSorter := ChangeSorter new myChangeSet: ChangeSet current. leftCngSorter parent: self. rightCngSorter := ChangeSorter new myChangeSet: ChangeSorter secondaryChangeSet. rightCngSorter parent: self. window := (SystemWindow labelled: leftCngSorter label) model: self. "topView minimumSize: 300 @ 200." leftCngSorter openAsMorphIn: window rect: (0@0 extent: 0.5@1). rightCngSorter openAsMorphIn: window rect: (0.5@0 extent: 0.5@1). ^ window ! ! !DualChangeSorter methodsFor: 'initialization' stamp: 'di 5/20/1998 21:44'! okToChange ^ leftCngSorter okToChange & rightCngSorter okToChange! ! !DualChangeSorter methodsFor: 'initialization' stamp: 'alain.plantec 5/30/2008 13:00'! open ^ self openAsMorph. ! ! !DualChangeSorter methodsFor: 'initialization' stamp: 'sw 3/6/1999 09:34'! openAsMorph ^ self morphicWindow openInWorld ! ! !DualChangeSorter methodsFor: 'initialization'! release leftCngSorter release. rightCngSorter release.! ! !DualChangeSorter methodsFor: 'other'! isLeftSide: theOne "Which side am I?" ^ theOne == leftCngSorter! ! !DualChangeSorter methodsFor: 'other' stamp: 'sd 11/20/2005 21:27'! labelString "The window label" | leftName rightName changesName | leftName := leftCngSorter changeSetCategory categoryName. rightName := rightCngSorter changeSetCategory categoryName. changesName := 'Changes go to "', ChangeSet current name, '"'. ^ ((leftName ~~ #All) or: [rightName ~~ #All]) ifTrue: ['(', leftName, ') - ', changesName, ' - (', rightName, ')'] ifFalse: [changesName]! ! !DualChangeSorter methodsFor: 'other'! other: theOne "Return the other side's ChangeSorter" ^ theOne == leftCngSorter ifTrue: [rightCngSorter] ifFalse: [leftCngSorter]! ! !DualChangeSorter methodsFor: 'toolbuilder' stamp: 'sd 11/20/2005 21:27'! buildWith: builder | windowSpec | leftCngSorter := ChangeSorter new myChangeSet: ChangeSet current. leftCngSorter parent: self. rightCngSorter := ChangeSorter new myChangeSet: ChangeSorter secondaryChangeSet. rightCngSorter parent: self. windowSpec := builder pluggableWindowSpec new. windowSpec model: self. windowSpec label: 'Change Sorter'. windowSpec children: OrderedCollection new. leftCngSorter buildWith: builder in: windowSpec rect: (0@0 extent: 0.5@1). rightCngSorter buildWith: builder in: windowSpec rect: (0.5@0 extent: 0.5@1). ^builder build: windowSpec ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DualChangeSorter class instanceVariableNames: ''! !DualChangeSorter class methodsFor: 'initialization' stamp: 'asm 4/10/2003 12:44'! registerInFlapsRegistry "Register the receiver in the system's flaps registry" self environment at: #Flaps ifPresent: [:cl | cl registerQuad: #(DualChangeSorter prototypicalToolWindow 'Change Sorter' 'Shows two change sets side by side') forFlapNamed: 'Tools']! ! !DualChangeSorter class methodsFor: 'initialization' stamp: 'asm 4/11/2003 12:33'! unload "Unload the receiver from global registries" self environment at: #Flaps ifPresent: [:cl | cl unregisterQuadsWithReceiver: self] ! ! !DualChangeSorter class methodsFor: 'opening' stamp: 'sw 3/24/1999 17:50'! open "Open a new instance of the receiver's class" self new open! ! !DualChangeSorter class methodsFor: 'opening' stamp: 'sw 6/11/2001 17:38'! prototypicalToolWindow "Answer an example of myself seen in a tool window, for the benefit of parts-launching tools" ^ self new morphicWindow applyModelExtent! ! !DualChangeSorter class methodsFor: 'window color' stamp: 'sw 2/26/2002 14:12'! windowColorSpecification "Answer a WindowColorSpec object that declares my preference" ^ WindowColorSpec classSymbol: self name wording: 'Dual Change Sorter' brightColor: #lightBlue pastelColor: #paleBlue helpMessage: 'Lets you view and manipulate two change sets concurrently.'! ! AbstractSoundSystem subclass: #DummySoundSystem instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Support'! !DummySoundSystem commentStamp: 'gk 2/24/2004 23:14' prior: 0! This is a dummy sound system registered in SoundService to absorb all sound playing and to use the primitive beep instead of sampled sounds when playing a beep.! !DummySoundSystem methodsFor: 'misc' stamp: 'gk 2/23/2004 20:48'! randomBitsFromSoundInput: bitCount "I'm not sure what the right thing to do here is." self error: 'Can not provide random data.'! ! !DummySoundSystem methodsFor: 'misc' stamp: 'gk 2/23/2004 19:54'! sampledSoundChoices "No choices other than this." ^ #('silence')! ! !DummySoundSystem methodsFor: 'misc' stamp: 'gk 2/23/2004 19:55'! soundNamed: soundName "There are no sounds to look up." ^ nil! ! !DummySoundSystem methodsFor: 'playing' stamp: 'gk 2/24/2004 23:53'! beep "Make a primitive beep." Beeper beepPrimitive! ! !DummySoundSystem methodsFor: 'playing' stamp: 'gk 2/23/2004 19:53'! playSampledSound: samples rate: rate "Do nothing." ! ! !DummySoundSystem methodsFor: 'playing' stamp: 'gk 2/23/2004 19:54'! playSoundNamed: soundName "Do nothing."! ! !DummySoundSystem methodsFor: 'playing' stamp: 'gk 2/23/2004 19:54'! playSoundNamed: soundName ifAbsentReadFrom: aifFileName "Do nothing."! ! !DummySoundSystem methodsFor: 'playing' stamp: 'gk 4/8/2005 14:15'! playSoundNamedOrBeep: soundName "There is no sound support, so we make the beep." self beep! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DummySoundSystem class instanceVariableNames: ''! !DummySoundSystem class methodsFor: 'initialization' stamp: 'gk 2/23/2004 21:08'! initialize SoundService register: self new.! ! !DummySoundSystem class methodsFor: 'initialization' stamp: 'gk 2/23/2004 21:08'! unload SoundService registeredClasses do: [:ss | (ss isKindOf: self) ifTrue: [SoundService unregister: ss]].! ! Stream subclass: #DummyStream instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Object Storage'! !DummyStream commentStamp: '' prior: 0! The purpose of this class is to absorb all steam messages and do nothing. This is so ReferenceStream can pretend to write on it while traversing all objects it would normally write. We need to know what those object are. 8/17/96 tk ! !DummyStream methodsFor: 'accessing'! nextInt32Put: arg "do nothing"! ! !DummyStream methodsFor: 'accessing'! nextNumber: cnt put: num "do nothing"! ! !DummyStream methodsFor: 'accessing' stamp: 'tk 6/8/1998 21:06'! nextPutAll: aByteArray "do nothing"! ! !DummyStream methodsFor: 'accessing' stamp: 'tk 6/8/1998 21:07'! nextPut: aByte "do nothing"! ! !DummyStream methodsFor: 'accessing'! nextStringPut: aString "do nothing"! ! !DummyStream methodsFor: 'accessing' stamp: 'tk 3/6/2000 11:10'! originalContents ^ ''! ! !DummyStream methodsFor: 'accessing'! position "Return any random number. Here is where the real lying begins. We are a DummyStream afterall. 8/17/96 tk" ^ 47 ! ! !DummyStream methodsFor: 'accessing' stamp: 'tk 7/12/1998 12:51'! position: anOffset "Pretend to position wherever the caller says!!" ! ! !DummyStream methodsFor: 'error handling'! subclassResponsibility "Do nothing. Most messages to class Stream are defined as subclassResponsibility. Just accept them. 8/17/96 tk" "No error. Just go on."! ! !DummyStream methodsFor: 'positioning' stamp: '6/10/97 17:14 tk'! skip: aNumber "Do nothing."! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DummyStream class instanceVariableNames: ''! !DummyStream class methodsFor: 'instance creation' stamp: 'jm 12/3/97 20:25'! on: aFile "Return a new DummyStream instance, ignoring the argument." ^ self basicNew ! ! Magnitude subclass: #Duration instanceVariableNames: 'nanos seconds' classVariableNames: '' poolDictionaries: 'ChronologyConstants' category: 'Kernel-Chronology'! !Duration commentStamp: 'marcus.denker 6/5/2009 11:27' prior: 0! I represent a duration of time. I have nanosecond precision! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 07:59'! * operand "operand is a Number" ^ self class nanoSeconds: ( (self asNanoSeconds * operand) asInteger) ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 07:59'! + operand "operand is a Duration" ^ self class nanoSeconds: (self asNanoSeconds + operand asNanoSeconds) ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 07:59'! - operand "operand is a Duration" ^ self + operand negated ! ! !Duration methodsFor: 'ansi protocol' stamp: 'sd 3/16/2008 15:36'! / operand "operand is a Duration or a Number" ^ operand isNumber ifTrue: [ self class nanoSeconds: (self asNanoSeconds / operand) asInteger ] ifFalse: [ self asNanoSeconds / operand asDuration asNanoSeconds ] ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:00'! < comparand ^ self asNanoSeconds < comparand asNanoSeconds ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 1/9/2004 06:25'! = comparand "Answer whether the argument is a representing the same period of time as the receiver." ^ self == comparand ifTrue: [true] ifFalse: [self species = comparand species ifTrue: [self asNanoSeconds = comparand asNanoSeconds] ifFalse: [false] ]! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:01'! abs ^ self class seconds: seconds abs nanoSeconds: nanos abs ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:01'! asDuration ^ self ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:01'! asSeconds ^ seconds ! ! !Duration methodsFor: 'ansi protocol' stamp: 'gk 8/30/2006 23:42'! days "Answer the number of days the receiver represents." ^ seconds quo: SecondsInDay ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:01'! hash ^seconds bitXor: nanos ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:01'! hours "Answer the number of hours the receiver represents." ^ (seconds rem: SecondsInDay) quo: SecondsInHour ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:01'! minutes "Answer the number of minutes the receiver represents." ^ (seconds rem: SecondsInHour) quo: SecondsInMinute ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:02'! negated ^ self class seconds: seconds negated nanoSeconds: nanos negated ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:02'! negative ^ self positive not ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 5/13/2003 08:02'! positive ^ seconds = 0 ifTrue: [ nanos positive ] ifFalse: [ seconds positive ] ! ! !Duration methodsFor: 'ansi protocol' stamp: 'brp 8/23/2003 10:03'! seconds "Answer the number of seconds the receiver represents." ^ (seconds rem: SecondsInMinute) + (nanos / NanosInSecond)! ! !Duration methodsFor: 'initialize-release' stamp: 'alain.plantec 5/28/2009 09:51'! initialize super initialize. self seconds: 0 nanoSeconds: 0. ! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 9/25/2003 14:29'! // operand "operand is a Duration or a Number" ^ operand isNumber ifTrue: [ self class nanoSeconds: (self asNanoSeconds // operand) asInteger ] ifFalse: [ self asNanoSeconds // operand asDuration asNanoSeconds ] ! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 9/25/2003 15:07'! \\ operand "modulo. Remainder defined in terms of //. Answer a Duration with the same sign as aDuration. operand is a Duration or a Number." ^ operand isNumber ifTrue: [ self class nanoSeconds: (self asNanoSeconds \\ operand) ] ifFalse: [ self - (operand * (self // operand)) ] ! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 9/25/2003 13:42'! asDelay ^ Delay forDuration: self! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 5/13/2003 08:03'! asMilliSeconds ^ ((seconds * NanosInSecond) + nanos) // (10 raisedToInteger: 6) ! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 5/13/2003 08:03'! asNanoSeconds ^ (seconds * NanosInSecond) + nanos ! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 4/13/2006 10:20'! isZero ^ seconds = 0 and: [ nanos = 0 ] ! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 5/13/2003 08:03'! nanoSeconds ^ nanos ! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 9/25/2003 13:22'! printOn: aStream "Format as per ANSI 5.8.2.16: [-]D:HH:MM:SS[.S]" | d h m s n | d := self days abs. h := self hours abs. m := self minutes abs. s := self seconds abs truncated. n := self nanoSeconds abs. self negative ifTrue: [ aStream nextPut: $- ]. d printOn: aStream. aStream nextPut: $:. h < 10 ifTrue: [ aStream nextPut: $0. ]. h printOn: aStream. aStream nextPut: $:. m < 10 ifTrue: [ aStream nextPut: $0. ]. m printOn: aStream. aStream nextPut: $:. s < 10 ifTrue: [ aStream nextPut: $0. ]. s printOn: aStream. n = 0 ifFalse: [ | z ps | aStream nextPut: $.. ps := n printString padded: #left to: 9 with: $0. z := ps findLast: [ :c | c asciiValue > $0 asciiValue ]. ps from: 1 to: z do: [ :c | aStream nextPut: c ] ]. ! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 9/25/2003 15:42'! roundTo: aDuration "e.g. if the receiver is 5 minutes, 37 seconds, and aDuration is 2 minutes, answer 6 minutes." ^ self class nanoSeconds: (self asNanoSeconds roundTo: aDuration asNanoSeconds) ! ! !Duration methodsFor: 'squeak protocol' stamp: 'brp 9/25/2003 15:38'! truncateTo: aDuration "e.g. if the receiver is 5 minutes, 37 seconds, and aDuration is 2 minutes, answer 4 minutes." ^ self class nanoSeconds: (self asNanoSeconds truncateTo: aDuration asNanoSeconds) ! ! !Duration methodsFor: 'private' stamp: 'adrian_lienhard 1/7/2009 18:19'! seconds: secondCount nanoSeconds: nanoCount "Private - only used by Duration class" seconds := secondCount. nanos := nanoCount rounded! ! !Duration methodsFor: 'private' stamp: 'brp 9/25/2003 14:42'! storeOn: aStream aStream nextPut: $(; nextPutAll: self className; nextPutAll: ' seconds: '; print: seconds; nextPutAll: ' nanoSeconds: '; print: nanos; nextPut: $). ! ! !Duration methodsFor: 'private' stamp: 'adrian_lienhard 1/7/2009 18:21'! ticks "Answer an array {days. seconds. nanoSeconds}. Used by DateAndTime and Time." | days | days := self days. ^ Array with: days with: seconds - (days * SecondsInDay) with: nanos! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Duration class instanceVariableNames: ''! !Duration class methodsFor: 'ansi protocol' stamp: 'gk 8/31/2006 01:09'! days: days hours: hours minutes: minutes seconds: seconds ^ self days: days hours: hours minutes: minutes seconds: seconds nanoSeconds: 0! ! !Duration class methodsFor: 'ansi protocol' stamp: 'gk 8/30/2006 23:18'! days: days seconds: seconds ^ self basicNew seconds: days * SecondsInDay + seconds nanoSeconds: 0 ! ! !Duration class methodsFor: 'ansi protocol' stamp: 'gk 8/31/2006 01:34'! seconds: seconds ^ self seconds: seconds nanoSeconds: 0 ! ! !Duration class methodsFor: 'ansi protocol' stamp: 'gk 8/31/2006 00:09'! zero ^ self basicNew seconds: 0 nanoSeconds: 0 ! ! !Duration class methodsFor: 'squeak protocol' stamp: 'gk 8/31/2006 01:25'! days: aNumber ^ self seconds: aNumber * SecondsInDay nanoSeconds: 0! ! !Duration class methodsFor: 'squeak protocol' stamp: 'gk 8/31/2006 01:26'! days: days hours: hours minutes: minutes seconds: seconds nanoSeconds: nanos ^ self seconds: ((days * SecondsInDay) + (hours * SecondsInHour) + (minutes * SecondsInMinute) + seconds) nanoSeconds: nanos ! ! !Duration class methodsFor: 'squeak protocol' stamp: 'PeterHugossonMiller 9/2/2009 16:18'! fromString: aString ^ self readFrom: aString readStream ! ! !Duration class methodsFor: 'squeak protocol' stamp: 'gk 8/31/2006 01:26'! hours: aNumber ^ self seconds: aNumber * SecondsInHour nanoSeconds: 0! ! !Duration class methodsFor: 'squeak protocol' stamp: 'gk 8/31/2006 01:35'! milliSeconds: milliCount "Since seconds is 0 we can call the instance directly." ^ self basicNew seconds: 0 nanoSeconds: milliCount * NanosInMillisecond! ! !Duration class methodsFor: 'squeak protocol' stamp: 'gk 8/31/2006 01:27'! minutes: aNumber ^ self seconds: aNumber * SecondsInMinute nanoSeconds: 0! ! !Duration class methodsFor: 'squeak protocol' stamp: 'brp 1/9/2004 17:20'! month: aMonth "aMonth is an Integer or a String" ^ (Month month: aMonth year: Year current year) duration ! ! !Duration class methodsFor: 'squeak protocol' stamp: 'adrian_lienhard 1/7/2009 18:22'! nanoSeconds: nanos "This method is slow. If you have nanos less than 10^6 you should use #seconds:nanoSeconds: instead." | quo | quo := nanos quo: NanosInSecond. ^ self basicNew seconds: quo nanoSeconds: nanos - (quo * NanosInSecond)! ! !Duration class methodsFor: 'squeak protocol' stamp: 'brp 8/23/2003 12:47'! readFrom: aStream "Formatted as per ANSI 5.8.2.16: [-]D:HH:MM:SS[.S] To assiste DateAndTime>>#readFrom: SS may be unpadded or absent." | sign days hours minutes seconds nanos ws ch | sign := (aStream peekFor: $-) ifTrue: [-1] ifFalse: [1]. days := (aStream upTo: $:) asInteger sign: sign. hours := (aStream upTo: $:) asInteger sign: sign. minutes := (aStream upTo: $:) asInteger sign: sign. aStream atEnd ifTrue: [seconds := 0. nanos := 0] ifFalse: [ ws := String new writeStream. [ch := aStream next. (ch isNil) | (ch = $.)] whileFalse: [ ws nextPut: ch ]. seconds := ws contents asInteger sign: sign. ws reset. 9 timesRepeat: [ ch := aStream next. ws nextPut: (ch ifNil: [$0] ifNotNil: [ch]) ]. nanos := ws contents asInteger sign: sign]. ^ self days: days hours: hours minutes: minutes seconds: seconds nanoSeconds: nanos. " '0:00:00:00' asDuration '0:00:00:00.000000001' asDuration '0:00:00:00.999999999' asDuration '0:00:00:00.100000000' asDuration '0:00:00:00.10' asDuration '0:00:00:00.1' asDuration '0:00:00:01' asDuration '0:12:45:45' asDuration '1:00:00:00' asDuration '365:00:00:00' asDuration '-7:09:12:06.10' asDuration '+0:01:02' asDuration '+0:01:02:3' asDuration " ! ! !Duration class methodsFor: 'squeak protocol' stamp: 'adrian_lienhard 1/7/2009 18:19'! seconds: seconds nanoSeconds: nanos ^ self basicNew seconds: seconds truncated nanoSeconds: seconds fractionPart * NanosInSecond + nanos! ! !Duration class methodsFor: 'squeak protocol' stamp: 'gk 8/30/2006 23:20'! weeks: aNumber ^ self days: (aNumber * 7) seconds: 0 ! ! ClassTestCase subclass: #DurationTest instanceVariableNames: 'aDuration' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Chronology'! !DurationTest methodsFor: 'Coverage' stamp: 'brp 9/25/2003 14:30'! classToBeTested ^ Duration ! ! !DurationTest methodsFor: 'Coverage' stamp: 'brp 9/25/2003 14:30'! selectorsToBeIgnored | private | private := #( #printOn: ). ^ super selectorsToBeIgnored, private ! ! !DurationTest methodsFor: 'Tests' stamp: 'brp 1/9/2004 06:32'! testComparing | d1 d2 d3 | d1 := Duration seconds: 10 nanoSeconds: 1. d2 := Duration seconds: 10 nanoSeconds: 1. d3 := Duration seconds: 10 nanoSeconds: 2. self assert: (d1 = d1); assert: (d1 = d2); deny: (d1 = d3); assert: (d1 < d3) ! ! !DurationTest methodsFor: 'Tests' stamp: 'brp 1/21/2004 18:36'! testModulo | d1 d2 d3 | d1 := 11.5 seconds. d2 := d1 \\ 3. self assert: d2 = (Duration nanoSeconds: 1). d3 := d1 \\ (3 seconds). self assert: d3 = (Duration seconds: 2 nanoSeconds: 500000000). self assert: aDuration \\ aDuration = (Duration days: 0 hours: 0 minutes: 0 seconds: 0 nanoSeconds: 0). self assert: aDuration \\ 2 = (Duration days: 0 hours: 0 minutes: 0 seconds: 0 nanoSeconds: 1). ! ! !DurationTest methodsFor: 'Tests' stamp: 'brp 1/16/2004 14:17'! testMonthDurations | jan feb dec | jan := Duration month: #January. feb := Duration month: #February. dec := Duration month: #December. self assert: jan = (Year current months first duration); assert: feb = (Year current months second duration); assert: dec = (Year current months last duration) ! ! !DurationTest methodsFor: 'Tests' stamp: 'brp 1/9/2004 06:28'! testNumberConvenienceMethods self assert: 1 week = (Duration days: 7); assert: -1 week = (Duration days: -7); assert: 1 day = (Duration days: 1); assert: -1 day = (Duration days: -1); assert: 1 hours = (Duration hours: 1); assert: -1 hour = (Duration hours: -1); assert: 1 minute = (Duration seconds: 60); assert: -1 minute = (Duration seconds: -60); assert: 1 second = (Duration seconds: 1); assert: -1 second = (Duration seconds: -1); assert: 1 milliSecond = (Duration milliSeconds: 1); assert: -1 milliSecond = (Duration milliSeconds: -1); assert: 1 nanoSecond = (Duration nanoSeconds: 1); assert: -1 nanoSecond = (Duration nanoSeconds: -1) ! ! !DurationTest methodsFor: 'Tests' stamp: 'brp 9/25/2003 14:57'! testQuotient | d1 d2 q | d1 := 11.5 seconds. d2 := d1 // 3. self assert: d2 = (Duration seconds: 3 nanoSeconds: 833333333). q := d1 // (3 seconds). self assert: q = 3. ! ! !DurationTest methodsFor: 'Tests' stamp: 'brp 1/21/2004 18:38'! testRoundTo self assert: ((5 minutes + 37 seconds) roundTo: (2 minutes)) = (6 minutes). self assert: (aDuration roundTo: (Duration days: 1)) = (Duration days: 1 hours: 0 minutes: 0 seconds: 0 nanoSeconds: 0). self assert: (aDuration roundTo: (Duration hours: 1)) = (Duration days: 1 hours: 2 minutes: 0 seconds: 0 nanoSeconds: 0). self assert: (aDuration roundTo: (Duration minutes: 1)) = (Duration days: 1 hours: 2 minutes: 3 seconds: 0 nanoSeconds: 0).! ! !DurationTest methodsFor: 'Tests' stamp: 'brp 1/21/2004 18:37'! testTruncateTo self assert: ((5 minutes + 37 seconds) truncateTo: (2 minutes)) = (4 minutes). self assert: (aDuration truncateTo: (Duration days: 1)) = (Duration days: 1 hours: 0 minutes: 0 seconds: 0 nanoSeconds: 0). self assert: (aDuration truncateTo: (Duration hours: 1)) = (Duration days: 1 hours: 2 minutes: 0 seconds: 0 nanoSeconds: 0). self assert: (aDuration truncateTo: (Duration minutes: 1)) = (Duration days: 1 hours: 2 minutes: 3 seconds: 0 nanoSeconds: 0).! ! !DurationTest methodsFor: 'running' stamp: 'brp 1/21/2004 18:36'! setUp aDuration := Duration days: 1 hours: 2 minutes: 3 seconds: 4 nanoSeconds: 5 ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testAbs self assert: aDuration abs = aDuration. self assert: (Duration nanoSeconds: -5) abs = (Duration nanoSeconds: 5). ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testAsDelay self deny: aDuration asDelay = aDuration. "want to come up with a more meaningful test" ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testAsDuration self assert: aDuration asDuration = aDuration ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testAsMilliSeconds self assert: (Duration nanoSeconds: 1000000) asMilliSeconds = 1. self assert: (Duration seconds: 1) asMilliSeconds = 1000. self assert: (Duration nanoSeconds: 1000000) asMilliSeconds = 1. self assert: (Duration nanoSeconds: 1000000) asMilliSeconds = 1. self assert: aDuration asMilliSeconds = 93784000.! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testAsNanoSeconds self assert: (Duration nanoSeconds: 1) asNanoSeconds = 1. self assert: (Duration seconds: 1) asNanoSeconds = 1000000000. self assert: aDuration asNanoSeconds = 93784000000005.! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testAsSeconds self assert: (Duration nanoSeconds: 1000000000) asSeconds = 1. self assert: (Duration seconds: 1) asSeconds = 1. self assert: aDuration asSeconds = 93784.! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testDays self assert: aDuration days = 1. self assert: (Duration days: 1) days= 1. ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testDivide self assert: aDuration / aDuration = 1. self assert: aDuration / 2 = (Duration days: 0 hours: 13 minutes: 1 seconds: 32 nanoSeconds: 2). self assert: aDuration / (1/2) = (Duration days: 2 hours: 4 minutes: 6 seconds: 8 nanoSeconds: 10). ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testFromString self assert: aDuration = (Duration fromString: '1:02:03:04.000000005'). ! ! !DurationTest methodsFor: 'testing' stamp: 'al 6/12/2008 21:57'! testHash self assert: aDuration hash = (Duration days: 1 hours: 2 minutes: 3 seconds: 4 nanoSeconds: 5) hash! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testHours self assert: aDuration hours = 2. self assert: (Duration hours: 2) hours = 2. ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testIntegerDivision self assert: aDuration // aDuration = 1. self assert: aDuration // 2 = (aDuration / 2). "is there ever a case where this is not true, since precision is always to the nano second?"! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testLessThan self assert: aDuration < (aDuration + 1 day ). self deny: aDuration < aDuration. ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testMilliSeconds self assert: (Duration milliSeconds: 5) nanoSeconds = 5000000. ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testMinus self assert: aDuration - aDuration = (Duration seconds: 0). self assert: aDuration - (Duration days: -1 hours: -2 minutes: -3 seconds: -4 nanoSeconds: -5) = (Duration days: 2 hours: 4 minutes: 6 seconds: 8 nanoSeconds: 10). self assert: aDuration - (Duration days: 0 hours: 1 minutes: 2 seconds: 3 nanoSeconds: 4) = (Duration days: 1 hours: 1 minutes: 1 seconds: 1 nanoSeconds: 1). self assert: aDuration - (Duration days: 0 hours: 3 minutes: 0 seconds: 5 nanoSeconds: 0) = (Duration days: 0 hours: 23 minutes: 2 seconds: 59 nanoSeconds: 5). ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testMinutes self assert: aDuration minutes = 3. self assert: (Duration minutes: 3) minutes = 3. ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testMultiply self assert: aDuration * 2 = (Duration days: 2 hours: 4 minutes: 6 seconds: 8 nanoSeconds: 10). ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testNanoSeconds self assert: aDuration nanoSeconds = 5. self assert: (Duration nanoSeconds: 5) nanoSeconds = 5. ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testNegated self assert: aDuration + aDuration negated = (Duration seconds: 0). ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testNegative self deny: aDuration negative. self assert: aDuration negated negative ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testNew "self assert: Duration new = (Duration seconds: 0)." "new is not valid as a creation method: MessageNotUnderstood: UndefinedObject>>quo:, where Duration seconds is nil"! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testPlus self assert: (aDuration + 0 hours) = aDuration. self assert: (aDuration + aDuration) = (Duration days: 2 hours: 4 minutes: 6 seconds: 8 nanoSeconds: 10). ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testPositive self assert: (Duration nanoSeconds: 0) positive. self assert: aDuration positive. self deny: aDuration negated positive ! ! !DurationTest methodsFor: 'testing' stamp: 'damiencassou 5/30/2008 11:09'! testPrintOn | cs rw | cs := '1:02:03:04.000000005' readStream. rw := ReadWriteStream on: ''. aDuration printOn: rw. self assert: rw contents = cs contents! ! !DurationTest methodsFor: 'testing' stamp: 'damiencassou 5/30/2008 11:09'! testReadFrom self assert: aDuration = (Duration readFrom: '1:02:03:04.000000005' readStream)! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testSeconds self assert: aDuration seconds = (800000001/200000000). self assert: (Duration nanoSeconds: 2) seconds = (2/1000000000). self assert: (Duration seconds: 2) seconds = 2. self assert: (Duration days: 1 hours: 2 minutes: 3 seconds:4) seconds = (4). self deny: (Duration days: 1 hours: 2 minutes: 3 seconds:4) seconds = (1*24*60*60+(2*60*60)+(3*60)+4). ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testSecondsNanoSeconds self assert: (Duration seconds: 0 nanoSeconds: 5) = (Duration nanoSeconds: 5). "not sure I should include in sunit since its Private " self assert: (aDuration seconds: 0 nanoSeconds: 1) = (Duration nanoSeconds: 1). ! ! !DurationTest methodsFor: 'testing' stamp: 'PeterHugossonMiller 9/3/2009 16:02'! testStoreOn | stream | aDuration storeOn: (stream := (String new: 20) writeStream). self assert: stream contents = '(Duration seconds: 93784 nanoSeconds: 5)'. ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testTicks self assert: aDuration ticks = #(1 7384 5)! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testWeeks self assert: (Duration weeks: 1) days= 7. ! ! !DurationTest methodsFor: 'testing' stamp: 'brp 1/21/2004 18:38'! testZero self assert: (Duration zero) = (Duration seconds: 0). ! ! ProcessSpecificVariable subclass: #DynamicVariable instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Processes'! !DynamicVariable commentStamp: 'mvl 3/13/2007 13:55' prior: 0! My subclasses are dynamic variables: each subclass represents a variable whose value persists inside the block passed to #value:during:. There is no way to change the value inside such a block, but it is possible to temporarirly rebind it in a nested manner.! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DynamicVariable class instanceVariableNames: ''! !DynamicVariable class methodsFor: 'accessing' stamp: 'mvl 3/13/2007 14:26'! value: anObject during: aBlock | p oldValue | p := Processor activeProcess. oldValue := p environmentAt: self ifAbsent: [self default]. [ p environmentAt: self put: anObject. aBlock value. ] ensure: [ p environmentAt: self put: oldValue ].! ! BDFFontReader subclass: #EFontBDFFontReader instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Multilingual-Display'! !EFontBDFFontReader methodsFor: 'as yet unclassified' stamp: 'sd 2/4/2008 20:28'! readCharactersInRangeFrom: start to: stop totalNums: upToNum storeInto: chars | array form code | 1 to: upToNum do: [:i | array := self readOneCharacter. code := array at: 2. code > stop ifTrue: [^ self]. (code between: start and: stop) ifTrue: [ form := array at: 1. form ifNotNil: [ chars add: array. ]. ]. ]. ! ! !EFontBDFFontReader methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! readFrom: start to: end | xTable strikeWidth glyphs ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx width blt lastAscii pointSize ret lastValue | form := encoding := bbx := nil. self initialize. self readAttributes. height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2). ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first. descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first. (properties includesKey: 'POINT_SIZE' asSymbol) ifTrue: [ pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10 ] ifFalse: [ pointSize := (ascent + descent) * 72 // 96 ]. maxWidth := 0. minAscii := 2097152. strikeWidth := 0. maxAscii := 0. charsNum := Integer readFromString: (properties at: #CHARS) first. chars := Set new: charsNum. self readCharactersInRangeFrom: start to: end totalNums: charsNum storeInto: chars. chars := chars asSortedCollection: [ :x :y | (x at: 2) <= (y at: 2) ]. charsNum := chars size. "undefined encodings make this different" chars do: [ :array | encoding := array at: 2. bbx := array at: 3. width := bbx at: 1. maxWidth := maxWidth max: width. minAscii := minAscii min: encoding. maxAscii := maxAscii max: encoding. strikeWidth := strikeWidth + width ]. glyphs := Form extent: strikeWidth @ height. blt := BitBlt toForm: glyphs. "xTable := XTableForUnicodeFont new ranges: (Array with: (Array with: start with: end))." xTable := SparseLargeTable new: end + 3 chunkSize: 32 arrayClass: Array base: start + 1 defaultValue: -1. lastAscii := start. 1 to: charsNum do: [ :i | form := (chars at: i) first. encoding := (chars at: i) second. bbx := (chars at: i) third. "lastAscii+1 to: encoding-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)]." lastValue := xTable at: lastAscii + 1 + 1. xTable at: encoding + 1 put: lastValue. blt copy: ((xTable at: encoding + 1) @ (ascent - (bbx at: 2) - (bbx at: 4)) extent: (bbx at: 1) @ (bbx at: 2)) from: 0 @ 0 in: form. xTable at: encoding + 2 put: (xTable at: encoding + 1) + (bbx at: 1). lastAscii := encoding ]. xTable zapDefaultOnlyEntries. ret := Array new: 8. ret at: 1 put: xTable. ret at: 2 put: glyphs. ret at: 3 put: minAscii. ret at: 4 put: maxAscii. ret at: 5 put: maxWidth. ret at: 6 put: ascent. ret at: 7 put: descent. ret at: 8 put: pointSize. ^ ret " ^{xTable. glyphs. minAscii. maxAscii. maxWidth. ascent. descent. pointSize}"! ! EFontBDFFontReader subclass: #EFontBDFFontReaderForRanges instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Multilingual-Display'! !EFontBDFFontReaderForRanges methodsFor: 'as yet unclassified' stamp: 'sd 2/4/2008 20:32'! additionalRangesForJapanese | basics | basics := { Array with: 16r5C with: 16rFF3C. Array with: 16r3013 with: 16rFFFD. }. ^ basics ! ! !EFontBDFFontReaderForRanges methodsFor: 'as yet unclassified' stamp: 'sd 2/4/2008 20:32'! additionalRangesForKorean | basics | basics := { Array with: 16rA1 with: 16rFFE6C. Array with: 16r3000 with: 16rFFFD. }. ^ basics ! ! !EFontBDFFontReaderForRanges methodsFor: 'as yet unclassified' stamp: 'damiencassou 5/30/2008 15:30'! override: chars with: otherFileName ranges: pairArray transcodingTable: table additionalRange: additionalRange | other rangeStream currentRange newChars code form u newArray j | other := BDFFontReader readOnlyFileNamed: otherFileName. rangeStream := pairArray readStream. currentRange := rangeStream next. newChars := PluggableSet new. newChars hashBlock: [ :elem | (elem at: 2) hash ]. newChars equalBlock: [ :a :b | (a at: 2) = (b at: 2) ]. other readChars do: [ :array | code := array at: 2. "code printStringHex printString displayAt: 0@0." code > currentRange last ifTrue: [ [ rangeStream atEnd not and: [ currentRange := rangeStream next. currentRange last < code ] ] whileTrue. rangeStream atEnd ifTrue: [ newChars addAll: chars. ^ newChars ] ]. (code between: currentRange first and: currentRange last) ifTrue: [ form := array at: 1. form ifNotNil: [ j := array at: 2. u := table at: (j // 256 - 33) * 94 + (j \\ 256 - 33) + 1. u ~= -1 ifTrue: [ array at: 2 put: u. newChars add: array. additionalRange do: [ :e | e first = (array at: 2) ifTrue: [ newArray := array clone. newArray at: 2 put: e second. newChars add: newArray ] ] ] ] ] ]. self error: 'should not reach here'! ! !EFontBDFFontReaderForRanges methodsFor: 'as yet unclassified' stamp: 'sd 2/4/2008 20:34'! rangesForJapanese | basics etc | basics := { Array with: 16r5C with: 16r5C. Array with: 16rA2 with: 16rA3. Array with: 16rA7 with: 16rA8. Array with: 16rAC with: 16rAC. Array with: 16rB0 with: 16rB1. Array with: 16rB4 with: 16rB4. Array with: 16rB6 with: 16rB6. Array with: 16rD7 with: 16rD7. Array with: 16rF7 with: 16rF7 }. etc := { Array with: 16r370 with: 16r3FF. "greek" Array with: 16r400 with: 16r52F. "cyrillic" Array with: 16r1D00 with: 16r1D7F. "phonetic" Array with: 16r1E00 with: 16r1EFF. "latin extended additional" Array with: 16r2000 with: 16r206F. "general punctuation" Array with: 16r20A0 with: 16r20CF. "currency symbols" Array with: 16r2100 with: 16r214F. "letterlike" Array with: 16r2150 with: 16r218F. "number form" Array with: 16r2190 with: 16r21FF. "arrows" Array with: 16r2200 with: 16r22FF. "math operators" Array with: 16r2300 with: 16r23FF. "misc tech" Array with: 16r2460 with: 16r24FF. "enclosed alnum" Array with: 16r2500 with: 16r257F. "box drawing" Array with: 16r2580 with: 16r259F. "box elem" Array with: 16r25A0 with: 16r25FF. "geometric shapes" Array with: 16r2600 with: 16r26FF. "misc symbols" Array with: 16r2700 with: 16r27BF. "dingbats" Array with: 16r27C0 with: 16r27EF. "misc math A" Array with: 16r27F0 with: 16r27FF. "supplimental arrow A" Array with: 16r2900 with: 16r297F. "supplimental arrow B" Array with: 16r2980 with: 16r29FF. "misc math B" Array with: 16r2A00 with: 16r2AFF. "supplimental math op" Array with: 16r2900 with: 16r297F. "supplimental arrow B" Array with: 16r2E80 with: 16r2EFF. "cjk radicals suppliment" Array with: 16r2F00 with: 16r2FDF. "kangxi radicals" Array with: 16r3000 with: 16r303F. "cjk symbols" Array with: 16r3040 with: 16r309F. "hiragana" Array with: 16r30A0 with: 16r30FF. "katakana" Array with: 16r3190 with: 16r319F. "kanbun" Array with: 16r31F0 with: 16r31FF. "katakana extension" Array with: 16r3200 with: 16r32FF. "enclosed CJK" Array with: 16r3300 with: 16r33FF. "CJK compatibility" Array with: 16r3400 with: 16r4DBF. "CJK unified extension A" Array with: 16r4E00 with: 16r9FAF. "CJK ideograph" Array with: 16rF900 with: 16rFAFF. "CJK compatiblity ideograph" Array with: 16rFE30 with: 16rFE4F. "CJK compatiblity forms" Array with: 16rFF00 with: 16rFFEF. "half and full" Array with: 16rFFFF with: 16rFFFF. "sentinel" }. ^ basics, etc. ! ! !EFontBDFFontReaderForRanges methodsFor: 'as yet unclassified' stamp: 'sd 2/4/2008 20:34'! rangesForKorean | basics etc | basics := { Array with: 16rA1 with: 16rFF }. etc := { Array with: 16r100 with: 16r17F. "extended latin" Array with: 16r370 with: 16r3FF. "greek" Array with: 16r400 with: 16r52F. "cyrillic" Array with: 16r2000 with: 16r206F. "general punctuation" Array with: 16r2100 with: 16r214F. "letterlike" Array with: 16r2150 with: 16r218F. "number form" Array with: 16r2190 with: 16r21FF. "arrows" Array with: 16r2200 with: 16r22FF. "math operators" Array with: 16r2300 with: 16r23FF. "misc tech" Array with: 16r2460 with: 16r24FF. "enclosed alnum" Array with: 16r2500 with: 16r257F. "box drawing" Array with: 16r2580 with: 16r259F. "box elem" Array with: 16r25A0 with: 16r25FF. "geometric shapes" Array with: 16r2600 with: 16r26FF. "misc symbols" Array with: 16r3000 with: 16r303F. "cjk symbols" Array with: 16r3040 with: 16r309F. "hiragana" Array with: 16r30A0 with: 16r30FF. "katakana" Array with: 16r3190 with: 16r319F. "kanbun" Array with: 16r31F0 with: 16r31FF. "katakana extension" Array with: 16r3200 with: 16r32FF. "enclosed CJK" Array with: 16r3300 with: 16r33FF. "CJK compatibility" Array with: 16r4E00 with: 16r9FAF. "CJK ideograph" Array with: 16rAC00 with: 16rD7AF. "Hangul Syllables" Array with: 16rF900 with: 16rFAFF. "CJK compatiblity ideograph" Array with: 16rFF00 with: 16rFFEF. "half and full" }. ^ basics, etc. ! ! !EFontBDFFontReaderForRanges methodsFor: 'as yet unclassified' stamp: 'yo 1/19/2005 11:20'! rangesForLatin2 ^ { Array with: 0 with: 16r17F. Array with: 16r2B0 with: 16r2FF. Array with: 16r2000 with: 16r206F. Array with: 16r2122 with: 16r2122. Array with: 16rFFFF with: 16rFFFF. "sentinel" }. ! ! !EFontBDFFontReaderForRanges methodsFor: 'as yet unclassified' stamp: 'damiencassou 5/30/2008 15:30'! readCharactersInRanges: ranges storeInto: chars | array form code rangeStream currentRange | rangeStream := ranges readStream. currentRange := rangeStream next. [ true ] whileTrue: [ array := self readOneCharacter. array second ifNil: [ ^ self ]. code := array at: 2. code > currentRange last ifTrue: [ [ rangeStream atEnd not and: [ currentRange := rangeStream next. currentRange last < code ] ] whileTrue. rangeStream atEnd ifTrue: [ ^ self ] ]. (code between: currentRange first and: currentRange last) ifTrue: [ form := array at: 1. form ifNotNil: [ chars add: array ] ] ]! ! !EFontBDFFontReaderForRanges methodsFor: 'as yet unclassified' stamp: 'sd 2/4/2008 21:09'! readRanges: ranges | xTable strikeWidth glyphs ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx width blt lastAscii pointSize ret lastValue start end | form := encoding := bbx := nil. self initialize. self readAttributes. height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2). ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first. descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first. (properties includesKey: 'POINT_SIZE' asSymbol) ifTrue: [ pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10. ] ifFalse: [ pointSize := (ascent + descent) * 72 // 96. ]. maxWidth := 0. minAscii := 16r200000. strikeWidth := 0. maxAscii := 0. charsNum := Integer readFromString: (properties at: #CHARS) first. chars := Set new: charsNum. self readCharactersInRanges: ranges storeInto: chars. chars := chars asSortedCollection: [:x :y | (x at: 2) <= (y at: 2)]. charsNum := chars size. "undefined encodings make this different" chars do: [:array | encoding := array at: 2. bbx := array at: 3.. width := bbx at: 1. maxWidth := maxWidth max: width. minAscii := minAscii min: encoding. maxAscii := maxAscii max: encoding. strikeWidth := strikeWidth + width. ]. glyphs := Form extent: strikeWidth@height. blt := BitBlt toForm: glyphs. start := (ranges collect: [:r | r first]) min. end := (ranges collect: [:r | r second]) max + 3. xTable := SparseLargeTable new: end chunkSize: 64 arrayClass: Array base: start +1 defaultValue: -1. lastAscii := start. xTable at: lastAscii + 2 put: 0. 1 to: charsNum do: [:i | form := (chars at: i) first. encoding := (chars at: i) second. bbx := (chars at: i) third. "lastAscii+1 to: encoding-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)]." lastValue := xTable at: lastAscii + 1 + 1. xTable at: encoding + 1 put: lastValue. blt copy: (((xTable at: encoding+1)@(ascent - (bbx at: 2) - (bbx at: 4))) extent: (bbx at: 1)@(bbx at: 2)) from: 0@0 in: form. xTable at: encoding+2 put: (xTable at: encoding+1)+(bbx at: 1). lastAscii := encoding. ]. xTable at: xTable size put: (xTable at: xTable size - 1). xTable zapDefaultOnlyEntries. ret := Array new: 8. ret at: 1 put: xTable. ret at: 2 put: glyphs. ret at: 3 put: minAscii. ret at: 4 put: maxAscii. ret at: 5 put: maxWidth. ret at: 6 put: ascent. ret at: 7 put: descent. ret at: 8 put: pointSize. ^ret. " ^{xTable. glyphs. minAscii. maxAscii. maxWidth. ascent. descent. pointSize}" ! ! !EFontBDFFontReaderForRanges methodsFor: 'as yet unclassified' stamp: 'sd 2/4/2008 20:39'! readRanges: ranges overrideWith: otherFileName otherRanges: otherRanges additionalOverrideRange: additionalRange | xTable strikeWidth glyphs ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx width blt lastAscii pointSize ret lastValue start end | form := encoding := bbx := nil. self initialize. self readAttributes. height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2). ascent := Integer readFromString: (properties at: 'FONT_ASCENT' asSymbol) first. descent := Integer readFromString: (properties at: 'FONT_DESCENT' asSymbol) first. (properties includesKey: 'POINT_SIZE' asSymbol) ifTrue: [ pointSize := (Integer readFromString: (properties at: 'POINT_SIZE' asSymbol) first) // 10. ] ifFalse: [ pointSize := (ascent + descent) * 72 // 96. ]. maxWidth := 0. minAscii := 16r200000. strikeWidth := 0. maxAscii := 0. charsNum := Integer readFromString: (properties at: #CHARS) first. chars := Set new: charsNum. self readCharactersInRanges: ranges storeInto: chars. chars := self override: chars with: otherFileName ranges: otherRanges transcodingTable: (UCSTable jisx0208Table) additionalRange: additionalRange. chars := chars asSortedCollection: [:x :y | (x at: 2) <= (y at: 2)]. charsNum := chars size. "undefined encodings make this different" chars do: [:array | encoding := array at: 2. bbx := array at: 3.. width := bbx at: 1. maxWidth := maxWidth max: width. minAscii := minAscii min: encoding. maxAscii := maxAscii max: encoding. strikeWidth := strikeWidth + width. ]. glyphs := Form extent: strikeWidth@height. blt := BitBlt toForm: glyphs. start := ((ranges collect: [:r | r first]), (additionalRange collect: [:r2 | r2 first])) min. end := ((ranges collect: [:r | r second]), (additionalRange collect: [:r2 | r2 second])) max + 3. "xRange := Array with: (Array with: ((ranges collect: [:r | r first]), (additionalRange collect: [:r2 | r2 first])) min with: (((ranges collect: [:r | r second]), (additionalRange collect: [:r2 | r2 second])) max + 2))." "xTable := XTableForUnicodeFont new ranges: xRange." xTable := SparseLargeTable new: end chunkSize: 64 arrayClass: Array base: start defaultValue: -1. lastAscii := start. xTable at: lastAscii + 2 put: 0. 1 to: charsNum do: [:i | form := (chars at: i) first. encoding := (chars at: i) second. bbx := (chars at: i) third. "lastAscii+1 to: encoding-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)]." lastValue := xTable at: lastAscii + 1 + 1. xTable at: encoding + 1 put: lastValue. blt copy: (((xTable at: encoding+1)@(ascent - (bbx at: 2) - (bbx at: 4))) extent: (bbx at: 1)@(bbx at: 2)) from: 0@0 in: form. xTable at: encoding+2 put: (xTable at: encoding+1)+(bbx at: 1). lastAscii := encoding. ]. xTable at: xTable size put: (xTable at: xTable size - 1). xTable zapDefaultOnlyEntries. ret := Array new: 8. ret at: 1 put: xTable. ret at: 2 put: glyphs. ret at: 3 put: minAscii. ret at: 4 put: maxAscii. ret at: 5 put: maxWidth. ret at: 6 put: ascent. ret at: 7 put: descent. ret at: 8 put: pointSize. ^ret. " ^{xTable. glyphs. minAscii. maxAscii. maxWidth. ascent. descent. pointSize}" ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EFontBDFFontReaderForRanges class instanceVariableNames: ''! !EFontBDFFontReaderForRanges class methodsFor: 'as yet unclassified' stamp: 'yo 1/19/2005 11:24'! rangesForGreek ^ { Array with: 16r1 with: 16rFF. Array with: 16r370 with: 16r3FF. Array with: 16r1F00 with: 16r1FFF. Array with: 16r2000 with: 16r206F. Array with: 16r20A0 with: 16r20AF }. ! ! !EFontBDFFontReaderForRanges class methodsFor: 'as yet unclassified' stamp: 'yo 1/19/2005 11:24'! rangesForLatin2 ^ { Array with: 0 with: 16r17F. Array with: 16r2B0 with: 16r2FF. Array with: 16r2000 with: 16r206F. Array with: 16r2122 with: 16r2122. Array with: 16rFFFF with: 16rFFFF. "sentinel" }. ! ! !EFontBDFFontReaderForRanges class methodsFor: 'as yet unclassified' stamp: 'yo 12/11/2007 11:19'! rangesForRussian ^ { Array with: 16r1 with: 16rFF. Array with: 16r400 with: 16r513. Array with: 16r2219 with: 16r2219. Array with: 16r221A with: 16r221A. Array with: 16r2248 with: 16r2248. Array with: 16r2264 with: 16r2265. Array with: 16r2320 with: 16r2321. Array with: 16r2500 with: 16r25A0. }. ! ! EUCTextConverter subclass: #EUCJPTextConverter instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Multilingual-TextConversion'! !EUCJPTextConverter commentStamp: '' prior: 0! Text converter for Japanese variation of EUC.! !EUCJPTextConverter methodsFor: 'private' stamp: 'yo 3/17/2004 00:41'! languageEnvironment ^ JapaneseEnvironment. ! ! !EUCJPTextConverter methodsFor: 'private' stamp: 'yo 10/23/2002 10:09'! leadingChar ^ JISX0208 leadingChar ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EUCJPTextConverter class instanceVariableNames: ''! !EUCJPTextConverter class methodsFor: 'utilities' stamp: 'yo 12/19/2003 22:00'! encodingNames ^ #('euc-jp' 'eucjp') copy ! ! EUCTextConverter subclass: #EUCKRTextConverter instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Multilingual-TextConversion'! !EUCKRTextConverter commentStamp: '' prior: 0! Text converter for Korean variation of EUC.! !EUCKRTextConverter methodsFor: 'private' stamp: 'yo 3/17/2004 00:41'! languageEnvironment ^ KoreanEnvironment. ! ! !EUCKRTextConverter methodsFor: 'private' stamp: 'yo 10/23/2002 15:19'! leadingChar ^ KSX1001 leadingChar ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EUCKRTextConverter class instanceVariableNames: ''! !EUCKRTextConverter class methodsFor: 'utilities' stamp: 'yo 2/17/2004 18:45'! encodingNames ^ #('euc-kr' 'ks-c-5601-1987' 'euckr') copy ! ! TextConverter subclass: #EUCTextConverter instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Multilingual-TextConversion'! !EUCTextConverter commentStamp: '' prior: 0! Text converter for Extended Unix Character. This is an abstract class. The CJK variations are implemented as subclasses.! !EUCTextConverter methodsFor: 'conversion' stamp: 'marcus.denker 9/14/2008 21:15'! nextFromStream: aStream | character1 character2 offset value1 value2 nonUnicodeChar | aStream isBinary ifTrue: [^ aStream basicNext]. character1 := aStream basicNext. character1 isNil ifTrue: [^ nil]. character1 asciiValue <= 127 ifTrue: [^ character1]. character2 := aStream basicNext. character2 isNil ifTrue: [^ nil]. offset := 16rA1. value1 := character1 asciiValue - offset. value2 := character2 asciiValue - offset. (value1 < 0 or: [value1 > 93]) ifTrue: [^ nil]. (value2 < 0 or: [value2 > 93]) ifTrue: [^ nil]. nonUnicodeChar := Character leadingChar: self leadingChar code: value1 * 94 + value2. ^ Character leadingChar: self languageEnvironment leadingChar code: nonUnicodeChar asUnicode. ! ! !EUCTextConverter methodsFor: 'conversion' stamp: 'ar 4/12/2005 14:10'! nextPut: aCharacter toStream: aStream | value leadingChar nonUnicodeChar value1 value2 | aStream isBinary ifTrue: [^aCharacter storeBinaryOn: aStream]. value := aCharacter charCode. leadingChar := aCharacter leadingChar. (leadingChar = 0 and: [value < 128]) ifTrue: [ aStream basicNextPut: (Character value: value). ^ aStream ]. (128 <= value and: [value < 256]) ifTrue: [^ aStream]. aCharacter isTraditionalDomestic ifFalse: [ nonUnicodeChar := self nonUnicodeClass charFromUnicode: value. ] ifTrue: [ nonUnicodeChar :=(Character value: value) ]. nonUnicodeChar ifNotNil: [ value := nonUnicodeChar charCode. value1 := value // 94 + 161. value2 := value \\ 94 + 161. aStream basicNextPut: (Character value: value1). aStream basicNextPut: (Character value: value2). ^ aStream ] ! ! !EUCTextConverter methodsFor: 'private' stamp: 'yo 3/17/2004 00:40'! languageEnvironment self subclassResponsibility ! ! !EUCTextConverter methodsFor: 'private' stamp: 'yo 10/23/2002 10:09'! leadingChar ^ self subclassResponsibility ! ! !EUCTextConverter methodsFor: 'private' stamp: 'yo 10/4/2003 15:48'! nonUnicodeClass ^ (EncodedCharSet charsetAt: self leadingChar). ! ! AbstractResizerMorph subclass: #EdgeGripMorph instanceVariableNames: 'target edgeName' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !EdgeGripMorph commentStamp: 'gvc 9/23/2008 11:58' prior: 0! Similar to a ProportionalSplitterMorph but designed to attach to an edge of a single morph only.! !EdgeGripMorph methodsFor: 'accessing' stamp: 'gvc 10/1/2007 13:03'! edgeName "Answer the value of edgeName" ^ edgeName! ! !EdgeGripMorph methodsFor: 'accessing' stamp: 'gvc 10/1/2007 13:23'! edgeName: anObject "Set the value of edgeName" edgeName := anObject. self layoutFrame: self gripLayoutFrame; layoutChanged! ! !EdgeGripMorph methodsFor: 'accessing' stamp: 'gvc 2/12/2007 16:43'! target "Answer the value of target" ^ target! ! !EdgeGripMorph methodsFor: 'accessing' stamp: 'gvc 7/30/2009 13:58'! target: aMorph "Set the value of target" target := aMorph! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:26'! adoptPaneColor: paneColor "Change our color too." super adoptPaneColor: paneColor. self fillStyle: self normalFillStyle! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 13:53'! bottomLayoutFrame "Answer the layout frame for a bottom edge." ^LayoutFrame fractions: (0 @ 1 corner: 1 @ 1) offsets: (22 @ SystemWindow borderWidth negated corner: -22 @ 0)! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/12/2007 16:56'! defaultHeight "Answer the default height for the receiver." ^22! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/12/2007 16:56'! defaultWidth "Answer the default width for the receiver." ^22! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/19/2007 21:25'! extent: aPoint "If our minor extent changes then adopt the pane colour to reflect any size based gradient in the theme. Assumes fillStyle will not change on the major extent for performance reasons." |ext| ext := self extent. super extent: aPoint. self isHorizontal ifTrue: [self extent y ~= ext y ifTrue: [ self adoptPaneColor: self paneColor]] ifFalse: [self extent x ~= ext x ifTrue: [ self adoptPaneColor: self paneColor]] ! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:03'! gripLayoutFrame "Answer the layout frame dependinbg on our edge." self edgeName == #top ifTrue: [^self topLayoutFrame]. self edgeName == #bottom ifTrue: [^self bottomLayoutFrame]. self edgeName == #left ifTrue: [^self leftLayoutFrame]. ^self rightLayoutFrame! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 13:53'! initialize "Initialize the receiver." super initialize. self edgeName: #right; extent: self defaultWidth+2 @ (self defaultHeight+2); hResizing: #spaceFill; vResizing: #spaceFill! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:20'! isHorizontal "Answer true if the receiver has a horizontal layout." ^self edgeName == #top or: [self edgeName == #bottom]! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:07'! leftLayoutFrame "Answer the layout frame for a left edge." ^LayoutFrame fractions: (0 @ 0 corner: 0 @ 1) offsets: (0 @ -7 corner: SystemWindow borderWidth @ (SystemWindow borderWidth - 26))! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:27'! mouseDown: anEvent "Remember the receiver and target offsets too." |cp| (self bounds containsPoint: anEvent cursorPoint) ifTrue: [self fillStyle: self pressedFillStyle]. cp := anEvent cursorPoint. lastMouse := {cp. cp - self position. cp - self targetPoint}! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 13:05'! mouseMove: anEvent "Track the mouse for resizing." target ifNil: [^self]. Preferences fastDragWindowForMorphic ifTrue: [target doFastWindowReframe: self edgeName] ifFalse: [ lastMouse at: 1 put: anEvent cursorPoint. self targetPoint: lastMouse first - lastMouse last. self positionPoint: (lastMouse first - lastMouse second)].! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:33'! mouseUp: anEvent "Change the cursor back to normal if necessary and change the color back to normal." (self bounds containsPoint: anEvent cursorPoint) ifFalse: [anEvent hand showTemporaryCursor: nil]. self adoptPaneColor: self paneColor! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:23'! normalFillStyle "Return the normal fillStyle of the receiver." ^self theme splitterNormalFillStyleFor: self! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 13:05'! positionPoint: aPoint "Reposition based on ptName." (#(top bottom) includes: self edgeName) ifTrue: [^self position: self left @ aPoint y]. (#(left right) includes: self edgeName) ifTrue: [^self position: aPoint x @ self top]. ^self position: aPoint! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:23'! pressedFillStyle "Return the pressed fillStyle of the receiver." ^self theme splitterPressedFillStyleFor: self! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 13:05'! resizeCursor ^ Cursor resizeForEdge: self edgeName! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:09'! rightLayoutFrame "Answer the layout frame for a right edge." ^LayoutFrame fractions: (1 @ 0 corner: 1 @ 1) offsets: (SystemWindow borderWidth negated @ -7 corner: 0 @ (SystemWindow borderWidth - 26))! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/3/2007 15:11'! splitsTopAndBottom "Answer true if the receiver has a horizontal layout." ^self isHorizontal! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 13:05'! targetPoint "Answer the reference point of the target." ^self target bounds pointAtSideOrCorner: self edgeName! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/17/2008 12:34'! targetPoint: aPoint "Set the reference point of the target." |minExt rect| rect := self target bounds withSideOrCorner: self edgeName setToPoint: aPoint. minExt := self target minimumExtent. rect width <= minExt x ifTrue: [ rect := self edgeName = #left ifTrue: [rect withSideOrCorner: #left setToPoint: self target bounds bottomRight - minExt] ifFalse: [rect withSideOrCorner: #right setToPoint: self target bounds topLeft + minExt]]. rect height <= minExt y ifTrue: [ rect := self edgeName = #top ifTrue: [rect withSideOrCorner: #top setToPoint: self target bounds bottomRight - minExt] ifFalse: [rect withSideOrCorner: #bottom setToPoint: self target bounds topLeft + minExt]]. self target bounds: rect! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/9/2007 14:26'! themeChanged "Update the fill style." self fillStyle: self normalFillStyle. super themeChanged! ! !EdgeGripMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/1/2007 14:47'! topLayoutFrame "Answer the layout frame for a top edge." ^LayoutFrame fractions: (0 @ 0 corner: 1 @ 0) offsets: (22 @ -29 corner: -22 @ (SystemWindow borderWidth - 29))! ! Object subclass: #EditCommand instanceVariableNames: 'textMorph phase replacedText replacedTextInterval newText newTextInterval' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Text Support'! !EditCommand commentStamp: '' prior: 0! This class handles all paragraph surgery in VI. In general, subclasses of EditCommand should be able to rely on the super class' undo/redo machinery -- only the repeat command needs to be overridden in most cases. This assumes, of course, that the newText, replacedText, newTextInterval, and replacedTextInterval have been set correctly. When setting the interval, use normal mode style selections, not insert mode selections (see class comment of VIMorphEditor). Possible useful expressions for doIt or printIt. Structure: instVar1 type -- comment about the purpose of instVar1 instVar2 type -- comment about the purpose of instVar2 Any further useful comments about the general approach of this implementation.! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/11/2002 17:12'! iEditCommand ^true! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/5/2002 16:36'! newText ^newText! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/4/2002 22:37'! newTextInterval ^newTextInterval! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/5/2002 16:36'! newTextInterval: anInterval ^newText := anInterval! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/5/2002 16:36'! newText: aText ^newText := aText! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 7/24/2003 17:01'! pEditor ^textMorph editor ! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 7/24/2003 13:40'! phase ^phase ! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 7/24/2003 13:40'! phase: aSymbol ^phase := aSymbol ! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/11/2002 20:58'! printOn: aStream | | aStream nextPutAll: self class name; nextPut: $[; nextPutAll: ('new: ', newTextInterval asString,' -> "', newText, '", rText: ', replacedTextInterval asString,' -> "', replacedText, '"'); nextPut: $].! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/5/2002 16:37'! replacedText ^replacedText! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/4/2002 22:30'! replacedTextInterval ^replacedTextInterval! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/5/2002 16:36'! replacedTextInterval: anInterval ^replacedTextInterval := anInterval! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 1/5/2002 16:37'! replacedText: aText ^replacedText := aText! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 7/24/2003 17:04'! textMorphEditor ^textMorph editor ! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 7/24/2003 17:05'! textMorphString ^textMorph text string ! ! !EditCommand methodsFor: 'accessors' stamp: 'sps 7/24/2003 17:02'! textMorphStringSize ^textMorph text string size ! ! !EditCommand methodsFor: 'command execution' stamp: 'sps 1/7/2002 21:37'! doCommand ^self redoCommand ! ! !EditCommand methodsFor: 'command execution' stamp: 'sps 7/24/2003 17:04'! redoCommand | | "Debug dShow: ('rInterval: ', replacedTextInterval asString, '. rText: ', replacedText string, ' nInterval: ', newTextInterval asString, ' nText: ', newText string)." self textMorphEditor noUndoReplace: replacedTextInterval with: newText. "Debug dShow: ('lastSelInt: ', lastSelectionInterval asString)." ! ! !EditCommand methodsFor: 'command execution' stamp: 'sps 7/24/2003 17:04'! undoCommand "Debug dShow: ('new Interval: ', newTextInterval asString, '. rText: ', replacedText string)." self textMorphEditor noUndoReplace: newTextInterval with: replacedText. ! ! !EditCommand methodsFor: 'initialization' stamp: 'sps 7/24/2003 17:01'! textMorph: tm replacedText: rText replacedTextInterval: rInterval newText: nText newTextInterval: nInterval textMorph := tm. replacedText := rText. replacedTextInterval := rInterval. newText := nText. newTextInterval := nInterval. ! ! !EditCommand methodsFor: 'selection' stamp: 'sps 1/7/2002 19:54'! doSelectionInterval ^self redoSelectionInterval! ! !EditCommand methodsFor: 'selection' stamp: 'sps 7/24/2003 17:34'! redoSelectionInterval "Return an interval to be displayed as a subtle selection after undo, or nil" ^newTextInterval ! ! !EditCommand methodsFor: 'selection' stamp: 'sps 7/24/2003 17:36'! undoSelection "Return an interval to be displayed as a selection after undo, or nil" ^replacedTextInterval first to: (replacedTextInterval first + replacedText size - 1) ! ! !EditCommand methodsFor: 'selection' stamp: 'sps 7/24/2003 17:03'! undoSelectionInterval "Return an interval to be displayed as a selection after undo, or nil" | i | i := (replacedTextInterval first min: self textMorphStringSize). ^i to: i - 1 ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EditCommand class instanceVariableNames: ''! !EditCommand class methodsFor: 'instance creation' stamp: 'sps 7/24/2003 17:08'! textMorph: tm replacedText: replacedText replacedTextInterval: replacedTextInterval newText: newText newTextInterval: newTextInterval ^(self new) textMorph: tm replacedText: replacedText replacedTextInterval: replacedTextInterval newText: newText newTextInterval: newTextInterval; yourself ! ! ObjectWithDocumentation subclass: #ElementCategory instanceVariableNames: 'categoryName keysInOrder elementDictionary' classVariableNames: '' poolDictionaries: '' category: 'Tools-Changes'! !ElementCategory commentStamp: '' prior: 0! ElementCategory Contains a list of elements that affords keyed access but also has an inherent order. Add items to the category by sending it elementAt:put:. Obtain the elements in order by sending #elementsInOrder Obtain the value of an element at a given key by sending #elementAt:! !ElementCategory methodsFor: 'category name' stamp: 'sw 1/26/2001 22:45'! categoryName "Answer the formal name of the category" ^ categoryName! ! !ElementCategory methodsFor: 'category name' stamp: 'stephaneducasse 2/4/2006 20:39'! categoryName: aName "Set the category name" categoryName := aName! ! !ElementCategory methodsFor: 'copying' stamp: 'sw 12/1/2000 22:45'! copy "Answer a copy of the receiver" ^ super copy copyFrom: self! ! !ElementCategory methodsFor: 'copying' stamp: 'stephaneducasse 2/4/2006 20:39'! copyFrom: donor "Copy the receiver's contents from the donor" keysInOrder := donor keysInOrder. elementDictionary := donor copyOfElementDictionary! ! !ElementCategory methodsFor: 'copying' stamp: 'sw 12/1/2000 22:46'! copyOfElementDictionary "Answer a copy of the element dictionary" ^ elementDictionary copy! ! !ElementCategory methodsFor: 'elements' stamp: 'sw 12/1/2000 22:46'! elementAt: aKey "Answer the element at the given key" ^ elementDictionary at: aKey ifAbsent: [nil]! ! !ElementCategory methodsFor: 'elements' stamp: 'sw 1/26/2001 22:54'! elementAt: sym put: element "Add symbol at the end of my sorted list (unless it is already present), and put the element in the dictionary" (keysInOrder includes: sym) ifFalse: [keysInOrder add: sym]. ^ elementDictionary at: sym put: element! ! !ElementCategory methodsFor: 'elements' stamp: 'sw 9/12/2001 22:59'! elementSymbol "Answer the element symbol for the receiver. Here, the categoryName dominates" ^ categoryName! ! !ElementCategory methodsFor: 'elements' stamp: 'sw 12/1/2000 22:47'! elementsInOrder "Answer the elements in order" ^ keysInOrder collect: [:aKey | elementDictionary at: aKey]! ! !ElementCategory methodsFor: 'elements' stamp: 'sw 4/3/2001 11:06'! fasterElementAt: sym put: element "Add symbol at the end of my sorted list and put the element in the dictionary. This variant adds the key at the end of the keys list without checking whether it already exists." keysInOrder add: sym. ^ elementDictionary at: sym put: element! ! !ElementCategory methodsFor: 'elements' stamp: 'sw 4/11/2001 20:08'! removeElementAt: aKey "Remove the element at the given key" elementDictionary removeKey: aKey ifAbsent: [^ self]. keysInOrder remove: aKey ifAbsent: []! ! !ElementCategory methodsFor: 'initialization' stamp: 'sw 3/30/2001 00:12'! addCategoryItem: anItem "Add the item at the end, obtaining its key from itself (it must respond to #categoryName)" self elementAt: anItem categoryName put: anItem! ! !ElementCategory methodsFor: 'initialization' stamp: 'stephaneducasse 2/4/2006 20:39'! clear "Clear the receiber's keysInOrder and elementDictionary" keysInOrder := OrderedCollection new. elementDictionary := IdentityDictionary new! ! !ElementCategory methodsFor: 'initialization' stamp: 'sw 3/28/2001 19:47'! initialize "Initialize the receiver (automatically called when instances are created via 'new')" super initialize. self clear! ! !ElementCategory methodsFor: 'keys' stamp: 'sw 12/11/2000 15:36'! includesKey: aKey "Answer whether the receiver's dictionary holds the given key" ^ elementDictionary includesKey: aKey! ! !ElementCategory methodsFor: 'keys' stamp: 'sw 12/1/2000 22:47'! keysInOrder "Answer the keys in their sorted order" ^ keysInOrder copy! ! !ElementCategory methodsFor: 'printing' stamp: 'sw 1/26/2001 22:47'! printOn: aStream "Append to the argument, aStream, a sequence of characters that identifies the receiver." super printOn: aStream. categoryName ifNotNil: [aStream nextPutAll: ' named ', categoryName asString]! ! !ElementCategory methodsFor: 'translation' stamp: 'dgd 12/4/2003 20:22'! translated "answer the receiver translated to the current language" ^ self class new categoryName: categoryName asString translated asSymbol! ! !ElementCategory methodsFor: 'private' stamp: 'sw 8/6/2004 10:34'! initWordingAndDocumentation "Initialize wording and documentation (helpMessage) for getters and setters" self wording: self categoryName! ! Object subclass: #EllipseMidpointTracer instanceVariableNames: 'rect x y a b aSquared bSquared d1 d2 inFirstRegion' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'! !EllipseMidpointTracer methodsFor: 'computing' stamp: 'ar 6/28/1999 15:35'! stepInY "Step to the next y value" inFirstRegion ifTrue:[ "In the upper region we must step until we reach the next y value" [(aSquared * (y-0.5)) > (bSquared * (x+1))] whileTrue:[ d1 < 0.0 ifTrue:[d1 := d1 + (bSquared * (2*x+3)). x := x + 1] ifFalse:[d1 := d1 + (bSquared * (2*x+3)) + (aSquared * (-2*y+2)). y := y - 1. ^x := x + 1]]. "Stepping into second region" d2 := (bSquared * (x + 0.5) squared) + (aSquared * (y-1) squared) - (aSquared * bSquared). inFirstRegion := false. ]. "In the lower region each step is a y-step" d2 < 0.0 ifTrue:[d2 := d2 + (bSquared * (2*x+2)) + (aSquared * (-2*y+3)). x := x + 1] ifFalse:[d2 := d2 + (aSquared * (-2*y+3))]. y := y - 1. ^x! ! !EllipseMidpointTracer methodsFor: 'initialize' stamp: 'ar 6/28/1999 15:33'! on: aRectangle rect := aRectangle. a := rect width // 2. b := rect height // 2. x := 0. y := b. aSquared := a * a. bSquared := b * b. d1 := bSquared - (aSquared * b) + (0.25 * aSquared). d2 := nil. inFirstRegion := true.! ! BorderedMorph subclass: #EllipseMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Basic'! !EllipseMorph commentStamp: 'kfr 10/27/2003 10:32' prior: 0! A round BorderedMorph. Supports borderWidth and borderColor. Only simple borderStyle is implemented. EllipseMorph new borderWidth:10; borderColor: Color green; openInWorld. EllipseMorph new borderStyle:(SimpleBorder width: 5 color: Color blue); openInWorld.! !EllipseMorph methodsFor: 'accessing' stamp: 'sw 11/24/1999 14:59'! couldHaveRoundedCorners ^ false! ! !EllipseMorph methodsFor: 'accessing' stamp: 'di 6/20/97 11:29'! doesBevels ^ false! ! !EllipseMorph methodsFor: 'drawing' stamp: 'di 6/24/1998 14:27'! areasRemainingToFill: aRectangle "Could be improved by quick check of inner rectangle" ^ Array with: aRectangle! ! !EllipseMorph methodsFor: 'drawing' stamp: 'di 5/25/2001 01:37'! drawOn: aCanvas aCanvas isShadowDrawing ifTrue: [^ aCanvas fillOval: bounds fillStyle: self fillStyle borderWidth: 0 borderColor: nil]. aCanvas fillOval: bounds fillStyle: self fillStyle borderWidth: borderWidth borderColor: borderColor. ! ! !EllipseMorph methodsFor: 'geometry' stamp: 'nk 8/31/2004 14:25'! bottomLeftCorner ^self intersectionWithLineSegmentFromCenterTo: bounds bottomLeft ! ! !EllipseMorph methodsFor: 'geometry' stamp: 'nk 8/31/2004 14:23'! bottomRightCorner ^self intersectionWithLineSegmentFromCenterTo: bounds bottomRight ! ! !EllipseMorph methodsFor: 'geometry' stamp: 'nk 2/15/2001 16:08'! closestPointTo: aPoint ^self intersectionWithLineSegmentFromCenterTo: aPoint! ! !EllipseMorph methodsFor: 'geometry' stamp: 'nk 2/13/2001 18:16'! intersectionWithLineSegmentFromCenterTo: aPoint | dx aSquared bSquared m mSquared xSquared x y dy | (self containsPoint: aPoint) ifTrue: [ ^aPoint ]. dx := aPoint x - self center x. dy := aPoint y - self center y. dx = 0 ifTrue: [ ^self bounds pointNearestTo: aPoint ]. m := dy / dx. mSquared := m squared. aSquared := (self bounds width / 2) squared. bSquared := (self bounds height / 2) squared. xSquared := 1 / ((1 / aSquared) + (mSquared / bSquared)). x := xSquared sqrt. dx < 0 ifTrue: [ x := x negated ]. y := m * x. ^ self center + (x @ y) asIntegerPoint. ! ! !EllipseMorph methodsFor: 'geometry' stamp: 'nk 8/31/2004 14:23'! topLeftCorner ^self intersectionWithLineSegmentFromCenterTo: bounds topLeft ! ! !EllipseMorph methodsFor: 'geometry' stamp: 'nk 8/31/2004 14:26'! topRightCorner ^self intersectionWithLineSegmentFromCenterTo: bounds topRight ! ! !EllipseMorph methodsFor: 'geometry testing' stamp: 'di 11/14/97 13:50'! containsPoint: aPoint | radius other delta xOverY | (bounds containsPoint: aPoint) ifFalse: [^ false]. "quick elimination" (bounds width = 1 or: [bounds height = 1]) ifTrue: [^ true]. "Degenerate case -- code below fails by a bit" radius := bounds height asFloat / 2. other := bounds width asFloat / 2. delta := aPoint - bounds topLeft - (other@radius). xOverY := bounds width asFloat / bounds height asFloat. ^ (delta x asFloat / xOverY) squared + delta y squared <= radius squared! ! !EllipseMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:37'! defaultBorderWidth "answer the default border width for the receiver" ^ 1! ! !EllipseMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:26'! defaultColor "answer the default color/fill style for the receiver" ^ Color yellow! ! !EllipseMorph methodsFor: 'rounding' stamp: 'ka 12/4/2005 00:52'! cornerStyle: aSymbol "Set the receiver's corner style. But, in this case, do *not*" self removeProperty: #cornerStyle. self changed! ! !EllipseMorph methodsFor: 'testing' stamp: 'ar 8/25/2001 19:08'! canDrawBorder: aBorderStyle ^aBorderStyle style == #simple! ! !EllipseMorph methodsFor: 'visual properties' stamp: 'ar 6/25/1999 11:14'! canHaveFillStyles "Return true if the receiver can have general fill styles; not just colors. This method is for gradually converting old morphs." ^true! ! MenuMorph subclass: #EmbeddedMenuMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !EmbeddedMenuMorph commentStamp: 'gvc 5/18/2007 13:18' prior: 0! Menu designed to be embedded in another morph rather than popped up directly.! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 3/17/2008 17:04'! allEnabledSiblingItems "Answer the receiver's submorphs followed by the (wrapping) owner's submorph items. Answer only enabled items." ^self allSiblingItems select: [:item | item isEnabled]! ! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 3/20/2008 21:18'! allSiblingItems "Answer the receiver's submorphs followed by the (wrapping) owner's submorph items. Nasty." |menus str index| str := (Array new: 40) writeStream. menus := self owner submorphs select: [:m | m isKindOf: self class]. menus := (menus copyFrom: (index := menus indexOf: self) to: menus size), (menus copyFrom: 1 to: index - 1). menus do: [:menu | str nextPutAll: menu items]. ^str contents! ! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/16/2007 14:17'! drawOn: aCanvas "Draw the receiver on the canvas." self perform: #drawOn: withArguments: {aCanvas} inSuperclass: Morph. self hasKeyboardFocus ifTrue: [self drawKeyboardFocusOn: aCanvas]! ! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/16/2007 14:22'! handlesKeyboard: evt "Answer whether the receiver handles the keystroke represented by the event" ^true! ! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/21/2007 14:37'! keyStroke: evt "Handle tabbing and arrows and cr/space." |char selectable| (self navigationKey: evt) ifTrue: [^self]. char := evt keyCharacter. char = Character space ifTrue: [selectedItem ifNotNil: [selectedItem hasSubMenu ifTrue: [evt hand newMouseFocus: selectedItem subMenu. ^selectedItem subMenu takeKeyboardFocus] ifFalse: [^selectedItem invokeWithEvent: evt]]. (selectable := self items) size = 1 ifTrue: [^selectable first invokeWithEvent: evt]. ^self]. (char = Character arrowLeft or: [char = Character arrowRight]) ifTrue: [ (selectedItem notNil and: [selectedItem hasSubMenu]) ifTrue: [ evt hand newMouseFocus: selectedItem subMenu. selectedItem subMenu moveSelectionDown: 1 event: evt. ^evt hand newKeyboardFocus: selectedItem subMenu]]. char = Character arrowUp ifTrue: [^self moveSelectionDown: -1 event: evt]. "up arrow key" char = Character arrowDown ifTrue: [^self moveSelectionDown: 1 event: evt]. "down arrow key" char = Character pageUp ifTrue: [^self moveSelectionDown: -5 event: evt]. "page up key" char = Character pageDown ifTrue: [^self moveSelectionDown: 5 event: evt]. "page down key" ! ! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 2/6/2008 10:31'! keyboardFocusChange: aBoolean "Nasty hack for scrolling upon keyboard focus." super keyboardFocusChange: aBoolean. aBoolean ifTrue: [(self ownerThatIsA: GeneralScrollPane) ifNotNilDo: [:sp | sp scrollToShow: self bounds]] ifFalse: [self selectItem: nil event: nil]! ! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 3/17/2008 17:17'! moveSelectionDown: anInteger event: anEvent "Move the selection down or up (negative number) by (at least) the specified amount. If the item is not enabled, scan one at a time in that direction. If we move off the top/bottom then switch focus to any sibling menu and start scanning at the relevant end." |index allEnabledSiblingItems m| allEnabledSiblingItems := self allEnabledSiblingItems. index := (allEnabledSiblingItems indexOf: selectedItem ifAbsent: [0 + (anInteger negative ifTrue: [1] ifFalse: [0])]) + anInteger. allEnabledSiblingItems do: "Ensure finite" [:unused | m := allEnabledSiblingItems atWrap: index. ((m isKindOf: MenuItemMorph) and: [m isEnabled]) ifTrue: [m owner = self owner ifFalse: [ anEvent hand newKeyboardFocus: m owner]. ^m owner selectItem: m event: anEvent]. "Keep looking for an enabled item" index := index + anInteger sign]. ^self selectItem: nil event: anEvent! ! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/6/2008 14:56'! selectItem: aMenuItem event: anEvent "Deselect any sibling menus." |menus| menus := self owner submorphs select: [:m | (m isKindOf: self class) and: [m ~~ self]]. menus do: [:menu | menu perform: #selectItem:event: withArguments: {nil. anEvent} inSuperclass: self class superclass]. ^super selectItem: aMenuItem event: anEvent! ! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/12/2008 13:28'! selectLastPrefix: aString "Answer the last subitem that has text that matches the given prefix. Answer nil if none. Disable non-matching items and enable matching items." |firstMatch match| self items reverseDo: [:item | match := aString isEmpty or: [item contents asString asLowercase beginsWith: aString]. item isEnabled: match. (match and: [firstMatch isNil]) ifTrue: [firstMatch := item]]. ^firstMatch! ! !EmbeddedMenuMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/12/2008 13:28'! selectPrefix: aString "Answer the first subitem that has text that matches the given prefix. Answer nil if none. Disable non-matching items and enable matching items." |firstMatch match| self items do: [:item | match := aString isEmpty or: [item contents asString asLowercase beginsWith: aString]. item isEnabled: match. (match and: [firstMatch isNil]) ifTrue: [firstMatch := item]]. ^firstMatch! ! StringMorph subclass: #EmbossedStringMorph instanceVariableNames: 'style trackPaneColor' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !EmbossedStringMorph commentStamp: 'gvc 5/18/2007 13:15' prior: 0! A label that underdraws to the top-left and/or bottom-right with a lighter and/or darker colour to the receiver.! !EmbossedStringMorph methodsFor: 'accessing' stamp: 'gvc 4/27/2006 12:09'! style "Answer the value of style" ^ style! ! !EmbossedStringMorph methodsFor: 'accessing' stamp: 'gvc 5/10/2006 15:26'! style: anObject "Set the value of style" style := anObject. self changed! ! !EmbossedStringMorph methodsFor: 'accessing' stamp: 'gvc 8/9/2007 11:52'! trackPaneColor "Answer the value of trackPaneColor" ^ trackPaneColor! ! !EmbossedStringMorph methodsFor: 'accessing' stamp: 'gvc 8/9/2007 11:52'! trackPaneColor: anObject "Set the value of trackPaneColor" trackPaneColor := anObject! ! !EmbossedStringMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/9/2007 11:53'! adoptPaneColor: paneColor "Set the color." (paneColor notNil and: [self trackPaneColor]) ifTrue: [self color: paneColor]. super adoptPaneColor: paneColor! ! !EmbossedStringMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/9/2007 17:03'! drawOn: aCanvas "Draw the hi/lowlights too." |box| self style == #plain ifTrue: [^super drawOn: aCanvas]. box := self bounds. (self style == #inset or: [self style == #insetNoHighlight]) ifTrue: [self style == #insetNoHighlight ifFalse: [aCanvas drawString: self contents in: (box translateBy: 1) font: self fontToUse color: self color veryMuchLighter]. aCanvas drawString: self contents in: (box translateBy: -1) font: self fontToUse color: self color muchDarker; drawString: self contents in: box font: self fontToUse color: self color] ifFalse: [self style == #raisedNoHighlight ifFalse: [aCanvas drawString: self contents in: (box translateBy: -1) font: self fontToUse color: self color veryMuchLighter]. aCanvas drawString: self contents in: (box translateBy: 1) font: self fontToUse color: self color muchDarker; drawString: self contents in: box font: self fontToUse color: self color]! ! !EmbossedStringMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/9/2007 11:55'! initWithContents: aString font: aFont emphasis: emphasisCode "Grrr, why do they do basicNew?" super initWithContents: aString font: aFont emphasis: emphasisCode. self style: #inset; trackPaneColor: true.! ! !EmbossedStringMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/9/2007 11:52'! initialize "Initialize the receiver." super initialize. self style: #inset; trackPaneColor: true! ! !EmbossedStringMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/18/2007 13:16'! measureContents "Measure the contents for fitting. Add 2@2 for hi/lowlights." ^super measureContents + 2! ! !EmbossedStringMorph methodsFor: 'as yet unclassified' stamp: 'gvc 8/9/2007 11:35'! styleSymbols "Answer the valid styles." ^#(plain inset insetNoHighlight raised raisedNoHighlight)! ! Object subclass: #EncodedCharSet instanceVariableNames: '' classVariableNames: 'EncodedCharSets' poolDictionaries: '' category: 'Multilingual-Encodings'! !EncodedCharSet commentStamp: 'yo 10/19/2004 19:08' prior: 0! An abstract superclasss of the classes that represent encoded character sets. In the old implementation, the charsets had more important role. However, in the current implementation, the subclasses are used only for keeping the backward compatibility. The other confusion comes from the name of "Latin1" class. It used to mean the Latin-1 (ISO-8859-1) character set, but now it primarily means that the "Western European languages that are covered by the characters in Latin-1 character set. ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EncodedCharSet class instanceVariableNames: 'compoundTextSequence'! !EncodedCharSet class methodsFor: 'accessing - displaying' stamp: 'yo 12/18/2002 12:34'! isBreakableAt: index in: text self subclassResponsibility. ! ! !EncodedCharSet class methodsFor: 'accessing - displaying' stamp: 'yo 9/4/2002 22:51'! printingDirection self subclassResponsibility. ! ! !EncodedCharSet class methodsFor: 'character classification' stamp: 'yo 8/5/2003 16:55'! canBeGlobalVarInitial: char | leadingChar | leadingChar := char leadingChar. leadingChar = 0 ifTrue: [^ self isUppercase: char]. ^ self isLetter: char. ! ! !EncodedCharSet class methodsFor: 'character classification' stamp: 'yo 8/5/2003 17:18'! canBeNonGlobalVarInitial: char | leadingChar | leadingChar := char leadingChar. leadingChar = 0 ifTrue: [^ self isLowercase: char]. ^ self isLetter: char. ! ! !EncodedCharSet class methodsFor: 'character classification' stamp: 'yo 8/5/2003 16:44'! isDigit: char "Answer whether the receiver is a digit." | value | value := char asciiValue. ^ value >= 48 and: [value <= 57]. ! ! !EncodedCharSet class methodsFor: 'character classification' stamp: 'yo 8/5/2003 16:40'! isLetter: char "Answer whether the receiver is a letter." | value | value := char asciiValue. ^ (8r141 <= value and: [value <= 8r172]) or: [8r101 <= value and: [value <= 8r132]]. ! ! !EncodedCharSet class methodsFor: 'character classification' stamp: 'yo 8/5/2003 16:40'! isLowercase: char "Answer whether the receiver is a lowercase letter. (The old implementation answered whether the receiver is not an uppercase letter.)" | value | value := char asciiValue. ^ 8r141 <= value and: [value <= 8r172]. ! ! !EncodedCharSet class methodsFor: 'character classification' stamp: 'yo 8/5/2003 16:44'! isUppercase: char "Answer whether the receiver is an uppercase letter. (The old implementation answered whether the receiver is not a lowercase letter.)" | value | value := char asciiValue. ^ 8r101 <= value and: [value <= 8r132]. ! ! !EncodedCharSet class methodsFor: 'class methods' stamp: 'tak 11/5/2005 18:14'! charFromUnicode: unicode | table index | unicode < 128 ifTrue: [^ Character value: unicode]. table := self ucsTable. index := table indexOf: unicode. index = 0 ifTrue: [ ^ nil. ]. ^ Character leadingChar: self leadingChar code: index - 1. ! ! !EncodedCharSet class methodsFor: 'class methods' stamp: 'yo 9/4/2002 22:57'! charsetAt: encoding ^ EncodedCharSets at: encoding + 1 ifAbsent: [EncodedCharSets at: 1]. ! ! !EncodedCharSet class methodsFor: 'class methods' stamp: 'yo 12/1/2003 19:29'! digitValue: char "Answer 0-9 if the receiver is $0-$9, 10-35 if it is $A-$Z, and < 0 otherwise. This is used to parse literal numbers of radix 2-36." | value | value := char charCode. value <= $9 asciiValue ifTrue: [^value - $0 asciiValue]. value >= $A asciiValue ifTrue: [value <= $Z asciiValue ifTrue: [^value - $A asciiValue + 10]]. ^ -1 ! ! !EncodedCharSet class methodsFor: 'class methods' stamp: 'yo 6/12/2008 14:38'! initialize " self initialize " self allSubclassesDo: [:each | each initialize]. EncodedCharSets := Array new: 256. EncodedCharSets at: 0+1 put: Latin1Environment. EncodedCharSets at: 1+1 put: JISX0208. EncodedCharSets at: 2+1 put: GB2312. EncodedCharSets at: 3+1 put: KSX1001. EncodedCharSets at: 4+1 put: JISX0208. EncodedCharSets at: 5+1 put: JapaneseEnvironment. EncodedCharSets at: 6+1 put: SimplifiedChineseEnvironment. EncodedCharSets at: 7+1 put: KoreanEnvironment. EncodedCharSets at: 8+1 put: GB2312. "EncodedCharSets at: 9+1 put: UnicodeTraditionalChinese." "EncodedCharSets at: 10+1 put: UnicodeVietnamese." EncodedCharSets at: 12+1 put: KSX1001. EncodedCharSets at: 13+1 put: GreekEnvironment. EncodedCharSets at: 14+1 put: Latin2Environment. EncodedCharSets at: 15+1 put: RussianEnvironment. EncodedCharSets at: 15+1 put: NepaleseEnvironment. EncodedCharSets at: 256 put: Unicode. ! ! !EncodedCharSet class methodsFor: 'class methods' stamp: 'yo 12/2/2004 16:13'! isCharset ^ true. ! ! !EncodedCharSet class methodsFor: 'class methods' stamp: 'yo 9/2/2002 16:32'! leadingChar self subclassResponsibility. ! ! !EncodedCharSet class methodsFor: 'class methods' stamp: 'yo 11/4/2002 14:43'! nextPutValue: ascii toStream: aStream withShiftSequenceIfNeededForTextConverterState: state self subclassResponsibility. ! ! !EncodedCharSet class methodsFor: 'class methods' stamp: 'yo 10/14/2003 10:19'! ucsTable ^ UCSTable latin1Table. ! ! ParseNode subclass: #Encoder instanceVariableNames: 'scopeTable nTemps supered requestor class selector literalStream selectorSet litIndSet litSet sourceRanges globalSourceRanges addedSelectorAndMethodClassLiterals' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Kernel'! !Encoder commentStamp: '' prior: 0! I encode names and literals into tree nodes with byte codes for the compiler. Byte codes for literals are not assigned until the tree-sizing pass of the compiler, because only then is it known which literals are actually needed. I also keep track of sourceCode ranges during parsing and code generation so I can provide an inverse map for the debugger.! !Encoder methodsFor: 'accessing' stamp: 'eem 5/29/2008 09:36'! methodNodeClass ^MethodNode! ! !Encoder methodsFor: 'accessing' stamp: 'ar 9/9/2006 12:06'! selector ^selector! ! !Encoder methodsFor: 'accessing' stamp: 'ar 9/9/2006 12:06'! selector: aSymbol selector := aSymbol! ! !Encoder methodsFor: 'encoding'! cantStoreInto: varName ^StdVariables includesKey: varName! ! !Encoder methodsFor: 'encoding' stamp: 'eem 9/5/2009 20:04'! doItInContextName ^'ThisContext'! ! !Encoder methodsFor: 'encoding'! encodeLiteral: object ^self name: object key: (class literalScannedAs: object notifying: self) class: LiteralNode type: LdLitType set: litSet! ! !Encoder methodsFor: 'encoding'! encodeSelector: selector ^self name: selector key: selector class: SelectorNode type: SendType set: selectorSet! ! !Encoder methodsFor: 'encoding' stamp: 'di 12/4/1999 20:09'! encodeVariable: name ^ self encodeVariable: name sourceRange: nil ifUnknown: [ self undeclared: name ]! ! !Encoder methodsFor: 'encoding' stamp: 'ls 1/19/2001 12:59'! encodeVariable: name ifUnknown: action ^self encodeVariable: name sourceRange: nil ifUnknown: action! ! !Encoder methodsFor: 'encoding' stamp: 'eem 4/30/2009 17:03'! encodeVariable: name sourceRange: range ifUnknown: action | varNode | varNode := scopeTable at: name ifAbsent: [(self lookupInPools: name ifFound: [:assoc | varNode := self global: assoc name: name]) ifTrue: [varNode] ifFalse: [^action value]]. range ifNotNil: [ name first canBeGlobalVarInitial ifTrue: [globalSourceRanges addLast: { name. range. false }]. ]. (varNode isTemp and: [varNode scope < 0]) ifTrue: [ OutOfScopeNotification signal ifFalse: [ ^self notify: 'out of scope']. ]. ^ varNode! ! !Encoder methodsFor: 'encoding' stamp: 'eem 5/27/2009 09:25'! environment "Answer the environment of the current compilation context, be it in a class or global (e.g. a workspace)" ^class == nil ifTrue: [Smalltalk] ifFalse: [class environment]! ! !Encoder methodsFor: 'encoding'! litIndex: literal | p | p := literalStream position. p = 256 ifTrue: [self notify: 'More than 256 literals referenced. You must split or otherwise simplify this method. The 257th literal is: ', literal printString. ^nil]. "Would like to show where it is in the source code, but that info is hard to get." literalStream nextPut: literal. ^ p! ! !Encoder methodsFor: 'encoding' stamp: 'eem 5/16/2008 18:30'! sharableLitIndex: literal "Special access prevents multiple entries for post-allocated super send special selectors" 1 to: literalStream position do: [:index| (litSet literalEquality: literal and: (literalStream originalContents at: index)) ifTrue: [^index - 1]]. ^self litIndex: literal! ! !Encoder methodsFor: 'encoding' stamp: 'eem 7/27/2008 17:41'! undeclared: name | sym | requestor interactive ifTrue: [requestor requestor == #error: ifTrue: [requestor error: 'Undeclared']. ^self notify: 'Undeclared']. "Allow knowlegeable clients to squash the undeclared warning if they want (e.g. Diffing pretty printers that are simply formatting text). As this breaks compilation it should only be used by clients that want to discard the result of the compilation. To squash the warning use e.g. [Compiler format: code in: class notifying: nil decorated: false] on: UndeclaredVariableWarning do: [:ex| ex resume: false]" sym := name asSymbol. ^(UndeclaredVariableWarning new name: name selector: selector class: class) signal ifTrue: [Undeclared at: sym put: nil. self global: (Undeclared associationAt: sym) name: sym] ifFalse: [self global: (Association key: sym) name: sym]! ! !Encoder methodsFor: 'error handling'! notify: string "Put a separate notifier on top of the requestor's window" | req | requestor == nil ifFalse: [req := requestor. self release. req notify: string]. ^false! ! !Encoder methodsFor: 'error handling'! notify: string at: location | req | requestor == nil ifFalse: [req := requestor. self release. req notify: string at: location]. ^false! ! !Encoder methodsFor: 'error handling'! requestor: req "Often the requestor is a BrowserCodeController" requestor := req! ! !Encoder methodsFor: 'initialize-release' stamp: 'PeterHugossonMiller 9/2/2009 16:18'! fillDict: dict with: nodeClass mapping: keys to: codeArray | codeStream | codeStream := codeArray readStream. keys do: [:key | dict at: key put: (nodeClass new name: key key: key code: codeStream next)]! ! !Encoder methodsFor: 'initialize-release' stamp: 'eem 6/24/2008 14:24'! init: aClass context: aContext notifying: req requestor := req. class := aClass. nTemps := 0. supered := false. self initScopeAndLiteralTables. class variablesAndOffsetsDo: [:variable "" :offset "" | offset isNil ifTrue: [scopeTable at: variable name put: (FieldNode new fieldDefinition: variable)] ifFalse: [scopeTable at: variable put: (offset >= 0 ifTrue: [InstanceVariableNode new name: variable index: offset] ifFalse: [MaybeContextInstanceVariableNode new name: variable index: offset negated])]]. aContext ~~ nil ifTrue: [| homeNode | homeNode := self bindTemp: self doItInContextName. "0th temp = aContext passed as arg" aContext tempNames withIndexDo: [:variable :index| scopeTable at: variable put: (MessageAsTempNode new receiver: homeNode selector: #namedTempAt: arguments: (Array with: (self encodeLiteral: index)) precedence: 3 from: self)]]. sourceRanges := Dictionary new: 32. globalSourceRanges := OrderedCollection new: 32! ! !Encoder methodsFor: 'initialize-release' stamp: 'PeterHugossonMiller 9/3/2009 01:24'! initScopeAndLiteralTables scopeTable := StdVariables copy. litSet := StdLiterals copy. "comments can be left hanging on nodes from previous compilations. probably better than this hack fix is to create the nodes afresh on each compilation." scopeTable do: [:varNode| varNode comment: nil]. litSet do: [:varNode| varNode comment: nil]. selectorSet := StdSelectors copy. litIndSet := Dictionary new: 16. literalStream := (Array new: 32) writeStream. addedSelectorAndMethodClassLiterals := false! ! !Encoder methodsFor: 'initialize-release' stamp: 'PeterHugossonMiller 9/2/2009 16:17'! nTemps: n literals: lits class: cl "Decompile." supered := false. class := cl. nTemps := n. (literalStream := lits readStream) position: lits size. sourceRanges := Dictionary new: 32. globalSourceRanges := OrderedCollection new: 32. ! ! !Encoder methodsFor: 'initialize-release'! noteSuper supered := true! ! !Encoder methodsFor: 'initialize-release'! release requestor := nil! ! !Encoder methodsFor: 'initialize-release' stamp: 'PeterHugossonMiller 9/2/2009 16:17'! temps: tempVars literals: lits class: cl "Decompile." supered := false. class := cl. nTemps := tempVars size. tempVars do: [:node | scopeTable at: node name put: node]. (literalStream := lits readStream) position: lits size. sourceRanges := Dictionary new: 32. globalSourceRanges := OrderedCollection new: 32. ! ! !Encoder methodsFor: 'results' stamp: 'bgf 3/12/2009 17:42'! allLiterals ((literalStream isKindOf: WriteStream) and: [ (addedSelectorAndMethodClassLiterals ifNil: [ false ]) not]) ifTrue: [addedSelectorAndMethodClassLiterals := true. self litIndex: nil. self litIndex: self associationForClass]. ^literalStream contents "The funky ifNil: [false], even though the init method initializes addedSAMCL, is simply so that Monticello can load and compile this update without killing the encoder that is compiling that update itself..."! ! !Encoder methodsFor: 'results' stamp: 'eem 5/27/2009 09:25'! associationForClass | assoc | assoc := self environment associationAt: class name ifAbsent: [nil]. ^assoc value == class ifTrue: [assoc] ifFalse: [Association new value: class]! ! !Encoder methodsFor: 'results'! literals "Should only be used for decompiling primitives" ^ literalStream contents! ! !Encoder methodsFor: 'results' stamp: 'di 10/12/1999 16:12'! tempNames ^ self tempNodes collect: [:node | (node isMemberOf: MessageAsTempNode) ifTrue: [scopeTable keyAtValue: node] ifFalse: [node key]]! ! !Encoder methodsFor: 'results' stamp: 'eem 5/27/2008 12:07'! tempNodes | tempNodes | tempNodes := SortedCollection sortBlock: [:n1 :n2 | n1 code <= n2 code]. scopeTable associationsDo: [:assn | assn value isArray ifTrue: [assn value do: [:temp| tempNodes add: temp]] ifFalse: [assn value isTemp ifTrue: [tempNodes add: assn value]]]. ^tempNodes! ! !Encoder methodsFor: 'results' stamp: 'eem 9/8/2008 18:27'! tempsAndBlockArgs | tempNodes | tempNodes := OrderedCollection new. scopeTable associationsDo: [:assn | | var | var := assn value. (var isTemp and: [var isMethodArg not and: [var scope = 0 or: [var scope = -1]]]) ifTrue: [tempNodes add: var]]. ^tempNodes! ! !Encoder methodsFor: 'results' stamp: 'eem 6/24/2008 14:24'! unusedTempNames | unused | unused := OrderedCollection new. scopeTable associationsDo: [:assn | | name | (assn value isUnusedTemp) ifTrue: [name := assn value key. name ~= self doItInContextName ifTrue: [unused add: name]]]. ^ unused! ! !Encoder methodsFor: 'source mapping' stamp: 'di 12/4/1999 22:27'! globalSourceRanges ^ globalSourceRanges! ! !Encoder methodsFor: 'source mapping'! noteSourceRange: range forNode: node sourceRanges at: node put: range! ! !Encoder methodsFor: 'source mapping' stamp: 'RAA 8/21/1999 06:52'! rawSourceRanges ^ sourceRanges ! ! !Encoder methodsFor: 'source mapping'! sourceMap "Answer with a sorted set of associations (pc range)." ^ (sourceRanges keys collect: [:key | Association key: key pc value: (sourceRanges at: key)]) asSortedCollection! ! !Encoder methodsFor: 'source mapping' stamp: 'ar 11/19/2002 14:41'! sourceRangeFor: node ^sourceRanges at: node! ! !Encoder methodsFor: 'temps' stamp: 'ar 9/9/2006 12:05'! autoBind: name "Declare a block argument as a temp if not already declared." | node | node := scopeTable at: name ifAbsent: [(self lookupInPools: name ifFound: [:assoc | assoc]) ifTrue: [self warnAboutShadowed: name]. ^ (self reallyBind: name) nowHasDef nowHasRef scope: 1]. node isTemp ifTrue: [node scope >= 0 ifTrue: [^ self notify: 'Name already used in this method']. node nowHasDef nowHasRef scope: 1] ifFalse: [^ self notify: 'Name already used in this class']. ^node! ! !Encoder methodsFor: 'temps' stamp: 'di 10/12/1999 16:53'! bindAndJuggle: name | node nodes first thisCode | node := self reallyBind: name. "Declared temps must precede block temps for decompiler and debugger to work right" nodes := self tempNodes. (first := nodes findFirst: [:n | n scope > 0]) > 0 ifTrue: [node == nodes last ifFalse: [self error: 'logic error']. thisCode := (nodes at: first) code. first to: nodes size - 1 do: [:i | (nodes at: i) key: (nodes at: i) key code: (nodes at: i+1) code]. nodes last key: nodes last key code: thisCode]. ^ node! ! !Encoder methodsFor: 'temps' stamp: 'jm 9/18/97 21:06'! bindArg: name "Declare an argument." | node | nTemps >= 15 ifTrue: [^self notify: 'Too many arguments']. node := self bindTemp: name. ^ node nowHasDef nowHasRef! ! !Encoder methodsFor: 'temps' stamp: 'eem 5/30/2008 12:05'! bindBlockArg: name within: aBlockNode "With standard Smalltalk-80 (BlueBook) blocks it used to be legal to use a method temp as a block argument. This shouldn't be the case with the current compiler, which checks for temp names already being used as block arguments. But it is easily fooled by local block temps in optimized blocks, e.g. false ifTrue: [| temp |] ifFalse:[[:temp|]] Rather than fix this we keep the semantics and fix it in the closure compiler." ^self autoBind: name! ! !Encoder methodsFor: 'temps' stamp: 'crl 2/26/1999 12:18'! bindBlockTemp: name "Declare a temporary block variable; complain if it's not a field or class variable." | node | node := scopeTable at: name ifAbsent: [^self reallyBind: name]. node isTemp ifTrue: [ node scope >= 0 ifTrue: [^ self notify: 'Name already used in this method']. node scope: 0] ifFalse: [^self notify: 'Name already used in this class']. ^node ! ! !Encoder methodsFor: 'temps' stamp: 'eem 5/30/2008 14:14'! bindBlockTemp: name within: aBlockNode "The BlockContext compiler (the Smalltalk-80 BlueBook compiler) does provide support for ANSI block syntax, but not for ANSI block semantics. Here all temps live at the same level, the method level. The approach taken to two block-local temps in different blocks is to merge them into a single temp. e.g. expr ifTrue: [|temp| self statementOne] ifFalse: [|temp| self statementTwo] is effectvely transformed into | temp | expr ifTrue: [self statementOne] ifFalse: [self statementTwo] and expr do: [:each| | temp | ...]. expr do: [:each| | temp | ...]. is also effectively transformed into | temp | expr do: [:each| ...]. expr do: [:each| ...]. The closure compiler treats the former similarly, but not the latter. The indirection through #bindBlockTemp:within: allows the closure encoder to do this." ^self bindBlockTemp: name! ! !Encoder methodsFor: 'temps' stamp: 'ar 9/9/2006 12:06'! bindTemp: name "Declare a temporary; error not if a field or class variable." scopeTable at: name ifPresent:[:node| "When non-interactive raise the error only if its a duplicate" (node isTemp) ifTrue:[^self notify:'Name is already defined'] ifFalse:[self warnAboutShadowed: name]]. ^self reallyBind: name! ! !Encoder methodsFor: 'temps' stamp: 'mir 1/17/2004 12:31'! bindTemp: name in: methodSelector "Declare a temporary; error not if a field or class variable." scopeTable at: name ifPresent:[:node| "When non-interactive raise the error only if its a duplicate" (node isTemp or:[requestor interactive]) ifTrue:[^self notify:'Name is already defined'] ifFalse:[Transcript show: '(', name, ' is shadowed in "' , class printString , '>>' , methodSelector printString , '")']]. ^self reallyBind: name! ! !Encoder methodsFor: 'temps' stamp: 'eem 12/1/2008 12:07'! fixTemp: name | node | node := scopeTable at: name ifAbsent: []. node class ~~ TempVariableNode ifTrue: [self error: 'can only fix a floating temp var']. node index: nTemps. nTemps := nTemps + 1. ^node! ! !Encoder methodsFor: 'temps' stamp: 'eem 7/13/2007 14:13'! floatTemp: node (node ~~ (scopeTable at: node name ifAbsent: []) or: [node class ~~ TempVariableNode or: [node code ~= (node code: nTemps - 1 type: LdTempType)]]) ifTrue: [self error: 'can only float the last allocated temp var']. nTemps := nTemps - 1! ! !Encoder methodsFor: 'temps'! maxTemp ^nTemps! ! !Encoder methodsFor: 'temps'! newTemp: name nTemps := nTemps + 1. ^ TempVariableNode new name: name index: nTemps - 1 type: LdTempType scope: 0! ! !Encoder methodsFor: 'visiting' stamp: 'eem 5/30/2008 09:44'! accept: aVisitor "I am not really a ParseNode. Only here to access constants defined in parseNode." self shouldNotImplement! ! !Encoder methodsFor: 'private'! classEncoding "This is a hack so that the parser may findout what class it was parsing for when it wants to create a syntax error view." ^ class! ! !Encoder methodsFor: 'private' stamp: 'ar 8/14/2001 23:12'! global: ref name: name ^self name: name key: ref class: LiteralVariableNode type: LdLitIndType set: litIndSet! ! !Encoder methodsFor: 'private' stamp: 'ar 3/26/2004 15:44'! interactive ^requestor interactive! ! !Encoder methodsFor: 'private' stamp: 'eem 9/10/2008 14:03'! lookupInPools: varName ifFound: assocBlock ^Symbol hasInterned: varName ifTrue: [:sym| (class bindingOf: sym) ifNil: [^false] ifNotNil: [:assoc| assocBlock value: assoc]]! ! !Encoder methodsFor: 'private' stamp: 'eem 6/11/2008 17:31'! name: name key: key class: leafNodeClass type: type set: dict ^dict at: key ifAbsent: [dict at: key put: (leafNodeClass new name: name key: key index: nil type: type)]! ! !Encoder methodsFor: 'private' stamp: 'ar 1/2/2002 14:53'! possibleNamesFor: proposedName | results | results := class possibleVariablesFor: proposedName continuedFrom: nil. ^ proposedName correctAgainst: nil continuedFrom: results. ! ! !Encoder methodsFor: 'private' stamp: 'yo 11/11/2002 10:23'! possibleVariablesFor: proposedVariable | results | results := proposedVariable correctAgainstDictionary: scopeTable continuedFrom: nil. proposedVariable first canBeGlobalVarInitial ifTrue: [ results := class possibleVariablesFor: proposedVariable continuedFrom: results ]. ^ proposedVariable correctAgainst: nil continuedFrom: results. ! ! !Encoder methodsFor: 'private'! reallyBind: name | node | node := self newTemp: name. scopeTable at: name put: node. ^node! ! !Encoder methodsFor: 'private' stamp: 'eem 6/19/2008 13:02'! warnAboutShadowed: name requestor addWarning: name,' is shadowed'. selector ifNotNil: [Transcript cr; show: class name,'>>', selector, '(', name,' is shadowed)']! ! BytecodeEncoder subclass: #EncoderForLongFormV3 instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Kernel'! !EncoderForLongFormV3 commentStamp: '' prior: 0! I am an alternate to EncoderForV3 that tries to use thje longest forms of bytecodes possible so as to avoid using as many bytecode as possible to allow for the unused portions of the bytecode set this makes available to be reassigned. I do not use the following ranges 0 through 111 0- 15 0000iiii Push Receiver Variable #iiii 16- 31 0001iiii Push Temporary Location #iiii 32- 63 001iiiii Push Literal Constant #iiiii 64- 95 010iiiii Push Literal Variable #iiiii 96-103 01100iii Pop and Store Receiver Variable #iii 104-111 01101iii Pop and Store Temporary Location #iii 138-159 138-143 Unused. 144-151 10010iii Jump iii + 1 (i.e., 1 through 8). 152-159 10011iii Pop and Jump 0n False iii +1 (i.e., 1 through 8). 176-255 176-191 1011iiii Send Arithmetic Message #iiii 192-207 1100iiii Send Special Message #iiii 208-223 1101iiii Send Literal Selector #iiii With No Arguments 224-239 1110iiii Send Literal Selector #iiii With 1 Argument 240-255 1111iiii Send Literal Selector #iiii With 2 Arguments = 112 + (160 - 138) + (256 - 176) = 214, or 84% of the bytecodes! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:52'! genBranchPopFalse: distance "See BlueBook page 596" distance < 0 ifTrue: [^self outOfRangeError: 'distance' index: distance range: 0 to: 1023]. distance < 1024 ifTrue: ["172-175 101011ii jjjjjjjj Pop and Jump On False ii *256+jjjjjjjj" stream nextPut: 172 + (distance bitShift: -8); nextPut: distance + 1024 \\ 256. ^self]. ^self outOfRangeError: 'distance' index: distance range: 0 to: 1023! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:53'! genBranchPopTrue: distance "See BlueBook page 596" distance < 0 ifTrue: [^self outOfRangeError: 'distance' index: distance range: 0 to: 1023]. distance < 1024 ifTrue: ["168-171 101010ii jjjjjjjj Pop and Jump On True ii *256+jjjjjjjj" stream nextPut: 168 + (distance bitShift: -8); nextPut: distance + 1024 \\ 256. ^self]. ^self outOfRangeError: 'distance' index: distance range: 0 to: 1023! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:12'! genDup "See BlueBook page 596" "136 10001000 Duplicate Stack Top" stream nextPut: 136! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:20'! genJump: distance "See BlueBook page 596" ^self genJumpLong: distance! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:53'! genJumpLong: distance "See BlueBook page 596" (distance >= -1024 and: [distance < 1024]) ifTrue: ["160-167 10100iii jjjjjjjj Jump(iii - 4) *256+jjjjjjjj" stream nextPut: 160 + (distance + 1024 bitShift: -8); nextPut: distance + 1024 \\ 256. ^self]. ^self outOfRangeError: 'distance' index: distance range: -1024 to: 1023! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:12'! genPop "See BlueBook page 596" "135 10000111 Pop Stack Top" stream nextPut: 135! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:46'! genPushInstVar: instVarIndex "See BlueBook page 596" (instVarIndex >= 0 and: [instVarIndex < 64]) ifTrue: ["128 10000000 jjkkkkkk Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk" stream nextPut: 128; nextPut: instVarIndex. ^self]. self genPushInstVarLong: instVarIndex! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:51'! genPushInstVarLong: instVarIndex "See BlueBook page 596" "See also MaybeContextInstanceVariableNode" (instVarIndex >= 0 and: [instVarIndex < 256]) ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 64; nextPut: instVarIndex. ^self]. ^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 255! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:54'! genPushLiteral: literalIndex "See BlueBook page 596" literalIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255]. literalIndex < 64 ifTrue: ["128 10000000 jjkkkkkk Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk" stream nextPut: 128; nextPut: 128 + literalIndex. ^self]. literalIndex < 256 ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 96; nextPut: literalIndex. ^self]. ^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:54'! genPushLiteralVar: literalIndex "See BlueBook page 596" literalIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255]. literalIndex < 64 ifTrue: ["128 10000000 jjkkkkkk Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk" stream nextPut: 128; nextPut: 192 + literalIndex. ^self]. literalIndex < 256 ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 128; nextPut: literalIndex. ^self]. ^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:12'! genPushReceiver "See BlueBook page 596" "112-119 01110iii Push (receiver, true, false, nil, -1, 0, 1, 2) [iii]" stream nextPut: 112! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:12'! genPushSpecialLiteral: aLiteral "112-119 01110iii Push (receiver, true, false, nil, -1, 0, 1, 2) [iii]" | index | index := #(true false nil -1 0 1 2) indexOf: aLiteral ifAbsent: 0. index = 0 ifTrue: [^self error: 'push special literal: ', aLiteral printString, ' is not one of true false nil -1 0 1 2']. stream nextPut: index + 112! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:54'! genPushTemp: tempIndex "See BlueBook page 596" tempIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63]. tempIndex < 64 ifTrue: ["128 10000000 jjkkkkkk Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk" stream nextPut: 128; nextPut: 64 + tempIndex. ^self]. ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:12'! genPushThisContext "See BlueBook page 596" "137 10001001 Push Active Context" stream nextPut: 137! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:12'! genReturnReceiver "See BlueBook page 596" "120-123 011110ii Return (receiver, true, false, nil) [ii] From Message" stream nextPut: 120! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:12'! genReturnSpecialLiteral: aLiteral "120-123 011110ii Return (receiver, true, false, nil) [ii] From Message" | index | index := #(true false nil) indexOf: aLiteral ifAbsent: 0. index = 0 ifTrue: [^self error: 'return special literal: ', aLiteral printString, ' is not one of true false nil']. stream nextPut: 120 + index! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:12'! genReturnTop "See BlueBook page 596" "124-125 0111110i Return Stack Top From (Message, Block) [i]" stream nextPut: 124! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 14:12'! genReturnTopToCaller "See BlueBook page 596" "124-125 0111110i Return Stack Top From (Message, Block) [i]" stream nextPut: 125! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:56'! genSend: selectorLiteralIndex numArgs: nArgs "See BlueBook page 596 (with exceptions for 132 & 134)" nArgs < 0 ifTrue: [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"]. selectorLiteralIndex < 0 ifTrue: ["No special selector sends in long form." ^self outOfRangeError: 'selector literal index' index: selectorLiteralIndex range: 0 to: 255]. (selectorLiteralIndex < 32 and: [nArgs < 8]) ifTrue: [" 131 10000011 jjjkkkkk Send Literal Selector #kkkkk With jjj Arguments" stream nextPut: 131; nextPut: ((nArgs bitShift: 5) + selectorLiteralIndex). ^self]. (selectorLiteralIndex < 64 and: [nArgs < 4]) ifTrue: ["In Squeak V3 134 10000110 jjjjjjjj kkkkkkkk Send Literal Selector #kkkkkkkk To Superclass With jjjjjjjj Arguments is replaced by 134 10000110 jjkkkkkk Send Literal Selector #kkkkkk With jj Arguments" stream nextPut: 134; nextPut: ((nArgs bitShift: 6) + selectorLiteralIndex). ^self]. (selectorLiteralIndex <= 255 and: [nArgs <= 31]) ifTrue: ["In Squeak V3 132 10000100 jjjjjjjj kkkkkkkk Send Literal Selector #kkkkkkkk With jjjjjjjj Arguments is replaced by 132 10000100 ooojjjjj kkkkkkkk ooo = 0 => Send Literal Selector #kkkkkkkk With jjjjj Arguments ooo = 1 => Send Literal Selector #kkkkkkkk To Superclass With jjjjj Arguments" stream nextPut: 132; nextPut: nArgs; nextPut: selectorLiteralIndex. ^self]. nArgs > 31 ifTrue: [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31]. selectorLiteralIndex > 255 ifTrue: [^self outOfRangeError: 'selector literal index' index: selectorLiteralIndex range: 0 to: 255]! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:55'! genSendSuper: selectorLiteralIndex numArgs: nArgs "See BlueBook page 596 (with exceptions for 132 & 134)" nArgs < 0 ifTrue: [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"]. selectorLiteralIndex < 0 ifTrue: [^self outOfRangeError: 'selector literal index' index: selectorLiteralIndex range: 0 to: 255]. (selectorLiteralIndex < 32 and: [nArgs < 8]) ifTrue: [" 133 10000011 jjjkkkkk Send Literal Selector #kkkkk To Superclass With jjj Arguments" stream nextPut: 133; nextPut: ((nArgs bitShift: 5) + selectorLiteralIndex). ^self]. (selectorLiteralIndex <= 255 and: [nArgs <= 31]) ifTrue: ["In Squeak V3 132 10000100 jjjjjjjj kkkkkkkk Send Literal Selector #kkkkkkkk With jjjjjjjj Arguments is replaced by 132 10000100 ooojjjjj kkkkkkkk ooo = 0 => Send Literal Selector #kkkkkkkk With jjjjj Arguments ooo = 1 => Send Literal Selector #kkkkkkkk To Superclass With jjjjj Arguments" stream nextPut: 132; nextPut: 32 + nArgs; nextPut: selectorLiteralIndex. ^self]. nArgs > 31 ifTrue: [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31]. selectorLiteralIndex > 255 ifTrue: [^self outOfRangeError: 'selector literal index' index: selectorLiteralIndex range: 0 to: 255]! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:48'! genStoreInstVar: instVarIndex "See BlueBook page 596" (instVarIndex >= 0 and: [instVarIndex < 64]) ifTrue: ["129 10000001 jjkkkkkk Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 129; nextPut: instVarIndex. ^self]. self genStoreInstVarLong: instVarIndex! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:51'! genStoreInstVarLong: instVarIndex "See BlueBook page 596" "See also MaybeContextInstanceVariableNode" (instVarIndex >= 0 and: [instVarIndex < 256]) ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 160; nextPut: instVarIndex. ^self]. ^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 255! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:57'! genStoreLiteralVar: literalIndex "See BlueBook page 596" literalIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255]. literalIndex < 64 ifTrue: ["129 10000001 jjkkkkkk Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 129; nextPut: 192 + literalIndex. ^self]. literalIndex <= 255 ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 224; nextPut: literalIndex. ^self]. ^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:50'! genStorePopInstVar: instVarIndex "See BlueBook page 596" (instVarIndex >= 0 and: [instVarIndex < 64]) ifTrue: ["130 10000010 jjkkkkkk Pop and Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 130; nextPut: instVarIndex. ^self]. self genStorePopInstVarLong: instVarIndex! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:51'! genStorePopInstVarLong: instVarIndex "See BlueBook page 596" "See also MaybeContextInstanceVariableNode" (instVarIndex >= 0 and: [instVarIndex < 256]) ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 192; nextPut: instVarIndex. ^self]. ^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 255! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:58'! genStorePopLiteralVar: literalIndex "See BlueBook page 596" literalIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255]. literalIndex < 64 ifTrue: ["130 10000010 jjkkkkkk Pop and Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 130; nextPut: 192 + literalIndex. ^self]. literalIndex <= 255 ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 224; nextPut: literalIndex. self genPop. ^self]. ^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:58'! genStorePopTemp: tempIndex "See BlueBook page 596" tempIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63]. tempIndex < 64 ifTrue: ["130 10000010 jjkkkkkk Pop and Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 130; nextPut: 64 + tempIndex. ^self]. ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63! ! !EncoderForLongFormV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:58'! genStoreTemp: tempIndex "See BlueBook page 596" tempIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63]. tempIndex < 64 ifTrue: ["129 10000001 jjkkkkkk Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 129; nextPut: 64 + tempIndex. ^self]. ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63! ! !EncoderForLongFormV3 methodsFor: 'initialize-release' stamp: 'eem 5/15/2008 14:11'! initScopeAndLiteralTables super initScopeAndLiteralTables. "Start with an empty selector set to avoid the special selectors." selectorSet := Dictionary new: 16! ! EncoderForLongFormV3 subclass: #EncoderForLongFormV3PlusClosures instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Kernel'! !EncoderForLongFormV3PlusClosures commentStamp: '' prior: 0! An encoder for the V3 bytecode set augmented with the following bytecodes that are part of the full closure implementation. 138 10001010 jkkkkkkk Push (Array new: kkkkkkk) (j = 0) or Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1) 140 10001100 kkkkkkkk jjjjjjjj Push Temp At kkkkkkkk In Temp Vector At: jjjjjjjj 141 10001101 kkkkkkkk jjjjjjjj Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj 142 10001110 kkkkkkkk jjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj 143 10001111 llllkkkk jjjjjjjj iiiiiiii Push Closure Num Copied llll Num Args kkkk BlockSize jjjjjjjjiiiiiiii This is an exact duplicate of EncoderForV3PlusClosures. Could be a trait (or in Newspeak, a Mixin). For now we impose upon you to synchronise any and all changes between these two classes.! !EncoderForLongFormV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:10'! genPushClosureCopyNumCopiedValues: numCopied numArgs: numArgs jumpSize: jumpSize "143 10001111 llllkkkk jjjjjjjj iiiiiiii Push Closure Num Copied llll Num Args kkkk BlockSize jjjjjjjjiiiiiiii" (jumpSize < 0 or: [jumpSize > 65535]) ifTrue: [^self outOfRangeError: 'block size' index: jumpSize range: 0 to: 65535]. (numCopied < 0 or: [numCopied > 15]) ifTrue: [^self outOfRangeError: 'num copied' index: numCopied range: 0 to: 15]. (numArgs < 0 or: [numArgs > 15]) ifTrue: [^self outOfRangeError: 'num args' index: numArgs range: 0 to: 15]. stream nextPut: 143; nextPut: numArgs + (numCopied bitShift: 4); nextPut: (jumpSize bitShift: -8); nextPut: (jumpSize bitAnd: 16rFF)! ! !EncoderForLongFormV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:06'! genPushConsArray: size (size < 0 or: [size > 127]) ifTrue: [^self outOfRangeError: 'numElements' index: size range: 0 to: 127]. "138 10001010 1kkkkkkk Pop kkkkkkk into: (Array new: kkkkkkk)" stream nextPut: 138; nextPut: size + 128! ! !EncoderForLongFormV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:05'! genPushNewArray: size (size < 0 or: [size > 127]) ifTrue: [^self outOfRangeError: 'size' index: size range: 0 to: 127]. "138 10001010 0kkkkkkk Push (Array new: kkkkkkk)" stream nextPut: 138; nextPut: size! ! !EncoderForLongFormV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 6/16/2008 09:45'! genPushRemoteTemp: tempIndex inVectorAt: tempVectorIndex (tempIndex >= 0 and: [tempIndex < 256 and: [tempVectorIndex >= 0 and: [tempVectorIndex < 256]]]) ifTrue: ["140 10001100 kkkkkkkk jjjjjjjj Push Temp At kkkkkkkk In Temp Vector At: jjjjjjjj" stream nextPut: 140; nextPut: tempIndex; nextPut: tempVectorIndex. ^self]. tempIndex >= 256 ifTrue: [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255]. tempVectorIndex >= 256 ifTrue: [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255]! ! !EncoderForLongFormV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:04'! genStorePopRemoteTemp: tempIndex inVectorAt: tempVectorIndex "142 10001110 kkkkkkkk jjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj" (tempIndex >= 0 and: [tempIndex < 256 and: [tempVectorIndex >= 0 and: [tempVectorIndex < 256]]]) ifTrue: [stream nextPut: 142; nextPut: tempIndex; nextPut: tempVectorIndex. ^self]. tempIndex >= 256 ifTrue: [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255]. tempVectorIndex >= 256 ifTrue: [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255]! ! !EncoderForLongFormV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:04'! genStoreRemoteTemp: tempIndex inVectorAt: tempVectorIndex "141 10001101 kkkkkkkk jjjjjjjj Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj" (tempIndex >= 0 and: [tempIndex < 256 and: [tempVectorIndex >= 0 and: [tempVectorIndex < 256]]]) ifTrue: [stream nextPut: 141; nextPut: tempIndex; nextPut: tempVectorIndex. ^self]. tempIndex >= 256 ifTrue: [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255]. tempVectorIndex >= 256 ifTrue: [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255]! ! !EncoderForLongFormV3PlusClosures methodsFor: 'testing' stamp: 'eem 5/24/2008 18:12'! supportsClosureOpcodes ^true! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EncoderForLongFormV3PlusClosures class instanceVariableNames: ''! BytecodeEncoder subclass: #EncoderForV3 instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Kernel'! !EncoderForV3 commentStamp: '' prior: 0! I add behaviour to Encoder to size and emit bytecodes for the Squeak V3.x VM bytecode set. The intention is for another subclass to restrict the range of bytecodes used to long forms only, allowing the bytecode set to be redefined by avoiding using the many short forms. The short forms may then be reassigned.! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:59'! genBranchPopFalse: distance "See BlueBook page 596" distance < 0 ifTrue: [^self outOfRangeError: 'distance' index: distance range: 0 to: 1023]. (distance > 0 and: [distance < 9]) ifTrue: ["152-159 10011iii Pop and Jump 0n False iii +1 (i.e., 1 through 8)" stream nextPut: 152 + distance - 1. ^self]. distance < 1024 ifTrue: ["172-175 101011ii jjjjjjjj Pop and Jump On False ii *256+jjjjjjjj" stream nextPut: 172 + (distance bitShift: -8); nextPut: distance + 1024 \\ 256. ^self]. ^self outOfRangeError: 'distance' index: distance range: 0 to: 1023! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:59'! genBranchPopTrue: distance "See BlueBook page 596" distance < 0 ifTrue: [^self outOfRangeError: 'distance' index: distance range: 0 to: 1023]. distance < 1024 ifTrue: ["168-171 101010ii jjjjjjjj Pop and Jump On True ii *256+jjjjjjjj" stream nextPut: 168 + (distance bitShift: -8); nextPut: distance + 1024 \\ 256. ^self]. ^self outOfRangeError: 'distance' index: distance range: 0 to: 1023! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/15/2008 09:40'! genDup "See BlueBook page 596" "136 10001000 Duplicate Stack Top" stream nextPut: 136! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/14/2008 17:41'! genJump: distance "See BlueBook page 596" (distance > 0 and: [distance < 9]) ifTrue: ["144-151 10010iii Jump iii + 1 (i.e., 1 through 8)" stream nextPut: 144 + distance - 1. ^self]. "160-167 10100iii jjjjjjjj Jump(iii - 4) *256+jjjjjjjj" ^self genJumpLong: distance! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:59'! genJumpLong: distance "See BlueBook page 596" (distance >= -1024 and: [distance < 1024]) ifTrue: ["160-167 10100iii jjjjjjjj Jump(iii - 4) *256+jjjjjjjj" stream nextPut: 160 + (distance + 1024 bitShift: -8); nextPut: distance + 1024 \\ 256. ^self]. ^self outOfRangeError: 'distance' index: distance range: -1024 to: 1023! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/14/2008 17:27'! genPop "See BlueBook page 596" "135 10000111 Pop Stack Top" stream nextPut: 135! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:40'! genPushInstVar: instVarIndex "See BlueBook page 596" instVarIndex >= 0 ifTrue: [instVarIndex < 16 ifTrue: ["0-15 0000iiii Push Receiver Variable #iiii" stream nextPut: 0 + instVarIndex. ^self]. instVarIndex < 64 ifTrue: ["128 10000000 jjkkkkkk Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk" stream nextPut: 128; nextPut: instVarIndex. ^self]]. self genPushInstVarLong: instVarIndex! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:51'! genPushInstVarLong: instVarIndex "See BlueBook page 596" "See also MaybeContextInstanceVariableNode" (instVarIndex >= 0 and: [instVarIndex < 256]) ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 64; nextPut: instVarIndex. ^self]. ^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 255! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:00'! genPushLiteral: literalIndex "See BlueBook page 596" literalIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255]. literalIndex < 32 ifTrue: ["32-63 001iiiii Push Literal Constant #iiiii" stream nextPut: 32 + literalIndex. ^self]. literalIndex < 64 ifTrue: ["128 10000000 jjkkkkkk Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk" stream nextPut: 128; nextPut: 128 + literalIndex. ^self]. literalIndex < 256 ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 96; nextPut: literalIndex. ^self]. ^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 16:59'! genPushLiteralVar: literalIndex "See BlueBook page 596" literalIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255]. literalIndex < 32 ifTrue: ["64-95 010iiiii Push Literal Variable #iiiii" stream nextPut: 64 + literalIndex. ^self]. literalIndex < 64 ifTrue: ["128 10000000 jjkkkkkk Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk" stream nextPut: 128; nextPut: 192 + literalIndex. ^self]. literalIndex < 256 ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 128; nextPut: literalIndex. ^self]. ^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/14/2008 16:16'! genPushReceiver "See BlueBook page 596" "112-119 01110iii Push (receiver, true, false, nil, -1, 0, 1, 2) [iii]" stream nextPut: 112! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/14/2008 17:38'! genPushSpecialLiteral: aLiteral "112-119 01110iii Push (receiver, true, false, nil, -1, 0, 1, 2) [iii]" | index | index := #(true false nil -1 0 1 2) indexOf: aLiteral ifAbsent: 0. index = 0 ifTrue: [^self error: 'push special literal: ', aLiteral printString, ' is not one of true false nil -1 0 1 2']. stream nextPut: index + 112! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:00'! genPushTemp: tempIndex "See BlueBook page 596" tempIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63]. tempIndex < 16 ifTrue: ["16-31 0001iiii Push Temporary Location #iiii" stream nextPut: 16 + tempIndex. ^self]. tempIndex < 64 ifTrue: ["128 10000000 jjkkkkkk Push (Receiver Variable, Temporary Location, Literal Constant, Literal Variable) [jj] #kkkkkk" stream nextPut: 128; nextPut: 64 + tempIndex. ^self]. ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/14/2008 17:36'! genPushThisContext "See BlueBook page 596" "137 10001001 Push Active Context" stream nextPut: 137! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/14/2008 17:40'! genReturnReceiver "See BlueBook page 596" "120-123 011110ii Return (receiver, true, false, nil) [ii] From Message" stream nextPut: 120! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/14/2008 17:39'! genReturnSpecialLiteral: aLiteral "120-123 011110ii Return (receiver, true, false, nil) [ii] From Message" | index | index := #(true false nil) indexOf: aLiteral ifAbsent: 0. index = 0 ifTrue: [^self error: 'return special literal: ', aLiteral printString, ' is not one of true false nil']. stream nextPut: 120 + index! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/14/2008 17:35'! genReturnTop "See BlueBook page 596" "124-125 0111110i Return Stack Top From (Message, Block) [i]" stream nextPut: 124! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/14/2008 17:35'! genReturnTopToCaller "See BlueBook page 596" "124-125 0111110i Return Stack Top From (Message, Block) [i]" stream nextPut: 125! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:00'! genSend: selectorLiteralIndex numArgs: nArgs "See BlueBook page 596 (with exceptions for 132 & 134)" nArgs < 0 ifTrue: [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"]. selectorLiteralIndex < 0 ifTrue: ["Special selector sends. 176-191 1011iiii Send Arithmetic Message #iiii 192-207 1100iiii Send Special Message #iiii" self flag: #yuck. (selectorLiteralIndex negated between: 176 and: 207) ifFalse: [^self outOfRangeError: 'special selector code' index: selectorLiteralIndex negated range: 176 to: 207]. stream nextPut: selectorLiteralIndex negated. ^self]. (selectorLiteralIndex < 16 and: [nArgs < 3]) ifTrue: [" 208-223 1101iiii Send Literal Selector #iiii With No Arguments 224-239 1110iiii Send Literal Selector #iiii With 1 Argument 240-255 1111iiii Send Literal Selector #iiii With 2 Arguments" stream nextPut: 208 + (nArgs * 16) + selectorLiteralIndex. ^self]. (selectorLiteralIndex < 32 and: [nArgs < 8]) ifTrue: [" 131 10000011 jjjkkkkk Send Literal Selector #kkkkk With jjj Arguments" stream nextPut: 131; nextPut: ((nArgs bitShift: 5) + selectorLiteralIndex). ^self]. (selectorLiteralIndex < 64 and: [nArgs < 4]) ifTrue: ["In Squeak V3 134 10000110 jjjjjjjj kkkkkkkk Send Literal Selector #kkkkkkkk To Superclass With jjjjjjjj Arguments is replaced by 134 10000110 jjkkkkkk Send Literal Selector #kkkkkk With jj Arguments" stream nextPut: 134; nextPut: ((nArgs bitShift: 6) + selectorLiteralIndex). ^self]. (selectorLiteralIndex < 256 and: [nArgs < 32]) ifTrue: ["In Squeak V3 132 10000100 jjjjjjjj kkkkkkkk Send Literal Selector #kkkkkkkk With jjjjjjjj Arguments is replaced by 132 10000100 ooojjjjj kkkkkkkk ooo = 0 => Send Literal Selector #kkkkkkkk With jjjjj Arguments ooo = 1 => Send Literal Selector #kkkkkkkk To Superclass With jjjjj Arguments" stream nextPut: 132; nextPut: nArgs; nextPut: selectorLiteralIndex. ^self]. nArgs >= 32 ifTrue: [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31]. selectorLiteralIndex >= 256 ifTrue: [^self outOfRangeError: 'selector literal index' index: selectorLiteralIndex range: 0 to: 255]! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:00'! genSendSuper: selectorLiteralIndex numArgs: nArgs "See BlueBook page 596 (with exceptions for 132 & 134)" nArgs < 0 ifTrue: [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"]. selectorLiteralIndex < 0 ifTrue: [^self outOfRangeError: 'selector literal index' index: selectorLiteralIndex range: 0 to: 255]. (selectorLiteralIndex < 32 and: [nArgs < 8]) ifTrue: [" 133 10000011 jjjkkkkk Send Literal Selector #kkkkk To Superclass With jjj Arguments" stream nextPut: 133; nextPut: ((nArgs bitShift: 5) + selectorLiteralIndex). ^self]. (selectorLiteralIndex < 256 and: [nArgs < 32]) ifTrue: ["In Squeak V3 132 10000100 jjjjjjjj kkkkkkkk Send Literal Selector #kkkkkkkk With jjjjjjjj Arguments is replaced by 132 10000100 ooojjjjj kkkkkkkk ooo = 0 => Send Literal Selector #kkkkkkkk With jjjjj Arguments ooo = 1 => Send Literal Selector #kkkkkkkk To Superclass With jjjjj Arguments" stream nextPut: 132; nextPut: 32 + nArgs; nextPut: selectorLiteralIndex. ^self]. nArgs >= 32 ifTrue: [^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31]. selectorLiteralIndex >= 256 ifTrue: [^self outOfRangeError: 'selector literal index' index: selectorLiteralIndex range: 0 to: 255]! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:37'! genStoreInstVar: instVarIndex "See BlueBook page 596" (instVarIndex >= 0 and: [instVarIndex < 64]) ifTrue: ["129 10000001 jjkkkkkk Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 129; nextPut: instVarIndex. ^self]. self genStoreInstVarLong: instVarIndex! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:51'! genStoreInstVarLong: instVarIndex "See BlueBook page 596" "See also MaybeContextInstanceVariableNode" (instVarIndex >= 0 and: [instVarIndex < 256]) ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 160; nextPut: instVarIndex. ^self]. ^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 255! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:01'! genStoreLiteralVar: literalIndex "See BlueBook page 596" literalIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255]. literalIndex < 64 ifTrue: ["129 10000001 jjkkkkkk Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 129; nextPut: 192 + literalIndex. ^self]. literalIndex < 256 ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 224; nextPut: literalIndex. ^self]. ^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:43'! genStorePopInstVar: instVarIndex "See BlueBook page 596" instVarIndex >= 0 ifTrue: [instVarIndex < 8 ifTrue: ["96-103 01100iii Pop and Store Receiver Variable #iii" stream nextPut: 96 + instVarIndex. ^self]. instVarIndex < 64 ifTrue: ["130 10000010 jjkkkkkk Pop and Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 130; nextPut: instVarIndex. ^self]]. self genStorePopInstVarLong: instVarIndex! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 6/19/2008 08:52'! genStorePopInstVarLong: instVarIndex "See BlueBook page 596" "See also MaybeContextInstanceVariableNode" (instVarIndex >= 0 and: [instVarIndex < 256]) ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 192; nextPut: instVarIndex. ^self]. ^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 255! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:01'! genStorePopLiteralVar: literalIndex "See BlueBook page 596" literalIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255]. literalIndex < 64 ifTrue: ["130 10000010 jjkkkkkk Pop and Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 130; nextPut: 192 + literalIndex. ^self]. literalIndex < 256 ifTrue: ["132 10000100 iiijjjjj kkkkkkkk (Send, Send Super, Push Receiver Variable, Push Literal Constant, Push Literal Variable, Store Receiver Variable, Store-Pop Receiver Variable, Store Literal Variable)[iii] #kkkkkkkk jjjjj" stream nextPut: 132; nextPut: 224; nextPut: literalIndex. self genPop. ^self]. ^self outOfRangeError: 'index' index: literalIndex range: 0 to: 255! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:01'! genStorePopTemp: tempIndex "See BlueBook page 596" tempIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63]. tempIndex < 8 ifTrue: ["104-111 01101iii Pop and Store Temporary Location #iii" stream nextPut: 104 + tempIndex. ^self]. tempIndex < 64 ifTrue: ["130 10000010 jjkkkkkk Pop and Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 130; nextPut: 64 + tempIndex. ^self]. ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63! ! !EncoderForV3 methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:01'! genStoreTemp: tempIndex "See BlueBook page 596" tempIndex < 0 ifTrue: [^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63]. tempIndex < 64 ifTrue: ["129 10000001 jjkkkkkk Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk" stream nextPut: 129; nextPut: 64 + tempIndex. ^self]. ^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63! ! EncoderForV3 subclass: #EncoderForV3PlusClosures instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Compiler-Kernel'! !EncoderForV3PlusClosures commentStamp: '' prior: 0! An encoder for the V3 bytecode set augmented with the following bytecodes that are part of the full closure implementation. 138 10001010 jkkkkkkk Push (Array new: kkkkkkk) (j = 0) or Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1) 140 10001100 kkkkkkkk jjjjjjjj Push Temp At kkkkkkkk In Temp Vector At: jjjjjjjj 141 10001101 kkkkkkkk jjjjjjjj Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj 142 10001110 kkkkkkkk jjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj 143 10001111 llllkkkk jjjjjjjj iiiiiiii Push Closure Num Copied llll Num Args kkkk BlockSize jjjjjjjjiiiiiiii This is an exact duplicate of EncoderForLongFormV3PlusClosures. Could be a trait (or in Newspeak, a Mixin). For now we impose upon you to synchronise any and all changes between these two classes.! !EncoderForV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:11'! genPushClosureCopyNumCopiedValues: numCopied numArgs: numArgs jumpSize: jumpSize "143 10001111 llllkkkk jjjjjjjj iiiiiiii Push Closure Num Copied llll Num Args kkkk BlockSize jjjjjjjjiiiiiiii" (jumpSize < 0 or: [jumpSize > 65535]) ifTrue: [^self outOfRangeError: 'block size' index: jumpSize range: 0 to: 65535]. (numCopied < 0 or: [numCopied > 15]) ifTrue: [^self outOfRangeError: 'num copied' index: numCopied range: 0 to: 15]. (numArgs < 0 or: [numArgs > 15]) ifTrue: [^self outOfRangeError: 'num args' index: numArgs range: 0 to: 15]. stream nextPut: 143; nextPut: numArgs + (numCopied bitShift: 4); nextPut: (jumpSize bitShift: -8); nextPut: (jumpSize bitAnd: 16rFF)! ! !EncoderForV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:03'! genPushConsArray: size (size < 0 or: [size > 127]) ifTrue: [^self outOfRangeError: 'numElements' index: size range: 0 to: 127]. "138 10001010 1kkkkkkk Push (Array new: kkkkkkk)" stream nextPut: 138; nextPut: size + 128! ! !EncoderForV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:06'! genPushNewArray: size (size < 0 or: [size > 127]) ifTrue: [^self outOfRangeError: 'numElements' index: size range: 0 to: 127]. "138 10001010 0kkkkkkk Pop kkkkkkk into: (Array new: kkkkkkk)" stream nextPut: 138; nextPut: size! ! !EncoderForV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 6/16/2008 09:45'! genPushRemoteTemp: tempIndex inVectorAt: tempVectorIndex (tempIndex >= 0 and: [tempIndex < 256 and: [tempVectorIndex >= 0 and: [tempVectorIndex < 256]]]) ifTrue: ["140 10001100 kkkkkkkk jjjjjjjj Push Temp At kkkkkkkk In Temp Vector At: jjjjjjjj" stream nextPut: 140; nextPut: tempIndex; nextPut: tempVectorIndex. ^self]. tempIndex >= 256 ifTrue: [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255]. tempVectorIndex >= 256 ifTrue: [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255]! ! !EncoderForV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:02'! genStorePopRemoteTemp: tempIndex inVectorAt: tempVectorIndex "142 10001110 kkkkkkkk jjjjjjjj Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj" (tempIndex >= 0 and: [tempIndex < 256 and: [tempVectorIndex >= 0 and: [tempVectorIndex < 256]]]) ifTrue: [stream nextPut: 142; nextPut: tempIndex; nextPut: tempVectorIndex. ^self]. tempIndex >= 256 ifTrue: [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255]. tempVectorIndex >= 256 ifTrue: [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255]! ! !EncoderForV3PlusClosures methodsFor: 'bytecode generation' stamp: 'eem 5/30/2008 17:02'! genStoreRemoteTemp: tempIndex inVectorAt: tempVectorIndex "141 10001101 kkkkkkkk jjjjjjjj Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj" (tempIndex >= 0 and: [tempIndex < 256 and: [tempVectorIndex >= 0 and: [tempVectorIndex < 256]]]) ifTrue: [stream nextPut: 141; nextPut: tempIndex; nextPut: tempVectorIndex. ^self]. tempIndex >= 256 ifTrue: [^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255]. tempVectorIndex >= 256 ifTrue: [^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255]! ! !EncoderForV3PlusClosures methodsFor: 'testing' stamp: 'eem 5/24/2008 18:12'! supportsClosureOpcodes ^true! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EncoderForV3PlusClosures class instanceVariableNames: ''! Error subclass: #EndOfStream instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Extensions'! !EndOfStream commentStamp: '' prior: 0! Signalled when ReadStream>>next encounters a premature end.! !EndOfStream methodsFor: 'description' stamp: 'mir 9/25/2008 15:16'! isResumable "EndOfStream is resumable, so ReadStream>>next can answer." ^ true! ! !EndOfStream methodsFor: 'exceptiondescription' stamp: 'RAA 5/17/2000 03:10'! defaultAction "Answer ReadStream>>next default reply." ^ nil! ! PrototypeTester subclass: #EqualityTester instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'SUnit-Utilities'! !EqualityTester commentStamp: 'mjr 8/20/2003 13:04' prior: 0! I provide a simple way to test the equality properties of any object.! !EqualityTester methodsFor: 'as yet unclassified' stamp: 'mjr 8/20/2003 18:56'! resultFor: runs "Test that equality is the same over runs and answer the result" 1 to: runs do: [:i | self prototype = self prototype ifFalse: [^ false]]. ^ true! ! Exception subclass: #Error instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !Error commentStamp: '' prior: 0! >From the ANSI standard: This protocol describes the behavior of instances of class Error. These are used to represent error conditions that prevent the normal continuation of processing. Actual error exceptions used by an application may be subclasses of this class. As Error is explicitly specified to be subclassable, conforming implementations must implement its behavior in a non-fragile manner. Additional notes: Error>defaultAction uses an explicit test for the presence of the Debugger class to decide whether or not it is in development mode. In the future, TFEI hopes to enhance the semantics of #defaultAction to improve support for pluggable default handlers.! !Error methodsFor: 'exceptiondescription' stamp: 'ajh 9/4/2002 19:24'! defaultAction "No one has handled this error, but now give them a chance to decide how to debug it. If none handle this either then open debugger (see UnhandedError-defaultAction)" UnhandledError signalForException: self! ! !Error methodsFor: 'private' stamp: 'ajh 2/1/2003 00:54'! isResumable "Determine whether an exception is resumable." ^ false! ! MessageDialogWindow subclass: #ErrorDialogWindow instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !ErrorDialogWindow commentStamp: 'gvc 5/18/2007 14:51' prior: 0! A message dialog with an error icon.! !ErrorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/18/2007 14:52'! icon "Answer an icon for the receiver." ^self theme errorIcon! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ErrorDialogWindow class instanceVariableNames: ''! !ErrorDialogWindow class methodsFor: 'as yet unclassified' stamp: 'gvc 5/22/2007 11:54'! taskbarIcon "Answer the icon for the receiver in a task bar." ^self theme smallErrorIcon! ! Object subclass: #EventHandler instanceVariableNames: 'mouseDownRecipient mouseDownSelector mouseMoveRecipient mouseMoveSelector mouseStillDownRecipient mouseStillDownSelector mouseUpRecipient mouseUpSelector mouseEnterRecipient mouseEnterSelector mouseLeaveRecipient mouseLeaveSelector mouseEnterDraggingRecipient mouseEnterDraggingSelector mouseLeaveDraggingRecipient mouseLeaveDraggingSelector keyStrokeRecipient keyStrokeSelector valueParameter startDragRecipient startDragSelector doubleClickSelector doubleClickRecipient doubleClickTimeoutSelector doubleClickTimeoutRecipient clickSelector clickRecipient' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Events'! !EventHandler commentStamp: '' prior: 0! Events in Morphic originate in a Hand, pass to a target morph, and are then dispatched by an EventHandler. EventHandlers support redirection of mouse and keyboard activity by specifying and independent recipient object and message selector for each of the possible events. In addition each eventHandler can supply an optional value parameter for distinguishing between, eg, events from a number of otherwise identical source morphs. The basic protocol of an event handler is to receive a message of the form mouseDown: event in: targetMorph and redirect this as one of mouseDownRecipient perform: mouseDownSelector0 mouseDownRecipient perform: mouseDownSelector1 with: event mouseDownRecipient perform: mouseDownSelector2 with: event with: targetMorph mouseDownRecipient perform: mouseDownSelector3 with: event with: targetMorph with: valueParameter depending on the arity of the mouseDownSelector. ! !EventHandler methodsFor: 'access' stamp: 'ar 10/25/2000 17:33'! allRecipients "Answer a list, without duplication, of all the objects serving as recipients to any of the events I handle. Intended for debugging/documentation use only" | aList | aList := OrderedCollection with: mouseDownRecipient with: mouseStillDownRecipient with: mouseUpRecipient with: mouseEnterRecipient with: mouseLeaveRecipient. aList addAll: (OrderedCollection with: mouseEnterDraggingRecipient with: mouseLeaveDraggingRecipient with: doubleClickRecipient with: keyStrokeRecipient). aList add: mouseMoveRecipient. ^ (aList copyWithout: nil) asSet asArray! ! !EventHandler methodsFor: 'access' stamp: 'ar 10/25/2000 17:34'! firstMouseSelector "Answer the selector corresponding to the first mouse-handling selector fielded. Created in support of providing balloon-help for halo handles, triggered by the selector handled" mouseDownSelector ifNotNil: [^ mouseDownSelector]. mouseMoveSelector ifNotNil:[^mouseMoveSelector]. mouseStillDownSelector ifNotNil: [^ mouseStillDownSelector]. mouseUpSelector ifNotNil: [^ mouseUpSelector]. mouseEnterSelector ifNotNil: [^ mouseEnterSelector]. mouseLeaveSelector ifNotNil: [^ mouseLeaveSelector]. mouseEnterDraggingSelector ifNotNil: [^ mouseEnterDraggingSelector]. mouseLeaveDraggingSelector ifNotNil: [^ mouseLeaveDraggingSelector]. doubleClickSelector ifNotNil: [^ doubleClickSelector]. ^ nil! ! !EventHandler methodsFor: 'access'! messageList "Return a list of 'Class selector' for each message I can send. tk 9/13/97" | list | self flag: #mref. "is this still needed? I replaced the one use that I could spot with #methodRefList " list := SortedCollection new. mouseDownRecipient ifNotNil: [list add: (mouseDownRecipient class whichClassIncludesSelector: mouseDownSelector) name , ' ' , mouseDownSelector]. mouseMoveRecipient ifNotNil: [list add: (mouseMoveRecipient class whichClassIncludesSelector: mouseMoveSelector) name , ' ' , mouseMoveSelector]. mouseStillDownRecipient ifNotNil: [list add: (mouseStillDownRecipient class whichClassIncludesSelector: mouseStillDownSelector) name , ' ' , mouseStillDownSelector]. mouseUpRecipient ifNotNil: [list add: (mouseUpRecipient class whichClassIncludesSelector: mouseUpSelector) name , ' ' , mouseUpSelector]. mouseEnterRecipient ifNotNil: [list add: (mouseEnterRecipient class whichClassIncludesSelector: mouseEnterSelector) name , ' ' , mouseEnterSelector]. mouseLeaveRecipient ifNotNil: [list add: (mouseLeaveRecipient class whichClassIncludesSelector: mouseLeaveSelector) name , ' ' , mouseLeaveSelector]. mouseEnterDraggingRecipient ifNotNil: [list add: (mouseEnterDraggingRecipient class whichClassIncludesSelector: mouseEnterDraggingSelector) name , ' ' , mouseEnterDraggingSelector]. mouseLeaveDraggingRecipient ifNotNil: [list add: (mouseLeaveDraggingRecipient class whichClassIncludesSelector: mouseLeaveDraggingSelector) name , ' ' , mouseLeaveDraggingSelector]. doubleClickRecipient ifNotNil: [list add: (doubleClickRecipient class whichClassIncludesSelector: doubleClickSelector) name , ' ' , doubleClickSelector]. keyStrokeRecipient ifNotNil: [list add: (keyStrokeRecipient class whichClassIncludesSelector: keyStrokeSelector) name , ' ' , keyStrokeSelector]. ^ list! ! !EventHandler methodsFor: 'access'! methodRefList "Return a MethodReference for each message I can send. tk 9/13/97, raa 5/29/01 " | list adder | list := SortedCollection new. adder := [:recip :sel | recip ifNotNil: [list add: (MethodReference new setStandardClass: (recip class whichClassIncludesSelector: sel) methodSymbol: sel)]]. adder value: mouseDownRecipient value: mouseDownSelector. adder value: mouseMoveRecipient value: mouseMoveSelector. adder value: mouseStillDownRecipient value: mouseStillDownSelector. adder value: mouseUpRecipient value: mouseUpSelector. adder value: mouseEnterRecipient value: mouseEnterSelector. adder value: mouseLeaveRecipient value: mouseLeaveSelector. adder value: mouseEnterDraggingRecipient value: mouseEnterDraggingSelector. adder value: mouseLeaveDraggingRecipient value: mouseLeaveDraggingSelector. adder value: doubleClickRecipient value: doubleClickSelector. adder value: keyStrokeRecipient value: keyStrokeSelector. ^ list! ! !EventHandler methodsFor: 'access' stamp: 'di 9/14/1998 08:32'! mouseDownSelector ^ mouseDownSelector! ! !EventHandler methodsFor: 'access' stamp: 'ar 10/25/2000 18:27'! mouseStillDownRecipient ^mouseStillDownRecipient! ! !EventHandler methodsFor: 'access' stamp: 'ar 10/25/2000 18:27'! mouseStillDownSelector ^mouseStillDownSelector! ! !EventHandler methodsFor: 'access' stamp: 'di 9/14/1998 08:32'! mouseUpSelector ^ mouseUpSelector! ! !EventHandler methodsFor: 'copying' stamp: 'tk 1/22/2001 17:43'! veryDeepFixupWith: deepCopier | old | "ALL inst vars were weakly copied. If they were in the tree being copied, fix them up, otherwise point to the originals!!!!" super veryDeepFixupWith: deepCopier. 1 to: self class instSize do: [:ii | old := self instVarAt: ii. self instVarAt: ii put: (deepCopier references at: old ifAbsent: [old])]. ! ! !EventHandler methodsFor: 'copying' stamp: 'nk 2/14/2004 18:24'! veryDeepInner: deepCopier "ALL fields are weakly copied!! Can't duplicate an object by duplicating a button that activates it. See DeepCopier." super veryDeepInner: deepCopier. "just keep old pointers to all fields" ! ]style[(25 108 10 78)f1b,f1,f1LDeepCopier Comment;,f1! ! !EventHandler methodsFor: 'events' stamp: 'ar 10/7/2000 22:55'! click: event fromMorph: sourceMorph "This message is sent only when double clicks are handled." ^ self send: clickSelector to: clickRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events' stamp: 'LC 2/14/2000 08:38'! doubleClick: event fromMorph: sourceMorph ^ self send: doubleClickSelector to: doubleClickRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events' stamp: 'jcg 9/21/2001 13:06'! doubleClickTimeout: event fromMorph: sourceMorph ^ self send: doubleClickTimeoutSelector to: doubleClickTimeoutRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events'! keyStroke: event fromMorph: sourceMorph ^ self send: keyStrokeSelector to: keyStrokeRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events' stamp: 'ar 10/7/2000 22:54'! mouseDown: event fromMorph: sourceMorph "Take double-clicks into account." ((self handlesClickOrDrag: event) and:[event redButtonPressed]) ifTrue:[ event hand waitForClicksOrDrag: sourceMorph event: event. ]. ^self send: mouseDownSelector to: mouseDownRecipient withEvent: event fromMorph: sourceMorph. ! ! !EventHandler methodsFor: 'events'! mouseEnter: event fromMorph: sourceMorph ^ self send: mouseEnterSelector to: mouseEnterRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events' stamp: 'di 9/15/1998 16:35'! mouseEnterDragging: event fromMorph: sourceMorph ^ self send: mouseEnterDraggingSelector to: mouseEnterDraggingRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events'! mouseLeave: event fromMorph: sourceMorph ^ self send: mouseLeaveSelector to: mouseLeaveRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events' stamp: 'di 9/15/1998 16:35'! mouseLeaveDragging: event fromMorph: sourceMorph ^ self send: mouseLeaveDraggingSelector to: mouseLeaveDraggingRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events' stamp: 'ar 10/25/2000 17:32'! mouseMove: event fromMorph: sourceMorph ^ self send: mouseMoveSelector to: mouseMoveRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events'! mouseStillDown: event fromMorph: sourceMorph ^ self send: mouseStillDownSelector to: mouseStillDownRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events'! mouseUp: event fromMorph: sourceMorph ^ self send: mouseUpSelector to: mouseUpRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'events' stamp: 'ar 3/17/2001 14:34'! send: selector to: recipient withEvent: event fromMorph: sourceMorph | arity | recipient ifNil: [^ self]. arity := selector numArgs. arity = 0 ifTrue: [^ recipient perform: selector]. arity = 1 ifTrue: [^ recipient perform: selector with: event]. arity = 2 ifTrue: [^ recipient perform: selector with: event with: sourceMorph]. arity = 3 ifTrue: [^ recipient perform: selector with: valueParameter with: event with: sourceMorph]. self error: 'Event handling selectors must be Symbols and take 0-3 arguments'! ! !EventHandler methodsFor: 'events' stamp: 'mir 5/23/2000 17:43'! startDrag: event fromMorph: sourceMorph ^ self send: startDragSelector to: startDragRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandler methodsFor: 'fixups' stamp: 'stephane.ducasse 11/18/2008 21:50'! fixReversedValueMessages "ar 3/18/2001: Due to the change in the ordering of the value parameter old event handlers may have messages that need to be fixed up. Do this here." self replaceSendsIn: #( renameCharAction:sourceMorph:requestor: makeGetter:from:forPart: makeSetter:from:forPart: clickOnLine:evt:envelope: limitHandleMoveEvent:from:index: mouseUpEvent:linkMorph:formData: mouseUpEvent:linkMorph:browserAndUrl: mouseDownEvent:noteMorph:pitch: mouseMoveEvent:noteMorph:pitch: mouseUpEvent:noteMorph:pitch: dragVertex:fromHandle:vertIndex: dropVertex:fromHandle:vertIndex: newVertex:fromHandle:afterVert: prefMenu:rcvr:pref: event:arrow:upDown:) with: #( renameCharAction:event:sourceMorph: makeGetter:event:from: makeSetter:event:from: clickOn:evt:from: limitHandleMove:event:from: mouseUpFormData:event:linkMorph: mouseUpBrowserAndUrl:event:linkMorph: mouseDownPitch:event:noteMorph: mouseMovePitch:event:noteMorph: mouseUpPitch:event:noteMorph: dragVertex:event:fromHandle: dropVertex:event:fromHandle: newVertex:event:fromHandle: prefMenu:event:rcvr: upDown:event:arrow:). "sw 3/28/2001 extended Andreas's original lists by one item"! ! !EventHandler methodsFor: 'fixups' stamp: 'ar 3/18/2001 17:18'! replaceSendsIn: array1 with: array2 "Replace all the sends that occur in array1 with those in array2. Used for fixing old event handlers in files." | old index | 1 to: self class instSize do:[:i| old := self instVarAt: i. index := array1 identityIndexOf: old. index > 0 ifTrue:[self instVarAt: i put: (array2 at: index)]].! ! !EventHandler methodsFor: 'initialization' stamp: 'nk 2/15/2004 08:16'! on: eventName send: selector to: recipient eventName == #mouseDown ifTrue: [mouseDownRecipient := recipient. mouseDownSelector := selector. ^ self]. eventName == #mouseMove ifTrue: [mouseMoveRecipient := recipient. mouseMoveSelector := selector. ^ self]. eventName == #mouseStillDown ifTrue: [mouseStillDownRecipient := recipient. mouseStillDownSelector := selector. ^ self]. eventName == #mouseUp ifTrue: [mouseUpRecipient := recipient. mouseUpSelector := selector. ^ self]. eventName == #mouseEnter ifTrue: [mouseEnterRecipient := recipient. mouseEnterSelector := selector. ^ self]. eventName == #mouseLeave ifTrue: [mouseLeaveRecipient := recipient. mouseLeaveSelector := selector. ^ self]. eventName == #mouseEnterDragging ifTrue: [mouseEnterDraggingRecipient := recipient. mouseEnterDraggingSelector := selector. ^ self]. eventName == #mouseLeaveDragging ifTrue: [mouseLeaveDraggingRecipient := recipient. mouseLeaveDraggingSelector := selector. ^ self]. eventName == #click ifTrue: [clickRecipient := recipient. clickSelector := selector. ^ self]. eventName == #doubleClick ifTrue: [doubleClickRecipient := recipient. doubleClickSelector := selector. ^ self]. eventName == #doubleClickTimeout ifTrue: [doubleClickTimeoutRecipient := recipient. doubleClickTimeoutSelector := selector. ^ self]. eventName == #startDrag ifTrue: [startDragRecipient := recipient. startDragSelector := selector. ^ self]. eventName == #keyStroke ifTrue: [keyStrokeRecipient := recipient. keyStrokeSelector := selector. ^ self]. eventName == #gesture ifTrue: [ ^self onGestureSend: selector to: recipient ]. self error: 'Event name, ' , eventName , ' is not recognizable.' ! ! !EventHandler methodsFor: 'initialization' stamp: 'wiz 8/21/2005 01:44'! on: eventName send: selector to: recipient withValue: value selector numArgs = 3 ifFalse: [self halt: 'Warning: value parameters are passed as first of 3 arguments']. self on: eventName send: selector to: recipient. valueParameter := value ! ! !EventHandler methodsFor: 'initialization' stamp: 'nk 2/15/2004 08:59'! onGestureSend: selector to: recipient! ! !EventHandler methodsFor: 'printing' stamp: 'dgd 2/22/2003 18:40'! printOn: aStream | aVal recipients | super printOn: aStream. #('mouseDownSelector' 'mouseStillDownSelector' 'mouseUpSelector' 'mouseEnterSelector' 'mouseLeaveSelector' 'mouseEnterDraggingSelector' 'mouseLeaveDraggingSelector' 'doubleClickSelector' 'keyStrokeSelector') do: [:aName | (aVal := self instVarNamed: aName) notNil ifTrue: [aStream nextPutAll: '; ' , aName , '=' , aVal]]. (recipients := self allRecipients) notEmpty ifTrue: [aStream nextPutAll: ' recipients: '. recipients printOn: aStream]! ! !EventHandler methodsFor: 'testing' stamp: 'ar 10/7/2000 22:56'! handlesClickOrDrag: evt clickRecipient ifNotNil:[^true]. doubleClickRecipient ifNotNil:[^true]. startDragRecipient ifNotNil:[^true]. ^false! ! !EventHandler methodsFor: 'testing' stamp: 'nk 2/15/2004 08:57'! handlesGestureStart: evt "Does the associated morph want to handle gestures?" ^false! ! !EventHandler methodsFor: 'testing' stamp: 'ar 10/28/2000 22:17'! handlesKeyboard: evt keyStrokeRecipient ifNotNil: [^ true]. ^ false! ! !EventHandler methodsFor: 'testing' stamp: 'nk 2/15/2004 08:13'! handlesMouseDown: evt mouseDownRecipient ifNotNil: [^ true]. mouseStillDownRecipient ifNotNil: [^ true]. mouseUpRecipient ifNotNil: [^ true]. (self handlesClickOrDrag: evt) ifTrue:[^true]. ^self handlesGestureStart: evt! ! !EventHandler methodsFor: 'testing' stamp: 'ar 10/25/2000 17:33'! handlesMouseMove: evt ^mouseMoveRecipient notNil and:[mouseMoveSelector notNil]! ! !EventHandler methodsFor: 'testing'! handlesMouseOver: evt mouseEnterRecipient ifNotNil: [^ true]. mouseLeaveRecipient ifNotNil: [^ true]. ^ false! ! !EventHandler methodsFor: 'testing' stamp: 'di 9/15/1998 16:35'! handlesMouseOverDragging: evt mouseEnterDraggingRecipient ifNotNil: [^ true]. mouseLeaveDraggingRecipient ifNotNil: [^ true]. ^ false! ! !EventHandler methodsFor: 'testing' stamp: 'ar 10/22/2000 17:05'! handlesMouseStillDown: evt ^mouseStillDownRecipient notNil and:[mouseStillDownSelector notNil]! ! EventHandler subclass: #EventHandlerPlus instanceVariableNames: 'mouseOverRecipient mouseOverSelector' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !EventHandlerPlus commentStamp: 'gvc 5/18/2007 13:13' prior: 0! Support for handling mouseOver events (no button down).! !EventHandlerPlus methodsFor: 'as yet unclassified' stamp: 'gvc 5/1/2007 17:19'! handlesMouseOver: evt "Answer whether we can handle the event." mouseOverRecipient ifNotNil: [^ true]. ^super handlesMouseOver: evt! ! !EventHandlerPlus methodsFor: 'as yet unclassified' stamp: 'gvc 5/1/2007 17:23'! methodRefList "Return a MethodReference for each message I can send." |list adder| list := super methodRefList. adder := [:recip :sel | recip ifNotNil: [list add: (MethodReference new setStandardClass: (recip class whichClassIncludesSelector: sel) methodSymbol: sel)]]. adder value: mouseOverRecipient value: mouseOverSelector. ^list! ! !EventHandlerPlus methodsFor: 'as yet unclassified' stamp: 'gvc 5/1/2007 17:20'! mouseOver: event fromMorph: sourceMorph "Relay the event." ^ self send: mouseOverSelector to: mouseOverRecipient withEvent: event fromMorph: sourceMorph! ! !EventHandlerPlus methodsFor: 'as yet unclassified' stamp: 'gvc 5/1/2007 17:24'! on: eventName send: selector to: recipient "Register the selector and recipient for the given event name." eventName == #mouseOver ifTrue: [mouseOverRecipient := recipient. mouseOverSelector := selector. ^ self]. ^super on: eventName send: selector to: recipient! ! Object subclass: #EventManager instanceVariableNames: 'actionMap' classVariableNames: 'ActionMaps' poolDictionaries: '' category: 'System-Object Events'! !EventManager commentStamp: 'tlk 5/7/2006 20:01' prior: 0! An EventManager is used to registers a 'observer' object's interest in in changes to an 'observed' object. Then when the observered object is changed, EventManager broadcasts the an update message to all objects with a registered interest. Finally, the Event manager can be used to remove an object from the list of observer object. An interested object is said to be a dependant on the target object. Registering an interest in an event is called adding a dependant. Deregistering is called removing a dependant. The EventManager's action map is a WeakIdentityDictionary that maps events (selectors) to dependants (objects & selectors) in a way that ensures the mapping is to specific objects (hence identity) and in a way that allows the object to be garbage collected if not other used (hence weak.) EventManager class has ActionMaps which has one actionMap for each object. Classic uses of an EventManager are to implement the Observer Pattern, see ChangeNotification or the MorphicModle as examples.! !EventManager methodsFor: 'accessing' stamp: 'reThink 2/18/2001 15:37'! actionMap ^actionMap == nil ifTrue: [self createActionMap] ifFalse: [actionMap]! ! !EventManager methodsFor: 'accessing' stamp: 'reThink 3/3/2001 10:07'! changedEventSelector ^#changed:! ! !EventManager methodsFor: 'accessing' stamp: 'reThink 2/18/2001 15:39'! releaseActionMap actionMap := nil! ! !EventManager methodsFor: 'accessing' stamp: 'reThink 3/3/2001 10:07'! updateEventSelector ^#update:! ! !EventManager methodsFor: 'accessing' stamp: 'reThink 2/18/2001 15:38'! updateableActionMap actionMap == nil ifTrue: [actionMap := self createActionMap]. ^actionMap! ! !EventManager methodsFor: 'copying' stamp: 'reThink 3/3/2001 10:22'! copy | answer | answer := super copy. answer release. ^answer! ! !EventManager methodsFor: 'dependents access' stamp: 'reThink 3/3/2001 10:07'! addDependent: anObject "Make the given object one of the receiver's dependents." self when: self changedEventSelector send: self updateEventSelector to: anObject. ^anObject! ! !EventManager methodsFor: 'dependents access' stamp: 'reThink 3/3/2001 10:07'! breakDependents "Remove all of the receiver's dependents." self removeActionsForEvent: self changedEventSelector! ! !EventManager methodsFor: 'dependents access' stamp: 'reThink 3/3/2001 10:18'! dependents ^(self actionSequenceForEvent: self changedEventSelector) asSet collect: [:each | each receiver]! ! !EventManager methodsFor: 'dependents access' stamp: 'reThink 3/3/2001 10:07'! removeDependent: anObject "Remove the given object as one of the receiver's dependents." self removeActionsWithReceiver: anObject forEvent: self changedEventSelector. ^ anObject! ! !EventManager methodsFor: 'updating' stamp: 'reThink 3/3/2001 10:20'! changed: aParameter "Receiver changed. The change is denoted by the argument aParameter. Usually the argument is a Symbol that is part of the dependent's change protocol. Inform all of the dependents." self triggerEvent: self changedEventSelector with: aParameter! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EventManager class instanceVariableNames: ''! !EventManager class methodsFor: 'accessing' stamp: 'reThink 2/18/2001 14:42'! actionMapFor: anObject ^self actionMaps at: anObject ifAbsent: [self createActionMap]! ! !EventManager class methodsFor: 'accessing' stamp: 'rww 10/2/2001 07:20'! actionMaps ActionMaps == nil ifTrue: [ActionMaps := WeakIdentityKeyDictionary new]. ^ActionMaps! ! !EventManager class methodsFor: 'accessing' stamp: 'reThink 2/25/2001 08:52'! updateableActionMapFor: anObject ^self actionMaps at: anObject ifAbsentPut: [self createActionMap]! ! !EventManager class methodsFor: 'initialization' stamp: 'rw 2/10/2002 13:09'! flushEvents "Object flushEvents" | msgSet | self actionMaps keysAndValuesDo:[:rcvr :evtDict| rcvr ifNotNil:[ "make sure we don't modify evtDict while enumerating" evtDict keys do:[:evtName| msgSet := evtDict at: evtName ifAbsent:[nil]. (msgSet == nil) ifTrue:[rcvr removeActionsForEvent: evtName]]]]. EventManager actionMaps finalizeValues. ! ! !EventManager class methodsFor: 'releasing' stamp: 'reThink 2/18/2001 15:34'! releaseActionMapFor: anObject self actionMaps removeKey: anObject ifAbsent: []! ! ClassTestCase subclass: #EventManagerTest instanceVariableNames: 'eventSource eventListener succeeded' classVariableNames: '' poolDictionaries: '' category: 'Tests-Object Events'! !EventManagerTest methodsFor: 'running' stamp: 'JWS 9/7/2000 17:19'! setUp super setUp. eventSource := EventManager new. eventListener := Bag new. succeeded := false! ! !EventManagerTest methodsFor: 'running' stamp: 'jws 11/28/2000 16:25'! tearDown eventSource releaseActionMap. eventSource := nil. eventListener := nil. super tearDown. ! ! !EventManagerTest methodsFor: 'running-broadcast query' stamp: 'JWS 9/7/2000 17:21'! testMultipleValueSuppliers eventSource when: #needsValue send: #getFalse to: self. eventSource when: #needsValue send: #getTrue to: self. succeeded := eventSource triggerEvent: #needsValue. self should: [succeeded]! ! !EventManagerTest methodsFor: 'running-broadcast query' stamp: 'JWS 9/7/2000 17:21'! testMultipleValueSuppliersEventHasArguments eventSource when: #needsValue: send: #getFalse: to: self. eventSource when: #needsValue: send: #getTrue: to: self. succeeded := eventSource triggerEvent: #needsValue: with: 'kolme'. self should: [succeeded]! ! !EventManagerTest methodsFor: 'running-broadcast query' stamp: 'JWS 9/7/2000 17:22'! testNoValueSupplier succeeded := eventSource triggerEvent: #needsValue ifNotHandled: [true]. self should: [succeeded]! ! !EventManagerTest methodsFor: 'running-broadcast query' stamp: 'JWS 9/7/2000 17:22'! testNoValueSupplierHasArguments succeeded := eventSource triggerEvent: #needsValue: with: 'nelja' ifNotHandled: [true]. self should: [succeeded]! ! !EventManagerTest methodsFor: 'running-broadcast query' stamp: 'jws 11/28/2000 15:52'! testSingleValueSupplier eventSource when: #needsValue send: #getTrue to: self. succeeded := eventSource triggerEvent: #needsValue. self should: [succeeded]! ! !EventManagerTest methodsFor: 'running-copying' stamp: 'SqR 11/12/2000 19:38'! testCopy "Ensure that the actionMap is zapped when you make a copy of anEventManager" eventSource when: #blah send: #yourself to: eventListener. self assert: eventSource actionMap keys isEmpty not. self assert: eventSource copy actionMap keys isEmpty! ! !EventManagerTest methodsFor: 'running-dependent action' stamp: 'ar 8/26/2009 21:37'! testBlockReceiverNoArgs eventSource when: #anEvent evaluate:[self heardEvent]. eventSource triggerEvent: #anEvent. self should: [succeeded]! ! !EventManagerTest methodsFor: 'running-dependent action' stamp: 'ar 8/26/2009 21:37'! testBlockReceiverOneArg eventSource when: #anEvent: evaluate:[:arg1| eventListener add: arg1]. eventSource triggerEvent: #anEvent: with: 9. self should: [eventListener includes: 9]! ! !EventManagerTest methodsFor: 'running-dependent action' stamp: 'ar 8/26/2009 21:38'! testBlockReceiverTwoArgs eventSource when: #anEvent:info: evaluate:[:arg1 :arg2| self addArg1: arg1 addArg2: arg2]. eventSource triggerEvent: #anEvent:info: withArguments: #( 9 42 ). self should: [(eventListener includes: 9) and: [eventListener includes: 42]]! ! !EventManagerTest methodsFor: 'running-dependent action' stamp: 'jws 9/7/2000 16:39'! testNoArgumentEvent eventSource when: #anEvent send: #heardEvent to: self. eventSource triggerEvent: #anEvent. self should: [succeeded]! ! !EventManagerTest methodsFor: 'running-dependent action' stamp: 'JWS 9/7/2000 17:20'! testOneArgumentEvent eventSource when: #anEvent: send: #add: to: eventListener. eventSource triggerEvent: #anEvent: with: 9. self should: [eventListener includes: 9]! ! !EventManagerTest methodsFor: 'running-dependent action' stamp: 'JWS 9/7/2000 17:20'! testTwoArgumentEvent eventSource when: #anEvent:info: send: #addArg1:addArg2: to: self. eventSource triggerEvent: #anEvent:info: withArguments: #( 9 42 ). self should: [(eventListener includes: 9) and: [eventListener includes: 42]]! ! !EventManagerTest methodsFor: 'running-dependent action supplied arguments' stamp: 'JWS 9/7/2000 17:20'! testNoArgumentEventDependentSuppliedArgument eventSource when: #anEvent send: #add: to: eventListener with: 'boundValue'. eventSource triggerEvent: #anEvent. self should: [eventListener includes: 'boundValue']! ! !EventManagerTest methodsFor: 'running-dependent action supplied arguments' stamp: 'JWS 9/7/2000 17:21'! testNoArgumentEventDependentSuppliedArguments eventSource when: #anEvent send: #addArg1:addArg2: to: self withArguments: #('hello' 'world'). eventSource triggerEvent: #anEvent. self should: [(eventListener includes: 'hello') and: [eventListener includes: 'world']]! ! !EventManagerTest methodsFor: 'running-dependent value' stamp: 'JWS 9/7/2000 17:21'! testReturnValueWithManyListeners | value newListener | newListener := 'busybody'. eventSource when: #needsValue send: #yourself to: eventListener. eventSource when: #needsValue send: #yourself to: newListener. value := eventSource triggerEvent: #needsValue. self should: [value == newListener]! ! !EventManagerTest methodsFor: 'running-dependent value' stamp: 'JWS 9/7/2000 17:21'! testReturnValueWithNoListeners | value | value := eventSource triggerEvent: #needsValue. self should: [value == nil]! ! !EventManagerTest methodsFor: 'running-dependent value' stamp: 'JWS 9/7/2000 17:21'! testReturnValueWithOneListener | value | eventSource when: #needsValue send: #yourself to: eventListener. value := eventSource triggerEvent: #needsValue. self should: [value == eventListener]! ! !EventManagerTest methodsFor: 'running-remove actions' stamp: 'SqR 2/19/2001 14:01'! testRemoveActionsForEvent eventSource when: #anEvent send: #size to: eventListener; when: #anEvent send: #getTrue to: self; when: #anEvent: send: #fizzbin to: self. eventSource removeActionsForEvent: #anEvent. self shouldnt: [eventSource hasActionForEvent: #anEvent]! ! !EventManagerTest methodsFor: 'running-remove actions' stamp: 'SqR 2/19/2001 14:01'! testRemoveActionsTwiceForEvent eventSource when: #anEvent send: #size to: eventListener; when: #anEvent send: #getTrue to: self; when: #anEvent: send: #fizzbin to: self. eventSource removeActionsForEvent: #anEvent. self assert: (eventSource hasActionForEvent: #anEvent) not. eventSource removeActionsForEvent: #anEvent. self assert: (eventSource hasActionForEvent: #anEvent) not.! ! !EventManagerTest methodsFor: 'running-remove actions' stamp: 'gk 8/14/2007 23:51'! testRemoveActionsWithReceiver | action | eventSource when: #anEvent send: #size to: eventListener; when: #anEvent send: #getTrue to: self; when: #anEvent: send: #fizzbin to: self. self assert: (eventSource hasActionsWithReceiver: self). eventSource removeActionsWithReceiver: self. action := eventSource actionForEvent: #anEvent. self assert: (action respondsTo: #receiver). self assert: ((action receiver == self) not). self assert: ((eventSource hasActionsWithReceiver: self) not)! ! !EventManagerTest methodsFor: 'private' stamp: 'jws 9/7/2000 16:37'! addArg1: arg1 addArg2: arg2 eventListener add: arg1; add: arg2! ! !EventManagerTest methodsFor: 'private' stamp: 'JWS 9/7/2000 17:19'! getFalse ^false! ! !EventManagerTest methodsFor: 'private' stamp: 'JWS 9/7/2000 17:19'! getFalse: anArg ^false! ! !EventManagerTest methodsFor: 'private' stamp: 'JWS 9/7/2000 17:19'! getTrue ^true! ! !EventManagerTest methodsFor: 'private' stamp: 'JWS 9/7/2000 17:19'! getTrue: anArg ^true! ! !EventManagerTest methodsFor: 'private' stamp: 'JWS 9/7/2000 17:20'! heardEvent succeeded := true! ! InputSensor subclass: #EventSensor instanceVariableNames: 'mouseButtons mousePosition keyboardBuffer interruptKey interruptSemaphore eventQueue inputSemaphore lastEventPoll hasInputSemaphore' classVariableNames: 'EventPollPeriod EventTicklerProcess' poolDictionaries: 'EventSensorConstants' category: 'Kernel-Processes'! !EventSensor commentStamp: 'nk 4/13/2004 11:18' prior: 0! EventSensor is a replacement for InputSensor based on a set of (optional) event primitives. An EventSensor updates its state when events are received so that all state based users of Sensor (e.g., Sensor keyboard, Sensor leftShiftDown, Sensor mouseButtons) will work exactly as before, by moving the current VM mechanisms into EventSensor itself. An optional input semaphore is part of the new design. For platforms that support true asynchronous event notification, the semaphore will be signaled to indicate pending events. On platforms that do not support asynchronous notifications about events, the UI will have to poll EventSensor periodically to read events from the VM. Instance variables: mouseButtons - mouse button state as replacement for primMouseButtons mousePosition - mouse position as replacement for primMousePt keyboardBuffer - keyboard input buffer interruptKey - currently defined interrupt key interruptSemaphore - the semaphore signaled when the interruptKey is detected eventQueue - an optional event queue for event driven applications inputSemaphore - the semaphore signaled by the VM if asynchronous event notification is supported lastEventPoll - the last millisecondClockValue at which we called fetchMoreEvents hasInputSemaphore - true if my inputSemaphore has actually been signaled at least once. Class variables: EventPollPeriod - the number of milliseconds to wait between polling for more events in the userInterruptHandler. EventTicklerProcess - the process that makes sure that events are polled for often enough (at least every EventPollPeriod milliseconds). Event format: The current event format is very simple. Each event is recorded into an 8 element array. All events must provide some SmallInteger ID (the first field in the event buffer) and a time stamp (the second field in the event buffer), so that the difference between the time stamp of an event and the current time can be reported. Currently, the following events are defined: Null event ============= The Null event is returned when the ST side asks for more events but no more events are available. Structure: [1] - event type 0 [2-8] - unused Mouse event structure ========================== Mouse events are generated when mouse input is detected. Structure: [1] - event type 1 [2] - time stamp [3] - mouse x position [4] - mouse y position [5] - button state; bitfield with the following entries: 1 - yellow (e.g., right) button 2 - blue (e.g., middle) button 4 - red (e.g., left) button [all other bits are currently undefined] [6] - modifier keys; bitfield with the following entries: 1 - shift key 2 - ctrl key 4 - (Mac specific) option key 8 - Cmd/Alt key [all other bits are currently undefined] [7] - reserved. [8] - reserved. Keyboard events ==================== Keyboard events are generated when keyboard input is detected. [1] - event type 2 [2] - time stamp [3] - character code For now the character code is in Mac Roman encoding. [4] - press state; integer with the following meaning 0 - character 1 - key press (down) 2 - key release (up) [5] - modifier keys (same as in mouse events) [6] - reserved. [7] - reserved. [8] - reserved. ! !EventSensor methodsFor: 'accessing' stamp: 'ar 7/23/2000 14:37'! eventQueue "Return the current event queue" ^eventQueue! ! !EventSensor methodsFor: 'accessing' stamp: 'nk 4/12/2004 19:36'! eventTicklerProcess "Answer my event tickler process, if any" ^EventTicklerProcess! ! !EventSensor methodsFor: 'accessing' stamp: 'JMM 10/5/2001 13:46'! flushAllButDandDEvents | newQueue oldQueue | newQueue := SharedQueue new. self eventQueue ifNil: [self eventQueue: newQueue. ^self]. oldQueue := self eventQueue. [oldQueue size > 0] whileTrue: [| item type | item := oldQueue next. type := item at: 1. type = EventTypeDragDropFiles ifTrue: [ newQueue nextPut: item]]. self eventQueue: newQueue. ! ! !EventSensor methodsFor: 'accessing' stamp: 'ar 2/7/2001 17:13'! flushEvents eventQueue ifNotNil:[eventQueue flush].! ! !EventSensor methodsFor: 'accessing' stamp: 'marcus.denker 9/14/2008 22:00'! nextEvent "Return the next event from the receiver." eventQueue ifNil:[^self nextEventSynthesized] ifNotNil:[^self nextEventFromQueue] ! ! !EventSensor methodsFor: 'accessing' stamp: 'JMM 11/7/2005 14:38'! peekButtons self wait2ms. self fetchMoreEvents. ^mouseButtons! ! !EventSensor methodsFor: 'accessing' stamp: 'JMM 1/15/2007 11:21'! peekEvent "Look ahead at the next event." self fetchMoreEvents. ^self eventQueue peek! ! !EventSensor methodsFor: 'accessing' stamp: 'tpr 1/5/2005 17:34'! peekKeyboardEvent "Return the next keyboard char event from the receiver or nil if none available" ^eventQueue nextOrNilSuchThat: [:buf | buf first = EventTypeKeyboard and: [(buf fourth) = EventKeyChar]]! ! !EventSensor methodsFor: 'accessing' stamp: 'ar 2/8/2001 21:45'! peekMousePt ^mousePosition! ! !EventSensor methodsFor: 'accessing' stamp: 'JMM 11/7/2005 14:38'! peekPosition self wait2ms. self fetchMoreEvents. ^mousePosition! ! !EventSensor methodsFor: 'initialize' stamp: 'alain.plantec 5/28/2009 09:52'! initialize "Initialize the receiver" super initialize. mouseButtons := 0. mousePosition := 0 @ 0. keyboardBuffer := SharedQueue new. eventQueue := SharedQueue new. self setInterruptKey: (interruptKey ifNil: [$. asciiValue bitOr: 16r0800 ]). "cmd-." interruptSemaphore := (Smalltalk specialObjectsArray at: 31) ifNil: [Semaphore new]. self flushAllButDandDEvents. inputSemaphore := Semaphore new. hasInputSemaphore := false.! ! !EventSensor methodsFor: 'initialize' stamp: 'nk 4/12/2004 20:13'! shutDown super shutDown. EventTicklerProcess ifNotNil: [ EventTicklerProcess terminate. EventTicklerProcess := nil. ]. inputSemaphore ifNotNil:[Smalltalk unregisterExternalObject: inputSemaphore]. ! ! !EventSensor methodsFor: 'initialize' stamp: 'pavel.krivanek 11/21/2008 16:54'! startUp "Run the I/O process" self initialize. self primSetInputSemaphore: (Smalltalk registerExternalObject: inputSemaphore). super startUp. self installEventTickler. UIManager default onEventSensorStartup: self.. "Attempt to discover whether the input semaphore is actually being signaled. " hasInputSemaphore := false. inputSemaphore initSignals! ! !EventSensor methodsFor: 'mouse' stamp: 'ar 5/18/2003 18:27'! createMouseEvent "create and return a new mouse event from the current mouse position; this is useful for restarting normal event queue processing after manual polling" | buttons modifiers pos mapped eventBuffer | eventBuffer := Array new: 8. buttons := self primMouseButtons. pos := self primMousePt. modifiers := buttons bitShift: -3. buttons := buttons bitAnd: 7. mapped := self mapButtons: buttons modifiers: modifiers. eventBuffer at: 1 put: EventTypeMouse; at: 2 put: Time millisecondClockValue; at: 3 put: pos x; at: 4 put: pos y; at: 5 put: mapped; at: 6 put: modifiers. ^ eventBuffer! ! !EventSensor methodsFor: 'private' stamp: 'nk 4/12/2004 20:16'! eventTickler "Poll infrequently to make sure that the UI process is not been stuck. If it has been stuck, then spin the event loop so that I can detect the interrupt key." | delay | delay := Delay forMilliseconds: self class eventPollPeriod. self lastEventPoll. "ensure not nil." [| delta | [ delay wait. delta := Time millisecondClockValue - lastEventPoll. (delta < 0 or: [delta > self class eventPollPeriod]) ifTrue: ["force check on rollover" self fetchMoreEvents]] on: Error do: [:ex | ]. true ] whileTrue.! ! !EventSensor methodsFor: 'private' stamp: 'di 10/1/2001 20:52'! flushNonKbdEvents eventQueue ifNil: [^ self]. eventQueue flushAllSuchThat: [:buf | (self isKbdEvent: buf) not] ! ! !EventSensor methodsFor: 'private' stamp: 'nk 6/21/2004 10:40'! installEventTickler "Initialize the interrupt watcher process. Terminate the old process if any." "Sensor installEventTickler" EventTicklerProcess ifNotNil: [EventTicklerProcess terminate]. EventTicklerProcess := [self eventTickler] forkAt: Processor lowIOPriority. ! ! !EventSensor methodsFor: 'private' stamp: 'di 10/1/2001 20:51'! isKbdEvent: buf ^ (buf at: 1) = EventTypeKeyboard and: [(buf at: 4) = EventKeyChar]! ! !EventSensor methodsFor: 'private' stamp: 'nk 3/18/2004 13:21'! lastEventPoll "Answer the last clock value at which fetchMoreEvents was called." ^lastEventPoll ifNil: [ lastEventPoll := Time millisecondClockValue ]! ! !EventSensor methodsFor: 'private' stamp: 'JMM 7/22/2004 14:08'! nextEventFromQueue "Return the next event from the receiver." self eventQueue isEmpty ifTrue:[self fetchMoreEvents]. self eventQueue isEmpty ifTrue:[^nil] ifFalse:[^self eventQueue next]! ! !EventSensor methodsFor: 'private' stamp: 'nk 3/17/2004 07:09'! nextEventSynthesized "Return a synthesized event. This method is called if an event driven client wants to receive events but the primary user interface is not event-driven (e.g., the receiver does not have an event queue but only updates its state). This can, for instance, happen if a Morphic World is run in an MVC window. To simplify the clients work this method will always return all available keyboard events first, and then (repeatedly) the mouse events. Since mouse events come last, the client can assume that after one mouse event has been received there are no more to come. Note that it is impossible for EventSensor to determine if a mouse event has been issued before so the client must be aware of the possible problem of getting repeatedly the same mouse events. See HandMorph>>processEvents for an example on how to deal with this." | kbd array buttons pos modifiers mapped | "First check for keyboard" array := Array new: 8. kbd := self primKbdNext. kbd ifNotNil: ["simulate keyboard event" array at: 1 put: EventTypeKeyboard. "evt type" array at: 2 put: Time millisecondClockValue. "time stamp" array at: 3 put: (kbd bitAnd: 255). "char code" array at: 4 put: EventKeyChar. "key press/release" array at: 5 put: (kbd bitShift: -8). "modifier keys" ^ array]. "Then check for mouse" pos := self primMousePt. buttons := mouseButtons. modifiers := buttons bitShift: -3. buttons := buttons bitAnd: 7. mapped := self mapButtons: buttons modifiers: modifiers. array at: 1 put: EventTypeMouse; at: 2 put: Time millisecondClockValue; at: 3 put: pos x; at: 4 put: pos y; at: 5 put: mapped; at: 6 put: modifiers. ^ array ! ! !EventSensor methodsFor: 'private' stamp: 'ar 7/23/2000 00:34'! primInterruptSemaphore: aSemaphore "Primitive. Install the argument as the semaphore to be signalled whenever the user presses the interrupt key. The semaphore will be signaled once each time the interrupt key is pressed." interruptSemaphore := aSemaphore. "backward compatibility: use the old primitive which is obsolete now" super primInterruptSemaphore: aSemaphore! ! !EventSensor methodsFor: 'private' stamp: 'michael.rueger 2/5/2009 13:59'! primKbdNext "Allows for use of old Sensor protocol to get at the keyboard, as when running kbdTest or the InterpreterSimulator in Morphic" | evtBuf | self wait2ms. self fetchMoreEvents. keyboardBuffer isEmpty ifFalse:[^ keyboardBuffer next]. evtBuf := self eventQueue nextOrNilSuchThat: [:buf | self isKbdEvent: buf]. self flushNonKbdEvents. ^ evtBuf ifNotNil: [evtBuf at: 6]! ! !EventSensor methodsFor: 'private' stamp: 'michael.rueger 2/5/2009 13:59'! primKbdPeek "Allows for use of old Sensor protocol to get at the keyboard, as when running kbdTest or the InterpreterSimulator in Morphic" | char | self wait2ms. self fetchMoreEvents. keyboardBuffer isEmpty ifFalse: [^ keyboardBuffer peek]. char := nil. self eventQueue nextOrNilSuchThat: "NOTE: must not return out of this block, so loop to end" [:buf | (self isKbdEvent: buf) ifTrue: [char ifNil: [char := buf at: 6]]. false "NOTE: block value must be false so Queue won't advance"]. ^ char! ! !EventSensor methodsFor: 'private' stamp: 'JMM 11/7/2005 14:39'! primMouseButtons self wait2ms. self fetchMoreEvents. self flushNonKbdEvents. ^ mouseButtons! ! !EventSensor methodsFor: 'private' stamp: 'JMM 11/7/2005 14:39'! primMousePt self wait2ms. self fetchMoreEvents. self flushNonKbdEvents. ^ mousePosition! ! !EventSensor methodsFor: 'private' stamp: 'ls 10/23/2000 14:14'! primSetInterruptKey: anInteger "Primitive. Register the given keycode as the user interrupt key. The low byte of the keycode is the ISO character and its next four bits are the Smalltalk modifer bits ." interruptKey := anInteger. "backward compatibility: use the old primitive which is obsolete now" super primSetInterruptKey: anInteger! ! !EventSensor methodsFor: 'private' stamp: 'JMM 11/7/2005 14:37'! wait2ms (Delay forMilliseconds: 2) wait.! ! !EventSensor methodsFor: 'private-I/O' stamp: 'nk 4/12/2004 20:01'! fetchMoreEvents "Fetch more events from the VM" | eventBuffer type | "Reset input semaphore so clients can wait for the next events after this one." inputSemaphore isSignaled ifTrue: [ hasInputSemaphore := true. inputSemaphore initSignals ]. "Remember the last time that I checked for events." lastEventPoll := Time millisecondClockValue. eventBuffer := Array new: 8. [self primGetNextEvent: eventBuffer. type := eventBuffer at: 1. type = EventTypeNone] whileFalse: [self processEvent: eventBuffer]. ! ! !EventSensor methodsFor: 'private-I/O' stamp: 'ar 7/30/2000 18:12'! mapButtons: buttons modifiers: modifiers "Map the buttons to yellow or blue based on the given modifiers. If only the red button is pressed, then map Ctrl-RedButton -> BlueButton. Cmd-RedButton -> YellowButton. " (buttons = RedButtonBit) ifFalse:[^buttons]. (modifiers allMask: CtrlKeyBit) ifTrue:[^BlueButtonBit]. (modifiers allMask: CommandKeyBit) ifTrue:[^YellowButtonBit]. ^buttons! ! !EventSensor methodsFor: 'private-I/O' stamp: 'marcus.denker 9/14/2008 21:15'! primGetNextEvent: array "Store the next OS event available into the provided array. Essential. If the VM is not event driven the ST code will fall back to the old-style mechanism and use the state based primitives instead." | kbd buttons modifiers pos mapped | "Simulate the events" array at: 1 put: EventTypeNone. "assume no more events" "First check for keyboard" kbd := super primKbdNext. kbd isNil ifFalse:[ "simulate keyboard event" array at: 1 put: EventTypeKeyboard. "evt type" array at: 2 put: Time millisecondClockValue. "time stamp" array at: 3 put: (kbd bitAnd: 255). "char code" array at: 4 put: EventKeyChar. "key press/release" array at: 5 put: (kbd bitShift: -8). "modifier keys" ^self]. "Then check for mouse" buttons := super primMouseButtons. pos := super primMousePt. modifiers := buttons bitShift: -3. buttons := buttons bitAnd: 7. mapped := self mapButtons: buttons modifiers: modifiers. (pos = mousePosition and:[(mapped bitOr: (modifiers bitShift: 3)) = mouseButtons]) ifTrue:[^self]. array at: 1 put: EventTypeMouse; at: 2 put: Time millisecondClockValue; at: 3 put: pos x; at: 4 put: pos y; at: 5 put: mapped; at: 6 put: modifiers. ! ! !EventSensor methodsFor: 'private-I/O' stamp: 'ar 7/30/2000 18:16'! primSetInputSemaphore: semaIndex "Set the input semaphore the VM should use for asynchronously signaling the availability of events. Primitive. Optional." ^nil! ! !EventSensor methodsFor: 'private-I/O' stamp: 'JMM 1/15/2007 13:10'! processEvent: evt "Process a single event. This method is run at high priority." | type window | type := evt at: 1. window := evt at: 8. (window isNil or: [window isZero]) ifTrue: [window := 1. evt at: 8 put: window]. window := evt at: 8. (window isNil or: [window isZero]) ifTrue: [window := 1. evt at: 8 put: window]. "Tackle mouse events first" type = EventTypeMouse ifTrue: [evt at: 5 put: (ButtonDecodeTable at: (evt at: 5) + 1). self queueEvent: evt. self processMouseEvent: evt . ^self]. "Store the event in the queue if there's any" type = EventTypeKeyboard ifTrue: [ "Check if the event is a user interrupt" ((evt at: 4) = 0 and: [((evt at: 3) bitOr: (((evt at: 5) bitAnd: 8) bitShift: 8)) = interruptKey]) ifTrue: ["interrupt key is meta - not reported as event" ^ interruptSemaphore signal]. "Else swap ctrl/alt keys if neeeded.wi" KeyDecodeTable at: {evt at: 3. evt at: 5} ifPresent: [:a | evt at: 3 put: a first; at: 5 put: a second]. self queueEvent: evt. self processKeyboardEvent: evt . ^self ]. EventTypeWindow = type ifTrue: [self processWindowEvent: evt. ^self]. EventTypeMenu = type ifTrue: [self processMenuEvent: evt. ^self]. "Handle all events other than Keyborad or Mouse." self queueEvent: evt. ! ! !EventSensor methodsFor: 'private-I/O' stamp: 'marcus.denker 9/14/2008 21:15'! processKeyboardEvent: evt "process a keyboard event, updating InputSensor state" | charCode pressCode | "Never update keyboardBuffer if we have an eventQueue active" mouseButtons := (mouseButtons bitAnd: 7) bitOr: ((evt at: 5) bitShift: 3). eventQueue ifNotNil:[^self]. charCode := evt at: 3. charCode isNil ifTrue:[^self]. "extra characters not handled in MVC" pressCode := evt at: 4. pressCode = EventKeyChar ifFalse:[^self]. "key down/up not handled in MVC" "mix in modifiers" charCode := charCode bitOr: ((evt at: 5) bitShift: 8). keyboardBuffer nextPut: charCode.! ! !EventSensor methodsFor: 'private-I/O' stamp: 'JMM 11/12/2004 14:12'! processMenuEvent: evt | handler localCopyOfEvt | localCopyOfEvt := evt clone. handler := (HostSystemMenus defaultMenuBarForWindowIndex: (localCopyOfEvt at: 8)) getHandlerForMenu: (localCopyOfEvt at: 3) item: (localCopyOfEvt at: 4). [[handler handler value: localCopyOfEvt] ifError: [:err :rcvr | ]] forkAt: Processor activePriority.! ! !EventSensor methodsFor: 'private-I/O' stamp: 'ar 8/16/2000 22:07'! processMouseEvent: evt "process a mouse event, updating InputSensor state" | modifiers buttons mapped | mousePosition := (evt at: 3) @ (evt at: 4). buttons := evt at: 5. modifiers := evt at: 6. mapped := self mapButtons: buttons modifiers: modifiers. mouseButtons := mapped bitOr: (modifiers bitShift: 3).! ! !EventSensor methodsFor: 'private-I/O' stamp: 'JMM 10/4/2004 17:41'! processWindowEvent: evt ! ! !EventSensor methodsFor: 'private-I/O' stamp: 'ar 7/23/2000 14:55'! queueEvent: evt "Queue the given event in the event queue (if any). Note that the event buffer must be copied since it will be reused later on." eventQueue ifNil:[^self]. eventQueue nextPut: evt clone.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EventSensor class instanceVariableNames: ''! !EventSensor class methodsFor: 'class initialization' stamp: 'nk 4/12/2004 18:55'! eventPollPeriod ^EventPollPeriod ifNil: [ EventPollPeriod := 500 ].! ! !EventSensor class methodsFor: 'class initialization' stamp: 'nk 4/12/2004 18:55'! eventPollPeriod: msec "Set the number of milliseconds between checking for events to msec." EventPollPeriod := msec max: 10.! ! !EventSensor class methodsFor: 'class initialization' stamp: 'ar 7/23/2000 15:06'! install "EventSensor install" "Install an EventSensor in place of the current Sensor." | newSensor | Sensor shutDown. newSensor := self new. newSensor startUp. "Note: We must use #become: here to replace all references to the old sensor with the new one, since Sensor is referenced from all the existing controllers." Sensor becomeForward: newSensor. "done"! ! SharedPool subclass: #EventSensorConstants instanceVariableNames: '' classVariableNames: 'BlueButtonBit CommandKeyBit CtrlKeyBit EventKeyChar EventKeyDown EventKeyUp EventTypeDragDropFiles EventTypeKeyboard EventTypeMenu EventTypeMouse EventTypeNone EventTypeWindow OptionKeyBit RedButtonBit ShiftKeyBit WindowEventActivated WindowEventClose WindowEventIconise WindowEventMetricChange WindowEventPaint YellowButtonBit' poolDictionaries: '' category: 'Kernel-Processes'! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EventSensorConstants class instanceVariableNames: ''! !EventSensorConstants class methodsFor: 'pool initialization' stamp: 'John M McIntosh 10/31/2008 14:34'! initialize "EventSensorConstants initialize" RedButtonBit := 4. BlueButtonBit := 2. YellowButtonBit := 1. ShiftKeyBit := 1. CtrlKeyBit := 2. OptionKeyBit := 4. CommandKeyBit := 8. "Types of events" EventTypeNone := 0. EventTypeMouse := 1. EventTypeKeyboard := 2. EventTypeDragDropFiles := 3. EventTypeMenu := 4. EventTypeWindow := 5. "Press codes for keyboard events" EventKeyChar := 0. EventKeyDown := 1. EventKeyUp := 2. "Window event action codes" WindowEventMetricChange := 1. " size or position of window changed - value1-4 are left/top/right/bottom values " WindowEventClose := 2. " window close icon pressed " WindowEventIconise := 3. " window iconised or hidden etc " WindowEventActivated :=4. " window made active - some platforms only - do not rely upon this " WindowEventPaint := 5. " window area (in value1-4) needs updating. Some platforms do not need to send this, do not rely on it in image " ! ! TestCase subclass: #EventTest instanceVariableNames: 'eventSource eventListener succeeded' classVariableNames: '' poolDictionaries: '' category: 'Tests-Object Events'! !EventTest methodsFor: 'running' stamp: 'jws 9/7/2000 16:37'! setUp super setUp. eventSource := Object new. eventListener := Bag new. succeeded := false! ! !EventTest methodsFor: 'running' stamp: 'jws 11/28/2000 16:25'! tearDown eventSource releaseActionMap. eventSource := nil. eventListener := nil. super tearDown. ! ! !EventTest methodsFor: 'running-broadcast query' stamp: 'jws 9/7/2000 16:41'! testMultipleValueSuppliers eventSource when: #needsValue send: #getFalse to: self. eventSource when: #needsValue send: #getTrue to: self. succeeded := eventSource triggerEvent: #needsValue. self should: [succeeded]! ! !EventTest methodsFor: 'running-broadcast query' stamp: 'jws 9/7/2000 16:41'! testMultipleValueSuppliersEventHasArguments eventSource when: #needsValue: send: #getFalse: to: self. eventSource when: #needsValue: send: #getTrue: to: self. succeeded := eventSource triggerEvent: #needsValue: with: 'kolme'. self should: [succeeded]! ! !EventTest methodsFor: 'running-broadcast query' stamp: 'marcus.denker 9/14/2008 21:15'! testMultipleValueSuppliersEventHasArgumentsWithGC eventSource when: #needsValue: send: #getFalse: to: self with: Object new. eventSource when: #needsValue: send: #getTrue: to: self with: Object new. Smalltalk garbageCollectMost. succeeded := eventSource triggerEvent: #needsValue: with: 'kolme'. self should: [succeeded isNil] ! ! !EventTest methodsFor: 'running-broadcast query' stamp: 'jws 9/7/2000 16:41'! testNoValueSupplier succeeded := eventSource triggerEvent: #needsValue ifNotHandled: [true]. self should: [succeeded]! ! !EventTest methodsFor: 'running-broadcast query' stamp: 'jws 9/7/2000 16:41'! testNoValueSupplierHasArguments succeeded := eventSource triggerEvent: #needsValue: with: 'nelja' ifNotHandled: [true]. self should: [succeeded]! ! !EventTest methodsFor: 'running-broadcast query' stamp: 'jws 9/7/2000 16:42'! testSingleValueSupplier eventSource when: #needsValue send: #getTrue to: self. succeeded := eventSource triggerEvent: #needsValue. self should: [succeeded]! ! !EventTest methodsFor: 'running-dependent action' stamp: 'jws 9/7/2000 16:39'! testNoArgumentEvent eventSource when: #anEvent send: #heardEvent to: self. eventSource triggerEvent: #anEvent. self should: [succeeded]! ! !EventTest methodsFor: 'running-dependent action' stamp: 'jws 9/7/2000 16:39'! testOneArgumentEvent eventSource when: #anEvent: send: #add: to: eventListener. eventSource triggerEvent: #anEvent: with: 9. self should: [eventListener includes: 9]! ! !EventTest methodsFor: 'running-dependent action' stamp: 'jws 9/7/2000 16:39'! testTwoArgumentEvent eventSource when: #anEvent:info: send: #addArg1:addArg2: to: self. eventSource triggerEvent: #anEvent:info: withArguments: #( 9 42 ). self should: [(eventListener includes: 9) and: [eventListener includes: 42]]! ! !EventTest methodsFor: 'running-dependent action supplied arguments' stamp: 'jws 9/7/2000 16:39'! testNoArgumentEventDependentSuppliedArgument eventSource when: #anEvent send: #add: to: eventListener with: 'boundValue'. eventSource triggerEvent: #anEvent. self should: [eventListener includes: 'boundValue']! ! !EventTest methodsFor: 'running-dependent action supplied arguments' stamp: 'jws 9/7/2000 16:40'! testNoArgumentEventDependentSuppliedArguments eventSource when: #anEvent send: #addArg1:addArg2: to: self withArguments: #('hello' 'world'). eventSource triggerEvent: #anEvent. self should: [(eventListener includes: 'hello') and: [eventListener includes: 'world']]! ! !EventTest methodsFor: 'running-dependent value' stamp: 'jws 9/7/2000 16:40'! testReturnValueWithManyListeners | value newListener | newListener := 'busybody'. eventSource when: #needsValue send: #yourself to: eventListener. eventSource when: #needsValue send: #yourself to: newListener. value := eventSource triggerEvent: #needsValue. self should: [value == newListener]! ! !EventTest methodsFor: 'running-dependent value' stamp: 'jws 9/7/2000 16:40'! testReturnValueWithNoListeners | value | value := eventSource triggerEvent: #needsValue. self should: [value == nil]! ! !EventTest methodsFor: 'running-dependent value' stamp: 'jws 9/7/2000 16:40'! testReturnValueWithOneListener | value | eventSource when: #needsValue send: #yourself to: eventListener. value := eventSource triggerEvent: #needsValue. self should: [value == eventListener]! ! !EventTest methodsFor: 'running-remove actions' stamp: 'SqR 2/19/2001 14:04'! testRemoveActionsForEvent eventSource when: #anEvent send: #size to: eventListener; when: #anEvent send: #getTrue to: self; when: #anEvent: send: #fizzbin to: self. eventSource removeActionsForEvent: #anEvent. self shouldnt: [eventSource hasActionForEvent: #anEvent]! ! !EventTest methodsFor: 'running-remove actions' stamp: 'SqR 2/19/2001 14:05'! testRemoveActionsTwiceForEvent eventSource when: #anEvent send: #size to: eventListener; when: #anEvent send: #getTrue to: self; when: #anEvent: send: #fizzbin to: self. eventSource removeActionsForEvent: #anEvent. self assert: (eventSource hasActionForEvent: #anEvent) not. eventSource removeActionsForEvent: #anEvent. self assert: (eventSource hasActionForEvent: #anEvent) not.! ! !EventTest methodsFor: 'running-remove actions' stamp: 'SqR 2/19/2001 14:05'! testRemoveActionsWithReceiver | action | eventSource when: #anEvent send: #size to: eventListener; when: #anEvent send: #getTrue to: self; when: #anEvent: send: #fizzbin to: self. eventSource removeActionsWithReceiver: self. action := eventSource actionForEvent: #anEvent. self assert: (action respondsTo: #receiver). self assert: ((action receiver == self) not)! ! !EventTest methodsFor: 'private' stamp: 'jws 9/7/2000 16:37'! addArg1: arg1 addArg2: arg2 eventListener add: arg1; add: arg2! ! !EventTest methodsFor: 'private' stamp: 'jws 9/7/2000 16:37'! getFalse ^false! ! !EventTest methodsFor: 'private' stamp: 'jws 9/7/2000 16:37'! getFalse: anArg ^false! ! !EventTest methodsFor: 'private' stamp: 'jws 9/7/2000 16:38'! getTrue ^true! ! !EventTest methodsFor: 'private' stamp: 'jws 9/7/2000 16:38'! getTrue: anArg ^true! ! !EventTest methodsFor: 'private' stamp: 'jws 9/7/2000 16:38'! heardEvent succeeded := true! ! MorphicModel subclass: #ExampleBuilderMorph uses: TEasilyThemed instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !ExampleBuilderMorph commentStamp: 'gvc 7/19/2007 16:49' prior: 0! Morph with an inset border by default and theme access. Overrides openModal: to allow multiple free example dialogs to be presented.! !ExampleBuilderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 12/11/2007 16:53'! openModal: aSystemWindow "Open the given window an available position without modality. Answer the system window." |baseArea areas searching foundRect| aSystemWindow extent: aSystemWindow initialExtent. areas := World submorphs select: [:m | m isKindOf: DialogWindow] thenCollect: [:m | m bounds expandBy: 8]. . baseArea := (RealEstateAgent reduceByFlaps: RealEstateAgent maximumUsableArea) insetBy: 8. searching := true. baseArea allAreasOutsideList: areas do: [:rect | searching ifTrue: [ aSystemWindow extent <= (rect insetBy: 8) extent ifTrue: [foundRect := rect. searching := false]]]. searching ifTrue: [foundRect := baseArea]. aSystemWindow setWindowColor: self theme windowColor. aSystemWindow position: foundRect topLeft + 8. aSystemWindow openAsIs. ^aSystemWindow! ! !ExampleBuilderMorph methodsFor: 'controls'! newAlphaImage: aForm help: helpText "Answer an alpha image morph." ^self theme newAlphaImageIn: self image: aForm help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newAlphaSelector: aModel getAlpha: getSel setAlpha: setSel help: helpText "Answer an alpha channel selector with the given selectors." ^self theme newAlphaSelectorIn: self for: aModel getAlpha: getSel setAlpha: setSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newAutoAcceptTextEditorFor: aModel getText: getSel setText: setSel getEnabled: enabledSel "Answer a text editor for the given model." ^self theme newAutoAcceptTextEditorIn: self for: aModel getText: getSel setText: setSel getEnabled: enabledSel! ! !ExampleBuilderMorph methodsFor: 'controls'! newAutoAcceptTextEntryFor: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel font: aFont help: helpText "Answer a text entry for the given model." ^self theme newAutoAcceptTextEntryIn: self for: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel font: aFont help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newAutoAcceptTextEntryFor: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel help: helpText "Answer a text entry for the given model." ^self theme newAutoAcceptTextEntryIn: self for: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newAutoAcceptTextEntryFor: aModel getText: getSel setText: setSel getEnabled: enabledSel font: aFont help: helpText "Answer a text entry for the given model." ^self theme newAutoAcceptTextEntryIn: self for: aModel get: getSel set: setSel class: String getEnabled: enabledSel font: aFont help: helpText ! ! !ExampleBuilderMorph methodsFor: 'controls'! newAutoAcceptTextEntryFor: aModel getText: getSel setText: setSel getEnabled: enabledSel help: helpText "Answer a text entry for the given model." ^self theme newAutoAcceptTextEntryIn: self for: aModel get: getSel set: setSel class: String getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newBalloonHelp: aTextStringOrMorph for: aMorph "Answer a new balloon help with the given contents for aMorph at a given corner." ^self theme newBalloonHelpIn: self contents: aTextStringOrMorph for: aMorph corner: #bottomLeft! ! !ExampleBuilderMorph methodsFor: 'controls'! newBalloonHelp: aTextStringOrMorph for: aMorph corner: cornerSymbol "Answer a new balloon help with the given contents for aMorph at a given corner." ^self theme newBalloonHelpIn: self contents: aTextStringOrMorph for: aMorph corner: cornerSymbol! ! !ExampleBuilderMorph methodsFor: 'controls'! newBracketSliderFor: aModel getValue: getSel setValue: setSel min: minValue max: maxValue quantum: quantum getEnabled: enabledSel help: helpText "Answer a bracket slider with the given selectors." ^self theme newBracketSliderIn: self for: aModel getValue: getSel setValue: setSel min: minValue max: maxValue quantum: quantum getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newBracketSliderFor: aModel getValue: getSel setValue: setSel min: minValue max: maxValue quantum: quantum help: helpText "Answer a bracket slider with the given selectors." ^self newBracketSliderFor: aModel getValue: getSel setValue: setSel min: minValue max: maxValue quantum: quantum getEnabled: nil help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newButtonFor: aModel action: actionSel getEnabled: enabledSel label: stringOrText help: helpText "Answer a new button." ^self newButtonFor: aModel getState: nil action: actionSel arguments: nil getEnabled: enabledSel label: stringOrText help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newButtonFor: aModel action: actionSel label: stringOrText help: helpText "Answer a new button." ^self newButtonFor: aModel getState: nil action: actionSel arguments: nil getEnabled: nil label: stringOrText help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newButtonFor: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel getLabel: labelSel help: helpText "Answer a new button." ^self theme newButtonIn: self for: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel getLabel: labelSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newButtonFor: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel label: stringOrText help: helpText "Answer a new button." ^self theme newButtonIn: self for: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel label: stringOrText help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newButtonFor: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel labelForm: aForm help: helpText "Answer a new button." ^self theme newButtonIn: self for: aModel getState: stateSel action: actionSel arguments: args getEnabled: enabledSel label: (AlphaImageMorph new image: aForm) help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newCancelButton "Answer a new cancel button." ^self newCancelButtonFor: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newCancelButtonFor: aModel "Answer a new cancel button." ^self theme newCancelButtonIn: self for: aModel! ! !ExampleBuilderMorph methodsFor: 'controls'! newCheckboxFor: aModel getSelected: getSel setSelected: setSel getEnabled: enabledSel label: stringOrText help: helpText "Answer a checkbox with the given label." ^self theme newCheckboxIn: self for: aModel getSelected: getSel setSelected: setSel getEnabled: enabledSel label: stringOrText help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newCheckboxFor: aModel getSelected: getSel setSelected: setSel label: stringOrText help: helpText "Answer a checkbox with the given label." ^self theme newCheckboxIn: self for: aModel getSelected: getSel setSelected: setSel getEnabled: nil label: stringOrText help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newCloseButton "Answer a new close button." ^self newCloseButtonFor: self ! ! !ExampleBuilderMorph methodsFor: 'controls'! newCloseButtonFor: aModel "Answer a new close button." ^self theme newCloseButtonIn: self for: aModel! ! !ExampleBuilderMorph methodsFor: 'controls'! newColorChooserFor: aModel getColor: getSel setColor: setSel getEnabled: enabledSel help: helpText "Answer a color chooser with the given selectors." ^self theme newColorChooserIn: self for: aModel getColor: getSel setColor: setSel getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newColorChooserFor: aModel getColor: getSel setColor: setSel help: helpText "Answer a color chooser with the given selectors." ^self theme newColorChooserIn: self for: aModel getColor: getSel setColor: setSel getEnabled: nil help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newColorPickerFor: target getter: getterSymbol setter: setterSymbol "Answer a new color picker for the given morph and accessors." ^self theme newColorPickerIn: self for: target getter: getterSymbol setter: setterSymbol! ! !ExampleBuilderMorph methodsFor: 'controls'! newColorPresenterFor: aModel getColor: getSel help: helpText "Answer a color presenter with the given selectors." ^self theme newColorPresenterIn: self for: aModel getColor: getSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newColumn: controls "Answer a morph laid out with a column of controls." ^self theme newColumnIn: self for: controls! ! !ExampleBuilderMorph methodsFor: 'controls'! newDialogPanel "Answer a new main dialog panel." ^self theme newDialogPanelIn: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel help: helpText "Answer a drop list for the given model." ^self theme newDropListIn: self for: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: true help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: useIndex help: helpText "Answer a drop list for the given model." ^self theme newDropListIn: self for: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: useIndex help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel help: helpText "Answer a drop list for the given model." ^self newDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: nil useIndex: true help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newEmbeddedMenu "Answer a new menu." ^self theme newEmbeddedMenuIn: self for: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newExpander: aString "Answer an expander with the given label." ^self theme newExpanderIn: self label: aString forAll: #()! ! !ExampleBuilderMorph methodsFor: 'controls'! newExpander: aString for: aControl "Answer an expander with the given label and control." ^self theme newExpanderIn: self label: aString forAll: {aControl}! ! !ExampleBuilderMorph methodsFor: 'controls'! newExpander: aString forAll: controls "Answer an expander with the given label and controls." ^self theme newExpanderIn: self label: aString forAll: controls! ! !ExampleBuilderMorph methodsFor: 'controls'! newFuzzyLabel: aString "Answer a new fuzzy label." ^self theme newFuzzyLabelIn: self for: nil label: aString offset: 1 alpha: 0.5 getEnabled: nil! ! !ExampleBuilderMorph methodsFor: 'controls'! newFuzzyLabelFor: aModel label: aString getEnabled: enabledSel "Answer a new fuzzy label." ^self theme newFuzzyLabelIn: self for: aModel label: aString offset: 1 alpha: 0.5 getEnabled: enabledSel! ! !ExampleBuilderMorph methodsFor: 'controls'! newFuzzyLabelFor: aModel label: aString offset: offset alpha: alpha getEnabled: enabledSel "Answer a new fuzzy label." ^self theme newFuzzyLabelIn: self for: aModel label: aString offset: offset alpha: alpha getEnabled: enabledSel! ! !ExampleBuilderMorph methodsFor: 'controls'! newGroupbox "Answer a plain groupbox." ^self theme newGroupboxIn: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newGroupbox: aString "Answer a groupbox with the given label." ^self theme newGroupboxIn: self label: aString! ! !ExampleBuilderMorph methodsFor: 'controls'! newGroupbox: aString for: control "Answer a groupbox with the given label and control." ^self theme newGroupboxIn: self label: aString for: control! ! !ExampleBuilderMorph methodsFor: 'controls'! newGroupbox: aString forAll: controls "Answer a groupbox with the given label and controls." ^self theme newGroupboxIn: self label: aString forAll: controls! ! !ExampleBuilderMorph methodsFor: 'controls'! newGroupboxFor: control "Answer a plain groupbox with the given control." ^self theme newGroupboxIn: self for: control! ! !ExampleBuilderMorph methodsFor: 'controls'! newGroupboxForAll: controls "Answer a plain groupbox with the given controls." ^self theme newGroupboxIn: self forAll: controls! ! !ExampleBuilderMorph methodsFor: 'controls'! newHSVASelector: aColor help: helpText "Answer a hue-saturation-volume selector with the given color." ^self theme newHSVASelectorIn: self color: aColor help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newHSVSelector: aColor help: helpText "Answer a hue-saturation-volume selector with the given color." ^self theme newHSVSelectorIn: self color: aColor help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newHueSelector: aModel getHue: getSel setHue: setSel help: helpText "Answer a hue selector with the given selectors." ^self theme newHueSelectorIn: self for: aModel getHue: getSel setHue: setSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newImage: aForm "Answer a new image." ^self theme newImageIn: self form: aForm! ! !ExampleBuilderMorph methodsFor: 'controls'! newImage: aForm size: aPoint "Answer a new image." ^self theme newImageIn: self form: aForm size: aPoint! ! !ExampleBuilderMorph methodsFor: 'controls'! newIncrementalSliderFor: aModel getValue: getSel setValue: setSel min: min max: max quantum: quantum getEnabled: enabledSel help: helpText "Answer an inremental slider with the given selectors." ^self theme newIncrementalSliderIn: self for: aModel getValue: getSel setValue: setSel min: min max: max quantum: quantum getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newLabel: aString "Answer a new text label." ^self newLabelFor: nil label: aString getEnabled: nil! ! !ExampleBuilderMorph methodsFor: 'controls'! newLabelFor: aModel label: aString getEnabled: enabledSel "Answer a new text label." ^self theme newLabelIn: self for: aModel label: aString getEnabled: enabledSel! ! !ExampleBuilderMorph methodsFor: 'controls'! newLabelGroup: labelsAndControls "Answer a morph laid out with a column of labels and a column of associated controls." ^self theme newLabelGroupIn: self for: labelsAndControls spaceFill: false! ! !ExampleBuilderMorph methodsFor: 'controls'! newLabelGroup: labelsAndControls font: aFont labelColor: aColor "Answer a morph laid out with a column of labels and a column of associated controls." ^self theme newLabelGroupIn: self for: labelsAndControls spaceFill: false font: aFont labelColor: aColor ! ! !ExampleBuilderMorph methodsFor: 'controls'! newLabelGroupSpread: labelsAndControls "Answer a morph laid out with a column of labels and a column of associated controls." ^self theme newLabelGroupIn: self for: labelsAndControls spaceFill: true! ! !ExampleBuilderMorph methodsFor: 'controls'! newListFor: aModel list: listSelector selected: getSelector changeSelected: setSelector getEnabled: enabledSel help: helpText "Answer a list for the given model." ^self theme newListIn: self for: aModel list: listSelector selected: getSelector changeSelected: setSelector getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newListFor: aModel list: listSelector selected: getSelector changeSelected: setSelector help: helpText "Answer a list for the given model." ^self newListFor: aModel list: listSelector selected: getSelector changeSelected: setSelector getEnabled: nil help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newMenu "Answer a new menu." ^self theme newMenuIn: self for: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newMenuFor: aModel "Answer a new menu." ^self theme newMenuIn: self for: aModel! ! !ExampleBuilderMorph methodsFor: 'controls'! newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel help: helpText "Answer a morph drop list for the given model." ^self newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: true help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: useIndex help: helpText "Answer a morph drop list for the given model." ^self theme newMorphDropListIn: self for: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: enabledSel useIndex: useIndex help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel help: helpText "Answer a morph drop list for the given model." ^self newMorphDropListFor: aModel list: listSel getSelected: getSel setSelected: setSel getEnabled: nil useIndex: true help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newMorphListFor: aModel list: listSelector getSelected: getSelector setSelected: setSelector getEnabled: enabledSel help: helpText "Answer a morph list for the given model." ^self theme newMorphListIn: self for: aModel list: listSelector getSelected: getSelector setSelected: setSelector getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newMorphListFor: aModel list: listSelector getSelected: getSelector setSelected: setSelector help: helpText "Answer a morph list for the given model." ^self newMorphListFor: aModel list: listSelector getSelected: getSelector setSelected: setSelector getEnabled: nil help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newNoButton "Answer a new No button." ^self newNoButtonFor: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newNoButtonFor: aModel "Answer a new No button." ^self theme newNoButtonIn: self for: aModel! ! !ExampleBuilderMorph methodsFor: 'controls'! newOKButton "Answer a new OK button." ^self newOKButtonFor: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newOKButtonFor: aModel "Answer a new OK button." ^self newOKButtonFor: aModel getEnabled: nil! ! !ExampleBuilderMorph methodsFor: 'controls'! newOKButtonFor: aModel getEnabled: enabledSel "Answer a new OK button." ^self theme newOKButtonIn: self for: aModel getEnabled: enabledSel! ! !ExampleBuilderMorph methodsFor: 'controls'! newPanel "Answer a new panel." ^self theme newPanelIn: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newPluggableDialogWindow "Answer a new pluggable dialog." ^self newPluggableDialogWindow: 'Dialog'! ! !ExampleBuilderMorph methodsFor: 'controls'! newPluggableDialogWindow: title "Answer a new pluggable dialog with the given content." ^self newPluggableDialogWindow: title for: nil! ! !ExampleBuilderMorph methodsFor: 'controls'! newPluggableDialogWindow: title for: contentMorph "Answer a new pluggable dialog with the given content." ^self theme newPluggableDialogWindowIn: self title: title for: contentMorph! ! !ExampleBuilderMorph methodsFor: 'controls'! newRadioButtonFor: aModel getSelected: getSel setSelected: setSel getEnabled: enabledSel label: stringOrText help: helpText "Answer a checkbox (radio button appearance) with the given label." ^self theme newRadioButtonIn: self for: aModel getSelected: getSel setSelected: setSel getEnabled: enabledSel label: stringOrText help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newRadioButtonFor: aModel getSelected: getSel setSelected: setSel label: stringOrText help: helpText "Answer a checkbox (radio button appearance) with the given label." ^self newRadioButtonFor: aModel getSelected: getSel setSelected: setSel getEnabled: nil label: stringOrText help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newRow "Answer a morph laid out as a row." ^self theme newRowIn: self for: #()! ! !ExampleBuilderMorph methodsFor: 'controls'! newRow: controls "Answer a morph laid out with a row of controls." ^self theme newRowIn: self for: controls! ! !ExampleBuilderMorph methodsFor: 'controls'! newSVSelector: aColor help: helpText "Answer a saturation-volume selector with the given color." ^self theme newSVSelectorIn: self color: aColor help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newSeparator "Answer an horizontal separator." ^self theme newSeparatorIn: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newSliderFor: aModel getValue: getSel setValue: setSel getEnabled: enabledSel help: helpText "Answer a slider with the given selectors." ^self theme newSliderIn: self for: aModel getValue: getSel setValue: setSel min: 0 max: 1 quantum: nil getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newSliderFor: aModel getValue: getSel setValue: setSel help: helpText "Answer a slider with the given selectors." ^self theme newSliderIn: self for: aModel getValue: getSel setValue: setSel min: 0 max: 1 quantum: nil getEnabled: nil help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newSliderFor: aModel getValue: getSel setValue: setSel min: min max: max quantum: quantum getEnabled: enabledSel help: helpText "Answer a slider with the given selectors." ^self theme newSliderIn: self for: aModel getValue: getSel setValue: setSel min: min max: max quantum: quantum getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newString: aStringOrText "Answer a new embossed string." ^self theme newStringIn: self label: aStringOrText font: self theme labelFont style: #plain! ! !ExampleBuilderMorph methodsFor: 'controls'! newString: aStringOrText font: aFont style: aStyle "Answer a new embossed string." ^self theme newStringIn: self label: aStringOrText font: aFont style: aStyle! ! !ExampleBuilderMorph methodsFor: 'controls'! newString: aStringOrText style: aStyle "Answer a new embossed string." ^self theme newStringIn: self label: aStringOrText font: self theme labelFont style: aStyle! ! !ExampleBuilderMorph methodsFor: 'controls'! newTabGroup: labelsAndPages "Answer a tab group with the given tab labels associated with pages." ^self theme newTabGroupIn: self for: labelsAndPages! ! !ExampleBuilderMorph methodsFor: 'controls'! newText: aStringOrText "Answer a new text." ^self theme newTextIn: self text: aStringOrText! ! !ExampleBuilderMorph methodsFor: 'controls'! newTextEditorFor: aModel getText: getSel setText: setSel "Answer a text editor for the given model." ^self newTextEditorFor: aModel getText: getSel setText: setSel getEnabled: nil! ! !ExampleBuilderMorph methodsFor: 'controls'! newTextEditorFor: aModel getText: getSel setText: setSel getEnabled: enabledSel "Answer a text editor for the given model." ^self theme newTextEditorIn: self for: aModel getText: getSel setText: setSel getEnabled: enabledSel ! ! !ExampleBuilderMorph methodsFor: 'controls'! newTextEntryFor: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel help: helpText "Answer a text entry for the given model." ^self theme newTextEntryIn: self for: aModel get: getSel set: setSel class: aClass getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newTextEntryFor: aModel getText: getSel setText: setSel getEnabled: enabledSel help: helpText "Answer a text entry for the given model." ^self theme newTextEntryIn: self for: aModel get: getSel set: setSel class: String getEnabled: enabledSel help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newTextEntryFor: aModel getText: getSel setText: setSel help: helpText "Answer a text entry for the given model." ^self newTextEntryFor: aModel get: getSel set: setSel class: String getEnabled: nil help: helpText! ! !ExampleBuilderMorph methodsFor: 'controls'! newTitle: aString for: control "Answer a morph laid out with a column with a title." ^self theme newTitleIn: self label: aString for: control! ! !ExampleBuilderMorph methodsFor: 'controls'! newToolDockingBar "Answer a tool docking bar." ^self theme newToolDockingBarIn: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newToolSpacer "Answer a tool spacer." ^self theme newToolSpacerIn: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newToolbar "Answer a toolbar." ^self theme newToolbarIn: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newToolbar: controls "Answer a toolbar with the given controls." ^self theme newToolbarIn: self for: controls! ! !ExampleBuilderMorph methodsFor: 'controls'! newToolbarHandle "Answer a toolbar handle." ^self theme newToolbarHandleIn: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newTreeFor: aModel list: listSelector selected: getSelector changeSelected: setSelector "Answer a new tree morph." ^self theme newTreeIn: self for: aModel list: listSelector selected: getSelector changeSelected: setSelector! ! !ExampleBuilderMorph methodsFor: 'controls'! newVerticalSeparator "Answer a vertical separator." ^self theme newVerticalSeparatorIn: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newYesButton "Answer a new Yes button." ^self newYesButtonFor: self! ! !ExampleBuilderMorph methodsFor: 'controls'! newYesButtonFor: aModel "Answer a new yes button." ^self theme newYesButtonIn: self for: aModel! ! !ExampleBuilderMorph methodsFor: 'services'! abort: aStringOrText "Open an error dialog." ^self abort: aStringOrText title: 'Error' translated! ! !ExampleBuilderMorph methodsFor: 'services'! abort: aStringOrText title: aString "Open an error dialog." ^self theme abortIn: self text: aStringOrText title: aString! ! !ExampleBuilderMorph methodsFor: 'services'! alert: aStringOrText "Open an alert dialog." ^self alert: aStringOrText title: 'Alert' translated! ! !ExampleBuilderMorph methodsFor: 'services'! alert: aStringOrText title: aString "Open an alert dialog." ^self alert: aStringOrText title: aString configure: [:d | ]! ! !ExampleBuilderMorph methodsFor: 'services'! alert: aStringOrText title: aString configure: aBlock "Open an alert dialog. Configure the dialog with the 1 argument block before opening modally." ^self theme alertIn: self text: aStringOrText title: aString configure: aBlock! ! !ExampleBuilderMorph methodsFor: 'services'! chooseColor "Answer the result of a color selector dialog ." ^self chooseColor: Color black! ! !ExampleBuilderMorph methodsFor: 'services'! chooseColor: aColor "Answer the result of a color selector dialog with the given color." ^self theme chooseColorIn: self title: 'Colour Selector' translated color: aColor! ! !ExampleBuilderMorph methodsFor: 'services'! chooseColor: aColor title: title "Answer the result of a color selector dialog with the given title and initial colour." ^self theme chooseColorIn: self title: title color: aColor! ! !ExampleBuilderMorph methodsFor: 'services'! chooseDirectory: title "Answer the result of a file dialog with the given title, answer a directory." ^self chooseDirectory: title path: nil! ! !ExampleBuilderMorph methodsFor: 'services'! chooseDirectory: title path: path "Answer the result of a file dialog with the given title, answer a directory." ^self theme chooseDirectoryIn: self title: title path: path! ! !ExampleBuilderMorph methodsFor: 'services'! chooseDropList: aStringOrText list: aList "Open a drop list chooser dialog." ^self chooseDropList: aStringOrText title: 'Choose' translated list: aList! ! !ExampleBuilderMorph methodsFor: 'services'! chooseDropList: aStringOrText title: aString list: aList "Open a drop list chooser dialog." ^self theme chooseDropListIn: self text: aStringOrText title: aString list: aList! ! !ExampleBuilderMorph methodsFor: 'services'! chooseFileName: title extensions: exts path: path preview: preview "Answer the result of a file name chooser dialog with the given title, extensions to show, path and preview type." ^self theme chooseFileNameIn: self title: title extensions: exts path: path preview: preview! ! !ExampleBuilderMorph methodsFor: 'services'! chooseFont "Answer the result of a font selector dialog." ^self chooseFont: nil! ! !ExampleBuilderMorph methodsFor: 'services'! chooseFont: aFont "Answer the result of a font selector dialog with the given initial font." ^self theme chooseFontIn: self title: 'Font Selector' translated font: aFont! ! !ExampleBuilderMorph methodsFor: 'services'! deny: aStringOrText "Open a denial dialog." ^self deny: aStringOrText title: 'Access Denied' translated! ! !ExampleBuilderMorph methodsFor: 'services'! deny: aStringOrText title: aString "Open a denial dialog." ^self theme denyIn: self text: aStringOrText title: aString! ! !ExampleBuilderMorph methodsFor: 'services'! fileOpen: title "Answer the result of a file open dialog with the given title." ^self fileOpen: title extensions: nil! ! !ExampleBuilderMorph methodsFor: 'services'! fileOpen: title extensions: exts "Answer the result of a file open dialog with the given title and extensions to show." ^self fileOpen: title extensions: exts path: nil! ! !ExampleBuilderMorph methodsFor: 'services'! fileOpen: title extensions: exts path: path "Answer the result of a file open dialog with the given title, extensions to show and path." ^self fileOpen: title extensions: exts path: path preview: nil! ! !ExampleBuilderMorph methodsFor: 'services'! fileOpen: title extensions: exts path: path preview: preview "Answer the result of a file open dialog with the given title, extensions to show, path and preview type." ^self theme fileOpenIn: self title: title extensions: exts path: path preview: preview! ! !ExampleBuilderMorph methodsFor: 'services'! fileSave: title "Answer the result of a file save dialog with the given title." ^self fileSave: title extensions: nil path: nil! ! !ExampleBuilderMorph methodsFor: 'services'! fileSave: title extensions: exts "Answer the result of a file save dialog with the given title." ^self fileSave: title extensions: exts path: nil! ! !ExampleBuilderMorph methodsFor: 'services'! fileSave: title extensions: exts path: path "Answer the result of a file save dialog with the given title, extensions to show and path." ^self theme fileSaveIn: self title: title extensions: exts path: path! ! !ExampleBuilderMorph methodsFor: 'services'! fileSave: title path: path "Answer the result of a file save open dialog with the given title." ^self fileSave: title extensions: nil path: path! ! !ExampleBuilderMorph methodsFor: 'services'! longMessage: aStringOrText title: aString "Open a (long) message dialog." ^self theme longMessageIn: self text: aStringOrText title: aString! ! !ExampleBuilderMorph methodsFor: 'services'! message: aStringOrText "Open a message dialog." ^self message: aStringOrText title: 'Information' translated! ! !ExampleBuilderMorph methodsFor: 'services'! message: aStringOrText title: aString "Open a message dialog." ^self theme messageIn: self text: aStringOrText title: aString! ! !ExampleBuilderMorph methodsFor: 'services'! proceed: aStringOrText "Open a proceed dialog." ^self proceed: aStringOrText title: 'Proceed' translated! ! !ExampleBuilderMorph methodsFor: 'services'! proceed: aStringOrText title: aString "Open a proceed dialog and answer true if not cancelled, false otherwise." ^self theme proceedIn: self text: aStringOrText title: aString! ! !ExampleBuilderMorph methodsFor: 'services'! question: aStringOrText "Open a question dialog." ^self question: aStringOrText title: 'Question' translated! ! !ExampleBuilderMorph methodsFor: 'services'! question: aStringOrText title: aString "Open a question dialog and answer true if yes, false if no and nil if cancelled." ^self theme questionIn: self text: aStringOrText title: aString! ! !ExampleBuilderMorph methodsFor: 'services'! questionWithoutCancel: aStringOrText "Open a question dialog." ^self questionWithoutCancel: aStringOrText title: 'Question' translated! ! !ExampleBuilderMorph methodsFor: 'services'! questionWithoutCancel: aStringOrText title: aString "Open a question dialog and answer true if yes, false if no and nil if cancelled." ^self theme questionWithoutCancelIn: self text: aStringOrText title: aString! ! !ExampleBuilderMorph methodsFor: 'services'! textEntry: aStringOrText "Open a text entry dialog." ^self textEntry: aStringOrText title: 'Entry' translated! ! !ExampleBuilderMorph methodsFor: 'services'! textEntry: aStringOrText title: aString "Open a text entry dialog." ^self textEntry: aStringOrText title: aString entryText: ''! ! !ExampleBuilderMorph methodsFor: 'services'! textEntry: aStringOrText title: aString entryText: defaultEntryText "Open a text entry dialog." ^self theme textEntryIn: self text: aStringOrText title: aString entryText: defaultEntryText! ! !ExampleBuilderMorph methodsFor: 'theme'! theme "Answer the ui theme that provides controls." ^UITheme current! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ExampleBuilderMorph class uses: TEasilyThemed classTrait instanceVariableNames: ''! Object subclass: #ExampleRadioButtonModel instanceVariableNames: 'option' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !ExampleRadioButtonModel commentStamp: 'gvc 9/23/2008 11:58' prior: 0! Model used for radio buttons in example of basic controls (see "UITheme exampleBasicControls").! !ExampleRadioButtonModel methodsFor: 'accessing' stamp: 'gvc 8/7/2007 13:13'! option "Answer the value of option" ^ option! ! !ExampleRadioButtonModel methodsFor: 'accessing' stamp: 'gvc 8/7/2007 13:15'! option: aSymbol "Set the value of option" option := aSymbol. self changed: #isLeft; changed: #isCenter; changed: #isRight! ! !ExampleRadioButtonModel methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 13:17'! beCenter "Set the option to #center." self option: #center! ! !ExampleRadioButtonModel methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 13:17'! beLeft "Set the option to #left." self option: #left! ! !ExampleRadioButtonModel methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 13:17'! beRight "Set the option to #right." self option: #right! ! !ExampleRadioButtonModel methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 13:17'! initialize "Initialize the receiver." super initialize. self option: #left! ! !ExampleRadioButtonModel methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 13:16'! isCenter "Answer whether the option if #center." ^self option == #center! ! !ExampleRadioButtonModel methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 13:16'! isLeft "Answer whether the option if #left." ^self option == #left! ! !ExampleRadioButtonModel methodsFor: 'as yet unclassified' stamp: 'gvc 8/7/2007 13:16'! isRight "Answer whether the option if #right." ^self option == #right! ! Object subclass: #Exception instanceVariableNames: 'messageText tag signalContext handlerContext outerContext' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !Exception commentStamp: '' prior: 0! This is the main class used to implement the exception handling system (EHS). It plays two distinct roles: that of the exception, and that of the exception handler. More specifically, it implements the bulk of the protocols laid out in the ANSI specification - those protocol names are reflected in the message categories. Exception is an abstract class. Instances should neither be created nor trapped. In most cases, subclasses should inherit from Error or Notification rather than directly from Exception. In implementing this EHS, The Fourth Estate Inc. incorporated some ideas and code from Craig Latta's EHS. His insights were crucial in allowing us to implement BlockContext>>valueUninterruptably (and by extension, #ensure: and #ifCurtailed:), and we imported the following methods with little or no modification: ContextPart>>terminateTo: ContextPart>>terminate MethodContext>>receiver: MethodContext>>answer: Thanks, Craig!!! !Exception methodsFor: 'exceptionbuilder' stamp: 'pnm 8/16/2000 15:23'! tag: t "This message is not specified in the ANSI protocol, but that looks like an oversight because #tag is specified, and the spec states that the signaler may store the tag value." tag := t! ! !Exception methodsFor: 'exceptiondescription' stamp: 'pnm 8/16/2000 14:54'! tag "Return an exception's tag value." ^tag == nil ifTrue: [self messageText] ifFalse: [tag]! ! !Exception methodsFor: 'handling' stamp: 'ajh 2/1/2003 01:32'! isNested "Determine whether the current exception handler is within the scope of another handler for the same exception." ^ handlerContext nextHandlerContext canHandleSignal: self! ! !Exception methodsFor: 'handling' stamp: 'ajh 6/27/2003 22:13'! outer "Evaluate the enclosing exception action and return to here instead of signal if it resumes (see #resumeUnchecked:)." | prevOuterContext | self isResumable ifTrue: [ prevOuterContext := outerContext. outerContext := thisContext contextTag. ]. self pass. ! ! !Exception methodsFor: 'handling' stamp: 'ajh 2/1/2003 01:33'! pass "Yield control to the enclosing exception action for the receiver." handlerContext nextHandlerContext handleSignal: self! ! !Exception methodsFor: 'handling' stamp: 'ajh 1/22/2003 23:04'! resignalAs: replacementException "Signal an alternative exception in place of the receiver." self resumeUnchecked: replacementException signal! ! !Exception methodsFor: 'handling' stamp: 'ajh 1/13/2002 15:09'! resume "Return from the message that signaled the receiver." self resume: nil! ! !Exception methodsFor: 'handling' stamp: 'ajh 6/27/2003 22:30'! resumeUnchecked: resumptionValue "Return resumptionValue as the value of #signal, unless this was called after an #outer message, then return resumptionValue as the value of #outer." | ctxt | outerContext ifNil: [ signalContext return: resumptionValue ] ifNotNil: [ ctxt := outerContext. outerContext := ctxt tempAt: 1. "prevOuterContext in #outer" ctxt return: resumptionValue ]. ! ! !Exception methodsFor: 'handling' stamp: 'ajh 1/13/2002 15:14'! resume: resumptionValue "Return resumptionValue as the value of the signal message." self isResumable ifFalse: [IllegalResumeAttempt signal]. self resumeUnchecked: resumptionValue! ! !Exception methodsFor: 'handling' stamp: 'ajh 1/29/2003 13:36'! retry "Abort an exception handler and re-evaluate its protected block." handlerContext restart! ! !Exception methodsFor: 'handling' stamp: 'ajh 1/29/2003 13:37'! retryUsing: alternativeBlock "Abort an exception handler and evaluate a new block in place of the handler's protected block." handlerContext restartWithNewReceiver: alternativeBlock ! ! !Exception methodsFor: 'handling' stamp: 'ajh 9/30/2001 15:33'! return "Return nil as the value of the block protected by the active exception handler." self return: nil! ! !Exception methodsFor: 'handling' stamp: 'ajh 1/29/2003 13:37'! return: returnValue "Return the argument as the value of the block protected by the active exception handler." handlerContext return: returnValue! ! !Exception methodsFor: 'handling' stamp: 'ajh 2/16/2003 17:37'! searchFrom: aContext " Set the context where the handler search will start. " signalContext := aContext contextTag! ! !Exception methodsFor: 'printing' stamp: 'pnm 8/16/2000 14:53'! description "Return a textual description of the exception." | desc mt | desc := self class name asString. ^(mt := self messageText) == nil ifTrue: [desc] ifFalse: [desc, ': ', mt]! ! !Exception methodsFor: 'printing' stamp: 'ajh 9/30/2001 15:33'! messageText "Return an exception's message text." ^messageText! ! !Exception methodsFor: 'printing' stamp: 'ajh 9/30/2001 15:33'! printOn: stream stream nextPutAll: self description! ! !Exception methodsFor: 'printing' stamp: 'ajh 10/22/2001 14:24'! receiver ^ self signalerContext receiver! ! !Exception methodsFor: 'printing' stamp: 'ar 6/28/2003 00:13'! signalerContext "Find the first sender of signal(:)" ^ signalContext findContextSuchThat: [:ctxt | (ctxt receiver == self or: [ctxt receiver == self class]) not]! ! !Exception methodsFor: 'priv handling' stamp: 'ajh 9/30/2001 15:33'! defaultAction "The default action taken if the exception is signaled." self subclassResponsibility! ! !Exception methodsFor: 'priv handling' stamp: 'ajh 2/1/2003 00:58'! isResumable "Determine whether an exception is resumable." ^ true! ! !Exception methodsFor: 'priv handling' stamp: 'ajh 1/29/2003 13:44'! privHandlerContext: aContextTag handlerContext := aContextTag! ! !Exception methodsFor: 'signaling' stamp: 'ajh 9/30/2001 15:33'! messageText: signalerText "Set an exception's message text." messageText := signalerText! ! !Exception methodsFor: 'signaling' stamp: 'ajh 2/1/2003 01:33'! signal "Ask ContextHandlers in the sender chain to handle this signal. The default is to execute and return my defaultAction." signalContext := thisContext contextTag. ^ thisContext nextHandlerContext handleSignal: self! ! !Exception methodsFor: 'signaling' stamp: 'ajh 9/30/2001 20:13'! signal: signalerText "Signal the occurrence of an exceptional condition with a specified textual description." self messageText: signalerText. ^ self signal! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Exception class instanceVariableNames: ''! !Exception class methodsFor: 'exceptioninstantiator' stamp: 'ajh 9/30/2001 21:54'! signal "Signal the occurrence of an exceptional condition." ^ self new signal! ! !Exception class methodsFor: 'exceptioninstantiator' stamp: 'ajh 9/30/2001 21:54'! signal: signalerText "Signal the occurrence of an exceptional condition with a specified textual description." ^ self new signal: signalerText! ! !Exception class methodsFor: 'exceptionselector' stamp: 'ajh 9/30/2001 15:33'! , anotherException "Create an exception set." ^ExceptionSet new add: self; add: anotherException; yourself! ! !Exception class methodsFor: 'exceptionselector' stamp: 'ajh 8/5/2003 11:33'! handles: exception "Determine whether an exception handler will accept a signaled exception." ^ exception isKindOf: self! ! Notification subclass: #ExceptionAboutToReturn instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !ExceptionAboutToReturn commentStamp: '' prior: 0! This class is private to the EHS implementation. Its use allows for ensured execution to survive code such as: [self doThis. ^nil] ensure: [self doThat] Signaling or handling this exception is not recommended. Not even slightly.! Object subclass: #ExceptionSet instanceVariableNames: 'exceptions' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !ExceptionSet commentStamp: '' prior: 0! An ExceptionSet is a grouping of exception handlers which acts as a single handler. Within the group, the most recently added handler will be the last handler found during a handler search (in the case where more than one handler in the group is capable of handling a given exception). ! !ExceptionSet methodsFor: 'exceptionselector' stamp: 'tfei 6/4/1999 18:37'! , anException "Return an exception set that contains the receiver and the argument exception. This is commonly used to specify a set of exception selectors for an exception handler." self add: anException. ^self! ! !ExceptionSet methodsFor: 'exceptionselector' stamp: 'pnm 8/16/2000 15:15'! handles: anException "Determine whether an exception handler will accept a signaled exception." exceptions do: [:ex | (ex handles: anException) ifTrue: [^true]]. ^false! ! !ExceptionSet methodsFor: 'private' stamp: 'tfei 7/16/1999 1:07'! add: anException exceptions add: anException! ! !ExceptionSet methodsFor: 'private' stamp: 'alain.plantec 5/28/2009 09:52'! initialize super initialize. exceptions := OrderedCollection new! ! Object subclass: #ExceptionTester instanceVariableNames: 'log suiteLog iterationsBeforeTimeout' classVariableNames: '' poolDictionaries: '' category: 'Tests-Exceptions'! !ExceptionTester methodsFor: 'accessing' stamp: 'dtl 6/1/2004 21:53'! basicANSISignaledExceptionTestSelectors ^#( simpleIsNestedTest simpleOuterTest doubleOuterTest doubleOuterPassTest doublePassOuterTest simplePassTest simpleResignalAsTest simpleResumeTest simpleRetryTest simpleRetryUsingTest simpleReturnTest)! ! !ExceptionTester methodsFor: 'accessing' stamp: 'brp 10/21/2004 17:54'! basicTestSelectors ^ #(#simpleEnsureTest #simpleEnsureTestWithNotification #simpleEnsureTestWithUparrow #simpleEnsureTestWithError #signalFromHandlerActionTest #resumableFallOffTheEndHandler #nonResumableFallOffTheEndHandler #doubleResumeTest #simpleTimeoutWithZeroDurationTest #simpleTimeoutTest simpleNoTimeoutTest)! ! !ExceptionTester methodsFor: 'accessing' stamp: 'tfei 6/8/1999 09:14'! doSomethingElseString ^'Do something else.'! ! !ExceptionTester methodsFor: 'accessing' stamp: 'tfei 6/8/1999 09:14'! doSomethingExceptionalString ^'Do something exceptional.'! ! !ExceptionTester methodsFor: 'accessing' stamp: 'tfei 6/8/1999 09:13'! doSomethingString ^'Do something.'! ! !ExceptionTester methodsFor: 'accessing' stamp: 'tfei 6/8/1999 09:15'! doYetAnotherThingString ^'Do yet another thing.'! ! !ExceptionTester methodsFor: 'accessing' stamp: 'brp 10/21/2004 17:15'! iterationsBeforeTimeout ^ iterationsBeforeTimeout! ! !ExceptionTester methodsFor: 'accessing' stamp: 'brp 10/21/2004 17:16'! iterationsBeforeTimeout: anInteger iterationsBeforeTimeout := anInteger! ! !ExceptionTester methodsFor: 'accessing' stamp: 'tfei 6/7/1999 15:03'! log log == nil ifTrue: [log := OrderedCollection new]. ^log! ! !ExceptionTester methodsFor: 'accessing' stamp: 'tfei 6/8/1999 09:30'! suiteLog suiteLog == nil ifTrue: [suiteLog := OrderedCollection new]. ^suiteLog! ! !ExceptionTester methodsFor: 'accessing' stamp: 'tfei 6/8/1999 09:15'! testString ^'This is only a test.'! ! !ExceptionTester methodsFor: 'logging' stamp: 'tfei 6/8/1999 09:17'! clearLog log := nil! ! !ExceptionTester methodsFor: 'logging' stamp: 'PeterHugossonMiller 9/3/2009 01:25'! contents ^( self log inject: (String new: 80) writeStream into: [:result :item | result cr; nextPutAll: item; yourself] ) contents! ! !ExceptionTester methodsFor: 'logging' stamp: 'tfei 6/7/1999 15:03'! log: aString self log add: aString! ! !ExceptionTester methodsFor: 'logging' stamp: 'tfei 6/12/1999 23:07'! logTest: aSelector self suiteLog add: aSelector! ! !ExceptionTester methodsFor: 'logging' stamp: 'tfei 6/8/1999 09:38'! logTestResult: aString | index | index := self suiteLog size. self suiteLog at: index put: ((self suiteLog at: index), ' ', aString)! ! !ExceptionTester methodsFor: 'pseudo actions' stamp: 'tfei 6/8/1999 09:13'! doSomething self log: self doSomethingString! ! !ExceptionTester methodsFor: 'pseudo actions' stamp: 'tfei 6/8/1999 09:14'! doSomethingElse self log: self doSomethingElseString! ! !ExceptionTester methodsFor: 'pseudo actions' stamp: 'tfei 6/8/1999 09:14'! doSomethingExceptional self log: self doSomethingExceptionalString! ! !ExceptionTester methodsFor: 'pseudo actions' stamp: 'tfei 6/8/1999 09:15'! doYetAnotherThing self log: self doYetAnotherThingString! ! !ExceptionTester methodsFor: 'pseudo actions' stamp: 'tfei 6/8/1999 09:16'! methodWithError MyTestError signal: self testString! ! !ExceptionTester methodsFor: 'pseudo actions' stamp: 'tfei 6/8/1999 09:16'! methodWithNotification MyTestNotification signal: self testString! ! !ExceptionTester methodsFor: 'results' stamp: 'tfei 11/14/1999 17:29'! doubleResumeTestResults ^OrderedCollection new add: self doSomethingString; add: self doSomethingElseString; add: self doYetAnotherThingString; yourself! ! !ExceptionTester methodsFor: 'results' stamp: 'tfei 6/8/1999 09:21'! nonResumableFallOffTheEndHandlerResults ^OrderedCollection new add: self doSomethingString; add: self doSomethingExceptionalString; add: self doYetAnotherThingString; yourself! ! !ExceptionTester methodsFor: 'results' stamp: 'tfei 8/19/1999 02:39'! resumableFallOffTheEndHandlerResults ^OrderedCollection new add: self doSomethingString; add: self doSomethingExceptionalString; add: self doYetAnotherThingString; yourself! ! !ExceptionTester methodsFor: 'results' stamp: 'tfei 8/19/1999 01:51'! signalFromHandlerActionTestResults ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; add: 'Unhandled Exception'; yourself! ! !ExceptionTester methodsFor: 'results' stamp: 'tfei 6/8/1999 09:47'! simpleEnsureTestResults ^OrderedCollection new add: self doSomethingString; add: self doSomethingElseString; add: self doYetAnotherThingString; yourself! ! !ExceptionTester methodsFor: 'results' stamp: 'tfei 6/9/1999 17:44'! simpleEnsureTestWithErrorResults ^OrderedCollection new add: self doSomethingString; add: 'Unhandled Exception'; add: self doYetAnotherThingString; yourself! ! !ExceptionTester methodsFor: 'results' stamp: 'tfei 6/8/1999 10:13'! simpleEnsureTestWithNotificationResults ^OrderedCollection new add: self doSomethingString; add: self doSomethingElseString; add: self doYetAnotherThingString; yourself! ! !ExceptionTester methodsFor: 'results' stamp: 'tfei 6/8/1999 18:55'! simpleEnsureTestWithUparrowResults ^OrderedCollection new add: self doSomethingString; " add: self doSomethingElseString;" add: self doYetAnotherThingString; yourself! ! !ExceptionTester methodsFor: 'results' stamp: 'brp 10/21/2004 16:54'! simpleNoTimeoutTestResults ^OrderedCollection new add: self doSomethingString; yourself! ! !ExceptionTester methodsFor: 'results' stamp: 'brp 10/21/2004 17:44'! simpleTimeoutTestResults | things | things := OrderedCollection new: self iterationsBeforeTimeout. self iterationsBeforeTimeout timesRepeat: [ things add: self doSomethingString ]. things add: self doSomethingElseString. ^ things! ! !ExceptionTester methodsFor: 'results' stamp: 'brp 10/21/2004 16:52'! simpleTimeoutWithZeroDurationTestResults ^OrderedCollection new add: self doSomethingElseString; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'dtl 6/1/2004 21:56'! doubleOuterPassTestResults ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; add: self doSomethingElseString; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'dtl 6/1/2004 21:56'! doublePassOuterTestResults ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; add: self doSomethingElseString; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'tfei 6/13/1999 01:09'! simpleIsNestedTestResults ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; add: self doSomethingElseString; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'tfei 6/13/1999 01:10'! simpleOuterTestResults ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; add: self doSomethingElseString; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'tfei 6/13/1999 01:10'! simplePassTestResults ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; add: 'Unhandled Exception'; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'tfei 6/13/1999 01:11'! simpleResignalAsTestResults ^OrderedCollection new add: self doSomethingString; add: 'Unhandled Exception'; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'RAA 12/8/2000 12:59'! simpleResumeTestResults "see if we can resume twice" ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; add: self doSomethingElseString; add: self doYetAnotherThingString; add: self doSomethingElseString; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'tfei 6/13/1999 01:23'! simpleRetryTestResults ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; add: self doSomethingString; add: self doSomethingElseString; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'tfei 6/13/1999 01:23'! simpleRetryUsingTestResults ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; yourself! ! !ExceptionTester methodsFor: 'signaledexception results' stamp: 'tfei 6/13/1999 02:22'! simpleReturnTestResults ^OrderedCollection new add: self doSomethingString; add: self doYetAnotherThingString; yourself! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'dtl 6/1/2004 21:51'! doubleOuterPassTest "uses #resume" [[[self doSomething. MyTestNotification signal. self doSomethingExceptional] on: MyTestNotification do: [:ex | ex outer. self doSomethingElse]] on: MyTestNotification do: [:ex | ex pass. self doSomethingExceptional]] on: MyTestNotification do: [:ex | self doYetAnotherThing. ex resume]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'dtl 6/1/2004 21:49'! doubleOuterTest "uses #resume" [[[self doSomething. MyTestNotification signal. self doSomethingExceptional] on: MyTestNotification do: [:ex | ex outer. self doSomethingExceptional]] on: MyTestNotification do: [:ex | ex outer. self doSomethingElse]] on: MyTestNotification do: [:ex | self doYetAnotherThing. ex resume]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'dtl 6/1/2004 21:52'! doublePassOuterTest "uses #resume" [[[self doSomething. MyTestNotification signal. self doSomethingExceptional] on: MyTestNotification do: [:ex | ex pass. self doSomethingExceptional]] on: MyTestNotification do: [:ex | ex outer. self doSomethingElse]] on: MyTestNotification do: [:ex | self doYetAnotherThing. ex resume]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'tfei 6/13/1999 01:27'! simpleIsNestedTest "uses resignalAs:" [self doSomething. MyTestError signal. self doSomethingElse] on: MyTestError do: [:ex | ex isNested "expecting to detect handler in #runTest:" ifTrue: [self doYetAnotherThing. ex resignalAs: MyTestNotification new]]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'tpr 5/27/2004 21:50'! simpleOuterTest "uses #resume" [[self doSomething. MyTestNotification signal. "self doSomethingElse" self doSomethingExceptional] on: MyTestNotification do: [:ex | ex outer. self doSomethingElse]] on: MyTestNotification do: [:ex | self doYetAnotherThing. ex resume]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'tfei 6/13/1999 00:37'! simplePassTest [self doSomething. MyTestError signal. self doSomethingElse] on: MyTestError do: [:ex | self doYetAnotherThing. ex pass "expecting handler in #runTest:"]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'tfei 6/13/1999 02:12'! simpleResignalAsTest "ExceptionTester new simpleResignalAsTest" [self doSomething. MyTestNotification signal. self doSomethingElse] on: MyTestNotification do: [:ex | ex resignalAs: MyTestError new]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'RAA 12/8/2000 12:58'! simpleResumeTest "see if we can resume twice" | it | [self doSomething. it := MyResumableTestError signal. it = 3 ifTrue: [self doSomethingElse]. it := MyResumableTestError signal. it = 3 ifTrue: [self doSomethingElse]. ] on: MyResumableTestError do: [:ex | self doYetAnotherThing. ex resume: 3]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'tfei 6/13/1999 01:02'! simpleRetryTest | theMeaningOfLife | theMeaningOfLife := nil. [self doSomething. theMeaningOfLife == nil ifTrue: [MyTestError signal] ifFalse: [self doSomethingElse]] on: MyTestError do: [:ex | theMeaningOfLife := 42. self doYetAnotherThing. ex retry]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'tfei 6/13/1999 01:03'! simpleRetryUsingTest [self doSomething. MyTestError signal. self doSomethingElse] on: MyTestError do: [:ex | ex retryUsing: [self doYetAnotherThing]]! ! !ExceptionTester methodsFor: 'signaledexception tests' stamp: 'tfei 6/13/1999 00:59'! simpleReturnTest | it | it := [self doSomething. MyTestError signal. self doSomethingElse] on: MyTestError do: [:ex | ex return: 3]. it = 3 ifTrue: [self doYetAnotherThing]! ! !ExceptionTester methodsFor: 'suites' stamp: 'tfei 6/13/1999 01:25'! runAllTests "ExceptionTester new runAllTests" self runBasicTests; runBasicANSISignaledExceptionTests! ! !ExceptionTester methodsFor: 'suites' stamp: 'tfei 6/12/1999 23:54'! runBasicANSISignaledExceptionTests self basicANSISignaledExceptionTestSelectors do: [:eachTestSelector | self runTest: eachTestSelector]! ! !ExceptionTester methodsFor: 'suites' stamp: 'tfei 6/9/1999 16:06'! runBasicTests self basicTestSelectors do: [:eachTestSelector | self runTest: eachTestSelector]! ! !ExceptionTester methodsFor: 'testing' stamp: 'brp 10/21/2004 17:40'! runTest: aSelector | actualResult expectedResult | [ self logTest: aSelector; clearLog; perform: aSelector ] on: MyTestError do: [ :ex | self log: 'Unhandled Exception'. ex return: nil ]. actualResult := self log. expectedResult := self perform: (aSelector, #Results) asSymbol. actualResult = expectedResult ifTrue: [self logTestResult: 'succeeded'] ifFalse: [self logTestResult: 'failed' ]. ! ! !ExceptionTester methodsFor: 'tests' stamp: 'tfei 11/14/1999 17:26'! doubleResumeTest [self doSomething. MyResumableTestError signal. self doSomethingElse. MyResumableTestError signal. self doYetAnotherThing] on: MyResumableTestError do: [:ex | ex resume].! ! !ExceptionTester methodsFor: 'tests' stamp: 'tfei 6/7/1999 13:43'! nonResumableFallOffTheEndHandler [self doSomething. MyTestError signal. self doSomethingElse] on: MyTestError do: [:ex | self doSomethingExceptional]. self doYetAnotherThing! ! !ExceptionTester methodsFor: 'tests' stamp: 'tfei 6/9/1999 16:07'! resumableFallOffTheEndHandler [self doSomething. MyTestNotification signal. self doSomethingElse] on: MyTestNotification do: [:ex | self doSomethingExceptional]. self doYetAnotherThing! ! !ExceptionTester methodsFor: 'tests' stamp: 'tfei 8/19/1999 01:39'! signalFromHandlerActionTest [self doSomething. MyTestError signal. self doSomethingElse] on: MyTestError do: [self doYetAnotherThing. MyTestError signal]! ! !ExceptionTester methodsFor: 'tests' stamp: 'tfei 6/8/1999 09:44'! simpleEnsureTest [self doSomething. self doSomethingElse] ensure: [self doYetAnotherThing]. ! ! !ExceptionTester methodsFor: 'tests' stamp: 'tfei 6/8/1999 12:50'! simpleEnsureTestWithError [self doSomething. MyTestError signal. self doSomethingElse] ensure: [self doYetAnotherThing]. ! ! !ExceptionTester methodsFor: 'tests' stamp: 'tfei 6/8/1999 10:15'! simpleEnsureTestWithNotification [self doSomething. self methodWithNotification. self doSomethingElse] ensure: [self doYetAnotherThing]. ! ! !ExceptionTester methodsFor: 'tests' stamp: 'tfei 6/9/1999 16:04'! simpleEnsureTestWithUparrow [self doSomething. true ifTrue: [^nil]. self doSomethingElse] ensure: [self doYetAnotherThing]. ! ! !ExceptionTester methodsFor: 'tests' stamp: 'brp 10/22/2004 12:00'! simpleNoTimeoutTest [ self doSomething ] valueWithin: 1 day onTimeout: [ self doSomethingElse ]. ! ! !ExceptionTester methodsFor: 'tests' stamp: 'brp 10/22/2004 12:00'! simpleTimeoutTest | n | [1 to: 1000000 do: [ :i | n := i. self doSomething ] ] valueWithin: 50 milliSeconds onTimeout: [ self iterationsBeforeTimeout: n. self doSomethingElse ]! ! !ExceptionTester methodsFor: 'tests' stamp: 'brp 10/22/2004 12:00'! simpleTimeoutWithZeroDurationTest [ self doSomething ] valueWithin: 0 seconds onTimeout: [ self doSomethingElse ]. ! ! !ExceptionTester methodsFor: 'tests' stamp: 'tfei 6/7/1999 14:28'! warningTest self log: 'About to signal warning.'. Warning signal: 'Ouch'. self log: 'Warning signal handled and resumed.'! ! TestCase subclass: #ExceptionTests instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Exceptions'! !ExceptionTests methodsFor: 'testing' stamp: 'brp 10/21/2004 16:42'! testNoTimeout self assertSuccess: (ExceptionTester new runTest: #simpleNoTimeoutTest ) ! ! !ExceptionTests methodsFor: 'testing' stamp: 'brp 10/21/2004 16:41'! testTimeoutWithZeroDuration self assertSuccess: (ExceptionTester new runTest: #simpleTimeoutWithZeroDurationTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'dtl 6/1/2004 21:54'! testDoubleOuterPass self assertSuccess: (ExceptionTester new runTest: #doubleOuterPassTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'dtl 6/1/2004 21:54'! testDoublePassOuter self assertSuccess: (ExceptionTester new runTest: #doublePassOuterTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:43'! testDoubleResume self assertSuccess: (ExceptionTester new runTest: #doubleResumeTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:44'! testNonResumableFallOffTheEndHandler self assertSuccess: (ExceptionTester new runTest: #nonResumableFallOffTheEndHandler ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:44'! testResumableFallOffTheEndHandler self assertSuccess: (ExceptionTester new runTest: #resumableFallOffTheEndHandler ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:44'! testSignalFromHandlerActionTest self assertSuccess: (ExceptionTester new runTest: #signalFromHandlerActionTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:48'! testSimpleEnsure self assertSuccess: (ExceptionTester new runTest: #simpleEnsureTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:45'! testSimpleEnsureTestWithError self assertSuccess: (ExceptionTester new runTest: #simpleEnsureTestWithError ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:46'! testSimpleEnsureTestWithNotification self assertSuccess: (ExceptionTester new runTest: #simpleEnsureTestWithNotification ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:45'! testSimpleEnsureTestWithUparrow self assertSuccess: (ExceptionTester new runTest: #simpleEnsureTestWithUparrow ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:46'! testSimpleIsNested self assertSuccess: (ExceptionTester new runTest: #simpleIsNestedTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:41'! testSimpleOuter self assertSuccess: (ExceptionTester new runTest: #simpleOuterTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:42'! testSimplePass self assertSuccess: (ExceptionTester new runTest: #simplePassTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:43'! testSimpleResignalAs self assertSuccess: (ExceptionTester new runTest: #simpleResignalAsTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:48'! testSimpleResume self assertSuccess: (ExceptionTester new runTest: #simpleResumeTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:48'! testSimpleRetry self assertSuccess: (ExceptionTester new runTest: #simpleRetryTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:47'! testSimpleRetryUsing self assertSuccess: (ExceptionTester new runTest: #simpleRetryUsingTest ) ! ! !ExceptionTests methodsFor: 'testing-exceptiontester' stamp: 'md 3/25/2003 23:48'! testSimpleReturn self assertSuccess: (ExceptionTester new runTest: #simpleReturnTest ) ! ! !ExceptionTests methodsFor: 'testing-outer' stamp: 'dtl 6/1/2004 21:59'! testNonResumableOuter self should: [ [Error signal. 4] on: Error do: [:ex | ex outer. ex return: 5] ] raise: Error ! ! !ExceptionTests methodsFor: 'testing-outer' stamp: 'dtl 6/1/2004 22:00'! testNonResumablePass self should: [ [Error signal. 4] on: Error do: [:ex | ex pass. ex return: 5] ] raise: Error ! ! !ExceptionTests methodsFor: 'testing-outer' stamp: 'dtl 6/1/2004 22:00'! testResumableOuter | result | result := [Notification signal. 4] on: Notification do: [:ex | ex outer. ex return: 5]. self assert: result == 5 ! ! !ExceptionTests methodsFor: 'testing-outer' stamp: 'dtl 6/1/2004 22:00'! testResumablePass | result | result := [Notification signal. 4] on: Notification do: [:ex | ex pass. ex return: 5]. self assert: result == 4 ! ! !ExceptionTests methodsFor: 'private' stamp: 'md 3/25/2003 23:40'! assertSuccess: anExceptionTester self should: [ ( anExceptionTester suiteLog first) endsWith: 'succeeded'].! ! NonReentrantWeakMessageSend weakSubclass: #ExclusiveWeakMessageSend instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-EventEnhancements'! !ExclusiveWeakMessageSend methodsFor: 'as yet unclassified' stamp: 'gvc 7/30/2009 13:39'! basicExecuting: aValueHolder "Set the shared value holder." executing := aValueHolder! ! !ExclusiveWeakMessageSend methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 18:07'! executing "Answer from the shared value holder." ^executing contents! ! !ExclusiveWeakMessageSend methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 18:06'! executing: aBoolean "Set on the shared value holder." executing contents: aBoolean! ! !ExclusiveWeakMessageSend methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 18:13'! initialize "Initialize the receiver." executing := self class newSharedState. super initialize.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ExclusiveWeakMessageSend class instanceVariableNames: ''! !ExclusiveWeakMessageSend class methodsFor: 'as yet unclassified' stamp: 'gvc 10/25/2006 18:13'! newSharedState "Answer a new ValueHolder with false as the contents." ^ValueHolder new contents: false! ! PanelMorph subclass: #ExpanderMorph instanceVariableNames: 'titleMorph' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !ExpanderMorph commentStamp: 'gvc 5/18/2007 13:13' prior: 0! A morph that can expand or collapse to show its contents.! !ExpanderMorph methodsFor: 'accessing' stamp: 'gvc 7/27/2006 10:30'! titleMorph "Answer the value of titleMorph" ^ titleMorph! ! !ExpanderMorph methodsFor: 'accessing' stamp: 'gvc 7/27/2006 10:35'! titleMorph: aMorph "Set the value of titleMorph" titleMorph ifNotNil: [titleMorph delete; removeDependent: self]. titleMorph := aMorph. aMorph ifNotNil: [ aMorph addDependent: self. self addMorph: aMorph]! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/27/2006 11:24'! addedMorph: aMorph "Notify the receiver that the given morph was just added." aMorph == self titleMorph ifFalse: [ self titleMorph ifNotNil: [ aMorph visible: self expanded; disableTableLayout: self expanded not]]! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/27/2006 10:33'! defaultTitleMorph "Answer a default title morph for the receiver." ^ExpanderTitleMorph new hResizing: #spaceFill; vResizing: #shrinkWrap! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/27/2006 11:23'! expanded "Answer whether the title is expanded." ^self titleMorph expanded! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/27/2006 11:23'! expanded: aBoolean "Set whether the title is expanded." self titleMorph expanded: aBoolean! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/18/2006 11:57'! fixLayout "Fix the owner layout, nasty!!" self owner ifNil: [^self]. self owner allMorphsDo: [:m | (m respondsTo: #resetExtent) ifTrue: [ WorldState addDeferredUIMessage: (MessageSend receiver: m selector: #resetExtent). WorldState addDeferredUIMessage: (MessageSend receiver: m selector: #setScrollDeltas)]. (m isKindOf: self class) ifTrue: [WorldState addDeferredUIMessage: (MessageSend receiver: m selector: #adoptPaneColor)]]. WorldState addDeferredUIMessage: (MessageSend receiver: self owner selector: #changed)! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/13/2006 10:29'! font "Answer the title font" ^self titleMorph font! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/13/2006 10:30'! font: aFont "Set the title font" self titleMorph font: aFont! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/27/2006 10:37'! initialize "Initialize the receiver." super initialize. self changeTableLayout; listDirection: #topToBottom; hResizing: #spaceFill; vResizing: #shrinkWrap; titleMorph: self defaultTitleMorph! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/27/2006 11:32'! showMorphs: aBoolean "Hide/Show the other morphs." self submorphs do: [:m | m == self titleMorph ifFalse: [ m visible: aBoolean; disableTableLayout: aBoolean not]]! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/27/2006 10:55'! titleText: aStringOrText "Set the text if the title morph is capable." (self titleMorph respondsTo: #titleText:) ifTrue: [self titleMorph titleText: aStringOrText]! ! !ExpanderMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/28/2006 11:26'! update: aspect "Update the receiver." aspect = #expanded ifTrue: [self vResizing: (self expanded ifTrue: [#spaceFill] ifFalse: [#shrinkWrap]). self showMorphs: self expanded. self fixLayout]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ExpanderMorph class instanceVariableNames: ''! !ExpanderMorph class methodsFor: 'as yet unclassified' stamp: 'gvc 7/27/2006 10:54'! titleText: aStringOrText "Answer a new instance of the receiver with the given title text." ^self new titleText: aStringOrText! ! PanelMorph subclass: #ExpanderTitleMorph instanceVariableNames: 'labelMorph buttonMorph expanded' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets'! !ExpanderTitleMorph commentStamp: 'gvc 5/18/2007 13:12' prior: 0! The titlebar area for and ExpanderMorph. Includes title label and expand/collapse button.! !ExpanderTitleMorph methodsFor: 'accessing' stamp: 'gvc 1/22/2009 15:37'! buttonMorph "Answer the value of buttonMorph" ^ buttonMorph! ! !ExpanderTitleMorph methodsFor: 'accessing' stamp: 'gvc 1/22/2009 15:37'! buttonMorph: anObject "Set the value of buttonMorph" buttonMorph := anObject! ! !ExpanderTitleMorph methodsFor: 'accessing' stamp: 'gvc 7/27/2006 10:16'! expanded "Answer the value of expanded" ^ expanded! ! !ExpanderTitleMorph methodsFor: 'accessing' stamp: 'gvc 7/27/2006 10:24'! expanded: aBoolean "Set the value of expanded" expanded := aBoolean. self changed: #expanded; changed: #expandLabel! ! !ExpanderTitleMorph methodsFor: 'accessing' stamp: 'gvc 9/13/2006 10:23'! labelMorph "Answer the value of labelMorph" ^ labelMorph! ! !ExpanderTitleMorph methodsFor: 'accessing' stamp: 'gvc 3/12/2007 12:55'! labelMorph: anObject "Set the value of labelMorph. need to wrap to provide clipping!!" labelMorph ifNotNil: [self removeMorph: labelMorph owner]. labelMorph := anObject. labelMorph ifNotNil: [self addMorph: ( Morph new color: Color transparent; changeTableLayout; listDirection: #leftToRight; listCentering: #center; hResizing: #spaceFill; vResizing: #shrinkWrap; clipSubmorphs: true; addMorph: labelMorph)]! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/23/2009 16:30'! adoptPaneColor: paneColor "Update the fill styles, corner styles, label colour and expansion button indicator." super adoptPaneColor: paneColor. paneColor ifNil: [^self]. self fillStyle: self normalFillStyle. self borderStyle baseColor: paneColor twiceDarker. self buttonMorph cornerStyle: self cornerStyle. self labelMorph color: paneColor contrastingColor. self changed: #expandLabel! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/28/2009 17:08'! buttonWidth "Answer based on scrollbar size." ^(Preferences scrollBarsNarrow ifTrue: [12] ifFalse: [16]) max: self theme expanderTitleControlButtonWidth! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/23/2006 16:46'! defaultBorderStyle "Answer the default border style for the receiver." ^BorderStyle raised width: 1! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/31/2009 16:41'! expandLabel "Answer the label for the expand button." ^AlphaImageMorph new image: ( ScrollBar arrowOfDirection: (self expanded ifTrue: [#top] ifFalse: [#bottom]) size: self buttonWidth - 3 color: self paneColor darker)! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/13/2006 10:29'! font "Answer the label font" ^((self labelMorph isKindOf: StringMorph) or: [self labelMorph isTextMorph]) ifTrue: [self labelMorph font]! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/13/2006 10:28'! font: aFont "Set the label font" ((self labelMorph isKindOf: StringMorph) or: [self labelMorph isTextMorph]) ifTrue: [self labelMorph font: aFont]! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/22/2009 15:37'! initialize "Initialize the receiver." super initialize. self expanded: false; changeTableLayout; borderStyle: self defaultBorderStyle; layoutInset: (self theme expanderTitleInsetFor: self); listDirection: #leftToRight; listCentering: #center; wrapCentering: #center; buttonMorph: self newExpandButtonMorph; addMorph: self buttonMorph; labelMorph: self newLabelMorph; on: #mouseUp send: #toggleExpanded to: self! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 1/22/2009 15:35'! newExpandButtonMorph "Answer a new expand button." ^(ControlButtonMorph on: self getState: nil action: #toggleExpanded label: #expandLabel) hResizing: #rigid; vResizing: #spaceFill; cornerStyle: self cornerStyle; extent: self buttonWidth asPoint! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 3/12/2007 12:57'! newLabelMorph "Answer a new label morph for the receiver." ^TextMorph new hResizing: #spaceFill; vResizing: #shrinkWrap; margins: (3@3 corner: 3@0); lock! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 5/23/2007 14:28'! normalFillStyle "Return the normal fillStyle of the receiver." ^self theme expanderTitleNormalFillStyleFor: self! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 10/18/2006 11:15'! titleText "Answer the text if the title morph is capable." ^((self labelMorph isKindOf: StringMorph) or: [self labelMorph isTextMorph]) ifTrue: [self labelMorph contents] ifFalse: ['']! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 9/13/2006 10:24'! titleText: aStringOrText "Set the text if the title morph is capable." ((self labelMorph isKindOf: StringMorph) or: [self labelMorph isTextMorph]) ifTrue: [self labelMorph contents: aStringOrText]! ! !ExpanderTitleMorph methodsFor: 'as yet unclassified' stamp: 'gvc 7/27/2006 10:23'! toggleExpanded "Toggle the expanded state." self expanded: self expanded not! ! Clipboard subclass: #ExternalClipboard instanceVariableNames: 'clipboard' classVariableNames: '' poolDictionaries: '' category: 'System-Clipboard'! !ExternalClipboard commentStamp: 'michael.rueger 3/2/2009 13:25' prior: 0! An ExternalClipboard is the abstract superclass for the platform specific clipboards based on the clipboard plugin (former ExtendedClipboardInterface originally developed for Sophie). Instance Variables clipboard: SmallInteger clipboard - handle for the external clipboard. If 0 the external clipboard is invalid ! !ExternalClipboard methodsFor: 'accessing' stamp: 'michael.rueger 3/2/2009 13:42'! clearClipboard clipboard = 0 ifTrue: [^self]. ^ self primClearClipboard: clipboard.! ! !ExternalClipboard methodsFor: 'accessing' stamp: 'michael.rueger 6/10/2009 13:42'! clipboardText "Return the text currently in the clipboard. If the system clipboard is empty, or if it differs from the Smalltalk clipboard text, use the Smalltalk clipboard. This is done since (a) the Mac clipboard gives up on very large chunks of text and (b) since not all platforms support the notion of a clipboard." | decodedString bytes | clipboard = 0 ifTrue: [^super clipboardText]. bytes := self primReadClipboardData: clipboard format: 'public.utf8-plain-text'. bytes ifNil: [^super clipboardText]. decodedString := bytes asString convertFromWithConverter: UTF8TextConverter new. decodedString := decodedString replaceAll: 10 asCharacter with: 13 asCharacter. ^decodedString = contents asString ifTrue: [contents] ifFalse: [decodedString asText]. ! ! !ExternalClipboard methodsFor: 'accessing' stamp: 'michael.rueger 3/25/2009 14:47'! clipboardText: text | string data | string := text asString. self noteRecentClipping: text asText. contents := text asText. data := (string convertToWithConverter: UTF8TextConverter new) asByteArray. clipboard = 0 ifTrue: [^super clipboardText: text]. self clearClipboard. self primAddClipboardData: clipboard data: data dataFormat: 'public.utf8-plain-text'! ! !ExternalClipboard methodsFor: 'initialize' stamp: 'StephaneDucasse 8/30/2009 14:55'! initialize super initialize. clipboard := [self createClipboard] on: Error do: [:ex | clipboard := 0]! ! !ExternalClipboard methodsFor: 'primitives' stamp: 'michael.rueger 3/25/2009 14:22'! addClipboardData: data dataFormat: aFormat clipboard = 0 ifTrue: [Clipboard clipboardText: data asString. ^self]. self primAddClipboardData: clipboard data: data dataFormat: aFormat! ! !ExternalClipboard methodsFor: 'primitives' stamp: 'michael.rueger 3/25/2009 14:25'! primAddClipboardData: aClipboard data: data dataFormat: aFormat ^ self primitiveFailed! ! !ExternalClipboard methodsFor: 'primitives' stamp: 'michael.rueger 3/2/2009 13:42'! primClearClipboard: aClipboard ^ self primitiveFailed. ! ! !ExternalClipboard methodsFor: 'primitives' stamp: 'michael.rueger 3/2/2009 13:42'! primCreateClipboard ^ self primitiveFailed. ! ! !ExternalClipboard methodsFor: 'primitives' stamp: 'michael.rueger 3/25/2009 14:25'! primGetClipboardFormat: aClipboard formatNumber: formatNumber ^ self primitiveFailed! ! !ExternalClipboard methodsFor: 'primitives' stamp: 'marcus.denker 6/11/2009 12:24'! primReadClipboardData: aClipboard format: format ^ self primitiveFailed! ! !ExternalClipboard methodsFor: 'private' stamp: 'michael.rueger 3/2/2009 13:42'! createClipboard clipboard = 0 ifTrue: [^self]. ^ self primCreateClipboard.! ! Object subclass: #ExternalDropHandler instanceVariableNames: 'action type extension' classVariableNames: 'DefaultHandler RegisteredHandlers' poolDictionaries: '' category: 'System-Support'! !ExternalDropHandler methodsFor: 'accessing' stamp: 'mir 1/10/2002 15:54'! extension ^extension! ! !ExternalDropHandler methodsFor: 'accessing' stamp: 'mir 1/10/2002 17:29'! handle: dropStream in: pasteUp dropEvent: anEvent | numArgs | numArgs := action numArgs. numArgs == 1 ifTrue: [^action value: dropStream]. numArgs == 2 ifTrue: [^action value: dropStream value: pasteUp]. numArgs == 3 ifTrue: [^action value: dropStream value: pasteUp value: anEvent]. self error: 'Wrong number of args for dop action.'! ! !ExternalDropHandler methodsFor: 'accessing' stamp: 'mir 1/10/2002 15:54'! type ^type! ! !ExternalDropHandler methodsFor: 'initialize' stamp: 'mir 1/10/2002 17:17'! type: aType extension: anExtension action: anAction action := anAction. type := aType. extension := anExtension! ! !ExternalDropHandler methodsFor: 'testing' stamp: 'spfa 5/25/2004 13:38'! matchesExtension: aExtension (self extension isNil or: [aExtension isNil]) ifTrue: [^false]. FileDirectory activeDirectoryClass isCaseSensitive ifTrue: [^extension = aExtension] ifFalse: [^extension sameAs: aExtension]! ! !ExternalDropHandler methodsFor: 'testing' stamp: 'mir 1/10/2002 16:35'! matchesTypes: types (self type isNil or: [types isNil]) ifTrue: [^false]. ^types anySatisfy: [:mimeType | mimeType beginsWith: self type]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ExternalDropHandler class instanceVariableNames: ''! !ExternalDropHandler class methodsFor: 'accessing' stamp: 'mir 1/10/2002 17:17'! defaultHandler DefaultHandler ifNil: [DefaultHandler := ExternalDropHandler type: nil extension: nil action: [:dropStream | dropStream edit]]. ^DefaultHandler! ! !ExternalDropHandler class methodsFor: 'accessing' stamp: 'mir 1/10/2002 16:54'! defaultHandler: externalDropHandler DefaultHandler := externalDropHandler! ! !ExternalDropHandler class methodsFor: 'accessing' stamp: 'mir 8/24/2004 15:37'! lookupExternalDropHandler: stream | types extension serviceHandler | types := stream mimeTypes. types ifNotNil: [ self registeredHandlers do: [:handler | (handler matchesTypes: types) ifTrue: [^handler]]]. extension := FileDirectory extensionFor: stream name. self registeredHandlers do: [:handler | (handler matchesExtension: extension) ifTrue: [^handler]]. serviceHandler := self lookupServiceBasedHandler: stream. ^serviceHandler ifNil: [self defaultHandler]! ! !ExternalDropHandler class methodsFor: 'accessing' stamp: 'mir 8/24/2004 17:15'! lookupServiceBasedHandler: dropStream "the file was just droped, let's do our job" | fileName services theOne | fileName := dropStream name. services := (FileList itemsForFile: fileName) reject: [:svc | self unwantedSelectors includes: svc selector]. "no service, default behavior" services isEmpty ifTrue: [^nil]. theOne := self chooseServiceFrom: services. ^theOne ifNotNil: [ExternalDropHandler type: nil extension: nil action: [:stream | theOne performServiceFor: stream]]! ! !ExternalDropHandler class methodsFor: 'accessing' stamp: 'mir 1/10/2002 17:19'! registerHandler: aHandler self registeredHandlers add: aHandler! ! !ExternalDropHandler class methodsFor: 'initialization' stamp: 'mir 1/10/2002 17:37'! initialize "ExternalDropHandler initialize" self resetRegisteredHandlers. self registerHandler: self defaultImageHandler; registerHandler: self defaultGZipHandler; registerHandler: self defaultProjectHandler! ! !ExternalDropHandler class methodsFor: 'initialization' stamp: 'nk 6/12/2004 16:15'! registerStandardExternalDropHandlers "ExternalDropHandler registerStandardExternalDropHandlers" self registeredHandlers add: ( ExternalDropHandler type: 'image/' extension: nil action: [:stream :pasteUp :event | pasteUp addMorph: (World drawingClass withForm: (Form fromBinaryStream: stream binary)) centeredNear: event position])! ! !ExternalDropHandler class methodsFor: 'instance creation' stamp: 'mir 1/10/2002 17:16'! type: aType extension: anExtension action: anAction ^self new type: aType extension: anExtension action: anAction ! ! !ExternalDropHandler class methodsFor: 'private' stamp: 'alain.plantec 2/8/2009 22:06'! chooseServiceFrom: aCollection "private - choose a service from aCollection asking the user if needed" aCollection size = 1 ifTrue: [^ aCollection anyOne]. "" ^ UIManager default chooseFrom: (aCollection collect: [:each | each label]) values: aCollection. ! ! !ExternalDropHandler class methodsFor: 'private' stamp: 'mir 1/10/2002 17:23'! defaultGZipHandler ^ExternalDropHandler type: nil extension: 'gz' action: [:stream :pasteUp :event | stream viewGZipContents]! ! !ExternalDropHandler class methodsFor: 'private' stamp: 'stephane.ducasse 4/13/2009 21:13'! defaultImageHandler | image sketch | ^ExternalDropHandler type: 'image/' extension: nil action: [:stream :pasteUp :event | stream binary. image := Form fromBinaryStream: ((RWBinaryOrTextStream with: stream contents) reset). Project current resourceManager addResource: image url: (FileDirectory urlForFileNamed: stream name) asString. sketch := World drawingClass withForm: image. pasteUp addMorph: sketch centeredNear: event position. image := sketch := nil]! ! !ExternalDropHandler class methodsFor: 'private' stamp: 'mir 1/10/2002 17:38'! defaultProjectHandler ^ExternalDropHandler type: nil extension: 'pr' action: [:stream | ProjectLoading openName: nil stream: stream fromDirectory: nil withProjectView: nil] ! ! !ExternalDropHandler class methodsFor: 'private' stamp: 'mir 1/10/2002 15:57'! registeredHandlers RegisteredHandlers ifNil: [RegisteredHandlers := OrderedCollection new]. ^RegisteredHandlers! ! !ExternalDropHandler class methodsFor: 'private' stamp: 'mir 1/10/2002 15:57'! resetRegisteredHandlers RegisteredHandlers := nil! ! !ExternalDropHandler class methodsFor: 'private' stamp: 'mir 8/24/2004 15:28'! unwantedSelectors "private - answer a collection well known unwanted selectors " ^ #(#removeLineFeeds: #addFileToNewZip: #compressFile: #putUpdate: )! ! Object subclass: #ExternalSemaphoreTable instanceVariableNames: '' classVariableNames: 'ProtectTable' poolDictionaries: '' category: 'System-Support'! !ExternalSemaphoreTable commentStamp: '' prior: 0! By John M McIntosh johnmci@smalltalkconsulting.com This class was written to mange the external semaphore table. When I was writing a Socket test server I discovered various race conditions on the access to the externalSemaphore table. This new class uses class side methods to restrict access using a mutex semaphore. It seemed cleaner to deligate the reponsibility here versus adding more code and another class variable to SystemDictionary Note that in Smalltalk recreateSpecialObjectsArray we still directly play with the table.! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ExternalSemaphoreTable class instanceVariableNames: ''! !ExternalSemaphoreTable class methodsFor: 'accessing' stamp: 'JMM 6/6/2000 20:36'! clearExternalObjects "Clear the array of objects that have been registered for use in non-Smalltalk code." ProtectTable critical: [Smalltalk specialObjectsArray at: 39 put: Array new]. ! ! !ExternalSemaphoreTable class methodsFor: 'accessing' stamp: 'JMM 6/6/2000 21:01'! externalObjects ^ProtectTable critical: [Smalltalk specialObjectsArray at: 39].! ! !ExternalSemaphoreTable class methodsFor: 'accessing' stamp: 'JMM 6/6/2000 20:44'! registerExternalObject: anObject ^ ProtectTable critical: [self safelyRegisterExternalObject: anObject] ! ! !ExternalSemaphoreTable class methodsFor: 'accessing' stamp: 'JMM 6/6/2000 20:57'! safelyRegisterExternalObject: anObject "Register the given object in the external objects array and return its index. If it is already there, just return its index." | objects firstEmptyIndex obj sz newObjects | objects := Smalltalk specialObjectsArray at: 39. "find the first empty slot" firstEmptyIndex := 0. 1 to: objects size do: [:i | obj := objects at: i. obj == anObject ifTrue: [^ i]. "object already there, just return its index" (obj == nil and: [firstEmptyIndex = 0]) ifTrue: [firstEmptyIndex := i]]. "if no empty slots, expand the array" firstEmptyIndex = 0 ifTrue: [ sz := objects size. newObjects := objects species new: sz + 20. "grow linearly" newObjects replaceFrom: 1 to: sz with: objects startingAt: 1. firstEmptyIndex := sz + 1. Smalltalk specialObjectsArray at: 39 put: newObjects. objects := newObjects]. objects at: firstEmptyIndex put: anObject. ^ firstEmptyIndex ! ! !ExternalSemaphoreTable class methodsFor: 'accessing' stamp: 'JMM 6/6/2000 20:59'! safelyUnregisterExternalObject: anObject "Unregister the given object in the external objects array. Do nothing if it isn't registered. JMM change to return if we clear the element, since it should only appear once in the array" | objects | anObject ifNil: [^ self]. objects := Smalltalk specialObjectsArray at: 39. 1 to: objects size do: [:i | (objects at: i) == anObject ifTrue: [objects at: i put: nil. ^self]]. ! ! !ExternalSemaphoreTable class methodsFor: 'accessing' stamp: 'JMM 6/6/2000 20:45'! unregisterExternalObject: anObject ProtectTable critical: [self safelyUnregisterExternalObject: anObject] ! ! !ExternalSemaphoreTable class methodsFor: 'initialize' stamp: 'JMM 6/6/2000 20:32'! initialize ProtectTable := Semaphore forMutualExclusion! ! Object subclass: #ExternalSettings instanceVariableNames: '' classVariableNames: 'RegisteredClients' poolDictionaries: '' category: 'System-Support'! !ExternalSettings commentStamp: '' prior: 0! ExternalSettings manages settings kept externally, e.g. files. Objects can register themselves as clients to be notified at startup time to read their settings. Eventually all the preferences should be managed through this mechanism. ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ExternalSettings class instanceVariableNames: ''! !ExternalSettings class methodsFor: 'accessing' stamp: 'sw 1/25/2002 12:39'! assuredPreferenceDirectory "Answer the preference directory, creating it if necessary" | prefDir | prefDir := self preferenceDirectory. prefDir ifNil: [prefDir := FileDirectory default directoryNamed: self preferenceDirectoryName. prefDir assureExistence]. ^ prefDir! ! !ExternalSettings class methodsFor: 'accessing' stamp: 'dc 5/30/2008 10:17'! parseServerEntryArgsFrom: stream "Args are in the form : delimited by end of line. It's not a very robust format and should be replaced by something like XML later. But it avoids evaluating the entries for security reasons." | entries lineStream entryName entryValue | entries := Dictionary new. stream skipSeparators. [ stream atEnd ] whileFalse: [ lineStream := stream nextLine readStream. entryName := lineStream upTo: $:. lineStream skipSeparators. entryValue := lineStream upToEnd. (entryName isEmptyOrNil or: [ entryValue isEmptyOrNil ]) ifFalse: [ entries at: entryName put: entryValue withoutTrailingBlanks ]. stream skipSeparators ]. ^ entries! ! !ExternalSettings class methodsFor: 'accessing' stamp: 'sd 9/30/2003 14:01'! preferenceDirectory | prefDirName path | prefDirName := self preferenceDirectoryName. path := SmalltalkImage current vmPath. ^(FileDirectory default directoryExists: prefDirName) ifTrue: [FileDirectory default directoryNamed: prefDirName] ifFalse: [ ((FileDirectory on: path) directoryExists: prefDirName) ifTrue: [(FileDirectory on: path) directoryNamed: prefDirName] ifFalse: [nil]] ! ! !ExternalSettings class methodsFor: 'accessing' stamp: 'mir 11/16/2001 13:33'! preferenceDirectoryName ^'prefs'! ! !ExternalSettings class methodsFor: 'accessing' stamp: 'mir 6/25/2001 18:45'! registerClient: anObject "Register anObject as a settings client to be notified on startup." self registeredClients add: anObject! ! !ExternalSettings class methodsFor: 'initialization' stamp: 'ar 8/23/2001 22:56'! initialize "ExternalSettings initialize" "Order: ExternalSettings, SecurityManager, AutoStart" Smalltalk addToStartUpList: self. Smalltalk addToShutDownList: self! ! !ExternalSettings class methodsFor: 'initialization' stamp: 'mir 8/22/2001 15:17'! shutDown "Look for external defs and load them." "ExternalSettings shutDown" self registeredClients do: [:client | client releaseExternalSettings]! ! !ExternalSettings class methodsFor: 'initialization' stamp: 'mir 11/16/2001 13:29'! startUp "Look for external defs and load them." "ExternalSettings startUp" | prefDir | prefDir := self preferenceDirectory. prefDir ifNil: [^self]. self registeredClients do: [:client | client fetchExternalSettingsIn: prefDir]! ! !ExternalSettings class methodsFor: 'private' stamp: 'mir 6/25/2001 18:46'! registeredClients RegisteredClients ifNil: [RegisteredClients := Set new]. ^RegisteredClients! ! Object subclass: #FT2BitmapSize instanceVariableNames: 'height width size xPpEm yPpEm' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Base'! !FT2BitmapSize commentStamp: '' prior: 0! Do not rearrange these fields!! This structure models the size of a bitmap strike (i.e., a bitmap instance of the font for a given resolution) in a fixed-size font face. It is used for the `availableSizes' field of the FT2Face structure. height :: The (vertical) baseline-to-baseline distance in pixels. It makes most sense to define the height of a bitmap font in this way. width :: The average width of the font (in pixels). Since the algorithms to compute this value are different for the various bitmap formats, it can only give an additional hint if the `height' value isn't sufficient to select the proper font. For monospaced fonts the average width is the same as the maximum width. size :: The point size in 26.6 fractional format this font shall represent (for a given vertical resolution). x_ppem :: The horizontal ppem value (in 26.6 fractional format). y_ppem :: The vertical ppem value (in 26.6 fractional format). Usually, this is the `nominal' pixel height of the font. The values in this structure are taken from the bitmap font. If the font doesn't provide a parameter it is set to zero to indicate that the information is not available. The following formula converts from dpi to ppem: ppem = size * dpi / 72 where `size' is in points. Windows FNT: The `size' parameter is not reliable: There exist fonts (e.g., app850.fon) which have a wrong size for some subfonts; x_ppem and y_ppem are thus set equal to pixel width and height given in in the Windows FNT header. TrueType embedded bitmaps: `size', `width', and `height' values are not contained in the bitmap strike itself. They are computed from the global font parameters. ! SharedPool subclass: #FT2Constants instanceVariableNames: '' classVariableNames: 'LoadCropBitmap LoadDefault LoadForceAutohint LoadIgnoreGlobalAdvanceWidth LoadIgnoreTransform LoadLinearDesign LoadMonochrome LoadNoAutohint LoadNoBitmap LoadNoHinting LoadNoRecurse LoadNoScale LoadPedantic LoadRender LoadSbitsOnly LoadTargetLCD LoadTargetLCDV LoadTargetLight LoadTargetMono LoadTargetNormal LoadVerticalLayout PixelModeGray PixelModeGray2 PixelModeGray4 PixelModeLCD PixelModeLCDV PixelModeMono PixelModeNone RenderModeLCD RenderModeLCDV RenderModeLight RenderModeMono RenderModeNormal StyleFlagBold StyleFlagItalic' poolDictionaries: '' category: 'FreeType-Base'! !FT2Constants commentStamp: '' prior: 0! The various flags from the Freetype/2 header. The LoadXXXX flags can be used with primitiveLoadGlyph:flags: or with the Cairo primCairoFtFontCreateForFtFace:flags:scale: primitives. FT_LOAD_DEFAULT :: Corresponding to 0, this value is used a default glyph load. In this case, the following will happen: 1. FreeType looks for a bitmap for the glyph corresponding to the face's current size. If one is found, the function returns. The bitmap data can be accessed from the glyph slot (see note below). 2. If no embedded bitmap is searched or found, FreeType looks for a scalable outline. If one is found, it is loaded from the font file, scaled to device pixels, then "hinted" to the pixel grid in order to optimize it. The outline data can be accessed from the glyph slot (see note below). Note that by default, the glyph loader doesn't render outlines into bitmaps. The following flags are used to modify this default behaviour to more specific and useful cases. FT_LOAD_NO_SCALE :: Don't scale the vector outline being loaded to 26.6 fractional pixels, but kept in font units. Note that this also disables hinting and the loading of embedded bitmaps. You should only use it when you want to retrieve the original glyph outlines in font units. FT_LOAD_NO_HINTING :: Don't hint glyph outlines after their scaling to device pixels. This generally generates "blurrier" glyphs in anti-aliased modes. This flag is ignored if @FT_LOAD_NO_SCALE is set. FT_LOAD_RENDER :: Render the glyph outline immediately into a bitmap before the glyph loader returns. By default, the glyph is rendered for the @FT_RENDER_MODE_NORMAL mode, which corresponds to 8-bit anti-aliased bitmaps using 256 opacity levels. You can use either @FT_LOAD_TARGET_MONO or @FT_LOAD_MONOCHROME to render 1-bit monochrome bitmaps. This flag is ignored if @FT_LOAD_NO_SCALE is set. FT_LOAD_NO_BITMAP :: Don't look for bitmaps when loading the glyph. Only scalable outlines will be loaded when available, and scaled, hinted, or rendered depending on other bit flags. This does not prevent you from rendering outlines to bitmaps with @FT_LOAD_RENDER, however. FT_LOAD_VERTICAL_LAYOUT :: Prepare the glyph image for vertical text layout. This basically means that `face.glyph.advance' will correspond to the vertical advance height (instead of the default horizontal advance width), and that the glyph image will be translated to match the vertical bearings positions. FT_LOAD_FORCE_AUTOHINT :: Force the use of the FreeType auto-hinter when a glyph outline is loaded. You shouldn't need this in a typical application, since it is mostly used to experiment with its algorithm. FT_LOAD_CROP_BITMAP :: Indicates that the glyph loader should try to crop the bitmap (i.e., remove all space around its black bits) when loading it. This is only useful when loading embedded bitmaps in certain fonts, since bitmaps rendered with @FT_LOAD_RENDER are always cropped by default. FT_LOAD_PEDANTIC :: Indicates that the glyph loader should perform pedantic verifications during glyph loading, rejecting invalid fonts. This is mostly used to detect broken glyphs in fonts. By default, FreeType tries to handle broken fonts also. FT_LOAD_IGNORE_GLOBAL_ADVANCE_WIDTH :: Indicates that the glyph loader should ignore the global advance width defined in the font. As far as we know, this is only used by the X-TrueType font server, in order to deal correctly with the incorrect metrics contained in DynaLab's TrueType CJK fonts. FT_LOAD_NO_RECURSE :: This flag is only used internally. It merely indicates that the glyph loader should not load composite glyphs recursively. Instead, it should set the `num_subglyph' and `subglyphs' values of the glyph slot accordingly, and set "glyph->format" to @FT_GLYPH_FORMAT_COMPOSITE. The description of sub-glyphs is not available to client applications for now. FT_LOAD_IGNORE_TRANSFORM :: Indicates that the glyph loader should not try to transform the loaded glyph image. This doesn't prevent scaling, hinting, or rendering. FT_LOAD_MONOCHROME :: This flag is used with @FT_LOAD_RENDER to indicate that you want to render a 1-bit monochrome glyph bitmap from a vectorial outline. Note that this has no effect on the hinting algorithm used by the glyph loader. You should better use @FT_LOAD_TARGET_MONO if you want to render monochrome-optimized glyph images instead. FT_LOAD_LINEAR_DESIGN :: Return the linearly scaled metrics expressed in original font units instead of the default 16.16 pixel values. FT_LOAD_NO_AUTOHINT :: Indicates that the auto-hinter should never be used to hint glyph outlines. This doesn't prevent native format-specific hinters from being used. This can be important for certain fonts where unhinted output is better than auto-hinted one. One of following flags (as LoadTargetXXX) can be used to further specify the result. FT_RENDER_MODE_NORMAL :: This is the default render mode; it corresponds to 8-bit anti-aliased bitmaps, using 256 levels of opacity. FT_RENDER_MODE_LIGHT :: This is similar to @FT_RENDER_MODE_NORMAL, except that this changes the hinting to prevent stem width quantization. This results in glyph shapes that are more similar to the original, while being a bit more fuzzy ("better shapes", instead of "better contrast" if you want :-). FT_RENDER_MODE_MONO :: This mode corresponds to 1-bit bitmaps. FT_RENDER_MODE_LCD :: This mode corresponds to horizontal RGB/BGR sub-pixel displays, like LCD-screens. It produces 8-bit bitmaps that are 3 times the width of the original glyph outline in pixels, and which use the @FT_PIXEL_MODE_LCD mode. FT_RENDER_MODE_LCD_V :: This mode corresponds to vertical RGB/BGR sub-pixel displays (like PDA screens, rotated LCD displays, etc.). It produces 8-bit bitmaps that are 3 times the height of the original glyph outline in pixels and use the @FT_PIXEL_MODE_LCD_V mode. The LCD-optimized glyph bitmaps produced by FT_Render_Glyph are _not filtered_ to reduce color-fringes. It is up to the caller to perform this pass. ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FT2Constants class instanceVariableNames: ''! !FT2Constants class methodsFor: 'class initialization' stamp: 'tween 8/13/2006 15:55'! initialize "FT2Constants initialize" LoadDefault := 0. LoadNoScale := 1. LoadNoHinting := 2. LoadRender := 4. LoadNoBitmap := 8. LoadVerticalLayout := 16. LoadForceAutohint := 32. LoadCropBitmap := 64. LoadPedantic := 128. LoadIgnoreGlobalAdvanceWidth := 512. LoadNoRecurse := 1024. LoadIgnoreTransform := 2048. LoadMonochrome := 4096. LoadLinearDesign := 8192. LoadSbitsOnly := 16384. LoadNoAutohint := 32768. "One of these flags may be OR'd with the above." LoadTargetNormal := 0. LoadTargetLight := 1 bitShift: 16. LoadTargetMono := 2 bitShift: 16. LoadTargetLCD := 3 bitShift: 16. LoadTargetLCDV := 4 bitShift: 16. "rendering mode constants" RenderModeNormal := 0. RenderModeLight := 1. RenderModeMono := 2. RenderModeLCD := 3. RenderModeLCDV := 4. "pixel mode constants" PixelModeNone := 0. PixelModeMono := 1. PixelModeGray := 2. PixelModeGray2 := 3. PixelModeGray4 := 4. PixelModeLCD := 5. PixelModeLCDV := 6. StyleFlagItalic := 1. StyleFlagBold := 2. ! ! Error subclass: #FT2Error instanceVariableNames: 'errorCode errorString' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Base'! !FT2Error commentStamp: '' prior: 0! This is an Error that knows how to get the Freetype2 error code and string.! !FT2Error methodsFor: 'accessing' stamp: 'nk 11/4/2004 13:31'! errorCode errorCode ifNotNil: [^ errorCode]. ^ errorCode := [FT2Library errorCode] on: Error do: [:ex | ex return: 'can''t get error code']! ! !FT2Error methodsFor: 'accessing' stamp: 'nk 11/4/2004 13:31'! errorString errorString ifNotNil: [^ errorString]. ^ errorString := [FT2Library errorString] on: Error do: [:ex | ex return: 'can''t get error string']! ! !FT2Error methodsFor: 'accessing' stamp: 'nk 3/17/2005 12:50'! messageText ^String streamContents: [ :strm | messageText ifNotNil: [ strm nextPutAll: messageText; space ]. self errorCode isZero ifFalse: [ strm nextPutAll: '[error '; print: self errorCode; nextPutAll: ']['; nextPutAll: self errorString; nextPut: $] ]]! ! FT2Handle subclass: #FT2Face instanceVariableNames: 'numFaces faceIndex faceFlags styleFlags numGlyphs familyName styleName numFixedSizes availableSizes numCharmaps charmaps bbox unitsPerEm ascender descender height maxAdvanceWidth maxAdvanceHeight underlinePosition underlineThickness glyph encoding platformId encodingId size' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Base'! !FT2Face commentStamp: '' prior: 0! Do not rearrange these fields!! New fields should go at the end, because the plugin has to know about these indexes. ByteArray representing a pointer to the malloc'd FT_Face struct: handle Copied from the FT_Face struct on creation: numFaces faceIndex faceFlags styleFlags numGlyphs familyName styleName numFixedSizes availableSizes numCharmaps charmaps Copied on creation, but only relevant to scalable outlines: bbox unitsPerEm ascender descender height maxAdvanceWidth maxAdvanceHeight underlinePosition underlineThickness Working memory: glyph -- FT2GlyphSlot, set by loadGlyph or loadChar size -- the active size, set by activateSize, used by loadGlyph, getKerning, etc. charmap -- set by setCharmap ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! ascender ^ascender! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! availableSizes ^availableSizes! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 17:06'! bbox bbox ifNil: [bbox := Rectangle new. self primLoadBbox: bbox]. ^ bbox! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 21:05'! charmaps "Answer an Array of Strings naming the different character maps available for setCharMap:" charmaps ifNil: [ charmaps := Array new: numCharmaps. self getCharMapsInto: charmaps ]. ^charmaps! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! descender ^descender! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 20:46'! encoding encoding ifNil: [ self getCharMap ]. ^encoding! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! faceFlags ^faceFlags! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! faceIndex ^faceIndex! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! familyName ^familyName! ! !FT2Face methodsFor: 'accessing' stamp: 'bf 11/17/2005 15:56'! glyph glyph ifNil: [ glyph := FT2GlyphSlot fromFace: self ]. ^glyph! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! handle ^handle! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! height ^height! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! maxAdvanceHeight ^maxAdvanceHeight! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! maxAdvanceWidth ^maxAdvanceWidth! ! !FT2Face methodsFor: 'accessing' stamp: 'tween 7/24/2006 22:49'! memoryFaceData self subclassResponsibility! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! numCharmaps ^numCharmaps! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! numFaces ^numFaces! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! numFixedSizes ^numFixedSizes! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! numGlyphs ^numGlyphs! ! !FT2Face methodsFor: 'accessing' stamp: 'tween 8/11/2007 11:24'! postscriptName ^self primGetPostscriptName! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! size ^size! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! styleFlags ^styleFlags! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! styleName ^styleName! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! underlinePosition ^underlinePosition! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! underlineThickness ^underlineThickness! ! !FT2Face methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:56'! unitsPerEm ^unitsPerEm! ! !FT2Face methodsFor: 'charmaps' stamp: 'nk 11/3/2004 19:36'! getCharMap self primGetCharMap.! ! !FT2Face methodsFor: 'charmaps' stamp: 'nk 11/3/2004 20:38'! getCharMapsInto: array self primGetCharMapsInto: array.! ! !FT2Face methodsFor: 'charmaps' stamp: 'nk 11/3/2004 20:39'! setCharMap: encodingString self primSetCharMap: encodingString. self primGetCharMap. ! ! !FT2Face methodsFor: 'glyphs' stamp: 'jl 5/30/2006 14:08'! glyphOfCharacter: aCharacter "load a glyph with outline, glyph is not scaled " | em aGlyph | em := self unitsPerEm. self validate. self setPixelWidth: em height: em. self loadCharacter: aCharacter asInteger flags: LoadIgnoreTransform. "load glyph metrics" aGlyph := self glyph shallowCopy. " copy because 'face glyph' is only a slot" aGlyph outline: (self characterOutline: aCharacter). ^aGlyph! ! !FT2Face methodsFor: 'glyphs' stamp: 'nk 11/3/2004 18:25'! loadCharacter: index flags: flags self primLoadCharacter: index flags: flags. glyph ifNil: [ glyph := FT2GlyphSlot fromFace: self ] ifNotNil: [ glyph loadFrom: self ]. ! ! !FT2Face methodsFor: 'glyphs' stamp: 'nk 11/3/2004 18:25'! loadGlyph: index flags: flags self primLoadGlyph: index flags: flags. glyph ifNil: [ glyph := FT2GlyphSlot fromFace: self ] ifNotNil: [ glyph loadFrom: self ]. ! ! !FT2Face methodsFor: 'glyphs' stamp: 'nk 11/3/2004 18:23'! setPixelWidth: x height: y self primSetPixelWidth: x height: y! ! !FT2Face methodsFor: 'initialize-release' stamp: 'tween 8/12/2006 10:01'! newFaceFromExternalMemory: aFreeTypeExternalMemory index: anInteger | memSize | aFreeTypeExternalMemory validate. memSize := aFreeTypeExternalMemory bytes size. [self primNewFaceFromExternalMemory: aFreeTypeExternalMemory size: memSize index: anInteger] on: FT2Error do:[:e |"need to do something here?"]. self isValid ifTrue:[self class register: self]! ! !FT2Face methodsFor: 'initialize-release' stamp: 'tween 3/16/2007 03:58'! newFaceFromFile: fileName index: anInteger [self primNewFaceFromFile: fileName index: anInteger] on: FT2Error do:[:e | ^self "need to do something here?"]. self class register: self.! ! !FT2Face methodsFor: 'kerning' stamp: 'tween 3/11/2007 21:17'! kerningLeft: leftCharacter right: rightCharacter [^self primGetKerningLeft: (self primGetCharIndex: leftCharacter asInteger) right: (self primGetCharIndex: rightCharacter asInteger) ] on: FT2Error do:[:e | ^0@0]! ! !FT2Face methodsFor: 'outlines' stamp: 'jl 5/24/2006 15:22'! loadCharacterOutline: index flags: flags | em outline | em := unitsPerEm. self setPixelWidth: em height: em. self loadCharacter: index flags: flags. outline := FT2Outline new. outline primLoadSizesFrom: self. outline allocateArrays. outline primLoadArraysFrom: self. ^outline! ! !FT2Face methodsFor: 'printing' stamp: 'tween 7/28/2006 14:53'! printOn: aStream super printOn: aStream. handle isNil ifTrue: [^self]. "self familyName isNil ifTrue: [ self loadFields ]." aStream nextPut: $[; nextPutAll: (self familyName ifNil: ['?']); space; nextPutAll: (self styleName ifNil: ['?']); nextPut: $]! ! !FT2Face methodsFor: 'rendering' stamp: 'bf 11/21/2005 18:07'! angle: angle scale: scale offset: aPoint | one matrix delta | one := (16r10000 * scale) asInteger. matrix := IntegerArray new: 4. angle isZero ifTrue: [ matrix at: 1 put: one. matrix at: 4 put: one. ] ifFalse: [ | phi cos sin | phi := angle degreesToRadians. cos := (phi sin * one) rounded. sin := (phi cos * one) rounded. matrix at: 1 put: sin. matrix at: 2 put: cos negated. matrix at: 3 put: cos. matrix at: 4 put: sin. ]. delta := IntegerArray new: 2. delta at: 1 put: (aPoint x * 64) rounded. delta at: 2 put: (aPoint y * 64) rounded. self primSetTransform: matrix delta: delta. ! ! !FT2Face methodsFor: 'rendering' stamp: 'tween 8/2/2006 10:05'! angle: angle scale: scale offset: aPoint slant: slant | one matrix delta slantOne | one := (16r10000 * scale) asInteger. slantOne := (16r10000 * scale* slant) asInteger. matrix := IntegerArray new: 4. angle isZero ifTrue: [ matrix at: 1 put: one. matrix at: 2 put: slantOne. matrix at: 4 put: one. ] ifFalse: [ | phi cos sin | phi := angle degreesToRadians. cos := (phi sin * one) rounded. sin := (phi cos * one) rounded. matrix at: 1 put: sin. matrix at: 2 put: cos negated. matrix at: 3 put: cos. matrix at: 4 put: sin. ]. delta := IntegerArray new: 2. delta at: 1 put: (aPoint x * 64) rounded. delta at: 2 put: (aPoint y * 64) rounded. self primSetTransform: matrix delta: delta. ! ! !FT2Face methodsFor: 'rendering' stamp: 'tween 3/22/2006 23:07'! angle: angle scalePoint: scalePoint offset: aPoint | oneX oneY matrix delta | oneX := (16r10000 * scalePoint x) asInteger. oneY := (16r10000 * scalePoint y) asInteger. matrix := IntegerArray new: 4. angle isZero ifTrue: [ matrix at: 1 put: oneX. matrix at: 4 put: oneY. ] ifFalse: [ | phi cos sin | phi := angle degreesToRadians. cos := (phi sin * oneX) rounded. sin := (phi cos * oneY) rounded. matrix at: 1 put: sin. matrix at: 2 put: cos negated. matrix at: 3 put: cos. matrix at: 4 put: sin. ]. delta := IntegerArray new: 2. delta at: 1 put: (aPoint x * 64) rounded. delta at: 2 put: (aPoint y * 64) rounded. self primSetTransform: matrix delta: delta. ! ! !FT2Face methodsFor: 'rendering' stamp: 'tween 8/2/2006 17:40'! angle: angle scalePoint: scalePoint offset: aPoint slant: slant | oneX oneY matrix delta slantOne| oneX := (16r10000 * scalePoint x) asInteger. oneY := (16r10000 * scalePoint y) asInteger. slantOne := (16r10000 * scalePoint x * slant) asInteger. matrix := IntegerArray new: 4. angle isZero ifTrue: [ matrix at: 1 put: oneX. matrix at: 2 put: slantOne. matrix at: 4 put: oneY. ] ifFalse: [ | phi cos sin | phi := angle degreesToRadians. cos := (phi sin * oneX) rounded. sin := (phi cos * oneY) rounded. matrix at: 1 put: sin. matrix at: 2 put: cos negated. matrix at: 3 put: cos. matrix at: 4 put: sin. ]. delta := IntegerArray new: 2. delta at: 1 put: (aPoint x * 64) rounded. delta at: 2 put: (aPoint y * 64) rounded. self primSetTransform: matrix delta: delta. ! ! !FT2Face methodsFor: 'rendering' stamp: 'tween 8/2/2006 21:19'! emboldenOutline: strength ^self primEmboldenGlyphSlotOutline: (strength * 64) rounded! ! !FT2Face methodsFor: 'rendering' stamp: 'bf 11/19/2005 12:56'! renderGlyphIntoForm: aForm "render the current glyph (selected by loadChar/loadGlyph into the given form (1 or 8 bpp)" self primRenderGlyphIntoForm: aForm ! ! !FT2Face methodsFor: 'rendering' stamp: 'tween 8/13/2006 15:57'! renderGlyphIntoForm: aForm pixelMode: anInteger "render the current glyph (selected by loadChar/loadGlyph into the given form (1 or 8 bpp) with pixel mode anInteger " self primRenderGlyphIntoForm: aForm pixelMode: anInteger ! ! !FT2Face methodsFor: 'rendering' stamp: 'tween 8/2/2006 20:47'! transformOutlineAngle: angle scalePoint: scalePoint slant: slant | oneX oneY matrix slantOne| oneX := (16r10000 * scalePoint x) asInteger. oneY := (16r10000 * scalePoint y) asInteger. slantOne := (16r10000 * scalePoint x * slant) asInteger. matrix := IntegerArray new: 4. angle isZero ifTrue: [ matrix at: 1 put: oneX. matrix at: 2 put: slantOne. matrix at: 4 put: oneY. ] ifFalse: [ | phi cos sin | phi := angle degreesToRadians. cos := (phi sin * oneX) rounded. sin := (phi cos * oneY) rounded. matrix at: 1 put: sin. matrix at: 2 put: cos negated. matrix at: 3 put: cos. matrix at: 4 put: sin. ]. self primTransformGlyphSlotOutline: matrix! ! !FT2Face methodsFor: 'rendering' stamp: 'tween 8/2/2006 20:48'! translateOutlineBy: aPoint | delta| delta := IntegerArray new: 2. delta at: 1 put: (aPoint x * 64) rounded. delta at: 2 put: (aPoint y * 64) rounded. self primTranslateGlyphSlotOutline: delta.! ! !FT2Face methodsFor: 'testing' stamp: 'tween 8/7/2006 08:46'! isBold styleFlags == nil ifTrue:[^false]. ^styleFlags allMask: StyleFlagBold! ! !FT2Face methodsFor: 'testing' stamp: 'tween 8/7/2006 08:47'! isFixedWidth styleFlags == nil ifTrue:[^false]. ^faceFlags allMask: 4 "FT:=FACE:=FLAG:=FIXED:=WIDTH" ! ! !FT2Face methodsFor: 'testing' stamp: 'tween 8/7/2006 08:47'! isItalic styleFlags == nil ifTrue:[^false]. ^styleFlags allMask: StyleFlagItalic! ! !FT2Face methodsFor: 'testing' stamp: 'tween 8/7/2006 08:47'! isRegular styleFlags == nil ifTrue:[^true]. ^styleFlags = 0! ! !FT2Face methodsFor: 'private' stamp: 'tween 7/31/2006 21:30'! loadFields self isValid ifTrue:[ [self primLoadFields] on: FT2Error do:[:e | "need to do something here"]]! ! !FT2Face methodsFor: 'private' stamp: 'tween 7/29/2006 11:31'! primLoadFields ^self primitiveFailed! ! !FT2Face methodsFor: 'private-primitives' stamp: 'tween 8/6/2006 15:47'! primDestroyHandle ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'tween 8/2/2006 21:14'! primEmboldenGlyphSlotOutline: strengthInteger ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'jl 5/30/2006 13:21'! primGetCharIndex: characterCode "Return the glyph index of a given character code" ^self primitiveFailed. ! ! !FT2Face methodsFor: 'private-primitives' stamp: 'nk 11/3/2004 19:35'! primGetCharMap ^self primitiveFailed! ! !FT2Face methodsFor: 'private-primitives' stamp: 'nk 11/4/2004 13:35'! primGetCharMapsInto: array ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'jl 5/30/2006 13:23'! primGetKerningLeft: leftGlyphIndex right: rightGlyphIndex "self primGetKerningLeft: $V asInteger right: $a asInteger " ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'tween 8/11/2007 11:24'! primGetPostscriptName ^nil! ! !FT2Face methodsFor: 'private-primitives' stamp: 'jl 5/30/2006 15:59'! primGetTrackKerningPointSize: pointSize degree: degree ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'jl 5/29/2006 15:52'! primHasKerning ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'nk 11/4/2004 13:34'! primLoadBbox: aRectangle ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'nk 11/3/2004 18:05'! primLoadCharacter: index flags: flags ^self primitiveFailed! ! !FT2Face methodsFor: 'private-primitives' stamp: 'nk 11/3/2004 18:05'! primLoadGlyph: index flags: flags ^self primitiveFailed! ! !FT2Face methodsFor: 'private-primitives' stamp: 'nk 11/3/2004 15:58'! primNewFaceFromFile: fileName index: anInteger ^self primitiveFailed! ! !FT2Face methodsFor: 'private-primitives' stamp: 'tween 7/24/2006 21:10'! primNewMemoryFaceByteSize: anInteger index: anInteger2 ^self primitiveFailed! ! !FT2Face methodsFor: 'private-primitives' stamp: 'bf 11/19/2005 12:56'! primRenderGlyphIntoForm: aForm ^self primitiveFailed! ! !FT2Face methodsFor: 'private-primitives' stamp: 'tween 8/13/2006 15:56'! primRenderGlyphIntoForm: aForm pixelMode: anInteger ^self primitiveFailed! ! !FT2Face methodsFor: 'private-primitives' stamp: 'bf 11/18/2005 19:33'! primSetBitmapLeft: x top: y ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'nk 11/3/2004 19:35'! primSetCharMap: encodingString ^self primitiveFailed! ! !FT2Face methodsFor: 'private-primitives' stamp: 'nk 11/4/2004 13:35'! primSetPixelWidth: x height: y ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'bf 11/19/2005 15:36'! primSetTransform: matrixWordArray delta: deltaWordArray "matrix is 16.16 fixed point x' = x*m[0] + y*m[1] y' = x*m[2] + y*yy[3] delta is 26.6 fixed point x' = x + d[0] y' = y + d[1] " ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'tween 8/2/2006 20:45'! primTransformGlyphSlotOutline: anIntegerArray ^self primitiveFailed.! ! !FT2Face methodsFor: 'private-primitives' stamp: 'tween 8/2/2006 20:45'! primTranslateGlyphSlotOutline: anIntegerArray ^self primitiveFailed.! ! Object subclass: #FT2GlyphSlot instanceVariableNames: 'face linearHorizontalAdvance linearVerticalAdvance advanceX advanceY format bitmapLeft bitmapTop width height hBearingX hBearingY hAdvance vBearingX vBearingY vAdvance outline' classVariableNames: '' poolDictionaries: 'FT2Constants' category: 'FreeType-Base'! !FT2GlyphSlot commentStamp: '' prior: 0! Do not rearrange these fields!! face -- the FT2Face that owns this FT2GlyphSlot. Note that even when the glyph image is transformed, the metrics are not. linearHoriAdvance -- For scalable formats only, this field holds the linearly scaled horizontal advance width for the glyph (i.e. the scaled and unhinted value of the hori advance). This can be important to perform correct WYSIWYG layout. Note that this value is expressed by default in 16.16 pixels. However, when the glyph is loaded with the FT_LOAD_LINEAR_DESIGN flag, this field contains simply the value of the advance in original font units. linearVertAdvance -- For scalable formats only, this field holds the linearly scaled vertical advance height for the glyph. See linearHoriAdvance for comments. advance -- This is the transformed advance width for the glyph. format -- This field indicates the format of the image contained in the glyph slot. Typically FT_GLYPH_FORMAT_BITMAP, FT_GLYPH_FORMAT_OUTLINE, and FT_GLYPH_FORMAT_COMPOSITE, but others are possible. bitmap -- This field is used as a bitmap descriptor when the slot format is FT_GLYPH_FORMAT_BITMAP. Note that the address and content of the bitmap buffer can change between calls of @FT_Load_Glyph and a few other functions. bitmap_left -- This is the bitmap's left bearing expressed in integer pixels. Of course, this is only valid if the format is FT_GLYPH_FORMAT_BITMAP. bitmap_top -- This is the bitmap's top bearing expressed in integer pixels. Remember that this is the distance from the baseline to the top-most glyph scanline, upwards y-coordinates being *positive*. outline -- The outline descriptor for the current glyph image if its format is FT_GLYPH_FORMAT_OUTLINE. num_subglyphs -- The number of subglyphs in a composite glyph. This field is only valid for the composite glyph format that should normally only be loaded with the @FT_LOAD_NO_RECURSE flag. For now this is internal to FreeType. subglyphs -- An array of subglyph descriptors for composite glyphs. There are `num_subglyphs' elements in there. Currently internal to FreeType. control_data -- Certain font drivers can also return the control data for a given glyph image (e.g. TrueType bytecode, Type 1 charstrings, etc.). This field is a pointer to such data. control_len -- This is the length in bytes of the control data. other -- Really wicked formats can use this pointer to present their own glyph image to client apps. Note that the app will need to know about the image format. width, height, hBearingX, hBearingY, hAdvance, vBearingX, vBearingY, vAdvance -- The metrics of the last loaded glyph in the slot. The returned values depend on the last load flags (see the @FT_Load_Glyph API function) and can be expressed either in 26.6 fractional pixels or font units. ! !FT2GlyphSlot methodsFor: 'accessing-convenience' stamp: 'bf 11/19/2005 17:16'! advance ^advanceX@advanceY! ! !FT2GlyphSlot methodsFor: 'accessing-convenience' stamp: 'bf 11/20/2005 14:42'! extent ^width@height! ! !FT2GlyphSlot methodsFor: 'accessing-convenience' stamp: 'bf 11/20/2005 14:56'! hBearing ^hBearingX@hBearingY! ! !FT2GlyphSlot methodsFor: 'accessing-convenience' stamp: 'tween 8/5/2007 11:14'! linearAdvance ^"("(linearHorizontalAdvance @ linearVerticalAdvance) "* 2540) rounded" ! ! !FT2GlyphSlot methodsFor: 'accessing-convenience' stamp: 'tween 3/11/2007 08:56'! roundedPixelLinearAdvance "Answer the scaled linearAdvance, rounded to whole pixels" ^linearHorizontalAdvance rounded @ linearVerticalAdvance rounded ! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'nk 11/3/2004 12:11'! advanceX ^advanceX! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'nk 11/3/2004 12:11'! advanceY ^advanceY! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'nk 11/3/2004 12:11'! bitmapLeft ^bitmapLeft! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'nk 11/3/2004 12:11'! bitmapTop ^bitmapTop! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'nk 11/3/2004 12:11'! format ^format! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'bf 11/20/2005 14:52'! hBearingX ^hBearingX! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'bf 11/20/2005 14:52'! hBearingY ^hBearingY! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'bf 11/20/2005 14:53'! height ^height! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'nk 11/3/2004 12:11'! linearHorizontalAdvance ^linearHorizontalAdvance! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'nk 11/3/2004 12:11'! linearVerticalAdvance ^linearVerticalAdvance! ! !FT2GlyphSlot methodsFor: 'accessing-fields' stamp: 'bf 11/20/2005 14:53'! width ^width! ! !FT2GlyphSlot methodsFor: 'private' stamp: 'bf 11/20/2005 14:43'! loadFrom: anFT2Face face := anFT2Face. self primLoadFrom: anFT2Face. format := ((SmalltalkImage current isLittleEndian) ifTrue: [ format reversed ] ifFalse: [ format ]) asString. linearHorizontalAdvance := linearHorizontalAdvance / 65536.0. linearVerticalAdvance isZero ifFalse: [ linearVerticalAdvance := linearVerticalAdvance / 65536.0 ]. advanceX := advanceX bitShift: -6. advanceY isZero ifFalse: [ advanceY := advanceY bitShift: -6 ]. width := width + 63 bitShift: -6. "round up" height := height + 63 bitShift: -6. "round up" hBearingX := hBearingX bitShift: -6. hBearingY := hBearingY bitShift: -6. hAdvance := hAdvance bitShift: -6. vBearingX := vBearingX bitShift: -6. vBearingY := vBearingY bitShift: -6. vAdvance := vAdvance bitShift: -6.! ! !FT2GlyphSlot methodsFor: 'private' stamp: 'nk 11/3/2004 17:58'! primLoadFrom: anFT2Face ^self primitiveFailed.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FT2GlyphSlot class instanceVariableNames: ''! !FT2GlyphSlot class methodsFor: 'instance creation' stamp: 'nk 11/3/2004 17:38'! fromFace: anFT2Face ^(super new) loadFrom: anFT2Face; yourself.! ! Object subclass: #FT2Handle instanceVariableNames: 'handle' classVariableNames: 'Registry' poolDictionaries: 'FT2Constants' category: 'FreeType-Base'! !FT2Handle commentStamp: '' prior: 0! handle holds a (typically 32-bit) pointer to an externally managed object.! !FT2Handle methodsFor: 'error handling' stamp: 'nk 11/3/2004 13:51'! errorCode ^self primitiveFailed! ! !FT2Handle methodsFor: 'error handling' stamp: 'nk 11/3/2004 21:07'! errorString ^self primitiveFailed! ! !FT2Handle methodsFor: 'error handling' stamp: 'nk 11/4/2004 13:32'! primitiveFailed ^self primitiveFailed: 'Freetype2 primitive failed'! ! !FT2Handle methodsFor: 'error handling' stamp: 'nk 11/4/2004 13:33'! primitiveFailed: aString ^FT2Error new signal: aString! ! !FT2Handle methodsFor: 'finalization' stamp: 'nk 11/3/2004 12:21'! finalize self pvtDestroyHandle. ! ! !FT2Handle methodsFor: 'initialize-release' stamp: 'nk 3/11/2005 18:44'! initialize self shouldNotImplement.! ! !FT2Handle methodsFor: 'printing' stamp: 'nk 3/17/2005 16:40'! isValid ^handle notNil and: [ handle anySatisfy: [ :b | b isZero not ] ]! ! !FT2Handle methodsFor: 'printing' stamp: 'nk 3/17/2005 14:08'! printOn: aStream | handleHex | super printOn: aStream. handle isNil ifTrue: [ ^aStream nextPutAll: '' ]. handleHex := (handle unsignedLongAt: 1 bigEndian: SmalltalkImage current isBigEndian) printStringHex. aStream nextPutAll: '<0x'; nextPutAll: handleHex; nextPut: $>.! ! !FT2Handle methodsFor: 'private' stamp: 'nk 11/3/2004 16:10'! beNull handle := nil.! ! !FT2Handle methodsFor: 'private' stamp: 'nk 11/4/2004 16:44'! destroyHandle self class deregister: self. self pvtDestroyHandle! ! !FT2Handle methodsFor: 'private' stamp: 'nk 11/3/2004 21:19'! handle ^handle! ! !FT2Handle methodsFor: 'private' stamp: 'nk 11/3/2004 12:21'! primDestroyHandle self subclassResponsibility! ! !FT2Handle methodsFor: 'private' stamp: 'nk 11/3/2004 16:23'! pvtDestroyHandle "This should only be sent from the finalizer." handle ifNil: [ ^self ]. self primDestroyHandle. self beNull.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FT2Handle class instanceVariableNames: ''! !FT2Handle class methodsFor: 'class initialization' stamp: 'tween 7/28/2006 07:42'! initialize "FT2Handle initialize" Smalltalk removeFromStartUpList: self. "in case it was added by earlier version" Smalltalk addToShutDownList: self. ! ! !FT2Handle class methodsFor: 'error reporting' stamp: 'nk 11/3/2004 13:51'! errorCode ^self primitiveFailed! ! !FT2Handle class methodsFor: 'error reporting' stamp: 'nk 11/3/2004 15:49'! errorString ^self primitiveFailed! ! !FT2Handle class methodsFor: 'error reporting' stamp: 'nk 11/3/2004 15:50'! moduleErrorCode ^self primitiveFailed! ! !FT2Handle class methodsFor: 'initialize-release' stamp: 'nk 11/3/2004 21:00'! unload Smalltalk removeFromStartUpList: self. Smalltalk removeFromShutDownList: self. ! ! !FT2Handle class methodsFor: 'system startup' stamp: 'nk 3/17/2005 16:23'! clearRegistry Registry ifNotNilDo: [:r | r finalizeValues. r do: [:k | k ifNotNil: [k beNull] ]]. Registry := nil! ! !FT2Handle class methodsFor: 'system startup' stamp: 'AndrewTween 8/31/2009 21:40'! shutDown: quitting "we must not save handles (which are pointers) in the image" self clearRegistry. FreeTypeFace allInstances do:[:i | "destroy any faces that are still being referenced" i isValid ifTrue:[i destroyHandle]]. FT2Handle allSubInstances do: [:h | h beNull]. "if some handle was not registered" ! ! !FT2Handle class methodsFor: 'private-handle registry' stamp: 'nk 3/17/2005 16:28'! deregister: aHandle Registry ifNotNilDo: [ :reg | | finalizer | finalizer := reg remove: aHandle ifAbsent: []. finalizer ifNotNil: [ finalizer beNull ] ]. ! ! !FT2Handle class methodsFor: 'private-handle registry' stamp: 'tween 7/25/2006 00:58'! register: aHandle self registry ifNotNilDo: [ :reg | reg add: aHandle. ^self ]. self error: 'WeakArrays are not supported in this VM!!' ! ! !FT2Handle class methodsFor: 'private-handle registry' stamp: 'nk 3/17/2005 16:51'! registry WeakArray isFinalizationSupported ifFalse:[^nil]. ^Registry ifNil: [ Registry := FT2HandleRegistry new]! ! WeakRegistry subclass: #FT2HandleRegistry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Base'! !FT2HandleRegistry methodsFor: 'as yet unclassified' stamp: 'nk 3/17/2005 16:54'! add: anObject "Add anObject to the receiver. Store the object as well as the associated executor." | executor dup | executor := anObject executor. dup := nil. self protected:[ dup := valueDictionary detect: [ :v | v handle = executor handle ] ifNone: [ ]. valueDictionary at: anObject put: executor. ]. dup ifNotNil: [ self error: 'Duplicate object added!!'. self remove: anObject ]. ^anObject! ! FT2Handle subclass: #FT2Library instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Base'! !FT2Library commentStamp: '' prior: 0! This is a wrapper for the global 'library' in the plugin. It is provided for the use of Cairo APIs that take an FT_Library argument.! !FT2Library methodsFor: 'private-primitives' stamp: 'tween 3/17/2007 14:18'! current ^[self primCurrentLibrary] on: Error do: [:e | nil]! ! !FT2Library methodsFor: 'private-primitives' stamp: 'nk 11/4/2004 13:27'! destroyHandle "This is not a managed handle, but a global. Do nothing."! ! !FT2Library methodsFor: 'private-primitives' stamp: 'nk 11/4/2004 13:32'! primCurrentLibrary ^self primitiveFailed! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FT2Library class instanceVariableNames: ''! !FT2Library class methodsFor: 'instance creation' stamp: 'nk 3/17/2005 14:19'! current ^[ (self basicNew) current ] on: FT2Error do: [ :ex | ex return: nil ].! ! FT2Handle subclass: #FT2MemoryFaceData instanceVariableNames: 'bytes' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Base'! !FT2MemoryFaceData methodsFor: 'accessing' stamp: 'tween 7/24/2006 23:04'! bytes ^bytes ! ! !FT2MemoryFaceData methodsFor: 'accessing' stamp: 'tween 7/24/2006 22:43'! bytes: aByteArray bytes := aByteArray. ! ! !FT2MemoryFaceData methodsFor: 'initialize-release' stamp: 'tween 7/24/2006 21:53'! free ^self destroyHandle! ! !FT2MemoryFaceData methodsFor: 'primitives' stamp: 'tween 7/24/2006 21:52'! primDestroyHandle ^self primitiveFailed.! ! !FT2MemoryFaceData methodsFor: 'primitives' stamp: 'tween 7/24/2006 22:32'! primMalloc: aByteArray "copy aByteArray into newly allocated, external memory, and store the address of that memory in the receiver's handle" ^self primitiveFailed! ! !FT2MemoryFaceData methodsFor: 'validation' stamp: 'tween 7/31/2006 21:48'! validate self isValid ifFalse: [ bytes ifNotNil:[ [self primMalloc: bytes] on: FT2Error do:[:e |"need to do something here?"]. self isValid ifTrue:[self class register: self]]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FT2MemoryFaceData class instanceVariableNames: ''! !FT2MemoryFaceData class methodsFor: 'instance creation' stamp: 'tween 8/6/2006 11:11'! bytes: aByteArray | answer | answer := self basicNew bytes: aByteArray; yourself. ^answer! ! Object subclass: #FT2Outline instanceVariableNames: 'contoursSize pointsSize points tags contours flags' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Base'! !FT2Outline commentStamp: '' prior: 0! @instVar: contoursSize - The number of contours in the outline. @instVar: pointsSize - The number of points in the outline. @instVar: points - an array of 26.6 fixed point integer pairs giving the outline's point coordinates. @instVar: tags - an array of pointsSize bytes, giving each outline point's type. (counting from 0) If bit 0 is unset, the point is 'off' the curve, i.e., a Bézier control point, while it is 'on' when set. Bit 1 is meaningful for 'off' points only. If set, it indicates a third-order Bézier arc control point; and a second-order control point if unset. @instVar: contours - an array of contoursSize shorts, giving the end point of each contour within the outline. For example, the first contour is defined by the points '0' to 'contours[0]', the second one is defined by the points 'contours[0]+1' to 'contours[1]', etc. @instVar: flags - a set of bit flags used to characterize the outline and give hints to the scan-converter and hinter on how to convert/grid-fit it.! !FT2Outline methodsFor: 'accessing' stamp: 'jl 5/24/2006 15:19'! contoursCollection "returns a list of contours with tag => points list pairs" | allPoints result start end | allPoints := self pointCollection. result := OrderedCollection new. start := 1. "no normal iteration because contours size can be bigger than contourSize" 1 to: contoursSize do: [ :i | end := (contours at: i) + 1. "c converion" result add: ((tags copyFrom: start to: end) -> (allPoints copyFrom: start to: end)). start := end + 1. ]. ^result ! ! !FT2Outline methodsFor: 'accessing' stamp: 'jl 5/24/2006 14:26'! pointCollection ^(1 to: pointsSize * 2 by: 2) collect: [ :i | ((points at: i) / 64) @ ((points at: i + 1) / 64)] ! ! !FT2Outline methodsFor: 'private' stamp: 'jl 5/24/2006 13:58'! allocateArrays " allocate the arrays for the primLoadArraysFrom:" points := IntegerArray new: pointsSize * 2. tags := ByteArray new: pointsSize. contours := ShortIntegerArray new: contoursSize.! ! !FT2Outline methodsFor: 'private' stamp: 'jl 5/23/2006 17:01'! primLoadArraysFrom: anFT2Face ^self primitiveFailed.! ! !FT2Outline methodsFor: 'private' stamp: 'jl 5/23/2006 17:01'! primLoadSizesFrom: anFT2Face ^self primitiveFailed.! ! Object subclass: #FT2Version instanceVariableNames: 'major minor patch' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Base'! !FT2Version commentStamp: '' prior: 0! Do not rearrange these fields!! This is used to report FT2 version information. Its fields must remain unchanged, or you must change FT2Plugin>>primitiveVersion.! !FT2Version methodsFor: 'accessing' stamp: 'nk 3/21/2004 11:03'! major ^major! ! !FT2Version methodsFor: 'accessing' stamp: 'nk 3/21/2004 11:03'! minor ^minor! ! !FT2Version methodsFor: 'accessing' stamp: 'nk 11/3/2004 11:17'! patch ^patch! ! !FT2Version methodsFor: 'primitives' stamp: 'nk 11/3/2004 11:20'! libraryVersion ^self primitiveFailed. ! ! !FT2Version methodsFor: 'printing' stamp: 'nk 11/3/2004 11:22'! printOn: aStream aStream print: major; nextPut: $.; print: minor; nextPut:$.; print: patch.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FT2Version class instanceVariableNames: ''! !FT2Version class methodsFor: 'instance creation' stamp: 'nk 11/4/2004 11:10'! current " FT2Version current " ^ [(self new) libraryVersion; yourself] on: Error do: [:ex | ex return: nil]! ! TelnetProtocolClient subclass: #FTPClient instanceVariableNames: 'dataSocket' classVariableNames: '' poolDictionaries: '' category: 'Network-Protocols'! !FTPClient commentStamp: 'mir 5/12/2003 17:55' prior: 0! A minimal FTP client program. Could store all state in inst vars, and use an instance to represent the full state of a connection in progress. But simpler to do all that in one method and have it be a complete transaction. Always operates in passive mode (PASV). All connections are initiated from client in order to get through firewalls. See ServerDirectory openFTP, ServerDirectory getFileNamed:, ServerDirectory putFile:named: for examples of use. See TCP/IP, second edition, by Dr. Sidnie Feit, McGraw-Hill, 1997, Chapter 14, p311.! !FTPClient methodsFor: 'protocol' stamp: 'mir 2/13/2002 18:05'! abortDataConnection self sendCommand: 'ABOR'. self closeDataSocket! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 3/7/2002 13:36'! ascii self sendCommand: 'TYPE A'. self lookForCode: 200! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 3/7/2002 13:36'! binary self sendCommand: 'TYPE I'. self lookForCode: 200! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/13/2002 17:52'! changeDirectoryTo: newDirName self sendCommand: 'CWD ' , newDirName. self checkResponse. ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/19/2002 17:11'! deleteDirectory: dirName self sendCommand: 'RMD ' , dirName. self checkResponse. ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/19/2002 17:12'! deleteFileNamed: fileName self sendCommand: 'DELE ' , fileName. self checkResponse. ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 2/20/2002 13:53'! getDirectory | dirList | self openPassiveDataConnection. self sendCommand: 'LIST'. dirList := self getData. self checkResponse. self checkResponse. ^dirList ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/19/2002 16:50'! getFileList | dirList | self openPassiveDataConnection. self sendCommand: 'NLST'. dirList := self getData. self checkResponse. self checkResponse. ^dirList ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/19/2002 19:23'! getFileNamed: remoteFileName | data | self openPassiveDataConnection. self sendCommand: 'RETR ', remoteFileName. [self checkResponse] on: TelnetProtocolError do: [:ex | self closeDataSocket. ex pass]. data := self getData. self checkResponse. ^data ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 5/9/2003 15:50'! getFileNamed: remoteFileName into: dataStream self openPassiveDataConnection. self sendCommand: 'RETR ', remoteFileName. [self checkResponse] on: TelnetProtocolError do: [:ex | self closeDataSocket. ex pass]. self getDataInto: dataStream. self closeDataSocket. self checkResponse! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 10/31/2000 19:03'! getPartial: limit fileNamed: remoteFileName into: dataStream | data | self openPassiveDataConnection. self sendCommand: 'RETR ', remoteFileName. [self checkResponse] on: TelnetProtocolError do: [:ex | self closeDataSocket. ex pass]. data := self get: limit dataInto: dataStream. self abortDataConnection. ^data ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/12/2002 18:39'! loginUser: userName password: passwdString self user: userName. self password: passwdString. self login! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/19/2002 17:10'! makeDirectory: newDirName self sendCommand: 'MKD ' , newDirName. self checkResponse. ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/14/2002 17:51'! openDataSocket: remoteHostAddress port: dataPort dataSocket := Socket new. dataSocket connectTo: remoteHostAddress port: dataPort! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/14/2002 16:55'! passive self sendCommand: 'PASV'. self lookForCode: 227! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/19/2002 16:54'! putFileNamed: filePath as: fileNameOnServer "FTP a file to the server." | fileStream | fileStream := FileStream readOnlyFileNamed: filePath. fileStream ifNil: [(FileDoesNotExistException fileName: filePath) signal]. self putFileStreamContents: fileStream as: fileNameOnServer ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 12/8/2003 16:54'! putFileStreamContents: fileStream as: fileNameOnServer "FTP a file to the server." self openPassiveDataConnection. self sendCommand: 'STOR ', fileNameOnServer. fileStream reset. [self sendStreamContents: fileStream] ensure: [self closeDataSocket]. self checkResponse. self checkResponse. ! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/14/2002 16:43'! pwd | result | self sendCommand: 'PWD'. self lookForCode: 257. result := self lastResponse. ^result copyFrom: (result indexOf: $")+1 to: (result lastIndexOf: $")-1! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 10/31/2000 13:12'! quit self sendCommand: 'QUIT'. self close! ! !FTPClient methodsFor: 'protocol' stamp: 'mir 11/13/2002 17:50'! removeFileNamed: remoteFileName self sendCommand: 'DELE ', remoteFileName. self checkResponse. ! ! !FTPClient methodsFor: 'protocol' stamp: 'nk 1/26/2005 16:40'! renameFileNamed: oldFileName to: newFileName self sendCommand: 'RNFR ' , oldFileName. self lookForCode: 350. self sendCommand: 'RNTO ' , newFileName. self lookForCode: 250! ! !FTPClient methodsFor: 'private' stamp: 'mir 2/19/2002 18:27'! closeDataSocket self dataSocket ifNotNil: [ self dataSocket closeAndDestroy. self dataSocket: nil] ! ! !FTPClient methodsFor: 'private' stamp: 'mir 10/31/2000 16:24'! dataSocket ^dataSocket! ! !FTPClient methodsFor: 'private' stamp: 'mir 10/31/2000 18:23'! dataSocket: aSocket dataSocket := aSocket! ! !FTPClient methodsFor: 'private' stamp: 'mir 4/7/2003 17:20'! login self user ifNil: [^self]. ["repeat both USER and PASS since some servers require it" self sendCommand: 'USER ', self user. "331 Password required" self lookForCode: 331. "will ask user, if needed" self sendCommand: 'PASS ', self password. "230 User logged in" ([self lookForCode: 230.] on: TelnetProtocolError do: [false]) == false ] whileTrue: [ (LoginFailedException protocolInstance: self) signal: self lastResponse] ! ! !FTPClient methodsFor: 'private' stamp: 'mir 11/14/2002 18:14'! sendStreamContents: aStream self dataSocket sendStreamContents: aStream checkBlock: [self checkForPendingError. true]! ! !FTPClient methodsFor: 'private protocol' stamp: 'svp 10/28/2003 11:06'! get: limit dataInto: dataStream "Reel in data until the server closes the connection or the limit is reached. At the same time, watch for errors on otherSocket." | buf bytesRead currentlyRead | currentlyRead := 0. buf := String new: 4000. [currentlyRead < limit and: [self dataSocket isConnected or: [self dataSocket dataAvailable]]] whileTrue: [ self checkForPendingError. bytesRead := self dataSocket receiveDataWithTimeoutInto: buf. 1 to: (bytesRead min: (limit - currentlyRead)) do: [:ii | dataStream nextPut: (buf at: ii)]. currentlyRead := currentlyRead + bytesRead]. dataStream reset. "position: 0." ^ dataStream! ! !FTPClient methodsFor: 'private protocol' stamp: 'mir 2/13/2002 18:06'! getData | dataStream | dataStream := RWBinaryOrTextStream on: (String new: 4000). self getDataInto: dataStream. self closeDataSocket. ^dataStream contents ! ! !FTPClient methodsFor: 'private protocol' stamp: 'svp 10/28/2003 11:04'! getDataInto: dataStream "Reel in all data until the server closes the connection. At the same time, watch for errors on otherSocket. Don't know how much is coming. Put the data on the stream." | buf bytesRead | buf := String new: 4000. [self dataSocket isConnected or: [self dataSocket dataAvailable]] whileTrue: [ self checkForPendingError. bytesRead := self dataSocket receiveDataWithTimeoutInto: buf. 1 to: bytesRead do: [:ii | dataStream nextPut: (buf at: ii)]]. dataStream reset. "position: 0." ^ dataStream! ! !FTPClient methodsFor: 'private protocol' stamp: 'gk 9/9/2005 09:31'! lookForCode: code ifDifferent: handleBlock "We are expecting a certain numeric code next. However, in the FTP protocol, multiple lines are allowed. If the response is multi-line, the fourth character of the first line is a $- and the last line repeats the numeric code but the code is followed by a space. So it's possible that there are more lines left of the last response that we need to throw away. We use peekForAll: so that we don't discard the next response that is not a continuation line." | headToDiscard | "check for multi-line response" (self lastResponse size > 3 and: [(self lastResponse at: 4) = $-]) ifTrue: ["Discard continuation lines." [headToDiscard := self lastResponse first: 4. [[self stream peekForAll: headToDiscard] whileTrue: [self stream nextLine]] on: Exception do: [:ex | ^handleBlock value: nil]]]. ^ super lookForCode: code ifDifferent: handleBlock! ! !FTPClient methodsFor: 'private protocol' stamp: 'michael.rueger 6/16/2009 11:28'! openPassiveDataConnection | portInfo list dataPort remoteHostAddress remoteAddressString | self sendCommand: 'PASV'. self lookForCode: 227 ifDifferent: [:response | (TelnetProtocolError protocolInstance: self) signal: 'Could not enter passive mode: ' , response]. portInfo := (self lastResponse findTokens: '()') at: 2. list := portInfo findTokens: ','. remoteHostAddress := ByteArray with: (list at: 1) asNumber with: (list at: 2) asNumber with: (list at: 3) asNumber with: (list at: 4) asNumber. remoteAddressString := String streamContents: [:addrStream | remoteHostAddress do: [ :each | each printOn: addrStream ] separatedBy: [ addrStream nextPut: $. ]]. dataPort := (list at: 5) asNumber * 256 + (list at: 6) asNumber. self openDataSocket: (NetNameResolver addressForName: remoteAddressString) port: dataPort! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FTPClient class instanceVariableNames: ''! !FTPClient class methodsFor: 'accessing' stamp: 'mir 10/30/2000 20:10'! defaultPortNumber ^21! ! !FTPClient class methodsFor: 'accessing' stamp: 'mir 2/25/2002 19:08'! logFlag ^#ftp! ! !FTPClient class methodsFor: 'accessing' stamp: 'mir 2/13/2002 17:50'! rawResponseCodes #(200 'Command okay.' 500 'Syntax error, command unrecognized. This may include errors such as command line too long.' 501 'Syntax error in parameters or arguments.' 202 'Command not implemented, superfluous at this site.' 502 'Command not implemented.' 503 'Bad sequence of commands.' 504 'Command not implemented for that parameter.' 110 'Restart marker reply. In this case, the text is exact and not left to the particular implementation; it must read: MARK yyyy = mmmm Where yyyy is User-process data stream marker, and mmmm server''s equivalent marker (note the spaces between markers and "=").' 211 'System status, or system help reply.' 212 'Directory status.' 213 'File status.' 214 'Help message. On how to use the server or the meaning of a particular non-standard command. This reply is useful only to the human user.' 215 'NAME system type. Where NAME is an official system name from the list in the Assigned Numbers document.' 120 'Service ready in nnn minutes.' 220 'Service ready for new user.' 221 'Service closing control connection. Logged out if appropriate.' 421 'Service not available, closing control connection. This may be a reply to any command if the service knows it must shut down.' 125 'Data connection already open; transfer starting.' 225 'Data connection open; no transfer in progress.' 425 'Can''t open data connection.' 226 'Closing data connection. Requested file action successful (for example, file transfer or file abort).' 426 'Connection closed; transfer aborted.' 227 'Entering Passive Mode (h1,h2,h3,h4,p1,p2).' 230 'User logged in, proceed.' 530 'Not logged in.' 331 'User name okay, need password.' 332 'Need account for login.' 532 'Need account for storing files.' 150 'File status okay; about to open data connection.' 250 'Requested file action okay, completed.' 257 '"PATHNAME" created.' 350 'Requested file action pending further information.' 450 'Requested file action not taken. File unavailable (e.g., file busy).' 550 'Requested action not taken. File unavailable (e.g., file not found, no access).' 451 'Requested action aborted. Local error in processing.' 551 'Requested action aborted. Page type unknown.' 452 'Requested action not taken. Insufficient storage space in system.' 552 'Requested file action aborted. Exceeded storage allocation (for current directory or dataset).' 553 'Requested action not taken. File name not allowed.') ! ! Error subclass: #FTPConnectionException instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !FTPConnectionException methodsFor: 'as yet unclassified' stamp: 'RAA 3/9/2001 07:47'! defaultAction self resume! ! !FTPConnectionException methodsFor: 'as yet unclassified' stamp: 'RAA 3/14/2001 15:57'! isResumable ^true! ! Object subclass: #FakeClassPool instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-Tools'! !FakeClassPool commentStamp: '' prior: 0! The sole purpose of this class is to allow the Browser code pane to evaluate the class variables of the class whose method it is showing. It does this by stuffing a pointer to the classpool dictionary of the class being shown into its own classpool. It does this just around a doIt in the code pane. An instance of FakeClasspool is then used as the receiver of the doIt.! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FakeClassPool class instanceVariableNames: ''! !FakeClassPool class methodsFor: 'initialize' stamp: 'dvf 9/27/2005 19:05'! adopt: classOrNil "Temporarily use the classPool and sharedPools of another class" classOrNil isBehavior ifFalse: [classPool := nil. sharedPools := nil] ifTrue: [classPool := classOrNil classPool. sharedPools := classOrNil sharedPools] ! ! Boolean subclass: #False instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Objects'! !False commentStamp: '' prior: 0! False defines the behavior of its single instance, false -- logical negation. Notice how the truth-value checks become direct message sends, without the need for explicit testing. Be aware however that most of these methods are not sent as real messages in normal use. Most are inline coded by the compiler as test and jump bytecodes - avoiding the overhead of the full message sends. So simply redefining these methods here will have no effect.! !False methodsFor: 'controlling'! and: alternativeBlock "Nonevaluating conjunction -- answer with false since the receiver is false." ^self! ! !False methodsFor: 'controlling'! ifFalse: alternativeBlock "Answer the value of alternativeBlock. Execution does not actually reach here because the expression is compiled in-line." ^alternativeBlock value! ! !False methodsFor: 'controlling'! ifFalse: falseAlternativeBlock ifTrue: trueAlternativeBlock "Answer the value of falseAlternativeBlock. Execution does not actually reach here because the expression is compiled in-line." ^falseAlternativeBlock value! ! !False methodsFor: 'controlling'! ifTrue: alternativeBlock "Since the condition is false, answer the value of the false alternative, which is nil. Execution does not actually reach here because the expression is compiled in-line." ^nil! ! !False methodsFor: 'controlling'! ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock "Answer the value of falseAlternativeBlock. Execution does not actually reach here because the expression is compiled in-line." ^falseAlternativeBlock value! ! !False methodsFor: 'controlling'! or: alternativeBlock "Nonevaluating disjunction -- answer value of alternativeBlock." ^alternativeBlock value! ! !False methodsFor: 'logical operations' stamp: 'md 7/30/2005 18:05'! & aBoolean "Evaluating conjunction -- answer false since receiver is false." ^self! ! !False methodsFor: 'logical operations'! not "Negation -- answer true since the receiver is false." ^true! ! !False methodsFor: 'logical operations' stamp: 'em 3/24/2009 14:05'! xor: aBoolean "Posted by Eliot Miranda to squeak-dev on 3/24/2009" ^aBoolean! ! !False methodsFor: 'logical operations'! | aBoolean "Evaluating disjunction (OR) -- answer with the argument, aBoolean." ^aBoolean! ! !False methodsFor: 'printing' stamp: 'ajh 7/1/2004 10:36'! asBit ^ 0! ! !False methodsFor: 'printing'! printOn: aStream aStream nextPutAll: 'false'! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! False class instanceVariableNames: ''! !False class methodsFor: 'as yet unclassified' stamp: 'sw 5/8/2000 11:09'! initializedInstance ^ false! ! ClassTestCase subclass: #FalseTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Objects'! !FalseTest commentStamp: '' prior: 0! This is the unit test for the class False. Unit tests are a good way to exercise the functionality of your system in a repeatable and automatic manner. They are therefore recommended if you plan to release anything. For more information, see: - http://www.c2.com/cgi/wiki?UnitTest - http://minnow.cc.gatech.edu/squeak/1547 - the sunit class category ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:02'! testAND self assert: (false & true) = false. self assert: (false & false) = false.! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:02'! testAnd self assert: (false and: ['alternativeBlock']) = false.! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:03'! testIfFalse self assert: ((false ifFalse: ['alternativeBlock']) = 'alternativeBlock'). ! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:03'! testIfFalseIfTrue self assert: (false ifFalse: ['falseAlternativeBlock'] ifTrue: ['trueAlternativeBlock']) = 'falseAlternativeBlock'. ! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:03'! testIfTrue self assert: (false ifTrue: ['alternativeBlock']) = nil. ! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:03'! testIfTrueIfFalse self assert: (false ifTrue: ['trueAlternativeBlock'] ifFalse: ['falseAlternativeBlock']) = 'falseAlternativeBlock'. ! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:03'! testNew self should: [False new] raise: TestResult error. ! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:03'! testNot self assert: (false not = true).! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:04'! testOR self assert: (false | true) = true. self assert: (false | false) = false.! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:04'! testOr self assert: (false or: ['alternativeBlock']) = 'alternativeBlock'.! ! !FalseTest methodsFor: 'tests' stamp: 'sd 6/5/2005 09:04'! testPrintOn self assert: (String streamContents: [:stream | false printOn: stream]) = 'false'. ! ! !FalseTest methodsFor: 'tests' stamp: 'NikoSchwarz 10/17/2009 18:20'! testXor self assert: (false xor: true) = true. self assert: (false xor: false) = false. self should: [(false xor: [false]) ifTrue: ["This should never be true, do not signal an Error and let the test fail"] ifFalse: [self error: 'OK, this should be false, raise an Error']] raise: Error description: 'a Block argument is not allowed. If it were, answer would be false'.! ! InflateStream subclass: #FastInflateStream instanceVariableNames: '' classVariableNames: 'DistanceMap FixedDistTable FixedLitTable LiteralLengthMap' poolDictionaries: '' category: 'Compression-Streams'! !FastInflateStream commentStamp: '' prior: 0! This class adds the following optimizations to the basic Inflate decompression: a) Bit reversed access If we want to fetch the bits efficiently then we have them in the wrong bit order (e.g., when we should fetch 2r100 we would get 2r001). But since the huffman tree lookup determines the efficiency of the decompression, reversing the bits before traversal is expensive. Therefore the entries in each table are stored in REVERSE BIT ORDER. This is achieved by a reverse increment of the current table index in the huffman table construction phase (see method increment:bits:). According to my measures this speeds up the implementation by about 30-40%. b) Inplace storage of code meanings and extra bits Rather than looking up the meaning for each code during decompression of blocks we store the appropriate values directly in the huffman tables, using a pre-defined mapping. Even though this does not make a big difference in speed, it cleans up the code and allows easier translation into primitive code (which is clearly one goal of this implementation). c) Precomputed huffman tables for fixed blocks So we don't have to compute the huffman tables from scratch. The precomputed tables are not in our superclass to avoid double storage (and my superclass is more intended for documentation anyways).! !FastInflateStream methodsFor: 'bit access' stamp: 'ar 12/4/1998 02:02'! nextSingleBits: n "Fetch the bits all at once" ^self nextBits: n.! ! !FastInflateStream methodsFor: 'huffman trees' stamp: 'ar 12/4/1998 02:26'! distanceMap ^DistanceMap! ! !FastInflateStream methodsFor: 'huffman trees' stamp: 'ar 12/4/1998 01:48'! increment: value bits: nBits "Increment value in reverse bit order, e.g. for a 3 bit value count as follows: 000 / 100 / 010 / 110 001 / 101 / 011 / 111 See the class comment why we need this." | result bit | result := value. "Test the lowest bit first" bit := 1 << (nBits - 1). "If the currently tested bit is set then we need to turn this bit off and test the next bit right to it" [(result bitAnd: bit) = 0] whileFalse:[ "Turn off current bit" result := result bitXor: bit. "And continue testing the next bit" bit := bit bitShift: -1]. "Turn on the right-most bit that we haven't touched in the loop above" ^result bitXor: bit! ! !FastInflateStream methodsFor: 'huffman trees' stamp: 'ar 12/4/1998 02:26'! literalLengthMap ^LiteralLengthMap! ! !FastInflateStream methodsFor: 'inflating' stamp: 'ar 2/2/2001 15:47'! decompressBlock: llTable with: dTable "Process the compressed data in the block. llTable is the huffman table for literal/length codes and dTable is the huffman table for distance codes." | value extra length distance oldPos oldBits oldBitPos | [readLimit < collection size and:[sourcePos <= sourceLimit]] whileTrue:[ "Back up stuff if we're running out of space" oldBits := bitBuf. oldBitPos := bitPos. oldPos := sourcePos. value := self decodeValueFrom: llTable. value < 256 ifTrue:[ "A literal" collection byteAt: (readLimit := readLimit + 1) put: value. ] ifFalse:["length/distance or end of block" value = 256 ifTrue:["End of block" state := state bitAnd: StateNoMoreData. ^self]. "Compute the actual length value (including possible extra bits)" extra := (value bitShift: -16) - 1. length := value bitAnd: 16rFFFF. extra > 0 ifTrue:[length := length + (self nextBits: extra)]. "Compute the distance value" value := self decodeValueFrom: dTable. extra := (value bitShift: -16). distance := value bitAnd: 16rFFFF. extra > 0 ifTrue:[distance := distance + (self nextBits: extra)]. (readLimit + length >= collection size) ifTrue:[ bitBuf := oldBits. bitPos := oldBitPos. sourcePos := oldPos. ^self]. collection replaceFrom: readLimit+1 to: readLimit + length + 1 with: collection startingAt: readLimit - distance + 1. readLimit := readLimit + length. ]. ].! ! !FastInflateStream methodsFor: 'inflating' stamp: 'ar 12/4/1998 19:15'! processFixedBlock litTable := FixedLitTable. distTable := FixedDistTable. state := state bitOr: BlockProceedBit. self proceedFixedBlock.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FastInflateStream class instanceVariableNames: ''! !FastInflateStream class methodsFor: 'initialization' stamp: 'ar 12/21/1999 23:00'! initialize "FastInflateStream initialize" | low high | "Init literal/length map" low := #(3 4 5 6 7 8 9 10 11 13 15 17 19 23 27 31 35 43 51 59 67 83 99 115 131 163 195 227 258 ). high := #(0 0 0 0 0 0 0 0 1 1 1 1 2 2 2 2 3 3 3 3 4 4 4 4 5 5 5 5 0 0). LiteralLengthMap := WordArray new: 256 + 32. 1 to: 257 do:[:i| LiteralLengthMap at: i put: i-1]. 1 to: 29 do:[:i| LiteralLengthMap at: 257+i put: (low at:i) + ( (high at: i) + 1 << 16)]. "Init distance map" high := #(0 0 0 0 1 1 2 2 3 3 4 4 5 5 6 6 7 7 8 8 9 9 10 10 11 11 12 12 13 13). low := #(1 2 3 4 5 7 9 13 17 25 33 49 65 97 129 193 257 385 513 769 1025 1537 2049 3073 4097 6145 8193 12289 16385 24577). DistanceMap := WordArray new: 32. 1 to: 30 do:[:i| DistanceMap at: i put: (low at: i) + ( (high at: i) << 16)]. "Init fixed block huffman tables" FixedLitTable := self basicNew huffmanTableFrom: FixedLitCodes mappedBy: LiteralLengthMap. FixedDistTable := self basicNew huffmanTableFrom: FixedDistCodes mappedBy: DistanceMap.! ! VariableNode subclass: #FieldNode instanceVariableNames: 'fieldDef rcvrNode readNode writeNode' classVariableNames: '' poolDictionaries: '' category: 'Compiler-ParseNodes'! !FieldNode commentStamp: '' prior: 0! FileNode handles field access in Tweak, e.g. self fieldName := foo => self fieldName: foo.! ]style[(90)i! !FieldNode methodsFor: 'accessing' stamp: 'eem 5/12/2008 13:40'! fieldDef ^fieldDef! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! emitForEffect: stack on: strm ! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! emitForValue: stack on: aStream fieldDef accessKey ifNil:[ rcvrNode emitForValue: stack on: aStream. readNode emit: stack args: 0 on: aStream super: false. ] ifNotNil:[ rcvrNode emitForValue: stack on: aStream. super emitForValue: stack on: aStream. readNode emit: stack args: 1 on: aStream super: false. ]. ! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! emitLoad: stack on: strm rcvrNode emitForValue: stack on: strm. fieldDef accessKey ifNotNil:[ super emitForValue: stack on: strm. ].! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! emitStore: stack on: strm fieldDef accessKey ifNil:[ writeNode emit: stack args: 1 on: strm super: false. ] ifNotNil:[ writeNode emit: stack args: 2 on: strm super: false. ].! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! emitStorePop: stack on: strm self emitStore: stack on: strm. strm nextPut: Pop. stack pop: 1.! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! encodeReceiverOn: encoder "encode the receiver node" rcvrNode := encoder encodeVariable: 'self'.! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! sizeForEffect: encoder ^0! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! sizeForStore: encoder rcvrNode ifNil:[self encodeReceiverOn: encoder]. fieldDef accessKey ifNil:[ writeNode ifNil:[writeNode := encoder encodeSelector: fieldDef toSet]. ^(rcvrNode sizeForValue: encoder) + (writeNode size: encoder args: 1 super: false) ]. writeNode ifNil:[writeNode := encoder encodeSelector: #set:to:]. ^(rcvrNode sizeForValue: encoder) + (super sizeForValue: encoder) + (writeNode size: encoder args: 2 super: false)! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! sizeForStorePop: encoder ^(self sizeForStore: encoder) + 1! ! !FieldNode methodsFor: 'code generation' stamp: 'eem 5/12/2008 13:40'! sizeForValue: encoder rcvrNode ifNil:[self encodeReceiverOn: encoder]. fieldDef accessKey ifNil:[ readNode ifNil:[readNode := encoder encodeSelector: fieldDef toGet]. ^(rcvrNode sizeForValue: encoder) + (readNode size: encoder args: 0 super: false) ]. readNode ifNil:[readNode := encoder encodeSelector: #get:]. ^(rcvrNode sizeForValue: encoder) + (super sizeForValue: encoder) + (readNode size: encoder args: 1 super: false)! ! !FieldNode methodsFor: 'initialize-release' stamp: 'eem 5/12/2008 13:40'! fieldDefinition: fieldDefinition self name: fieldDefinition name key: fieldDefinition index: nil type: LdLitType! ! !FieldNode methodsFor: 'initialize-release' stamp: 'eem 5/12/2008 13:40'! name: varName key: objRef index: i type: type fieldDef := objRef. ^super name: varName key: objRef key index: nil type: LdLitType! ! !FieldNode methodsFor: 'testing' stamp: 'eem 5/12/2008 13:40'! assignmentCheck: encoder at: location (encoder cantStoreInto: name) ifTrue: [^location]. fieldDef toSet ifNil:[ encoder interactive ifTrue:[^location]. fieldDef := fieldDef clone assignDefaultSetter. ]. ^-1! ! !FieldNode methodsFor: 'visiting' stamp: 'eem 5/30/2008 09:49'! accept: aVisitor aVisitor visitFieldNode: self! ! !FieldNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 14:52'! emitCodeForEffect: stack encoder: encoder! ! !FieldNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 14:52'! emitCodeForLoad: stack encoder: encoder rcvrNode emitCodeForValue: stack encoder: encoder. fieldDef accessKey ifNotNil:[ super emitCodeForValue: stack encoder: encoder. ].! ! !FieldNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 14:52'! emitCodeForStore: stack encoder: encoder fieldDef accessKey ifNil:[ writeNode emitCode: stack args: 1 encoder: encoder super: false. ] ifNotNil:[ writeNode emitCode: stack args: 2 encoder: encoder super: false. ].! ! !FieldNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 16:18'! emitCodeForStorePop: stack encoder: encoder self emitCodeForStore: stack encoder: encoder. encoder genPop. stack pop: 1.! ! !FieldNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 14:52'! emitCodeForValue: stack encoder: encoder fieldDef accessKey ifNil:[ rcvrNode emitCodeForValue: stack encoder: encoder. readNode emitCode: stack args: 0 encoder: encoder super: false. ] ifNotNil:[ rcvrNode emitCodeForValue: stack encoder: encoder. super emitCodeForValue: stack encoder: encoder. readNode emitCode: stack args: 1 encoder: encoder super: false. ].! ! !FieldNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 14:52'! sizeCodeForEffect: encoder ^0! ! !FieldNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 14:52'! sizeCodeForStore: encoder rcvrNode ifNil:[self encodeReceiverOn: encoder]. fieldDef accessKey ifNil:[ writeNode ifNil:[writeNode := encoder encodeSelector: fieldDef toSet]. ^(rcvrNode sizeCodeForValue: encoder) + (writeNode sizeCode: encoder args: 1 super: false) ]. writeNode ifNil:[writeNode := encoder encodeSelector: #set:to:]. ^(rcvrNode sizeCodeForValue: encoder) + (super sizeCodeForValue: encoder) + (writeNode sizeCode: encoder args: 2 super: false)! ! !FieldNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 17:17'! sizeCodeForStorePop: encoder ^(self sizeCodeForStore: encoder) + encoder sizePop! ! !FieldNode methodsFor: 'code generation (new scheme)' stamp: 'eem 5/14/2008 14:52'! sizeCodeForValue: encoder rcvrNode ifNil:[self encodeReceiverOn: encoder]. fieldDef accessKey ifNil:[ readNode ifNil:[readNode := encoder encodeSelector: fieldDef toGet]. ^(rcvrNode sizeCodeForValue: encoder) + (readNode sizeCode: encoder args: 0 super: false) ]. readNode ifNil:[readNode := encoder encodeSelector: #get:]. ^(rcvrNode sizeCodeForValue: encoder) + (super sizeCodeForValue: encoder) + (readNode sizeCode: encoder args: 1 super: false)! ! Browser subclass: #FileContentsBrowser instanceVariableNames: 'packages infoString' classVariableNames: '' poolDictionaries: '' category: 'Tools-File Contents Browser'! !FileContentsBrowser commentStamp: '' prior: 0! I am a class browser view on a fileout (either a source file (.st) or change set (.cs)). I do not actually load the code into to the system, nor do I alter the classes in the image. Use me to vet code in a comfortable way before loading it into your image. From a FileList, I can be invoked by selecting a source file and selecting the "browse code" menu item from the yellow button menu. I use PseudoClass, PseudoClassOrganizers, and PseudoMetaclass to model the class structure of the source file.! !FileContentsBrowser methodsFor: 'accessing'! contents self updateInfoView. (editSelection == #newClass and:[self selectedPackage notNil]) ifTrue: [^self selectedPackage packageInfo]. editSelection == #editClass ifTrue:[^self modifiedClassDefinition]. ^super contents! ! !FileContentsBrowser methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'! contents: input notifying: aController "The retrieved information has changed and its source must now be updated. The information can be a variety of things, depending on the list selections (such as templates for class or message definition, methods) or the user menu commands (such as definition, comment, hierarchy). Answer the result of updating the source." | aString aText theClass | aString := input asString. aText := input asText. editSelection == #editComment ifTrue: [theClass := self selectedClass. theClass ifNil: [self inform: 'You must select a class before giving it a comment.'. ^ false]. theClass comment: aText. ^ true]. editSelection == #editMessageCategories ifTrue: [^ self changeMessageCategories: aString]. self inform:'You cannot change the current selection'. ^false ! ! !FileContentsBrowser methodsFor: 'accessing'! packages ^packages! ! !FileContentsBrowser methodsFor: 'accessing'! packages: aDictionary packages := aDictionary.! ! !FileContentsBrowser methodsFor: 'accessing'! selectedPackage | cat | cat := self selectedSystemCategoryName. cat isNil ifTrue:[^nil]. ^self packages at: cat asString ifAbsent:[nil]! ! !FileContentsBrowser methodsFor: 'class list' stamp: 'ar 9/27/2005 20:27'! browseMethodFull | myClass | (myClass := self selectedClassOrMetaClass) ifNotNil: [ToolSet browse: myClass realClass selector: self selectedMessageName]! ! !FileContentsBrowser methodsFor: 'class list'! classList "Answer an array of the class names of the selected category. Answer an empty array if no selection exists." (systemCategoryListIndex = 0 or:[self selectedPackage isNil]) ifTrue: [^Array new] ifFalse: [^self selectedPackage classes keys asSortedCollection].! ! !FileContentsBrowser methodsFor: 'class list' stamp: 'DamienCassou 9/23/2009 08:37'! findClass | pattern foundClass classNames index foundPackage | self okToChange ifFalse: [^ self classNotFound]. pattern := (UIManager default request: 'Class Name?') asLowercase. pattern isEmptyOrNil ifTrue: [^ self]. classNames := Set new. self packages do:[:p| classNames addAll: p classes keys]. classNames := classNames asArray select: [:n | (n asLowercase indexOfSubCollection: pattern startingAt: 1) > 0]. classNames isEmpty ifTrue: [^ self]. index := classNames size == 1 ifTrue: [1] ifFalse: [(UIManager default chooseFrom: classNames lines: #())]. index = 0 ifTrue: [^ self]. foundPackage := nil. foundClass := nil. self packages do:[:p| (p classes includesKey: (classNames at: index)) ifTrue:[ foundClass := p classes at: (classNames at: index). foundPackage := p]]. foundClass isNil ifTrue:[^self]. self systemCategoryListIndex: (self systemCategoryList indexOf: foundPackage packageName asSymbol). self classListIndex: (self classList indexOf: foundClass name). ! ! !FileContentsBrowser methodsFor: 'class list' stamp: 'DamienCassou 9/29/2009 09:11'! renameClass | oldName newName | classListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. oldName := self selectedClass name. newName := (self request: 'Please type new class name' initialAnswer: oldName) asSymbol. (newName isEmptyOrNil or:[newName = oldName]) ifTrue: [^ self]. (self selectedPackage classes includesKey: newName) ifTrue: [^ self error: newName , ' already exists in the package']. systemOrganizer classify: newName under: self selectedSystemCategoryName. systemOrganizer removeElement: oldName. self selectedPackage renameClass: self selectedClass to: newName. self changed: #classList. self classListIndex: ((systemOrganizer listAtCategoryNamed: self selectedSystemCategoryName) indexOf: newName). ! ! !FileContentsBrowser methodsFor: 'class list'! selectedClass "Answer the class that is currently selected. Answer nil if no selection exists." self selectedClassName == nil ifTrue: [^nil]. ^self selectedPackage classAt: self selectedClassName! ! !FileContentsBrowser methodsFor: 'creation' stamp: 'md 2/24/2006 15:46'! addLowerPanesTo: window at: nominalFractions with: editString | verticalOffset row codePane infoPane infoHeight divider | row := AlignmentMorph newColumn hResizing: #spaceFill; vResizing: #spaceFill; layoutInset: 0; borderWidth: 1; borderColor: Color black; layoutPolicy: ProportionalLayout new. codePane := MorphicTextEditor default on: self text: #contents accept: #contents:notifying: readSelection: #contentsSelection menu: #codePaneMenu:shifted:. infoPane := PluggableTextMorph on: self text: #infoViewContents accept: nil readSelection: nil menu: nil. infoPane askBeforeDiscardingEdits: false. verticalOffset := 0. ">>not with this browser--- at least not yet --- innerFractions := 0@0 corner: 1@0. verticalOffset := self addOptionalAnnotationsTo: row at: innerFractions plus: verticalOffset. verticalOffset := self addOptionalButtonsTo: row at: innerFractions plus: verticalOffset. <<<<" infoHeight := 20. row addMorph: (codePane borderWidth: 0) fullFrame: ( LayoutFrame fractions: (0@0 corner: 1@1) offsets: (0@verticalOffset corner: 0@infoHeight negated) ). divider := BorderedSubpaneDividerMorph forTopEdge. divider extent: 4@4; color: Color transparent; borderColor: #raised; borderWidth: 2. row addMorph: divider fullFrame: ( LayoutFrame fractions: (0@1 corner: 1@1) offsets: (0@infoHeight negated corner: 0@(1-infoHeight)) ). row addMorph: (infoPane borderWidth: 0; hideScrollBarsIndefinitely) fullFrame: ( LayoutFrame fractions: (0@1 corner: 1@1) offsets: (0@(1-infoHeight) corner: 0@0) ). window addMorph: row frame: nominalFractions. row on: #mouseEnter send: #paneTransition: to: window. row on: #mouseLeave send: #paneTransition: to: window. ! ! !FileContentsBrowser methodsFor: 'creation' stamp: 'alain.plantec 5/30/2008 13:03'! createViews contentsSymbol := self defaultDiffsSymbol. "#showDiffs or #prettyDiffs" ^ self openAsMorph! ! !FileContentsBrowser methodsFor: 'creation' stamp: 'sd 11/20/2005 21:27'! openAsMorph "Create a pluggable version of all the views for a Browser, including views and controllers." | window aListExtent next mySingletonList | window := (SystemWindow labelled: 'later') model: self. self packages size = 1 ifTrue: [ aListExtent := 0.333333 @ 0.34. self systemCategoryListIndex: 1. mySingletonList := PluggableListMorph on: self list: #systemCategorySingleton selected: #indexIsOne changeSelected: #indexIsOne: menu: #packageListMenu: keystroke: #packageListKey:from:. mySingletonList hideScrollBarsIndefinitely. window addMorph: mySingletonList frame: (0@0 extent: 1.0@0.06). next := 0@0.06] ifFalse: [ aListExtent := 0.25 @ 0.4. window addMorph: (PluggableListMorph on: self list: #systemCategoryList selected: #systemCategoryListIndex changeSelected: #systemCategoryListIndex: menu: #packageListMenu: keystroke: #packageListKey:from:) frame: (0@0 extent: aListExtent). next := aListExtent x @ 0]. self addClassAndSwitchesTo: window at: (next extent: aListExtent) plus: 0. next := next + (aListExtent x @ 0). window addMorph: (PluggableListMorph on: self list: #messageCategoryList selected: #messageCategoryListIndex changeSelected: #messageCategoryListIndex: menu: #messageCategoryMenu:) frame: (next extent: aListExtent). next := next + (aListExtent x @ 0). window addMorph: (PluggableListMorph on: self list: #messageList selected: #messageListIndex changeSelected: #messageListIndex: menu: #messageListMenu: keystroke: #messageListKey:from:) frame: (next extent: aListExtent). self addLowerPanesTo: window at: (0@0.4 corner: 1@1) with: nil. ^ window ! ! !FileContentsBrowser methodsFor: 'diffs' stamp: 'sd 11/20/2005 21:27'! methodDiffFor: aString class: aPseudoClass selector: selector meta: meta "Answer the diff between the current copy of the given class/selector/meta for the string provided" | theClass source | theClass := Smalltalk at: aPseudoClass name ifAbsent: [^ aString copy]. meta ifTrue: [theClass := theClass class]. (theClass includesSelector: selector) ifFalse: [^ aString copy]. source := theClass sourceCodeAt: selector. ^ Cursor wait showWhile: [TextDiffBuilder buildDisplayPatchFrom: source to: aString inClass: theClass prettyDiffs: self showingPrettyDiffs]! ! !FileContentsBrowser methodsFor: 'diffs'! modifiedClassDefinition | pClass rClass old new diff | pClass := self selectedClassOrMetaClass. pClass hasDefinition ifFalse:[^pClass definition]. rClass := Smalltalk at: self selectedClass name asSymbol ifAbsent:[nil]. rClass isNil ifTrue:[^pClass definition]. self metaClassIndicated ifTrue:[ rClass := rClass class]. old := rClass definition. new := pClass definition. Cursor wait showWhile:[ diff := ClassDiffBuilder buildDisplayPatchFrom: old to: new ]. ^diff! ! !FileContentsBrowser methodsFor: 'edit pane' stamp: 'md 2/13/2006 14:36'! selectedBytecodes "Compile the source code for the selected message selector and extract and return the bytecode listing." | class selector | class := self selectedClassOrMetaClass. selector := self selectedMessageName. contents := class sourceCodeAt: selector. contents := Compiler new parse: contents in: class notifying: nil. contents := contents generate. ^ contents symbolic asText! ! !FileContentsBrowser methodsFor: 'edit pane' stamp: 'alain.plantec 5/18/2009 15:55'! selectedMessage "Answer a copy of the source code for the selected message selector." | class selector | class := self selectedClassOrMetaClass. selector := self selectedMessageName. contents := class sourceCodeAt: selector. Preferences browseWithPrettyPrint ifTrue: [contents := class prettyPrinterClass format: contents in: class notifying: nil]. self showingAnyKindOfDiffs ifTrue: [contents := self methodDiffFor: contents class: self selectedClass selector: self selectedMessageName meta: self metaClassIndicated]. ^contents asText makeSelectorBoldIn: class! ! !FileContentsBrowser methodsFor: 'filein/fileout'! fileInClass Cursor read showWhile:[ self selectedClass fileIn. ].! ! !FileContentsBrowser methodsFor: 'filein/fileout' stamp: 'wod 6/16/1998 17:14'! fileInMessage self selectedMessageName ifNil: [^self]. Cursor read showWhile: [ self selectedClassOrMetaClass fileInMethod: self selectedMessageName. ].! ! !FileContentsBrowser methodsFor: 'filein/fileout' stamp: 'wod 2/3/1999 18:46'! fileInMessageCategories Cursor read showWhile:[ self selectedClassOrMetaClass fileInCategory: self selectedMessageCategoryName. ].! ! !FileContentsBrowser methodsFor: 'filein/fileout' stamp: 'wod 5/13/1998 12:50'! fileInPackage Cursor read showWhile:[ self selectedPackage fileIn. ].! ! !FileContentsBrowser methodsFor: 'filein/fileout' stamp: 'ar 9/27/2005 20:07'! fileIntoNewChangeSet | p ff | (p := self selectedPackage) ifNil: [^ Beeper beep]. ff := FileStream readOnlyFileNamed: p fullPackageName. ChangeSet newChangesFromStream: ff named: p packageName! ! !FileContentsBrowser methodsFor: 'filein/fileout'! fileOutClass Cursor write showWhile:[ self selectedClass fileOut. ].! ! !FileContentsBrowser methodsFor: 'filein/fileout' stamp: 'wod 6/16/1998 17:14'! fileOutMessage self selectedMessageName ifNil: [^self]. Cursor write showWhile: [ self selectedClassOrMetaClass fileOutMethod: self selectedMessageName].! ! !FileContentsBrowser methodsFor: 'filein/fileout' stamp: 'wod 2/3/1999 18:46'! fileOutMessageCategories Cursor write showWhile:[ self selectedClassOrMetaClass fileOutCategory: self selectedMessageCategoryName. ].! ! !FileContentsBrowser methodsFor: 'filein/fileout' stamp: 'wod 5/13/1998 14:19'! fileOutPackage Cursor write showWhile:[ self selectedPackage fileOut. ].! ! !FileContentsBrowser methodsFor: 'infoview' stamp: 'sma 5/6/2000 19:19'! extraInfo ^ (self methodDiffFor: (self selectedClassOrMetaClass sourceCodeAt: self selectedMessageName) class: self selectedClass selector: self selectedMessageName meta: self metaClassIndicated) unembellished ifTrue: [' - identical'] ifFalse: [' - modified']! ! !FileContentsBrowser methodsFor: 'infoview'! infoString ^infoString isNil ifTrue:[infoString := StringHolder new] ifFalse:[infoString]! ! !FileContentsBrowser methodsFor: 'infoview' stamp: 'sd 11/20/2005 21:27'! infoViewContents "Answer the string to show in the info view" | theClass stamp exists | editSelection == #newClass ifTrue: [^ self packageInfo: self selectedPackage]. self selectedClass isNil ifTrue: [^ '']. theClass := Smalltalk at: self selectedClass name asSymbol ifAbsent: []. editSelection == #editClass ifTrue: [^ theClass notNil ifTrue: ['Class exists already in the system' translated] ifFalse: ['New class' translated]]. editSelection == #editMessage ifFalse: [^ '']. (theClass notNil and: [self metaClassIndicated]) ifTrue: [theClass := theClass class]. stamp := self selectedClassOrMetaClass stampAt: self selectedMessageName. exists := theClass notNil and: [theClass includesSelector: self selectedMessageName]. ^ stamp = 'methodWasRemoved' ifTrue: [exists ifTrue: ['Existing method removed by this change-set' translated] ifFalse: ['Removal request for a method that is not present in this image' translated]] ifFalse: [stamp, ' · ', (exists ifTrue: ['Method already exists' translated , self extraInfo] ifFalse: ['New method' translated])]! ! !FileContentsBrowser methodsFor: 'infoview'! packageInfo: p | nClasses newClasses oldClasses | p isNil ifTrue:[^'']. nClasses := newClasses := oldClasses := 0. p classes do:[:cls| nClasses := nClasses + 1. (Smalltalk includesKey: (cls name asSymbol)) ifTrue:[oldClasses := oldClasses + 1] ifFalse:[newClasses := newClasses + 1]]. ^nClasses printString,' classes (', newClasses printString, ' new / ', oldClasses printString, ' modified)'! ! !FileContentsBrowser methodsFor: 'infoview' stamp: 'alain.plantec 5/30/2008 13:04'! updateInfoView self changed: #infoViewContents! ! !FileContentsBrowser methodsFor: 'initialization' stamp: 'dew 9/15/2001 16:19'! defaultBrowserTitle ^ 'File Contents Browser'! ! !FileContentsBrowser methodsFor: 'keys' stamp: 'sma 5/6/2000 18:48'! classListKey: aChar from: view aChar == $b ifTrue: [^ self browseMethodFull]. aChar == $N ifTrue: [^ self browseClassRefs]. self packageListKey: aChar from: view! ! !FileContentsBrowser methodsFor: 'keys' stamp: 'sma 5/6/2000 18:50'! messageListKey: aChar from: view aChar == $b ifTrue: [^ self browseMethodFull]. super messageListKey: aChar from: view! ! !FileContentsBrowser methodsFor: 'keys' stamp: 'sma 2/6/2000 12:05'! packageListKey: aChar from: view aChar == $f ifTrue: [^ self findClass]. self arrowKey: aChar from: view! ! !FileContentsBrowser methodsFor: 'menus' stamp: 'sma 5/6/2000 18:36'! classListMenu: aMenu ^ aMenu labels: 'definition comment browse full (b) class refs (N) fileIn fileOut rename... remove remove existing' lines: #(2 4 6 8) selections: #(editClass editComment browseMethodFull browseClassRefs fileInClass fileOutClass renameClass removeClass removeUnmodifiedCategories) ! ! !FileContentsBrowser methodsFor: 'menus' stamp: 'tpr 3/11/2001 21:26'! classListMenu: aMenu shifted: ignored "Answer the class list menu, ignoring the state of the shift key in this case" ^ self classListMenu: aMenu! ! !FileContentsBrowser methodsFor: 'menus' stamp: 'sw 11/13/2001 09:12'! contentsSymbolQuints "Answer a list of quintuplets representing information on the alternative views available in the code pane. For the file-contents browser, the choices are restricted to source and the two diffing options" ^ self sourceAndDiffsQuintsOnly! ! !FileContentsBrowser methodsFor: 'menus' stamp: 'wod 5/13/1998 17:39'! messageCategoryMenu: aMenu ^ aMenu labels: 'fileIn fileOut reorganize add item... rename... remove remove existing' lines: #(2 3 6) selections: #(fileInMessageCategories fileOutMessageCategories editMessageCategories addCategory renameCategory removeMessageCategory removeUnmodifiedMethods)! ! !FileContentsBrowser methodsFor: 'menus' stamp: 'sma 2/6/2000 12:28'! messageListMenu: aMenu ^ aMenu labels: 'fileIn fileOut senders (n) implementors (m) method inheritance (h) versions (v) remove' lines: #(2 6) selections: #(fileInMessage fileOutMessage browseSenders browseImplementors methodHierarchy browseVersions removeMessage).! ! !FileContentsBrowser methodsFor: 'menus' stamp: 'sma 4/22/2000 20:52'! packageListMenu: aMenu ^ aMenu labels: 'find class... (f) fileIn file into new changeset fileOut remove remove existing' lines: #(1 4 5) selections: #(findClass fileInPackage fileIntoNewChangeSet fileOutPackage removePackage removeUnmodifiedClasses)! ! !FileContentsBrowser methodsFor: 'metaclass' stamp: 'sd 11/20/2005 21:27'! selectedClassOrMetaClass "Answer the selected class or metaclass." | cls | self metaClassIndicated ifTrue: [^ (cls := self selectedClass) ifNotNil: [cls metaClass]] ifFalse: [^ self selectedClass]! ! !FileContentsBrowser methodsFor: 'metaclass' stamp: 'sd 11/20/2005 21:27'! setClassOrganizer "Install whatever organization is appropriate" | theClass | classOrganizer := nil. metaClassOrganizer := nil. classListIndex = 0 ifTrue: [^ self]. classOrganizer := (theClass := self selectedClass) organization. metaClassOrganizer := theClass metaClass organization. ! ! !FileContentsBrowser methodsFor: 'other' stamp: 'bkv 8/13/2003 23:59'! browseSenders "Create and schedule a message set browser on all senders of the currently selected message selector. Do nothing if no message is selected." messageListIndex ~= 0 ifTrue: [self systemNavigation browseAllCallsOn: self selectedMessageName]! ! !FileContentsBrowser methodsFor: 'other' stamp: 'sd 11/20/2005 21:27'! browseVersions "Create and schedule a message set browser on all versions of the currently selected message selector." | class selector | (selector := self selectedMessageName) ifNotNil: [class := self selectedClassOrMetaClass. (class exists and: [class realClass includesSelector: selector]) ifTrue: [VersionsBrowser browseVersionsOf: (class realClass compiledMethodAt: selector) class: class realClass theNonMetaClass meta: class realClass isMeta category: self selectedMessageCategoryName selector: selector]]! ! !FileContentsBrowser methodsFor: 'other'! changeMessageCategories: aString "The characters in aString represent an edited version of the the message categories for the selected class. Update this information in the system and inform any dependents that the categories have been changed. This message is invoked because the user had issued the categories command and edited the message categories. Then the user issued the accept command." self classOrMetaClassOrganizer changeFromString: aString. self unlock. self editClass. self classListIndex: classListIndex. ^ true! ! !FileContentsBrowser methodsFor: 'other' stamp: 'sd 11/20/2005 21:27'! didCodeChangeElsewhere "Determine whether the code for the currently selected method and class has been changed somewhere else." | aClass | (aClass := self selectedClassOrMetaClass) ifNil: [^ false]. (aClass isKindOf: PseudoClass) ifTrue: [^ false]. "class not installed" ^super didCodeChangeElsewhere! ! !FileContentsBrowser methodsFor: 'other' stamp: 'sw 10/1/2001 11:16'! labelString "Answer the string for the window title" ^ 'File Contents Browser ', (self selectedSystemCategoryName ifNil: [''])! ! !FileContentsBrowser methodsFor: 'other' stamp: 'sma 2/6/2000 12:27'! methodHierarchy (self selectedClassOrMetaClass isNil or: [self selectedClassOrMetaClass hasDefinition]) ifFalse: [super methodHierarchy]! ! !FileContentsBrowser methodsFor: 'removing' stamp: 'sd 11/20/2005 21:27'! removeClass | class | classListIndex = 0 ifTrue: [^ self]. class := self selectedClass. (self confirm:'Are you certain that you want to delete the class ', class name, '?') ifFalse:[^self]. self selectedPackage removeClass: class. self classListIndex: 0. self changed: #classList.! ! !FileContentsBrowser methodsFor: 'removing' stamp: 'sd 11/20/2005 21:27'! removeMessage | messageName | messageListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. messageName := self selectedMessageName. (self selectedClass confirmRemovalOf: messageName) ifFalse: [^ false]. self selectedClassOrMetaClass removeMethod: self selectedMessageName. self messageListIndex: 0. self setClassOrganizer. "In case organization not cached" self changed: #messageList! ! !FileContentsBrowser methodsFor: 'removing' stamp: 'sd 11/20/2005 21:27'! removeMessageCategory "If a message category is selected, create a Confirmer so the user can verify that the currently selected message category should be removed from the system. If so, remove it." | messageCategoryName | messageCategoryListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. messageCategoryName := self selectedMessageCategoryName. (self messageList size = 0 or: [self confirm: 'Are you sure you want to remove this method category and all its methods?']) ifFalse: [^ self]. self selectedClassOrMetaClass removeCategory: messageCategoryName. self messageCategoryListIndex: 0. self changed: #messageCategoryList.! ! !FileContentsBrowser methodsFor: 'removing' stamp: 'wod 5/24/1998 20:52'! removePackage systemCategoryListIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. (self confirm: 'Are you sure you want to remove this package and all its classes?') ifFalse:[^self]. (systemOrganizer listAtCategoryNamed: self selectedSystemCategoryName) do:[:el| systemOrganizer removeElement: el]. self packages removeKey: self selectedPackage packageName. systemOrganizer removeCategory: self selectedSystemCategoryName. self systemCategoryListIndex: 0. self changed: #systemCategoryList! ! !FileContentsBrowser methodsFor: 'removing' stamp: 'sd 11/20/2005 21:27'! removeUnmodifiedCategories | theClass | self okToChange ifFalse: [^self]. theClass := self selectedClass. theClass isNil ifTrue: [^self]. Cursor wait showWhile: [theClass removeUnmodifiedMethods: theClass selectors. theClass metaClass removeUnmodifiedMethods: theClass metaClass selectors]. self messageCategoryListIndex: 0. self changed: #messageCategoryList.! ! !FileContentsBrowser methodsFor: 'removing' stamp: 'wod 5/24/1998 20:37'! removeUnmodifiedClasses | packageList | self okToChange ifFalse:[^self]. packageList := self selectedPackage isNil ifTrue:[self packages] ifFalse:[Array with: self selectedPackage]. packageList do:[:package| package classes copy do:[:theClass| Cursor wait showWhile:[ theClass removeAllUnmodified. ]. theClass hasChanges ifFalse:[ package removeClass: theClass. ]. ]]. self classListIndex: 0. self changed: #classList.! ! !FileContentsBrowser methodsFor: 'removing' stamp: 'wod 2/3/1999 18:47'! removeUnmodifiedMethods | theClass cat | self okToChange ifFalse:[^self]. theClass := self selectedClassOrMetaClass. theClass isNil ifTrue:[^self]. cat := self selectedMessageCategoryName. cat isNil ifTrue:[^self]. Cursor wait showWhile:[ theClass removeUnmodifiedMethods: (theClass organization listAtCategoryNamed: cat). ]. self messageListIndex: 0. self changed: #messageList.! ! !FileContentsBrowser methodsFor: 'toolbuilder' stamp: 'ar 2/12/2005 14:20'! buildWith: builder "Create the ui for the browser" | windowSpec listSpec textSpec buttonSpec panelSpec max | windowSpec := builder pluggableWindowSpec new. windowSpec model: self. windowSpec label: 'System Browser'. windowSpec children: OrderedCollection new. max := self wantsOptionalButtons ifTrue:[0.43] ifFalse:[0.5]. listSpec := builder pluggableListSpec new. listSpec model: self; list: #systemCategoryList; getIndex: #systemCategoryListIndex; setIndex: #systemCategoryListIndex:; menu: #packageListMenu:; keyPress: #packageListKey:from:; frame: (0@0 corner: 0.25@max). windowSpec children add: listSpec. listSpec := builder pluggableListSpec new. listSpec model: self; list: #classList; getIndex: #classListIndex; setIndex: #classListIndex:; menu: #classListMenu:; keyPress: #classListKey:from:; frame: (0.25@0 corner: 0.5@(max-0.1)). windowSpec children add: listSpec. panelSpec := builder pluggablePanelSpec new. panelSpec frame: (0.25@(max-0.1) corner: 0.5@max). panelSpec children: OrderedCollection new. windowSpec children addLast: panelSpec. buttonSpec := builder pluggableButtonSpec new. buttonSpec model: self; label: 'instance'; state: #instanceMessagesIndicated; action: #indicateInstanceMessages; frame: (0@0 corner: 0.4@1). panelSpec children addLast: buttonSpec. buttonSpec := builder pluggableButtonSpec new. buttonSpec model: self; label: '?'; state: #classCommentIndicated; action: #plusButtonHit; frame: (0.4@0 corner: 0.6@1). panelSpec children addLast: buttonSpec. buttonSpec := builder pluggableButtonSpec new. buttonSpec model: self; label: 'class'; state: #classMessagesIndicated; action: #indicateClassMessages; frame: (0.6@0 corner: 1@1). panelSpec children addLast: buttonSpec. listSpec := builder pluggableListSpec new. listSpec model: self; list: #messageCategoryList; getIndex: #messageCategoryListIndex; setIndex: #messageCategoryListIndex:; menu: #messageCategoryMenu:; keyPress: #arrowKey:from:; frame: (0.5@0 corner: 0.75@max). windowSpec children add: listSpec. listSpec := builder pluggableListSpec new. listSpec model: self; list: #messageList; getIndex: #messageListIndex; setIndex: #messageListIndex:; menu: #messageListMenu:shifted:; keyPress: #messageListKey:from:; frame: (0.75@0 corner: 1@max). windowSpec children add: listSpec. self wantsOptionalButtons ifTrue:[ panelSpec := self buildOptionalButtonsWith: builder. panelSpec frame: (0@0.43 corner: 1@0.5). windowSpec children add: panelSpec. ]. textSpec := builder pluggableTextSpec new. textSpec model: self; getText: #contents; setText: #contents:notifying:; selection: #contentsSelection; menu: #codePaneMenu:shifted:; frame: (0@0.5corner: 1@0.92). windowSpec children add: textSpec. textSpec := builder pluggableInputFieldSpec new. textSpec model: self; getText: #infoViewContents; frame: (0@0.92corner: 1@1). windowSpec children add: textSpec. ^builder build: windowSpec! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileContentsBrowser class instanceVariableNames: ''! !FileContentsBrowser class methodsFor: 'file list services' stamp: 'nk 6/12/2004 11:41'! fileReaderServicesForDirectory: aDirectory ^{ self serviceBrowseCodeFiles }! ! !FileContentsBrowser class methodsFor: 'file list services' stamp: 'nk 2/17/2004 19:18'! fileReaderServicesForFile: fullName suffix: suffix ((FileStream isSourceFileSuffix: suffix) or: [ suffix = '*' ]) ifTrue: [ ^Array with: self serviceBrowseCode]. ^(fullName endsWith: 'cs.gz') ifTrue: [ Array with: self serviceBrowseCompressedCode ] ifFalse: [#()] ! ! !FileContentsBrowser class methodsFor: 'file list services' stamp: 'DamienCassou 9/29/2009 09:11'! selectAndBrowseFile: aFileList "When no file are selected you can ask to browse several of them" | selectionPattern files | selectionPattern := UIManager default request:'What files?' initialAnswer: '*.cs;*.st'. selectionPattern ifNil: [selectionPattern := String new]. files := (aFileList directory fileNamesMatching: selectionPattern) collect: [:each | aFileList directory fullNameFor: each]. self browseFiles: files. ! ! !FileContentsBrowser class methodsFor: 'file list services' stamp: 'nk 4/29/2004 10:35'! serviceBrowseCode "Answer the service of opening a file-contents browser" ^ (SimpleServiceEntry provider: self label: 'code-file browser' selector: #browseStream: description: 'open a "file-contents browser" on this file, allowing you to view and selectively load its code' buttonLabel: 'code') argumentGetter: [ :fileList | fileList readOnlyStream ]! ! !FileContentsBrowser class methodsFor: 'file list services' stamp: 'nk 6/12/2004 11:35'! serviceBrowseCodeFiles ^ (SimpleServiceEntry provider: self label: 'browse code files' selector: #selectAndBrowseFile:) argumentGetter: [ :fileList | fileList ]; yourself! ! !FileContentsBrowser class methodsFor: 'file list services' stamp: 'nk 4/29/2004 10:35'! serviceBrowseCompressedCode "Answer a service for opening a changelist browser on a file" ^ (SimpleServiceEntry provider: self label: 'code-file browser' selector: #browseCompressedCodeStream: description: 'open a "file-contents browser" on this file, allowing you to view and selectively load its code' buttonLabel: 'code') argumentGetter: [ :fileList | fileList readOnlyStream ]! ! !FileContentsBrowser class methodsFor: 'file list services' stamp: 'md 11/23/2004 13:34'! services "Answer potential file services associated with this class" ^ {self serviceBrowseCode}.! ! !FileContentsBrowser class methodsFor: 'initialization' stamp: 'GabrielOmarCotelli 6/4/2009 20:36'! initialize FileServices registerFileReader: self! ! !FileContentsBrowser class methodsFor: 'initialization' stamp: 'GabrielOmarCotelli 6/4/2009 20:37'! unload FileServices unregisterFileReader: self ! ! !FileContentsBrowser class methodsFor: 'instance creation' stamp: 'tak 3/16/2005 11:37'! browseCompressedCodeStream: aStandardFileStream "Browse the selected file in fileIn format." | zipped unzipped | [zipped := GZipReadStream on: aStandardFileStream. unzipped := MultiByteBinaryOrTextStream with: zipped contents asString] ensure: [aStandardFileStream close]. unzipped reset. self browseStream: unzipped named: aStandardFileStream name! ! !FileContentsBrowser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! browseFiles: fileList | package organizer packageDict browser | Cursor wait showWhile: [ packageDict := Dictionary new. organizer := SystemOrganizer defaultList: Array new. fileList do: [:fileName | package := FilePackage fromFileNamed: fileName. packageDict at: package packageName put: package. organizer classifyAll: package classes keys under: package packageName]. (browser := self systemOrganizer: organizer) packages: packageDict]. self openBrowserView: browser createViews label: 'File Contents Browser'. ! ! !FileContentsBrowser class methodsFor: 'instance creation' stamp: 'nb 6/17/2003 12:25'! browseFile: aFilename "Open a file contents browser on a file of the given name" aFilename ifNil: [^ Beeper beep]. self browseFiles: (Array with: aFilename)! ! !FileContentsBrowser class methodsFor: 'instance creation' stamp: 'edc 5/12/2006 07:09'! browseStream: aStream aStream setConverterForCode. self browseStream: aStream named: aStream name! ! !FileContentsBrowser class methodsFor: 'instance creation' stamp: 'sd 11/20/2005 21:28'! browseStream: aStream named: aString | package organizer packageDict browser | Cursor wait showWhile: [ packageDict := Dictionary new. browser := self new. organizer := SystemOrganizer defaultList: Array new. package := (FilePackage new fullName: aString; fileInFrom: aStream). packageDict at: package packageName put: package. organizer classifyAll: package classes keys under: package packageName. (browser := self systemOrganizer: organizer) packages: packageDict]. self openBrowserView: browser createViews label: 'File Contents Browser'. ! ! !FileContentsBrowser class methodsFor: 'window color' stamp: 'sw 2/26/2002 14:25'! windowColorSpecification "Answer a WindowColorSpec object that declares my preference" ^ WindowColorSpec classSymbol: self name wording: 'File Contents Browser' brightColor: #tan pastelColor: #paleTan helpMessage: 'Lets you view the contents of a file as code, in a browser-like tool.'! ! DialogWindow subclass: #FileDialogWindow instanceVariableNames: 'directoryTreeMorph fileListMorph directories selectedDirectory selectedFileIndex fileSelectionBlock showDirectoriesInFileList fileSortBlock fileNameText defaultExtension actionSelector answer entryCache entryCacheDirectory previewType previewMorph' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !FileDialogWindow commentStamp: 'gvc 5/18/2007 13:10' prior: 0! Dialog based file chooser for selcting or saving files. Supports various types of answer (file stream, file name, directory path etc) with optional extension filters and image or text file preview.! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/27/2006 10:33'! actionSelector "Answer the value of actionSelector" ^ actionSelector! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/27/2006 10:33'! actionSelector: anObject "Set the value of actionSelector" actionSelector := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 10/11/2006 13:33'! defaultExtension "Answer the value of defaultExtension" ^ defaultExtension! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 10/11/2006 13:33'! defaultExtension: anObject "Set the value of defaultExtension" defaultExtension := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/23/2006 14:19'! directories "Answer the value of directories" ^ directories! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/23/2006 14:19'! directories: anObject "Set the value of directories" directories := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/23/2006 19:51'! directoryTreeMorph "Answer the value of directoryTreeMorph" ^ directoryTreeMorph! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/23/2006 19:51'! directoryTreeMorph: anObject "Set the value of directoryTreeMorph" directoryTreeMorph := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/27/2006 10:21'! entryCache "Answer the value of entryCache" ^ entryCache! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/27/2006 10:21'! entryCache: anObject "Set the value of entryCache" entryCache := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/27/2006 10:21'! entryCacheDirectory "Answer the value of entryCacheDirectory" ^ entryCacheDirectory! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/27/2006 10:21'! entryCacheDirectory: anObject "Set the value of entryCacheDirectory" entryCacheDirectory := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/23/2006 19:51'! fileListMorph "Answer the value of fileListMorph" ^ fileListMorph! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/23/2006 19:51'! fileListMorph: anObject "Set the value of fileListMorph" fileListMorph := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/24/2006 08:39'! fileSelectionBlock "Answer the value of fileSelectionBlock" ^ fileSelectionBlock! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/24/2006 08:45'! fileSelectionBlock: anObject "Set the value of fileSelectionBlock" fileSelectionBlock := anObject. self updateFiles! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/24/2006 08:51'! fileSortBlock "Answer the value of fileSortBlock" ^ fileSortBlock! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/24/2006 08:51'! fileSortBlock: anObject "Set the value of fileSortBlock" fileSortBlock := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/27/2006 13:55'! previewMorph "Answer the value of previewMorph" ^ previewMorph! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/27/2006 13:55'! previewMorph: anObject "Set the value of previewMorph" previewMorph := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 9/27/2006 13:30'! previewType "Answer the value of previewType" ^ previewType! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 5/14/2007 16:42'! previewType: anObject "Set the value of previewType. See #updatePreview for supported types." previewType := anObject! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/23/2006 14:33'! selectedDirectory "Answer the value of selectedDirectory" ^ selectedDirectory! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/24/2006 08:49'! selectedDirectory: anObject "Set the value of selectedDirectory" selectedDirectory := anObject. self selectedFileIndex: 0; updateSelectedDirectory; updateFiles! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/23/2006 15:42'! selectedFileIndex "Answer the value of selectedFileIndex" ^ selectedFileIndex! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/24/2006 08:46'! selectedFileIndex: anObject "Set the value of selectedFileIndex" selectedFileIndex := anObject. self updateSelectedFile! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/24/2006 08:42'! showDirectoriesInFileList "Answer the value of showDirectoriesInFileList" ^ showDirectoriesInFileList! ! !FileDialogWindow methodsFor: 'accessing' stamp: 'gvc 8/24/2006 08:44'! showDirectoriesInFileList: anObject "Set the value of showDirectoriesInFileList" showDirectoriesInFileList := anObject. self updateFiles! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/24/2006 10:49'! addInitialPanel "Add the panel." super addInitialPanel. self selectDirectory: FileDirectory default! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/31/2006 15:19'! answer "Answer the result of performing the action selector." self cancelled ifTrue: [^nil]. ^answer! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 7/30/2009 14:00'! answer: anObject "Set the answer." answer := anObject! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 3/23/2007 16:04'! answerDirectory "Set the receiver to answer a directory." self actionSelector: #selectedAnyFileDirectory. self fileSelectionBlock: self directoryFileSelectionBlock. self changed: #okEnabled! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/4/2007 16:08'! answerFileEntry "Set the receiver to answer the selected file entry." self actionSelector: #selectedFileEntry. self changed: #okEnabled! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/4/2007 16:00'! answerFileName "Set the receiver to answer the selected file name." self actionSelector: #selectedFileName. self changed: #okEnabled! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 3/23/2007 16:04'! answerForceSaveFile "Set the receiver to answer a forced new file stream." self actionSelector: #saveForcedSelectedFile. self changed: #okEnabled! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 3/23/2007 16:04'! answerOpenFile "Set the receiver to answer a new file stream on an existing file." self actionSelector: #openSelectedFile. self changed: #okEnabled! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 3/23/2007 16:04'! answerPathName "Set the receiver to answer the selected path name." self actionSelector: #selectedPathName. self changed: #okEnabled! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 3/23/2007 16:04'! answerSaveFile "Set the receiver to answer a new file stream." self actionSelector: #saveSelectedFile. self changed: #okEnabled! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/27/2006 11:38'! cache: dir "Cache the contents of the given directory and answer them." self entryCacheDirectory = dir ifFalse: [Cursor wait showWhile: [ self entryCache: dir entries; entryCacheDirectory: dir]]. ^self entryCache! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 11:23'! clearEntryCache "Clear the entry cache." self entryCache: nil; entryCacheDirectory: nil! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'stephane.ducasse 4/13/2009 21:06'! defaultFileSelectionBlock "Answer the default file selection block." ^[:de | de isDirectory ifTrue: [self showDirectoriesInFileList] ifFalse: [self fileNamePattern match: de name]]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'stephane.ducasse 4/13/2009 21:06'! defaultFileSortBlock "Answer the default file stor block" ^[:de1 :de2 | de1 isDirectory = de2 isDirectory ifTrue: [de1 name <= de2 name] ifFalse: [de1 isDirectory ifTrue: [true] ifFalse: [de2 isDirectory ifTrue: [false] ifFalse: [de1 name <= de2 name]]]]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/23/2006 14:19'! defaultLabel "Answer the default label for the receiver." ^'File' translated! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 11:29'! deleteFileOrDirectory "Delete the selected file or directory." |entry| self hasSelectedFileOrDirectory ifFalse: [^self]. entry := self selectedFileEntry. entry isDirectory ifTrue: [(self proceed: 'Are you sure you wish to delete the\selected directory along with its files?' withCRs translated title: 'Delete Directory' translated) ifTrue: [ self selectedFileDirectory deleteDirectory: entry name. self clearEntryCache; updateDirectories]] ifFalse: [(self proceed: 'Are you sure you wish to delete the\file' withCRs translated, ' "', entry name, '"?' title: 'Delete Directory' translated) ifTrue: [ self selectedFileDirectory deleteFileNamed: entry name. self selectedFileIndex: 0; clearEntryCache; updateFiles]].! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'stephane.ducasse 4/13/2009 21:06'! directoryFileSelectionBlock "Answer the directory file selection block." ^[:de | de isDirectory ifTrue: [self showDirectoriesInFileList] ifFalse: [false]] ! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/23/2006 14:29'! directoryNamesFor: item "Answer the filtered entries." ^item directoryNames! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/15/2007 15:13'! doubleClickFile "If the selected entry is a directory then navigate it otherwise ok the dialog." |fe de sm| fe := self selectedFileEntry. fe ifNil: [^self]. fe isDirectory ifTrue: [de := self selectedFileDirectory. sm := self directoryTreeMorph selectedMorph. self changed: #(openPath), de pathParts. self selectedDirectory: (sm children detect: [:w | w complexContents item localName = fe name]) complexContents] ifFalse: [self ok]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/16/2007 11:07'! fileItems "Answer the items for the contents of the selected directory." ^Cursor wait showWhile: [ self files collect: [:de | (self newRow: { ImageMorph new newForm: (self iconFor: de). StringMorph contents: de name font: self theme listFont}) hResizing: #shrinkWrap; vResizing: #shrinkWrap; fullBounds; hResizing: #rigid; vResizing: #rigid; changeNoLayout]]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/24/2006 16:13'! fileNamePattern "Answer the file name pattern to filter on." ^self fileNameText withBlanksTrimmed, '*'! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/24/2006 15:54'! fileNameText "Answer the typed file name." ^fileNameText! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/3/2007 15:19'! fileNameText: aString "The typed file name has changed." fileNameText = aString asString ifTrue: [^self]. fileNameText := aString asString. self updateFiles. self changed: #fileNameText; changed: #okEnabled. self selectFileFromPattern! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/27/2006 11:39'! files "Answer the contents of the selected directory." ^(self selectedDirectory ifNil: [^#()]) item isNil ifTrue: [#()] ifFalse: [Cursor wait showWhile: [ ((self cache: self selectedDirectory item) select: self fileSelectionBlock) asSortedCollection: self fileSortBlock]]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 10:21'! hasParentDirectory "Answer whether the selected directory in the tree part has a parent." ^(self selectedFileDirectory ifNil: [^false]) containingDirectory pathName notEmpty! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 10:17'! hasSelectedFileOrDirectory "Answer whether a file or directopry is selected in the file list." ^self selectedFileIndex ~= 0! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/27/2006 13:50'! iconFor: anEntry "Answer the icon to use for the directory entry." ^anEntry isDirectory ifTrue: [MenuIcons smallOpenIcon] ifFalse: [(self isImageFile: anEntry name) ifTrue: [MenuIcons smallPaintIcon] ifFalse: [MenuIcons smallLeftFlushIcon]]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/23/2006 14:18'! initialDirectories "Answer the initial directories." | dirList | dirList := (FileDirectory on: '') directoryNames collect: [ :each | FileDirectoryWrapper with: (FileDirectory on: each) name: each model: self]. dirList isEmpty ifTrue:[ dirList := Array with: (FileDirectoryWrapper with: FileDirectory default name: FileDirectory default localName model: self)]. ^dirList! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 7/30/2009 14:01'! initialize "Initialize the receiver." selectedFileIndex := 0. fileNameText := ''. self answerPathName; directories: self initialDirectories; showDirectoriesInFileList: true; fileSelectionBlock: self defaultFileSelectionBlock; fileSortBlock: self defaultFileSortBlock. super initialize! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 10/9/2006 13:53'! isImageFile: aString "Answer whether the file name indicates an image file." aString ifNil: [^false]. ^#('pcx' 'bmp' 'jpeg' 'xbm' 'pnm' 'ppm' 'gif' 'pam' 'jpg' 'png' 'pbm') includes: (FileDirectory extensionFor: aString) asLowercase! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2009 11:17'! isResizeable "Answer whether we are not we can be resized." ^true! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 10:39'! newActionButtonRow "Answer a new row with the action buttons." ^(self newRow: { self newUpButton. self newNewDirectoryButton. self newDeleteButton}) listCentering: #bottomRight! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2009 10:55'! newContentMorph "Answer a new content morph." self directoryTreeMorph: self newDirectoryTree; fileListMorph: self newFileList; previewMorph: self newPreviewMorph. ^(self newRow: { self newColumn: { self newGroupbox: 'Directory' translated for: self directoryTreeMorph. (self newLabelGroup: { 'File name' translated->self newFileNameTextEntry}) vResizing: #shrinkWrap}. self newGroupbox: 'File' translated forAll: { self fileListMorph. self newActionButtonRow}}, (self previewMorph notNil ifTrue: [{self newGroupbox: 'Preview' translated for: self previewMorph}] ifFalse: [#()])) vResizing: #spaceFill! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:00'! newDeleteButton "Answer a new delete button." ^self newButtonFor: self getState: nil action: #deleteFileOrDirectory arguments: nil getEnabled: #hasSelectedFileOrDirectory labelForm: MenuIcons smallDeleteIcon help: 'Press to delete the selected file or directory' translated! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 11:19'! newDirectory "Create a new directory within the selected directory." |dir dirName title| dir := self selectedFileDirectory ifNil: [^self]. title := 'Create Directory' translated. dirName := self textEntry: 'Enter directory name' translated title: title. dirName ifNil: [^self]. [dir createDirectory: dirName] on: Error do: [:ex | [((dir fileExists: dirName) or: [(dir directoryNamed: dirName) exists]) ifTrue: [^self alert: 'A file or directory already exists\with the name' withCRs translated, ' "', dirName, '"' title: title]] on: Error do: []. ^self alert: 'Invalid directory name' translated, ' "', dirName, '"' title: title]. self updateDirectories! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/22/2009 10:54'! newDirectoryTree "Answer a new directory tree." ^(self newTreeFor: self list: #directories selected: #selectedDirectory changeSelected: #selectedDirectory:) minHeight: 200; minWidth: 180! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/9/2007 13:29'! newFileList "Answer a new file list." ^(self newMorphListFor: self list: #fileItems getSelected: #selectedFileIndex setSelected: #selectedFileIndex: help: nil) doubleClickSelector: #doubleClickFile; minWidth: 200! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/3/2007 15:20'! newFileNameTextEntry "Answer a new file name text entry morph." ^self newAutoAcceptTextEntryFor: self getText: #fileNameText setText: #fileNameText: getEnabled: nil help: 'File name filter pattern' translated! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/14/2007 16:33'! newImagePreviewMorph "Answer a new image preview morph." ^ImagePreviewMorph new cornerStyle: self preferredCornerStyle; image: nil size: self previewSize! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:01'! newNewDirectoryButton "Answer a new 'new directory' button." ^self newButtonFor: self getState: nil action: #newDirectory arguments: nil getEnabled: nil labelForm: MenuIcons smallOpenIcon help: 'Press to create a new directory within the current directory' translated! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 3/23/2007 15:59'! newOKButton "Answer a new OK button." ^self newOKButtonFor: self getEnabled: #okEnabled! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/14/2007 16:24'! newPreviewMorph "Answer a new preview morph." self previewType == #image ifTrue: [^self newImagePreviewMorph]. self previewType == #text ifTrue: [^self newTextPreviewMorph]. ^nil! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/14/2007 16:39'! newTextPreviewMorph "Answer a new text preview morph." ^(self newTextEditorFor: self getText: nil setText: nil getEnabled: nil) hResizing: #rigid; vResizing: #spaceFill; extent: self previewSize; minWidth: self previewSize x; minHeight: self previewSize y; enabled: false! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:01'! newUpButton "Answer a new up one directory level button." ^self newButtonFor: self getState: nil action: #selectParentDirectory arguments: nil getEnabled: #hasParentDirectory labelForm: MenuIcons smallUndoIcon help: 'Press to switch to the parent of the current directory' translated! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/10/2007 10:41'! ok "Apply the changes and close." self cancelled: false. self applyChanges. self answer: (self perform: self actionSelector). answer ifNil: [ self cancelled: true. ^self delete]. super ok! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/4/2007 16:34'! okEnabled "Answer wether the ok button should be enabled." (#(selectedAnyFileDirectory selectedPathName) includes: self actionSelector) ifTrue: [^true]. ((#(saveSelectedFile saveForcedSelectedFile) includes: self actionSelector) and: [self fileNameText notEmpty]) ifTrue: [^true]. (self actionSelector = #selectedFileName and: [ self selectedFileName notNil]) ifTrue: [^true]. ^self selectedFileName notNil and: [self selectedFileEntry isDirectory not]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 3/23/2007 15:51'! openSelectedFile "Open a stream on the selected file if available and return it." |d f| d := self selectedFileDirectory ifNil: [^nil]. f := self selectedFileName ifNil: [^nil]. self selectedFileEntry isDirectory ifTrue: [^nil]. ^ (d oldFileNamed: f) ifNil: [d readOnlyFileNamed: f]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/14/2007 16:38'! previewSize "Answer the size of preview to use." self previewType == #text ifTrue: [^256@256]. ^128@128! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/15/2007 15:13'! saveForcedSelectedFile "Open a stream on the selected file if available and return it." |d f| d := self selectedFileDirectory ifNil: [^nil]. f := self selectedFileName ifNil: [self fileNameText withBlanksTrimmed]. f ifEmpty: [^nil]. ^d forceNewFileNamed: f! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/1/2007 12:22'! saveSelectedFile "Open a stream on the selected file if available and return it." |d f| d := self selectedFileDirectory ifNil: [^nil]. f := self selectedFileName ifNil: [self fileNameText withBlanksTrimmed]. f ifEmpty: [^nil]. ((FileDirectory extensionFor: f) isEmpty and: [self defaultExtension notNil]) ifTrue: [f := FileDirectory fileName: f extension: self defaultExtension]. ^[d newFileNamed: f] on: FileExistsException do: [ (self proceed: ('The file {1} already exists. Overwrite the file?' translated format: {f printString}) title: 'Save File' translated) ifTrue: [d forceNewFileNamed: f]]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/24/2006 10:49'! selectDirectory: aFileDirectory "Expand and select the given directory." self changed: #(openPath), aFileDirectory pathParts! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/2/2007 12:19'! selectFileFromPattern "If there is a single file matching the pattern then select it. If none then try for a directory." |f matches subMatches| f := self files. matches := f select: [:de | self fileNamePattern match: de name]. subMatches := matches select: [:de | de isDirectory not]. subMatches size = 1 ifTrue: [ ^self selectedFileIndex: (f indexOf: subMatches first)]. subMatches := matches select: [:de | de isDirectory]. subMatches size = 1 ifTrue: [^self selectedFileIndex: (f indexOf: subMatches first)]. self selectedFileIndex: 0! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 10:43'! selectParentDirectory "Switch to the parent directory." self hasParentDirectory ifFalse: [^self]. self selectDirectory: self selectedFileDirectory containingDirectory! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/15/2007 15:04'! selectPathName: aString "Select the directory and set the file name text from the given string." |dir local| (FileDirectory default directoryExists: aString) ifTrue: [self selectDirectory: (FileDirectory on: aString)] ifFalse: [((FileDirectory on: '') directoryExists: aString) ifTrue: [^self selectDirectory: (FileDirectory on: aString)]. dir := FileDirectory forFileName: aString. dir exists ifTrue: [(dir directoryExists: aString) ifTrue: [self selectDirectory: (dir directoryNamed: aString)] ifFalse: [self selectDirectory: dir. local := FileDirectory localNameFor: aString. (local notEmpty and: [FileDirectory isLegalFileName: local]) ifTrue: [self fileNameText: local]]] ifFalse: [self selectDirectory: FileDirectory default. self fileNameText: '']]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/15/2007 15:21'! selectedAnyFileDirectory "Answer the file directory for the selected file or, if none or not a directory, the selected file directory." ^self selectedFileEntry ifNil: [self selectedFileDirectory] ifNotNilDo: [:fe | self selectedFileDirectory ifNotNilDo: [:fd | fe isDirectory ifTrue: [ fd directoryNamed: fe name]]]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/15/2007 15:14'! selectedDirectoryName "Answer the name of the selected directory." ^(self selectedFileDirectory ifNil: [^nil]) name! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/15/2007 15:13'! selectedFileDirectory "Answer the selected file directory in the tree part." ^(self selectedDirectory ifNil: [^nil]) item! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 11/5/2008 12:09'! selectedFileEntry "Answer the selected file." self selectedFileIndex = 0 ifTrue: [^nil]. ^self files at: self selectedFileIndex ifAbsent: [nil]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/23/2006 17:02'! selectedFileName "Answer the name of the selected file." ^(self selectedFileEntry ifNil: [^nil]) name! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 1/15/2007 15:14'! selectedPathName "Answer the name of the selected path." ^(self selectedFileDirectory ifNil: [^nil]) fullNameFor: (self selectedFileName ifNil: [^self selectedFileDirectory pathName])! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 7/30/2009 14:01'! updateDirectories "Update the directory tree and reselect the current." |dir| dir := self selectedFileDirectory. self changed: #directories. self selectDirectory: dir! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 8/24/2006 08:46'! updateFiles "Notify that the files have changed." self changed: #files; changed: #fileItems! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/14/2007 16:33'! updateImagePreview "Update the image preview." |str form| (self isImageFile: self selectedFileName) ifFalse: [^self previewMorph image: nil size: self previewSize]. str := self openSelectedFile. str ifNil: [^self]. [[str binary. form := ImageReadWriter formFromStream: str] on: Error do: []] ensure: [str close]. self previewMorph image: form size: self previewSize! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/14/2007 16:25'! updatePreview "Update the preview." self previewType == #image ifTrue: [self updateImagePreview]. self previewType == #text ifTrue: [self updateTextPreview]! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 10:41'! updateSelectedDirectory "Notify that the selected directory has changed." self changed: #selectedDirectory; changed: #selectedFileDirectory; changed: #selectedPathName; changed: #hasParentDirectory! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/24/2007 10:40'! updateSelectedFile "Notify that the selected file has changed." self changed: #selectedFileIndex; changed: #selectedFileEntry; changed: #selectedFileName; changed: #selectedPathName; changed: #okEnabled; changed: #hasSelectedFileOrDirectory. self updatePreview! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 5/14/2007 16:36'! updateTextPreview "Update the text preview." |str text| str := self openSelectedFile. str ifNil: [^self]. [[text := str next: 5000] on: Error do: []] ensure: [str close]. text ifNil: [text := '']. self previewMorph setText: text! ! !FileDialogWindow methodsFor: 'as yet unclassified' stamp: 'stephane.ducasse 4/13/2009 21:06'! validExtensions: aList "Set the filter for the files to be those with the given extensions." aList notEmpty ifTrue: [self defaultExtension: aList first]. self fileSelectionBlock: [:de | de isDirectory ifTrue: [self showDirectoriesInFileList] ifFalse: [(self fileNamePattern match: de name) and: [ aList includes: (FileDirectory extensionFor: de name asLowercase)]]] ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileDialogWindow class instanceVariableNames: ''! !FileDialogWindow class methodsFor: 'as yet unclassified' stamp: 'gvc 5/21/2007 12:41'! taskbarIcon "Answer the icon for the receiver in a task bar." ^MenuIcons smallOpenIcon! ! Object subclass: #FileDirectory instanceVariableNames: 'pathName' classVariableNames: 'DefaultDirectory DirectoryClass StandardMIMEMappings' poolDictionaries: '' category: 'Files-Directories'! !FileDirectory commentStamp: '' prior: 0! A FileDirectory represents a folder or directory in the underlying platform's file system. It carries a fully-qualified path name for the directory it represents, and can enumerate the files and directories within that directory. A FileDirectory can be thought of as a Dictionary whose keys are the local names of files in that directory, and whose values are directory "entries". Each entry is an array of five items: The times are given in seconds, and can be converted to a time and date via Time>dateAndTimeFromSeconds:. See the comment in lookupEntry:... which provides primitive access to this information. ! !FileDirectory methodsFor: '*Network-MIME' stamp: 'JMM 5/14/2006 13:59'! fileSuffixesForMimeType: mimeType "Return a list file suffixes for mime type. This is a suboptimal solution." | results | results := SortedCollection sortBlock: [:a :b | a size <= b size]. MIMEType mimeMappings keysAndValuesDo: [:k :v | v do: [: mime | mimeType = mime ifTrue: [results add: k]]]. ^results! ! !FileDirectory methodsFor: '*Network-MIME' stamp: 'JMM 12/1/2007 15:21'! mimeTypesFor: fileName "Return a list of MIME types applicable to the receiver. This default implementation uses the file name extension to figure out what we're looking at but specific subclasses may use other means of figuring out what the type of some file is. Some systems like the macintosh use meta data on the file to indicate data type" ^MIMEType forFileNameReturnMimeTypesOrDefault: fileName! ! !FileDirectory methodsFor: '*network-uri' stamp: 'bf 1/27/2006 18:00'! uri "Convert my path into a file:// type url. For odd characters use %20 notation." | list | list := self pathParts. ^(String streamContents: [:strm | strm nextPutAll: 'file:'. list do: [:each | strm nextPut: $/; nextPutAll: each encodeForHTTP]. strm nextPut: $/]) asURI! ! !FileDirectory methodsFor: '*network-uri' stamp: 'adrian_lienhard 7/20/2009 21:33'! url "Convert my path into a file:// type url String." ^self asUrl asString! ! !FileDirectory methodsFor: 'enumeration' stamp: 'yo 12/19/2003 21:15'! containingDirectory "Return the directory containing this directory." ^ FileDirectory on: (FileDirectory dirPathFor: pathName asSqueakPathName) ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'nk 2/23/2001 11:35'! directoryEntry ^self containingDirectory entryAt: self localName! ! !FileDirectory methodsFor: 'enumeration' stamp: 'stephaneducasse 2/4/2006 20:31'! directoryEntryFor: filenameOrPath "Answer the directory entry for the given file or path. Sorta like a poor man's stat()." | fName dir | DirectoryClass splitName: filenameOrPath to:[:filePath :name | fName := name. filePath isEmpty ifTrue: [dir := self] ifFalse: [dir := FileDirectory on: filePath]]. self isCaseSensitive ifTrue:[^dir entries detect:[:entry| entry name = fName] ifNone:[nil]] ifFalse:[^dir entries detect:[:entry| entry name sameAs: fName] ifNone:[nil]]! ! !FileDirectory methodsFor: 'enumeration' stamp: 'jm 12/5/97 15:46'! directoryNamed: localFileName "Return the subdirectory of this directory with the given name." ^ FileDirectory on: (self fullNameFor: localFileName) ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'jm 12/5/97 15:44'! directoryNames "Return a collection of names for the subdirectories of this directory." "FileDirectory default directoryNames" ^ (self entries select: [:entry | entry at: 4]) collect: [:entry | entry first] ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'jm 12/5/97 12:23'! entries "Return a collection of directory entries for the files and directories in this directory. Each entry is a five-element array: (). See primLookupEntryIn:index: for further details." "FileDirectory default entries" ^ self directoryContentsFor: pathName ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'jm 12/5/97 15:39'! fileAndDirectoryNames "FileDirectory default fileAndDirectoryNames" ^ self entries collect: [:entry | entry first] ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'jm 12/5/97 15:44'! fileNames "Return a collection of names for the files (but not directories) in this directory." "FileDirectory default fileNames" ^ (self entries select: [:entry | (entry at: 4) not]) collect: [:entry | entry first] ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'yo 12/19/2003 21:15'! fullName "Return the full name of this directory." ^pathName asSqueakPathName ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'stephaneducasse 2/4/2006 20:31'! fullNamesOfAllFilesInSubtree "Answer a collection containing the full names of all the files in the subtree of the file system whose root is this directory." | result todo dir | result := OrderedCollection new: 100. todo := OrderedCollection with: self. [todo size > 0] whileTrue: [ dir := todo removeFirst. dir fileNames do: [:n | result add: (dir fullNameFor: n)]. dir directoryNames do: [:n | todo add: (dir directoryNamed: n)]]. ^ result asArray ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'jm 12/5/97 15:39'! keysDo: nameBlock "Evaluate the given block for each file or directory name in this directory." ^ self fileAndDirectoryNames do: nameBlock ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'yo 12/19/2003 21:15'! localName "Return the local name of this directory." ^FileDirectory localNameFor: pathName asSqueakPathName! ! !FileDirectory methodsFor: 'enumeration' stamp: 'mir 8/24/2001 12:01'! matchingEntries: criteria "Ignore the filter criteria for now" ^self entries! ! !FileDirectory methodsFor: 'enumeration' stamp: 'stephaneducasse 2/4/2006 20:31'! statsForDirectoryTree: rootedPathName "Return the size statistics for the entire directory tree starting at the given root. The result is a three element array of the form: (). This method also serves as an example of how recursively enumerate a directory tree." "wod 6/16/1998: add Cursor wait, and use 'self pathNameDelimiter asString' rather than hardwired ':' " "FileDirectory default statsForDirectoryTree: '\smalltalk'" | dirs files bytes todo p entries | Cursor wait showWhile: [ dirs := files := bytes := 0. todo := OrderedCollection with: rootedPathName. [todo isEmpty] whileFalse: [ p := todo removeFirst. entries := self directoryContentsFor: p. entries do: [:entry | (entry at: 4) ifTrue: [ todo addLast: (p, self pathNameDelimiter asString, (entry at: 1)). dirs := dirs + 1] ifFalse: [ files := files + 1. bytes := bytes + (entry at: 5)]]]]. ^ Array with: dirs with: files with: bytes ! ! !FileDirectory methodsFor: 'enumeration' stamp: 'stephaneducasse 2/4/2006 20:31'! withAllSubdirectoriesCollect: aBlock "Evaluate aBlock with each of the directories in the subtree of the file system whose root is this directory. Answer the results of these evaluations." | result todo dir | result := OrderedCollection new: 100. todo := OrderedCollection with: self. [todo size > 0] whileTrue: [ dir := todo removeFirst. result add: (aBlock value: dir). dir directoryNames do: [:n | todo add: (dir directoryNamed: n)]]. ^ result ! ! !FileDirectory methodsFor: 'file directory' stamp: 'stephaneducasse 2/4/2006 20:31'! assureExistenceOfPath: lPath "Make sure the local directory exists. If necessary, create all parts in between" | localPath | localPath := lPath. localPath isEmpty ifTrue: [ ^self ]. "Assumed to exist" (self directoryExists: localPath) ifTrue: [^ self]. "exists" "otherwise check parent first and then create local dir" self containingDirectory assureExistenceOfPath: self localName. self createDirectory: localPath! ! !FileDirectory methodsFor: 'file directory' stamp: 'RAA 7/28/2000 13:47'! localNameFor: fullName "Return the local part the given name." ^self class localNameFor: fullName! ! !FileDirectory methodsFor: 'file directory' stamp: 'tk 12/13/1999 18:55'! sleep "Leave the FileList window. Do nothing. Disk directories do not have to be shut down." ! ! !FileDirectory methodsFor: 'file directory' stamp: 'di 2/11/2000 22:37'! wakeUp "Entering a FileList window. Do nothing. Disk directories do not have to be awakened." ! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'gk 2/10/2004 13:22'! asUrl "Convert my path into a file:// type url - a FileUrl." ^FileUrl pathParts: (self pathParts copyWith: '')! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'stephaneducasse 2/4/2006 20:31'! checkName: aFileName fixErrors: fixing "Check a string aFileName for validity as a file name. Answer the original file name if it is valid. If the name is not valid (e.g., it is too long or contains illegal characters) and fixing is false, raise an error. If fixing is true, fix the name (usually by truncating and/or tranforming characters), and answer the corrected name. The default behavior is just to truncate the name to the maximum length for this platform. Subclasses can do any kind of checking and correction appropriate for their platform." | maxLength | aFileName size = 0 ifTrue: [self error: 'zero length file name']. maxLength := self class maxFileNameLength. aFileName size > maxLength ifTrue: [ fixing ifTrue: [^ aFileName contractTo: maxLength] ifFalse: [self error: 'file name is too long']]. ^ aFileName ! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'stephaneducasse 2/4/2006 20:31'! fileNamesMatching: pat " FileDirectory default fileNamesMatching: '*' FileDirectory default fileNamesMatching: '*.image;*.changes' " | files | files := OrderedCollection new. (pat findTokens: ';', String crlf) do: [ :tok | files addAll: (self fileNames select: [:name | tok match: name]) ]. ^files ! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'stephaneducasse 2/4/2006 20:31'! fullNameFor: fileName "Return a corrected, fully-qualified name for the given file name. If the given name is already a full path (i.e., it contains a delimiter character), assume it is already a fully-qualified name. Otherwise, prefix it with the path to this directory. In either case, correct the local part of the file name." "Details: Note that path relative to a directory, such as '../../foo' are disallowed by this algorithm. Also note that this method is tolerent of a nil argument -- is simply returns nil in this case." | correctedLocalName prefix | fileName ifNil: [^ nil]. DirectoryClass splitName: fileName to: [:filePath :localName | correctedLocalName := localName isEmpty ifFalse: [self checkName: localName fixErrors: true] ifTrue: [localName]. prefix := self fullPathFor: filePath]. prefix isEmpty ifTrue: [^correctedLocalName]. prefix last = self pathNameDelimiter ifTrue:[^ prefix, correctedLocalName] ifFalse:[^ prefix, self slash, correctedLocalName]! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'jm 12/4/97 21:19'! isLegalFileName: aString "Answer true if the given string is a legal file name." ^ (self checkName: aString fixErrors: true) = aString ! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'ar 2/27/2001 22:23'! isTypeFile ^true! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'stephaneducasse 2/4/2006 20:31'! lastNameFor: baseFileName extension: extension "Assumes a file name includes a version number encoded as '.' followed by digits preceding the file extension. Increment the version number and answer the new file name. If a version number is not found, set the version to 1 and answer a new file name" | files splits | files := self fileNamesMatching: (baseFileName,'*', self class dot, extension). splits := files collect: [:file | self splitNameVersionExtensionFor: file] thenSelect: [:split | (split at: 1) = baseFileName]. splits := splits asSortedCollection: [:a :b | (a at: 2) < (b at: 2)]. ^splits isEmpty ifTrue: [nil] ifFalse: [(baseFileName, '.', (splits last at: 2) asString, self class dot, extension) asFileName]! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'stephaneducasse 2/4/2006 20:31'! nextNameFor: baseFileName extension: extension "Assumes a file name includes a version number encoded as '.' followed by digits preceding the file extension. Increment the version number and answer the new file name. If a version number is not found, set the version to 1 and answer a new file name" | files splits version | files := self fileNamesMatching: (baseFileName,'*', self class dot, extension). splits := files collect: [:file | self splitNameVersionExtensionFor: file] thenSelect: [:split | (split at: 1) = baseFileName]. splits := splits asSortedCollection: [:a :b | (a at: 2) < (b at: 2)]. splits isEmpty ifTrue: [version := 1] ifFalse: [version := (splits last at: 2) + 1]. ^ (baseFileName, '.', version asString, self class dot, extension) asFileName! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'stephaneducasse 2/4/2006 20:31'! realUrl "Senders expect url without trailing slash - #url returns slash" | url | url := self url. url last = $/ ifTrue:[^url copyFrom: 1 to: url size-1]. ^url! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'yo 12/19/2003 21:15'! relativeNameFor: aFileName "Return the full name for aFileName, assuming that aFileName is a name relative to me." aFileName isEmpty ifTrue: [ ^pathName asSqueakPathName]. ^aFileName first = self pathNameDelimiter ifTrue: [ pathName asSqueakPathName, aFileName ] ifFalse: [ pathName asSqueakPathName, self slash, aFileName ] ! ! !FileDirectory methodsFor: 'file name utilities' stamp: 'stephaneducasse 2/4/2006 20:31'! splitNameVersionExtensionFor: fileName " answer an array with the root name, version # and extension. See comment in nextSequentialNameFor: for more details" | baseName version extension i j | baseName := self class baseNameFor: fileName. extension := self class extensionFor: fileName. i := j := baseName findLast: [:c | c isDigit not]. i = 0 ifTrue: [version := 0] ifFalse: [(baseName at: i) = $. ifTrue: [version := (baseName copyFrom: i+1 to: baseName size) asNumber. j := j - 1] ifFalse: [version := 0]. baseName := baseName copyFrom: 1 to: j]. ^ Array with: baseName with: version with: extension! ! !FileDirectory methodsFor: 'file operations' stamp: 'stephaneducasse 2/4/2006 20:31'! copyFileNamed: fileName1 toFileNamed: fileName2 "Copy the contents of the existing file with the first name into a new file with the second name. Both files are assumed to be in this directory." "FileDirectory default copyFileNamed: 'todo.txt' toFileNamed: 'todocopy.txt'" | file1 file2 | file1 := (self readOnlyFileNamed: fileName1) binary. file2 := (self newFileNamed: fileName2) binary. self copyFile: file1 toFile: file2. file1 close. file2 close. ! ! !FileDirectory methodsFor: 'file operations' stamp: 'stephaneducasse 2/4/2006 20:31'! copyFileWithoutOverwriteConfirmationNamed: fileName1 toFileNamed: fileName2 "Copy the contents of the existing file with the first name into a file with the second name (which may or may not exist). If the second file exists, force an overwrite without confirming. Both files are assumed to be in this directory." "FileDirectory default copyFileWithoutOverwriteConfirmationNamed: 'todo.txt' toFileNamed: 'todocopy.txt'" | file1 file2 | fileName1 = fileName2 ifTrue: [^ self]. file1 := (self readOnlyFileNamed: fileName1) binary. file2 := (self forceNewFileNamed: fileName2) binary. self copyFile: file1 toFile: file2. file1 close. file2 close.! ! !FileDirectory methodsFor: 'file operations' stamp: 'stephaneducasse 2/4/2006 20:31'! copyFile: fileStream1 toFile: fileStream2 | buffer | buffer := String new: 50000. [fileStream1 atEnd] whileFalse: [fileStream2 nextPutAll: (fileStream1 nextInto: buffer)]. ! ! !FileDirectory methodsFor: 'file operations' stamp: 'yo 2/24/2005 18:33'! createDirectory: localFileName "Create a directory with the given name in this directory. Fail if the name is bad or if a file or directory with that name already exists." self primCreateDirectory: (self fullNameFor: localFileName) asVmPathName ! ! !FileDirectory methodsFor: 'file operations' stamp: 'yo 2/24/2005 18:33'! deleteDirectory: localDirName "Delete the directory with the given name in this directory. Fail if the path is bad or if a directory by that name does not exist." self primDeleteDirectory: (self fullNameFor: localDirName) asVmPathName. ! ! !FileDirectory methodsFor: 'file operations' stamp: 'jm 12/5/97 16:33'! deleteFileNamed: localFileName "Delete the file with the given name in this directory." self deleteFileNamed: localFileName ifAbsent: []. ! ! !FileDirectory methodsFor: 'file operations' stamp: 'stephaneducasse 2/4/2006 20:31'! deleteFileNamed: localFileName ifAbsent: failBlock "Delete the file of the given name if it exists, else evaluate failBlock. If the first deletion attempt fails do a GC to force finalization of any lost references. ar 3/21/98 17:53" | fullName | fullName := self fullNameFor: localFileName. (StandardFileStream retryWithGC:[self primDeleteFileNamed: (self fullNameFor: localFileName) asVmPathName] until:[:result| result notNil] forFileNamed: fullName) == nil ifTrue: [^failBlock value]. ! ! !FileDirectory methodsFor: 'file operations' stamp: 'tpr 3/26/2002 16:48'! deleteLocalFiles "Delete the local files in this directory." self fileNames do:[:fn| self deleteFileNamed: fn ifAbsent: [(CannotDeleteFileException new messageText: 'Could not delete the old version of file ' , (self fullNameFor: fn)) signal]] ! ! !FileDirectory methodsFor: 'file operations' stamp: 'stephaneducasse 2/4/2006 20:31'! fileOrDirectoryExists: filenameOrPath "Answer true if either a file or a directory file of the given name exists. The given name may be either a full path name or a local name within this directory." "FileDirectory default fileOrDirectoryExists: Smalltalk sourcesName" | fName dir | DirectoryClass splitName: filenameOrPath to: [:filePath :name | fName := name. filePath isEmpty ifTrue: [dir := self] ifFalse: [dir := FileDirectory on: filePath]]. ^ (dir includesKey: fName) or: [ fName = '' and:[ dir entries size > 1]]! ! !FileDirectory methodsFor: 'file operations' stamp: 'stephaneducasse 2/4/2006 20:31'! getMacFileTypeAndCreator: fileName | results typeString creatorString | "get the Macintosh file type and creator info for the file with the given name. Fails if the file does not exist or if the type and creator type arguments are not strings of length 4. Does nothing on other platforms (where the underlying primitive is a noop)." "FileDirectory default getMacFileNamed: 'foo'" typeString := ByteArray new: 4 withAll: ($? asInteger). creatorString := ByteArray new: 4 withAll: ($? asInteger). [self primGetMacFileNamed: (self fullNameFor: fileName) asVmPathName type: typeString creator: creatorString.] ensure: [typeString := typeString asString. creatorString := creatorString asString]. results := Array with: typeString convertFromSystemString with: creatorString convertFromSystemString. ^results ! ! !FileDirectory methodsFor: 'file operations' stamp: 'stephaneducasse 2/4/2006 20:31'! putFile: file1 named: destinationFileName "Copy the contents of the existing fileStream into the file destinationFileName in this directory. fileStream can be anywhere in the fileSystem." | file2 | file1 binary. (file2 := self newFileNamed: destinationFileName) ifNil: [^ false]. file2 binary. self copyFile: file1 toFile: file2. file1 close. file2 close. ^ true ! ! !FileDirectory methodsFor: 'file operations' stamp: 'tk 2/26/2000 12:54'! putFile: file1 named: destinationFileName retry: aBool "Copy the contents of the existing fileStream into the file destinationFileName in this directory. fileStream can be anywhere in the fileSystem. No retrying for local file systems." ^ self putFile: file1 named: destinationFileName ! ! !FileDirectory methodsFor: 'file operations' stamp: 'tpr 3/26/2002 18:09'! recursiveDelete "Delete the this directory, recursing down its tree." self directoryNames do: [:dn | (self directoryNamed: dn) recursiveDelete]. self deleteLocalFiles. "should really be some exception handling for directory deletion, but no support for it yet" self containingDirectory deleteDirectory: self localName! ! !FileDirectory methodsFor: 'file operations' stamp: 'alain.plantec 2/10/2009 18:08'! rename: oldFileName toBe: newFileName | selection oldName newName | "Rename the file of the given name to the new name. Fail if there is no file of the old name or if there is an existing file with the new name." "Modified for retry after GC ar 3/21/98 18:09" oldName := self fullNameFor: oldFileName. newName := self fullNameFor: newFileName. (StandardFileStream retryWithGC:[self primRename: oldName asVmPathName to: newName asVmPathName] until:[:result| result notNil] forFileNamed: oldName) ~~ nil ifTrue:[^self]. (self fileExists: oldFileName) ifFalse:[ ^self error:'Attempt to rename a non-existent file'. ]. (self fileExists: newFileName) ifTrue:[ selection := UIManager default confirm: 'Trying to rename a file to be' translated, ' ', newFileName , ' ', 'and it already exists' translated, ' ', 'delete old version?' translated. selection ifTrue: [self deleteFileNamed: newFileName. ^ self rename: oldFileName toBe: newFileName]]. ^self error:'Failed to rename file'.! ! !FileDirectory methodsFor: 'file operations' stamp: 'yo 2/24/2005 18:34'! setMacFileNamed: fileName type: typeString creator: creatorString "Set the Macintosh file type and creator info for the file with the given name. Fails if the file does not exist or if the type and creator type arguments are not strings of length 4. Does nothing on other platforms (where the underlying primitive is a noop)." "FileDirectory default setMacFileNamed: 'foo' type: 'TEXT' creator: 'ttxt'" self primSetMacFileNamed: (self fullNameFor: fileName) asVmPathName type: typeString convertToSystemString creator: creatorString convertToSystemString. ! ! !FileDirectory methodsFor: 'file operations' stamp: 'stephaneducasse 2/4/2006 20:31'! upLoadProject: projectFile named: destinationFileName resourceUrl: resUrl retry: aBool "Copy the contents of the existing fileStream into the file destinationFileName in this directory. fileStream can be anywhere in the fileSystem. No retrying for local file systems." | result | result := self putFile: projectFile named: destinationFileName. [self setMacFileNamed: destinationFileName type: 'SOBJ' creator: 'FAST'] on: Error do: [ "ignore" ]. ^result! ! !FileDirectory methodsFor: 'file status' stamp: 'mdr 1/14/2000 21:16'! entryAt: fileName "find the entry with local name fileName" ^self entryAt: fileName ifAbsent: [ self error: 'file not in directory: ', fileName ].! ! !FileDirectory methodsFor: 'file status' stamp: 'stephaneducasse 2/4/2006 20:31'! entryAt: fileName ifAbsent: aBlock "Find the entry with local name fileName and answer it. If not found, answer the result of evaluating aBlock." | comparisonBlock | self isCaseSensitive ifTrue: [comparisonBlock := [:entry | (entry at: 1) = fileName]] ifFalse: [comparisonBlock := [:entry | (entry at: 1) sameAs: fileName]]. ^ self entries detect: comparisonBlock ifNone: [aBlock value]! ! !FileDirectory methodsFor: 'file stream creation' stamp: 'tk 5/19/1998 09:03'! fileNamed: localFileName "Open the file with the given name in this directory for writing." ^ FileStream concreteStream fileNamed: (self fullNameFor: localFileName) ! ! !FileDirectory methodsFor: 'file stream creation' stamp: 'dew 10/26/2000 02:08'! forceNewFileNamed: localFileName "Open the file with the given name in this directory for writing. If it already exists, delete it first without asking." ^ FileStream concreteStream forceNewFileNamed: (self fullNameFor: localFileName) ! ! !FileDirectory methodsFor: 'file stream creation' stamp: 'tk 5/19/1998 09:03'! newFileNamed: localFileName "Create a new file with the given name in this directory." ^ FileStream concreteStream newFileNamed: (self fullNameFor: localFileName) ! ! !FileDirectory methodsFor: 'file stream creation' stamp: 'tk 5/19/1998 09:03'! oldFileNamed: localFileName "Open the existing file with the given name in this directory." ^ FileStream concreteStream oldFileNamed: (self fullNameFor: localFileName) ! ! !FileDirectory methodsFor: 'file stream creation' stamp: 'GabrielOmarCotelli 6/6/2009 19:11'! oldFileOrNoneNamed: localFileName "If the file exists, answer a read-only FileStream on it. If it doesn't, answer nil." ^ FileStream oldFileOrNoneNamed: (self fullNameFor: localFileName) ! ! !FileDirectory methodsFor: 'file stream creation' stamp: 'tk 5/19/1998 09:03'! readOnlyFileNamed: localFileName "Open the existing file with the given name in this directory for read-only access." ^ FileStream concreteStream readOnlyFileNamed: (self fullNameFor: localFileName) ! ! !FileDirectory methodsFor: 'nil' stamp: 'adrian-lienhard 5/17/2009 22:03'! assureExistence "Make sure the current directory exists. If necessary, create all parts in between" self containingDirectory assureExistenceOfPath: self localName! ! !FileDirectory methodsFor: 'path access' stamp: 'yo 12/19/2003 21:15'! fullPathFor: path ^path isEmpty ifTrue:[pathName asSqueakPathName] ifFalse:[path]! ! !FileDirectory methodsFor: 'path access' stamp: 'tk 5/18/1998 22:29'! on: fullPath "Return another instance" ^ self class on: fullPath! ! !FileDirectory methodsFor: 'path access' stamp: 'stephaneducasse 2/4/2006 20:31'! pathFromUrl: aFileUrl | first | ^String streamContents: [ :s | first := false. aFileUrl path do: [ :p | first ifTrue: [ s nextPut: self pathNameDelimiter ]. first := true. s nextPutAll: p ] ].! ! !FileDirectory methodsFor: 'path access' stamp: 'yo 12/19/2003 21:15'! pathName "Return the path from the root of the file system to this directory." ^ pathName asSqueakPathName. ! ! !FileDirectory methodsFor: 'path access' stamp: 'jm 12/5/97 12:19'! pathNameDelimiter "Return the delimiter character for this kind of directory. This depends on the current platform." ^ self class pathNameDelimiter ! ! !FileDirectory methodsFor: 'path access' stamp: 'yo 12/19/2003 21:15'! pathParts "Return the path from the root of the file system to this directory as an array of directory names." ^ pathName asSqueakPathName findTokens: self pathNameDelimiter asString! ! !FileDirectory methodsFor: 'path access' stamp: 'ar 12/18/1999 00:36'! slash ^self class slash! ! !FileDirectory methodsFor: 'printing' stamp: 'yo 12/19/2003 21:15'! printOn: aStream "Refer to the comment in Object|printOn:." aStream nextPutAll: self class name. aStream nextPutAll: ' on '. pathName asSqueakPathName printOn: aStream. ! ! !FileDirectory methodsFor: 'searching' stamp: 'stephaneducasse 2/4/2006 20:31'! filesContaining: searchString caseSensitive: aBoolean | aList | "Search the contents of all files in the receiver and its subdirectories for the search string. Return a list of paths found. Make the search case sensitive if aBoolean is true." aList := OrderedCollection new. self withAllFilesDo: [:stream | (stream contentsOfEntireFile includesSubstring: searchString caseSensitive: aBoolean) ifTrue: [aList add: stream name]] andDirectoriesDo: [:d | d pathName]. ^ aList "FileDirectory default filesContaining: 'includesSubstring:' caseSensitive: true"! ! !FileDirectory methodsFor: 'searching' stamp: 'stephane.ducasse 4/13/2009 20:30'! withAllFilesDo: fileStreamBlock andDirectoriesDo: directoryBlock "For the receiver and all it's subdirectories evaluate directoryBlock. For a read only file stream on each file within the receiver and it's subdirectories evaluate fileStreamBlock." | todo dir | todo := OrderedCollection with: self. [todo size > 0] whileTrue: [ dir := todo removeFirst. directoryBlock value: dir. dir fileNames do: [:n | fileStreamBlock value: (FileStream readOnlyFileNamed: (dir fullNameFor: n))]. dir directoryNames do: [:n | todo add: (dir directoryNamed: n)]] ! ! !FileDirectory methodsFor: 'squeaklets' stamp: 'RAA 10/17/2000 14:57'! directoryObject ^self! ! !FileDirectory methodsFor: 'squeaklets' stamp: 'mir 6/17/2001 23:42'! downloadUrl ^''! ! !FileDirectory methodsFor: 'squeaklets' stamp: 'RAA 10/12/2000 17:18'! updateProjectInfoFor: aProject "only swiki servers for now"! ! !FileDirectory methodsFor: 'squeaklets' stamp: 'dgd 12/23/2003 16:21'! writeProject: aProject inFileNamed: fileNameString fromDirectory: localDirectory "write aProject (a file version can be found in the file named fileNameString in localDirectory)" aProject writeFileNamed: fileNameString fromDirectory: localDirectory toServer: self! ! !FileDirectory methodsFor: 'testing' stamp: 'mir 6/25/2001 13:08'! acceptsUploads ^true! ! !FileDirectory methodsFor: 'testing' stamp: 'stephaneducasse 2/4/2006 20:31'! directoryExists: filenameOrPath "Answer true if a directory of the given name exists. The given name may be either a full path name or a local directory within this directory." "FileDirectory default directoryExists: FileDirectory default pathName" | fName dir | DirectoryClass splitName: filenameOrPath to: [:filePath :name | fName := name. filePath isEmpty ifTrue: [dir := self] ifFalse: [dir := self directoryNamed: filePath]]. ^dir exists and: [ self isCaseSensitive ifTrue:[dir directoryNames includes: fName] ifFalse:[dir directoryNames anySatisfy: [:name| name sameAs: fName]]]. ! ! !FileDirectory methodsFor: 'testing' stamp: 'stephaneducasse 2/4/2006 20:31'! exists "Answer whether the directory exists" | result | result := self primLookupEntryIn: pathName asVmPathName index: 1. ^ result ~= #badDirectoryPath ! ! !FileDirectory methodsFor: 'testing' stamp: 'stephaneducasse 2/4/2006 20:31'! fileExists: filenameOrPath "Answer true if a file of the given name exists. The given name may be either a full path name or a local file within this directory." "FileDirectory default fileExists: Smalltalk sourcesName" | fName dir | DirectoryClass splitName: filenameOrPath to: [:filePath :name | fName := name. filePath isEmpty ifTrue: [dir := self] ifFalse: [dir := FileDirectory on: filePath]]. self isCaseSensitive ifTrue:[^dir fileNames includes: fName] ifFalse:[^dir fileNames anySatisfy: [:name| name sameAs: fName]]. ! ! !FileDirectory methodsFor: 'testing' stamp: 'di 11/21/1999 20:17'! includesKey: localName "Answer true if this directory includes a file or directory of the given name. Note that the name should be a local file name, in contrast with fileExists:, which takes either local or full-qualified file names." "(FileDirectory on: Smalltalk vmPath) includesKey: 'SqueakV2.sources'" self isCaseSensitive ifTrue:[^ self fileAndDirectoryNames includes: localName] ifFalse:[^ self fileAndDirectoryNames anySatisfy: [:str| str sameAs: localName]].! ! !FileDirectory methodsFor: 'testing' stamp: 'ar 5/30/2001 21:42'! isAFileNamed: fName ^FileStream isAFileNamed: (self fullNameFor: fName)! ! !FileDirectory methodsFor: 'testing' stamp: 'ar 5/1/1999 01:51'! isCaseSensitive "Return true if file names are treated case sensitive" ^self class isCaseSensitive! ! !FileDirectory methodsFor: 'testing' stamp: 'dgd 12/27/2003 10:46'! isRemoteDirectory "answer whatever the receiver is a remote directory" ^ false! ! !FileDirectory methodsFor: 'private' stamp: 'stephaneducasse 2/4/2006 20:31'! directoryContentsFor: fullPath "Return a collection of directory entries for the files and directories in the directory with the given path. See primLookupEntryIn:index: for further details." "FileDirectory default directoryContentsFor: ''" | entries index done entryArray f | entries := OrderedCollection new: 200. index := 1. done := false. f := fullPath asVmPathName. [done] whileFalse: [ entryArray := self primLookupEntryIn: f index: index. #badDirectoryPath = entryArray ifTrue: [ ^(InvalidDirectoryError pathName: pathName asSqueakPathName) signal]. entryArray == nil ifTrue: [done := true] ifFalse: [entries addLast: (DirectoryEntry fromArray: entryArray)]. index := index + 1]. ^ entries asArray collect: [:s | s convertFromSystemName]. ! ! !FileDirectory methodsFor: 'private' stamp: 'ar 2/2/2001 15:09'! primCreateDirectory: fullPath "Create a directory named by the given path. Fail if the path is bad or if a file or directory by that name already exists." self primitiveFailed ! ! !FileDirectory methodsFor: 'private' stamp: 'ar 2/2/2001 15:09'! primDeleteDirectory: fullPath "Delete the directory named by the given path. Fail if the path is bad or if a directory by that name does not exist." self primitiveFailed ! ! !FileDirectory methodsFor: 'private' stamp: 'ar 2/2/2001 15:09'! primDeleteFileNamed: aFileName "Delete the file of the given name. Return self if the primitive succeeds, nil otherwise." ^ nil ! ! !FileDirectory methodsFor: 'private' stamp: 'ar 2/2/2001 15:09'! primGetMacFileNamed: fileName type: typeString creator: creatorString "Get the Macintosh file type and creator info for the file with the given name. Fails if the file does not exist or if the type and creator type arguments are not strings of length 4. This primitive is Mac specific; it is a noop on other platforms." ! ! !FileDirectory methodsFor: 'private' stamp: 'ar 2/2/2001 15:09'! primLookupEntryIn: fullPath index: index "Look up the index-th entry of the directory with the given fully-qualified path (i.e., starting from the root of the file hierarchy) and return an array containing: The empty string enumerates the top-level files or drives. (For example, on Unix, the empty path enumerates the contents of '/'. On Macs and PCs, it enumerates the mounted volumes/drives.) The creation and modification times are in seconds since the start of the Smalltalk time epoch. DirFlag is true if the entry is a directory. FileSize the file size in bytes or zero for directories. The primitive returns nil when index is past the end of the directory. It fails if the given path is bad." ^ #badDirectoryPath ! ! !FileDirectory methodsFor: 'private' stamp: 'ar 2/2/2001 15:09'! primRename: oldFileFullName to: newFileFullName "Rename the file of the given name to the new name. Fail if there is no file of the old name or if there is an existing file with the new name. Changed to return nil instead of failing ar 3/21/98 18:04" ^nil! ! !FileDirectory methodsFor: 'private' stamp: 'ar 2/2/2001 15:09'! primSetMacFileNamed: fileName type: typeString creator: creatorString "Set the Macintosh file type and creator info for the file with the given name. Fails if the file does not exist or if the type and creator type arguments are not strings of length 4. This primitive is Mac specific; it is a noop on other platforms." self primitiveFailed ! ! !FileDirectory methodsFor: 'private' stamp: 'stephaneducasse 2/4/2006 20:31'! setPathName: pathString pathName := FilePath pathName: pathString. ! ! !FileDirectory methodsFor: 'private' stamp: 'mir 6/25/2001 18:05'! storeServerEntryOn: stream stream nextPutAll: 'name:'; tab; nextPutAll: self localName; cr; nextPutAll: 'directory:'; tab; nextPutAll: self pathName; cr; nextPutAll: 'type:'; tab; nextPutAll: 'file'; cr! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileDirectory class instanceVariableNames: ''! !FileDirectory class methodsFor: '*network-uri' stamp: 'JMM 2/3/2008 14:17'! contentStreamForURI: aURI | fullPath stream | fullPath := self fullPathForURI: aURI. stream := FileStream readOnlyFileFullyNamed: fullPath. ^stream binary ! ! !FileDirectory class methodsFor: '*network-uri' stamp: 'JMM 2/3/2008 14:14'! contentUTF8StreamForURI: aURI | fullPath | fullPath := self fullPathForURI: aURI. ^FileStream readOnlyFileFullyNamed: fullPath ! ! !FileDirectory class methodsFor: '*network-uri' stamp: 'JMM 2/3/2008 14:17'! contentUTF8WriteableStreamForURI: aURI | fullPath | fullPath := self fullPathForURI: aURI. ^FileStream oldFileFullyNamed: fullPath! ! !FileDirectory class methodsFor: '*network-uri' stamp: 'JMM 2/3/2008 14:17'! contentWriteableStreamForURI: aURI | fullPath stream | fullPath := self fullPathForURI: aURI. stream := FileStream oldFileFullyNamed: fullPath. ^stream binary! ! !FileDirectory class methodsFor: '*network-uri' stamp: 'mir 6/20/2005 18:53'! fullPathForURI: aURI ^self activeDirectoryClass privateFullPathForURI: (FileDirectory default uri resolveRelativeURI: aURI)! ! !FileDirectory class methodsFor: '*network-uri' stamp: 'mir 6/20/2005 18:53'! privateFullPathForURI: aURI ^(aURI path copyReplaceAll: '/' with: self slash) unescapePercents! ! !FileDirectory class methodsFor: '*network-uri' stamp: 'JMM 12/1/2007 15:31'! retrieveMIMEDocument: uri | file | file := [self contentStreamForURI: uri] on: FileDoesNotExistException do:[:ex| ex return: nil]. file ifNotNil: [^MIMEDocument contentStream: file mimeType: (MIMEType forURIReturnSingleMimeTypeOrDefault: uri)]. ^nil! ! !FileDirectory class methodsFor: '*network-uri' stamp: 'mir 6/20/2005 18:34'! uri: aURI ^self on: (FileDirectory fullPathForURI: aURI)! ! !FileDirectory class methodsFor: 'create/delete file' stamp: 'stephaneducasse 2/4/2006 20:32'! deleteFilePath: fullPathToAFile "Delete the file after finding its directory" | dir | dir := self on: (self dirPathFor: fullPathToAFile). dir deleteFileNamed: (self localNameFor: fullPathToAFile). ! ! !FileDirectory class methodsFor: 'create/delete file' stamp: 'stephaneducasse 2/4/2006 20:32'! lookInUsualPlaces: fileName "Check the default directory, the imagePath, and the vmPath (and the vmPath's owner) for this file." | vmp | (FileDirectory default fileExists: fileName) ifTrue: [^ FileDirectory default fileNamed: fileName]. ((vmp := FileDirectory on: SmalltalkImage current imagePath) fileExists: fileName) ifTrue: [^ vmp fileNamed: fileName]. ((vmp := FileDirectory on: SmalltalkImage current vmPath) fileExists: fileName) ifTrue: [^ vmp fileNamed: fileName]. ((vmp := vmp containingDirectory) fileExists: fileName) ifTrue: [^ vmp fileNamed: fileName]. ^ nil! ! !FileDirectory class methodsFor: 'instance creation' stamp: 'jm 12/4/97 19:24'! default "Answer the default directory." ^ DefaultDirectory ! ! !FileDirectory class methodsFor: 'instance creation' stamp: 'stephaneducasse 2/4/2006 20:32'! forFileName: aString | path | path := self dirPathFor: aString. path isEmpty ifTrue: [^ self default]. ^ self on: path ! ! !FileDirectory class methodsFor: 'instance creation' stamp: 'stephaneducasse 2/4/2006 20:32'! on: pathString "Return a new file directory for the given path, of the appropriate FileDirectory subclass for the current OS platform." | pathName | DirectoryClass ifNil: [self setDefaultDirectoryClass]. "If path ends with a delimiter (: or /) then remove it" ((pathName := pathString) endsWith: self pathNameDelimiter asString) ifTrue: [ pathName := pathName copyFrom: 1 to: pathName size - 1]. ^ DirectoryClass new setPathName: pathName ! ! !FileDirectory class methodsFor: 'instance creation' stamp: 'jm 12/4/97 23:29'! root "Answer the root directory." ^ self on: '' ! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'stephane.ducasse 4/13/2009 20:30'! baseNameFor: fileName "Return the given file name without its extension, if any. We have to remember that many (most?) OSs allow extension separators within directory names and so the leaf filename needs to be extracted, trimmed and rejoined. Yuck" "The test is FileDirectory baseNameFor: ((FileDirectory default directoryNamed: 'foo.bar') fullNameFor:'blim.blam') should end 'foo.bar/blim' (or as appropriate for your platform AND FileDirectory baseNameFor: ((FileDirectory default directoryNamed: 'foo.bar') fullNameFor:'blim') should be the same and NOT 'foo' Oh, and FileDirectory baseNameFor: 'foo.bar' should be 'foo' not '/foo' " | delim i leaf | self splitName: fileName to: [:path :fn| delim := DirectoryClass extensionDelimiter. i := fn findLast: [:c | c = delim]. leaf := i = 0 ifTrue: [fn] ifFalse: [fn copyFrom: 1 to: i - 1]. path isEmpty ifTrue:[^leaf]. ^path, self slash, leaf] ! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'TPR 5/10/1998 21:32'! changeSuffix "if 'changes' is not suitable, override this message to return something that is ok" ^'changes'! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'jf 2/7/2004 17:22'! checkName: fileName fixErrors: flag "Check a string fileName for validity as a file name on the current default file system. Answer the original file name if it is valid. If the name is not valid (e.g., it is too long or contains illegal characters) and fixing is false, raise an error. If fixing is true, fix the name (usually by truncating and/or tranforming characters), and answer the corrected name. The default behavior is to truncate the name to 31 chars. Subclasses can do any kind of checking and correction appropriate to the underlying platform." ^ DefaultDirectory checkName: fileName fixErrors: flag ! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'tpr 10/13/2003 10:59'! dirPathFor: fullName "Return the directory part the given name." DirectoryClass splitName: fullName to: [:dirPath :localName | ^ dirPath]! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'ar 4/7/2002 15:47'! directoryEntryFor: filenameOrPath ^self default directoryEntryFor: filenameOrPath! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'stephaneducasse 2/4/2006 20:32'! extensionFor: fileName "Return the extension of given file name, if any." | delim i | delim := DirectoryClass extensionDelimiter. i := fileName findLast: [:c | c = delim]. i = 0 ifTrue: [^ ''] ifFalse: [^ fileName copyFrom: i + 1 to: fileName size]. ! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'stephaneducasse 2/4/2006 20:32'! fileName: fileName extension: fileExtension | extension | extension := FileDirectory dot , fileExtension. ^(fileName endsWith: extension) ifTrue: [fileName] ifFalse: [fileName , extension].! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'TPR 5/10/1998 21:31'! imageSuffix "if 'image' is not suitable, override this message to return something that is ok" ^'image'! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'jm 12/4/97 23:40'! isLegalFileName: fullName "Return true if the given string is a legal file name." ^ DefaultDirectory isLegalFileName: (self localNameFor: fullName) ! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'tpr 10/13/2003 10:59'! localNameFor: fullName "Return the local part the given name." DirectoryClass splitName: fullName to: [:dirPath :localName | ^ localName]! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'stephaneducasse 2/4/2006 20:32'! splitName: fullName to: pathAndNameBlock "Take the file name and convert it to the path name of a directory and a local file name within that directory. FileName must be of the form: , where is optional. The part may contain delimiters." | delimiter i dirName localName | delimiter := self pathNameDelimiter. (i := fullName findLast: [:c | c = delimiter]) = 0 ifTrue: [dirName := String new. localName := fullName] ifFalse: [dirName := fullName copyFrom: 1 to: (i - 1 max: 1). localName := fullName copyFrom: i + 1 to: fullName size]. ^ pathAndNameBlock value: dirName value: localName! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'tpr 12/15/2003 12:03'! startUp "Establish the platform-specific FileDirectory subclass. Do any platform-specific startup." self setDefaultDirectoryClass. self setDefaultDirectory: (self dirPathFor: SmalltalkImage current imageName). Preferences startInUntrustedDirectory ifTrue:[ "The SecurityManager may override the default directory to prevent unwanted write access etc." self setDefaultDirectory: SecurityManager default untrustedUserDirectory. "Make sure we have a place to go to" DefaultDirectory assureExistence]. SmalltalkImage current openSourceFiles. ! ! !FileDirectory class methodsFor: 'name utilities' stamp: 'stephaneducasse 2/4/2006 20:32'! urlForFileNamed: aFilename "Create a URL for the given fully qualified file name" "FileDirectory urlForFileNamed: 'C:\Home\andreasr\Squeak\DSqueak3\DSqueak3:=1.1\DSqueak3.1.image' " | path localName | DirectoryClass splitName: aFilename to: [:p :n | path := p. localName := n]. ^ localName asUrlRelativeTo: (self on: path) url asUrl! ! !FileDirectory class methodsFor: 'platform specific' stamp: 'jm 3/27/98 08:17'! dot "Return a one-character string containing the filename extension delimiter for this platform (i.e., the local equivalent of 'dot')" ^ self extensionDelimiter asString ! ! !FileDirectory class methodsFor: 'platform specific' stamp: 'jm 3/27/98 06:57'! extensionDelimiter "Return the character used to delimit filename extensions on this platform. Most platforms use the period (.) character." ^ $. ! ! !FileDirectory class methodsFor: 'platform specific' stamp: 'ar 5/1/1999 01:48'! isCaseSensitive "Return true if file names are treated case sensitive" ^true! ! !FileDirectory class methodsFor: 'platform specific' stamp: 'nk 3/13/2003 10:58'! makeAbsolute: path "Ensure that path looks like an absolute path" ^path first = self pathNameDelimiter ifTrue: [ path ] ifFalse: [ self slash, path ]! ! !FileDirectory class methodsFor: 'platform specific' stamp: 'nk 3/13/2003 10:59'! makeRelative: path "Ensure that path looks like an relative path" ^path first = self pathNameDelimiter ifTrue: [ path copyWithoutFirst ] ifFalse: [ path ]! ! !FileDirectory class methodsFor: 'platform specific' stamp: 'jm 5/8/1998 20:45'! maxFileNameLength ^ 31 ! ! !FileDirectory class methodsFor: 'platform specific' stamp: 'TPR 5/12/1998 22:49'! pathNameDelimiter "return the active directory class's directory seperator character" ^ DirectoryClass pathNameDelimiter! ! !FileDirectory class methodsFor: 'platform specific' stamp: 'ar 4/18/1999 18:18'! slash ^ self pathNameDelimiter asString! ! !FileDirectory class methodsFor: 'system start up' stamp: 'stephaneducasse 2/4/2006 20:32'! openChanges: changesName forImage: imageName "find the changes file by looking in a) the directory derived from the image name b) the DefaultDirectory (which will normally be the directory derived from the image name or the SecurityManager's choice) If an old file is not found in either place, check for a read-only file in the same places. If that fails, return nil" | changes fd | "look for the changes file or an alias to it in the image directory" fd := FileDirectory on: (FileDirectory dirPathFor: imageName). (fd fileExists: changesName) ifTrue: [changes := fd oldFileNamed: changesName]. changes ifNotNil:[^changes]. "look for the changes in the default directory" fd := DefaultDirectory. (fd fileExists: changesName) ifTrue: [changes := fd oldFileNamed: changesName]. changes ifNotNil:[^changes]. "look for read-only changes in the image directory" fd := FileDirectory on: (FileDirectory dirPathFor: imageName). (fd fileExists: changesName) ifTrue: [changes := fd readOnlyFileNamed: changesName]. changes ifNotNil:[^changes]. "look for read-only changes in the default directory" fd := DefaultDirectory. (fd fileExists: changesName) ifTrue: [changes := fd readOnlyFileNamed: changesName]. "this may be nil if the last try above failed to open a file" ^changes ! ! !FileDirectory class methodsFor: 'system start up' stamp: 'adrian_lienhard 7/18/2009 15:55'! openSources: sourcesName andChanges: changesName forImage: imageName "Open the changes and sources files and install them in SourceFiles. Inform the user of problems regarding write permissions or CR/CRLF mixups." "Note: SourcesName and imageName are full paths; changesName is a local name." | sources changes msg wmsg | msg := 'Pharo cannot locate &fileRef. Please check that the file is named properly and is in the same directory as this image.'. wmsg := 'Pharo cannot write to &fileRef. Please check that you have write permission for this file. You won''t be able to save this image correctly until you fix this.'. sources := self openSources: sourcesName forImage: imageName. changes := self openChanges: changesName forImage: imageName. ((sources == nil or: [sources atEnd]) and: [Preferences valueOfFlag: #warnIfNoSourcesFile]) ifTrue: [SmalltalkImage current platformName = 'Mac OS' ifTrue: [msg := msg , ' Make sure the sources file is not an Alias.']. self inform: (msg copyReplaceAll: '&fileRef' with: 'the sources file named ' , sourcesName)]. (changes == nil and: [Preferences valueOfFlag: #warnIfNoChangesFile]) ifTrue: [self inform: (msg copyReplaceAll: '&fileRef' with: 'the changes file named ' , changesName)]. ((Preferences valueOfFlag: #warnIfNoChangesFile) and: [changes notNil]) ifTrue: [changes isReadOnly ifTrue: [self inform: (wmsg copyReplaceAll: '&fileRef' with: 'the changes file named ' , changesName)]. ((changes next: 200) includesSubString: String crlf) ifTrue: [self inform: 'The changes file named ' , changesName , ' has been injured by an unpacking utility. Crs were changed to CrLfs. Please set the preferences in your decompressing program to "do not convert text files" and unpack the system again.']]. SourceFiles := Array with: sources with: changes! ! !FileDirectory class methodsFor: 'system start up' stamp: 'stephaneducasse 2/4/2006 20:32'! openSources: fullSourcesName forImage: imageName "We first do a check to see if a compressed version ofthe sources file is present. Open the .sources file read-only after searching in: a) the directory where the VM lives b) the directory where the image came from c) the DefaultDirectory (which is likely the same as b unless the SecurityManager has changed it). " | sources fd sourcesName | (fullSourcesName endsWith: 'sources') ifTrue: ["Look first for a sources file in compressed format." sources := self openSources: (fullSourcesName allButLast: 7) , 'stc' forImage: imageName. sources ifNotNil: [^ CompressedSourceStream on: sources]]. sourcesName := FileDirectory localNameFor: fullSourcesName. "look for the sources file or an alias to it in the VM's directory" fd := FileDirectory on: SmalltalkImage current vmPath. (fd fileExists: sourcesName) ifTrue: [sources := fd readOnlyFileNamed: sourcesName]. sources ifNotNil: [^ sources]. "look for the sources file or an alias to it in the image directory" fd := FileDirectory on: (FileDirectory dirPathFor: imageName). (fd fileExists: sourcesName) ifTrue: [sources := fd readOnlyFileNamed: sourcesName]. sources ifNotNil: [^ sources]. "look for the sources in the current directory" fd := DefaultDirectory. (fd fileExists: sourcesName) ifTrue: [sources := fd readOnlyFileNamed: sourcesName]. "sources may still be nil here" ^sources ! ! !FileDirectory class methodsFor: 'system start up' stamp: 'stephaneducasse 2/4/2006 20:32'! setDefaultDirectory: directoryName "Initialize the default directory to the directory supplied. This method is called when the image starts up." | dirName | DirectoryClass := self activeDirectoryClass. dirName := (FilePath pathName: directoryName) asSqueakPathName. [dirName endsWith: self slash] whileTrue:[ dirName := dirName copyFrom: 1 to: dirName size - self slash size. ]. DefaultDirectory := self on: dirName.! ! !FileDirectory class methodsFor: 'system start up' stamp: 'stephaneducasse 2/4/2006 20:32'! setDefaultDirectoryClass "Initialize the default directory class to suit this platform. This method is called when the image starts up - it needs to be right at the front of the list of the startup sequence" DirectoryClass := self activeDirectoryClass ! ! !FileDirectory class methodsFor: 'system start up' stamp: 'stephaneducasse 2/4/2006 20:32'! setDefaultDirectoryFrom: imageName "Initialize the default directory to the directory containing the Squeak image file. This method is called when the image starts up." DirectoryClass := self activeDirectoryClass. DefaultDirectory := self on: (FilePath pathName: (self dirPathFor: imageName) isEncoded: true) asSqueakPathName. ! ! !FileDirectory class methodsFor: 'system start up' stamp: 'sd 11/16/2003 13:13'! shutDown SmalltalkImage current closeSourceFiles. ! ! !FileDirectory class methodsFor: 'private' stamp: 'TPR 5/10/1998 21:47'! activeDirectoryClass "Return the concrete FileDirectory subclass for the platform on which we are currently running." FileDirectory allSubclasses do: [:class | class isActiveDirectoryClass ifTrue: [^ class]]. "no responding subclass; use FileDirectory" ^ FileDirectory ! ! !FileDirectory class methodsFor: 'private' stamp: 'TPR 5/10/1998 21:40'! isActiveDirectoryClass "Does this class claim to be that properly active subclass of FileDirectory for this platform? Default test is whether the primPathNameDelimiter matches the one for this class. Other tests are possible" ^self pathNameDelimiter = self primPathNameDelimiter ! ! !FileDirectory class methodsFor: 'private' stamp: 'ar 2/2/2001 15:09'! primPathNameDelimiter "Return the path delimiter for the underlying platform's file system." self primitiveFailed ! ! ClassTestCase subclass: #FileDirectoryTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Files'! !FileDirectoryTest methodsFor: 'create/delete tests' stamp: 'adrian-lienhard 6/5/2009 23:01'! deleteDirectory (self directory exists) ifTrue: [self directory containingDirectory deleteDirectory: self directoryName]! ! !FileDirectoryTest methodsFor: 'create/delete tests' stamp: 'adrian-lienhard 6/5/2009 23:02'! testDeleteDirectory "Test deletion of a directory" | aContainingDirectory preTestItems | aContainingDirectory := self directory containingDirectory. preTestItems := aContainingDirectory fileAndDirectoryNames. self assert: self assuredDirectory exists. aContainingDirectory deleteDirectory: self directoryName. self shouldnt: [aContainingDirectory directoryNames includes: self directoryName ] description: 'Should successfully delete directory.'. self should: [preTestItems = aContainingDirectory fileAndDirectoryNames] description: 'Should only delete the indicated directory.'. ! ! !FileDirectoryTest methodsFor: 'existence tests' stamp: 'on 6/11/2008 16:29'! testAttemptExistenceCheckWhenFile "How should a FileDirectory instance respond with an existent file name?" | directory testFile | testFile := 'aTestFile'. FileDirectory default forceNewFileNamed: testFile. directory := FileDirectory default directoryNamed: testFile. self shouldnt: [directory exists] description: 'Files are not directories.'. FileDirectory default deleteFileNamed: testFile! ! !FileDirectoryTest methodsFor: 'existence tests' stamp: 'adrian-lienhard 6/5/2009 23:02'! testDirectoryExists self assert: self assuredDirectory exists. self should: [self directory containingDirectory directoryExists: self directoryName]. self directory containingDirectory deleteDirectory: self directoryName. self shouldnt: [self directory containingDirectory directoryExists: self directoryName]! ! !FileDirectoryTest methodsFor: 'existence tests' stamp: 'adrian-lienhard 6/5/2009 23:02'! testDirectoryExistsWhenLikeNamedFileExists | testFileName | [testFileName := self assuredDirectory fullNameFor: 'zDirExistsTest.testing'. (FileStream newFileNamed: testFileName) close. self should: [FileStream isAFileNamed: testFileName]. self shouldnt: [(FileDirectory on: testFileName) exists]] ensure: [self assuredDirectory deleteFileNamed: 'zDirExistsTest.testing'] ! ! !FileDirectoryTest methodsFor: 'existence tests' stamp: 'adrian-lienhard 6/5/2009 23:01'! testDirectoryNamed self should: [(self directory containingDirectory directoryNamed: self directoryName) pathName = self directory pathName]! ! !FileDirectoryTest methodsFor: 'existence tests' stamp: 'adrian-lienhard 6/5/2009 23:02'! testExists self should: [FileDirectory default exists] description: 'Should know default directory exists.'. self should: [self assuredDirectory exists] description: 'Should know created directory exists.'. self directory containingDirectory deleteDirectory: self directoryName. self shouldnt: [(self directory containingDirectory directoryNamed: self directoryName) exists] description: 'Should know that recently deleted directory no longer exists.'.! ! !FileDirectoryTest methodsFor: 'existence tests' stamp: 'stephaneducasse 2/4/2006 20:31'! testNonExistentDirectory | directory parentDirectory | directory :=FileDirectory default directoryNamed: 'nonExistentFolder'. self shouldnt: [directory exists] description: 'A FileDirectory instance should know if it points to a non-existent directory.'. parentDirectory :=FileDirectory default. self shouldnt: [parentDirectory directoryExists: 'nonExistentFolder'] description: 'A FileDirectory instance should know when a directory of the given name doesn''t exist'. ! ! !FileDirectoryTest methodsFor: 'existence tests' stamp: 'adrian-lienhard 6/5/2009 23:02'! testOldFileOrNoneNamed | file | file := self assuredDirectory oldFileOrNoneNamed: 'test.txt'. [self assert: file isNil. "Reproduction of Mantis #1049" (self assuredDirectory fileNamed: 'test.txt') nextPutAll: 'foo'; close. file := self assuredDirectory oldFileOrNoneNamed: 'test.txt'. self assert: file notNil] ensure: [ file ifNotNil: [file close]. self assuredDirectory deleteFileNamed: 'test.txt' ifAbsent: nil] ! ! !FileDirectoryTest methodsFor: 'resources' stamp: 'adrian-lienhard 6/5/2009 23:02'! assuredDirectory ^self directory assureExistence! ! !FileDirectoryTest methodsFor: 'resources' stamp: 'adrian-lienhard 6/5/2009 22:59'! directory ^FileDirectory default directoryNamed: self directoryName! ! !FileDirectoryTest methodsFor: 'resources' stamp: 'adrian-lienhard 6/5/2009 22:59'! directoryName ^ self class name! ! !FileDirectoryTest methodsFor: 'resources' stamp: 'adrian-lienhard 6/5/2009 23:03'! tearDown [ self deleteDirectory ] on: Error do: [ :ex | ]! ! ListItemWrapper subclass: #FileDirectoryWrapper instanceVariableNames: 'itemName balloonText hasContents' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Explorer'! !FileDirectoryWrapper methodsFor: 'accessing' stamp: 'RAA 7/21/2000 11:00'! balloonText ^balloonText! ! !FileDirectoryWrapper methodsFor: 'accessing' stamp: 'ar 2/12/2001 16:20'! contents ^((model directoryNamesFor: item) sortBy: [ :a :b | a caseInsensitiveLessOrEqual: b]) collect: [ :n | FileDirectoryWrapper with: (item directoryNamed: n) name: n model: self ] ! ! !FileDirectoryWrapper methodsFor: 'accessing' stamp: 'tpr 11/28/2003 14:02'! hasContents "Return whether this directory has subfolders. The value is cached to avoid a performance penalty. Also for performance reasons, the code below will just assume that the directory does indeed have contents in a few of cases: 1. If the item is not a FileDirectory (thus avoiding the cost of refreshing directories that are not local) 2. If it's the root directory of a given volume 3. If there is an error computing the FileDirectory's contents " hasContents ifNil: [hasContents := true. "default" ["Best test I could think of for determining if this is a local directory " ((item isKindOf: FileDirectory) and: ["test to see that it's not the root directory" "there has to be a better way of doing this test -tpr" item pathParts size > 1]) ifTrue: [hasContents := self contents notEmpty]] on: Error do: [hasContents := true]]. ^ hasContents! ! !FileDirectoryWrapper methodsFor: 'accessing' stamp: 'dgd 9/26/2004 18:22'! icon "Answer a form to be used as icon" ^ item isRemoteDirectory ifTrue: [MenuIcons smallRemoteOpenIcon] ifFalse: [MenuIcons smallOpenIcon]! ! !FileDirectoryWrapper methodsFor: 'as yet unclassified' stamp: 'RAA 7/21/2000 11:01'! balloonText: aStringOrNil balloonText := aStringOrNil! ! !FileDirectoryWrapper methodsFor: 'as yet unclassified' stamp: 'ar 2/12/2001 16:22'! directoryNamesFor: anItem ^model directoryNamesFor: anItem! ! !FileDirectoryWrapper methodsFor: 'as yet unclassified' stamp: 'sps 12/5/2002 16:59'! setItem: anObject name: aString model: aModel item := anObject. model := aModel. itemName := aString. hasContents := nil. ! ! !FileDirectoryWrapper methodsFor: 'as yet unclassified' stamp: 'RAA 6/16/2000 18:30'! settingSelector ^#setSelectedDirectoryTo:! ! !FileDirectoryWrapper methodsFor: 'converting' stamp: 'dgd 8/27/2004 18:45'! asString ^itemName translatedIfCorresponds! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileDirectoryWrapper class instanceVariableNames: ''! !FileDirectoryWrapper class methodsFor: 'as yet unclassified' stamp: 'RAA 6/15/2000 18:01'! with: anObject name: aString model: aModel ^self new setItem: anObject name: aString model: aModel! ! FileStreamException subclass: #FileDoesNotExistException instanceVariableNames: 'readOnly' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !FileDoesNotExistException methodsFor: 'accessing' stamp: 'mir 7/25/2000 16:41'! readOnly ^readOnly == true! ! !FileDoesNotExistException methodsFor: 'accessing' stamp: 'mir 7/25/2000 16:40'! readOnly: aBoolean readOnly := aBoolean! ! !FileDoesNotExistException methodsFor: 'exceptiondescription' stamp: 'mir 7/25/2000 18:22'! defaultAction "The default action taken if the exception is signaled." ^self readOnly ifTrue: [StandardFileStream readOnlyFileDoesNotExistUserHandling: self fileName] ifFalse: [StandardFileStream fileDoesNotExistUserHandling: self fileName] ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileDoesNotExistException class instanceVariableNames: ''! !FileDoesNotExistException class methodsFor: 'examples' stamp: 'mir 2/29/2000 11:44'! example "FileDoesNotExistException example" | result | result := [(StandardFileStream readOnlyFileNamed: 'error42.log') contentsOfEntireFile] on: FileDoesNotExistException do: [:ex | 'No error log']. Transcript show: result; cr! ! FileStreamException subclass: #FileExistsException instanceVariableNames: 'fileClass' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !FileExistsException methodsFor: 'accessing' stamp: 'LC 10/24/2001 21:49'! fileClass ^ fileClass ifNil: [StandardFileStream]! ! !FileExistsException methodsFor: 'accessing' stamp: 'LC 10/24/2001 21:42'! fileClass: aClass fileClass := aClass! ! !FileExistsException methodsFor: 'exceptiondescription' stamp: 'LC 10/24/2001 21:50'! defaultAction "The default action taken if the exception is signaled." ^ self fileClass fileExistsUserHandling: self fileName ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileExistsException class instanceVariableNames: ''! !FileExistsException class methodsFor: 'exceptioninstantiator' stamp: 'LC 10/24/2001 21:50'! fileName: aFileName fileClass: aClass ^ self new fileName: aFileName; fileClass: aClass! ! StringHolder subclass: #FileList instanceVariableNames: 'fileName directory volList volListIndex list listIndex pattern sortMode brevityState currentDirectorySelected fileSelectionBlock dirSelectionBlock optionalButtonSpecs modalView directoryChangeBlock ok' classVariableNames: 'FileReaderRegistry RecentDirs' poolDictionaries: '' category: 'Morphic-FileList'! !FileList commentStamp: 'BJP 11/19/2003 21:13' prior: 0! Some variations on FileList that - use a hierarchical pane to show folder structure - use different pane combinations, button layouts and prefiltering for specific uses FileList2 morphicView openInWorld "an alternative to the standard FileList" FileList2 morphicViewNoFile openInWorld "useful for selecting, but not viewing" FileList2 morphicViewProjectLoader openInWorld "useful for finding and loading projects" FileList2 modalFolderSelector "allows the user to select a folder" ! !FileList methodsFor: '*Polymorph-Widgets' stamp: 'gvc 2/6/2009 12:34'! morphicPatternPane "Remove the vertical scrollbar since the minHeight would otherwise be too large to fit the layout frame. Added here for Pharo since FileList2 has been merged into FileList." |pane| pane := PluggableTextMorph on: self text: #pattern accept: #pattern:. pane acceptOnCR: true; hideVScrollBarIndefinitely: true. ^pane! ! !FileList methodsFor: 'accessing' stamp: 'hfm 11/29/2008 18:47'! directory ^ directory! ! !FileList methodsFor: 'accessing' stamp: 'stephane.ducasse 5/21/2009 14:33'! directory: dir "Set the path of the volume to be displayed." self okToChange ifFalse: [^ self]. self modelSleep. directory := dir ifNil: [FileDirectory on: '']. self modelWakeUp. sortMode == nil ifTrue: [sortMode := #date]. volList := ((Array with: '[]'), directory pathParts) withIndexCollect: [:each :i | ( String new: i-1 withAll: $ ), each]. volListIndex := volList size. self changed: #relabel. self changed: #volumeList. self pattern: pattern! ! !FileList methodsFor: 'accessing' stamp: 'hfm 11/29/2008 18:30'! fileList "Answer the list of files in the current volume." ^ list! ! !FileList methodsFor: 'accessing' stamp: 'hfm 11/29/2008 18:31'! fileListIndex "Answer the index of the currently selected file." ^ listIndex! ! !FileList methodsFor: 'accessing' stamp: 'hfm 11/29/2008 18:32'! fileListIndex: anInteger "Select the file name having the given index, and display its contents." | item name | self okToChange ifFalse: [^ self]. listIndex := anInteger. listIndex = 0 ifTrue: [fileName := nil] ifFalse: [item := self fileNameFromFormattedItem: (list at: anInteger). (item endsWith: self folderString) ifTrue: ["remove [...] folder string and open the folder" name := item copyFrom: 1 to: item size - self folderString size. listIndex := 0. brevityState := #FileList. self addPath: name. name first = $^ ifTrue: [self directory: (ServerDirectory serverNamed: name allButFirst)] ifFalse: [volListIndex = 1 ifTrue: [name := name, directory slash]. self directory: (directory directoryNamed: name)]] ifFalse: [fileName := item]]. "open the file selected" brevityState := #needToGetBrief. self changed: #fileListIndex. self changed: #contents. self updateButtonRow! ! !FileList methodsFor: 'accessing' stamp: 'hfm 11/29/2008 18:48'! fileName ^ fileName! ! !FileList methodsFor: 'accessing' stamp: 'hfm 11/29/2008 18:22'! pattern ^ pattern ifNil: ['*'] ! ! !FileList methodsFor: 'accessing' stamp: 'hfm 11/29/2008 18:22'! pattern: textOrStringOrNil textOrStringOrNil ifNil: [pattern := '*'] ifNotNil: [pattern := textOrStringOrNil asString]. self updateFileList. ^ true ! ! !FileList methodsFor: 'as yet unclassified' stamp: 'BG 2/29/2004 23:40'! specsForImageViewer ^{self serviceSortByName. self serviceSortByDate. self serviceSortBySize }! ! !FileList methodsFor: 'drag''n''drop' stamp: 'hfm 11/29/2008 19:22'! acceptDroppingMorph: aTransferMorph event: evt inMorph: dest | oldName oldEntry destDirectory newName newEntry baseName response | destDirectory := self dropDestinationDirectory: dest event: evt. oldName := aTransferMorph passenger. baseName := FileDirectory localNameFor: oldName. newName := destDirectory fullNameFor: baseName. newName = oldName ifTrue: [ "Transcript nextPutAll: 'same as old name'; cr." ^ true ]. oldEntry := FileDirectory directoryEntryFor: oldName. newEntry := FileDirectory directoryEntryFor: newName. newEntry ifNotNil: [ | msg | msg := String streamContents: [ :s | s nextPutAll: 'destination file '; nextPutAll: newName; nextPutAll: ' exists already,'; cr; nextPutAll: 'and is '; nextPutAll: (oldEntry modificationTime < newEntry modificationTime ifTrue: [ 'newer' ] ifFalse: [ 'not newer' ]); nextPutAll: ' than source file '; nextPutAll: oldName; nextPut: $.; cr; nextPutAll: 'Overwrite file '; nextPutAll: newName; nextPut: $? ]. response := self confirm: msg. response ifFalse: [ ^false ]. ]. aTransferMorph shouldCopy ifTrue: [ self primitiveCopyFileNamed: oldName to: newName ] ifFalse: [ directory rename: oldName toBe: newName ]. self updateFileList; fileListIndex: 0. aTransferMorph source model ~= self ifTrue: [ aTransferMorph source model updateFileList; fileListIndex: 0 ]. "Transcript nextPutAll: 'copied'; cr." ^true! ! !FileList methodsFor: 'drag''n''drop' stamp: 'hfm 11/29/2008 19:20'! dragPassengerFor: item inMorph: dragSource ^self directory fullNameFor: ((self fileNameFromFormattedItem: item contents copy) copyReplaceAll: self folderString with: ''). ! ! !FileList methodsFor: 'drag''n''drop' stamp: 'hfm 11/29/2008 19:21'! dragTransferTypeForMorph: aMorph ^#file! ! !FileList methodsFor: 'drag''n''drop' stamp: 'nk 6/15/2003 13:07'! dropDestinationDirectory: dest event: evt "Answer a FileDirectory representing the drop destination in the directory hierarchy morph dest" ^ (dest itemFromPoint: evt position) withoutListWrapper! ! !FileList methodsFor: 'drag''n''drop' stamp: 'nk 6/15/2003 22:00'! isDirectoryList: aMorph ^aMorph isKindOf: SimpleHierarchicalListMorph! ! !FileList methodsFor: 'drag''n''drop' stamp: 'hfm 11/29/2008 19:27'! primitiveCopyFileNamed: srcName to: dstName "Copied from VMMaker code. This really ought to be a facility in file system. The major annoyance here is that file types and permissions are not handled by current Squeak code. NOTE that this will clobber the destination file!!" | buffer src dst | "primitiveExternalCall" "If the plugin doesn't do it, go the slow way and lose the filetype info" "This method may signal FileDoesNotExistException if either the source or dest files cannnot be opened; possibly permissions or bad name problems" [[src := FileStream readOnlyFileNamed: srcName] on: FileDoesNotExistException do: [^ self error: ('could not open file ', srcName)]. [dst := FileStream forceNewFileNamed: dstName] on: FileDoesNotExistException do: [^ self error: ('could not open file ', dstName)]. buffer := String new: 50000. [src atEnd] whileFalse: [dst nextPutAll: (src nextInto: buffer)]] ensure: [src ifNotNil: [src close]. dst ifNotNil: [dst close]]! ! !FileList methodsFor: 'drag''n''drop' stamp: 'hfm 11/29/2008 19:35'! wantsDroppedMorph: aTransferMorph event: evt inMorph: dest | retval | retval := (aTransferMorph isKindOf: TransferMorph) and: [ aTransferMorph dragTransferType == #file ] and: [ self isDirectoryList: dest ]. "retval ifFalse: [ Transcript nextPutAll: 'drop not wanted'; cr ]." ^retval! ! !FileList methodsFor: 'file list' stamp: 'hfm 11/29/2008 18:47'! readOnlyStream "Answer a read-only stream on the selected file. For the various stream-reading services." ^self directory ifNotNil: [ :dir | dir readOnlyFileNamed: self fileName ]! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 19:24'! fileContentsMenu: aMenu shifted: shifted "Construct aMenu to have items appropriate for the file browser's code pane, given the shift state provided" | shiftMenu services maybeLine extraLines | shifted ifTrue: [shiftMenu := ParagraphEditor shiftedYellowButtonMenu. ^ aMenu addAllFrom: shiftMenu]. fileName ifNotNil: [services := OrderedCollection new. (#(briefHex briefFile needToGetBriefHex needToGetBrief) includes: brevityState) ifTrue: [services add: self serviceGet]. (#(fullHex briefHex needToGetFullHex needToGetBriefHex) includes: brevityState) ifFalse: [services add: self serviceGetHex]. (#(needToGetShiftJIS needToGetEUCJP needToGetCNGB needToGetEUCKR needToGetUTF8) includes: brevityState) ifFalse: [services add: self serviceGetEncodedText]. maybeLine := services size. (FileStream sourceFileSuffixes includes: self suffixOfSelectedFile) ifTrue: [services addAll: (self servicesFromSelectorSpecs: #(fileIntoNewChangeSet: fileIn: browseChangesFile: browseFile:))]. extraLines := OrderedCollection new. maybeLine > 0 ifTrue: [extraLines add: maybeLine]. services size > maybeLine ifTrue: [extraLines add: services size]. aMenu addServices: services for: self fullName extraLines: extraLines]. aMenu addList: { {'find...(f)' translated. #find}. {'find again (g)' translated. #findAgain}. {'set search string (h)' translated. #setSearchString}. #-. {'do again (j)' translated. #again}. {'undo (z)' translated. #undo}. #-. {'copy (c)' translated. #copySelection}. {'cut (x)' translated. #cut}. {'paste (v)' translated. #paste}. {'paste...' translated. #pasteRecent}. #-. {'do it (d)' translated. #doIt}. {'print it (p)' translated. #printIt}. {'inspect it (i)' translated. #inspectIt}. {'fileIn selection (G)' translated. #fileItIn}. #-. {'accept (s)' translated. #accept}. {'cancel (l)' translated. #cancel}. #-. {'more...' translated. #shiftedYellowButtonActivity}}. ^ aMenu ! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 18:41'! fileListMenu: aMenu fileName ifNil: [^ self noFileSelectedMenu: aMenu] ifNotNil: [^ self fileSelectedMenu: aMenu]. ! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 18:41'! fileSelectedMenu: aMenu | firstItems secondItems thirdItems n1 n2 n3 services | firstItems := self itemsForFile: self fullName. secondItems := self itemsForAnyFile. thirdItems := self itemsForNoFile. n1 := firstItems size. n2 := n1 + secondItems size. n3 := n2 + thirdItems size. services := firstItems, secondItems, thirdItems, self serviceAllFileOptions. services do: [ :svc | svc addDependent: self ]. ^ aMenu addServices2: services for: self extraLines: (Array with: n1 with: n2 with: n3) ! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 18:46'! fullFileListMenu: aMenu shifted: aBoolean "Fill the menu with all possible items for the file list pane, regardless of selection. " | lastProvider | aMenu title: 'all possible file operations' translated. aMenu addStayUpItemSpecial. lastProvider := nil. (self itemsForFile: 'a.*') do: [:svc | (lastProvider notNil and: [svc provider ~~ lastProvider]) ifTrue: [aMenu addLine]. svc addServiceFor: self toMenu: aMenu. aMenu submorphs last setBalloonText: svc description. lastProvider := svc provider. svc addDependent: self]. ^ aMenu! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 18:42'! itemsForAnyFile "Answer a list of universal services that could apply to any file" | services | services := OrderedCollection new: 4. services add: self serviceCopyName. services add: self serviceRenameFile. services add: self serviceDeleteFile. services add: self serviceViewContentsInWorkspace. ^ services! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 18:57'! itemsForDirectory: dir | services | services := OrderedCollection new. dir ifNotNil: [ services addAll: (self class itemsForDirectory: dir). services last useLineAfter: true. ]. services add: self serviceAddNewFile. services add: self serviceAddNewDirectory. ^ services! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 18:34'! itemsForFile: fullName "Answer a list of services appropriate for a file of the given full name" | suffix | suffix := self class suffixOf: fullName. ^ (self class itemsForFile: fullName) , (self myServicesForFile: fullName suffix: suffix)! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 18:43'! itemsForNoFile | services | services := OrderedCollection new. services add: self serviceSortByName. services add: self serviceSortBySize. services add: (self serviceSortByDate useLineAfter: true). services addAll: (self itemsForDirectory: (self isFileSelected ifFalse: [ self directory ] ifTrue: [])). ^ services ! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 19:26'! myServicesForFile: fullName suffix: suffix ^(FileStream isSourceFileSuffix: suffix) ifTrue: [ {self serviceBroadcastUpdate} ] ifFalse: [ #() ]! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 19:26'! noFileSelectedMenu: aMenu ^ aMenu addServices: self itemsForNoFile for: self extraLines: #() ! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 18:46'! offerAllFileOptions "Put up a menu offering all possible file options, whatever the suffix of the current selection may be. Specially useful if you're wanting to keep the menu up" self offerMenuFrom: #fullFileListMenu:shifted: shifted: true! ! !FileList methodsFor: 'file list menu' stamp: 'hfm 11/29/2008 19:33'! suffixOfSelectedFile "Answer the file extension of the receiver's selected file" ^ self class suffixOf: self fullName.! ! !FileList methodsFor: 'file menu action' stamp: 'DamienCassou 9/29/2009 12:57'! addNew: aString byEvaluating: aBlock "A parameterization of earlier versions of #addNewDirectory and #addNewFile. Fixes the bug in each that pushing the cancel button in the FillInTheBlank dialog gave a walkback." | response newName index ending | self okToChange ifFalse: [^ self]. (response := UIManager default request: ('New {1} Name?' translated format: {aString translated}) initialAnswer: ('{1}Name' translated format: {aString translated})) isEmptyOrNil ifTrue: [^ self]. newName := response asFileName. Cursor wait showWhile: [ aBlock value: newName]. self updateFileList. index := list indexOf: newName. index = 0 ifTrue: [ending := ') ',newName. index := list findFirst: [:line | line endsWith: ending]]. self fileListIndex: index. ! ! !FileList methodsFor: 'file menu action' stamp: 'hfm 11/29/2008 19:07'! addNewFile self addNew: 'File' byEvaluating: [:newName | (directory newFileNamed: newName) close] ! ! !FileList methodsFor: 'file menu action' stamp: 'hfm 11/29/2008 19:16'! compressFile "Compress the currently selected file" | f | f := StandardFileStream readOnlyFileNamed: (directory fullNameFor: self fullName). f compressFile. self updateFileList! ! !FileList methodsFor: 'file menu action' stamp: 'hfm 11/29/2008 19:10'! deleteFile "Delete the currently selected file" listIndex = 0 ifTrue: [^ self]. (self confirm: ('Really delete {1}?' translated format:{fileName})) ifFalse: [^ self]. directory deleteFileNamed: fileName. self updateFileList. brevityState := #FileList. self get! ! !FileList methodsFor: 'file menu action' stamp: 'hfm 11/29/2008 19:11'! get "Get contents of file again, it may have changed. Do this by making the cancel string be the contents, and doing a cancel." Cursor read showWhile: [ self okToChange ifFalse: [^ nil]. brevityState == #briefHex ifTrue: [brevityState := #needToGetFullHex] ifFalse: [brevityState := #needToGetFull]. self changed: #contents]. ! ! !FileList methodsFor: 'file menu action' stamp: 'hfm 11/29/2008 19:24'! getEncodedText Cursor read showWhile: [ self selectEncoding. self changed: #contents]. ! ! !FileList methodsFor: 'file menu action' stamp: 'hfm 11/29/2008 19:24'! getHex "Get contents of file again, and display in Hex. Do this by making the cancel string be the contents, and doing a cancel." Cursor read showWhile: [ brevityState := #needToGetBriefHex. self changed: #contents]. ! ! !FileList methodsFor: 'file menu action' stamp: 'DamienCassou 9/29/2009 12:57'! renameFile "Rename the currently selected file" | newName response | listIndex = 0 ifTrue: [^ self]. self okToChange ifFalse: [^ self]. (response := UIManager default request: 'NewFileName?' translated initialAnswer: fileName) isEmptyOrNil ifTrue: [^ self]. newName := response asFileName. newName = fileName ifTrue: [^ self]. directory rename: fileName toBe: newName. self updateFileList. listIndex := list findFirst: [:item | (self fileNameFromFormattedItem: item) = newName]. listIndex > 0 ifTrue: [fileName := newName]. self changed: #fileListIndex. ! ! !FileList methodsFor: 'file menu action' stamp: 'hfm 11/29/2008 18:51'! sortByDate self resort: #date! ! !FileList methodsFor: 'file menu action' stamp: 'hfm 11/29/2008 18:49'! sortByName self resort: #name! ! !FileList methodsFor: 'file menu action' stamp: 'hfm 11/29/2008 18:50'! sortBySize self resort: #size! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 18:33'! buttonSelectorsToSuppress "Answer a list of action selectors whose corresponding services we would prefer *not* to have appear in the filelist's button pane; this can be hand-jimmied to suit personal taste." ^ #(removeLineFeeds: addFileToNewZip: compressFile: putUpdate:)! ! !FileList methodsFor: 'initialization' stamp: 'RAA 8/17/2000 13:22'! directoryChangeBlock: aBlockOrNil directoryChangeBlock := aBlockOrNil.! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 18:31'! dynamicButtonServices "Answer services for buttons that may come and go in the button pane, depending on selection" ^ fileName isEmptyOrNil ifTrue: [#()] ifFalse: [ | toReject | toReject := self buttonSelectorsToSuppress. (self itemsForFile: self fullName) reject: [:svc | toReject includes: svc selector]]! ! !FileList methodsFor: 'initialization' stamp: 'RAA 6/16/2000 13:08'! fileSelectionBlock: aBlock fileSelectionBlock := aBlock! ! !FileList methodsFor: 'initialization' stamp: 'ar 2/12/2001 16:12'! initialDirectoryList | dir nameToShow dirList | dirList := (FileDirectory on: '') directoryNames collect: [ :each | FileDirectoryWrapper with: (FileDirectory on: each) name: each model: self]. dirList isEmpty ifTrue:[ dirList := Array with: (FileDirectoryWrapper with: FileDirectory default name: FileDirectory default localName model: self)]. dirList := dirList,( ServerDirectory serverNames collect: [ :n | dir := ServerDirectory serverNamed: n. nameToShow := n. (dir directoryWrapperClass with: dir name: nameToShow model: self) balloonText: dir realUrl ] ). ^dirList! ! !FileList methodsFor: 'initialization' stamp: 'RAA 6/16/2000 10:40'! labelString ^ (directory ifNil: [^'[]']) pathName contractTo: 50! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 19:25'! modelSleep "User has exited or collapsed the window -- close any remote connection." directory ifNotNil: [directory sleep]! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 19:26'! modelWakeUp "User has entered or expanded the window -- reopen any remote connection." (directory notNil and:[directory isRemoteDirectory]) ifTrue: [[directory wakeUp] on: TelnetProtocolError do: [ :ex | self inform: ex printString ]] "It would be good to implement a null method wakeUp on the root of directory"! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 18:29'! optionalButtonRow "Answer the button row associated with a file list" | aRow | aRow := AlignmentMorph newRow beSticky. aRow color: Color transparent. aRow clipSubmorphs: true. aRow layoutInset: 5@1; cellInset: 6. self universalButtonServices do: "just the three sort-by items" [:service | aRow addMorphBack: (service buttonToTriggerIn: self). (service selector == #sortBySize) ifTrue: [aRow addTransparentSpacerOfSize: (4@0)]]. aRow setNameTo: 'buttons'. aRow setProperty: #buttonRow toValue: true. "Used for dynamic retrieval later on" ^ aRow! ! !FileList methodsFor: 'initialization' stamp: 'hfm 12/12/2008 13:30'! optionalButtonSpecs "Answer a list of services underlying the optional buttons in their initial inception." ^ optionalButtonSpecs ifNil: [ { self serviceSortByName . self serviceSortByDate . self serviceSortBySize } ] ! ! !FileList methodsFor: 'initialization' stamp: 'RAA 6/16/2000 13:01'! optionalButtonSpecs: anArray optionalButtonSpecs := anArray! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 19:31'! release self modelSleep! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 18:30'! serviceSortByDate "Answer a service for sorting by date" ^ (SimpleServiceEntry new provider: self label: 'by date' selector: #sortByDate description: 'sort entries by date') extraSelector: #sortingByDate; buttonLabel: 'date'! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 18:30'! serviceSortByName "Answer a service for soring by name" ^ (SimpleServiceEntry new provider: self label: 'by name' selector: #sortByName description: 'sort entries by name') extraSelector: #sortingByName; buttonLabel: 'name'! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 18:30'! serviceSortBySize "Answer a service for sorting by size" ^ (SimpleServiceEntry provider: self label: 'by size' selector: #sortBySize description: 'sort entries by size') extraSelector: #sortingBySize; buttonLabel: 'size'! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 19:33'! setFileStream: aStream "Used to initialize a spawned file editor. Sets directory too." self directory: aStream directory. fileName := aStream localName. pattern := '*'. listIndex := 1. "pretend a file is selected" aStream close. brevityState := #needToGetBrief. self changed: #contents. ! ! !FileList methodsFor: 'initialization' stamp: 'sw 2/22/2002 02:34'! universalButtonServices "Answer the services to be reflected in the receiver's buttons" ^ self optionalButtonSpecs! ! !FileList methodsFor: 'initialization' stamp: 'hfm 11/29/2008 18:28'! updateButtonRow "Dynamically update the contents of the button row, if any." | aWindow aRow | aWindow := self dependents detect: [:m | (m isSystemWindow) and: [m model == self]] ifNone: [^self]. aRow := aWindow findDeepSubmorphThat: [:m | m hasProperty: #buttonRow] ifAbsent: [^self]. aRow submorphs size - 4 timesRepeat: [aRow submorphs last delete]. self dynamicButtonServices do: [:service | aRow addMorphBack: (service buttonToTriggerIn: self). service addDependent: self]! ! !FileList methodsFor: 'initialization' stamp: 'nk 6/14/2004 09:39'! updateDirectory "directory has been changed externally, by calling directory:. Now change the view to reflect the change." self changed: #currentDirectorySelected. self postOpen.! ! !FileList methodsFor: 'initialize-release' stamp: 'alain.plantec 5/28/2009 09:53'! initialize super initialize. fileSelectionBlock := [ :entry :myPattern | entry isDirectory ifTrue: [ false ] ifFalse: [ myPattern = '*' or: [myPattern match: entry name] ] ]. dirSelectionBlock := [ :dirName | true].! ! !FileList methodsFor: 'menu messages' stamp: 'hfm 11/29/2008 19:22'! copyName listIndex = 0 ifTrue: [^ self]. Clipboard clipboardText: self fullName asText. ! ! !FileList methodsFor: 'menu messages' stamp: 'hfm 11/29/2008 19:27'! perform: selector orSendTo: otherTarget "Selector was just chosen from a menu by a user. If it's one of the three sort-by items, handle it specially. If I can respond myself, then perform it on myself. If not, send it to otherTarget, presumably the editPane from which the menu was invoked." ^ (#(sortByDate sortBySize sortByName) includes: selector) ifTrue: [self resort: selector] ifFalse: [(#(get getHex copyName openImageInWindow importImage renameFile deleteFile addNewFile) includes: selector) ifTrue: [self perform: selector] ifFalse: [super perform: selector orSendTo: otherTarget]]! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:59'! addNewDirectory self addNew: 'Directory' byEvaluating: [:newName | directory createDirectory: newName] ! ! !FileList methodsFor: 'own services' stamp: 'nk 6/14/2004 09:42'! deleteDirectory super deleteDirectory. self updateDirectory.! ! !FileList methodsFor: 'own services' stamp: 'sd 5/11/2003 22:15'! importImage "Import the given image file and store the resulting Form in the default Imports" | fname image | fname := fileName sansPeriodSuffix. image := Form fromFileNamed: self fullName. Imports default importImage: image named: fname. ! ! !FileList methodsFor: 'own services' stamp: 'sw 2/22/2002 02:35'! okayAndCancelServices "Answer ok and cancel services" ^ {self serviceOkay. self serviceCancel}! ! !FileList methodsFor: 'own services' stamp: 'alain.plantec 5/30/2008 13:12'! openImageInWindow "Handle five file formats: GIF, JPG, PNG, Form stoteOn: (run coded), and BMP. Fail if file format is not recognized." | image myStream | myStream := (directory readOnlyFileNamed: fileName) binary. image := Form fromBinaryStream: myStream. myStream close. (World drawingClass withForm: image) openInWorld! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:45'! serviceAddNewDirectory "Answer a service entry characterizing the 'add new directory' command" ^ SimpleServiceEntry provider: self label: 'add new directory' selector: #addNewDirectory description: 'adds a new, empty directory (folder)' ! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:45'! serviceAddNewFile "Answer a service entry characterizing the 'add new file' command" ^ SimpleServiceEntry provider: self label: 'add new file' selector: #addNewFile description: 'create a new,. empty file, and add it to the current directory.'! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:45'! serviceAllFileOptions ^ {SimpleServiceEntry provider: self label: 'more...' selector: #offerAllFileOptions description: 'show all the options available'}! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:48'! serviceBroadcastUpdate "Answer a service for broadcasting a file as an update" ^ SimpleServiceEntry provider: self label: 'broadcast as update' selector: #putUpdate: description: 'broadcast file as update' buttonLabel: 'broadcast'! ! !FileList methodsFor: 'own services' stamp: 'nk 6/8/2004 17:09'! serviceCancel "Answer a service for hitting the cancel button" ^ (SimpleServiceEntry new provider: self label: 'cancel' selector: #cancelHit description: 'hit here to cancel ') buttonLabel: 'cancel'! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 19:32'! serviceCompressFile "Answer a service for compressing a file" ^ SimpleServiceEntry provider: self label: 'compress' selector: #compressFile description: 'compress file' buttonLabel: 'compress'! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:42'! serviceCopyName ^ (SimpleServiceEntry provider: self label: 'copy name to clipboard' selector: #copyName description:'copy name to clipboard' )! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:43'! serviceDeleteFile ^ (SimpleServiceEntry provider: self label: 'delete' selector: #deleteFile) description: 'delete the seleted item'! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 19:32'! serviceGet "Answer a service for getting the entire file" ^ (SimpleServiceEntry provider: self label: 'get entire file' selector: #get description: 'if the file has only been partially read in, because it is very large, read the entire file in at this time.')! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 19:32'! serviceGetEncodedText ^ (SimpleServiceEntry provider: self label: 'view as encoded text' selector: #getEncodedText description: 'view as encoded text') ! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 19:32'! serviceGetHex ^ (SimpleServiceEntry provider: self label: 'view as hex' selector: #getHex description: 'view as hex') ! ! !FileList methodsFor: 'own services' stamp: 'nk 6/8/2004 17:09'! serviceOkay "Answer a service for hitting the okay button" ^ (SimpleServiceEntry new provider: self label: 'okay' selector: #okHit description: 'hit here to accept the current selection') buttonLabel: 'ok'! ! !FileList methodsFor: 'own services' stamp: 'sw 2/22/2002 02:07'! serviceOpenProjectFromFile "Answer a service for opening a .pr project file" ^ SimpleServiceEntry provider: self label: 'load as project' selector: #openProjectFromFile description: 'open project from file' buttonLabel: 'load'! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:42'! serviceRenameFile ^ (SimpleServiceEntry provider: self label: 'rename' selector: #renameFile description: 'rename file')! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:43'! serviceViewContentsInWorkspace "Answer a service for viewing the contents of a file in a workspace" ^ (SimpleServiceEntry provider: self label: 'workspace with contents' selector: #viewContentsInWorkspace) description: 'open a new Workspace whose contents are set to the contents of this file'! ! !FileList methodsFor: 'own services' stamp: 'sw 2/22/2002 02:36'! servicesForFolderSelector "Answer the ok and cancel servies for the folder selector" ^ self okayAndCancelServices! ! !FileList methodsFor: 'own services' stamp: 'sw 2/22/2002 02:36'! servicesForProjectLoader "Answer the services to show in the button pane for the project loader" ^ {self serviceSortByName. self serviceSortByDate. self serviceSortBySize. self serviceOpenProjectFromFile}! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 20:13'! servicesFromSelectorSpecs: symbolArray "Answer an array of services represented by the incoming symbols, eliminating any that do not have a currently-registered service. Pass the symbol #- along unchanged to serve as a separator between services" "FileList new servicesFromSelectorSpecs: #(fileIn: fileIntoNewChangeSet: browseChangesFile:)" | res services col | col := OrderedCollection new. services := self class allRegisteredServices, (self myServicesForFile: #dummy suffix: '*'). symbolArray do: [:sel | sel == #- ifTrue: [col add: sel] ifFalse: [res := services detect: [:each | each selector = sel] ifNone: [nil]. res notNil ifTrue: [col add: res]]]. ^ col! ! !FileList methodsFor: 'own services' stamp: 'hfm 11/29/2008 18:51'! viewContentsInWorkspace "View the contents of my selected file in a new workspace" | aString aFileStream aName | aString := (aFileStream := directory readOnlyFileNamed: self fullName) setConverterForCode contentsOfEntireFile. aName := aFileStream localName. aFileStream close. UIManager default edit: aString label: 'Workspace from ', aName! ! !FileList methodsFor: 'server list' stamp: 'stephane.ducasse 7/3/2009 21:38'! askServerInfo "Get the user to create a ServerDirectory for a new server. Fill in and say Accept." | template | template := '"Please fill in the following info, then select all text and choose DoIt." | aa | self flag: #ViolateNonReferenceToOtherClasses. aa := ServerDirectory new. aa server: ''st.cs.uiuc.edu''. "host" aa user: ''anonymous''. aa password: ''yourEmail@school.edu''. aa directory: ''/Smalltalk/Squeak/Goodies''. aa url: ''''. "<- this is optional. Only used when *writing* update files." ServerDirectory addServer: aa named: ''UIUCArchive''. "<- known by this name in Squeak"'. (StringHolder new contents: template) openLabel: 'FTP Server Form' ! ! !FileList methodsFor: 'server list' stamp: 'alain.plantec 2/6/2009 16:54'! putUpdate: fullFileName "Put this file out as an Update on the servers." | names choice | self canDiscardEdits ifFalse: [^ self changed: #flash]. names := ServerDirectory groupNames asSortedArray. choice := UIManager default chooseFrom: names values: names. choice ifNil: [^ self]. (ServerDirectory serverInGroupNamed: choice) putUpdate: (directory oldFileNamed: fullFileName). self volumeListIndex: volListIndex. ! ! !FileList methodsFor: 'server list' stamp: 'alain.plantec 2/6/2009 16:55'! removeServer | choice names | self flag: #ViolateNonReferenceToOtherClasses. names := ServerDirectory serverNames asSortedArray. choice := UIManager default chooseFrom: names values: names. choice ifNil: [^ self]. ServerDirectory removeServerNamed: choice! ! !FileList methodsFor: 'updating' stamp: 'hfm 11/29/2008 19:33'! update: aParameter "Receive a change notice from an object of whom the receiver is a dependent" (aParameter == #fileListChanged) ifTrue: [self updateFileList]. super update: aParameter! ! !FileList methodsFor: 'user interface' stamp: 'stephane.ducasse 4/13/2009 21:06'! blueButtonForService: aService textColor: textColor inWindow: window | block result | block := [self fullName isNil ifTrue: [self inform: 'Please select a file' translated] ifFalse: [aService performServiceFor: self]]. result := window fancyText: aService buttonLabel capitalized translated font: Preferences standardEToysFont color: textColor. result setProperty: #buttonText toValue: aService buttonLabel capitalized; hResizing: #rigid; extent: 100 @ 20; layoutInset: 4; borderWidth: ColorTheme current dialogButtonBorderWidth; useRoundedCorners; setBalloonText: aService label. result on: #mouseUp send: #value to: block. ^ result! ! !FileList methodsFor: 'user interface' stamp: 'RAA 2/17/2001 12:18'! morphicDirectoryTreePane ^self morphicDirectoryTreePaneFiltered: #initialDirectoryList ! ! !FileList methodsFor: 'user interface' stamp: 'rww 12/13/2003 13:07'! morphicDirectoryTreePaneFiltered: aSymbol ^(SimpleHierarchicalListMorph on: self list: aSymbol selected: #currentDirectorySelected changeSelected: #setSelectedDirectoryTo: menu: #volumeMenu: keystroke: nil) autoDeselect: false; enableDrag: false; enableDrop: true; yourself ! ! !FileList methodsFor: 'user interface' stamp: 'RAA 6/16/2000 10:53'! morphicFileContentsPane ^PluggableTextMorph on: self text: #contents accept: #put: readSelection: #contentsSelection menu: #fileContentsMenu:shifted: ! ! !FileList methodsFor: 'user interface' stamp: 'nk 6/15/2003 13:05'! morphicFileListPane ^(PluggableListMorph on: self list: #fileList selected: #fileListIndex changeSelected: #fileListIndex: menu: #fileListMenu:) enableDrag: true; enableDrop: false; yourself ! ! !FileList methodsFor: 'volume list and pattern' stamp: 'nk 6/14/2004 09:45'! changeDirectoryTo: aFileDirectory "Change directory as requested." self directory: aFileDirectory. self updateDirectory! ! !FileList methodsFor: 'volume list and pattern' stamp: 'hfm 11/29/2008 18:27'! fileNameFormattedFrom: entry sizePad: sizePad "entry is a 5-element array of the form: (name creationTime modificationTime dirFlag fileSize)" | sizeStr nameStr dateStr | nameStr := (entry at: 4) ifTrue: [entry first , self folderString] ifFalse: [entry first]. dateStr := ((Date fromSeconds: (entry at: 3) ) printFormat: #(3 2 1 $. 1 1 2)) , ' ' , (String streamContents: [:s | (Time fromSeconds: (entry at: 3) \\ 86400) print24: true on: s]). sizeStr := (entry at: 5) asStringWithCommas. sortMode = #name ifTrue: [^ nameStr , ' (' , dateStr , ' ' , sizeStr , ')']. sortMode = #date ifTrue: [^ '(' , dateStr , ' ' , sizeStr , ') ' , nameStr]. sortMode = #size ifTrue: [^ '(' , ((sizeStr size to: sizePad) collect: [:i | $ ]) , sizeStr , ' ' , dateStr , ') ' , nameStr]. ! ! !FileList methodsFor: 'volume list and pattern' stamp: 'hfm 11/29/2008 18:25'! listForPatterns: anArray "Make the list be those file names which match the pattern." | sizePad newList | newList := Set new. anArray do: [ :pat | newList addAll: (self entriesMatching: pat) ]. newList := (SortedCollection sortBlock: self sortBlock) addAll: newList; yourself. sizePad := (newList inject: 0 into: [:mx :entry | mx max: (entry at: 5)]) asStringWithCommas size - 1. newList := newList collect: [ :e | self fileNameFormattedFrom: e sizePad: sizePad ]. volList size = 1 ifTrue: ["Include known servers along with other desktop volumes" ^ newList asArray , (ServerDirectory serverNames collect: [:n | '^' , n , self folderString])]. ^ newList asArray! ! !FileList methodsFor: 'volume list and pattern' stamp: 'hfm 11/29/2008 19:34'! veryDeepFixupWith: deepCopier super veryDeepFixupWith: deepCopier. volListIndex := 1. self directory: FileDirectory default. self updateFileList! ! !FileList methodsFor: 'volume list and pattern' stamp: 'hfm 11/29/2008 19:34'! volumeList "Answer the current list of volumes." ^ volList ! ! !FileList methodsFor: 'volume list and pattern' stamp: 'hfm 11/29/2008 19:34'! volumeListIndex "Answer the index of the currently selected volume." ^ volListIndex ! ! !FileList methodsFor: 'volume list and pattern' stamp: 'hfm 11/29/2008 19:34'! volumeListIndex: index "Select the volume name having the given index." | delim path | volListIndex := index. index = 1 ifTrue: [self directory: (FileDirectory on: '')] ifFalse: [delim := directory pathNameDelimiter. path := String streamContents: [:strm | 2 to: index do: [:i | strm nextPutAll: (volList at: i) withBlanksTrimmed. i < index ifTrue: [strm nextPut: delim]]]. self directory: (directory on: path)]. brevityState := #FileList. self addPath: path. self changed: #fileList. self changed: #contents. self updateButtonRow! ! !FileList methodsFor: 'volume menu' stamp: 'hfm 11/29/2008 18:57'! volumeMenu: aMenu aMenu addList: { {'recent...' translated. #recentDirs}. #-. {'add server...' translated. #askServerInfo}. {'remove server...' translated. #removeServer}. #-. {'delete directory...' translated. #deleteDirectory}. #-}. aMenu addServices: (self itemsForDirectory: self directory) for: self extraLines: #(). ^aMenu.! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 19:01'! addPath: aString "Add the given string to the list of recently visited directories." | full | aString ifNil: [^self]. full := String streamContents: [ :strm | 2 to: volList size do: [ :i | strm nextPutAll: (volList at: i) withBlanksTrimmed. strm nextPut: FileDirectory pathNameDelimiter]]. full := full, aString. "Remove and super-directories of aString from the collection." RecentDirs removeAllSuchThat: [ :aDir | ((aDir, '*') match: full)]. "If a sub-directory is in the list, do nothing." (RecentDirs detect: [ :aDir | ((full, '*') match: aDir)] ifNone: [nil]) ifNotNil: [^self]. [RecentDirs size >= 10] whileTrue: [RecentDirs removeFirst]. RecentDirs addLast: full! ! !FileList methodsFor: 'private' stamp: 'RAA 4/6/2001 12:45'! cancelHit modalView delete. directory := fileName := currentDirectorySelected := nil.! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 19:17'! contents "Answer the contents of the file, reading it first if needed." "Possible brevityState values: FileList, fullFile, briefFile, needToGetFull, needToGetBrief, fullHex, briefHex, needToGetFullHex, needToGetBriefHex" (listIndex = 0) | (brevityState == #FileList) ifTrue: [^ self defaultContents]. "no file selected" brevityState == #fullFile ifTrue: [^ contents]. brevityState == #fullHex ifTrue: [^ contents]. brevityState == #briefFile ifTrue: [^ contents]. brevityState == #briefHex ifTrue: [^ contents]. brevityState == #needToGetFullHex ifTrue: [^ self readContentsHex: false]. brevityState == #needToGetBriefHex ifTrue: [^ self readContentsHex: true]. brevityState == #needToGetFull ifTrue: [^ self readContentsBrief: false]. brevityState == #needToGetBrief ifTrue: [^ self readContentsBrief: true]. "default" (TextConverter allEncodingNames includes: brevityState) ifTrue: [ ^self readContentsAsEncoding: brevityState]. self halt: 'unknown state ' , brevityState printString! ! !FileList methodsFor: 'private' stamp: 'LC 1/6/2002 06:50'! currentDirectorySelected ^ currentDirectorySelected ! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 19:23'! defaultContents contents := list == nil ifTrue: [String new] ifFalse: [String streamContents: [:s | s nextPutAll: 'NO FILE SELECTED' translated; cr. s nextPutAll: ' -- Folder Summary --' translated; cr. list do: [:item | s nextPutAll: item; cr]]]. brevityState := #FileList. ^ contents! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 19:18'! defaultEncoderFor: aFileName "This method just illustrates the stupidest possible implementation of encoder selection." | l | l := aFileName asLowercase. " ((l endsWith: FileStream multiCs) or: [ l endsWith: FileStream multiSt]) ifTrue: [ ^ UTF8TextConverter new. ]. " ((l endsWith: FileStream cs) or: [ l endsWith: FileStream st]) ifTrue: [ ^ MacRomanTextConverter new. ]. ^ Latin1TextConverter new. ! ! !FileList methodsFor: 'private' stamp: 'ar 2/12/2001 16:20'! directoryNamesFor: item "item may be file directory or server directory" | entries | entries := item directoryNames. dirSelectionBlock ifNotNil:[entries := entries select: dirSelectionBlock]. ^entries! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:26'! entriesMatching: patternString "Answer a list of directory entries which match the patternString. The patternString may consist of multiple patterns separated by ';'. Each pattern can include a '*' or '#' as wildcards - see String>>match:" | entries patterns | entries := directory entries. patterns := patternString findTokens: ';'. (patterns anySatisfy: [:each | each = '*']) ifTrue: [^ entries]. ^ entries select: [:entry | entry isDirectory or: [patterns anySatisfy: [:each | each match: entry first]]]! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:32'! fileNameFromFormattedItem: item "Extract fileName and folderString from a formatted fileList item string" | from to | self sortingByName ifTrue: [ from := item lastIndexOf: $( ifAbsent: [0]. to := item lastIndexOf: $) ifAbsent: [0]] ifFalse: [ from := item indexOf: $( ifAbsent: [0]. to := item indexOf: $) ifAbsent: [0]]. ^ (from * to = 0 ifTrue: [item] ifFalse: [item copyReplaceFrom: from to: to with: '']) withBlanksTrimmed! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:27'! folderString ^ ' [...]'! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:33'! fullName "Answer the full name for the currently selected file; answer nil if no file is selected." ^ fileName ifNotNil: [directory ifNil: [FileDirectory default fullNameFor: fileName] ifNotNil: [directory fullNameFor: fileName]] ! ! !FileList methodsFor: 'private' stamp: 'LC 1/6/2002 06:51'! getSelectedDirectory ok == true ifFalse: [^ nil]. ^ currentDirectorySelected ! ! !FileList methodsFor: 'private' stamp: 'sw 9/12/2002 00:43'! getSelectedFile "Answer a filestream on the selected file. If it cannot be opened for read/write, try read-only before giving up; answer nil if unsuccessful" ok == true ifFalse: [^ nil]. directory ifNil: [^ nil]. fileName ifNil: [^ nil]. ^ (directory oldFileNamed: fileName) ifNil: [directory readOnlyFileNamed: fileName]! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:44'! isFileSelected "return if a file is currently selected" ^ fileName notNil! ! !FileList methodsFor: 'private' stamp: 'RAA 6/21/2000 12:06'! modalView: aSystemWindowOrSuch modalView := aSystemWindowOrSuch! ! !FileList methodsFor: 'private' stamp: 'md 10/22/2003 15:27'! okHit ok := true. currentDirectorySelected ifNil: [Beeper beep] ifNotNil: [modalView delete]! ! !FileList methodsFor: 'private' stamp: 'RAA 6/16/2000 10:48'! postOpen directory ifNotNil: [ self changed: #(openPath) , directory pathParts. ]. ! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 19:27'! put: aText "Private - put the supplied text onto the file" | ff type | brevityState == #fullFile ifTrue: [ff := directory newFileNamed: self fullName. Cursor write showWhile: [ff nextPutAll: aText asString; close]. fileName = ff localName ifTrue: [contents := aText asString] ifFalse: [self updateFileList]. "user renamed the file" ^ true "accepted"]. listIndex = 0 ifTrue: [self inform: 'No fileName is selected' translated. ^ false "failed"]. type := 'These'. brevityState = #briefFile ifTrue: [type := 'Abbreviated']. brevityState = #briefHex ifTrue: [type := 'Abbreviated']. brevityState = #fullHex ifTrue: [type := 'Hexadecimal']. brevityState = #FileList ifTrue: [type := 'Directory']. self inform: ('{1} contents cannot meaningfully be saved at present.' translated format:{type translated}). ^ false "failed" ! ! !FileList methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:26'! readContentsAsEncoding: encodingName | f writeStream converter c | f := directory oldFileOrNoneNamed: self fullName. f ifNil: [^ 'For some reason, this file cannot be read']. writeStream := String new writeStream. converter := TextConverter defaultConverterClassForEncoding: encodingName. converter ifNil: [^ 'This encoding is not supported']. f converter: converter new. f wantsLineEndConversion: true. [f atEnd or: [(c := f next) isNil]] whileFalse: [writeStream nextPut: c]. f close. ^ writeStream contents! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 19:18'! readContentsBrief: brevityFlag "Read the contents of the receiver's selected file, unless it is too long, in which case show just the first 5000 characters. Don't create a file if it doesn't already exist." | f fileSize first5000 | brevityFlag ifTrue: [ directory isRemoteDirectory ifTrue: [^ self readServerBrief]]. f := directory oldFileOrNoneNamed: self fullName. f ifNil: [^ 'For some reason, this file cannot be read' translated]. f converter: (self defaultEncoderFor: self fullName). (brevityFlag not or: [(fileSize := f size) <= 100000]) ifTrue: [contents := f contentsOfEntireFile. brevityState := #fullFile. "don't change till actually read" ^ contents]. "if brevityFlag is true, don't display long files when first selected" first5000 := f next: 5000. f close. contents := 'File ''{1}'' is {2} bytes long. You may use the ''get'' command to read the entire file. Here are the first 5000 characters... ------------------------------------------ {3} ------------------------------------------ ... end of the first 5000 characters.' translated format: {fileName. fileSize. first5000}. brevityState := #briefFile. "don't change till actually read" ^ contents. ! ! !FileList methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:28'! readContentsCNGB | f stream | f := directory oldFileOrNoneNamed: self fullName. f ifNil: [^ 'For some reason, this file cannot be read']. stream := String new writeStream. f converter: CNGBTextConverter new. [f atEnd] whileFalse: [stream nextPut: f next]. f close. ^ stream contents! ! !FileList methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:28'! readContentsEUCJP | f stream | f := directory oldFileOrNoneNamed: self fullName. f ifNil: [^ 'For some reason, this file cannot be read']. stream := String new writeStream. f converter: EUCJPTextConverter new. [f atEnd] whileFalse: [stream nextPut: f next]. f close. ^ stream contents! ! !FileList methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:29'! readContentsEUCKR | f stream | f := directory oldFileOrNoneNamed: self fullName. f ifNil: [^ 'For some reason, this file cannot be read']. stream := String new writeStream. f converter: EUCKRTextConverter new. [f atEnd] whileFalse: [stream nextPut: f next]. f close. ^ stream contents! ! !FileList methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:30'! readContentsHex: brevity "retrieve the contents from the external file unless it is too long. Don't create a file here. Check if exists." | f size data hexData s | f := directory oldFileOrNoneNamed: self fullName. f == nil ifTrue: [^ 'For some reason, this file cannot be read' translated]. f binary. ((size := f size)) > 5000 & brevity ifTrue: [data := f next: 10000. f close. brevityState := #briefHex] ifFalse: [data := f contentsOfEntireFile. brevityState := #fullHex]. s := (String new: data size*4) writeStream. 0 to: data size-1 by: 16 do: [:loc | s nextPutAll: loc printStringHex; space; nextPut: $(; print: loc; nextPut: $); space; tab. loc+1 to: (loc+16 min: data size) do: [:i | s nextPutAll: (data at: i) printStringHex; space]. s cr]. hexData := s contents. ^ contents := ((size > 5000) & brevity ifTrue: ['File ''{1}'' is {2} bytes long. You may use the ''get'' command to read the entire file. Here are the first 5000 characters... ------------------------------------------ {3} ------------------------------------------ ... end of the first 5000 characters.' translated format: {fileName. size. hexData}] ifFalse: [hexData]). ! ! !FileList methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:30'! readContentsShiftJIS | f stream | f := directory oldFileOrNoneNamed: self fullName. f ifNil: [^ 'For some reason, this file cannot be read']. stream := String new writeStream. f converter: ShiftJISTextConverter new. [f atEnd] whileFalse: [stream nextPut: f next]. f close. ^ stream contents! ! !FileList methodsFor: 'private' stamp: 'PeterHugossonMiller 9/3/2009 01:31'! readContentsUTF8 | f stream | f := directory oldFileOrNoneNamed: self fullName. f ifNil: [^ 'For some reason, this file cannot be read']. stream := String new writeStream. f converter: UTF8TextConverter new. [f atEnd] whileFalse: [stream nextPut: f next]. f close. ^ stream contents! ! !FileList methodsFor: 'private' stamp: 'alain.plantec 2/6/2009 16:55'! recentDirs "Put up a menu and let the user select from the list of recently visited directories." | dirName | RecentDirs isEmpty ifTrue: [^self]. dirName := UIManager default chooseFrom: RecentDirs values: RecentDirs. dirName ifNil: [^self]. self directory: (FileDirectory on: dirName)! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:38'! registeredFileReaderClasses "return the list of classes that provide file reader services" ^ self class registeredFileReaderClasses! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:50'! resort: newMode "Re-sort the list of files." | name | listIndex > 0 ifTrue: [name := self fileNameFromFormattedItem: (list at: listIndex)]. sortMode := newMode. self pattern: pattern. name ifNotNil: [ fileName := name. listIndex := list findFirst: [:item | (self fileNameFromFormattedItem: item) = name. ]. self changed: #fileListIndex]. listIndex = 0 ifTrue: [self changed: #contents]. self updateButtonRow ! ! !FileList methodsFor: 'private' stamp: 'alain.plantec 2/8/2009 22:07'! selectEncoding | aMenu encodingItems | aMenu := CustomMenu new. encodingItems := OrderedCollection new. TextConverter allSubclasses do: [:each | | names | names := each encodingNames. names notEmpty ifTrue: [ | label | label := '' writeStream. names do: [:eachName | label nextPutAll: eachName ] separatedBy: [ label nextPutAll: ', ']. encodingItems add: {label contents. names first asSymbol}. ]. ]. aMenu addList: encodingItems. brevityState := aMenu startUp. brevityState ifNil: [brevityState := #needToGetBrief]. ! ! !FileList methodsFor: 'private' stamp: 'LC 1/6/2002 09:03'! setSelectedDirectoryTo: aFileDirectoryWrapper currentDirectorySelected := aFileDirectoryWrapper. self directory: aFileDirectoryWrapper withoutListWrapper. brevityState := #FileList. "self addPath: path." self changed: #fileList. self changed: #contents. self changed: #currentDirectorySelected.! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:26'! sortBlock "Answer block to decide what order to display the directory entries." ^ [ :x :y | (x isDirectory = y isDirectory) ifTrue: [ "sort by user-specified criterion" sortMode = #name ifTrue: [(x name compare: y name) <= 2] ifFalse: [ sortMode = #date ifTrue: [ x modificationTime = y modificationTime ifTrue: [ (x name compare: y name) <= 2 ] ifFalse: [ x modificationTime > y modificationTime ] ] ifFalse: [ "size" x fileSize = y fileSize ifTrue: [ (x name compare: y name) <= 2 ] ifFalse: [ x fileSize > y fileSize ] ] ] ] ifFalse: [ "directories always precede files" x isDirectory ] ]! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:50'! sortingByDate ^ sortMode == #date! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:33'! sortingByName ^ sortMode == #name! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 19:33'! sortingBySize ^ sortMode == #size! ! !FileList methodsFor: 'private' stamp: 'hfm 11/29/2008 18:24'! updateFileList "Update my files list with file names in the current directory that match the pattern. The pattern string may have embedded newlines or semicolons; these separate different patterns." | patterns | patterns := OrderedCollection new. Cursor wait showWhile: [ (pattern findTokens: (String with: Character cr with: Character lf with: $;)) do: [ :each | (each includes: $*) | (each includes: $#) ifTrue: [ patterns add: each] ifFalse: [each isEmpty ifTrue: [ patterns add: '*'] ifFalse: [ patterns add: '*' , each , '*']]]. list := self listForPatterns: patterns. listIndex := 0. volListIndex := volList size. fileName := nil. contents := ''. self changed: #volumeListIndex. self changed: #fileList. self updateButtonRow]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileList class instanceVariableNames: ''! !FileList class methodsFor: 'as yet unclassified' stamp: 'ar 10/10/2000 15:59'! hideSqueakletDirectoryBlock ^[:dirName| (dirName sameAs: 'Squeaklets') not]! ! !FileList class methodsFor: 'as yet unclassified' stamp: 'stephane.ducasse 4/13/2009 21:04'! projectOnlySelectionBlock ^[ :entry :myPattern | entry isDirectory ifTrue: [false] ifFalse: [ #('*.pr' '*.pr.gz' '*.project') anySatisfy: [ :each | each match: entry name]]] ! ! !FileList class methodsFor: 'as yet unclassified' stamp: 'RAA 2/19/2001 06:57'! projectOnlySelectionMethod: incomingEntries | versionsAccepted basicInfoTuple basicName basicVersion | "this shows only the latest version of each project" versionsAccepted := Dictionary new. incomingEntries do: [ :entry | entry isDirectory ifFalse: [ (#('*.pr' '*.pr.gz' '*.project') anySatisfy: [ :each | each match: entry name]) ifTrue: [ basicInfoTuple := Project parseProjectFileName: entry name. basicName := basicInfoTuple first. basicVersion := basicInfoTuple second. ((versionsAccepted includesKey: basicName) and: [(versionsAccepted at: basicName) first > basicVersion]) ifFalse: [ versionsAccepted at: basicName put: {basicVersion. entry} ]. ] ] ]. ^versionsAccepted asArray collect: [ :each | each second]! ! !FileList class methodsFor: 'as yet unclassified' stamp: 'stephane.ducasse 4/13/2009 21:04'! selectionBlockForSuffixes: anArray ^[ :entry :myPattern | entry isDirectory ifTrue: [false] ifFalse: [anArray anySatisfy: [ :each | each match: entry name]]] ! ! !FileList class methodsFor: 'blue ui' stamp: 'dgd 11/3/2004 20:09'! blueButtonText: aString textColor: textColor color: aColor inWindow: window | result | result := window fancyText: aString translated font: Preferences standardEToysFont color: textColor. result setProperty: #buttonText toValue: aString; hResizing: #rigid; extent: 100 @ 20; layoutInset: 4; borderWidth: ColorTheme current dialogButtonBorderWidth; useRoundedCorners. aColor isNil ifFalse: [""result color: aColor. result borderColor: aColor muchDarker]. ^ result! ! !FileList class methodsFor: 'blue ui' stamp: 'dgd 11/3/2004 20:13'! blueButtonText: aString textColor: textColor color: aColor inWindow: window balloonText: balloonText selector: sel recipient: recip | result | result := window fancyText: aString translated font: Preferences standardEToysFont color: textColor. result setProperty: #buttonText toValue: aString; hResizing: #rigid; extent: 100 @ 20; layoutInset: 4; borderWidth: ColorTheme current dialogButtonBorderWidth; useRoundedCorners; setBalloonText: balloonText. result on: #mouseUp send: sel to: recip. aColor isNil ifFalse: ["" result color: aColor. result borderColor: aColor muchDarker]. ^ result! ! !FileList class methodsFor: 'blue ui' stamp: 'dgd 11/2/2004 21:43'! blueButtonText: aString textColor: textColor inWindow: window ^ self blueButtonText: aString textColor: textColor color: nil inWindow: window! ! !FileList class methodsFor: 'blue ui' stamp: 'dgd 11/3/2004 20:04'! blueButtonText: aString textColor: textColor inWindow: window balloonText: balloonText selector: sel recipient: recip ^ self blueButtonText: aString textColor: textColor color: nil inWindow: window balloonText: balloonText selector: sel recipient: recip ! ! !FileList class methodsFor: 'blue ui' stamp: 'nk 7/16/2003 17:13'! enableTypeButtons: typeButtons info: fileTypeInfo forDir: aDirectory | foundSuffixes fileSuffixes firstEnabled enableIt | firstEnabled := nil. foundSuffixes := (aDirectory ifNil: [ #()] ifNotNil: [ aDirectory fileNames]) collect: [ :each | (each findTokens: '.') last asLowercase]. foundSuffixes := foundSuffixes asSet. fileTypeInfo with: typeButtons do: [ :info :button | fileSuffixes := info second. enableIt := fileSuffixes anySatisfy: [ :patt | foundSuffixes includes: patt]. button setProperty: #enabled toValue: enableIt. enableIt ifTrue: [firstEnabled ifNil: [firstEnabled := button]]. ]. firstEnabled ifNotNil: [^firstEnabled mouseUp: nil]. typeButtons do: [ :each | each color: Color gray]. ! ! !FileList class methodsFor: 'blue ui' stamp: 'dgd 4/3/2006 14:02'! endingSpecs "Answer a collection of specs to build the selective 'find anything' tool called by the Navigator. This version uses the services registry to do so." "FileList2 morphicViewGeneralLoaderInWorld: World" | categories services specs rejects | rejects := #(addFileToNewZip: compressFile: openInZipViewer: extractAllFrom: openOn:). categories := #( ('Art' ('bmp' 'gif' 'jpg' 'jpeg' 'form' 'png' 'pcx' 'xbm' 'xpm' 'ppm' 'pbm')) ('Morphs' ('morph' 'morphs' 'sp')) ('Projects' ('extseg' 'project' 'pr')) ('MIDI' ('mid' 'midi')) ('Music' ('mp3')) ('Movies' ('movie' 'mpg' 'mpeg' 'qt' 'mov')) ('Flash' ('swf')) ). "('Books' ('bo'))" "('Code' ('st' 'cs'))" "('TrueType' ('ttf'))" "('3ds' ('3ds'))" "('Tape' ('tape'))" "('Wonderland' ('wrl'))" "('HTML' ('htm' 'html'))" categories first at: 2 put: ImageReadWriter allTypicalFileExtensions. specs := OrderedCollection new. categories do: [ :cat | | catSpecs catServices okExtensions | services := Dictionary new. catSpecs := Array new: 3. catServices := OrderedCollection new. okExtensions := Set new. cat second do: [ :ext | (FileList itemsForFile: 'fred.',ext) do: [ :i | (rejects includes: i selector) ifFalse: [ okExtensions add: ext. services at: i label put: i ]]]. services do: [ :svc | catServices add: svc ]. services isEmpty ifFalse: [ catSpecs at: 1 put: cat first; at: 2 put: okExtensions; at: 3 put: catServices. specs add: catSpecs ] ]. ^specs ! ! !FileList class methodsFor: 'blue ui' stamp: 'stephane.ducasse 4/13/2009 21:03'! morphicViewGeneralLoaderInWorld: aWorld " FileList morphicViewGeneralLoaderInWorld: self currentWorld " | window aFileList buttons treePane textColor1 fileListPane pane2a pane2b fileTypeInfo fileTypeButtons fileTypeRow actionRow | fileTypeInfo := self endingSpecs. window := AlignmentMorph newColumn. window hResizing: #shrinkWrap; vResizing: #shrinkWrap. textColor1 := Color r: 0.742 g: 0.839 b: 1.0. aFileList := self new directory: FileDirectory default. aFileList fileSelectionBlock: self projectOnlySelectionBlock; modalView: window. window setProperty: #FileList toValue: aFileList; wrapCentering: #center; cellPositioning: #topCenter; borderWidth: ColorTheme current dialogBorderWidth; borderColor: ColorTheme current dialogBorderColor; useRoundedCorners. fileTypeButtons := fileTypeInfo collect: [ :each | (self blueButtonText: each first textColor: Color gray inWindow: window) setProperty: #enabled toValue: true; hResizing: #shrinkWrap; useSquareCorners ]. buttons := {{'OK'. ColorTheme current okColor}. {'Cancel'. ColorTheme current cancelColor}} collect: [ :each | self blueButtonText: each first textColor: textColor1 color: each second inWindow: window ]. treePane := aFileList morphicDirectoryTreePane extent: 250@300; retractable: false; borderWidth: 0. fileListPane := aFileList morphicFileListPane extent: 350@300; retractable: false; borderWidth: 0. window addARow: {window fancyText: 'Find...' translated font: Preferences standardEToysTitleFont color: textColor1}. fileTypeRow := window addARowCentered: fileTypeButtons cellInset: 2. actionRow := window addARowCentered: { buttons first. (Morph new extent: 30@5) color: Color transparent. buttons second } cellInset: 2. window addARow: { (window inAColumn: {(pane2a := window inARow: {window inAColumn: {treePane}}) useRoundedCorners; layoutInset: 0; borderWidth: ColorTheme current dialogPaneBorderWidth; borderColor: ColorTheme current dialogPaneBorderColor }) layoutInset: 10. (window inAColumn: {(pane2b := window inARow: {window inAColumn: {fileListPane}}) useRoundedCorners; layoutInset: 0; borderWidth: ColorTheme current dialogPaneBorderWidth; borderColor: ColorTheme current dialogPaneBorderColor }) layoutInset: 10. }. window fullBounds. window fillWithRamp: ColorTheme current dialogRampOrColor oriented: 0.65. pane2a fillWithRamp: ColorTheme current dialogPaneRampOrColor oriented: (0.7 @ 0.35). pane2b fillWithRamp: ColorTheme current dialogPaneRampOrColor oriented: (0.7 @ 0.35). " buttons do: [ :each | each fillWithRamp: ColorTheme current dialogButtonsRampOrColor oriented: (0.75 @ 0). ]. " fileTypeButtons do: [ :each | each on: #mouseUp send: #value:value: to: [ :evt :morph | self update: actionRow in: window fileTypeRow: fileTypeRow morphUp: morph]]. buttons first on: #mouseUp send: #okHit to: aFileList. buttons second on: #mouseUp send: #cancelHit to: aFileList. aFileList postOpen. window position: aWorld topLeft + (aWorld extent - window extent // 2). aFileList directoryChangeBlock: [ :newDir | self update: actionRow in: window fileTypeRow: fileTypeRow morphUp: nil. self enableTypeButtons: fileTypeButtons info: fileTypeInfo forDir: newDir]. aFileList directory: aFileList directory. window adoptPaneColor: (Color r: 0.548 g: 0.677 b: 1.0). window becomeModal. ^ window openInWorld: aWorld.! ! !FileList class methodsFor: 'file reader registration' stamp: 'hfm 11/29/2008 19:35'! allRegisteredServices "self allRegisteredServices" | col | col := OrderedCollection new. self registeredFileReaderClasses do: [:each | col addAll: (each services)]. ^ col! ! !FileList class methodsFor: 'file reader registration' stamp: 'hfm 11/29/2008 19:36'! detectService: aBlock ifNone: anotherBlock "self detectService: [:each | each selector = #fileIn:] ifNone: [nil]" ^ self allRegisteredServices detect: aBlock ifNone: anotherBlock! ! !FileList class methodsFor: 'file reader registration' stamp: 'hfm 11/29/2008 19:36'! isReaderNamedRegistered: aSymbol "return if a given reader class has been registered. Note that this is on purpose that the argument is a symbol and not a class" ^ (self registeredFileReaderClasses collect: [:each | each name]) includes: aSymbol ! ! !FileList class methodsFor: 'file reader registration' stamp: 'hfm 11/29/2008 19:39'! unregisterFileReader: aProviderClass "unregister the given class as providing services for reading files" self registeredFileReaderClasses remove: aProviderClass ifAbsent: [nil]! ! !FileList class methodsFor: 'initialization' stamp: 'hfm 11/29/2008 19:06'! initialize "FileList2 initialize" RecentDirs := OrderedCollection new. (self systemNavigation allClassesImplementing: #fileReaderServicesForFile:suffix:) do: [:providerMetaclass | self registerFileReader: providerMetaclass soleInstance]! ! !FileList class methodsFor: 'initialization' stamp: 'hfm 11/29/2008 19:38'! removeObsolete "FileList removeObsolete" self registeredFileReaderClasses copy do:[:cls| cls isObsolete ifTrue:[self unregisterFileReader: cls]]! ! !FileList class methodsFor: 'initialization' stamp: 'hfm 11/29/2008 19:38'! unload "Unload the receiver from global registries" self environment at: #Flaps ifPresent: [:cl | cl unregisterQuadsWithReceiver: self] ! ! !FileList class methodsFor: 'instance creation' stamp: 'hfm 11/29/2008 19:35'! addButtonsAndFileListPanesTo: window at: upperFraction plus: offset forFileList: aFileList | fileListMorph row buttonHeight fileListTop divider dividerDelta buttons | fileListMorph := PluggableListMorph on: aFileList list: #fileList selected: #fileListIndex changeSelected: #fileListIndex: menu: #fileListMenu:. fileListMorph enableDrag: true; enableDrop: false. aFileList wantsOptionalButtons ifTrue: [buttons := aFileList optionalButtonRow. divider := BorderedSubpaneDividerMorph forBottomEdge. dividerDelta := 0. buttons color: Color transparent. buttons submorphsDo: [:m | m borderWidth: 2; borderColor: #raised]. divider extent: 4 @ 4; color: Color transparent; borderColor: #raised; borderWidth: 2. fileListMorph borderColor: Color transparent. dividerDelta := 3. row := AlignmentMorph newColumn hResizing: #spaceFill; vResizing: #spaceFill; layoutInset: 0; borderWidth: 2; layoutPolicy: ProportionalLayout new. buttonHeight := self defaultButtonPaneHeight. row addMorph: buttons fullFrame: (LayoutFrame fractions: (0 @ 0 corner: 1 @ 0) offsets: (0 @ 0 corner: 0 @ buttonHeight)). row addMorph: divider fullFrame: (LayoutFrame fractions: (0 @ 0 corner: 1 @ 0) offsets: (0 @ buttonHeight corner: 0 @ buttonHeight + dividerDelta)). row addMorph: fileListMorph fullFrame: (LayoutFrame fractions: (0 @ 0 corner: 1 @ 1) offsets: (0 @ buttonHeight + dividerDelta corner: 0 @ 0)). window addMorph: row fullFrame: (LayoutFrame fractions: upperFraction offsets: (0 @ offset corner: 0 @ 0)). row borderWidth: 2] ifFalse: [fileListTop := 0. window addMorph: fileListMorph frame: (0.3 @ fileListTop corner: 1 @ 0.3)].! ! !FileList class methodsFor: 'instance creation' stamp: 'md 2/24/2006 15:59'! addVolumesAndPatternPanesTo: window at: upperFraction plus: offset forFileList: aFileList | row patternHeight volumeListMorph patternMorph divider dividerDelta | row := AlignmentMorph newColumn hResizing: #spaceFill; vResizing: #spaceFill; layoutInset: 0; borderWidth: 0; layoutPolicy: ProportionalLayout new. patternHeight := 25. volumeListMorph := (PluggableListMorph on: aFileList list: #volumeList selected: #volumeListIndex changeSelected: #volumeListIndex: menu: #volumeMenu:) autoDeselect: false. volumeListMorph enableDrag: false; enableDrop: true. patternMorph := PluggableTextMorph on: aFileList text: #pattern accept: #pattern:. patternMorph acceptOnCR: true. patternMorph hideScrollBarsIndefinitely. divider := BorderedSubpaneDividerMorph horizontal. dividerDelta := 0. divider extent: 4 @ 4; color: Color transparent; borderColor: #raised; borderWidth: 2. volumeListMorph borderColor: Color transparent. patternMorph borderColor: Color transparent. dividerDelta := 3. row addMorph: (volumeListMorph autoDeselect: false) fullFrame: (LayoutFrame fractions: (0 @ 0 corner: 1 @ 1) offsets: (0 @ 0 corner: 0 @ patternHeight negated - dividerDelta)). row addMorph: divider fullFrame: (LayoutFrame fractions: (0 @ 1 corner: 1 @ 1) offsets: (0 @ patternHeight negated - dividerDelta corner: 0 @ patternHeight negated)). row addMorph: patternMorph fullFrame: (LayoutFrame fractions: (0 @ 1 corner: 1 @ 1) offsets: (0 @ patternHeight negated corner: 0 @ 0)). window addMorph: row fullFrame: (LayoutFrame fractions: upperFraction offsets: (0 @ offset corner: 0 @ 0)). row borderWidth: 2! ! !FileList class methodsFor: 'instance creation' stamp: 'hfm 11/29/2008 19:36'! defaultButtonPaneHeight "Answer the user's preferred default height for new button panes." ^ Preferences parameterAt: #defaultButtonPaneHeight ifAbsentPut: [25]! ! !FileList class methodsFor: 'instance creation' stamp: 'hfm 11/29/2008 19:36'! open "Open a view of an instance of me on the default directory." "FileList open openInWorld" ^ self openAsMorph! ! !FileList class methodsFor: 'instance creation' stamp: 'hfm 11/29/2008 19:37'! openAsMorph "Open a morphic view of a FileList on the default directory." | dir aFileList window upperFraction offset | dir := FileDirectory default. aFileList := self new directory: dir. window := (SystemWindow labelled: dir pathName) model: aFileList. upperFraction := 0.3. offset := 0. self addVolumesAndPatternPanesTo: window at: (0 @ 0 corner: 0.3 @ upperFraction) plus: offset forFileList: aFileList. self addButtonsAndFileListPanesTo: window at: (0.3 @ 0 corner: 1.0 @ upperFraction) plus: offset forFileList: aFileList. window addMorph: (PluggableTextMorph on: aFileList text: #contents accept: #put: readSelection: #contentsSelection menu: #fileContentsMenu:shifted:) frame: (0 @ 0.3 corner: 1 @ 1). ^ window! ! !FileList class methodsFor: 'instance creation' stamp: 'hfm 11/29/2008 19:37'! openEditorOn: aFileStream editString: editString "Open an editor on the given FileStream." ^ (self openMorphOn: aFileStream editString: editString) openInWorld! ! !FileList class methodsFor: 'instance creation' stamp: 'hfm 11/29/2008 19:37'! openFileDirectly | aResult | (aResult := StandardFileMenu oldFile) ifNotNil: [self openEditorOn: (aResult directory readOnlyFileNamed: aResult name) editString: nil]! ! !FileList class methodsFor: 'instance creation' stamp: 'hfm 11/29/2008 19:37'! openMorphOn: aFileStream editString: editString "Open a morphic view of a FileList on the given file." | fileModel window fileContentsView | fileModel := FileList new setFileStream: aFileStream. "closes the stream" window := (SystemWindow labelled: aFileStream fullName) model: fileModel. window addMorph: (fileContentsView := PluggableTextMorph on: fileModel text: #contents accept: #put: readSelection: #contentsSelection menu: #fileContentsMenu:shifted:) frame: (0@0 corner: 1@1). editString ifNotNil: [fileContentsView editString: editString. fileContentsView hasUnacceptedEdits: true]. ^ window! ! !FileList class methodsFor: 'instance creation' stamp: 'nk 7/12/2000 11:03'! openMorphicViewInWorld "FileList2 openMorphicViewInWorld" ^self morphicView openInWorld! ! !FileList class methodsFor: 'instance creation' stamp: 'nk 6/14/2004 08:41'! prototypicalToolWindow "Answer an example of myself seen in a tool window, for the benefit of parts-launching tools" ^ self morphicView applyModelExtent! ! !FileList class methodsFor: 'instance creation' stamp: 'hfm 11/29/2008 19:04'! registerFileReader: aProviderClass "register the given class as providing services for reading files" | registeredReaders | registeredReaders := self registeredFileReaderClasses. (registeredReaders includes: aProviderClass) ifFalse: [ registeredReaders addLast: aProviderClass ]! ! !FileList class methodsFor: 'instance creation' stamp: 'hfm 11/29/2008 19:38'! registerInFlapsRegistry "Register the receiver in the system's flaps registry" self environment at: #Flaps ifPresent: [:cl | cl registerQuad: #(FileList prototypicalToolWindow 'File List' 'A File List is a tool for browsing folders and files on disks and on ftp types.') forFlapNamed: 'Tools']! ! !FileList class methodsFor: 'modal dialogs' stamp: 'miki 8/15/2005 18:35'! modalFileSelector | window | window := self morphicViewFileSelector. window openCenteredInWorld. self modalLoopOn: window. ^(window valueOfProperty: #fileListModel) getSelectedFile! ! !FileList class methodsFor: 'modal dialogs' stamp: 'miki 8/15/2005 18:34'! modalFileSelectorForSuffixes: aList | window aFileList | window := self morphicViewFileSelectorForSuffixes: aList. aFileList := window valueOfProperty: #fileListModel. window openCenteredInWorld. self modalLoopOn: window. ^aFileList getSelectedFile! ! !FileList class methodsFor: 'modal dialogs' stamp: 'miki 8/15/2005 18:34'! modalFileSelectorForSuffixes: aList directory: aDirectory | window aFileList | window := self morphicViewFileSelectorForSuffixes: aList directory: aDirectory. aFileList := window valueOfProperty: #fileListModel. window openCenteredInWorld. self modalLoopOn: window. ^aFileList getSelectedFile! ! !FileList class methodsFor: 'modal dialogs' stamp: 'gh 9/16/2002 10:33'! modalFolderSelector ^self modalFolderSelector: FileDirectory default! ! !FileList class methodsFor: 'modal dialogs' stamp: 'miki 8/15/2005 18:33'! modalFolderSelector: aDir | window fileModel | window := self morphicViewFolderSelector: aDir. fileModel := window model. window openInWorld: self currentWorld extent: 300@400. self modalLoopOn: window. ^fileModel getSelectedDirectory withoutListWrapper! ! !FileList class methodsFor: 'morphic ui' stamp: 'btr 1/30/2004 00:56'! morphicView ^ self morphicViewOnDirectory: FileDirectory default! ! !FileList class methodsFor: 'morphic ui' stamp: 'RAA 3/6/2001 12:47'! morphicViewFileSelector ^self morphicViewFileSelectorForSuffixes: nil ! ! !FileList class methodsFor: 'morphic ui' stamp: 'miki 8/14/2005 21:21'! morphicViewFileSelectorForSuffixes: aList "Answer a morphic file-selector tool for the given suffix list." ^self morphicViewFileSelectorForSuffixes: aList directory: FileDirectory default.! ! !FileList class methodsFor: 'morphic ui' stamp: 'stephane.ducasse 4/13/2009 21:06'! morphicViewFileSelectorForSuffixes: aList directory: dir "Answer a morphic file-selector tool for the given suffix list and the given directory." | aFileList window fixedSize midLine gap | aFileList := self new directory: dir. aFileList optionalButtonSpecs: aFileList okayAndCancelServices. aList ifNotNil: [aFileList fileSelectionBlock: [:entry :myPattern | entry isDirectory ifTrue: [false] ifFalse: [aList includes: (FileDirectory extensionFor: entry name asLowercase)]]]. window := BorderedMorph new layoutPolicy: ProportionalLayout new; color: Color lightBlue; borderColor: Color blue; borderWidth: 4; layoutInset: 4; extent: 600@400; useRoundedCorners. window setProperty: #fileListModel toValue: aFileList. aFileList modalView: window. midLine := 0.4. fixedSize := 25. gap := 5. self addFullPanesTo: window from: { {self textRow: 'Please select a file'. 0 @ 0 corner: 1 @ 0. 0@0 corner: 0@fixedSize}. {aFileList optionalButtonRow. 0 @ 0 corner: 1 @ 0. 0@fixedSize corner: 0@(fixedSize * 2)}. {aFileList morphicDirectoryTreePane. 0@0 corner: midLine@1. gap @(fixedSize * 2) corner: gap negated@0}. {aFileList morphicFileListPane. midLine @ 0 corner: 1@1. gap@(fixedSize * 2) corner: gap negated@0}. }. aFileList postOpen. ^ window ! ! !FileList class methodsFor: 'morphic ui' stamp: 'gh 9/16/2002 10:30'! morphicViewFolderSelector ^self morphicViewFolderSelector: FileDirectory default! ! !FileList class methodsFor: 'morphic ui' stamp: 'bkv 11/12/2002 16:55'! morphicViewFolderSelector: aDir "Answer a tool that allows the user to select a folder" | aFileList window fixedSize | aFileList := self new directory: aDir. aFileList optionalButtonSpecs: aFileList servicesForFolderSelector. window := (SystemWindow labelled: aDir pathName) model: aFileList. aFileList modalView: window. fixedSize := 25. self addFullPanesTo: window from: { {self textRow: 'Please select a folder'. 0 @ 0 corner: 1 @ 0. 0@0 corner: 0@fixedSize}. {aFileList optionalButtonRow. 0 @ 0 corner: 1 @ 0. 0@fixedSize corner: 0@(fixedSize * 2)}. {aFileList morphicDirectoryTreePane. 0@0 corner: 1@1. 0@(fixedSize * 2) corner: 0@0}. }. aFileList postOpen. ^ window ! ! !FileList class methodsFor: 'morphic ui' stamp: 'stephane.ducasse 4/13/2009 21:07'! morphicViewImageViewer | dir aFileList window midLine fixedSize | dir := FileDirectory default. aFileList := self new directory: dir. aFileList optionalButtonSpecs: aFileList specsForImageViewer. aFileList fileSelectionBlock: [ :entry :myPattern | entry isDirectory ifTrue: [false] ifFalse: [ #('bmp' 'gif' 'jpg' 'form' 'png') includes: (FileDirectory extensionFor: entry name asLowercase)]]. window := (SystemWindow labelled: dir pathName) model: aFileList. fixedSize := 25. midLine := 0.4. self addFullPanesTo: window from: { {aFileList optionalButtonRow. 0 @ 0 corner: 1 @ 0. 0@0 corner: 0@fixedSize}. {aFileList morphicDirectoryTreePane. 0@0 corner: midLine@1. 0@fixedSize corner: 0@0}. {aFileList morphicFileListPane. midLine @ 0 corner: 1@1. 0@fixedSize corner: 0@0}. }. aFileList postOpen. ^ window ! ! !FileList class methodsFor: 'morphic ui' stamp: 'RAA 1/8/2001 21:39'! morphicViewNoFile | dir aFileList window midLine fixedSize | dir := FileDirectory default. aFileList := self new directory: dir. window := (SystemWindow labelled: dir pathName) model: aFileList. fixedSize := 25. midLine := 0.4. self addFullPanesTo: window from: { {aFileList morphicPatternPane. 0@0 corner: 0.3@0. 0@0 corner: 0@fixedSize}. {aFileList optionalButtonRow. 0.3 @ 0 corner: 1@0. 0@0 corner: 0@fixedSize}. {aFileList morphicDirectoryTreePane. 0@0 corner: midLine@1. 0@fixedSize corner: 0@0}. {aFileList morphicFileListPane. midLine @ 0 corner: 1@1. 0@fixedSize corner: 0@0}. }. aFileList postOpen. ^ window ! ! !FileList class methodsFor: 'morphic ui' stamp: 'gk 5/5/2006 02:05'! morphicViewOnDirectory: aFileDirectory | aFileList window fileListBottom midLine fileListTopOffset buttonPane | aFileList := self new directory: aFileDirectory. window := (SystemWindow labelled: aFileDirectory pathName) model: aFileList. fileListTopOffset := (TextStyle defaultFont pointSize * 2) + 14. fileListBottom := 0.4. midLine := 0.4. buttonPane := aFileList optionalButtonRow addMorph: (aFileList morphicPatternPane vResizing: #spaceFill; yourself). self addFullPanesTo: window from: { {buttonPane. 0@0 corner: 1@0. 0@0 corner: 0@fileListTopOffset}. {aFileList morphicDirectoryTreePane. 0@0 corner: midLine@fileListBottom. 0@fileListTopOffset corner: 0@0}. {aFileList morphicFileListPane. midLine @ 0 corner: 1@fileListBottom. 0@fileListTopOffset corner: 0@0}. {aFileList morphicFileContentsPane. 0@fileListBottom corner: 1@1. nil}. }. aFileList postOpen. ^ window ! ! !FileList class methodsFor: 'morphic ui' stamp: 'sw 2/22/2002 02:02'! morphicViewProjectLoader | dir aFileList window midLine fixedSize | dir := FileDirectory default. aFileList := self new directory: dir. aFileList optionalButtonSpecs: aFileList servicesForProjectLoader. aFileList fileSelectionBlock: self projectOnlySelectionBlock. window := (SystemWindow labelled: dir pathName) model: aFileList. fixedSize := 25. midLine := 0.4. self addFullPanesTo: window from: { {aFileList optionalButtonRow. 0 @ 0 corner: 1 @ 0. 0@0 corner: 0@fixedSize}. {aFileList morphicDirectoryTreePane. 0@0 corner: midLine@1. 0@fixedSize corner: 0@0}. {aFileList morphicFileListPane. midLine @ 0 corner: 1@1. 0@fixedSize corner: 0@0}. }. aFileList postOpen. ^ window ! ! !FileList class methodsFor: 'morphic ui' stamp: 'dgd 4/3/2006 14:04'! update: actionRow in: window fileTypeRow: fileTypeRow morphUp: morph | fileTypeInfo info2 buttons textColor1 fileSuffixes fileActions aFileList fileTypeString | (morph notNil and:[(morph valueOfProperty: #enabled) not]) ifTrue: [^self]. fileTypeRow submorphsDo: [ :sub | sub color: ( sub == morph ifTrue: [Color white] ifFalse: [(sub valueOfProperty: #enabled) ifTrue: [Color transparent] ifFalse: [Color gray]] ). ]. fileTypeString := morph isNil ifTrue:['xxxx'] ifFalse:[morph valueOfProperty: #buttonText]. aFileList := window valueOfProperty: #FileList. textColor1 := Color r: 0.742 g: 0.839 b: 1.0. actionRow removeAllMorphs. fileTypeInfo := self endingSpecs. info2 := fileTypeInfo detect: [ :each | each first = fileTypeString] ifNone: [ nil ]. info2 isNil ifTrue:[ buttons := OrderedCollection new ] ifFalse:[ fileSuffixes := info2 second. fileActions := info2 third. buttons := fileActions collect: [ :each | aFileList blueButtonForService: each textColor: textColor1 inWindow: window ]. buttons do: [ :each | each fillWithRamp: ColorTheme current okColor oriented: (0.75 @ 0). ]. ]. buttons addLast: (self blueButtonText: 'Cancel' textColor: textColor1 color: ColorTheme current cancelColor inWindow: window balloonText: 'Cancel this search' selector: #cancelHit recipient: aFileList). buttons do: [ :each | actionRow addMorphBack: each]. window fullBounds. fileSuffixes isNil ifFalse:[ aFileList fileSelectionBlock: ( self selectionBlockForSuffixes: (fileSuffixes collect: [ :each | '*.',each]) ). ]. aFileList updateFileList.! ! !FileList class methodsFor: 'utility' stamp: 'RAA 1/8/2001 21:23'! addFullPanesTo: window from: aCollection | frame | aCollection do: [ :each | frame := LayoutFrame fractions: each second offsets: each third. window addMorph: each first fullFrame: frame. ]! ! !FileList class methodsFor: 'utility' stamp: 'hfm 11/29/2008 18:58'! itemsForDirectory: aFileDirectory "Answer a list of services appropriate when no file is selected." | services | services := OrderedCollection new. self registeredFileReaderClasses do: [:reader | reader ifNotNil: [services addAll: (reader fileReaderServicesForDirectory: aFileDirectory) ]]. ^ services! ! !FileList class methodsFor: 'utility' stamp: 'hfm 11/29/2008 18:35'! itemsForFile: fullName "Answer a list of services appropriate for a file of the given full name" | services suffix | suffix := self suffixOf: fullName. services := OrderedCollection new. self registeredFileReaderClasses do: [:reader | reader ifNotNil: [services addAll: (reader fileReaderServicesForFile: fullName suffix: suffix)]]. ^ services! ! !FileList class methodsFor: 'utility' stamp: 'miki 8/15/2005 18:34'! modalLoopOn: aMorph [aMorph world notNil] whileTrue: [ aMorph outermostWorldMorph doOneCycle. ].! ! !FileList class methodsFor: 'utility' stamp: 'hfm 11/29/2008 18:37'! registeredFileReaderClasses FileReaderRegistry := nil. "wipe it out" ^FileServices registeredFileReaderClasses ! ! !FileList class methodsFor: 'utility' stamp: 'hfm 11/29/2008 18:35'! suffixOf: aName "Answer the file extension of the given file" ^ aName ifNil: [''] ifNotNil: [(FileDirectory extensionFor: aName) asLowercase]! ! !FileList class methodsFor: 'utility' stamp: 'RAA 3/6/2001 12:39'! textRow: aString ^AlignmentMorph newRow wrapCentering: #center; cellPositioning: #leftCenter; color: Color transparent; layoutInset: 0; addMorph: ( AlignmentMorph newColumn wrapCentering: #center; cellPositioning: #topCenter; color: Color transparent; vResizing: #shrinkWrap; layoutInset: 0; addMorph: ( AlignmentMorph newRow wrapCentering: #center; cellPositioning: #leftCenter; color: Color transparent; hResizing: #shrinkWrap; vResizing: #shrinkWrap; layoutInset: 0; addMorph: ((StringMorph contents: aString) color: Color blue; lock) ) )! ! !FileList class methodsFor: 'window color' stamp: 'hfm 11/29/2008 19:39'! windowColorSpecification "Answer a WindowColorSpec object that declares my preference" ^ WindowColorSpec classSymbol: self name wording: 'File List' brightColor: #lightMagenta pastelColor: #paleMagenta helpMessage: 'A tool for looking at files'! ! SimpleServiceEntry subclass: #FileModifyingSimpleServiceEntry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'System-FileRegistry'! !FileModifyingSimpleServiceEntry commentStamp: 'nk 11/26/2002 12:03' prior: 0! I represent a service that may change the contents of a directory. Such changes include: * file creation * file deletion * file modification! !FileModifyingSimpleServiceEntry methodsFor: 'as yet unclassified' stamp: 'nk 11/26/2002 12:08'! performServiceFor: anObject | retval | retval := super performServiceFor: anObject. self changed: #fileListChanged. ^retval "is this used anywhere?"! ! Object subclass: #FilePackage instanceVariableNames: 'fullName sourceSystem classes doIts classOrder' classVariableNames: 'LogFileStream' poolDictionaries: '' category: 'System-FilePackage'! !FilePackage methodsFor: '*monticello' stamp: 'al 12/2/2005 13:58'! classDefinition: string with: chgRec | tokens theClass | self flag: #traits. tokens := Scanner new scanTokens: string. "tokens size = 11 ifFalse:[^doIts add: chgRec]." theClass := self getClass: (tokens at: 3). theClass definition: string. classOrder add: theClass.! ! !FilePackage methodsFor: '*monticello' stamp: 'avi 1/19/2004 23:47'! doIts ^ doIts! ! !FilePackage methodsFor: 'accessing'! classAt: className ^self classes at: className! ! !FilePackage methodsFor: 'accessing'! classes ^classes! ! !FilePackage methodsFor: 'accessing' stamp: 'nk 2/18/2004 18:31'! fixClassOrder "Essentially bubble sort the classOrder so that superclasses appear before subclasses" | superClass index subClass superIndex | index := 0. [index < classOrder size] whileTrue:[ subClass := classOrder at: (index := index + 1). superClass := nil. subClass isMeta ifTrue:[ "Treat non-meta as superclass" superClass := self classes at: subClass name ifAbsent:[nil]. ] ifFalse:[ subClass hasDefinition ifTrue:[ superClass := self classes at: (Scanner new scanTokens: subClass definition) first ifAbsent:[nil]. superClass ifNotNil:[superClass hasDefinition ifFalse:[superClass := nil]]. ]. ]. superClass ifNotNil:[ superIndex := classOrder indexOf: superClass ifAbsent:[self error:'Where is the class?']. superIndex > index ifTrue:[ "Move superClass before index" classOrder remove: superClass. classOrder add: superClass before: subClass. "Rewind index - we need to check superClass itself" index := index - 1. ]. ]. ]. ! ! !FilePackage methodsFor: 'accessing' stamp: 'pnm 8/23/2000 17:10'! fullName: aString fullName := aString! ! !FilePackage methodsFor: 'accessing'! fullPackageName ^fullName! ! !FilePackage methodsFor: 'accessing'! packageInfo ^String streamContents:[:s| s nextPutAll:'Package: '. s nextPutAll: self fullPackageName; cr; cr. sourceSystem isEmpty ifFalse:[ s nextPutAll: sourceSystem; cr; cr]. doIts isEmpty ifFalse:[ s nextPutAll:'Unresolvable doIts:'; cr; cr. doIts do:[:chgRec| s nextPut:$!!; nextPutAll: chgRec string; nextPut: $!!; cr]]].! ! !FilePackage methodsFor: 'accessing' stamp: 'pnm 8/23/2000 17:12'! packageName ^FileDirectory localNameFor: self fullPackageName! ! !FilePackage methodsFor: 'accessing'! removeClass: aPseudoClass (self classes removeKey: aPseudoClass name). classOrder copy do:[:cls| cls name = aPseudoClass name ifTrue:[ classOrder remove: cls]. ].! ! !FilePackage methodsFor: 'accessing' stamp: 'ar 2/5/2004 15:11'! removeDoIts doIts := OrderedCollection new.! ! !FilePackage methodsFor: 'accessing'! renameClass: aPseudoClass to: newName | oldName | oldName := aPseudoClass name. self classes removeKey: oldName. self classes at: newName put: aPseudoClass. aPseudoClass renameTo: newName.! ! !FilePackage methodsFor: 'change record types'! classComment: chgRec (self getClass: chgRec methodClassName) classComment: chgRec! ! !FilePackage methodsFor: 'change record types'! doIt: chgRec | string | string := chgRec string. ('*ubclass:*instanceVariableNames:*classVariableNames:*poolDictionaries:*category:*' match: string) ifTrue:[^self classDefinition: string with: chgRec]. ('* class*instanceVariableNames:*' match: string) ifTrue:[^self metaClassDefinition: string with: chgRec]. ('* removeSelector: *' match: string) ifTrue:[^self removedMethod: string with: chgRec]. ('* comment:*' match: string) ifTrue:[^self msgClassComment: string with: chgRec]. ('* initialize' match: string) ifTrue:[^self]. "Initialization is done based on class>>initialize" ('''From *' match: string) ifTrue:[^self possibleSystemSource: chgRec]. doIts add: chgRec.! ! !FilePackage methodsFor: 'change record types'! method: chgRec (self getClass: chgRec methodClassName) methodChange: chgRec! ! !FilePackage methodsFor: 'change record types'! preamble: chgRec self doIt: chgRec! ! !FilePackage methodsFor: 'conflict checker' stamp: 'dew 2/14/2004 00:12'! checkForMoreRecentUpdateThanChangeSet: updateNumberChangeSet pseudoClass: pseudoClass selector: selector "Returns the source code for a conflict if a conflict is found, otherwise returns nil." | classOrMeta allChangeSets moreRecentChangeSets conflictingChangeSets changeRecordSource classAndMethodPrintString | classAndMethodPrintString := pseudoClass name, (pseudoClass hasMetaclass ifTrue: [' class'] ifFalse: ['']), '>>', selector asString. changeRecordSource := pseudoClass sourceCode at: selector. changeRecordSource isText ifTrue: [changeRecordSource := Text fromString: 'method: ', classAndMethodPrintString, ' was removed'] ifFalse: [changeRecordSource stamp isEmptyOrNil ifTrue: [self notify: 'Warning: ', classAndMethodPrintString, ' in ', self packageName, ' has no timestamp/initials!!']]. pseudoClass exists ifFalse: [(self classes at: pseudoClass name) hasDefinition ifTrue: [^ nil "a method was added for a newly defined class; not a conflict"] ifFalse: [self class logCr; log: 'CONFLICT found for ', classAndMethodPrintString, '... class ', pseudoClass name asString, ' does not exist in the image and is not defined in the file'. ^ changeRecordSource]]. classOrMeta := pseudoClass realClass. "Only printout the replacing methods here, but we still check for removed methods too in the rest of this method." (self class verboseConflicts and: [classOrMeta includesSelector: selector]) ifTrue: [self class logCr; log: '...checking ', classOrMeta asString, '>>', selector asString]. allChangeSets := ChangeSorter allChangeSets. moreRecentChangeSets := allChangeSets copyFrom: (allChangeSets indexOf: updateNumberChangeSet) to: (allChangeSets size). conflictingChangeSets := (moreRecentChangeSets select: [:cs | (cs atSelector: selector class: classOrMeta) ~~ #none]). conflictingChangeSets isEmpty ifTrue: [^ nil]. self class logCr; log: 'CONFLICT found for ', classAndMethodPrintString, (' with newer changeset' asPluralBasedOn: conflictingChangeSets). conflictingChangeSets do: [:cs | self class log: ' ', cs name]. ^ changeRecordSource ! ! !FilePackage methodsFor: 'conflict checker' stamp: 'DamienCassou 9/23/2009 08:40'! conflictsWithUpdatedMethods "Check this package for conflicts with methods in the image which are in newer updates." | localFileName stream updateNumberString updateNumber imageUpdateNumber updateNumberChangeSet conflicts fileStream | localFileName := FileDirectory localNameFor: fullName. stream := sourceSystem readStream. stream upToAll: 'latest update: #'. updateNumberString := stream upTo: $]. stream close. fileStream := FileStream readOnlyFileNamed: fullName. (fileStream contentsOfEntireFile includes: Character linefeed) ifTrue: [self notifyWithLabel: 'The changeset file ', localFileName, ' contains linefeeds. Proceed if... you know that this is okay (e.g. the file contains raw binary data).']. fileStream close. updateNumberString isEmpty ifFalse: "remove prepended junk, if any" [updateNumberString := (updateNumberString findTokens: Character space) last]. updateNumberString asInteger ifNil: [(self confirm: 'Error: ', localFileName, ' has no valid Latest Update number in its header. Do you want to enter an update number for this file?') ifFalse: [^ self] ifTrue: [updateNumberString := UIManager default request: 'Please enter the estimated update number (e.g. 4332).' translated]]. (updateNumberString isEmptyOrNil or: [updateNumberString asInteger isNil]) ifTrue: [self inform: 'Conflict check cancelled.' translated. ^ self]. updateNumber := updateNumberString asInteger. imageUpdateNumber := SystemVersion current highestUpdate. updateNumber > imageUpdateNumber ifTrue: [(self confirm: 'Warning: The update number for this file (#', updateNumberString, ') is greater than the highest update number for this image (#', imageUpdateNumber asString, '). This probably means you need to update your image. Should we proceed anyway as if the file update number is #', imageUpdateNumber asString, '?') ifTrue: [updateNumber := imageUpdateNumber. updateNumberString := imageUpdateNumber asString] ifFalse: [^ self]]. updateNumberChangeSet := self findUpdateChangeSetMatching: updateNumber. updateNumberChangeSet ifNil: [^ self]. self currentWorld findATranscript: self currentEvent. self class logCr; logCr; log: 'Checking ', localFileName, ' (#', updateNumberString, ') for method conflicts with changesets after ', updateNumberChangeSet name, ' ...'. conflicts := OrderedCollection new. self classes values do: [:pseudoClass | (Array with: pseudoClass with: pseudoClass metaClass) do: [:classOrMeta | classOrMeta selectors do: [:selector | | conflict | conflict := self checkForMoreRecentUpdateThanChangeSet: updateNumberChangeSet pseudoClass: classOrMeta selector: selector. conflict ifNotNil: [conflicts add: conflict]. ]. ]. ]. self class logCr; log: conflicts size asString, (' conflict' asPluralBasedOn: conflicts), ' found.'; logCr. self class closeLog. ^ conflicts! ! !FilePackage methodsFor: 'conflict checker' stamp: 'dew 10/19/2003 21:29'! findUpdateChangeSetMatching: updateNumber "Find update-changeset beginning with updateNumber, or reasonably close." "This is to account for the fact that many changeset files are output from final releases, but may be tested for conflicts in a following alpha image, which will often not include that particular update-changeset from the final release but will contain ones near it. For example, if the file updateNumber is 5180 (from 3.5 final), but the image has no update-changeset beginning with 5180 because it's a 3.6alpha image (which starts at 5181), it will try up to 5190 and down to 5170 for a close match." | updateNumberChangeSet updateNumberToTry | updateNumberToTry := updateNumber. updateNumberChangeSet := nil. [updateNumberChangeSet isNil and: [updateNumberToTry notNil]] whileTrue: [updateNumberChangeSet := ChangeSorter allChangeSets detect: [:cs | (cs name beginsWith: updateNumberToTry asString) and: [(cs name at: (updateNumberToTry asString size + 1)) isDigit not]] ifNone: [nil]. updateNumberToTry >= updateNumber ifTrue: [updateNumberToTry < (updateNumber + 10) ifTrue: [updateNumberToTry := updateNumberToTry + 1] ifFalse: [updateNumberToTry := updateNumber]]. updateNumberToTry <= updateNumber ifTrue: [updateNumberToTry > (updateNumber - 10) ifTrue: [updateNumberToTry := updateNumberToTry - 1] ifFalse: [updateNumberToTry := nil "we're done trying"]]. ]. updateNumberChangeSet ifNil: [(self confirm: 'Warning: No changeset beginning with ', updateNumber asString, ' (within +/- 10) was found in the image. You must have changesets going back this far in your image in order to accurately check for conflicts. Proceed anyway?') ifTrue: [updateNumberChangeSet := ChangeSorter allChangeSets first]]. ^ updateNumberChangeSet! ! !FilePackage methodsFor: 'filein/fileout' stamp: 'alain.plantec 2/6/2009 17:01'! askForDoits | choice choices | choices := {'do not process' translated. 'at the beginning' translated. 'at the end' translated}. choice := nil. [choices includes: choice] whileFalse: [ choice := UIManager default chooseFrom: choices values: choices title: 'Unprocessed doIts found. When to process those?' translated. choice ifNil: [^0]]. ^choices indexOf: choice! ! !FilePackage methodsFor: 'filein/fileout' stamp: 'alain.plantec 2/6/2009 17:02'! fileIn | doitsMark | doitsMark := 1. doIts isEmpty ifFalse:[doitsMark := self askForDoits]. doitsMark = 0 ifTrue: [^nil]. doitsMark = 2 ifTrue:[self fileInDoits]. classOrder do:[:cls| cls fileInDefinition. ]. classes do:[:cls| Transcript cr; show:'Filing in ', cls name. cls fileInMethods. cls hasMetaclass ifTrue:[cls metaClass fileInMethods]. ]. doitsMark = 3 ifTrue:[self fileInDoits].! ! !FilePackage methodsFor: 'filein/fileout'! fileInDoits doIts do:[:chgRec| chgRec fileIn].! ! !FilePackage methodsFor: 'filein/fileout' stamp: 'ar 7/17/2005 03:36'! fileOut | fileName stream | fileName := UIManager default request: 'Enter the file name' initialAnswer:''. stream := FileStream newFileNamed: fileName. sourceSystem isEmpty ifFalse:[ stream nextChunkPut: sourceSystem printString;cr ]. self fileOutOn: stream. stream cr; cr. self classes do:[:cls| cls needsInitialize ifTrue:[ stream cr; nextChunkPut: cls name,' initialize']]. stream cr. stream close. "DeepCopier new checkVariables." ! ! !FilePackage methodsFor: 'filein/fileout'! fileOutDoits: aStream doIts do:[:chgRec| chgRec fileOutOn: aStream].! ! !FilePackage methodsFor: 'filein/fileout' stamp: 'alain.plantec 2/6/2009 17:02'! fileOutOn: aStream | doitsMark | doitsMark := 1. doIts isEmpty ifFalse:[doitsMark := self askForDoits]. doitsMark = 0 ifTrue: [^nil]. doitsMark = 2 ifTrue:[self fileOutDoits: aStream]. classOrder do:[:cls| cls fileOutDefinitionOn: aStream. ]. classes do:[:cls| cls fileOutMethodsOn: aStream. cls hasMetaclass ifTrue:[cls metaClass fileOutMethodsOn: aStream]. ]. doitsMark = 3 ifTrue:[self fileOutDoits: aStream].! ! !FilePackage methodsFor: 'initialize' stamp: 'yo 8/17/2004 09:53'! fromFileNamed: aName | stream | fullName := aName. stream := FileStream readOnlyFileNamed: aName. stream setConverterForCode. [self fileInFrom: stream] ensure:[stream close].! ! !FilePackage methodsFor: 'initialize' stamp: 'yo 8/17/2004 09:54'! fromFileNamed: aName encoding: encodingName | stream | fullName := aName. stream := FileStream readOnlyFileNamed: aName. stream converter: (TextConverter newForEncoding: encodingName). self fileInFrom: stream.! ! !FilePackage methodsFor: 'initialize' stamp: 'alain.plantec 5/28/2009 09:54'! initialize super initialize. classes := Dictionary new. classOrder := OrderedCollection new. sourceSystem := ''. doIts := OrderedCollection new.! ! !FilePackage methodsFor: 'reading' stamp: 'ar 7/16/2005 15:05'! fileInFrom: aStream | chgRec changes | changes := ChangeSet scanFile: aStream from: 0 to: aStream size. aStream close. ('Processing ', self packageName) displayProgressAt: Sensor cursorPoint from: 1 to: changes size during:[:bar| 1 to: changes size do:[:i| bar value: i. chgRec := changes at: i. self perform: (chgRec type copyWith: $:) asSymbol with: chgRec. ]. ].! ! !FilePackage methodsFor: 'private'! getClass: className | pseudoClass | (classes includesKey: className) ifTrue:[ ^classes at: className. ]. pseudoClass := PseudoClass new. pseudoClass name: className. classes at: className put: pseudoClass. ^pseudoClass.! ! !FilePackage methodsFor: 'private'! metaClassDefinition: string with: chgRec | tokens theClass | tokens := Scanner new scanTokens: string. theClass := self getClass: (tokens at: 1). theClass metaClass definition: string. classOrder add: theClass metaClass.! ! !FilePackage methodsFor: 'private' stamp: 'ar 4/10/2005 18:46'! msgClassComment: string with: chgRec | tokens theClass | tokens := Scanner new scanTokens: string. (tokens size = 3 and:[(tokens at: 3) isString]) ifTrue:[ theClass := self getClass: tokens first. ^theClass commentString: tokens last]. (tokens size = 4 and:[(tokens at: 3) asString = 'class' and:[(tokens at: 4) isString]]) ifTrue:[ theClass := self getClass: tokens first. theClass metaClass commentString: tokens last]. ! ! !FilePackage methodsFor: 'private' stamp: 'ar 4/10/2005 18:46'! possibleSystemSource: chgRec | tokens | sourceSystem isEmpty ifTrue:[ tokens := Scanner new scanTokens: chgRec string. (tokens size = 1 and:[tokens first isString]) ifTrue:[ sourceSystem := tokens first. ^self]]. doIts add: chgRec.! ! !FilePackage methodsFor: 'private'! removedMethod: string with: chgRec | class tokens | tokens := Scanner new scanTokens: string. (tokens size = 3 and:[(tokens at: 2) == #removeSelector: ]) ifTrue:[ class := self getClass: (tokens at: 1). ^class removeSelector: (tokens at: 3). ]. (tokens size = 4 and:[(tokens at: 2) == #class and:[(tokens at: 3) == #removeSelector:]]) ifTrue:[ class := self getClass: (tokens at: 1). ^class metaClass removeSelector: (tokens at: 4). ]. doIts add: chgRec! ! !FilePackage methodsFor: 'private'! sampleMethod " In an existing method there are always a number of changes. Other stuff will be deleted Or even better, some things may be just modified. "! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FilePackage class instanceVariableNames: ''! !FilePackage class methodsFor: 'conflict checker logging' stamp: 'dew 2/13/2004 23:33'! closeLog self logFileStream close. LogFileStream := nil.! ! !FilePackage class methodsFor: 'conflict checker logging' stamp: 'dew 2/14/2004 23:03'! logCr Transcript cr. self logFileStream nextPut: Character cr. ! ! !FilePackage class methodsFor: 'conflict checker logging' stamp: 'stephaneducasse 11/1/2005 15:39'! logFileStream LogFileStream ifNil: [LogFileStream := FileStream fileNamed: 'ConflictChecker.log'. LogFileStream setToEnd]. ^ LogFileStream! ! !FilePackage class methodsFor: 'conflict checker logging' stamp: 'dew 2/14/2004 23:03'! log: aString Transcript show: aString. self logFileStream nextPutAll: aString. ! ! !FilePackage class methodsFor: 'conflict checker preferences' stamp: 'dew 12/22/2002 00:19'! showIdenticalConflicts "(Not implemented yet. Need to implement versionFromChangeSet first for this to work for the 'false' case.)" "Set this to true if we want to show conflicts with methods which have an identical timestamp to the one being checked. This type of conflict usually just proves that you've already loaded the changeset (or some part of it) in your image." ^ true ! ! !FilePackage class methodsFor: 'conflict checker preferences' stamp: 'dew 2/13/2004 23:32'! verboseConflicts "Set this to true if we want to list each replacing (potentially conflicting) method being checked." ^ true! ! !FilePackage class methodsFor: 'instance creation' stamp: 'dew 10/26/2003 22:08'! conflictsWithUpdatedMethods: fullName | conflicts changeList | conflicts := (self fromFileNamed: fullName) conflictsWithUpdatedMethods. conflicts isEmpty ifTrue: [^ self]. changeList := ChangeList new. changeList changes: conflicts file: (FileDirectory default readOnlyFileNamed: fullName) close; openAsMorphName: 'Conflicts for ', (FileDirectory localNameFor: fullName) multiSelect: true ! ! !FilePackage class methodsFor: 'instance creation'! fromFileNamed: aName ^self new fromFileNamed: aName! ! !FilePackage class methodsFor: 'reader service' stamp: 'dew 12/16/2002 18:29'! fileReaderServicesForFile: fullName suffix: suffix ^(suffix = 'st') | (suffix = 'cs') | (suffix = '*') ifTrue: [self services] ifFalse: [#()]! ! !FilePackage class methodsFor: 'reader service' stamp: 'dew 12/16/2002 18:29'! serviceConflictsWithUpdatedMethods ^ SimpleServiceEntry provider: self label: 'conflicts with updated methods' selector: #conflictsWithUpdatedMethods: description: 'check for conflicts with more recently updated methods in the image, showing the conflicts in a transcript window' buttonLabel: 'conflicts'! ! !FilePackage class methodsFor: 'reader service' stamp: 'dew 12/16/2002 18:28'! services ^ Array with: self serviceConflictsWithUpdatedMethods! ! Object subclass: #FilePath instanceVariableNames: 'squeakPathName vmPathName converter' classVariableNames: '' poolDictionaries: '' category: 'Files-Directories'! !FilePath commentStamp: 'yo 10/19/2004 21:36' prior: 0! This class absorb the difference of internal and external representation of the file path. The idea is to keep the internal one as much as possible, and only when it goes to a primitive, the encoded file path, i.e. the native platform representation is passsed to the primitive. The converter used is obtained by "LanguageEnvironment defaultFileNameConverter". ! !FilePath methodsFor: 'conversion' stamp: 'yo 12/19/2003 21:10'! asSqueakPathName ^ self pathName. ! ! !FilePath methodsFor: 'conversion' stamp: 'ar 1/31/2005 11:16'! asString ^self asSqueakPathName! ! !FilePath methodsFor: 'conversion' stamp: 'yo 2/24/2005 18:45'! asVmPathName ^ vmPathName. ! ! !FilePath methodsFor: 'conversion' stamp: 'stephaneducasse 2/4/2006 20:31'! coverter: aTextConverter converter class ~= aTextConverter class ifTrue: [ converter := aTextConverter. vmPathName := squeakPathName convertToWithConverter: converter ]. ! ! !FilePath methodsFor: 'conversion' stamp: 'yo 12/19/2003 21:07'! pathName ^ squeakPathName. ! ! !FilePath methodsFor: 'conversion' stamp: 'stephaneducasse 2/4/2006 20:31'! pathName: p isEncoded: isEncoded converter := LanguageEnvironment defaultFileNameConverter. isEncoded ifTrue: [ squeakPathName := p convertFromWithConverter: converter. vmPathName := p. ] ifFalse: [ squeakPathName := p isOctetString ifTrue: [p asOctetString] ifFalse: [p]. vmPathName := squeakPathName convertToWithConverter: converter. ]. ! ! !FilePath methodsFor: 'conversion' stamp: 'yo 12/19/2003 21:07'! printOn: aStream aStream nextPutAll: 'FilePath('''. aStream nextPutAll: squeakPathName. aStream nextPutAll: ''')'. ! ! !FilePath methodsFor: 'file in/out' stamp: 'stephaneducasse 2/4/2006 20:31'! copySystemToVm (self class instVarNames includes: 'systemPathName') ifTrue: [ vmPathName := self instVarNamed: 'systemPathName'. ]. ! ! !FilePath methodsFor: 'testing' stamp: 'tpr 11/5/2004 11:39'! isNullPath "an empty path is used to represent the root path(s) when calling the primitive to list directory entries. Some users need to check for this and this is cleaner than grabbing the pathname and assuming it is a plain String" ^self pathName isEmpty! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FilePath class instanceVariableNames: ''! !FilePath class methodsFor: 'as yet unclassified' stamp: 'yo 2/24/2005 18:38'! classVersion ^ 1. ! ! !FilePath class methodsFor: 'instance creation' stamp: 'yo 12/19/2003 16:30'! pathName: pathName ^ self pathName: pathName isEncoded: false. ! ! !FilePath class methodsFor: 'instance creation' stamp: 'yo 12/19/2003 16:30'! pathName: pathName isEncoded: aBoolean ^ (self new) pathName: pathName isEncoded: aBoolean; yourself. ! ! Object subclass: #FileServices instanceVariableNames: '' classVariableNames: 'FileReaderRegistry' poolDictionaries: '' category: 'System-FileRegistry'! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileServices class instanceVariableNames: ''! !FileServices class methodsFor: 'accessing' stamp: 'ar 7/16/2005 16:59'! allRegisteredServices "self allRegisteredServices" | col | col := OrderedCollection new. self registeredFileReaderClasses do: [:each | col addAll: (each services)]. ^ col! ! !FileServices class methodsFor: 'accessing' stamp: 'ar 9/29/2005 12:30'! initialize "FileServices initialize" Smalltalk allClassesDo:[:aClass| (aClass class includesSelector: #fileReaderServicesForFile:suffix:) ifTrue:[self registerFileReader: aClass]].! ! !FileServices class methodsFor: 'accessing' stamp: 'ar 7/16/2005 17:00'! isReaderNamedRegistered: aSymbol "return if a given reader class has been registered. Note that this is on purpose that the argument is a symbol and not a class" ^ (self registeredFileReaderClasses collect: [:each | each name]) includes: aSymbol ! ! !FileServices class methodsFor: 'accessing' stamp: 'ar 7/16/2005 17:00'! itemsForDirectory: aFileDirectory "Answer a list of services appropriate when no file is selected." | services | services := OrderedCollection new. self registeredFileReaderClasses do: [:reader | reader ifNotNil: [services addAll: (reader fileReaderServicesForDirectory: aFileDirectory) ]]. ^ services! ! !FileServices class methodsFor: 'accessing' stamp: 'ar 7/16/2005 17:00'! itemsForFile: fullName "Answer a list of services appropriate for a file of the given full name" | services suffix | suffix := self suffixOf: fullName. services := OrderedCollection new. self registeredFileReaderClasses do: [:reader | reader ifNotNil: [services addAll: (reader fileReaderServicesForFile: fullName suffix: suffix)]]. ^ services! ! !FileServices class methodsFor: 'accessing' stamp: 'ar 7/16/2005 16:59'! registeredFileReaderClasses FileReaderRegistry ifNil: [FileReaderRegistry := OrderedCollection new]. ^ FileReaderRegistry! ! !FileServices class methodsFor: 'accessing' stamp: 'ar 7/16/2005 17:00'! registerFileReader: aProviderClass "register the given class as providing services for reading files" | registeredReaders | registeredReaders := self registeredFileReaderClasses. (registeredReaders includes: aProviderClass) ifFalse: [ registeredReaders addLast: aProviderClass ]! ! !FileServices class methodsFor: 'accessing' stamp: 'ar 7/17/2005 02:36'! removeObsolete "FileServices removeObsolete" self registeredFileReaderClasses copy do:[:cls| cls isObsolete ifTrue:[self unregisterFileReader: cls]]! ! !FileServices class methodsFor: 'accessing' stamp: 'ar 7/16/2005 17:00'! unregisterFileReader: aProviderClass "unregister the given class as providing services for reading files" self registeredFileReaderClasses remove: aProviderClass ifAbsent: [nil]! ! ReadWriteStream subclass: #FileStream instanceVariableNames: 'rwmode' classVariableNames: '' poolDictionaries: '' category: 'Files-Kernel'! !FileStream commentStamp: '' prior: 0! I represent a Stream that accesses a FilePage from a File. One use for my instance is to access larger "virtual Strings" than can be stored contiguously in main memory. I restrict the objects stored and retrieved to be Integers or Characters. An end of file pointer terminates reading; it can be extended by writing past it, or the file can be explicitly truncated. To use the file system for most applications, you typically create a FileStream. This is done by sending a message to a FileDirectory (file:, oldFile:, newFile:, rename:newName:) which creates an instance of me. Accesses to the file are then done via my instance. *** On DOS, files cannot be shortened!! *** To overwrite a file with a shorter one, first delete the old file (FileDirectory deleteFilePath: 'Hard Disk:aFolder:dataFolder:foo') or (aFileDirectory deleteFileNamed: 'foo'). Then write your new shorter version.! !FileStream methodsFor: '*network-uri' stamp: 'bf 1/27/2006 18:01'! uri ^self directory uri resolveRelativeURI: self localName encodeForHTTP! ! !FileStream methodsFor: '*network-uri' stamp: 'fbs 2/2/2005 13:23'! url "Convert my path into a file:// type url String." ^self asUrl asString! ! !FileStream methodsFor: 'accessing' stamp: 'stephaneducasse 2/4/2006 20:31'! contents "Return the contents of the receiver. Do not close or otherwise touch the receiver. Return data in whatever mode the receiver is in (e.g., binary or text)." | s savePos | savePos := self position. self position: 0. s := self next: self size. self position: savePos. ^s! ! !FileStream methodsFor: 'accessing' stamp: 'stephaneducasse 2/4/2006 20:31'! contentsOfEntireFile "Read all of the contents of the receiver." | s binary | self readOnly. binary := self isBinary. self reset. "erases knowledge of whether it is binary" binary ifTrue: [self binary]. s := self next: self size. self close. ^s! ! !FileStream methodsFor: 'accessing' stamp: 'nk 2/22/2001 17:07'! directoryEntry ^self directory entryAt: self localName! ! !FileStream methodsFor: 'accessing' stamp: 'ar 1/25/2001 19:33'! mimeTypes ^FileDirectory default mimeTypesFor: self name.! ! !FileStream methodsFor: 'accessing' stamp: 'stephaneducasse 2/4/2006 20:31'! next (position >= readLimit and: [self atEnd]) ifTrue: [^nil] ifFalse: [^collection at: (position := position + 1)]! ! !FileStream methodsFor: 'accessing' stamp: 'stephaneducasse 2/4/2006 20:31'! next: anInteger | newCollection howManyRead increment | newCollection := collection species new: anInteger. howManyRead := 0. [howManyRead < anInteger] whileTrue: [self atEnd ifTrue: [(howManyRead + 1) to: anInteger do: [:i | newCollection at: i put: (self next)]. ^newCollection]. increment := (readLimit - position) min: (anInteger - howManyRead). newCollection replaceFrom: (howManyRead + 1) to: (howManyRead := howManyRead + increment) with: collection startingAt: (position + 1). position := position + increment]. ^newCollection! ! !FileStream methodsFor: 'accessing'! nextPut: aByte "1/31/96 sw: subclassResponsibility" self subclassResponsibility! ! !FileStream methodsFor: 'accessing'! nextPutAll: aCollection "1/31/96 sw: made subclass responsibility" self subclassResponsibility! ! !FileStream methodsFor: 'accessing'! size "Answer the size of the file in characters. 1/31/96 sw: made subclass responsibility" self subclassResponsibility! ! !FileStream methodsFor: 'converting' stamp: 'tk 2/4/2000 09:16'! asBinaryOrTextStream "I can switch between binary and text data" ^ self! ! !FileStream methodsFor: 'editing' stamp: 'di 5/20/1998 23:20'! edit "Create and schedule an editor on this file." FileList openEditorOn: self editString: nil. ! ! !FileStream methodsFor: 'editing' stamp: 'stephaneducasse 2/4/2006 20:31'! viewGZipContents "View the contents of a gzipped file" | stringContents | self binary. stringContents := self contentsOfEntireFile. Cursor wait showWhile: [stringContents := (GZipReadStream on: stringContents) upToEnd]. stringContents := stringContents asString withSqueakLineEndings. Workspace new contents: stringContents; openLabel: 'Decompressed contents of: ', self localName! ! !FileStream methodsFor: 'file accessing' stamp: 'gk 2/10/2004 13:21'! asUrl "Convert my path into a file:// type url - a FileUrl." ^FileUrl pathParts: (self directory pathParts copyWith: self localName)! ! !FileStream methodsFor: 'file accessing'! file "Answer the file for the page the receiver is streaming over. 1/31/96 sw: made subclass responsibility" self subclassResponsibility! ! !FileStream methodsFor: 'file accessing' stamp: 'jm 12/5/97 12:53'! localName ^ FileDirectory localNameFor: self name ! ! !FileStream methodsFor: 'file accessing'! name "Answer the name of the file for the page the receiver is streaming over. 1/31/96 sw: made subclassResponsibility" self subclassResponsibility! ! !FileStream methodsFor: 'file modes' stamp: 'jm 9/21/1998 13:01'! ascii "Set this file to ascii (text) mode." self subclassResponsibility ! ! !FileStream methodsFor: 'file modes' stamp: 'jm 9/21/1998 12:59'! binary "Set this file to binary mode." self subclassResponsibility ! ! !FileStream methodsFor: 'file modes' stamp: 'jm 9/21/1998 12:59'! readOnly "Set this file's mode to read-only." self subclassResponsibility ! ! !FileStream methodsFor: 'file modes' stamp: 'mir 8/24/2004 17:58'! readOnlyStream ^self readOnly! ! !FileStream methodsFor: 'file modes' stamp: 'jm 9/21/1998 13:00'! readWrite "Set this file's mode to read-write." self subclassResponsibility ! ! !FileStream methodsFor: 'file modes' stamp: 'jm 9/21/1998 13:01'! text "Set this file to text (ascii) mode." self ascii. ! ! !FileStream methodsFor: 'file open/close' stamp: 'jm 9/21/1998 13:02'! close "Close this file." self subclassResponsibility ! ! !FileStream methodsFor: 'file open/close' stamp: 'jm 9/21/1998 13:02'! closed "Answer true if this file is closed." self subclassResponsibility ! ! !FileStream methodsFor: 'file open/close' stamp: 'jm 9/21/1998 13:03'! flush "When writing, flush the current buffer out to disk." self subclassResponsibility ! ! !FileStream methodsFor: 'file open/close' stamp: 'jm 9/21/1998 13:04'! reopen "Ensure that the receiver is open, re-open it if necessary." "Details: Files that were open when a snapshot occurs are no longer valid when the snapshot is resumed. This operation re-opens the file if that has happened." self subclassResponsibility ! ! !FileStream methodsFor: 'filein/out' stamp: 'sw 11/19/1998 16:42'! fileIn "Guarantee that the receiver is readOnly before fileIn for efficiency and to eliminate remote sharing conflicts." self readOnly. self fileInAnnouncing: 'Loading ', self localName! ! !FileStream methodsFor: 'filein/out' stamp: 'tk 1/21/2000 16:38'! fileInObjectAndCode "Read the file directly, do not use an RWBinaryOrTextStream." self text. ^ super fileInObjectAndCode ! ! !FileStream methodsFor: 'filein/out' stamp: 'di 10/31/2001 12:07'! fileIntoNewChangeSet "File all of my contents into a new change set." self readOnly. ChangeSorter newChangesFromStream: self named: (self localName) ! ! !FileStream methodsFor: 'positioning'! position "Answer the current character position in the file. 1/31/96 sw: subclassResponsibility" self subclassResponsibility! ! !FileStream methodsFor: 'positioning'! position: pos "Set the current character position in the file to pos. 1/31/96 sw: made subclassResponsibility" self subclassResponsibility! ! !FileStream methodsFor: 'positioning'! reset "Set the current character position to the beginning of the file. 1/31/96 sw: subclassResponsibility" self subclassResponsibility! ! !FileStream methodsFor: 'positioning'! setToEnd "Set the current character position to the end of the File. The same as self position: self size. 1/31/96 sw: made subclassResponsibility" self subclassResponsibility! ! !FileStream methodsFor: 'positioning'! skip: n "Set the character position to n characters from the current position. Error if not enough characters left in the file 1/31/96 sw: made subclassResponsibility." self subclassResponsibility! ! !FileStream methodsFor: 'positioning' stamp: 'JMM 5/24/2001 22:58'! truncate: pos "Truncate file to pos" self subclassResponsibility! ! !FileStream methodsFor: 'printing' stamp: 'tk 12/5/2001 09:12'! longPrintOn: aStream "Do nothing, so it will print short. Called to print the error file. If the error was in a file operation, we can't read the contents of that file. Just print its name instead." ! ! !FileStream methodsFor: 'printing' stamp: 'tk 12/5/2001 09:32'! longPrintOn: aStream limitedTo: sizeLimit indent: indent "Do nothing, so it will print short. Called to print the error file. If the error was in a file operation, we can't read the contents of that file. Just print its name instead." aStream cr! ! !FileStream methodsFor: 'printing'! printOn: aStream super printOn: aStream. aStream nextPutAll: ' on '. self file printOn: aStream! ! !FileStream methodsFor: 'remote file compatibility' stamp: 'RAA 9/24/2000 18:00'! dataIsValid self flag: #bob. "we needed this if a remote stream, but could be local as well"! ! !FileStream methodsFor: 'testing'! atEnd "Answer true if the current position is >= the end of file position. 1/31/96 sw: subclassResponsibility" self subclassResponsibility! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileStream class instanceVariableNames: ''! !FileStream class methodsFor: '*network-uri' stamp: 'JMM 2/3/2008 14:17'! oldFileFullyNamed: t1 ^ self concreteStream oldFileNamed: t1! ! !FileStream class methodsFor: '*network-uri' stamp: 'JMM 2/3/2008 14:14'! readOnlyFileFullyNamed: t1 ^ self concreteStream readOnlyFileFullyNamed: t1! ! !FileStream class methodsFor: 'browser requests' stamp: 'stephaneducasse 2/4/2006 20:32'! httpPostDocument: url args: argsDict | argString | argString := argsDict ifNotNil: [argString := HTTPSocket argString: argsDict] ifNil: ['']. ^self post: argString url: url , argString ifError: [self halt]! ! !FileStream class methodsFor: 'browser requests' stamp: 'PeterHugossonMiller 9/3/2009 01:33'! httpPostMultipart: url args: argsDict | mimeBorder argsStream crLf fieldValue resultStream result | " do multipart/form-data encoding rather than x-www-urlencoded " crLf := String crlf. mimeBorder := '----squeak-', Time millisecondClockValue printString, '-stuff-----'. "encode the arguments dictionary" argsStream := String new writeStream. argsDict associationsDo: [:assoc | assoc value do: [ :value | "print the boundary" argsStream nextPutAll: '--', mimeBorder, crLf. " check if it's a non-text field " argsStream nextPutAll: 'Content-disposition: form-data; name="', assoc key, '"'. (value isKindOf: MIMEDocument) ifFalse: [fieldValue := value] ifTrue: [argsStream nextPutAll: ' filename="', value url pathForFile, '"', crLf, 'Content-Type: ', value contentType. fieldValue := (value content ifNil: [(FileStream fileNamed: value url pathForFile) contentsOfEntireFile] ifNotNil: [value content]) asString]. " Transcript show: 'field=', key, '; value=', fieldValue; cr. " argsStream nextPutAll: crLf, crLf, fieldValue, crLf. ]]. argsStream nextPutAll: '--', mimeBorder, '--'. resultStream := self post: ('Content-type: multipart/form-data; boundary=', mimeBorder, crLf, 'Content-length: ', argsStream contents size printString, crLf, crLf, argsStream contents) url: url ifError: [^'Error in post ' url asString]. "get the header of the reply" result := resultStream upToEnd. ^MIMEDocument content: result! ! !FileStream class methodsFor: 'browser requests' stamp: 'mir 2/2/2001 14:23'! post: data target: target url: url ifError: errorBlock ^self concreteStream new post: data target: target url: url ifError: errorBlock! ! !FileStream class methodsFor: 'browser requests' stamp: 'mir 2/2/2001 14:23'! post: data url: url ifError: errorBlock ^self post: data target: nil url: url ifError: errorBlock! ! !FileStream class methodsFor: 'browser requests' stamp: 'stephaneducasse 2/4/2006 20:32'! requestURL: url target: target "FileStream requestURL:'http://isgwww.cs.uni-magdeburg.de/~raab' target: ':=blank' " ^self concreteStream new requestURL: url target: target! ! !FileStream class methodsFor: 'browser requests'! requestURLStream: url "FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'" ^self concreteStream new requestURLStream: url! ! !FileStream class methodsFor: 'browser requests'! requestURLStream: url ifError: errorBlock "FileStream requestURLStream:'http://isgwww.cs.uni-magdeburg.de/~raab'" ^self concreteStream new requestURLStream: url ifError: errorBlock! ! !FileStream class methodsFor: 'concrete classes' stamp: 'yo 7/5/2004 20:18'! concreteStream "Who should we really direct class queries to? " ^ MultiByteFileStream. ! ! !FileStream class methodsFor: 'dnd requests' stamp: 'ar 1/10/2001 19:41'! requestDropStream: dropIndex "Request a read-only stream for some file that was dropped onto Squeak" ^self concreteStream new requestDropStream: dropIndex.! ! !FileStream class methodsFor: 'file reader services' stamp: 'yo 7/5/2004 21:01'! cs ^ 'cs' clone. ! ! !FileStream class methodsFor: 'file reader services' stamp: 'stephaneducasse 2/4/2006 20:32'! fileIn: fullName "File in the entire contents of the file specified by the name provided" | ff | fullName ifNil: [^ Beeper beep]. ff := self readOnlyFileNamed: (GZipReadStream uncompressedFileName: fullName). ff fileIn. ! ! !FileStream class methodsFor: 'file reader services' stamp: 'nk 7/16/2003 15:49'! fileReaderServicesForFile: fullName suffix: suffix "Answer services for the given file" ^ ((self isSourceFileSuffix: suffix) or: [ suffix = '*' ]) ifTrue: [{self serviceRemoveLineFeeds. self serviceFileIn}] ifFalse: [#()]! ! !FileStream class methodsFor: 'file reader services' stamp: 'tpr 9/15/2005 15:06'! isSourceFileSuffix: suffix ^ FileStream sourceFileSuffixes includes: suffix ! ! !FileStream class methodsFor: 'file reader services' stamp: 'yo 7/5/2004 21:00'! multiCs ^ 'mcs' clone. ! ! !FileStream class methodsFor: 'file reader services' stamp: 'yo 7/5/2004 21:01'! multiSt ^ 'mst' clone. ! ! !FileStream class methodsFor: 'file reader services' stamp: 'stephaneducasse 2/4/2006 20:32'! removeLineFeeds: fullName | fileContents | fileContents := ((FileStream readOnlyFileNamed: fullName) wantsLineEndConversion: true) contentsOfEntireFile. (FileStream newFileNamed: fullName) nextPutAll: fileContents; close.! ! !FileStream class methodsFor: 'file reader services' stamp: 'sw 2/17/2002 01:38'! serviceFileIn "Answer a service for filing in an entire file" ^ SimpleServiceEntry provider: self label: 'fileIn entire file' selector: #fileIn: description: 'file in the entire contents of the file, which is expected to contain Smalltalk code in fileout ("chunk") format' buttonLabel: 'filein'! ! !FileStream class methodsFor: 'file reader services' stamp: 'nk 11/26/2002 12:49'! serviceRemoveLineFeeds "Answer a service for removing linefeeds from a file" ^ FileModifyingSimpleServiceEntry provider: self label: 'remove line feeds' selector: #removeLineFeeds: description: 'remove line feeds in file' buttonLabel: 'remove lfs'! ! !FileStream class methodsFor: 'file reader services' stamp: 'sd 2/1/2002 22:28'! services ^ Array with: self serviceRemoveLineFeeds with: self serviceFileIn ! ! !FileStream class methodsFor: 'file reader services' stamp: 'yo 7/7/2004 09:43'! sourceFileSuffixes ^ {FileStream st. FileStream cs. FileStream multiSt. FileStream multiCs} asSet asArray. ! ! !FileStream class methodsFor: 'file reader services' stamp: 'yo 7/5/2004 21:01'! st ^ 'st' clone. ! ! !FileStream class methodsFor: 'file reader services' stamp: 'sd 4/25/2008 15:31'! writeSourceCodeFrom: aStream baseName: baseName isSt: stOrCsFlag | extension converter f fileName | aStream contents isAsciiString ifTrue: [ stOrCsFlag ifTrue: [ extension := (FileDirectory dot, FileStream st). ] ifFalse: [ extension := (FileDirectory dot, FileStream cs). ]. converter := MacRomanTextConverter new. ] ifFalse: [ stOrCsFlag ifTrue: [ extension := (FileDirectory dot, FileStream st "multiSt"). ] ifFalse: [ extension := (FileDirectory dot, FileStream cs "multiCs"). ]. converter := UTF8TextConverter new. ]. fileName := baseName, extension. f := FileStream newFileNamed: fileName. f ifNil: [^ self error: 'Cannot open file']. (converter isMemberOf: UTF8TextConverter) ifTrue: [f binary. UTF8TextConverter writeBOMOn: f]. f text. f converter: converter. f nextPutAll: aStream contents. f close. ! ! !FileStream class methodsFor: 'initialization' stamp: 'GabrielOmarCotelli 6/4/2009 20:36'! unload FileServices unregisterFileReader: self ! ! !FileStream class methodsFor: 'initialize-release' stamp: 'GabrielOmarCotelli 6/4/2009 20:35'! initialize FileServices registerFileReader: self! ! !FileStream class methodsFor: 'instance creation' stamp: 'CdG 10/19/2005 23:21'! detectFile: aBlock do: anotherBlock | file | file := aBlock value. ^ file ifNil: [ nil ] ifNotNil: [ [anotherBlock value: file] ensure: [file close]]! ! !FileStream class methodsFor: 'instance creation'! fileNamed: fileName ^ self concreteStream fileNamed: (self fullName: fileName)! ! !FileStream class methodsFor: 'instance creation' stamp: 'bkv 1/22/2004 17:28'! fileNamed: fileName do: aBlock "Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})). It's time Squeak had it, too.'' Returns the result of aBlock." ^ self detectFile: [ self fileNamed: fileName ] do: aBlock! ! !FileStream class methodsFor: 'instance creation' stamp: 'tpr 10/16/2001 12:49'! forceNewFileNamed: fileName "Create a new file with the given name, and answer a stream opened for writing on that file. If the file already exists, delete it without asking before creating the new file." ^self concreteStream forceNewFileNamed: fileName! ! !FileStream class methodsFor: 'instance creation' stamp: 'bkv 1/22/2004 17:29'! forceNewFileNamed: fileName do: aBlock "Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})). It's time Squeak had it, too.'' Returns the result of aBlock." ^ self detectFile: [ self forceNewFileNamed: fileName ] do: aBlock! ! !FileStream class methodsFor: 'instance creation'! fullName: fileName ^ FileDirectory default fullNameFor: fileName! ! !FileStream class methodsFor: 'instance creation' stamp: 'TPR 8/26/1999 10:49'! isAFileNamed: fName "return whether a file exists with the given name" ^self concreteStream isAFileNamed: (self fullName: fName)! ! !FileStream class methodsFor: 'instance creation' stamp: 'di 2/15/98 14:03'! new ^ self basicNew! ! !FileStream class methodsFor: 'instance creation'! newFileNamed: fileName ^ self concreteStream newFileNamed: (self fullName: fileName)! ! !FileStream class methodsFor: 'instance creation' stamp: 'bkv 1/22/2004 17:28'! newFileNamed: fileName do: aBlock "Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})). It's time Squeak had it, too.'' Returns the result of aBlock." ^ self detectFile: [ self newFileNamed: fileName ] do: aBlock! ! !FileStream class methodsFor: 'instance creation'! oldFileNamed: fileName ^ self concreteStream oldFileNamed: (self fullName: fileName)! ! !FileStream class methodsFor: 'instance creation' stamp: 'bkv 1/22/2004 17:29'! oldFileNamed: fileName do: aBlock "Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})). It's time Squeak had it, too.'' Returns the result of aBlock." ^ self detectFile: [ self oldFileNamed: fileName ] do: aBlock! ! !FileStream class methodsFor: 'instance creation' stamp: 'stephaneducasse 2/4/2006 20:32'! oldFileOrNoneNamed: fileName "If the file exists, answer a read-only FileStream on it. If it doesn't, answer nil." | fullName | fullName := self fullName: fileName. (self concreteStream isAFileNamed: fullName) ifTrue: [^ self concreteStream readOnlyFileNamed: fullName] ifFalse: [^ nil]. ! ! !FileStream class methodsFor: 'instance creation'! readOnlyFileNamed: fileName ^ self concreteStream readOnlyFileNamed: (self fullName: fileName)! ! !FileStream class methodsFor: 'instance creation' stamp: 'bkv 1/22/2004 17:29'! readOnlyFileNamed: fileName do: aBlock "Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})). It's time Squeak had it, too.'' Returns the result of aBlock." ^ self detectFile: [ self readOnlyFileNamed: fileName ] do: aBlock! ! !FileStream class methodsFor: 'utils' stamp: 'stephane.ducasse 7/10/2009 16:30'! convertCRtoLF: fileName "Convert the given file to LF line endings. Put the result in a file with the extention '.lf'" | in out c justPutCR | in := (self readOnlyFileNamed: fileName) binary. out := (self newFileNamed: fileName, '.lf') binary. justPutCR := false. [in atEnd] whileFalse: [ c := in next. c = 10 ifTrue: [ out nextPut: 13. justPutCR := true] ifFalse: [ (justPutCR and: [c = 10]) ifFalse: [out nextPut: c]. justPutCR := false]]. in close. out close. ! ! !FileStream class methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 07:51'! writeSourceCodeFrom: aStream baseName: baseName isSt: stOrCsFlag useHtml: useHtml | extension converter f fileName | self deprecated: 'Use ''writeSourceCodeFrom: aStream baseName: baseName isSt: stOrCsFlag'' instead.'. aStream contents isAsciiString ifTrue: [ stOrCsFlag ifTrue: [ extension := (FileDirectory dot, FileStream st). ] ifFalse: [ extension := (FileDirectory dot, FileStream cs). ]. converter := MacRomanTextConverter new. ] ifFalse: [ stOrCsFlag ifTrue: [ extension := (FileDirectory dot, FileStream st "multiSt"). ] ifFalse: [ extension := (FileDirectory dot, FileStream cs "multiCs"). ]. converter := UTF8TextConverter new. ]. fileName := useHtml ifTrue: [baseName, '.html'] ifFalse: [baseName, extension]. f := FileStream newFileNamed: fileName. f ifNil: [^ self error: 'Cannot open file']. (converter isMemberOf: UTF8TextConverter) ifTrue: [f binary. UTF8TextConverter writeBOMOn: f]. f text. f converter: converter. f nextPutAll: aStream contents. f close. ! ! Error subclass: #FileStreamException instanceVariableNames: 'fileName' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! !FileStreamException methodsFor: 'exceptionbuilder' stamp: 'mir 2/23/2000 20:13'! fileName: aFileName fileName := aFileName! ! !FileStreamException methodsFor: 'exceptiondescription' stamp: 'mir 2/25/2000 17:29'! fileName ^fileName! ! !FileStreamException methodsFor: 'exceptiondescription' stamp: 'mir 2/23/2000 20:13'! isResumable "Determine whether an exception is resumable." ^true! ! !FileStreamException methodsFor: 'exceptiondescription' stamp: 'mir 2/23/2000 20:14'! messageText "Return an exception's message text." ^messageText == nil ifTrue: [fileName printString] ifFalse: [messageText]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileStreamException class instanceVariableNames: ''! !FileStreamException class methodsFor: 'exceptioninstantiator' stamp: 'mir 2/23/2000 20:12'! fileName: aFileName ^self new fileName: aFileName! ! ClassTestCase subclass: #FileStreamTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Files'! !FileStreamTest methodsFor: 'as yet unclassified' stamp: 'SergeStinckwich 5/27/2008 23:14'! testDetectFileDo [(FileDirectory default forceNewFileNamed: 'filestream.tst') nextPutAll: '42'; close. FileStream detectFile: [FileDirectory default oldFileNamed: 'filestream.tst'] do: [:file | self assert: file notNil. self deny: file closed. self assert: file contentsOfEntireFile = '42']] ensure: [FileDirectory default deleteFileNamed: 'filestream.tst' ifAbsent: nil]! ! Url subclass: #FileUrl instanceVariableNames: 'host path isAbsolute' classVariableNames: '' poolDictionaries: '' category: 'Network-Url'! !FileUrl commentStamp: 'gk 10/21/2005 10:58' prior: 0! This class models a file URL according to (somewhat) RFC1738, see http://www.w3.org/Addressing/rfc1738.txt Here is the relevant part of the RFC: 3.10 FILES The file URL scheme is used to designate files accessible on a particular host computer. This scheme, unlike most other URL schemes, does not designate a resource that is universally accessible over the Internet. A file URL takes the form: file:/// where is the fully qualified domain name of the system on which the is accessible, and is a hierarchical directory path of the form //.../. For example, a VMS file DISK$USER:[MY.NOTES]NOTE123456.TXT might become As a special case, can be the string "localhost" or the empty string; this is interpreted as `the machine from which the URL is being interpreted'. The file URL scheme is unusual in that it does not specify an Internet protocol or access method for such files; as such, its utility in network protocols between hosts is limited. From the above we can conclude that the RFC says that the part never starts or ends with a slash and is always absolute. If the last name can be a directory instead of a file is not specified clearly. The path is stored as a SequenceableCollection of path parts. Notes regarding non RFC features in this class: - If the last path part is the empty string, then the FileUrl is referring to a directory. This is also shown with a trailing slash when converted to a String. - The FileUrl has an attribute isAbsolute which signals if the path should be considered absolute or relative to the current directory. This distinction is not visible in the String representation of FileUrl, since the RFC does not have that. - Fragment is supported (kept for historical reasons) ! !FileUrl methodsFor: 'access' stamp: 'gk 10/21/2005 10:21'! directoryUrl "The path always has at least one element so this works." ^self copy path: (path copyFrom: 1 to: path size - 1)! ! !FileUrl methodsFor: 'access' stamp: 'gk 10/21/2005 11:14'! fileName "Return the last part of the path, most often a filename but can also be a directory." ^self path last! ! !FileUrl methodsFor: 'access' stamp: 'ar 10/13/2004 17:54'! pathForFile "Path using local file system's delimiter. $\ or $:" ^FileDirectory default pathFromUrl: self! ! !FileUrl methodsFor: 'accessing' stamp: 'gk 2/10/2004 10:16'! host "Return the host name, either 'localhost', '', or a fully qualified domain name." ^host ifNil: ['']! ! !FileUrl methodsFor: 'accessing' stamp: 'gk 2/12/2004 16:22'! host: hostName "Set the host name, either 'localhost', '', or a fully qualified domain name." host := hostName! ! !FileUrl methodsFor: 'accessing' stamp: 'gk 10/21/2005 11:12'! isAbsolute "Should the path be considered absolute to the filesystem instead of relative to the default directory?" ^isAbsolute! ! !FileUrl methodsFor: 'accessing' stamp: 'gk 10/21/2005 11:13'! isAbsolute: aBoolean "Set if the path should be considered absolute to the filesystem instead of relative to the default directory." isAbsolute := aBoolean! ! !FileUrl methodsFor: 'accessing' stamp: 'gk 2/10/2004 00:15'! path "Return an ordered collection of the path elements." ^path! ! !FileUrl methodsFor: 'accessing' stamp: 'gk 10/21/2005 11:11'! path: aCollection "Set the collection of path elements." path := aCollection! ! !FileUrl methodsFor: 'classification' stamp: 'gk 2/10/2004 10:34'! scheme ^self class schemeName! ! !FileUrl methodsFor: 'classification' stamp: 'gk 2/10/2004 10:34'! schemeName ^self class schemeName! ! !FileUrl methodsFor: 'copying' stamp: 'gk 10/21/2005 11:15'! copy "Be sure not to share the path with the copy." ^self clone path: path copy! ! !FileUrl methodsFor: 'downloading' stamp: 'gk 2/10/2004 13:06'! default "Use the default local Squeak file directory." | local | local := self class pathParts: (FileDirectory default pathParts), #('') isAbsolute: true. self privateInitializeFromText: self pathString relativeTo: local. "sets absolute also"! ! !FileUrl methodsFor: 'downloading' stamp: 'ls 8/4/1998 20:42'! hasContents ^true! ! !FileUrl methodsFor: 'downloading' stamp: 'PeterHugossonMiller 9/3/2009 01:33'! retrieveContents | file pathString s type entries | pathString := self pathForFile. "We pursue the execution even if the file is not found" [file := FileStream readOnlyFileNamed: pathString. type := file mimeTypes. type ifNotNil: [type := type first]. type ifNil: [type := MIMEDocument guessTypeFromName: self path last]. ^MIMELocalFileDocument contentStream: file mimeType: type] on: FileDoesNotExistException do:[:ex| ]. "see if it's a directory... If not, then nil is returned" entries := [(FileDirectory on: pathString) entries] on: InvalidDirectoryError do: [:ex| ^ nil]. s := String new writeStream. (pathString endsWith: '/') ifFalse: [ pathString := pathString, '/' ]. s nextPutAll: 'Directory Listing for ', pathString, ''. s nextPutAll: '

Directory Listing for ', pathString, '

'. s nextPutAll: ''. ^MIMEDocument contentType: 'text/html' content: s contents url: ('file://', pathString)! ! !FileUrl methodsFor: 'paths' stamp: 'gk 2/10/2004 00:19'! pathDirString "Path to directory as url, using slash as delimiter. Filename is left out." ^String streamContents: [ :s | isAbsolute ifTrue: [ s nextPut: $/ ]. 1 to: self path size - 1 do: [ :ii | s nextPutAll: (path at: ii); nextPut: $/]]! ! !FileUrl methodsFor: 'paths' stamp: 'gk 10/21/2005 10:01'! pathForDirectory "Path using local file system's pathname delimiter. DOS paths with drive letters should not be prepended with a delimiter even though they are absolute. Filename is left out." | delimiter | delimiter := FileDirectory default pathNameDelimiter. ^String streamContents: [ :s | (self isAbsolute and: [self firstPartIsDriveLetter not]) ifTrue: [ s nextPut: delimiter ]. 1 to: self path size - 1 do: [ :ii | s nextPutAll: (path at: ii); nextPut: delimiter]]! ! !FileUrl methodsFor: 'paths' stamp: 'gk 2/10/2004 10:22'! pathString "Path as it appears in a URL with $/ as delimiter." | first | ^String streamContents: [ :s | "isAbsolute ifTrue:[ s nextPut: $/ ]." first := true. self path do: [ :p | first ifFalse: [ s nextPut: $/ ]. first := false. s nextPutAll: p encodeForHTTP ] ]! ! !FileUrl methodsFor: 'printing' stamp: 'fbs 2/2/2005 13:09'! printOn: aStream "Return the FileUrl according to RFC1738 plus supporting fragments: 'file:///#' Note that being '' is equivalent to 'localhost'. Note: The pathString can not start with a leading $/ to indicate an 'absolute' file path. This is not according to RFC1738 where the path should have no leading or trailing slashes, and always be considered absolute relative to the filesystem." aStream nextPutAll: self schemeName, '://'. host ifNotNil: [aStream nextPutAll: host]. aStream nextPut: $/; nextPutAll: self pathString. fragment ifNotNil: [aStream nextPut: $#; nextPutAll: fragment encodeForHTTP].! ! !FileUrl methodsFor: 'testing' stamp: 'gk 2/9/2004 20:32'! firstPartIsDriveLetter "Return true if the first part of the path is a letter followed by a $: like 'C:' " | firstPart | path isEmpty ifTrue: [^false]. firstPart := path first. ^firstPart size = 2 and: [ firstPart first isLetter and: [firstPart last = $:]]! ! !FileUrl methodsFor: 'private-initialization' stamp: 'gk 2/10/2004 13:05'! host: aHostString pathParts: aCollection isAbsolute: aBoolean host := aHostString. path := aCollection. isAbsolute := aBoolean! ! !FileUrl methodsFor: 'private-initialization' stamp: 'gk 2/12/2004 16:01'! initializeFromPathString: aPathString " is a file path as a String. We construct a path collection using various heuristics." | pathString hasDriveLetter | pathString := aPathString. pathString isEmpty ifTrue: [pathString := '/']. path := (pathString findTokens: '/') collect: [:token | token unescapePercents]. "A path like 'C:' refers in practice to 'c:/'" ((pathString endsWith: '/') or: [(hasDriveLetter := self firstPartIsDriveLetter) and: [path size = 1]]) ifTrue: [path add: '']. "Decide if we are absolute by checking for leading $/ or beginning with drive letter. Smarts for other OSes?" self isAbsolute: ((pathString beginsWith: '/') or: [hasDriveLetter ifNil: [self firstPartIsDriveLetter]])! ! !FileUrl methodsFor: 'private-initialization' stamp: 'gk 2/10/2004 13:04'! pathParts: aCollection isAbsolute: aBoolean ^self host: nil pathParts: aCollection isAbsolute: aBoolean! ! !FileUrl methodsFor: 'private-initialization' stamp: 'gk 2/12/2004 16:11'! privateInitializeFromText: aString "Calculate host and path from a file URL in String format. Some malformed formats are allowed and interpreted by guessing." | schemeName pathString bare hasDriveLetter stream char i | bare := aString withBlanksTrimmed. schemeName := Url schemeNameForString: bare. (schemeName isNil or: [schemeName ~= self schemeName]) ifTrue: [ host := ''. pathString := bare] ifFalse: [ "First remove schemeName and colon" bare := bare copyFrom: (schemeName size + 2) to: bare size. "A proper file URL then has two slashes before host, A malformed URL is interpreted as using syntax file:." (bare beginsWith: '//') ifTrue: [i := bare indexOf: $/ startingAt: 3. i=0 ifTrue: [ host := bare copyFrom: 3 to: bare size. pathString := ''] ifFalse: [ host := bare copyFrom: 3 to: i-1. pathString := bare copyFrom: host size + 3 to: bare size]] ifFalse: [host := ''. pathString := bare]]. self initializeFromPathString: pathString ! ! !FileUrl methodsFor: 'private-initialization' stamp: 'gk 2/12/2004 16:29'! privateInitializeFromText: pathString relativeTo: aUrl " should be a filesystem path. This url is adjusted to be aUrl + the path." | bare newPath | self host: aUrl host. self initializeFromPathString: pathString. self isAbsolute: aUrl isAbsolute. newPath := aUrl path copy. newPath removeLast. "empty string that says its a directory" path do: [ :token | ((token ~= '..') and: [token ~= '.']) ifTrue: [ newPath addLast: token unescapePercents ]. token = '..' ifTrue: [ newPath isEmpty ifFalse: [ newPath last = '..' ifFalse: [ newPath removeLast ] ] ]. "token = '.' do nothing" ]. path := newPath ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FileUrl class instanceVariableNames: ''! !FileUrl class methodsFor: 'constants' stamp: 'gk 2/10/2004 10:33'! schemeName ^'file'! ! !FileUrl class methodsFor: 'instance creation' stamp: 'gk 2/10/2004 12:16'! absoluteFromText: aString "Method that can be called explicitly to create a FileUrl." ^self new privateInitializeFromText: aString! ! !FileUrl class methodsFor: 'instance creation' stamp: 'gk 2/10/2004 13:04'! host: aHost pathParts: aCollectionOfPathParts isAbsolute: aBoolean "Create a FileUrl." ^self new host: aHost pathParts: aCollectionOfPathParts isAbsolute: aBoolean! ! !FileUrl class methodsFor: 'instance creation' stamp: 'gk 2/10/2004 13:10'! pathParts: aCollectionOfPathParts "Create a FileUrl." ^self host: nil pathParts: aCollectionOfPathParts isAbsolute: true! ! !FileUrl class methodsFor: 'instance creation' stamp: 'gk 2/10/2004 13:06'! pathParts: aCollectionOfPathParts isAbsolute: aBoolean "Create a FileUrl." ^self host: nil pathParts: aCollectionOfPathParts isAbsolute: aBoolean! ! ClassTestCase subclass: #FileUrlTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'NetworkTests-Url'! !FileUrlTest methodsFor: 'testing' stamp: 'fbs 2/2/2005 12:43'! testAsString | target url | target := 'file://localhost/etc/rc.conf'. url := target asUrl. self assert: url asString = target. ! ! StringHolder subclass: #FillInTheBlank instanceVariableNames: 'acceptOnCR done responseUponCancel' classVariableNames: '' poolDictionaries: '' category: 'ST80-Menus'! !FillInTheBlank commentStamp: '' prior: 0! I represent a prompt for string input from the user. The user is asked to type in and edit a string. The resulting string is supplied as the argument to a client-supplied action block. ! !FillInTheBlank methodsFor: 'accessing' stamp: 'jm 4/28/1998 06:18'! acceptOnCR "Answer whether a carriage return should cause input to be accepted." ^ acceptOnCR ! ! !FillInTheBlank methodsFor: 'accessing' stamp: 'jm 4/28/1998 06:18'! acceptOnCR: aBoolean acceptOnCR := aBoolean. ! ! !FillInTheBlank methodsFor: 'accessing' stamp: 'jm 5/6/1998 15:13'! done "Answer whether the user has ended the interaction." ^ done ! ! !FillInTheBlank methodsFor: 'accessing' stamp: 'jm 5/6/1998 15:13'! done: aBoolean done := aBoolean. ! ! !FillInTheBlank methodsFor: 'accessing' stamp: 'sw 1/31/2000 14:45'! responseUponCancel: resp responseUponCancel := resp! ! !FillInTheBlank methodsFor: 'accessing' stamp: 'sw 1/31/2000 14:47'! setResponseForCancel self contents: responseUponCancel! ! !FillInTheBlank methodsFor: 'initialization' stamp: 'sw 1/31/2000 14:42'! initialize super initialize. acceptOnCR := false. done := false. responseUponCancel := '' ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FillInTheBlank class instanceVariableNames: ''! !FillInTheBlank class methodsFor: 'instance creation' stamp: 'alain.plantec 5/30/2008 13:16'! multiLineRequest: queryString centerAt: aPoint initialAnswer: defaultAnswer answerHeight: answerHeight "Create a multi-line instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. Answer nil if the user cancels. An empty string returned means that the ussr cleared the editing area and then hit 'accept'. Because multiple lines are invited, we ask that the user use the ENTER key, or (in morphic anyway) hit the 'accept' button, to submit; that way, the return key can be typed to move to the next line. NOTE: The ENTER key does not work on Windows platforms." "FillInTheBlank multiLineRequest: 'Enter several lines; end input by accepting or canceling via menu or press Alt+s/Alt+l' centerAt: Display center initialAnswer: 'Once upon a time...' answerHeight: 200" ^self fillInTheBlankMorphClass request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: self currentWorld onCancelReturn: nil acceptOnCR: false! ! !FillInTheBlank class methodsFor: 'instance creation' stamp: 'ar 3/18/2001 00:53'! request: queryString "Create an instance of me whose question is queryString. Invoke it centered at the cursor, and answer the string the user accepts. Answer the empty string if the user cancels." "FillInTheBlank request: 'Your name?'" ^ self request: queryString initialAnswer: '' centerAt: (ActiveHand ifNil:[Sensor]) cursorPoint! ! !FillInTheBlank class methodsFor: 'instance creation' stamp: 'ar 3/18/2001 00:54'! request: queryString initialAnswer: defaultAnswer "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. Answer the empty string if the user cancels." "FillInTheBlank request: 'What is your favorite color?' initialAnswer: 'red, no blue. Ahhh!!'" ^ self request: queryString initialAnswer: defaultAnswer centerAt: (ActiveHand ifNil:[Sensor]) cursorPoint! ! !FillInTheBlank class methodsFor: 'instance creation' stamp: 'alain.plantec 5/30/2008 13:17'! request: queryString initialAnswer: defaultAnswer centerAt: aPoint "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. Answer the empty string if the user cancels." "FillInTheBlank request: 'Type something, then type CR.' initialAnswer: 'yo ho ho!!' centerAt: Display center" ^self fillInTheBlankMorphClass request: queryString initialAnswer: defaultAnswer centerAt: aPoint! ! !FillInTheBlank class methodsFor: 'instance creation' stamp: 'alain.plantec 5/30/2008 13:18'! requestPassword: queryString "Create an instance of me whose question is queryString. Invoke it centered at the cursor, and answer the string the user accepts. Answer the empty string if the user cancels." "FillInTheBlank requestPassword: 'POP password'" ^self fillInTheBlankMorphClass requestPassword: queryString! ! !FillInTheBlank class methodsFor: 'private' stamp: 'sma 6/18/2000 10:39'! fillInTheBlankMorphClass "By factoring out this class references, it becomes possible to discard morphic by simply removing this class. All calls to this method needs to be protected by 'Smalltalk isMorphic' tests." ^ FillInTheBlankMorph! ! RectangleMorph subclass: #FillInTheBlankMorph instanceVariableNames: 'response done textPane responseUponCancel' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Windows'! !FillInTheBlankMorph methodsFor: '*services-base' stamp: 'rr 1/9/2006 11:52'! selection "answers what is actually selected in the morph" ^ textPane selectionInterval! ! !FillInTheBlankMorph methodsFor: 'accessing' stamp: 'jm 5/4/1998 14:03'! response ^ response ! ! !FillInTheBlankMorph methodsFor: 'accessing' stamp: 'jm 5/4/1998 14:22'! response: aText "Sent when text pane accepts." response := aText asString. done := true. ^ true ! ! !FillInTheBlankMorph methodsFor: 'accessing' stamp: 'di 5/22/1998 00:58'! selectionInterval ^ 1 to: response size ! ! !FillInTheBlankMorph methodsFor: 'event handling' stamp: 'ar 10/7/2000 15:47'! handlesMouseDown: evt ^true! ! !FillInTheBlankMorph methodsFor: 'event handling' stamp: 'md 10/22/2003 16:20'! mouseDown: evt (self containsPoint: evt position) ifFalse:[^ Beeper beep]. "sent in response to outside modal click" evt hand grabMorph: self. "allow repositioning"! ! !FillInTheBlankMorph methodsFor: 'geometry' stamp: 'jrp 7/6/2005 21:42'! extent: aPoint "change the receiver's extent" super extent: aPoint . self setDefaultParameters. self updateColor! ! !FillInTheBlankMorph methodsFor: 'grabbing/dropping' stamp: 'ar 10/7/2000 15:50'! undoGrabCommand ^nil! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'dgd 4/3/2006 13:34'! createAcceptButton "create the [accept] button" | result frame | result := SimpleButtonMorph new target: self; color: ColorTheme current okColor. result borderColor: (Preferences menuAppearance3d ifTrue: [#raised] ifFalse: [result color twiceDarker]). result label: 'Accept(s)' translated; actionSelector: #accept. result setNameTo: 'accept'. frame := LayoutFrame new. frame rightFraction: 0.5; rightOffset: -10; bottomFraction: 1.0; bottomOffset: -2. result layoutFrame: frame. self addMorph: result. self updateColor: result color: result color intensity: 2. ^ result! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'dgd 4/3/2006 13:34'! createCancelButton "create the [cancel] button" | result frame | result := SimpleButtonMorph new target: self; color: ColorTheme current cancelColor. result borderColor: (Preferences menuAppearance3d ifTrue: [#raised] ifFalse: [result color twiceDarker]). result label: 'Cancel(l)' translated; actionSelector: #cancel. result setNameTo: 'cancel'. frame := LayoutFrame new. frame leftFraction: 0.5; leftOffset: 10; bottomFraction: 1.0; bottomOffset: -2. result layoutFrame: frame. self addMorph: result. self updateColor: result color: result color intensity: 2. ^ result! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'yo 7/2/2004 17:52'! createQueryTextMorph: queryString "create the queryTextMorph" | result frame | result := TextMorph new contents: queryString. result setNameTo: 'query' translated. result lock. frame := LayoutFrame new. frame topFraction: 0.0; topOffset: 2. frame leftFraction: 0.5; leftOffset: (result width // 2) negated. result layoutFrame: frame. self addMorph: result. ^ result! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'sd 11/8/2003 15:56'! createTextPaneExtent: answerExtent acceptBoolean: acceptBoolean topOffset: topOffset buttonAreaHeight: buttonAreaHeight "create the textPane" | result frame | result := PluggableTextMorph on: self text: #response accept: #response: readSelection: #selectionInterval menu: #codePaneMenu:shifted:. result extent: answerExtent. result hResizing: #spaceFill; vResizing: #spaceFill. result borderWidth: 1. result hasUnacceptedEdits: true. result acceptOnCR: acceptBoolean. result setNameTo: 'textPane'. frame := LayoutFrame new. frame leftFraction: 0.0; rightFraction: 1.0; topFraction: 0.0; topOffset: topOffset; bottomFraction: 1.0; bottomOffset: buttonAreaHeight negated. result layoutFrame: frame. self addMorph: result. ^ result! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:27'! defaultColor "answer the default color/fill style for the receiver" ^ Color white! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'ar 10/10/2000 22:35'! delete self breakDependents. super delete.! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'sd 11/8/2003 15:57'! initialize super initialize. self setDefaultParameters. self extent: 400 @ 150. responseUponCancel := ''. Preferences roundedMenuCorners ifTrue: [self useRoundedCorners]. ! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'sw 1/31/2000 11:01'! responseUponCancel: anObject responseUponCancel := anObject ! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'dgd 4/3/2006 10:54'! setDefaultParameters "change the receiver's appareance parameters" | colorFromMenu worldColor menuColor | colorFromMenu := Preferences menuColorFromWorld and: [Display depth > 4] and: [(worldColor := self currentWorld color) isColor]. menuColor := colorFromMenu ifTrue: [worldColor luminance > 0.7 ifTrue: [worldColor mixed: 0.85 with: Color black] ifFalse: [worldColor mixed: 0.4 with: Color white]] ifFalse: [Preferences menuColor]. self color: menuColor. self borderWidth: Preferences menuBorderWidth. Preferences menuAppearance3d ifTrue: [ self borderStyle: BorderStyle thinGray. self addDropShadow; shadowColor: (TranslucentColor r: 0.0 g: 0.0 b: 0.0 alpha: 0.666); shadowOffset: 1 @ 1 ] ifFalse: [ | menuBorderColor | menuBorderColor := colorFromMenu ifTrue: [worldColor muchDarker] ifFalse: [Preferences menuBorderColor]. self borderColor: menuBorderColor. ]. self layoutInset: 3. ! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'ar 11/4/2000 23:21'! setPasswordQuery: queryString initialAnswer: initialAnswer answerHeight: answerHeight acceptOnCR: acceptBoolean | pane | self setQuery: queryString initialAnswer: initialAnswer answerHeight: answerHeight acceptOnCR: acceptBoolean. pane := self submorphNamed: 'textPane'. pane font: (StrikeFont passwordFontSize: 12).! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'sd 11/8/2003 15:58'! setQuery: queryString initialAnswer: initialAnswer answerExtent: answerExtent acceptOnCR: acceptBoolean | query topOffset accept cancel buttonAreaHeight | response := initialAnswer. done := false. self removeAllMorphs. self layoutPolicy: ProportionalLayout new. query := self createQueryTextMorph: queryString. topOffset := query height + 4. accept := self createAcceptButton. cancel := self createCancelButton. buttonAreaHeight := (accept height max: cancel height) + 4. textPane := self createTextPaneExtent: answerExtent acceptBoolean: acceptBoolean topOffset: topOffset buttonAreaHeight: buttonAreaHeight. self extent: (query extent x max: answerExtent x) + 4 @ (topOffset + answerExtent y + 4 + buttonAreaHeight). ! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'NS 8/1/2000 11:44'! setQuery: queryString initialAnswer: initialAnswer answerHeight: answerHeight acceptOnCR: acceptBoolean self setQuery: queryString initialAnswer: initialAnswer answerExtent: (self class defaultAnswerExtent x @ answerHeight) acceptOnCR: acceptBoolean ! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'sd 11/8/2003 15:58'! updateColor "update the recevier's fillStyle" | textPaneBorderColor | self updateColor: self color: self color intensity: 1. textPane isNil ifTrue: [^ self]. textPaneBorderColor := self borderColor == #raised ifTrue: [#inset] ifFalse: [self borderColor]. textPane borderColor: textPaneBorderColor! ! !FillInTheBlankMorph methodsFor: 'initialization' stamp: 'jrp 7/6/2005 21:44'! updateColor: aMorph color: aColor intensity: anInteger "update the apareance of aMorph" | fill | Preferences gradientMenu ifFalse: [^ self]. fill := GradientFillStyle ramp: {0.0 -> Color white. 1 -> aColor}. fill radial: false; origin: aMorph topLeft; direction: 0 @ aMorph height. aMorph fillStyle: fill! ! !FillInTheBlankMorph methodsFor: 'invoking' stamp: 'marcus.denker 11/10/2008 10:04'! getUserResponse "Wait for the user to accept or cancel, and answer the result string. Answers the empty string if the user cancels." "Details: This is invoked synchronously from the caller. In order to keep processing inputs and updating the screen while waiting for the user to respond, this method has its own version of the World's event loop." | w | w := self world. w ifNil: [^ response]. (ProvideAnswerNotification signal: (self findA: TextMorph) userString) ifNotNil: [:answer | self delete. w doOneCycle. ^ response := (answer == #default) ifTrue: [response] ifFalse: [answer]]. done := false. w activeHand newKeyboardFocus: textPane. [done] whileFalse: [w doOneCycle]. self delete. w doOneCycle. ^ response ! ! !FillInTheBlankMorph methodsFor: 'invoking' stamp: 'RAA 7/19/2000 20:40'! morphicLayerNumber ^10.6! ! !FillInTheBlankMorph methodsFor: 'menu' stamp: 'jm 5/4/1998 14:21'! accept "Sent by the accept button." textPane accept. ! ! !FillInTheBlankMorph methodsFor: 'menu' stamp: 'sw 1/31/2000 11:11'! cancel "Sent by the cancel button." response := responseUponCancel. done := true. ! ! !FillInTheBlankMorph methodsFor: 'menu' stamp: 'jm 5/4/1998 15:15'! codePaneMenu: aMenu shifted: shifted ^ StringHolder new codePaneMenu: aMenu shifted: shifted. ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FillInTheBlankMorph class instanceVariableNames: ''! !FillInTheBlankMorph class methodsFor: 'default constants' stamp: 'dgd 4/27/2003 17:10'! defaultAnswerExtent ^ (200@60 * (Preferences standardMenuFont height / 12)) rounded! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'ar 3/18/2001 00:54'! request: queryString "Create an instance of me whose question is queryString. Invoke it centered at the cursor, and answer the string the user accepts. Answer the empty string if the user cancels." "FillInTheBlankMorph request: 'What is your favorite color?'" ^ self request: queryString initialAnswer: '' centerAt: (ActiveHand ifNil:[Sensor]) cursorPoint! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'ar 3/18/2001 00:54'! request: queryString initialAnswer: defaultAnswer "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. Answer the empty string if the user cancels." "FillInTheBlankMorph request: 'What is your favorite color?' initialAnswer: 'red, no blue. Ahhh!!'" ^ self request: queryString initialAnswer: defaultAnswer centerAt: ActiveHand cursorPoint! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'ar 3/17/2001 23:43'! request: queryString initialAnswer: defaultAnswer centerAt: aPoint "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. Answer the empty string if the user cancels. This variant is only for calling from within a Morphic project." "FillInTheBlankMorph request: 'Type something, then type CR.' initialAnswer: 'yo ho ho!!' centerAt: Display center" ^ self request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: ActiveWorld ! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'sw 1/31/2000 11:03'! request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. Answer the empty string if the user cancels." "FillInTheBlankMorph request: 'Type something, then type CR.' initialAnswer: 'yo ho ho!!' centerAt: Display center" ^ self request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld onCancelReturn: ''! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'sw 2/2/2000 22:43'! request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld onCancelReturn: returnOnCancel "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. If the user cancels, answer returnOnCancel. If user hits cr, treat it as a normal accept." "FillInTheBlankMorph request: 'Type something, then type CR.' initialAnswer: 'yo ho ho!!' centerAt: Display center" ^ self request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld onCancelReturn: returnOnCancel acceptOnCR: true! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'NS 8/1/2000 11:44'! request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld onCancelReturn: returnOnCancel acceptOnCR: acceptBoolean "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. If the user cancels, answer returnOnCancel." ^ self request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld onCancelReturn: returnOnCancel acceptOnCR: acceptBoolean answerExtent: self defaultAnswerExtent! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'NS 8/1/2000 11:39'! request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld onCancelReturn: returnOnCancel acceptOnCR: acceptBoolean answerExtent: answerExtent "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. If the user cancels, answer returnOnCancel." "FillInTheBlankMorph request: 'Type something, then type CR.' initialAnswer: 'yo ho ho!!' centerAt: Display center" | aFillInTheBlankMorph | aFillInTheBlankMorph := self new setQuery: queryString initialAnswer: defaultAnswer answerExtent: answerExtent acceptOnCR: acceptBoolean. aFillInTheBlankMorph responseUponCancel: returnOnCancel. aWorld addMorph: aFillInTheBlankMorph centeredNear: aPoint. ^ aFillInTheBlankMorph getUserResponse ! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'NS 8/1/2000 11:43'! request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld onCancelReturn: returnOnCancel acceptOnCR: acceptBoolean answerHeight: answerHeight "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. If the user cancels, answer returnOnCancel." ^ self request: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld onCancelReturn: returnOnCancel acceptOnCR: acceptBoolean answerExtent: self defaultAnswerExtent x @ answerHeight! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'bolot 5/18/2000 13:57'! requestPassword: queryString "Create an instance of me whose question is queryString. Invoke it centered at the cursor, and answer the string the user accepts. Answer the empty string if the user cancels." "use password font" "FillInTheBlankMorph requestPassword: 'Password?'" ^ self requestPassword: queryString initialAnswer: '' centerAt: Sensor cursorPoint inWorld: World onCancelReturn: '' acceptOnCR: true ! ! !FillInTheBlankMorph class methodsFor: 'instance creation' stamp: 'bolot 5/18/2000 13:53'! requestPassword: queryString initialAnswer: defaultAnswer centerAt: aPoint inWorld: aWorld onCancelReturn: returnOnCancel acceptOnCR: acceptBoolean "Create an instance of me whose question is queryString with the given initial answer. Invoke it centered at the given point, and answer the string the user accepts. If the user cancels, answer returnOnCancel." "FillInTheBlankMorph request: 'Type something, then type CR.' initialAnswer: 'yo ho ho!!' centerAt: Display center" | aFillInTheBlankMorph | aFillInTheBlankMorph := self new setPasswordQuery: queryString initialAnswer: defaultAnswer answerHeight: 50 acceptOnCR: acceptBoolean. aFillInTheBlankMorph responseUponCancel: returnOnCancel. aWorld addMorph: aFillInTheBlankMorph centeredNear: aPoint. ^ aFillInTheBlankMorph getUserResponse ! ! Object subclass: #FillStyle instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Balloon-Fills'! !FillStyle commentStamp: '' prior: 0! FillStyle is an abstract base class for fills in the BalloonEngine.! !FillStyle methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/21/2008 16:35'! fillRectangle: aRectangle on: aCanvas "Fill the given rectangle on the given canvas with the receiver." aCanvas fillRectangle: aRectangle basicFillStyle: self! ! !FillStyle methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/20/2008 23:03'! isCompositeFill "Answer whether the receiver is a composite fill. False by default." ^false! ! !FillStyle methodsFor: 'accessing' stamp: 'ar 1/14/1999 15:23'! scaledPixelValue32 "Return a pixel value of depth 32 for the primary color in the fill style" ^self asColor scaledPixelValue32! ! !FillStyle methodsFor: 'converting' stamp: 'ar 11/9/1998 13:53'! asColor ^self subclassResponsibility! ! !FillStyle methodsFor: 'converting' stamp: 'ar 6/4/2001 00:41'! mixed: fraction with: aColor ^self asColor mixed: fraction with: aColor! ! !FillStyle methodsFor: 'testing' stamp: 'ar 11/9/1998 13:54'! isBitmapFill ^false! ! !FillStyle methodsFor: 'testing' stamp: 'ar 11/9/1998 13:54'! isGradientFill ^false! ! !FillStyle methodsFor: 'testing' stamp: 'ar 6/18/1999 07:57'! isOrientedFill "Return true if the receiver keeps an orientation (e.g., origin, direction, and normal)" ^false! ! !FillStyle methodsFor: 'testing' stamp: 'ar 11/9/1998 13:54'! isSolidFill ^false! ! !FillStyle methodsFor: 'testing' stamp: 'ar 9/2/1999 14:28'! isTranslucent ^true "Since we don't know better"! ! !FillStyle methodsFor: 'testing' stamp: 'ar 10/26/2000 19:24'! isTransparent ^false! ! SimpleBorder subclass: #FillStyleBorder instanceVariableNames: 'fillStyle' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Borders'! !FillStyleBorder commentStamp: 'gvc 9/23/2008 11:56' prior: 0! BorderStyle supporting general (potentially composite) fillstyles. ! !FillStyleBorder methodsFor: 'accessing' stamp: 'gvc 6/24/2008 16:18'! fillStyle "Answer the value of fillStyle" ^fillStyle ifNil: [self color]! ! !FillStyleBorder methodsFor: 'accessing' stamp: 'gvc 6/24/2008 16:20'! fillStyle: anObject "Set the value of fillStyle" fillStyle := anObject. anObject ifNotNil: [self baseColor: anObject asColor]! ! !FillStyleBorder methodsFor: 'drawing' stamp: 'gvc 6/24/2008 16:15'! frameRectangle: aRectangle on: aCanvas "Fill the border areas with the fill style, clipping for each segment." (self borderRectsFor: aRectangle) do: [:r | aCanvas fillRectangle: r fillStyle: self fillStyle]! ! !FillStyleBorder methodsFor: 'geometry' stamp: 'gvc 6/24/2008 16:19'! borderRectsFor: aRectangle "Answer a collection of rectangles to fill. Just four here for a rectangular border." |rTop rBottom rLeft rRight w| w := self width. rTop := aRectangle topLeft corner: aRectangle right @ (aRectangle top + w). rBottom := aRectangle left @ (aRectangle bottom - w) corner: aRectangle bottomRight. rLeft := aRectangle left @ (aRectangle top + w) corner: aRectangle left + w @ (aRectangle bottom - w). rRight := aRectangle right - w @ (aRectangle top + w) corner: aRectangle right @ (aRectangle bottom - w). ^{rTop. rBottom. rLeft. rRight}! ! !FillStyleBorder methodsFor: 'testing' stamp: 'gvc 6/25/2008 12:11'! hasFillStyle "Answer true." ^true! ! Object subclass: #FixUnderscores instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'FixUnderscores'! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FixUnderscores class instanceVariableNames: ''! !FixUnderscores class methodsFor: 'fixing' stamp: 'bf 4/7/2006 14:47'! arrowChar "FIXME: this should rather be (Character leftArrow)" ^Character value: 16r8F! ! !FixUnderscores class methodsFor: 'fixing' stamp: 'bf 11/26/2004 21:52'! fixFonts "self fixFonts" StrikeFont allInstances do: [:fnt | self fixFont: fnt] displayingProgress: 'Fixing Bitmap Fonts'.! ! !FixUnderscores class methodsFor: 'fixing' stamp: 'bf 10/18/2005 19:05'! fixFont: aFont | glyph underline | glyph := aFont characterFormAt: $_. "save arrow glyph to arrowChar codepoint" ((glyph copy: (0@aFont ascent corner: glyph extent)) isAllWhite and: [(aFont characterFormAt: self arrowChar) isAllWhite]) ifTrue: [aFont characterFormAt: self arrowChar put: glyph]. "make underscore glyph" glyph fillWhite. underline := aFont ascent + 1. glyph fillBlack: (1@underline extent: glyph width-1@1). aFont characterFormAt: $_ put: glyph.! ! !FixUnderscores class methodsFor: 'fixing' stamp: 'sd 3/16/2008 15:28'! fixLFPackages: packageNames "FixUnderscores fixLFPackages: #('FixUnderscores')" | failed | failed := OrderedCollection new. packageNames do: [:pkgName | (PackageInfo named: pkgName) methods do: [:mRef | mRef fixLFInvisible ifFalse: [failed add: mRef]] displayingProgress: pkgName] displayingProgress: 'Fixing ...'. failed isEmpty ifFalse: [ MessageSet openMessageList: failed name: 'These methods with lf were not fixed' autoSelect: Character lf asString].! ! !FixUnderscores class methodsFor: 'fixing' stamp: 'bf 4/7/2006 15:23'! fixPackages: packageNames "FixUnderscores fixPackages: #('FixUnderscores' 'Bert')" | failed | failed := OrderedCollection new. packageNames do: [:pkgName | (PackageInfo named: pkgName) methods do: [:mRef | mRef fixUnderscores ifFalse: [failed add: mRef]] displayingProgress: pkgName] displayingProgress: 'Fixing ...'. failed isEmpty ifFalse: [ MessageSet openMessageList: failed name: 'These methods with literal underscores were not fixed' autoSelect: '_'].! ! !FixUnderscores class methodsFor: 'fixing' stamp: 'bf 4/7/2006 15:11'! fixPackage: aPackageName ^self fixPackages: {aPackageName} ! ! !FixUnderscores class methodsFor: 'initialization' stamp: 'bf 10/18/2005 12:13'! initialize "self initialize" self fixFonts. self inform: 'Fonts were _fixed_.\The arrow glyph is now Character value ' withCRs, self arrowChar asInteger hex, ' ($', self arrowChar asString, ')'. ! ! !FixUnderscores class methodsFor: 'tests' stamp: 'sd 3/16/2008 15:29'! asSeconds "Answer the seconds since the Squeak epoch: 1 January 1901" ^ 12 asSeconds! ! AbstractFont subclass: #FixedFaceFont instanceVariableNames: 'baseFont substitutionCharacter displaySelector' classVariableNames: '' poolDictionaries: '' category: 'Multilingual-Display'! !FixedFaceFont commentStamp: 'tak 12/22/2004 01:45' prior: 0! I am a font for special purpose like password or fallback. I can show same form whenever someone requests any character. Variable displaySelector is future use to show a form dynamically. (Although it would be unnecessary...)! !FixedFaceFont methodsFor: 'accessing' stamp: 'ar 1/5/2003 16:58'! ascent ^baseFont ascent! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'ar 1/5/2003 16:57'! baseFont ^baseFont! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'ar 1/5/2003 16:57'! baseFont: aFont baseFont := aFont! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'ar 1/5/2003 16:59'! baseKern ^baseFont baseKern! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'tak 12/22/2004 02:01'! characterFormAt: character ^ baseFont characterFormAt: substitutionCharacter! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'ar 1/5/2003 17:00'! descent ^baseFont descent! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'ar 1/5/2003 16:58'! descentKern ^baseFont descentKern! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'tak 12/20/2004 10:10'! emphasized: emph ^self class new baseFont: (baseFont emphasized: emph)! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'nk 8/31/2004 09:25'! familyName ^baseFont familyName, '-pw'! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'tak 12/20/2004 10:19'! fontSize: aNumber self baseFont: (StrikeFont familyName: baseFont familyName size: aNumber) copy! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'ar 1/5/2003 16:57'! height ^baseFont height! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'nk 8/31/2004 09:26'! lineGrid ^baseFont lineGrid! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'tak 12/20/2004 10:51'! maxAscii ^ SmallInteger maxVal! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'ar 1/5/2003 16:59'! passwordCharacter ^$*! ! !FixedFaceFont methodsFor: 'accessing' stamp: 'nk 8/31/2004 09:28'! pointSize ^baseFont pointSize! ! !FixedFaceFont methodsFor: 'caching' stamp: 'nk 3/15/2004 18:48'! releaseCachedState baseFont releaseCachedState.! ! !FixedFaceFont methodsFor: 'displaying' stamp: 'tak 12/20/2004 18:06'! displayErrorOn: aCanvas length: length at: aPoint kern: kernDelta | maskedString | maskedString := String new: length. maskedString atAllPut: substitutionCharacter. ^ baseFont displayString: maskedString on: aCanvas from: 1 to: length at: aPoint kern: kernDelta! ! !FixedFaceFont methodsFor: 'displaying' stamp: 'yo 1/7/2005 11:49'! displayErrorOn: aCanvas length: length at: aPoint kern: kernDelta baselineY: baselineY | maskedString | maskedString := String new: length. maskedString atAllPut: substitutionCharacter. ^ baseFont displayString: maskedString on: aCanvas from: 1 to: length at: aPoint kern: kernDelta baselineY: baselineY! ! !FixedFaceFont methodsFor: 'displaying' stamp: 'tak 12/20/2004 18:06'! displayPasswordOn: aCanvas length: length at: aPoint kern: kernDelta | maskedString | maskedString := String new: length. maskedString atAllPut: substitutionCharacter. ^ baseFont displayString: maskedString on: aCanvas from: 1 to: length at: aPoint kern: kernDelta! ! !FixedFaceFont methodsFor: 'displaying' stamp: 'yo 1/7/2005 11:50'! displayPasswordOn: aCanvas length: length at: aPoint kern: kernDelta baselineY: baselineY | maskedString | maskedString := String new: length. maskedString atAllPut: substitutionCharacter. ^ baseFont displayString: maskedString on: aCanvas from: 1 to: length at: aPoint kern: kernDelta baselineY: baselineY! ! !FixedFaceFont methodsFor: 'displaying' stamp: 'yo 1/7/2005 12:00'! displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta | size | size := stopIndex - startIndex + 1. ^ self perform: displaySelector withArguments: (Array with: aDisplayContext with: size with: aPoint with: kernDelta with: aPoint y + self ascent).! ! !FixedFaceFont methodsFor: 'displaying' stamp: 'yo 1/7/2005 12:19'! displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY | size | size := stopIndex - startIndex + 1. ^ self perform: displaySelector withArguments: (Array with: aDisplayContext with: size with: aPoint with: kernDelta with: baselineY).! ! !FixedFaceFont methodsFor: 'displaying' stamp: 'tak 12/20/2004 11:10'! displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta from: fromFont | destPoint | destPoint := self displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta. ^ Array with: stopIndex + 1 with: destPoint! ! !FixedFaceFont methodsFor: 'displaying' stamp: 'yo 1/7/2005 11:51'! displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta from: fromFont baselineY: baselineY | destPoint | destPoint := self displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY. ^ Array with: stopIndex + 1 with: destPoint! ! !FixedFaceFont methodsFor: 'displaying' stamp: 'ar 1/5/2003 17:00'! installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor ^baseFont installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor! ! !FixedFaceFont methodsFor: 'initialization' stamp: 'yo 1/7/2005 11:59'! errorFont displaySelector := #displayErrorOn:length:at:kern:baselineY:. substitutionCharacter := $?.! ! !FixedFaceFont methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:54'! initialize super initialize. baseFont := TextStyle defaultFont. self passwordFont! ! !FixedFaceFont methodsFor: 'initialization' stamp: 'yo 1/7/2005 11:59'! passwordFont displaySelector := #displayPasswordOn:length:at:kern:baselineY:. substitutionCharacter := $*! ! !FixedFaceFont methodsFor: 'measuring' stamp: 'tak 12/20/2004 18:05'! widthOf: aCharacter ^ baseFont widthOf: substitutionCharacter! ! !FixedFaceFont methodsFor: 'private' stamp: 'yo 1/11/2005 18:54'! glyphInfoOf: aCharacter into: glyphInfoArray ^ baseFont glyphInfoOf: substitutionCharacter into: glyphInfoArray. ! ! Array variableSubclass: #FixedIdentitySet instanceVariableNames: 'tally capacity' classVariableNames: '' poolDictionaries: '' category: 'Traits-Requires'! !FixedIdentitySet commentStamp: 'NS 5/26/2005 13:00' prior: 0! This is a fast but lazy implementation of fixed size identity sets. The two main difference to regular identity sets are: 1) These identity sets have a fixed size. If they are full, adding another element doesn't have any effect. 2) No rehashing. If two elements were to be stored on the same position in the underlying array, one of them is simply discarded. As a consequence of (1) and (2), these identity sets are very fast!! Note that this class inherits form Array. This is not clean but reduces memory overhead when instances are created.! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/24/2005 10:49'! addAll: aCollection aCollection do: [:each | self isFull ifTrue: [^ self]. self add: each. ].! ! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/24/2005 10:50'! addAll: aCollection notIn: notCollection aCollection do: [:each | self isFull ifTrue: [^ self]. (notCollection includes: each) ifFalse: [self add: each]. ].! ! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/24/2005 10:47'! add: anObject | index old | self isFull ifTrue: [^ false]. index := self indexOf: anObject. old := self basicAt: index. old == anObject ifTrue: [^ true]. old ifNotNil: [^ false]. self basicAt: index put: anObject. tally := tally + 1. ^ true! ! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/24/2005 08:44'! at: index self shouldNotImplement! ! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/24/2005 08:43'! at: index put: anObject self shouldNotImplement! ! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/23/2005 17:40'! capacity ^ capacity! ! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/24/2005 10:46'! destructiveAdd: anObject | index old | self isFull ifTrue: [^ false]. index := self indexOf: anObject. old := self basicAt: index. self basicAt: index put: anObject. old ifNil: [tally := tally + 1]. ^ true! ! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/24/2005 08:45'! includes: anObject ^ (self basicAt: (self indexOf: anObject)) == anObject! ! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/24/2005 13:12'! remove: anObject ifAbsent: aBlock | index | index := self indexOf: anObject. ^ (self basicAt: index) == anObject ifTrue: [self basicAt: index put: nil. tally := tally - 1. anObject] ifFalse: [aBlock value].! ! !FixedIdentitySet methodsFor: 'accessing' stamp: 'NS 5/23/2005 13:13'! size ^ tally! ! !FixedIdentitySet methodsFor: 'comparing' stamp: 'NS 5/24/2005 08:56'! hash "Answer an integer hash value for the receiver such that, -- the hash value of an unchanged object is constant over time, and -- two equal objects have equal hash values" | hash | hash := self species hash. self size <= 10 ifTrue: [self do: [:elem | hash := hash bitXor: elem hash]]. ^hash bitXor: self size hash! ! !FixedIdentitySet methodsFor: 'comparing' stamp: 'NikoSchwarz 10/15/2009 16:02'! = aCollection self == aCollection ifTrue: [^ true]. self species == aCollection species ifFalse: [^ false]. aCollection size = self size ifFalse: [^ false]. aCollection do: [:each | (self includes: each) ifFalse: [^ false]]. ^ true! ! !FixedIdentitySet methodsFor: 'enumerating' stamp: 'NS 5/24/2005 09:04'! do: aBlock | obj count | count := 0. 1 to: self basicSize do: [:index | count >= tally ifTrue: [^ self]. obj := self basicAt: index. obj ifNotNil: [count := count + 1. aBlock value: obj]. ]. ! ! !FixedIdentitySet methodsFor: 'enumerating' stamp: 'NS 5/24/2005 13:52'! select: aBlock | result | result := self species new: self capacity. self do: [:each | (aBlock value: each) ifTrue: [result add: each]]. ^ result.! ! !FixedIdentitySet methodsFor: 'initialization' stamp: 'NS 5/23/2005 17:39'! initializeCapacity: anInteger tally := 0. capacity := anInteger.! ! !FixedIdentitySet methodsFor: 'printing' stamp: 'NS 5/23/2005 18:32'! printOn: aStream | count | aStream nextPutAll: '#('. count := 0. self do: [:each | count := count + 1. each printOn: aStream. count < self size ifTrue: [aStream nextPut: $ ] ]. aStream nextPut: $).! ! !FixedIdentitySet methodsFor: 'testing' stamp: 'NS 5/24/2005 10:45'! isFull ^ tally >= capacity! ! !FixedIdentitySet methodsFor: 'testing' stamp: 'NS 5/24/2005 10:46'! notFull ^ tally < capacity! ! !FixedIdentitySet methodsFor: 'private' stamp: 'NS 5/23/2005 18:08'! arraySize ^ super size! ! !FixedIdentitySet methodsFor: 'private' stamp: 'NS 5/24/2005 10:48'! indexOf: anObject anObject isNil ifTrue: [self error: 'This class collection cannot handle nil as an element']. ^ (anObject identityHash bitAnd: self basicSize - 1) + 1! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FixedIdentitySet class instanceVariableNames: ''! !FixedIdentitySet class methodsFor: 'constants' stamp: 'NS 5/26/2005 13:02'! arraySizeForCapacity: anInteger "Because of the hash performance, the array size is always a power of 2 and at least twice as big as the capacity anInteger" ^ anInteger <= 0 ifTrue: [0] ifFalse: [1 << (anInteger << 1 - 1) highBit].! ! !FixedIdentitySet class methodsFor: 'constants' stamp: 'NS 5/26/2005 13:03'! defaultSize ^ 4! ! !FixedIdentitySet class methodsFor: 'constants' stamp: 'NS 5/23/2005 13:09'! new ^ self new: self defaultSize! ! !FixedIdentitySet class methodsFor: 'constants' stamp: 'NS 5/23/2005 17:40'! new: anInteger ^ (super new: (self arraySizeForCapacity: anInteger)) initializeCapacity: anInteger! ! !FixedIdentitySet class methodsFor: 'instance creation' stamp: 'NS 5/26/2005 13:05'! readonlyWithAll: aCollection notIn: notCollection "For performance reasons, this method may return an array rather than a FixedIdentitySet. Therefore it should only be used if the return value does not need to be modified. Use #withAll:notIn: if the return value might need to be modified." | size | aCollection isEmpty ifTrue: [^ #()]. size := aCollection size = 1 ifTrue: [1] ifFalse: [self sizeFor: aCollection]. ^ (self new: size) addAll: aCollection notIn: notCollection; yourself! ! !FixedIdentitySet class methodsFor: 'instance creation' stamp: 'NS 5/24/2005 13:57'! withAll: aCollection "Create a new collection containing all the elements from aCollection." ^ (self new: (self sizeFor: aCollection)) addAll: aCollection; yourself! ! !FixedIdentitySet class methodsFor: 'instance creation' stamp: 'NS 5/24/2005 13:58'! withAll: aCollection notIn: notCollection ^ (self new: (self sizeFor: aCollection)) addAll: aCollection notIn: notCollection; yourself! ! !FixedIdentitySet class methodsFor: 'instance creation' stamp: 'NS 5/24/2005 08:51'! with: anObject "Answer an instance of me containing anObject." ^ self new add: anObject; yourself! ! !FixedIdentitySet class methodsFor: 'instance creation' stamp: 'NS 5/24/2005 08:51'! with: firstObject with: secondObject "Answer an instance of me containing the two arguments as elements." ^ self new add: firstObject; add: secondObject; yourself! ! !FixedIdentitySet class methodsFor: 'instance creation' stamp: 'NS 5/24/2005 08:51'! with: firstObject with: secondObject with: thirdObject "Answer an instance of me containing the three arguments as elements." ^ self new add: firstObject; add: secondObject; add: thirdObject; yourself! ! !FixedIdentitySet class methodsFor: 'instance creation' stamp: 'NS 5/24/2005 08:51'! with: firstObject with: secondObject with: thirdObject with: fourthObject "Answer an instance of me, containing the four arguments as the elements." ^ self new add: firstObject; add: secondObject; add: thirdObject; add: fourthObject; yourself! ! !FixedIdentitySet class methodsFor: 'instance creation' stamp: 'NS 5/24/2005 08:52'! with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject "Answer an instance of me, containing the five arguments as the elements." ^ self new add: firstObject; add: secondObject; add: thirdObject; add: fourthObject; add: fifthObject; yourself! ! !FixedIdentitySet class methodsFor: 'instance creation' stamp: 'NS 5/24/2005 08:52'! with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject with: sixthObject "Answer an instance of me, containing the six arguments as the elements." ^ self new add: firstObject; add: secondObject; add: thirdObject; add: fourthObject; add: fifthObject; add: sixthObject; yourself! ! !FixedIdentitySet class methodsFor: 'private' stamp: 'NS 5/24/2005 13:57'! sizeFor: aCollection ^ aCollection species == self ifTrue: [aCollection capacity] ifFalse: [self defaultSize].! ! ReferenceMorph subclass: #FlapTab instanceVariableNames: 'flapShowing edgeToAdhereTo slidesOtherObjects popOutOnDragOver popOutOnMouseOver inboard dragged lastReferentThickness edgeFraction labelString' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Worlds'! !FlapTab commentStamp: '' prior: 0! The tab associated with a flap. nb: slidesOtherObjects and inboard are instance variables relating to disused features. The feature implementations still exist in the system, but the UI to them has been sealed off.! !FlapTab methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 4/16/2007 12:48'! spanWorld "Fix for making the height/width of a solid tab be the same as the flap." | container area | container := self pasteUpMorph ifNil: [self currentWorld]. area := container clearArea. self orientation == #vertical ifTrue: [ referent vResizing == #rigid ifTrue: [self isCurrentlySolid ifTrue: [self height: area height]. referent height: area height]. referent hResizing == #rigid ifTrue: [referent width: (referent width min: area width - self width)]. referent top: area top. referent bottom: (area bottom min: referent bottom) ] ifFalse: [ referent hResizing == #rigid ifTrue: [self isCurrentlySolid ifTrue: [self width: area width]. referent width: area width]. referent vResizing == #rigid ifTrue: [referent height: (referent height min: area height - self height)]. referent left: area left. referent right: (area right min: referent right) ]. ! ! !FlapTab methodsFor: 'access' stamp: 'dgd 8/31/2003 18:58'! acquirePlausibleFlapID "Give the receiver a flapID that is globally unique; try to hit the mark vis a vis the standard system flap id's, for the case when this method is invoked as part of the one-time transition" | wording | wording := self wording. (wording isEmpty or: [wording = '---']) ifTrue: [wording := 'Flap' translated]. ^ self provideDefaultFlapIDBasedOn: wording! ! !FlapTab methodsFor: 'access' stamp: 'sw 4/30/2001 18:39'! flapID "Answer the receiver's flapID, creating it if necessary" ^ self knownName ifNil: [self acquirePlausibleFlapID]! ! !FlapTab methodsFor: 'access' stamp: 'sw 4/30/2001 18:39'! flapID: anID "Set the receiver's flapID" self setNameTo: anID! ! !FlapTab methodsFor: 'access' stamp: 'sw 5/4/2001 23:25'! flapIDOrNil "If the receiver has a flapID, answer it, else answer nil" ^ self knownName! ! !FlapTab methodsFor: 'access' stamp: 'stephane.ducasse 2/14/2009 17:40'! flapShowing ^ flapShowing! ! !FlapTab methodsFor: 'access' stamp: 'MAL 1/7/2005 12:25'! orientation ^ (#left == edgeToAdhereTo or: [#right == edgeToAdhereTo]) ifTrue: [#vertical] ifFalse: [#horizontal]! ! !FlapTab methodsFor: 'access' stamp: 'sw 6/18/1999 13:38'! referentThickness ^ (self orientation == #horizontal) ifTrue: [referent height] ifFalse: [referent width]! ! !FlapTab methodsFor: 'access' stamp: 'sw 2/27/1999 13:14'! tabThickness ^ (self orientation == #vertical) ifTrue: [self width] ifFalse: [self height]! ! !FlapTab methodsFor: 'accessing' stamp: 'tk 9/25/2002 18:08'! labelString ^labelString! ! !FlapTab methodsFor: 'change reporting' stamp: 'ar 10/26/2000 17:36'! ownerChanged self fitOnScreen. ^super ownerChanged.! ! !FlapTab methodsFor: 'classification' stamp: 'ar 9/28/2000 13:53'! isFlapTab ^true! ! !FlapTab methodsFor: 'disused options' stamp: 'stephane.ducasse 2/14/2009 17:40'! inboard ^ inboard! ! !FlapTab methodsFor: 'disused options' stamp: 'sw 2/15/1999 12:57'! inboard: aBoolean inboard := aBoolean! ! !FlapTab methodsFor: 'disused options' stamp: 'sw 2/11/1999 10:55'! slidesOtherObjects ^ slidesOtherObjects! ! !FlapTab methodsFor: 'edge' stamp: 'sw 10/31/2001 20:51'! applyEdgeFractionWithin: aBoundsRectangle "Make the receiver reflect remembered edgeFraction" | newPosition | edgeFraction ifNil: [^ self]. self isCurrentlySolid ifTrue: [^ self]. newPosition := self ifVertical: [self left @ (self edgeFraction * (aBoundsRectangle height - self height))] ifHorizontal: [(self edgeFraction * (aBoundsRectangle width - self width) @ self top)]. self position: (aBoundsRectangle origin + newPosition) ! ! !FlapTab methodsFor: 'edge' stamp: 'sw 10/31/2001 15:01'! computeEdgeFraction "Compute and remember the edge fraction" | aBox aFraction | self isCurrentlySolid ifTrue: [^ edgeFraction ifNil: [self edgeFraction: 0.5]]. aBox := ((owner ifNil: [ActiveWorld]) bounds) insetBy: (self extent // 2). aFraction := self ifVertical: [(self center y - aBox top) / (aBox height max: 1)] ifHorizontal: [(self center x - aBox left) / (aBox width max: 1)]. ^ self edgeFraction: aFraction! ! !FlapTab methodsFor: 'edge' stamp: 'sw 10/31/2001 06:56'! edgeFraction ^ edgeFraction ifNil: [self computeEdgeFraction]! ! !FlapTab methodsFor: 'edge' stamp: 'sw 10/31/2001 08:38'! edgeFraction: aNumber "Set my edgeFraction to the given number, without side effects" edgeFraction := aNumber asFloat! ! !FlapTab methodsFor: 'edge' stamp: 'yo 2/10/2005 18:06'! edgeString ^ 'cling to edge... (current: {1})' translated format: {edgeToAdhereTo translated}! ! !FlapTab methodsFor: 'edge' stamp: 'sw 2/11/1999 00:41'! edgeToAdhereTo ^ edgeToAdhereTo! ! !FlapTab methodsFor: 'edge' stamp: 'MAL 1/7/2005 12:20'! edgeToAdhereTo: e edgeToAdhereTo := e asSymbol! ! !FlapTab methodsFor: 'edge' stamp: 'sw 10/31/2001 15:58'! ifVertical: block1 ifHorizontal: block2 "Evaluate and return the value of either the first or the second block, depending whether I am vertically or horizontally oriented" ^ self orientation == #vertical ifTrue: [block1 value] ifFalse: [block2 value] ! ! !FlapTab methodsFor: 'edge' stamp: 'MAL 1/7/2005 12:24'! setEdge: anEdge "Set the edge as indicated, if possible" | newOrientation e | e := anEdge asSymbol. self edgeToAdhereTo = anEdge ifTrue: [^ self]. newOrientation := nil. self orientation == #vertical ifTrue: [(#top == e or: [#bottom == e]) ifTrue: [newOrientation := #horizontal]] ifFalse: [(#top == e or: [#bottom == e]) ifFalse: [newOrientation := #vertical]]. self edgeToAdhereTo: e. newOrientation ifNotNil: [self transposeParts]. referent isInWorld ifTrue: [self positionReferent]. self adjustPositionVisAVisFlap! ! !FlapTab methodsFor: 'edge' stamp: 'dgd 10/17/2003 22:36'! setEdgeToAdhereTo | aMenu | aMenu := MenuMorph new defaultTarget: self. #(left top right bottom) do: [:sym | aMenu add: sym asString translated target: self selector: #setEdge: argument: sym]. aMenu popUpEvent: self currentEvent in: self world! ! !FlapTab methodsFor: 'event handling' stamp: 'sw 10/31/2001 15:46'! mouseMove: evt | aPosition newReferentThickness adjustedPosition thick | dragged ifFalse: [(thick := self referentThickness) > 0 ifTrue: [lastReferentThickness := thick]]. ((self containsPoint: (aPosition := evt cursorPoint)) and: [dragged not]) ifFalse: [flapShowing ifFalse: [self showFlap]. adjustedPosition := aPosition - evt hand targetOffset. (edgeToAdhereTo == #bottom) ifTrue: [newReferentThickness := inboard ifTrue: [self world height - adjustedPosition y] ifFalse: [self world height - adjustedPosition y - self height]]. (edgeToAdhereTo == #left) ifTrue: [newReferentThickness := inboard ifTrue: [adjustedPosition x + self width] ifFalse: [adjustedPosition x]]. (edgeToAdhereTo == #right) ifTrue: [newReferentThickness := inboard ifTrue: [self world width - adjustedPosition x] ifFalse: [self world width - adjustedPosition x - self width]]. (edgeToAdhereTo == #top) ifTrue: [newReferentThickness := inboard ifTrue: [adjustedPosition y + self height] ifFalse: [adjustedPosition y]]. self isCurrentlySolid ifFalse: [(#(left right) includes: edgeToAdhereTo) ifFalse: [self left: adjustedPosition x] ifTrue: [self top: adjustedPosition y]]. self applyThickness: newReferentThickness. dragged := true. self fitOnScreen. self computeEdgeFraction]! ! !FlapTab methodsFor: 'event handling' stamp: 'sw 11/22/2001 08:11'! mouseUp: evt "The mouse came back up, presumably after having dragged the tab. Caution: if not operating full-screen, this notification can easily be *missed*, which is why the edge-fraction-computation is also being done on mouseMove." super mouseUp: evt. (self referentThickness <= 0 or: [(referent isInWorld and: [(referent boundsInWorld intersects: referent owner boundsInWorld) not])]) ifTrue: [self hideFlap. flapShowing := false]. self fitOnScreen. dragged ifTrue: [self computeEdgeFraction. dragged := false]. Flaps doAutomaticLayoutOfFlapsIfAppropriate! ! !FlapTab methodsFor: 'events' stamp: 'stephane.ducasse 2/14/2009 17:41'! tabSelected "The user clicked on the tab. Show or hide the flap. Try to be a little smart about a click on a tab whose flap is open but only just barely." dragged ifTrue: [^ dragged := false]. self flapShowing ifTrue: [self referentThickness < 23 "an attractive number" ifTrue: [self openFully] ifFalse: [self hideFlap]] ifFalse: [self showFlap]! ! !FlapTab methodsFor: 'globalness' stamp: 'sw 5/4/2001 23:25'! isGlobalFlap "Answer whether the receiver is currently a shared flap" ^ Flaps globalFlapTabsIfAny includes: self! ! !FlapTab methodsFor: 'globalness' stamp: 'dgd 8/30/2003 21:36'! isGlobalFlapString "Answer a string to construct a menu item representing control over whether the receiver is or is not a shared flap" ^ (self isGlobalFlap ifTrue: [''] ifFalse: ['']) , 'shared by all projects' translated! ! !FlapTab methodsFor: 'globalness' stamp: 'sw 4/30/2001 18:52'! toggleIsGlobalFlap "Toggle whether the receiver is currently a global flap or not" | oldWorld | self hideFlap. oldWorld := self currentWorld. self isGlobalFlap ifTrue: [Flaps removeFromGlobalFlapTabList: self. oldWorld addMorphFront: self] ifFalse: [self delete. Flaps addGlobalFlap: self. self currentWorld addGlobalFlaps]. ActiveWorld reformulateUpdatingMenus ! ! !FlapTab methodsFor: 'graphical tabs' stamp: 'sw 6/17/1999 16:07'! graphicalTab self isCurrentlyGraphical ifTrue: [self changeTabGraphic] ifFalse: [self useGraphicalTab]! ! !FlapTab methodsFor: 'graphical tabs' stamp: 'dgd 8/30/2003 21:29'! graphicalTabString ^ (self isCurrentlyGraphical ifTrue: ['choose new graphic...'] ifFalse: ['use graphical tab']) translated! ! !FlapTab methodsFor: 'initialization' stamp: 'tk 12/11/2000 16:29'! adaptToWorld | wasShowing new | (wasShowing := self flapShowing) ifTrue: [self hideFlap]. (self respondsTo: #unhibernate) ifTrue: [ (new := self unhibernate) == self ifFalse: [ ^ new adaptToWorld]]. self spanWorld. self positionObject: self. wasShowing ifTrue: [self showFlap]! ! !FlapTab methodsFor: 'initialization' stamp: 'stephane.ducasse 2/14/2009 17:39'! initialize "initialize the state of the receiver" super initialize. edgeToAdhereTo := #left. flapShowing := false. slidesOtherObjects := false. popOutOnDragOver := false. popOutOnMouseOver := false. inboard := false. dragged := false! ! !FlapTab methodsFor: 'initialization' stamp: 'di 11/18/2001 13:09'! provideDefaultFlapIDBasedOn: aStem "Provide the receiver with a default flap id" | aNumber usedIDs anID | aNumber := 0. usedIDs := FlapTab allSubInstances select: [:f | f ~~ self] thenCollect: [:f | f flapIDOrNil]. anID := aStem. [usedIDs includes: anID] whileTrue: [aNumber := aNumber + 1. anID := aStem, (aNumber asString)]. self flapID: anID. ^ anID! ! !FlapTab methodsFor: 'initialization' stamp: 'di 11/19/2001 21:20'! setName: nameString edge: edgeSymbol color: flapColor "Set me up with the usual..." self setNameTo: nameString. self edgeToAdhereTo: edgeSymbol; inboard: false. self assumeString: nameString font: Preferences standardFlapFont orientation: self orientation color: flapColor. self setToPopOutOnDragOver: true. self setToPopOutOnMouseOver: false. ! ! !FlapTab methodsFor: 'layout' stamp: 'ar 10/26/2000 17:36'! layoutChanged self fitOnScreen. ^super layoutChanged! ! !FlapTab methodsFor: 'menu' stamp: 'dgd 8/30/2003 21:21'! addCustomMenuItems: aMenu hand: aHandMorph "Add further items to the menu as appropriate" aMenu add: 'tab color...' translated target: self action: #changeColor. aMenu add: 'flap color...' translated target: self action: #changeFlapColor. aMenu addLine. aMenu addUpdating: #edgeString action: #setEdgeToAdhereTo. aMenu addLine. aMenu addUpdating: #textualTabString action: #textualTab. aMenu addUpdating: #graphicalTabString action: #graphicalTab. aMenu addUpdating: #solidTabString enablement: #notSolid action: #solidTab. aMenu addLine. (referent isKindOf: PasteUpMorph) ifTrue: [aMenu addUpdating: #partsBinString action: #togglePartsBinMode]. aMenu addUpdating: #dragoverString action: #toggleDragOverBehavior. aMenu addUpdating: #mouseoverString action: #toggleMouseOverBehavior. aMenu addLine. aMenu addUpdating: #isGlobalFlapString enablement: #sharedFlapsAllowed action: #toggleIsGlobalFlap. aMenu balloonTextForLastItem: 'If checked, this flap will be available in all morphic projects; if not, it will be private to this project.,' translated. aMenu addLine. aMenu add: 'destroy this flap' translated action: #destroyFlap. "aMenu addUpdating: #slideString action: #toggleSlideBehavior. aMenu addUpdating: #inboardString action: #toggleInboardness. aMenu addUpdating: #thicknessString ('thickness... (current: ', self thickness printString, ')') action: #setThickness." ! ! !FlapTab methodsFor: 'menu' stamp: 'sw 6/20/1999 23:41'! applyThickness: newThickness | toUse | toUse := newThickness asNumber max: 0. (self orientation == #vertical) ifTrue: [referent width: toUse] ifFalse: [referent height: toUse]. self positionReferent. self adjustPositionVisAVisFlap! ! !FlapTab methodsFor: 'menu' stamp: 'dgd 9/21/2003 17:55'! changeColor self isCurrentlyGraphical ifTrue: [^ self inform: 'Color only pertains to a flap tab when the tab is textual or "solid". This tab is currently graphical, so color-choice does not apply.' translated]. super changeColor ! ! !FlapTab methodsFor: 'menu' stamp: 'dgd 9/21/2003 17:55'! changeFlapColor (self flapShowing) ifTrue: [referent changeColor] ifFalse: [self inform: 'The flap itself needs to be open before you can change its color.' translated]! ! !FlapTab methodsFor: 'menu' stamp: 'alain.plantec 2/6/2009 15:23'! changeTabText "Allow the user to change the text on the tab" | reply | reply := UIManager default request: 'New wording for this tab:' translated initialAnswer: self existingWording. reply isEmptyOrNil ifTrue: [^ self]. self changeTabText: reply. ! ! !FlapTab methodsFor: 'menu' stamp: 'dgd 9/5/2003 18:25'! destroyFlap "Destroy the receiver" | reply request | request := self isGlobalFlap ifTrue: ['Caution -- this would permanently remove this flap, so it would no longer be available in this or any other project. Do you really want to this? '] ifFalse: ['Caution -- this is permanent!! Do you really want to do this? ']. reply := self confirm: request translated orCancel: [^ self]. reply ifTrue: [self isGlobalFlap ifTrue: [Flaps removeFlapTab: self keepInList: false. self currentWorld reformulateUpdatingMenus] ifFalse: [referent isInWorld ifTrue: [referent delete]. self delete]]! ! !FlapTab methodsFor: 'menu' stamp: 'di 11/17/2001 20:17'! existingWording ^ labelString! ! !FlapTab methodsFor: 'menu' stamp: 'sw 7/8/1999 15:44'! flapMenuTitle ^ 'flap: ', self wording! ! !FlapTab methodsFor: 'menu' stamp: 'gm 2/22/2003 13:11'! isCurrentlyTextual | first | ^submorphs notEmpty and: [((first := submorphs first) isKindOf: StringMorph) or: [first isTextMorph]]! ! !FlapTab methodsFor: 'menu' stamp: 'sw 6/20/1999 19:17'! preserveDetails "The receiver is being switched to use a different format. Preserve the existing details (e.g. wording if textual, grapheme if graphical) so that if the user reverts back to the current format, the details will be right" | thickness | color = Color transparent ifFalse: [self setProperty: #priorColor toValue: color]. self isCurrentlyTextual ifTrue: [self setProperty: #priorWording toValue: self existingWording] ifFalse: [self isCurrentlyGraphical ifTrue: [self setProperty: #priorGraphic toValue: submorphs first form] ifFalse: [thickness := (self orientation == #vertical) ifTrue: [self width] ifFalse: [self height]. self setProperty: #priorThickness toValue: thickness]]! ! !FlapTab methodsFor: 'menu' stamp: 'sw 4/24/2001 11:04'! sharedFlapsAllowed "Answer (for the benefit of a menu item for which I am the target) whether the system presently allows shared flaps" ^ Flaps sharedFlapsAllowed! ! !FlapTab methodsFor: 'menu' stamp: 'sw 6/14/1999 16:38'! thicknessString ^ 'thickness... (currently ', self thickness printString, ')'! ! !FlapTab methodsFor: 'menu' stamp: 'ar 12/18/2000 16:38'! wording ^ self isCurrentlyTextual ifTrue: [self existingWording] ifFalse: [self valueOfProperty: #priorWording ifAbsent: ['---']]! ! !FlapTab methodsFor: 'menus' stamp: 'sw 6/19/1999 23:16'! addTitleForHaloMenu: aMenu aMenu addTitle: self externalName updatingSelector: #flapMenuTitle updateTarget: self! ! !FlapTab methodsFor: 'misc' stamp: 'di 11/19/2001 12:19'! fitContents self isCurrentlyTextual ifFalse: [^ super fitContents]. self ifVertical: [self extent: submorphs first extent + (2 * self borderWidth) + (0@4). submorphs first position: self position + self borderWidth + (1@4)] ifHorizontal: [self extent: submorphs first extent + (2 * self borderWidth) + (8@-1). submorphs first position: self position + self borderWidth + (5@1)]! ! !FlapTab methodsFor: 'miscellaneous' stamp: 'dgd 8/31/2003 18:43'! balloonTextForFlapsMenu "Answer the balloon text to show on a menu item in the flaps menu that governs the visibility of the receiver in the current project" | id | id := self flapID. #( ('Squeak' 'Has a few generally-useful controls; it is also a place where you can "park" objects') ('Tools' 'A quick way to get browsers, change sorters, file lists, etc.') ('Widgets' 'A variety of controls and media tools') ('Supplies' 'A source for many basic types of objects') ('Stack Tools' 'Tools for building stacks. Caution!! Powerful but young and underdocumented') ('Scripting' 'Tools useful when doing tile scripting') ('Navigator' 'Project navigator: includes controls for navigating through linked projects. Also supports finding, loading and publishing projects in a shared environment') ('Painting' 'A flap housing the paint palette. Click on the closed tab to make make a new painting')) do: [:pair | (FlapTab givenID: id matches: pair first translated) ifTrue: [^ pair second translated]]. ^ self balloonText! ! !FlapTab methodsFor: 'mouseover & dragover' stamp: 'sw 4/7/2000 07:52'! arrangeToPopOutOnDragOver: aBoolean aBoolean ifTrue: [self on: #mouseEnterDragging send: #showFlapIfHandLaden: to: self. referent on: #mouseLeaveDragging send: #maybeHideFlapOnMouseLeaveDragging to: self. self on: #mouseLeaveDragging send: #maybeHideFlapOnMouseLeaveDragging to: self] ifFalse: [self on: #mouseEnterDragging send: nil to: nil. referent on: #mouseLeaveDragging send: nil to: nil. self on: #mouseLeaveDragging send: nil to: nil]! ! !FlapTab methodsFor: 'mouseover & dragover' stamp: 'sw 7/31/2002 00:53'! arrangeToPopOutOnMouseOver: aBoolean aBoolean ifTrue: [self on: #mouseEnter send: #showFlap to: self. referent on: #mouseLeave send: #hideFlapUnlessBearingHalo to: self. self on: #mouseLeave send: #maybeHideFlapOnMouseLeave to: self] ifFalse: [self on: #mouseEnter send: nil to: nil. self on: #mouseLeave send: nil to: nil. referent on: #mouseLeave send: nil to: nil]! ! !FlapTab methodsFor: 'mouseover & dragover' stamp: 'dgd 8/30/2003 21:32'! dragoverString "Answer the string to be shown in a menu to represent the dragover status" ^ (popOutOnDragOver ifTrue: [''] ifFalse: ['']), 'pop out on dragover' translated! ! !FlapTab methodsFor: 'mouseover & dragover' stamp: 'dgd 8/30/2003 21:36'! mouseoverString "Answer the string to be shown in a menu to represent the mouseover status" ^ (popOutOnMouseOver ifTrue: [''] ifFalse: ['']) , 'pop out on mouseover' translated ! ! !FlapTab methodsFor: 'mouseover & dragover' stamp: 'sw 2/25/1999 14:53'! setToPopOutOnDragOver: aBoolean self arrangeToPopOutOnDragOver: (popOutOnDragOver := aBoolean)! ! !FlapTab methodsFor: 'mouseover & dragover' stamp: 'sw 2/25/1999 14:52'! setToPopOutOnMouseOver: aBoolean self arrangeToPopOutOnMouseOver: (popOutOnMouseOver := aBoolean)! ! !FlapTab methodsFor: 'mouseover & dragover' stamp: 'sw 2/15/1999 14:10'! toggleDragOverBehavior self arrangeToPopOutOnDragOver: (popOutOnDragOver := popOutOnDragOver not)! ! !FlapTab methodsFor: 'mouseover & dragover' stamp: 'sw 2/15/1999 14:07'! toggleMouseOverBehavior self arrangeToPopOutOnMouseOver: (popOutOnMouseOver := popOutOnMouseOver not)! ! !FlapTab methodsFor: 'objects from disk' stamp: 'sw 5/4/2001 23:27'! objectForDataStream: refStrm "I am about to be written on an object file. If I am a global flap, write a proxy instead." | dp | self isGlobalFlap ifTrue: [dp := DiskProxy global: #Flaps selector: #globalFlapTabOrDummy: args: {self flapID}. refStrm replace: self with: dp. ^ dp]. ^ super objectForDataStream: refStrm! ! !FlapTab methodsFor: 'parts bin' stamp: 'dgd 8/30/2003 21:31'! partsBinString "Answer the string to be shown in a menu to represent the parts-bin status" ^ (referent isPartsBin ifTrue: [''] ifFalse: ['']), 'parts-bin' translated! ! !FlapTab methodsFor: 'parts bin' stamp: 'sw 2/25/1999 13:17'! togglePartsBinMode referent setPartsBinStatusTo: referent isPartsBin not! ! !FlapTab methodsFor: 'positioning' stamp: 'sw 2/16/1999 18:13'! adjustPositionVisAVisFlap | sideToAlignTo opposite | opposite := Utilities oppositeSideTo: edgeToAdhereTo. sideToAlignTo := inboard ifTrue: [opposite] ifFalse: [edgeToAdhereTo]. self perform: (Utilities simpleSetterFor: sideToAlignTo) with: (referent perform: opposite)! ! !FlapTab methodsFor: 'positioning' stamp: 'dgd 4/4/2006 16:12'! fitOnScreen "19 sept 2000 - allow flaps in any paste up" | constrainer t l | constrainer := (owner ifNil: [self]) clearArea. self flapShowing "otherwise no point in doing this" ifTrue:[self spanWorld]. self orientation == #vertical ifTrue: [ t := ((self top min: (constrainer bottom- self height)) max: constrainer top). t = self top ifFalse: [self top: t]. ] ifFalse: [ l := ((self left min: (constrainer right - self width)) max: constrainer left). l = self left ifFalse: [self left: l]. ]. self flapShowing ifFalse: [self positionObject: self atEdgeOf: constrainer]. ! ! !FlapTab methodsFor: 'positioning' stamp: 'dgd 4/4/2006 16:08'! positionObject: anObject "anObject could be myself or my referent" "Could consider container := referent pasteUpMorph, to allow flaps on things other than the world, but for the moment, let's skip it!!" "19 sept 2000 - going for all paste ups" | pum | pum := self pasteUpMorph ifNil: [^ self]. ^self positionObject: anObject atEdgeOf: pum clearArea! ! !FlapTab methodsFor: 'positioning' stamp: 'RAA 6/14/2000 19:35'! positionObject: anObject atEdgeOf: container "anObject could be myself or my referent" edgeToAdhereTo == #left ifTrue: [^ anObject left: container left]. edgeToAdhereTo == #right ifTrue: [^ anObject right: container right]. edgeToAdhereTo == #top ifTrue: [^ anObject top: container top]. edgeToAdhereTo == #bottom ifTrue: [^ anObject bottom: container bottom]! ! !FlapTab methodsFor: 'positioning' stamp: 'sw 2/16/1999 17:58'! positionReferent self positionObject: referent! ! !FlapTab methodsFor: 'positioning' stamp: 'sw 2/11/1999 14:46'! stickOntoReferent "Place the receiver directly onto the referent -- for use when the referent is being shown as a flap" | newPosition | referent addMorph: self. edgeToAdhereTo == #left ifTrue: [newPosition := (referent width - self width) @ self top]. edgeToAdhereTo == #right ifTrue: [newPosition := (referent left @ self top)]. edgeToAdhereTo == #top ifTrue: [newPosition := self left @ (referent height - self height)]. edgeToAdhereTo == #bottom ifTrue: [newPosition := self left @ referent top]. self position: newPosition! ! !FlapTab methodsFor: 'positioning' stamp: 'di 11/21/2001 16:02'! transposeParts "The receiver's orientation has just been changed from vertical to horizontal or vice-versa." "First expand the flap to screen size, letting the submorphs lay out to fit, and then shrink the minor dimension back to the last row." self isCurrentlyTextual ifTrue: "First recreate the tab with proper orientation" [self assumeString: self existingWording font: Preferences standardFlapFont orientation: self orientation color: self color]. self orientation == #vertical ifTrue: "changed from horizontal" [referent listDirection: #topToBottom; wrapDirection: #leftToRight. referent hasSubmorphs ifTrue: [referent extent: self currentWorld extent. referent fullBounds. "Needed to trigger layout" referent width: (referent submorphs collect: [:m | m right]) max - referent left + self width]] ifFalse: [referent listDirection: #leftToRight; wrapDirection: #topToBottom. referent hasSubmorphs ifTrue: [referent extent: self currentWorld extent. referent fullBounds. "Needed to trigger layout" referent height: (referent submorphs collect: [:m | m bottom]) max - referent top + self height]]. referent hasSubmorphs ifFalse: [referent extent: 100@100]. self spanWorld. flapShowing ifTrue: [self showFlap]! ! !FlapTab methodsFor: 'printing' stamp: 'sw 11/6/2000 15:41'! printOn: aStream "Append a textual representation of the receiver to aStream" super printOn: aStream. aStream nextPutAll: ' "', self wording, '"'! ! !FlapTab methodsFor: 'rounding' stamp: 'di 11/20/2001 08:20'! roundedCorners edgeToAdhereTo == #bottom ifTrue: [^ #(1 4)]. edgeToAdhereTo == #right ifTrue: [^ #(1 2)]. edgeToAdhereTo == #left ifTrue: [^ #(3 4)]. ^ #(2 3) "#top and undefined" ! ! !FlapTab methodsFor: 'rounding' stamp: 'ar 12/22/2001 22:45'! wantsRoundedCorners ^self isCurrentlyTextual or:[super wantsRoundedCorners]! ! !FlapTab methodsFor: 'show & hide' stamp: 'sw 2/16/1999 17:58'! adjustPositionAfterHidingFlap self positionObject: self! ! !FlapTab methodsFor: 'show & hide' stamp: 'tk 1/31/2001 12:27'! hideFlap | aWorld | aWorld := self world ifNil: [self currentWorld]. referent privateDelete. aWorld removeAccommodationForFlap: self. flapShowing := false. self isInWorld ifFalse: [aWorld addMorphFront: self]. self adjustPositionAfterHidingFlap. aWorld haloMorphs do: [:m | m target isInWorld ifFalse: [m delete]]! ! !FlapTab methodsFor: 'show & hide' stamp: 'sw 12/29/1999 12:41'! hideFlapUnlessBearingHalo self hasHalo ifFalse: [self hideFlapUnlessOverReferent]! ! !FlapTab methodsFor: 'show & hide' stamp: 'sw 11/24/2001 21:50'! hideFlapUnlessOverReferent "Hide the flap unless the mouse is over my referent." | aWorld where | (referent isInWorld and: [where := self outermostWorldMorph activeHand lastEvent cursorPoint. referent bounds containsPoint: (referent globalPointToLocal: where)]) ifTrue: [^ self]. (aWorld := self world) ifNil: [^ self]. "In case flap tabs just got hidden" self referent delete. aWorld removeAccommodationForFlap: self. flapShowing := false. self isInWorld ifFalse: [self inboard ifTrue: [aWorld addMorphFront: self]]. self adjustPositionAfterHidingFlap! ! !FlapTab methodsFor: 'show & hide' stamp: 'sw 2/12/2001 16:49'! lastReferentThickness: anInteger "Set the last remembered referent thickness to the given integer" lastReferentThickness := anInteger! ! !FlapTab methodsFor: 'show & hide' stamp: 'RAA 6/2/2000 14:07'! maybeHideFlapOnMouseLeave self hasHalo ifTrue: [^ self]. referent isInWorld ifFalse: [^ self]. self hideFlapUnlessOverReferent. ! ! !FlapTab methodsFor: 'show & hide' stamp: 'sw 3/5/1999 17:42'! maybeHideFlapOnMouseLeaveDragging | aWorld | self hasHalo ifTrue: [^ self]. referent isInWorld ifFalse: [^ self]. (dragged or: [referent bounds containsPoint: self cursorPoint]) ifTrue: [^ self]. aWorld := self world. referent privateDelete. "could make me worldless if I'm inboard" aWorld ifNotNil: [aWorld removeAccommodationForFlap: self]. flapShowing := false. self isInWorld ifFalse: [aWorld addMorphFront: self]. self adjustPositionAfterHidingFlap! ! !FlapTab methodsFor: 'show & hide' stamp: 'sw 2/12/2001 16:59'! openFully "Make an educated guess at how wide or tall we are to be, and open to that thickness" | thickness amt | thickness := referent boundingBoxOfSubmorphs extent max: (100 @ 100). self applyThickness: (amt := self orientation == #horizontal ifTrue: [thickness y] ifFalse: [thickness x]). self lastReferentThickness: amt. self showFlap! ! !FlapTab methodsFor: 'show & hide' stamp: 'dgd 8/31/2004 16:25'! showFlap "Open the flap up" | thicknessToUse flapOwner | "19 sept 2000 - going for all paste ups <- raa note" flapOwner := self pasteUpMorph. self referentThickness <= 0 ifTrue: [thicknessToUse := lastReferentThickness ifNil: [100]. self orientation == #horizontal ifTrue: [referent height: thicknessToUse] ifFalse: [referent width: thicknessToUse]]. inboard ifTrue: [self stickOntoReferent]. "makes referent my owner, and positions me accordingly" referent pasteUpMorph == flapOwner ifFalse: [flapOwner accommodateFlap: self. "Make room if needed" flapOwner addMorphFront: referent. flapOwner startSteppingSubmorphsOf: referent. self positionReferent. referent adaptToWorld: flapOwner]. inboard ifFalse: [self adjustPositionVisAVisFlap]. flapShowing := true. self pasteUpMorph hideFlapsOtherThan: self ifClingingTo: edgeToAdhereTo. flapOwner bringTopmostsToFront! ! !FlapTab methodsFor: 'show & hide' stamp: 'sw 4/7/2000 07:51'! showFlapIfHandLaden: evt "The hand has drifted over the receiver with the button down. If the hand is carrying anything, show the flap. If the hand is empty, the likely cause is that it's manipulating a scrollbar or some such, so in that case don't pop the flap out." evt hand hasSubmorphs ifTrue: [self showFlap]! ! !FlapTab methodsFor: 'solid tabs' stamp: 'sw 2/27/1999 13:16'! applyTabThickness: newThickness (self orientation == #vertical) ifTrue: [submorphs first width: newThickness asNumber] ifFalse: [submorphs first height: newThickness asNumber]. self fitContents. self positionReferent. self adjustPositionVisAVisFlap! ! !FlapTab methodsFor: 'solid tabs' stamp: 'sw 6/21/1999 11:40'! changeTabSolidity "Presently no actual options associated with this menu item if the flap is currently alreadly solid, so entertain the user with an anuran sound. However, in latest scheme, the corresponding menu item is disabled in this circumstance, so this method is effectively unreachable." self playSoundNamed: 'croak'! ! !FlapTab methodsFor: 'solid tabs' stamp: 'DamienCassou 9/29/2009 12:58'! changeTabThickness | newThickness | newThickness := UIManager default request: 'New thickness:' translated initialAnswer: self tabThickness printString. newThickness isEmptyOrNil ifFalse: [self applyTabThickness: newThickness]! ! !FlapTab methodsFor: 'solid tabs' stamp: 'sw 6/21/1999 11:39'! isCurrentlySolid "Don't never use double negatives" ^ self notSolid not! ! !FlapTab methodsFor: 'solid tabs' stamp: 'sw 6/21/1999 11:36'! notSolid "Answer whether the receiver is currenty not solid. Used for determining whether the #solidTab menu item should be enabled" ^ self isCurrentlyTextual or: [self isCurrentlyGraphical]! ! !FlapTab methodsFor: 'solid tabs' stamp: 'sw 6/20/1999 21:34'! solidTab self isCurrentlySolid ifFalse: [self useSolidTab] ifTrue: [self changeTabSolidity]! ! !FlapTab methodsFor: 'solid tabs' stamp: 'dgd 8/30/2003 21:31'! solidTabString ^ (self isCurrentlySolid ifTrue: ['currently using solid tab'] ifFalse: ['use solid tab']) translated! ! !FlapTab methodsFor: 'solid tabs' stamp: 'sw 6/20/1999 20:55'! useSolidTab | thickness colorToUse | self preserveDetails. thickness := self valueOfProperty: #priorThickness ifAbsent: [20]. colorToUse := self valueOfProperty: #priorColor ifAbsent: [Color red muchLighter]. self color: colorToUse. self removeAllMorphs. (self orientation == #vertical) ifTrue: [self width: thickness. self height: self currentWorld height. self position: (self position x @ 0)] ifFalse: [self height: thickness. self width: self currentWorld width. self position: (0 @ self position y)]. self borderWidth: 0. self layoutChanged.! ! !FlapTab methodsFor: 'submorphs-add/remove' stamp: 'rbb 2/18/2005 14:13'! dismissViaHalo "Dismiss the receiver (and its referent), unless it resists" self resistsRemoval ifTrue: [(UIManager default chooseFrom: #( 'Yes' 'Um, no, let me reconsider') title: 'Really throw this flap away?') = 2 ifFalse: [^ self]]. referent delete. self delete! ! !FlapTab methodsFor: 'textual tabs' stamp: 'yo 7/16/2003 15:25'! assumeString: aString font: aFont orientation: orientationSymbol color: aColor | aTextMorph workString tabStyle | labelString := aString asString. workString := orientationSymbol == #vertical ifTrue: [String streamContents: [:s | labelString do: [:c | s nextPut: c] separatedBy: [s nextPut: Character cr]]] ifFalse: [labelString]. tabStyle := (TextStyle new) leading: 0; newFontArray: (Array with: aFont). aTextMorph := (TextMorph new setTextStyle: tabStyle) contents: (workString asText addAttribute: (TextKern kern: 3)). self removeAllMorphs. self borderWidth: 2; borderColor: #raised. aColor ifNotNil: [self color: aColor]. self addMorph: aTextMorph centered. aTextMorph lock " FlapTab allSubInstancesDo: [:ft | ft reformatTextualTab] "! ! !FlapTab methodsFor: 'textual tabs' stamp: 'ar 9/3/2004 14:58'! changeTabText: aString | label | aString isEmptyOrNil ifTrue: [^ self]. label := Locale current languageEnvironment class flapTabTextFor: aString in: self. label isEmptyOrNil ifTrue: [^ self]. self useStringTab: label. submorphs first delete. self assumeString: label font: Preferences standardFlapFont orientation: (Flaps orientationForEdge: self edgeToAdhereTo) color: nil. ! ! !FlapTab methodsFor: 'textual tabs' stamp: 'sw 12/8/1999 18:16'! reformatTextualTab "The font choice possibly having changed, reformulate the receiver" self isCurrentlyTextual ifFalse: [^ self]. self assumeString: self existingWording font: Preferences standardFlapFont orientation: self orientation color: self color! ! !FlapTab methodsFor: 'textual tabs' stamp: 'sw 6/17/1999 13:21'! textualTab self isCurrentlyTextual ifTrue: [self changeTabText] ifFalse: [self useTextualTab]! ! !FlapTab methodsFor: 'textual tabs' stamp: 'dgd 8/30/2003 21:27'! textualTabString ^ (self isCurrentlyTextual ifTrue: ['change tab wording...'] ifFalse: ['use textual tab']) translated! ! !FlapTab methodsFor: 'textual tabs' stamp: 'di 11/17/2001 20:22'! useStringTab: aString | aLabel | labelString := aString asString. aLabel := StringMorph new contents: labelString. self addMorph: aLabel. aLabel position: self position. aLabel highlightColor: self highlightColor; regularColor: self regularColor. aLabel lock. self fitContents. self layoutChanged! ! !FlapTab methodsFor: 'textual tabs' stamp: 'dgd 10/8/2003 19:03'! useTextualTab | stringToUse colorToUse | self preserveDetails. colorToUse := self valueOfProperty: #priorColor ifAbsent: [Color green muchLighter]. submorphs notEmpty ifTrue: [self removeAllMorphs]. stringToUse := self valueOfProperty: #priorWording ifAbsent: ['Unnamed Flap' translated]. self assumeString: stringToUse font: Preferences standardFlapFont orientation: self orientation color: colorToUse! ! !FlapTab methodsFor: 'thumbnail' stamp: 'sw 6/16/1999 11:29'! permitsThumbnailing ^ false! ! !FlapTab methodsFor: 'wiw support' stamp: 'RAA 10/3/2000 09:24'! morphicLayerNumber ^self flapShowing ifTrue: [26] ifFalse: [25] "As navigators"! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FlapTab class instanceVariableNames: ''! !FlapTab class methodsFor: 'as yet unclassified' stamp: 'di 11/19/2001 21:59'! givenID: aFlapID matches: pureID "eg, FlapTab givenID: 'Stack Tools2' matches: 'Stack Tools' " ^ aFlapID = pureID or: [(aFlapID beginsWith: pureID) and: [(aFlapID copyFrom: pureID size+1 to: aFlapID size) allSatisfy: [:c | c isDigit]]]! ! !FlapTab class methodsFor: 'new-morph participation' stamp: 'kfr 5/3/2000 12:51'! includeInNewMorphMenu "Not to be instantiated from the menu" ^ false! ! !FlapTab class methodsFor: 'printing' stamp: 'sw 2/11/1999 14:39'! defaultNameStemForInstances ^ 'flap tab'! ! Object subclass: #Flaps instanceVariableNames: '' classVariableNames: 'FlapsQuads SharedFlapTabs SharedFlapsAllowed' poolDictionaries: '' category: 'Morphic-Worlds'! !Flaps commentStamp: 'asm 3/13/2003 12:46' prior: 0! ClassVariables FlapsQuads quads defining predefined flaps default flaps are: 'PlugIn Supplies', 'Stack Tools', 'Supplies', 'Tools', 'Widgets' and 'Scripting' SharedFlapTabs an array of flaps shared between squeak projects SharedFlapsAllowed boolean ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Flaps class instanceVariableNames: ''! !Flaps class methodsFor: 'construction support' stamp: 'adrian_lienhard 7/19/2009 20:53'! addMorph: aMorph asElementNumber: aNumber inGlobalFlapSatisfying: flapBlock "If any global flap satisfies flapBlock, add aMorph to it at the given position. Applies to flaps that are parts bins and that like thumbnailing" | aFlapTab flapPasteUp | aFlapTab := self globalFlapTabsIfAny detect: [:aTab | flapBlock value: aTab] ifNone: [^ self]. flapPasteUp := aFlapTab referent. flapPasteUp addMorph: aMorph asElementNumber: aNumber. flapPasteUp setPartsBinStatusTo: true! ! !Flaps class methodsFor: 'construction support' stamp: 'sw 5/4/2001 23:52'! addMorph: aMorph asElementNumber: aNumber inGlobalFlapWithID: anID "If any global flap satisfies flapBlock, add aMorph to it at the given position. No senders in the image -- intended to be invoked by doits in code updates only, and applies to flaps that are parts bins and that like thumbnailing" ^ self addMorph: aMorph asElementNumber: aNumber inGlobalFlapSatisfying: [:aFlap | aFlap flapID = anID]! ! !Flaps class methodsFor: 'construction support' stamp: 'sw 4/30/2001 18:57'! addToSuppliesFlap: aMorph asElementNumber: aNumber "Add the given morph to the supplies flap. To be called by doits in updates, so don't be alarmed by its lack of senders." self addMorph: aMorph asElementNumber: aNumber inGlobalFlapWithID: 'Supplies'! ! !Flaps class methodsFor: 'construction support' stamp: 'sw 5/5/2001 02:12'! deleteMorphsSatisfying: deleteBlock fromGlobalFlapSatisfying: flapBlock "If any global flap satisfies flapBlock, then delete objects satisfying from deleteBlock from it. Occasionally called from do-its in updates or other fileouts." | aFlapTab flapPasteUp | aFlapTab := self globalFlapTabsIfAny detect: [:aTab | flapBlock value: aTab] ifNone: [^ self]. flapPasteUp := aFlapTab referent. flapPasteUp submorphs do: [:aMorph | (deleteBlock value: aMorph) ifTrue: [aMorph delete]]! ! !Flaps class methodsFor: 'flap mechanics' stamp: 'sw 2/16/1999 18:29'! clobberFlapTabList "Flaps clobberFlapTabList" SharedFlapTabs := nil! ! !Flaps class methodsFor: 'flap mechanics' stamp: 'sw 7/12/2001 22:01'! freshFlapsStart "To be called manually only, as a drastic measure. Delete all flap artifacts and establish fresh default global flaps Flaps freshFlapsStart " self currentWorld deleteAllFlapArtifacts. self clobberFlapTabList. self addStandardFlaps ! ! !Flaps class methodsFor: 'flap mechanics' stamp: 'dgd 10/7/2003 22:47'! reinstateDefaultFlaps "Remove all existing 'standard' global flaps clear the global list, and and add fresh ones. To be called by doits in updates etc. This is a radical step, but it does *not* clobber non-standard global flaps or local flaps. To get the effect of the *former* version of this method, call Flaps freshFlapsStart" "Flaps reinstateDefaultFlaps" self globalFlapTabsIfAny do: [:aFlapTab | ({ 'Painting' translated. 'Stack Tools' translated. 'Squeak' translated. 'Menu' translated. 'Widgets' translated. 'Tools' translated. 'Supplies' translated. 'Scripting' translated. 'Objects' translated. 'Navigator' translated } includes: aFlapTab flapID) ifTrue: [self removeFlapTab: aFlapTab keepInList: false]]. "The following reduces the risk that flaps will be created with variant IDs such as 'Stack Tools2', potentially causing some shared flap logic to fail." "Smalltalk garbageCollect." "-- see if we are OK without this" self addStandardFlaps. "self disableGlobalFlapWithID: 'Scripting'. self disableGlobalFlapWithID: 'Objects'." self currentWorld addGlobalFlaps. self currentWorld reformulateUpdatingMenus. ! ! !Flaps class methodsFor: 'flap mechanics' stamp: 'sw 4/17/2001 14:47'! removeFlapTab: aFlapTab keepInList: aBoolean "Remove the given flap tab from the screen, and, if aBoolean is true, also from the global list" (SharedFlapTabs ~~ nil and: [SharedFlapTabs includes: aFlapTab]) ifTrue: [aBoolean ifFalse: [self removeFromGlobalFlapTabList: aFlapTab]]. aFlapTab ifNotNil: [aFlapTab referent delete. aFlapTab delete]! ! !Flaps class methodsFor: 'flaps registry' stamp: 'adrian_lienhard 7/19/2009 17:46'! defaultsQuadsDefiningScriptingFlap "Answer a structure defining the default items in the Scripting flap. previously in quadsDeiningScriptingFlap" ^ #( (SimpleSliderMorph authoringPrototype 'Slider' 'A slider for showing and setting numeric values.') (JoystickMorph authoringPrototype 'Joystick' 'A joystick-like control') (TextFieldMorph exampleBackgroundField 'Scrolling Field' 'A scrolling data field which will have a different value on every card of the background') (PasteUpMorph authoringPrototype 'Playfield' 'A place for assembling parts or for staging animations') (TextMorph exampleBackgroundLabel 'Background Label' 'A piece of text that will occur on every card of the background') (TextMorph exampleBackgroundField 'Background Field' 'A data field which will have a different value on every card of the background') ) asOrderedCollection! ! !Flaps class methodsFor: 'flaps registry' stamp: 'stephane.ducasse 1/30/2009 22:49'! defaultsQuadsDefiningStackToolsFlap "Answer a structure defining the items on the default system Stack Tools flap. previously in quadsDefiningStackToolsFlap" ^ #( (TextMorph authoringPrototype 'Simple Text' 'Text that you can edit into anything you wish') (TextMorph fancyPrototype 'Fancy Text' 'A text field with a rounded shadowed border, with a fancy font.')) asOrderedCollection ! ! !Flaps class methodsFor: 'flaps registry' stamp: 'stephane.ducasse 5/1/2009 22:16'! defaultsQuadsDefiningSuppliesFlap "Answer a list of quads which define the objects to appear in the default Supplies flap. previously in quadsDefiningSuppliesFlap" ^ #( (RectangleMorph authoringPrototype 'Rectangle' 'A rectangle') (RectangleMorph roundRectPrototype 'RoundRect' 'A rectangle with rounded corners') (EllipseMorph authoringPrototype 'Ellipse' 'An ellipse or circle') (StarMorph authoringPrototype 'Star' 'A star') (CurveMorph authoringPrototype 'Curve' 'A curve') (PolygonMorph authoringPrototype 'Polygon' 'A straight-sided figure with any number of sides') (TextMorph boldAuthoringPrototype 'Text' 'Text that you can edit into anything you desire.') (ImageMorph authoringPrototype 'Picture' 'A non-editable picture of something') (SimpleSliderMorph authoringPrototype 'Slider' 'A slider for showing and setting numeric values.') (PasteUpMorph authoringPrototype 'Playfield' 'A place for assembling parts or for staging animations') (JoystickMorph authoringPrototype 'Joystick' 'A joystick-like control') (ClockMorph authoringPrototype 'Clock' 'A simple digital clock') ) asOrderedCollection! ! !Flaps class methodsFor: 'flaps registry' stamp: 'hfm 11/29/2008 20:06'! defaultsQuadsDefiningToolsFlap "Answer a structure defining the default Tools flap. previously in quadsDefiningToolsFlap" ^ OrderedCollection new addAll: #( (Browser prototypicalToolWindow 'Browser' 'A Browser is a tool that allows you to view all the code of all the classes in the system') (TranscriptStream openMorphicTranscript 'Transcript' 'A Transcript is a window usable for logging and debugging; browse references to #Transcript for examples of how to write to it.') (Workspace prototypicalToolWindow 'Workspace' 'A Workspace is a simple window for editing text. You can later save the contents to a file if you desire.')); add: { FileList . #prototypicalToolWindow. 'File List'. 'A File List is a tool for browsing folders and files on disks and FTP servers.' }; addAll: #( (DualChangeSorter prototypicalToolWindow 'Change Sorter' 'Shows two change sets side by side') (MessageNames prototypicalToolWindow 'Message Names' 'A tool for finding, viewing, and editing all methods whose names contain a given character sequence.') (Utilities recentSubmissionsWindow 'Recent' 'A message browser that tracks the most recently-submitted methods') (ProcessBrowser prototypicalToolWindow 'Processes' 'A Process Browser shows you all the running processes') (Preferences annotationEditingWindow 'Annotations' 'Allows you to specify the annotations to be shown in the annotation panes of browsers, etc.') (Scamper newOpenableMorph 'Scamper' 'A web browser') (Celeste newOpenableMorph 'Celeste' 'Celeste -- an EMail reader') (ChangeSorter prototypicalToolWindow 'Change Set' 'A tool that allows you to view and manipulate all the code changes in a single change set')); yourself! ! !Flaps class methodsFor: 'flaps registry' stamp: 'adrian_lienhard 7/19/2009 19:50'! defaultsQuadsDefiningWidgetsFlap "Answer a structure defining the default Widgets flap. previously in quadsDefiningWidgetsFlap" ^ #( (RecordingControlsMorph authoringPrototype 'Sound' 'A device for making sound recordings.') (MPEGMoviePlayerMorph authoringPrototype 'Movie Player' 'A Player for MPEG movies') (FrameRateMorph authoringPrototype 'Frame Rate' 'An indicator of how fast your system is running') (MagnifierMorph newRound 'Magnifier' 'A magnifying glass') (BouncingAtomsMorph new 'Bouncing Atoms' 'Atoms, mate') ) asOrderedCollection! ! !Flaps class methodsFor: 'flaps registry' stamp: 'asm 3/13/2003 10:58'! initializeFlapsQuads "initialize the list of dynamic flaps quads. self initializeFlapsQuads" FlapsQuads := nil. self registeredFlapsQuads at: 'PlugIn Supplies' put: self defaultsQuadsDefiningPlugInSuppliesFlap; at: 'Stack Tools' put: self defaultsQuadsDefiningStackToolsFlap; at: 'Supplies' put: self defaultsQuadsDefiningSuppliesFlap; at: 'Tools' put: self defaultsQuadsDefiningToolsFlap; at: 'Widgets' put: self defaultsQuadsDefiningWidgetsFlap; at: 'Scripting' put: self defaultsQuadsDefiningScriptingFlap. ^ self registeredFlapsQuads! ! !Flaps class methodsFor: 'flaps registry' stamp: 'asm 3/13/2003 09:55'! registeredFlapsQuads "Answer the list of dynamic flaps quads" FlapsQuads ifNil: [FlapsQuads := Dictionary new]. ^ FlapsQuads " FlapsQuads := nil. "! ! !Flaps class methodsFor: 'flaps registry' stamp: 'hpt 4/26/2004 16:46'! registeredFlapsQuadsAt: aLabel "Answer the list of dynamic flaps quads at aLabel" ^ (self registeredFlapsQuads at: aLabel) removeAllSuchThat: [:q | (self environment includesKey: q first) not or: [(self environment at: q first) isNil]] ! ! !Flaps class methodsFor: 'flaps registry' stamp: 'asm 3/13/2003 11:09'! registerQuad: aQuad forFlapNamed: aLabel "If any previous registration of the same label string is already known, delete the old one." "aQuad received must be an array of the form {TargetObject. #command label 'A Help String'} Flaps registerQuad: #(FileList2 openMorphicViewInWorld 'Enhanced File List' 'A nicer File List.') forFlapNamed: 'Tools' " self unregisterQuad: aQuad forFlapNamed: aLabel. (self registeredFlapsQuads at: aLabel) add: aQuad! ! !Flaps class methodsFor: 'flaps registry' stamp: 'ar 9/27/2005 22:10'! unregisterQuadsWithReceiver: aReceiver "delete all quads with receiver aReceiver." self registeredFlapsQuads do: [:assoc | assoc value removeAllSuchThat: [:q | (self environment at: (q first) ifAbsent:[nil]) = aReceiver ]]! ! !Flaps class methodsFor: 'flaps registry' stamp: 'asm 4/12/2003 14:16'! unregisterQuadsWithReceiver: aReceiver fromFlapNamed: aLabel "delete all quads with receiver aReceiver." (self registeredFlapsQuads at: aLabel) removeAllSuchThat: [:q | q first = aReceiver name]! ! !Flaps class methodsFor: 'flaps registry' stamp: 'asm 3/13/2003 10:34'! unregisterQuad: aQuad forFlapNamed: aLabel "If any previous registration at the same label string has the same receiver-command, delete the old one." (self registeredFlapsQuadsAt: aLabel) removeAllSuchThat: [:q | q first = aQuad first and: [q second = aQuad second]]! ! !Flaps class methodsFor: 'initialization' stamp: 'nk 6/14/2004 08:37'! initialize self initializeFlapsQuads! ! !Flaps class methodsFor: 'menu commands' stamp: 'mir 8/22/2001 18:55'! disableGlobalFlaps "Clobber all the shared flaps structures. First read the user her Miranda rights." self disableGlobalFlaps: true! ! !Flaps class methodsFor: 'menu commands' stamp: 'alain.plantec 5/30/2008 13:22'! disableGlobalFlaps: interactive "Clobber all the shared flaps structures. First read the user her Miranda rights. " interactive ifTrue: [(self confirm: 'CAUTION!! This will destroy all the shared flaps, so that they will not be present in *any* project. If, later, you want them back, you will have to reenable them, from this same menu, whereupon the standard default set of shared flaps will be created. Do you really want to go ahead and clobber all shared flaps at this time?' translated) ifFalse: [^ self]]. self globalFlapTabsIfAny do: [:aFlapTab | self removeFlapTab: aFlapTab keepInList: false. aFlapTab isInWorld ifTrue: [self error: 'Flap problem' translated]]. self clobberFlapTabList. SharedFlapsAllowed := false. ActiveWorld restoreMorphicDisplay. ActiveWorld reformulateUpdatingMenus! ! !Flaps class methodsFor: 'menu commands' stamp: 'alain.plantec 5/30/2008 13:20'! disableGlobalFlapWithID: aFlapID "Mark this project as having the given flapID disabled" | disabledFlapIDs aFlapTab currentProject | (currentProject := Project current) assureFlapIntegrity. disabledFlapIDs := currentProject parameterAt: #disabledGlobalFlapIDs. (aFlapTab := self globalFlapTabWithID: aFlapID) ifNotNil: [aFlapTab hideFlap]. (disabledFlapIDs includes: aFlapID) ifFalse: [disabledFlapIDs add: aFlapID]. aFlapTab ifNotNil: [aFlapTab delete] ! ! !Flaps class methodsFor: 'menu commands' stamp: 'alain.plantec 5/30/2008 13:23'! enableDisableGlobalFlapWithID: aFlapID "Toggle the enable/disable status of the given global flap" | disabledFlapIDs aFlapTab currentProject | (currentProject := Project current) assureFlapIntegrity. disabledFlapIDs := currentProject parameterAt: #disabledGlobalFlapIDs. (aFlapTab := self globalFlapTabWithID: aFlapID) ifNotNil: [aFlapTab hideFlap]. (disabledFlapIDs includes: aFlapID) ifTrue: [disabledFlapIDs remove: aFlapID. self currentWorld addGlobalFlaps] ifFalse: [disabledFlapIDs add: aFlapID. aFlapTab ifNotNil: [aFlapTab delete]]. self doAutomaticLayoutOfFlapsIfAppropriate! ! !Flaps class methodsFor: 'menu commands' stamp: 'alain.plantec 5/30/2008 13:24'! enableGlobalFlapWithID: aFlapID "Remove any memory of this flap being disabled in this project" | disabledFlapIDs currentProject | (currentProject := Project current) assureFlapIntegrity. disabledFlapIDs := currentProject parameterAt: #disabledGlobalFlapIDs ifAbsent: [^ self]. disabledFlapIDs remove: aFlapID ifAbsent: [] ! ! !Flaps class methodsFor: 'menu commands' stamp: 'sw 3/3/2004 15:49'! explainFlaps "Open a window giving flap help." (StringHolder new contents: self explainFlapsText translated) openLabel: 'Flaps' translated "Flaps explainFlaps" ! ! !Flaps class methodsFor: 'menu commands' stamp: 'sw 3/3/2004 15:51'! explainFlapsText "Answer the text, in English, to show in a help-window about Flaps." ^'Flaps are like drawers on the edge of the screen, which can be opened so that you can use what is inside them, and closed when you do not need them. They have many possible uses, a few of which are illustrated by the default set of flaps you can get as described below. ''Shared flaps'' are available in every morphic project. As you move from project to project, you will see these same shared flaps in each, though there are also options, on a project-by-project basis, to choose which of the shared flaps should be shown, and also momentarily to suppress the showing of all shared flaps. To get started using flaps, bring up the desktop menu and choose ''flaps...'', and make the menu stay up by choosing ''keep this menu up''. If you see, in this flaps menu, a list of flap names such as ''Squeak'', ''Tools'', etc., it means that shared flaps are already set up in your image. If you do not see the list, you will instead see a menu item that invites you to ''install default shared flaps''; choose that, and new flaps will be created, and the flaps menu will change to reflect their presence. ''Project flaps'' are flaps that belong to a single morphic project. You will see them when you are in that project, but not when you are in any other morphic project. If a flap is set up as a parts bin (such as the default Tools and Supplies flaps), you can use it to create new objects -- just open the flap, then find the object you want, and drag it out; when the cursor leaves the flap, the flap itself will snap closed, and you''ll be left holding the new object -- just click to place it exactly where you want it. If a flap is *not* set up as a parts bin (such as the default ''Squeak'' flap at the left edge of the screen) you can park objects there (this is an easy way to move objects from project to project) and you can place your own private controls there, etc. Everything in the default ''Squeak'' flap (and all the other default flaps, for that matter) is there only for illustrative purposes -- every user will want to fine-tune the flaps to suit his/her own style and needs. Each flap may be set up to appear on mouseover, dragover, both, or neither. See the menu items described below for more about these and other options. You can open a closed flap by clicking on its tab, or by dragging the tab toward the center of the screen You can close an open flap by clicking on its tab or by dragging the tab back off the edge of the screen. Drag the tab of a flap to reposition the tab and to resize the flap itself. Repositioning starts when you drag the cursor out of the original tab area. If flaps or their tabs seem wrongly positioned or lost, try issuing a restoreDisplay from the screen menu. The red-halo menu on a flap allows you to change the flap''s properties. For greatest ease of use, request ''keep this menu up'' here -- that way, you can easily explore all the options in the menu. tab color... Lets you change the color of the flap''s tab. flap color... Lets you change the color of the flap itself. use textual tab... If the tab is not textual, makes it become textual. change tab wording... If the tab is already textual, allows you to edit its wording. use graphical tab... If the tab is not graphical, makes it become graphical. choose tab graphic... If the tab is already graphical, allows you to change the picture. use solid tab... If the tab is not solid, makes it become solid, i.e. appear as a solid band of color along the entire length or width of the screen. parts-bin behavior If set, then dragging an object from the flap tears off a new copy of the object. dragover If set, the flap opens on dragover and closes again on drag-leave. mouseover If set, the flap opens on mouseover and closes again on mouse-leave. cling to edge... Governs which edge (left, right, top, bottom) the flap adheres to. shared If set, the same flap will be available in all projects; if not, the flap will will occur only in one project. destroy this flap Deletes the flap. To define a new flap, use ''make a new flap'', found in the ''flaps'' menu. To reinstate the default system flaps, you can use ''destroy all shared flaps'' from the ''flaps'' menu, and once they are destroyed, choose ''install default shared flaps''. To add, delete, or edit things on a given flap, it is often wise first to suspend the flap''s mouse-over and drag-over sensitivity, so it won''t keep disappearing on you while you''re trying to work with it. Besides the three standard flaps delivered with the default system, there are two other flaps readily available on demand from the ''flaps'' menu -- one is called ''Stack Tools'', which provides some tools useful for building stack-like content, the other is called ''Painting'', which provides a quick way to make a new painting. Simply clicking on the appropriate checkbox in the ''flaps'' menu will toggle the corresponding flap between being visible and not being visible in the project.'! ! !Flaps class methodsFor: 'menu support' stamp: 'sw 4/24/2001 11:03'! addIndividualGlobalFlapItemsTo: aMenu "Add items governing the enablement of specific global flaps to aMenu" | anItem | self globalFlapTabsIfAny do: [:aFlapTab | anItem := aMenu addUpdating: #globalFlapWithIDEnabledString: enablementSelector: #showSharedFlaps target: self selector: #enableDisableGlobalFlapWithID: argumentList: {aFlapTab flapID}. anItem wordingArgument: aFlapTab flapID. anItem setBalloonText: aFlapTab balloonTextForFlapsMenu].! ! !Flaps class methodsFor: 'menu support' stamp: 'alain.plantec 5/30/2008 13:25'! enableGlobalFlaps "Start using global flaps, given that they were not present." Cursor wait showWhile: [SharedFlapsAllowed := true. self globalFlapTabs. "This will create them" ActiveWorld addGlobalFlaps. self doAutomaticLayoutOfFlapsIfAppropriate. FlapTab allInstancesDo: [:aTab | aTab computeEdgeFraction]. ActiveWorld reformulateUpdatingMenus]! ! !Flaps class methodsFor: 'menu support' stamp: 'sw 4/17/2001 13:50'! globalFlapWithIDEnabledString: aFlapID "Answer the string to be shown in a menu to represent the status of the givne flap regarding whether it it should be shown in this project." | aFlapTab wording | aFlapTab := self globalFlapTabWithID: aFlapID. wording := aFlapTab ifNotNil: [aFlapTab wording] ifNil: ['(', aFlapID, ')']. ^ (Project current isFlapIDEnabled: aFlapID) ifTrue: ['', wording] ifFalse: ['', wording]! ! !Flaps class methodsFor: 'menu support' stamp: 'adrian_lienhard 7/19/2009 22:21'! setUpSuppliesFlapOnly "Set up the Supplies flap as the only shared flap. A special version formulated for this stand-alone use is used, defined in #newLoneSuppliesFlap" | | SharedFlapTabs isEmptyOrNil ifFalse: "get rid of pre-existing guys if any" [SharedFlapTabs do: [:t | t referent delete. t delete]]. SharedFlapsAllowed := true. SharedFlapTabs := OrderedCollection new. self enableGlobalFlapWithID: 'Supplies' translated. ActiveWorld addGlobalFlaps. ActiveWorld reformulateUpdatingMenus! ! !Flaps class methodsFor: 'menu support' stamp: 'dao 10/1/2004 12:59'! showSharedFlaps "Answer whether shared flaps are currently showing. Presumably it is in service of Alan's wishes to have flaps show sometimes on interior subprojects and sometomes on outer projects that Bob's CurrentProjectRefactoring is threaded into the logic here." ^ Project current showSharedFlaps! ! !Flaps class methodsFor: 'menu support' stamp: 'dao 10/1/2004 13:12'! suppressFlapsString "Answer the string to be shown in a menu to represent the suppress-flaps-in-this-project status" ^ Project current suppressFlapsString! ! !Flaps class methodsFor: 'miscellaneous' stamp: 'sw 11/22/2001 10:04'! automaticFlapLayoutChanged "Sent when the automaticFlapLayout preference changes. No senders in easily traceable in the image, but this is really sent by a Preference object!!" Preferences automaticFlapLayout ifTrue: [self positionNavigatorAndOtherFlapsAccordingToPreference]! ! !Flaps class methodsFor: 'miscellaneous' stamp: 'sw 11/22/2001 09:58'! doAutomaticLayoutOfFlapsIfAppropriate "Do automatic layout of flaps if appropriate" Preferences automaticFlapLayout ifTrue: [self positionNavigatorAndOtherFlapsAccordingToPreference]! ! !Flaps class methodsFor: 'miscellaneous' stamp: 'sd 1/16/2004 21:33'! fileOutChanges "Bug workaround for squeak-flap 'fileOutChanges' buttons which for a while were mistakenly sending their requests here..." ^ ChangeSet current verboseFileOut. ! ! !Flaps class methodsFor: 'miscellaneous' stamp: 'sw 4/17/2001 13:24'! orientationForEdge: anEdge "Answer the orientation -- #horizontal or #vertical -- that corresponds to the edge symbol" ^ (#(left right) includes: anEdge) ifTrue: [#vertical] ifFalse: [#horizontal]! ! !Flaps class methodsFor: 'miscellaneous' stamp: 'sw 11/6/2000 14:23'! removeFromGlobalFlapTabList: aFlapTab "If the flap tab is in the global list, remove it" SharedFlapTabs remove: aFlapTab ifAbsent: []! ! !Flaps class methodsFor: 'new flap' stamp: 'alain.plantec 2/9/2009 12:09'! addLocalFlap "Menu command -- let the user add a new project-local flap. Once the new flap is born, the user can tell it to become a shared flap. Obtain an initial name and edge for the flap, launch the flap, and also launch a menu governing the flap, so that the user can get started right away with customizing it." | aMenu reply aFlapTab aWorld edge | edge := UIManager default chooseFrom: (#(left right top bottom) collect: [:e | e translated]) values: #(left right top bottom) title: 'Where should the new flap cling?' translated. edge ifNotNil: [reply := UIManager default request: 'Wording for this flap: ' translated initialAnswer: 'Flap' translated. reply isEmptyOrNil ifFalse: [aFlapTab := self newFlapTitled: reply onEdge: edge. (aWorld := self currentWorld) addMorphFront: aFlapTab. aFlapTab adaptToWorld: aWorld. aMenu := aFlapTab buildHandleMenu: ActiveHand. aFlapTab addTitleForHaloMenu: aMenu. aFlapTab computeEdgeFraction. aMenu popUpEvent: ActiveEvent in: ActiveWorld]] ! ! !Flaps class methodsFor: 'new flap' stamp: 'sw 5/4/2001 23:59'! defaultColorForFlapBackgrounds "Answer the color to use, by default, in new flap backgrounds" ^ (Color blue mixed: 0.8 with: Color white) alpha: 0.6! ! !Flaps class methodsFor: 'new flap' stamp: 'sw 4/17/2001 13:24'! newFlapTitled: aString onEdge: anEdge "Create a new flap with the given title and place it on the given edge" ^ self newFlapTitled: aString onEdge: anEdge inPasteUp: self currentWorld ! ! !Flaps class methodsFor: 'new flap' stamp: 'di 11/19/2001 21:07'! newFlapTitled: aString onEdge: anEdge inPasteUp: aPasteUpMorph "Add a flap with the given title, placing it on the given edge, in the given pasteup" | aFlapBody aFlapTab | aFlapBody := PasteUpMorph newSticky. aFlapTab := FlapTab new referent: aFlapBody. aFlapTab setName: aString edge: anEdge color: (Color r: 0.516 g: 0.452 b: 1.0). anEdge == #left ifTrue: [aFlapTab position: (aPasteUpMorph left @ aPasteUpMorph top). aFlapBody extent: (200 @ aPasteUpMorph height)]. anEdge == #right ifTrue: [aFlapTab position: ((aPasteUpMorph right - aFlapTab width) @ aPasteUpMorph top). aFlapBody extent: (200 @ aPasteUpMorph height)]. anEdge == #top ifTrue: [aFlapTab position: ((aPasteUpMorph left + 50) @ aPasteUpMorph top). aFlapBody extent: (aPasteUpMorph width @ 200)]. anEdge == #bottom ifTrue: [aFlapTab position: ((aPasteUpMorph left + 50) @ (aPasteUpMorph bottom - aFlapTab height)). aFlapBody extent: (aPasteUpMorph width @ 200)]. aFlapBody beFlap: true. aFlapBody color: self defaultColorForFlapBackgrounds. ^ aFlapTab! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'adrian_lienhard 7/19/2009 22:27'! addStandardFlaps "Initialize the standard default out-of-box set of global flaps. This method creates them and places them in my class variable #SharedFlapTabs, but does not itself get them displayed. " SharedFlapTabs ifNil: [SharedFlapTabs := OrderedCollection new]. SharedFlapTabs add: self newPharoFlap. "SharedFlapTabs add: self newPaintingFlap. Temporarily commented to make flaps working again until painting morph is fixed" self disableGlobalFlapWithID: 'Stack Tools' translated. self disableGlobalFlapWithID: 'Painting' translated. ^ SharedFlapTabs! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'adrian_lienhard 7/19/2009 19:59'! defaultsQuadsDefiningPlugInSuppliesFlap "Answer a list of quads which define the objects to appear in the default Supplies flap used in the Plug-in image" ^ #( (GrabPatchMorph new 'Grab Patch' 'Allows you to create a new Sketch by grabbing a rectangular patch from the screen') (LassoPatchMorph new 'Lasso' 'Allows you to create a new Sketch by lassoing an area from the screen') "(StickyPadMorph newStandAlone 'Sticky Pad' 'Each time you obtain one of these pastel, translucent, borderless rectangles, it will be a different color from the previous time.') (PaintInvokingMorph new 'Paint' 'Drop this into an area to start making a fresh painting there')" (TextMorph boldAuthoringPrototype 'Text' 'Text that you can edit into anything you desire.') (RecordingControlsMorph authoringPrototype 'Sound' 'A device for making sound recordings.') (RectangleMorph authoringPrototype 'Rectangle' 'A rectangle') (RectangleMorph roundRectPrototype 'RoundRect' 'A rectangle with rounded corners') (EllipseMorph authoringPrototype 'Ellipse' 'An ellipse or circle') (StarMorph authoringPrototype 'Star' 'A star') (CurveMorph authoringPrototype 'Curve' 'A curve') (PolygonMorph authoringPrototype 'Polygon' 'A straight-sided figure with any number of sides') (PasteUpMorph authoringPrototype 'Playfield' 'A place for assembling parts or for staging animations') (SimpleSliderMorph authoringPrototype 'Slider' 'A slider for showing and setting numeric values.') (JoystickMorph authoringPrototype 'Joystick' 'A joystick-like control') (ClockMorph authoringPrototype 'Clock' 'A simple digital clock')) asOrderedCollection! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'sw 8/12/2001 16:55'! initializeStandardFlaps "Initialize the standard default out-of-box set of global flaps. This method creates them and places them in my class variable #SharedFlapTabs, but does not itself get them displayed." SharedFlapTabs := nil. self addStandardFlaps! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'adrian_lienhard 7/19/2009 18:02'! newPharoFlap "Answer a new default 'Pharo' flap for the left edge of the screen" | aFlap aFlapTab aButton aClock buttonColor anOffset bb aFont | aFlap := PasteUpMorph newSticky borderWidth: 0. aFlapTab := FlapTab new referent: aFlap. aFlapTab setName: 'Pharo' translated edge: #left color: (Color gray lighter lighter). aFlapTab position: (0 @ ((Display height - aFlapTab height) // 8)). aFlapTab setBalloonText: aFlapTab balloonTextForFlapsMenu. aFlap cellInset: 14@14. aFlap beFlap: true. aFlap color: (Color gray muchLighter alpha: 0.8). aFlap extent: 150 @ self currentWorld height. aFlap layoutPolicy: TableLayout new. aFlap wrapCentering: #topLeft. aFlap layoutInset: 2. aFlap listDirection: #topToBottom. aFlap wrapDirection: #leftToRight. "self addProjectNavigationButtonsTo: aFlap." anOffset := 16. buttonColor := Color cyan muchLighter. bb := SimpleButtonMorph new target: SmalltalkImage current. bb color: buttonColor. aButton := bb copy. aButton actionSelector: #saveSession. aButton setBalloonText: 'Make a complete snapshot of the current state of the image onto disk.' translated. aButton label: 'save' translated font: (aFont := Preferences standardEToysFont). aFlap addCenteredAtBottom: aButton offset: anOffset. aButton := bb copy target: Utilities. aButton actionSelector: #updateFromServer. aButton label: 'load code updates' translated font: aFont. aButton color: buttonColor. aButton setBalloonText: 'Check the Pharo server for any new code updates, and load any that are found.' translated. aFlap addCenteredAtBottom: aButton offset: anOffset. aButton := SimpleButtonMorph new target: SmalltalkImage current; actionSelector: #aboutThisSystem; label: 'about this system' translated font: aFont. aButton color: buttonColor. aButton setBalloonText: 'click here to find out version information' translated. aFlap addCenteredAtBottom: aButton offset: anOffset. aFlap addCenteredAtBottom: (Preferences themeChoiceButtonOfColor: buttonColor font: aFont) offset: anOffset. ^ aFlapTab "Flaps replaceGlobalFlapwithID: 'Pharo' translated "! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'sw 3/3/2004 13:38'! quadsDefiningPlugInSuppliesFlap "Answer a list of quads which define the objects to appear in the default Supplies flap used in the Plug-in image" ^ self registeredFlapsQuadsAt: 'PlugIn Supplies'! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'asm 3/13/2003 10:25'! quadsDefiningStackToolsFlap "Answer a structure defining the items on the default system Stack Tools flap" ^ self registeredFlapsQuadsAt: 'Stack Tools' "Flaps replaceGlobalFlapwithID: 'Stack Tools'"! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'asm 3/13/2003 10:26'! quadsDefiningSuppliesFlap "Answer a list of quads which define the objects to appear in the default Supplies flap" ^ self registeredFlapsQuadsAt: 'Supplies'! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'asm 3/13/2003 10:51'! quadsDefiningToolsFlap "Answer a structure defining the default Tools flap" ^ self registeredFlapsQuadsAt: 'Tools'! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'asm 3/13/2003 10:26'! quadsDefiningWidgetsFlap "Answer a structure defining the default Widgets flap" ^ self registeredFlapsQuadsAt: 'Widgets'! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'asm 3/13/2003 10:26'! quadsDeiningScriptingFlap "Answer a structure defining the default items in the Scripting flap" ^ self registeredFlapsQuadsAt: 'Scripting'! ! !Flaps class methodsFor: 'predefined flaps' stamp: 'adrian_lienhard 7/19/2009 19:59'! twiddleSuppliesButtonsIn: aStrip "Munge item(s) in the strip whose names as seen in the parts bin should be different from the names to be given to resulting torn-off instances" " (aStrip submorphs detect: [:m | m target == StickyPadMorph] ifNone: [nil]) ifNotNil: [:aButton | aButton arguments: {#newStandAlone. 'tear off'}] "! ! !Flaps class methodsFor: 'replacement' stamp: 'adrian_lienhard 7/19/2009 22:27'! replaceGlobalFlapwithID: flapID "If there is a global flap with flapID, replace it with an updated one." | replacement tabs | (tabs := self globalFlapTabsWithID: flapID) size = 0 ifTrue: [^ self]. tabs do: [:tab | self removeFlapTab: tab keepInList: false]. flapID = 'Pharo' translated ifTrue: [replacement := self newPharoFlap]. replacement ifNil: [^ self]. self addGlobalFlap: replacement. self currentWorld ifNotNil: [self currentWorld addGlobalFlaps] "Flaps replaceFlapwithID: 'Widgets' translated "! ! !Flaps class methodsFor: 'replacement' stamp: 'adrian_lienhard 7/19/2009 20:54'! replacePartSatisfying: elementBlock inGlobalFlapSatisfying: flapBlock with: replacement "If any global flap satisfies flapBlock, look in it for a part satisfying elementBlock; if such a part is found, replace it with the replacement morph, make sure the flap's layout is made right, etc." | aFlapTab flapPasteUp anElement | aFlapTab := self globalFlapTabsIfAny detect: [:aTab | flapBlock value: aTab] ifNone: [^ self]. flapPasteUp := aFlapTab referent. anElement := flapPasteUp submorphs detect: [:aMorph | elementBlock value: aMorph] ifNone: [^ self]. flapPasteUp replaceSubmorph: anElement by: replacement. flapPasteUp setPartsBinStatusTo: true. "Flaps replacePartSatisfying: [:el | (el isKindOf: MorphThumbnail) and: [(el morphRepresented isKindOf: SystemWindow) and: [el morphRepresented label = 'scripting area']]] inGlobalFlapSatisfying: [:fl | (fl submorphs size > 0) and: [(fl submorphs first isKindOf: TextMorph) and: [(fl submorphs first contents string copyWithout: Character cr) = 'Tools']]] with: ScriptingSystem newScriptingSpace"! ! !Flaps class methodsFor: 'replacement' stamp: 'sw 4/17/2001 13:15'! replacePartSatisfying: elementBlock inGlobalFlapWithID: aFlapID with: replacement "If a global flapl exists with the given flapID, look in it for a part satisfying elementBlock; if such a part is found, replace it with the replacement morph, make sure the flap's layout is made right, etc." ^ self replacePartSatisfying: elementBlock inGlobalFlapSatisfying: [:fl | fl flapID = aFlapID] with: replacement! ! !Flaps class methodsFor: 'replacement' stamp: 'dgd 8/31/2003 19:41'! replaceToolsFlap "if there is a global tools flap, replace it with an updated one." self replaceGlobalFlapwithID: 'Tools' translated "Flaps replaceToolsFlap"! ! !Flaps class methodsFor: 'shared flaps' stamp: 'sw 4/17/2001 13:31'! addGlobalFlap: aFlapTab "Add the given flap tab to the list of shared flaps" SharedFlapTabs ifNil: [SharedFlapTabs := OrderedCollection new]. SharedFlapTabs add: aFlapTab! ! !Flaps class methodsFor: 'shared flaps' stamp: 'sw 7/24/2001 22:01'! enableOnlyGlobalFlapsWithIDs: survivorList "In the current project, suppress all global flaps other than those with ids in the survivorList" self globalFlapTabsIfAny do: [:aFlapTab | (survivorList includes: aFlapTab flapID) ifTrue: [self enableGlobalFlapWithID: aFlapTab flapID] ifFalse: [self disableGlobalFlapWithID: aFlapTab flapID]]. ActiveWorld addGlobalFlaps "Flaps enableOnlyGlobalFlapsWithIDs: #('Supplies')"! ! !Flaps class methodsFor: 'shared flaps' stamp: 'sw 4/27/2001 16:36'! globalFlapTabOrDummy: aName "Answer a global flap tab in the current image with the given name. If none is found, answer a dummy StringMorph for some reason (check with tk about the use of this)" | gg | (gg := self globalFlapTab: aName) ifNil: [^ StringMorph contents: aName, ' can''t be found']. ^ gg! ! !Flaps class methodsFor: 'shared flaps' stamp: 'sw 5/5/2001 02:41'! globalFlapTabs "Answer the list of shared flap tabs, creating it if necessary. Much less aggressive is #globalFlapTabsIfAny" SharedFlapTabs ifNil: [self initializeStandardFlaps]. ^ SharedFlapTabs copy! ! !Flaps class methodsFor: 'shared flaps' stamp: 'sw 4/23/2001 18:04'! globalFlapTabsIfAny "Answer a list of the global flap tabs, but it they don't exist, just answer an empty list" ^ SharedFlapTabs copy ifNil: [Array new]! ! !Flaps class methodsFor: 'shared flaps' stamp: 'sw 4/8/2002 08:41'! globalFlapTabsWithID: aFlapID "Answer all flap tabs whose ids start with the given id" ^ self globalFlapTabsIfAny select: [:aFlapTab | (aFlapTab flapID = aFlapID) or: [FlapTab givenID: aFlapTab flapID matches: aFlapID]] "Flaps globalFlapTabsWithID: 'Stack Tools'"! ! !Flaps class methodsFor: 'shared flaps' stamp: 'di 11/19/2001 22:07'! globalFlapTabWithID: aFlapID "answer the global flap tab with the given id, or nil if none" ^ self globalFlapTabsIfAny detect: [:aFlapTab | aFlapTab flapID = aFlapID] ifNone: ["Second try allows sequence numbers" self globalFlapTabsIfAny detect: [:aFlapTab | FlapTab givenID: aFlapTab flapID matches: aFlapID] ifNone: [nil]]! ! !Flaps class methodsFor: 'shared flaps' stamp: 'sw 4/27/2001 16:34'! globalFlapTab: aName "Answer the global flap tab in the current system whose flapID is the same as aName, or nil if none found." | idToMatch | idToMatch := (aName beginsWith: 'flap: ') ifTrue: "Ted's old scheme; this convention may still be found in pre-existing content that has been externalized" [aName copyFrom: 7 to: aName size] ifFalse: [aName]. ^ self globalFlapTabsIfAny detect: [:ft | ft flapID = idToMatch] ifNone: [nil]! ! !Flaps class methodsFor: 'shared flaps' stamp: 'marcus.denker 11/26/2008 14:19'! positionNavigatorAndOtherFlapsAccordingToPreference "Lay out flaps along the designated edge right-to-left, possibly positioning the navigator flap, exceptionally, on the left." Flaps positionVisibleFlapsRightToLeftOnEdge: #bottom butPlaceAtLeftFlapsWithIDs: {'Navigator' translated}. "Flaps positionNavigatorAndOtherFlapsAccordingToPreference"! ! !Flaps class methodsFor: 'shared flaps' stamp: 'dgd 8/31/2003 19:29'! positionVisibleFlapsRightToLeftOnEdge: edgeSymbol butPlaceAtLeftFlapsWithIDs: idList "Lay out flaps along the designated edge right-to-left, while laying left-to-right any flaps found in the exception list Flaps positionVisibleFlapsRightToLeftOnEdge: #bottom butPlaceAtLeftFlapWithIDs: {'Navigator' translated. 'Supplies' translated} Flaps sharedFlapsAlongBottom" | leftX flapList flapsOnRight flapsOnLeft | flapList := self globalFlapTabsIfAny select: [:aFlapTab | aFlapTab isInWorld and: [aFlapTab edgeToAdhereTo == edgeSymbol]]. flapsOnLeft := flapList select: [:fl | idList includes: fl flapID]. flapList removeAll: flapsOnLeft. flapsOnRight := flapList asSortedCollection: [:f1 :f2 | f1 left > f2 left]. leftX := ActiveWorld width - 15. flapsOnRight do: [:aFlapTab | aFlapTab right: leftX - 3. leftX := aFlapTab left]. leftX := ActiveWorld left. flapsOnLeft := flapsOnLeft asSortedCollection: [:f1 :f2 | f1 left > f2 left]. flapsOnLeft do: [:aFlapTab | aFlapTab left: leftX + 3. leftX := aFlapTab right]. (flapsOnLeft asOrderedCollection, flapsOnRight asOrderedCollection) do: [:ft | ft computeEdgeFraction. ft flapID = 'Navigator' translated ifTrue: [ft referent left: (ft center x - (ft referent width//2) max: 0)]] ! ! !Flaps class methodsFor: 'shared flaps' stamp: 'mir 8/24/2001 20:42'! removeDuplicateFlapTabs "Remove flaps that were accidentally added multiple times" "Flaps removeDuplicateFlapTabs" | tabs duplicates same | SharedFlapTabs copy ifNil: [^self]. tabs := SharedFlapTabs copy. duplicates := Set new. tabs do: [:tab | same := tabs select: [:each | each wording = tab wording]. same isEmpty not ifTrue: [ same removeFirst. duplicates addAll: same]]. SharedFlapTabs removeAll: duplicates! ! !Flaps class methodsFor: 'shared flaps' stamp: 'sw 4/24/2001 11:17'! sharedFlapsAllowed "Answer whether the shared flaps feature is allowed in this system" ^ SharedFlapsAllowed ifNil: [SharedFlapsAllowed := SharedFlapTabs isEmptyOrNil not]! ! !Flaps class methodsFor: 'shared flaps' stamp: 'marcus.denker 11/10/2008 10:04'! sharedFlapsAlongBottom "Put all shared flaps (except Painting which can't be moved) along the bottom" "Flaps sharedFlapsAlongBottom" | leftX unordered ordered | unordered := self globalFlapTabsIfAny asIdentitySet. ordered := Array streamContents: [:s | { 'Squeak' translated. 'Navigator' translated. 'Supplies' translated. 'Widgets' translated. 'Stack Tools' translated. 'Tools' translated. 'Painting' translated. } do: [:id | (self globalFlapTabWithID: id) ifNotNil: [:ft | unordered remove: ft. id = 'Painting' translated ifFalse: [s nextPut: ft]]]]. "Pace off in order from right to left, setting positions" leftX := Display width-15. ordered , unordered asArray reverseDo: [:ft | ft setEdge: #bottom. ft right: leftX - 3. leftX := ft left]. "Put Nav Bar centered under tab if possible" (self globalFlapTabWithID: 'Navigator' translated) ifNotNil: [:ft | ft referent left: (ft center x - (ft referent width//2) max: 0)]. self positionNavigatorAndOtherFlapsAccordingToPreference. ! ! !Flaps class methodsFor: 'deprecated' stamp: 'AndrewBlack 9/1/2009 16:09'! newSqueakFlap "Answer a new default 'Squeak' flap for the left edge of the screen" | aFlap aFlapTab aButton buttonColor anOffset bb aFont | self deprecated: 'This is Pharo, use ''newPharoFlap'' instead.'. aFlap := PasteUpMorph newSticky borderWidth: 0. aFlapTab := FlapTab new referent: aFlap. aFlapTab setName: 'Squeak' translated edge: #left color: Color brown lighter lighter. aFlapTab position: (0 @ ((Display height - aFlapTab height) // 2)). aFlapTab setBalloonText: aFlapTab balloonTextForFlapsMenu. aFlap cellInset: 14@14. aFlap beFlap: true. aFlap color: (Color brown muchLighter lighter "alpha: 0.3"). aFlap extent: 150 @ self currentWorld height. aFlap layoutPolicy: TableLayout new. aFlap wrapCentering: #topLeft. aFlap layoutInset: 2. aFlap listDirection: #topToBottom. aFlap wrapDirection: #leftToRight. "self addProjectNavigationButtonsTo: aFlap." anOffset := 16. buttonColor := Color cyan muchLighter. bb := SimpleButtonMorph new target: SmalltalkImage current. bb color: buttonColor. aButton := bb copy. aButton actionSelector: #saveSession. aButton setBalloonText: 'Make a complete snapshot of the current state of the image onto disk.' translated. aButton label: 'save' translated font: (aFont := Preferences standardEToysFont). aFlap addCenteredAtBottom: aButton offset: anOffset. aButton := bb copy target: Utilities. aButton actionSelector: #updateFromServer. aButton label: 'load code updates' translated font: aFont. aButton color: buttonColor. aButton setBalloonText: 'Check the Squeak server for any new code updates, and load any that are found.' translated. aFlap addCenteredAtBottom: aButton offset: anOffset. aButton := SimpleButtonMorph new target: SmalltalkImage current; actionSelector: #aboutThisSystem; label: 'about this system' translated font: aFont. aButton color: buttonColor. aButton setBalloonText: 'click here to find out version information' translated. aFlap addCenteredAtBottom: aButton offset: anOffset. aFlap addCenteredAtBottom: (Preferences themeChoiceButtonOfColor: buttonColor font: aFont) offset: anOffset. ^ aFlapTab "Flaps replaceGlobalFlapwithID: 'Squeak' translated "! ! NullEncoder subclass: #FlattenEncoder instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'! !FlattenEncoder commentStamp: '' prior: 0! The simplest possible encoding: leave the objects as is. ! !FlattenEncoder methodsFor: 'filter streaming' stamp: 'MPW 1/1/1901 01:32'! elementSeparator ^target elementSeparator.! ! !FlattenEncoder methodsFor: 'writing' stamp: 'MPW 1/1/1901 21:51'! cr ^self print:String cr. ! ! !FlattenEncoder methodsFor: 'writing' stamp: 'MPW 1/1/1901 21:50'! writeArrayedCollection:anArrayedCollection ^self writeCollectionContents:anArrayedCollection. ! ! !FlattenEncoder methodsFor: 'writing' stamp: 'MPW 1/1/1901 01:03'! writeCollection:aCollection ^self writeCollectionContents:aCollection. ! ! !FlattenEncoder methodsFor: 'writing' stamp: 'MPW 1/4/1901 08:26'! writeCollectionContents:aCollection ^self writeCollectionContents:aCollection separator:self elementSeparator iterationMessage:#do:. ! ! !FlattenEncoder methodsFor: 'writing' stamp: 'MPW 1/4/1901 08:26'! writeCollectionContents:aCollection separator:separator ^self writeCollectionContents:aCollection separator:separator iterationMessage:#do:.! ! !FlattenEncoder methodsFor: 'writing' stamp: 'MPW 1/4/1901 08:25'! writeCollectionContents:aCollection separator:separator iterationMessage:op | first | first := true. aCollection perform:op with: [ :each | first ifFalse:[ self writeObject:separator ]. self write:each. first:=false.]. ! ! !FlattenEncoder methodsFor: 'writing' stamp: 'MPW 1/4/1901 08:30'! writeDictionary:aCollection ^self writeDictionaryContents:aCollection separator:nil. ! ! !FlattenEncoder methodsFor: 'writing' stamp: 'MPW 1/4/1901 08:29'! writeDictionaryContents:aCollection separator:separator ^self writeCollectionContents:aCollection separator:separator iterationMessage:#associationsDo:.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FlattenEncoder class instanceVariableNames: ''! !FlattenEncoder class methodsFor: 'configuring' stamp: 'MPW 1/1/1901 00:08'! filterSelector ^#flattenOnStream: ! ! Number variableWordSubclass: #Float instanceVariableNames: '' classVariableNames: 'E Epsilon Halfpi Infinity Ln10 Ln2 MaxVal MaxValLn MinValLogBase2 NaN NegativeInfinity NegativeZero Pi RadiansPerDegree Sqrt2 ThreePi Twopi' poolDictionaries: '' category: 'Kernel-Numbers'! !Float commentStamp: '' prior: 0! My instances represent IEEE-754 floating-point double-precision numbers. They have about 16 digits of accuracy and their range is between plus and minus 10^307. Some valid examples are: 8.0 13.3 0.3 2.5e6 1.27e-30 1.27e-31 -12.987654e12 Mainly: no embedded blanks, little e for tens power, and a digit on both sides of the decimal point. It is actually possible to specify a radix for Squeak Float constants. This is great for teaching about numbers, but may be confusing to the average reader: 3r20.2 --> 6.66666666666667 8r20.2 --> 16.25 If you don't have access to the definition of IEEE-754, you can figure out what is going on by printing various simple values in Float hex. It may help you to know that the basic format is... sign 1 bit exponent 11 bits with bias of 1023 (16r3FF) to produce an exponent in the range -1023 .. +1024 - 16r000: significand = 0: Float zero significand ~= 0: Denormalized number (exp = -1024, no hidden '1' bit) - 16r7FF: significand = 0: Infinity significand ~= 0: Not A Number (NaN) representation mantissa 53 bits, but only 52 are stored (20 in the first word, 32 in the second). This is because a normalized mantissa, by definition, has a 1 to the right of its floating point, and IEEE-754 omits this redundant bit to gain an extra bit of precision instead. People talk about the mantissa without its leading one as the FRACTION, and with its leading 1 as the SIGNFICAND. The single-precision format is... sign 1 bit exponent 8 bits, with bias of 127, to represent -126 to +127 - 0x0 and 0xFF reserved for Float zero (mantissa is ignored) - 16r7F reserved for Float underflow/overflow (mantissa is ignored) mantissa 24 bits, but only 23 are stored This format is used in FloatArray (qv), and much can be learned from the conversion routines, Float asIEEE32BitWord, and Float class fromIEEE32Bit:. Thanks to Rich Harmon for asking many questions and to Tim Olson, Bruce Cohen, Rick Zaccone and others for the answers that I have collected here.! !Float methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:54'! * aNumber "Primitive. Answer the result of multiplying the receiver by aNumber. Fail if the argument is not a Float. Essential. See Object documentation whatIsAPrimitive." ^ aNumber adaptToFloat: self andSend: #*! ! !Float methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:22'! + aNumber "Primitive. Answer the sum of the receiver and aNumber. Essential. Fail if the argument is not a Float. See Object documentation whatIsAPrimitive." ^ aNumber adaptToFloat: self andSend: #+! ! !Float methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:55'! - aNumber "Primitive. Answer the difference between the receiver and aNumber. Fail if the argument is not a Float. Essential. See Object documentation whatIsAPrimitive." ^ aNumber adaptToFloat: self andSend: #-! ! !Float methodsFor: 'arithmetic' stamp: 'GabrielOmarCotelli 6/6/2009 17:12'! / aNumber "Primitive. Answer the result of dividing receiver by aNumber. Fail if the argument is not a Float. Essential. See Object documentation whatIsAPrimitive." aNumber = 0.0 ifTrue: [ ZeroDivide signalWithDividend: self]. ^aNumber adaptToFloat: self andSend: #/! ! !Float methodsFor: 'arithmetic'! abs "This is faster than using Number abs." self < 0.0 ifTrue: [^ 0.0 - self] ifFalse: [^ self]! ! !Float methodsFor: 'arithmetic'! negated "Answer a Number that is the negation of the receiver." ^0.0 - self! ! !Float methodsFor: 'arithmetic' stamp: 'GabrielOmarCotelli 5/23/2009 20:40'! reciprocal "Returns the reciprocal. If self is 0.0 the / signals a ZeroDivide" ^1.0 / self! ! !Float methodsFor: 'comparing' stamp: 'nice 3/28/2006 23:36'! < aNumber "Primitive. Compare the receiver with the argument and return true if the receiver is less than the argument. Otherwise return false. Fail if the argument is not a Float. Essential. See Object documentation whatIsAPrimitive." ^ aNumber adaptToFloat: self andCompare: # ^ aNumber adaptToFloat: self andCompare: #<=! ! !Float methodsFor: 'comparing' stamp: 'nice 3/28/2006 23:36'! = aNumber "Primitive. Compare the receiver with the argument and return true if the receiver is equal to the argument. Otherwise return false. Fail if the argument is not a Float. Essential. See Object documentation whatIsAPrimitive." aNumber isNumber ifFalse: [^ false]. ^ aNumber adaptToFloat: self andCompare: #=! ! !Float methodsFor: 'comparing' stamp: 'nice 3/28/2006 23:36'! > aNumber "Primitive. Compare the receiver with the argument and return true if the receiver is greater than the argument. Otherwise return false. Fail if the argument is not a Float. Essential. See Object documentation whatIsAPrimitive." ^ aNumber adaptToFloat: self andCompare: #>! ! !Float methodsFor: 'comparing' stamp: 'nice 7/10/2009 22:14'! >= aNumber "Primitive. Compare the receiver with the argument and return true if the receiver is greater than or equal to the argument. Otherwise return false. Fail if the argument is not a Float. Optional. See Object documentation whatIsAPrimitive. " ^ aNumber adaptToFloat: self andCompare: #>=! ! !Float methodsFor: 'comparing' stamp: 'nice 7/19/2009 19:27'! closeTo: num "are these two numbers close?" num isNumber ifFalse: [^[self = num] ifError: [false]]. self = 0.0 ifTrue: [^num abs < 0.0001]. num = 0 ifTrue: [^self abs < 0.0001]. ^self = num asFloat or: [(self - num) abs / (self abs max: num abs) < 0.0001]! ! !Float methodsFor: 'comparing' stamp: 'nice 6/11/2009 01:03'! hash "Hash is reimplemented because = is implemented. Both words of the float are used; 8 bits are removed from each end to clear most of the exponent regardless of the byte ordering. (The bitAnd:'s ensure that the intermediate results do not become a large integer.) Slower than the original version in the ratios 12:5 to 2:1 depending on values. (DNS, 11 May, 1997)" (self isFinite and: [self fractionPart = 0.0]) ifTrue: [^self truncated hash]. ^ (((self basicAt: 1) bitAnd: 16r00FFFF00) + ((self basicAt: 2) bitAnd: 16r00FFFF00)) bitShift: -8 ! ! !Float methodsFor: 'comparing'! ~= aNumber "Primitive. Compare the receiver with the argument and return true if the receiver is not equal to the argument. Otherwise return false. Fail if the argument is not a Float. Optional. See Object documentation whatIsAPrimitive." ^super ~= aNumber! ! !Float methodsFor: 'converting' stamp: 'mk 10/27/2003 18:16'! adaptToComplex: rcvr andSend: selector "If I am involved in arithmetic with a Complex number, convert me to a Complex number." ^ rcvr perform: selector with: self asComplex! ! !Float methodsFor: 'converting' stamp: 'nice 1/4/2009 20:31'! adaptToFraction: rcvr andCompare: selector "If I am involved in comparison with a Fraction, convert myself to a Fraction. This way, no bit is lost and comparison is exact." self isFinite ifFalse: [ selector == #= ifTrue: [^false]. selector == #~= ifTrue: [^true]. self isNaN ifTrue: [^ false]. (selector = #< or: [selector = #'<=']) ifTrue: [^ self positive]. (selector = #> or: [selector = #'>=']) ifTrue: [^ self positive not]. ^self error: 'unknow comparison selector']. "Try to avoid asTrueFraction because it can cost" selector == #= ifTrue: [ rcvr denominator isPowerOfTwo ifFalse: [^false]]. selector == #~= ifTrue: [ rcvr denominator isPowerOfTwo ifFalse: [^true]]. ^ rcvr perform: selector with: self asTrueFraction! ! !Float methodsFor: 'converting' stamp: 'di 11/6/1998 13:38'! adaptToFraction: rcvr andSend: selector "If I am involved in arithmetic with a Fraction, convert it to a Float." ^ rcvr asFloat perform: selector with: self! ! !Float methodsFor: 'converting' stamp: 'nice 1/4/2009 20:31'! adaptToInteger: rcvr andCompare: selector "If I am involved in comparison with an Integer, convert myself to a Fraction. This way, no bit is lost and comparison is exact." self isFinite ifFalse: [ selector == #= ifTrue: [^false]. selector == #~= ifTrue: [^true]. self isNaN ifTrue: [^ false]. (selector = #< or: [selector = #'<=']) ifTrue: [^ self positive]. (selector = #> or: [selector = #'>=']) ifTrue: [^ self positive not]. ^self error: 'unknow comparison selector']. "Try to avoid asTrueFraction because it can cost" selector == #= ifTrue: [ self fractionPart = 0.0 ifFalse: [^false]]. selector == #~= ifTrue: [ self fractionPart = 0.0 ifFalse: [^true]]. ^ rcvr perform: selector with: self asTrueFraction! ! !Float methodsFor: 'converting' stamp: 'di 11/6/1998 13:07'! adaptToInteger: rcvr andSend: selector "If I am involved in arithmetic with an Integer, convert it to a Float." ^ rcvr asFloat perform: selector with: self! ! !Float methodsFor: 'converting' stamp: 'st 9/17/2004 17:17'! asApproximateFraction "Answer a Fraction approximating the receiver. This conversion uses the continued fraction method to approximate a floating point number." ^ self asApproximateFractionAtOrder: 0! ! !Float methodsFor: 'converting' stamp: 'st 9/17/2004 17:14'! asApproximateFractionAtOrder: maxOrder "Answer a Fraction approximating the receiver. This conversion uses the continued fraction method to approximate a floating point number. If maxOrder is zero, use maximum order" | num1 denom1 num2 denom2 int frac newD temp order | num1 := self asInteger. "The first of two alternating numerators" denom1 := 1. "The first of two alternating denominators" num2 := 1. "The second numerator" denom2 := 0. "The second denominator--will update" int := num1. "The integer part of self" frac := self fractionPart. "The fractional part of self" order := maxOrder = 0 ifTrue: [-1] ifFalse: [maxOrder]. [frac = 0 or: [order = 0] ] whileFalse: ["repeat while the fractional part is not zero and max order is not reached" order := order - 1. newD := 1.0 / frac. "Take reciprocal of the fractional part" int := newD asInteger. "get the integer part of this" frac := newD fractionPart. "and save the fractional part for next time" temp := num2. "Get old numerator and save it" num2 := num1. "Set second numerator to first" num1 := num1 * int + temp. "Update first numerator" temp := denom2. "Get old denominator and save it" denom2 := denom1. "Set second denominator to first" denom1 := int * denom1 + temp. "Update first denominator" 10000000000.0 < denom1 ifTrue: ["Is ratio past float precision? If so, pick which of the two ratios to use" num2 = 0.0 ifTrue: ["Is second denominator 0?" ^ Fraction numerator: num1 denominator: denom1]. ^ Fraction numerator: num2 denominator: denom2]]. "If fractional part is zero, return the first ratio" denom1 = 1 ifTrue: ["Am I really an Integer?" ^ num1 "Yes, return Integer result"] ifFalse: ["Otherwise return Fraction result" ^ Fraction numerator: num1 denominator: denom1]! ! !Float methodsFor: 'converting' stamp: 'mk 10/27/2003 17:46'! asComplex "Answer a Complex number that represents value of the the receiver." ^ Complex real: self imaginary: 0! ! !Float methodsFor: 'converting'! asFloat "Answer the receiver itself." ^self! ! !Float methodsFor: 'converting' stamp: 'sma 5/3/2000 21:46'! asFraction ^ self asTrueFraction ! ! !Float methodsFor: 'converting' stamp: 'nice 5/30/2006 02:29'! asIEEE32BitWord "Convert the receiver into a 32 bit Integer value representing the same number in IEEE 32 bit format. Used for conversion in FloatArrays only." | word1 word2 sign mantissa exponent destWord truncatedBits mask roundToUpper | "skip fast positive and nnegative zero" self = 0.0 ifTrue: [^self basicAt: 1]. "retrieve 64 bits of IEEE 754 double" word1 := self basicAt: 1. word2 := self basicAt: 2. "prepare sign exponent and mantissa of 32 bits float" sign := word1 bitAnd: 16r80000000. exponent := ((word1 bitShift: -20) bitAnd: 16r7FF) - 1023 + 127. mantissa := (word2 bitShift: -29) + ((word1 bitAnd: 16rFFFFF) bitShift: 3). truncatedBits := (word2 bitAnd: 16r1FFFFFFF). "We must now honour default IEEE rounding mode (round to nearest even)" "we are below gradual underflow, even if rounded to upper mantissa" exponent < -24 ifTrue: [^sign "this can be negative zero"]. "BEWARE: rounding occurs on less than 23bits when gradual underflow" exponent <= 0 ifTrue: [mask := 1 bitShift: exponent negated. mantissa := mantissa bitOr: 16r800000. roundToUpper := (mantissa bitAnd: mask) isZero not and: [truncatedBits isZero not or: [(mantissa bitAnd: mask - 1) isZero not or: [(mantissa bitAnd: mask*2) isZero not]]]. mantissa := mantissa bitShift: exponent - 1. "exponent := exponent + 1"] ifFalse: [roundToUpper := (truncatedBits bitAnd: 16r10000000) isZero not and: [(mantissa bitAnd: 16r1) isZero not or: [(truncatedBits bitAnd: 16r0FFFFFFF) isZero not]] ]. "adjust mantissa and exponent due to IEEE rounding mode" roundToUpper ifTrue: [mantissa := mantissa + 1. mantissa > 16r7FFFFF ifTrue: [mantissa := 0. exponent := exponent+1]]. exponent > 254 ifTrue: ["Overflow" exponent := 255. self isNaN ifTrue: [mantissa isZero ifTrue: ["BEWARE: do not convert a NaN to infinity due to truncatedBits" mantissa := 1]] ifFalse: [mantissa := 0]]. "Encode the word" destWord := (sign bitOr: ((exponent max: 0) bitShift: 23)) bitOr: mantissa. ^ destWord! ! !Float methodsFor: 'converting' stamp: 'nice 3/29/2006 01:01'! asTrueFraction " Answer a fraction that EXACTLY represents self, a double precision IEEE floating point number. Floats are stored in the same form on all platforms. (Does handle gradual underflow but not NANs.) By David N. Smith with significant performance improvements by Luciano Esteban Notarfrancesco. (Version of 11April97)" | signexp positive expPart exp fraction fractionPart signedFraction result zeroBitsCount | self isInfinite ifTrue: [self error: 'Cannot represent infinity as a fraction']. self isNaN ifTrue: [self error: 'Cannot represent Not-a-Number as a fraction']. " Extract the sign and the biased exponent " signexp := (self basicAt: 1) bitShift: -20. positive := (signexp bitAnd: 16r800) = 0. expPart := signexp bitAnd: 16r7FF. " Extract fractional part; answer 0 if this is a true 0.0 value " fractionPart := (((self basicAt: 1) bitAnd: 16rFFFFF) bitShift: 32)+ (self basicAt: 2). ( expPart=0 and: [ fractionPart=0 ] ) ifTrue: [ ^ 0 ]. " Replace omitted leading 1 in fraction unless gradual underflow" fraction := expPart = 0 ifTrue: [fractionPart bitShift: 1] ifFalse: [fractionPart bitOr: 16r0010000000000000]. signedFraction := positive ifTrue: [fraction] ifFalse: [fraction negated]. "Unbias exponent: 16r3FF is bias; 52 is fraction width" exp := 16r3FF + 52 - expPart. " Form the result. When exp>52, the exponent is adjusted by the number of trailing zero bits in the fraction to minimize the (huge) time otherwise spent in #gcd:. " exp negative ifTrue: [ result := signedFraction bitShift: exp negated ] ifFalse: [ zeroBitsCount := fraction lowBit - 1. exp := exp - zeroBitsCount. exp <= 0 ifTrue: [ zeroBitsCount := zeroBitsCount + exp. "exp := 0." " Not needed; exp not refernced again " result := signedFraction bitShift: zeroBitsCount negated ] ifFalse: [ result := Fraction numerator: (signedFraction bitShift: zeroBitsCount negated) denominator: (1 bitShift: exp) ] ]. "Low cost validation omitted after extensive testing" "(result asFloat = self) ifFalse: [self error: 'asTrueFraction validation failed']." ^ result ! ! !Float methodsFor: 'converting'! degreesToRadians "Answer the receiver in radians. Assumes the receiver is in degrees." ^self * RadiansPerDegree! ! !Float methodsFor: 'converting'! radiansToDegrees "Answer the receiver in degrees. Assumes the receiver is in radians." ^self / RadiansPerDegree! ! !Float methodsFor: 'copying'! deepCopy ^self copy! ! !Float methodsFor: 'copying'! shallowCopy ^self + 0.0! ! !Float methodsFor: 'copying' stamp: 'tk 8/19/1998 16:08'! veryDeepCopyWith: deepCopier "Return self. Do not record me." ^ self clone! ! !Float methodsFor: 'mathematical functions'! arcCos "Answer the angle in radians." ^ Halfpi - self arcSin! ! !Float methodsFor: 'mathematical functions' stamp: 'jsp 2/25/1999 11:15'! arcSin "Answer the angle in radians." ((self < -1.0) or: [self > 1.0]) ifTrue: [self error: 'Value out of range']. ((self = -1.0) or: [self = 1.0]) ifTrue: [^ Halfpi * self] ifFalse: [^ (self / (1.0 - (self * self)) sqrt) arcTan]! ! !Float methodsFor: 'mathematical functions'! arcTan "Answer the angle in radians. Optional. See Object documentation whatIsAPrimitive." | theta eps step sinTheta cosTheta | "Newton-Raphson" self < 0.0 ifTrue: [ ^ 0.0 - (0.0 - self) arcTan ]. "first guess" theta := (self * Halfpi) / (self + 1.0). "iterate" eps := Halfpi * Epsilon. step := theta. [(step * step) > eps] whileTrue: [ sinTheta := theta sin. cosTheta := theta cos. step := (sinTheta * cosTheta) - (self * cosTheta * cosTheta). theta := theta - step]. ^ theta! ! !Float methodsFor: 'mathematical functions' stamp: 'HilaireFernandes 1/16/2006 21:47'! arcTan: denominator "Answer the angle in radians. Optional. See Object documentation whatIsAPrimitive." | result | (self = 0.0) ifTrue: [ (denominator > 0.0) ifTrue: [ result := 0 ] ifFalse: [ result := Pi ] ] ifFalse: [(denominator = 0.0) ifTrue: [ (self > 0.0) ifTrue: [ result := Halfpi ] ifFalse: [ result := Halfpi negated ] ] ifFalse: [ (denominator > 0) ifTrue: [ result := (self / denominator) arcTan ] ifFalse: [ (self > 0) ifTrue: [result := ((self / denominator) arcTan) + Pi ] ifFalse: [result := ((self / denominator) arcTan) - Pi] ] ]. ]. ^ result.! ! !Float methodsFor: 'mathematical functions'! cos "Answer the cosine of the receiver taken as an angle in radians." ^ (self + Halfpi) sin! ! !Float methodsFor: 'mathematical functions'! degreeCos "Answer the cosine of the receiver taken as an angle in degrees." ^ self degreesToRadians cos! ! !Float methodsFor: 'mathematical functions'! degreeSin "Answer the sine of the receiver taken as an angle in degrees." ^ self degreesToRadians sin! ! !Float methodsFor: 'mathematical functions'! exp "Answer E raised to the receiver power. Optional. See Object documentation whatIsAPrimitive." | base fract correction delta div | "Taylor series" "check the special cases" self < 0.0 ifTrue: [^ (self negated exp) reciprocal]. self = 0.0 ifTrue: [^ 1]. self abs > MaxValLn ifTrue: [self error: 'exp overflow']. "get first approximation by raising e to integer power" base := E raisedToInteger: (self truncated). "now compute the correction with a short Taylor series" "fract will be 0..1, so correction will be 1..E" "in the worst case, convergance time is logarithmic with 1/Epsilon" fract := self fractionPart. fract = 0.0 ifTrue: [ ^ base ]. "no correction required" correction := 1.0 + fract. delta := fract * fract / 2.0. div := 2.0. [delta > Epsilon] whileTrue: [ correction := correction + delta. div := div + 1.0. delta := delta * fract / div]. correction := correction + delta. ^ base * correction! ! !Float methodsFor: 'mathematical functions' stamp: 'jm 3/27/98 06:28'! floorLog: radix "Answer the floor of the log base radix of the receiver." ^ (self log: radix) floor ! ! !Float methodsFor: 'mathematical functions'! ln "Answer the natural logarithm of the receiver. Optional. See Object documentation whatIsAPrimitive." | expt n mant x div pow delta sum eps | "Taylor series" self <= 0.0 ifTrue: [self error: 'ln is only defined for x > 0.0']. "get a rough estimate from binary exponent" expt := self exponent. n := Ln2 * expt. mant := self timesTwoPower: 0 - expt. "compute fine correction from mantinssa in Taylor series" "mant is in the range [0..2]" "we unroll the loop to avoid use of abs" x := mant - 1.0. div := 1.0. pow := delta := sum := x. x := x negated. "x <= 0" eps := Epsilon * (n abs + 1.0). [delta > eps] whileTrue: [ "pass one: delta is positive" div := div + 1.0. pow := pow * x. delta := pow / div. sum := sum + delta. "pass two: delta is negative" div := div + 1.0. pow := pow * x. delta := pow / div. sum := sum + delta]. ^ n + sum "2.718284 ln 1.0"! ! !Float methodsFor: 'mathematical functions'! log "Answer the base 10 logarithm of the receiver." ^ self ln / Ln10! ! !Float methodsFor: 'mathematical functions' stamp: 'tao 4/19/98 23:22'! reciprocalFloorLog: radix "Quick computation of (self log: radix) floor, when self < 1.0. Avoids infinite recursion problems with denormalized numbers" | adjust scale n | adjust := 0. scale := 1.0. [(n := radix / (self * scale)) isInfinite] whileTrue: [scale := scale * radix. adjust := adjust + 1]. ^ ((n floorLog: radix) + adjust) negated! ! !Float methodsFor: 'mathematical functions' stamp: 'tao 10/15/97 14:23'! reciprocalLogBase2 "optimized for self = 10, for use in conversion for printing" ^ self = 10.0 ifTrue: [Ln2 / Ln10] ifFalse: [Ln2 / self ln]! ! !Float methodsFor: 'mathematical functions' stamp: 'laza 12/21/1999 12:15'! safeArcCos "Answer the angle in radians." (self between: -1.0 and: 1.0) ifTrue: [^ self arcCos] ifFalse: [^ self sign arcCos]! ! !Float methodsFor: 'mathematical functions'! sin "Answer the sine of the receiver taken as an angle in radians. Optional. See Object documentation whatIsAPrimitive." | sum delta self2 i | "Taylor series" "normalize to the range [0..Pi/2]" self < 0.0 ifTrue: [^ (0.0 - ((0.0 - self) sin))]. self > Twopi ifTrue: [^ (self \\ Twopi) sin]. self > Pi ifTrue: [^ (0.0 - (self - Pi) sin)]. self > Halfpi ifTrue: [^ (Pi - self) sin]. "unroll loop to avoid use of abs" sum := delta := self. self2 := 0.0 - (self * self). i := 2.0. [delta > Epsilon] whileTrue: [ "once" delta := (delta * self2) / (i * (i + 1.0)). i := i + 2.0. sum := sum + delta. "twice" delta := (delta * self2) / (i * (i + 1.0)). i := i + 2.0. sum := sum + delta]. ^ sum! ! !Float methodsFor: 'mathematical functions' stamp: 'RAH 4/25/2000 19:49'! sqrt "Answer the square root of the receiver. Optional. See Object documentation whatIsAPrimitive." | exp guess eps delta | #Numeric. "Changed 200/01/19 For ANSI support." "Newton-Raphson" self <= 0.0 ifTrue: [self = 0.0 ifTrue: [^ 0.0] ifFalse: ["v Chg" ^ FloatingPointException signal: 'undefined if less than zero.']]. "first guess is half the exponent" exp := self exponent // 2. guess := self timesTwoPower: 0 - exp. "get eps value" eps := guess * Epsilon. eps := eps * eps. delta := self - (guess * guess) / (guess * 2.0). [delta * delta > eps] whileTrue: [guess := guess + delta. delta := self - (guess * guess) / (guess * 2.0)]. ^ guess! ! !Float methodsFor: 'mathematical functions'! tan "Answer the tangent of the receiver taken as an angle in radians." ^ self sin / self cos! ! !Float methodsFor: 'mathematical functions'! timesTwoPower: anInteger "Primitive. Answer with the receiver multiplied by 2.0 raised to the power of the argument. Optional. See Object documentation whatIsAPrimitive." anInteger < -29 ifTrue: [^ self * (2.0 raisedToInteger: anInteger)]. anInteger < 0 ifTrue: [^ self / (1 bitShift: (0 - anInteger)) asFloat]. anInteger < 30 ifTrue: [^ self * (1 bitShift: anInteger) asFloat]. ^ self * (2.0 raisedToInteger: anInteger)! ! !Float methodsFor: 'printing' stamp: 'MPW 1/1/1901 01:59'! absByteEncode: aStream base: base "Print my value on a stream in the given base. Assumes that my value is strictly positive; negative numbers, zero, and NaNs have already been handled elsewhere. Based upon the algorithm outlined in: Robert G. Burger and R. Kent Dybvig Printing Floating Point Numbers Quickly and Accurately ACM SIGPLAN 1996 Conference on Programming Language Design and Implementation June 1996. This version performs all calculations with Floats instead of LargeIntegers, and loses about 3 lsbs of accuracy compared to an exact conversion." | significantBits fBase exp baseExpEstimate r s mPlus mMinus scale d tc1 tc2 fixedFormat decPointCount | self isInfinite ifTrue: [aStream print: 'Infinity'. ^ self]. significantBits := 50. "approximately 3 lsb's of accuracy loss during conversion" fBase := base asFloat. exp := self exponent. baseExpEstimate := (exp * fBase reciprocalLogBase2 - 1.0e-10) ceiling. exp >= 0 ifTrue: [r := self. s := 1.0. mPlus := 1.0 timesTwoPower: exp - significantBits. mMinus := self significand ~= 1.0 ifTrue: [mPlus] ifFalse: [mPlus / 2.0]] ifFalse: [r := self timesTwoPower: significantBits. s := 1.0 timesTwoPower: significantBits. mMinus := 1.0 timesTwoPower: (exp max: -1024). mPlus := (exp = MinValLogBase2) | (self significand ~= 1.0) ifTrue: [mMinus] ifFalse: [mMinus * 2.0]]. baseExpEstimate >= 0 ifTrue: [s := s * (fBase raisedToInteger: baseExpEstimate). exp = 1023 ifTrue: "scale down to prevent overflow to Infinity during conversion" [r := r / fBase. s := s / fBase. mPlus := mPlus / fBase. mMinus := mMinus / fBase]] ifFalse: [exp < -1023 ifTrue: "scale up to prevent denorm reciprocals overflowing to Infinity" [d := (53 * fBase reciprocalLogBase2 - 1.0e-10) ceiling. scale := fBase raisedToInteger: d. r := r * scale. mPlus := mPlus * scale. mMinus := mMinus * scale. scale := fBase raisedToInteger: (baseExpEstimate + d) negated] ifFalse: [scale := fBase raisedToInteger: baseExpEstimate negated]. s := s / scale]. (r + mPlus >= s) ifTrue: [baseExpEstimate := baseExpEstimate + 1] ifFalse: [s := s / fBase]. (fixedFormat := baseExpEstimate between: -3 and: 6) ifTrue: [decPointCount := baseExpEstimate. baseExpEstimate <= 0 ifTrue: [aStream print: ('0.000000' truncateTo: 2 - baseExpEstimate)]] ifFalse: [decPointCount := 1]. [d := (r / s) truncated. r := r - (d * s). (tc1 := r <= mMinus) | (tc2 := r + mPlus >= s)] whileFalse: [aStream print: (Character digitValue: d). r := r * fBase. mPlus := mPlus * fBase. mMinus := mMinus * fBase. decPointCount := decPointCount - 1. decPointCount = 0 ifTrue: [aStream print: $.]]. tc2 ifTrue: [tc1 not | (tc1 & (r*2.0 >= s)) ifTrue: [d := d + 1]]. aStream print: (Character digitValue: d). decPointCount > 0 ifTrue: [decPointCount - 1 to: 1 by: -1 do: [:i | aStream print: $0]. aStream print: '.0']. fixedFormat ifFalse: [aStream print: $e. aStream print: (baseExpEstimate - 1) printString]! ! !Float methodsFor: 'printing' stamp: 'tao 4/19/98 23:21'! absPrintExactlyOn: aStream base: base "Print my value on a stream in the given base. Assumes that my value is strictly positive; negative numbers, zero, and NaNs have already been handled elsewhere. Based upon the algorithm outlined in: Robert G. Burger and R. Kent Dybvig Printing Floating Point Numbers Quickly and Accurately ACM SIGPLAN 1996 Conference on Programming Language Design and Implementation June 1996. This version guarantees that the printed representation exactly represents my value by using exact integer arithmetic." | fBase significand exp baseExpEstimate be be1 r s mPlus mMinus scale roundingIncludesLimits d tc1 tc2 fixedFormat decPointCount | self isInfinite ifTrue: [aStream nextPutAll: 'Infinity'. ^ self]. fBase := base asFloat. significand := self significandAsInteger. roundingIncludesLimits := significand even. exp := (self exponent - 52) max: MinValLogBase2. baseExpEstimate := (self exponent * fBase reciprocalLogBase2 - 1.0e-10) ceiling. exp >= 0 ifTrue: [be := 1 << exp. significand ~= 16r10000000000000 ifTrue: [r := significand * be * 2. s := 2. mPlus := be. mMinus := be] ifFalse: [be1 := be * 2. r := significand * be1 * 2. s := 4. mPlus := be1. mMinus := be]] ifFalse: [(exp = MinValLogBase2) | (significand ~= 16r10000000000000) ifTrue: [r := significand * 2. s := (1 << (exp negated)) * 2. mPlus := 1. mMinus := 1] ifFalse: [r := significand * 4. s := (1 << (exp negated + 1)) * 2. mPlus := 2. mMinus := 1]]. baseExpEstimate >= 0 ifTrue: [s := s * (base raisedToInteger: baseExpEstimate)] ifFalse: [scale := base raisedToInteger: baseExpEstimate negated. r := r * scale. mPlus := mPlus * scale. mMinus := mMinus * scale]. (r + mPlus > s) | (roundingIncludesLimits & (r + mPlus = s)) ifTrue: [baseExpEstimate := baseExpEstimate + 1] ifFalse: [r := r * base. mPlus := mPlus * base. mMinus := mMinus * base]. (fixedFormat := baseExpEstimate between: -3 and: 6) ifTrue: [decPointCount := baseExpEstimate. baseExpEstimate <= 0 ifTrue: [aStream nextPutAll: ('0.000000' truncateTo: 2 - baseExpEstimate)]] ifFalse: [decPointCount := 1]. [d := r // s. r := r \\ s. (tc1 := (r < mMinus) | (roundingIncludesLimits & (r = mMinus))) | (tc2 := (r + mPlus > s) | (roundingIncludesLimits & (r + mPlus = s)))] whileFalse: [aStream nextPut: (Character digitValue: d). r := r * base. mPlus := mPlus * base. mMinus := mMinus * base. decPointCount := decPointCount - 1. decPointCount = 0 ifTrue: [aStream nextPut: $.]]. tc2 ifTrue: [tc1 not | (tc1 & (r*2 >= s)) ifTrue: [d := d + 1]]. aStream nextPut: (Character digitValue: d). decPointCount > 0 ifTrue: [decPointCount - 1 to: 1 by: -1 do: [:i | aStream nextPut: $0]. aStream nextPutAll: '.0']. fixedFormat ifFalse: [aStream nextPut: $e. aStream nextPutAll: (baseExpEstimate - 1) printString]! ! !Float methodsFor: 'printing' stamp: 'tao 4/22/98 11:58'! absPrintOn: aStream base: base "Print my value on a stream in the given base. Assumes that my value is strictly positive; negative numbers, zero, and NaNs have already been handled elsewhere. Based upon the algorithm outlined in: Robert G. Burger and R. Kent Dybvig Printing Floating Point Numbers Quickly and Accurately ACM SIGPLAN 1996 Conference on Programming Language Design and Implementation June 1996. This version performs all calculations with Floats instead of LargeIntegers, and loses about 3 lsbs of accuracy compared to an exact conversion." | significantBits fBase exp baseExpEstimate r s mPlus mMinus scale d tc1 tc2 fixedFormat decPointCount | self isInfinite ifTrue: [aStream nextPutAll: 'Infinity'. ^ self]. significantBits := 50. "approximately 3 lsb's of accuracy loss during conversion" fBase := base asFloat. exp := self exponent. baseExpEstimate := (exp * fBase reciprocalLogBase2 - 1.0e-10) ceiling. exp >= 0 ifTrue: [r := self. s := 1.0. mPlus := 1.0 timesTwoPower: exp - significantBits. mMinus := self significand ~= 1.0 ifTrue: [mPlus] ifFalse: [mPlus / 2.0]] ifFalse: [r := self timesTwoPower: significantBits. s := 1.0 timesTwoPower: significantBits. mMinus := 1.0 timesTwoPower: (exp max: -1024). mPlus := (exp = MinValLogBase2) | (self significand ~= 1.0) ifTrue: [mMinus] ifFalse: [mMinus * 2.0]]. baseExpEstimate >= 0 ifTrue: [s := s * (fBase raisedToInteger: baseExpEstimate). exp = 1023 ifTrue: "scale down to prevent overflow to Infinity during conversion" [r := r / fBase. s := s / fBase. mPlus := mPlus / fBase. mMinus := mMinus / fBase]] ifFalse: [exp < -1023 ifTrue: "scale up to prevent denorm reciprocals overflowing to Infinity" [d := (53 * fBase reciprocalLogBase2 - 1.0e-10) ceiling. scale := fBase raisedToInteger: d. r := r * scale. mPlus := mPlus * scale. mMinus := mMinus * scale. scale := fBase raisedToInteger: (baseExpEstimate + d) negated] ifFalse: [scale := fBase raisedToInteger: baseExpEstimate negated]. s := s / scale]. (r + mPlus >= s) ifTrue: [baseExpEstimate := baseExpEstimate + 1] ifFalse: [s := s / fBase]. (fixedFormat := baseExpEstimate between: -3 and: 6) ifTrue: [decPointCount := baseExpEstimate. baseExpEstimate <= 0 ifTrue: [aStream nextPutAll: ('0.000000' truncateTo: 2 - baseExpEstimate)]] ifFalse: [decPointCount := 1]. [d := (r / s) truncated. r := r - (d * s). (tc1 := r <= mMinus) | (tc2 := r + mPlus >= s)] whileFalse: [aStream nextPut: (Character digitValue: d). r := r * fBase. mPlus := mPlus * fBase. mMinus := mMinus * fBase. decPointCount := decPointCount - 1. decPointCount = 0 ifTrue: [aStream nextPut: $.]]. tc2 ifTrue: [tc1 not | (tc1 & (r*2.0 >= s)) ifTrue: [d := d + 1]]. aStream nextPut: (Character digitValue: d). decPointCount > 0 ifTrue: [decPointCount - 1 to: 1 by: -1 do: [:i | aStream nextPut: $0]. aStream nextPutAll: '.0']. fixedFormat ifFalse: [aStream nextPut: $e. aStream nextPutAll: (baseExpEstimate - 1) printString]! ! !Float methodsFor: 'printing' stamp: 'MPW 1/1/1901 00:02'! byteEncode: aStream base: base "Handle sign, zero, and NaNs; all other values passed to absPrintOn:base:" self isNaN ifTrue: [aStream print: 'NaN'. ^ self]. "check for NaN before sign" self > 0.0 ifTrue: [self absByteEncode: aStream base: base] ifFalse: [self sign = -1 ifTrue: [aStream print: '-']. self = 0.0 ifTrue: [aStream print: '0.0'. ^ self] ifFalse: [aStream writeNumber:self negated base: base]]! ! !Float methodsFor: 'printing' stamp: 'eem 6/11/2008 17:38'! hex "If ya really want to know..." ^ String streamContents: [:strm | | word nibble | 1 to: 2 do: [:i | word := self at: i. 1 to: 8 do: [:s | nibble := (word bitShift: -8+s*4) bitAnd: 16rF. strm nextPut: ('0123456789ABCDEF' at: nibble+1)]]] " (-2.0 to: 2.0) collect: [:f | f hex] "! ! !Float methodsFor: 'printing' stamp: 'tao 4/19/98 23:31'! printOn: aStream base: base "Handle sign, zero, and NaNs; all other values passed to absPrintOn:base:" self isNaN ifTrue: [aStream nextPutAll: 'NaN'. ^ self]. "check for NaN before sign" self > 0.0 ifTrue: [self absPrintOn: aStream base: base] ifFalse: [self sign = -1 ifTrue: [aStream nextPutAll: '-']. self = 0.0 ifTrue: [aStream nextPutAll: '0.0'. ^ self] ifFalse: [self negated absPrintOn: aStream base: base]]! ! !Float methodsFor: 'printing' stamp: 'PeterHugossonMiller 9/3/2009 01:33'! printPaddedWith: aCharacter to: aNumber "Answer the string containing the ASCII representation of the receiver padded on the left with aCharacter to be at least on aNumber integerPart characters and padded the right with aCharacter to be at least anInteger fractionPart characters." | aStream digits fPadding fLen iPadding iLen curLen periodIndex | #Numeric. "2000/03/04 Harmon R. Added Date and Time support" aStream := (String new: 10) writeStream. self printOn: aStream. digits := aStream contents. periodIndex := digits indexOf: $.. curLen := periodIndex - 1. iLen := aNumber integerPart. curLen < iLen ifTrue: [iPadding := (String new: (iLen - curLen) asInteger) atAllPut: aCharacter; yourself] ifFalse: [iPadding := '']. curLen := digits size - periodIndex. fLen := (aNumber fractionPart * (aNumber asFloat exponent * 10)) asInteger. curLen < fLen ifTrue: [fPadding := (String new: fLen - curLen) atAllPut: aCharacter; yourself] ifFalse: [fPadding := '']. ^ iPadding , digits , fPadding! ! !Float methodsFor: 'printing' stamp: 'nice 3/24/2008 16:56'! printShowingDecimalPlaces: placesDesired "This implementation avoids any rounding error caused by rounded or roundTo:" ^self asTrueFraction printShowingDecimalPlaces: placesDesired! ! !Float methodsFor: 'printing' stamp: 'nice 10/11/2008 21:42'! storeOn: aStream base: base "Defined here to handle special cases of NaN Infinity and negative zero" | abs | self isNaN ifTrue: [aStream nextPutAll: 'NaN'. ^ self]. "check for NaN before sign" abs := self sign = -1 "Test sign rather than > 0 for special case of negative zero" ifTrue: [aStream nextPutAll: '-'. self negated] ifFalse: [self]. abs isInfinite ifTrue: [aStream nextPutAll: 'Infinity'. ^ self]. base = 10 ifFalse: [aStream print: base; nextPut: $r]. self = 0.0 ifTrue: [aStream nextPutAll: '0.0'. ^ self] ifFalse: [abs absPrintOn: aStream base: base]! ! !Float methodsFor: 'testing' stamp: 'bf 8/20/1999 12:56'! hasContentsInExplorer ^false! ! !Float methodsFor: 'testing' stamp: 'nice 3/14/2008 23:45'! isFinite "simple, byte-order independent test for rejecting Not-a-Number and (Negative)Infinity" ^(self - self) = 0.0! ! !Float methodsFor: 'testing'! isFloat ^ true! ! !Float methodsFor: 'testing' stamp: 'jm 4/30/1998 13:50'! isInfinite "Return true if the receiver is positive or negative infinity." ^ self = Infinity or: [self = NegativeInfinity] ! ! !Float methodsFor: 'testing' stamp: 'nice 3/14/2008 23:49'! isLiteral "There is no literal representation of NaN. However, there are literal representations of Infinity, like 1.0e1000. But since they are not able to print properly, only case of finite Float is considered." ^self isFinite! ! !Float methodsFor: 'testing' stamp: 'tao 10/10/97 16:39'! isNaN "simple, byte-order independent test for Not-a-Number" ^ self ~= self! ! !Float methodsFor: 'testing' stamp: 'ar 6/9/2000 18:56'! isPowerOfTwo "Return true if the receiver is an integral power of two. Floats never return true here." ^false! ! !Float methodsFor: 'testing'! isZero ^self = 0.0! ! !Float methodsFor: 'testing' stamp: 'jm 4/28/1998 01:10'! sign "Answer 1 if the receiver is greater than 0, -1 if less than 0, else 0. Handle IEEE-754 negative-zero by reporting a sign of -1" self > 0 ifTrue: [^ 1]. (self < 0 or: [((self at: 1) bitShift: -31) = 1]) ifTrue: [^ -1]. ^ 0! ! !Float methodsFor: 'truncation and round off'! exponent "Primitive. Consider the receiver to be represented as a power of two multiplied by a mantissa (between one and two). Answer with the SmallInteger to whose power two is raised. Optional. See Object documentation whatIsAPrimitive." | positive | self >= 1.0 ifTrue: [^self floorLog: 2]. self > 0.0 ifTrue: [positive := (1.0 / self) exponent. self = (1.0 / (1.0 timesTwoPower: positive)) ifTrue: [^positive negated] ifFalse: [^positive negated - 1]]. self = 0.0 ifTrue: [^-1]. ^self negated exponent! ! !Float methodsFor: 'truncation and round off'! fractionPart "Primitive. Answer a Float whose value is the difference between the receiver and the receiver's asInteger value. Optional. See Object documentation whatIsAPrimitive." ^self - self truncated asFloat! ! !Float methodsFor: 'truncation and round off'! integerPart "Answer a Float whose value is the receiver's truncated value." ^self - self fractionPart! ! !Float methodsFor: 'truncation and round off' stamp: 'nice 6/11/2009 20:37'! predecessor | mantissa biasedExponent | self isFinite ifFalse: [ (self isNaN or: [self negative]) ifTrue: [^self]. ^Float fmax]. self = 0.0 ifTrue: [^Float fmin negated]. mantissa := self significandAsInteger. (mantissa isPowerOfTwo and: [self positive]) ifTrue: [mantissa := mantissa bitShift: 1]. biasedExponent := self exponent - mantissa highBit + 1. ^self sign * (mantissa - self sign) asFloat timesTwoPower: biasedExponent! ! !Float methodsFor: 'truncation and round off' stamp: 'tk 12/30/2000 20:04'! reduce "If self is close to an integer, return that integer" (self closeTo: self rounded) ifTrue: [^ self rounded]! ! !Float methodsFor: 'truncation and round off' stamp: 'nice 7/24/2008 01:32'! rounded "Answer the integer nearest the receiver. Implementation note: super would not handle tricky inexact arithmetic" "self assert: 5000000000000001.0 rounded = 5000000000000001" self fractionPart abs < 0.5 ifTrue: [^self truncated] ifFalse: [^self truncated + self sign rounded]! ! !Float methodsFor: 'truncation and round off' stamp: 'tao 4/19/98 13:14'! significand ^ self timesTwoPower: (self exponent negated)! ! !Float methodsFor: 'truncation and round off' stamp: 'nice 3/23/2008 16:03'! significandAsInteger | exp sig | exp := self exponent. sig := (((self at: 1) bitAnd: 16r000FFFFF) bitShift: 32) bitOr: (self at: 2). (exp > -1023 and: [self ~= 0.0]) ifTrue: [sig := sig bitOr: (1 bitShift: 52)]. ^ sig.! ! !Float methodsFor: 'truncation and round off' stamp: 'nice 6/11/2009 20:37'! successor | mantissa biasedExponent | self isFinite ifFalse: [ (self isNaN or: [self positive]) ifTrue: [^self]. ^Float fmax negated]. self = 0.0 ifTrue: [^Float fmin]. mantissa := self significandAsInteger. (mantissa isPowerOfTwo and: [self negative]) ifTrue: [mantissa := mantissa bitShift: 1]. biasedExponent := self exponent - mantissa highBit + 1. ^self sign * (mantissa + self sign) asFloat timesTwoPower: biasedExponent! ! !Float methodsFor: 'truncation and round off' stamp: 'nice 4/26/2006 05:09'! truncated "Answer with a SmallInteger equal to the value of the receiver without its fractional part. The primitive fails if the truncated value cannot be represented as a SmallInteger. In that case, the code below will compute a LargeInteger truncated value. Essential. See Object documentation whatIsAPrimitive. " (self isInfinite or: [self isNaN]) ifTrue: [self error: 'Cannot truncate this number']. self abs < 2.0e16 ifTrue: ["Fastest way when it may not be an integer" "^ (self quo: 1073741823.0) * 1073741823 + (self rem: 1073741823.0) truncated" | di df q r | di := (SmallInteger maxVal bitShift: -1)+1. df := di asFloat. q := self quo: df. r := self - (q asFloat * df). ^q*di+r truncated] ifFalse: [^ self asTrueFraction. "Extract all bits of the mantissa and shift if necess"] ! ! !Float methodsFor: 'private' stamp: 'nice 8/9/2009 21:01'! absPrintOn: aStream base: base digitCount: digitCount "Print me in the given base, using digitCount significant figures." | fuzz x exp q fBase scale logScale xi | self isInfinite ifTrue: [^ aStream nextPutAll: 'Inf']. fBase := base asFloat. "x is myself normalized to [1.0, fBase), exp is my exponent" exp := self < 1.0 ifTrue: [self reciprocalFloorLog: fBase] ifFalse: [self floorLog: fBase]. scale := 1.0. logScale := 0. [(x := fBase raisedTo: (exp + logScale)) = 0] whileTrue: [scale := scale * fBase. logScale := logScale + 1]. x := self * scale / x. fuzz := fBase raisedTo: 1 - digitCount. "round the last digit to be printed" x := 0.5 * fuzz + x. x >= fBase ifTrue: ["check if rounding has unnormalized x" x := x / fBase. exp := exp + 1]. (exp < 6 and: [exp > -4]) ifTrue: ["decimal notation" q := 0. exp < 0 ifTrue: [1 to: 1 - exp do: [:i | aStream nextPut: ('0.0000' at: i)]]] ifFalse: ["scientific notation" q := exp. exp := 0]. [x >= fuzz] whileTrue: ["use fuzz to track significance" xi := x asInteger. aStream nextPut: (Character digitValue: xi). x := x - xi asFloat * fBase. fuzz := fuzz * fBase. exp := exp - 1. exp = -1 ifTrue: [aStream nextPut: $.]]. [exp >= -1] whileTrue: [aStream nextPut: $0. exp := exp - 1. exp = -1 ifTrue: [aStream nextPut: $.]]. q ~= 0 ifTrue: [aStream nextPut: $e. q printOn: aStream]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Float class instanceVariableNames: ''! !Float class methodsFor: 'class initialization' stamp: 'nice 3/15/2008 22:42'! initialize "Float initialize" "Constants from Computer Approximations, pp. 182-183: Pi = 3.14159265358979323846264338327950288 Pi/2 = 1.57079632679489661923132169163975144 Pi*2 = 6.28318530717958647692528676655900576 Pi/180 = 0.01745329251994329576923690768488612 2.0 ln = 0.69314718055994530941723212145817657 2.0 sqrt = 1.41421356237309504880168872420969808" Pi := 3.14159265358979323846264338327950288. Halfpi := Pi / 2.0. Twopi := Pi * 2.0. ThreePi := Pi * 3.0. RadiansPerDegree := Pi / 180.0. Ln2 := 0.69314718055994530941723212145817657. Ln10 := 10.0 ln. Sqrt2 := 1.41421356237309504880168872420969808. E := 2.718281828459045235360287471353. Epsilon := 0.000000000001. "Defines precision of mathematical functions" MaxVal := 1.7976931348623157e308. MaxValLn := 709.782712893384. MinValLogBase2 := -1074. Infinity := MaxVal * MaxVal. NegativeInfinity := 0.0 - Infinity. NaN := Infinity - Infinity. NegativeZero := 1.0 / Infinity negated. ! ! !Float class methodsFor: 'constants' stamp: 'nice 6/11/2009 12:29'! denormalized "Answer whether implementation supports denormalized numbers (also known as gradual underflow)." ^true! ! !Float class methodsFor: 'constants'! e "Answer the constant, E." ^E! ! !Float class methodsFor: 'constants' stamp: 'nice 6/8/2009 15:42'! emax "Answer exponent of maximal representable value" ^1023! ! !Float class methodsFor: 'constants' stamp: 'nice 6/8/2009 15:43'! emin "Answer exponent of minimal normalized representable value" ^-1022! ! !Float class methodsFor: 'constants' stamp: 'nice 6/11/2009 12:30'! epsilon "Answer difference between 1.0 and previous representable value" ^1.0 timesTwoPower: 1 - self precision! ! !Float class methodsFor: 'constants' stamp: 'nice 6/8/2009 15:20'! fmax "Answer the maximum finite floating point value representable." ^MaxVal! ! !Float class methodsFor: 'constants' stamp: 'nice 6/8/2009 15:33'! fmin "Answer minimum positive representable value." ^self denormalized ifTrue: [self fminDenormalized] ifFalse: [self fminNormalized]! ! !Float class methodsFor: 'constants' stamp: 'nice 6/8/2009 15:22'! fminDenormalized "Answer the minimum denormalized value representable." ^1.0 timesTwoPower: MinValLogBase2! ! !Float class methodsFor: 'constants' stamp: 'nice 6/8/2009 15:22'! fminNormalized "Answer the minimum normalized value representable." ^1.0 timesTwoPower: -1022! ! !Float class methodsFor: 'constants' stamp: 'sw 10/8/1999 22:59'! halfPi ^ Halfpi! ! !Float class methodsFor: 'constants' stamp: 'tao 4/23/98 11:37'! infinity "Answer the value used to represent an infinite magnitude" ^ Infinity! ! !Float class methodsFor: 'constants' stamp: 'tao 4/23/98 11:38'! nan "Answer the canonical value used to represent Not-A-Number" ^ NaN! ! !Float class methodsFor: 'constants' stamp: 'tao 4/23/98 12:05'! negativeZero ^ NegativeZero! ! !Float class methodsFor: 'constants' stamp: 'GabrielOmarCotelli 5/25/2009 15:42'! one ^1.0! ! !Float class methodsFor: 'constants'! pi "Answer the constant, Pi." ^Pi! ! !Float class methodsFor: 'constants' stamp: 'nice 6/11/2009 12:40'! precision "Answer the apparent precision of the floating point representation. That is the maximum number of radix-based digits (bits if radix=2) representable in floating point without round off error. Technically, 52 bits are stored in the representation, and normalized numbers have an implied leading 1 that does not need to be stored. Note that denormalized floating point numbers don't have the implied leading 1, and thus gradually loose precision. This format conforms IEEE 754 double precision standard." ^53! ! !Float class methodsFor: 'constants' stamp: 'nice 6/8/2009 15:16'! radix "Answer the radix used for internal floating point representation." ^2! ! !Float class methodsFor: 'constants' stamp: 'yo 6/17/2004 17:44'! threePi ^ ThreePi ! ! !Float class methodsFor: 'constants' stamp: 'yo 6/17/2004 17:41'! twoPi ^ Twopi ! ! !Float class methodsFor: 'instance creation' stamp: 'nice 5/30/2006 03:13'! fromIEEE32Bit: word "Convert the given 32 bit word (which is supposed to be a positive 32bit value) from a 32bit IEEE floating point representation into an actual Squeak float object (being 64bit wide). Should only be used for conversion in FloatArrays or likewise objects." | sign mantissa exponent newFloat delta | word negative ifTrue: [^ self error:'Cannot deal with negative numbers']. word = 0 ifTrue: [^ 0.0]. sign := word bitAnd: 16r80000000. word = sign ifTrue: [^self negativeZero]. exponent := ((word bitShift: -23) bitAnd: 16rFF) - 127. mantissa := word bitAnd: 16r7FFFFF. exponent = 128 ifTrue:["Either NAN or INF" mantissa = 0 ifFalse:[^ Float nan]. sign = 0 ifTrue:[^ Float infinity] ifFalse:[^ Float infinity negated]]. exponent = -127 ifTrue: [ "gradual underflow (denormalized number) Remove first bit of mantissa and adjust exponent" delta := mantissa highBit. mantissa := (mantissa bitShift: 1) bitAnd: (1 bitShift: delta) - 1. exponent := exponent + delta - 23]. "Create new float" newFloat := self new: 2. newFloat basicAt: 1 put: ((sign bitOr: (1023 + exponent bitShift: 20)) bitOr: (mantissa bitShift: -3)). newFloat basicAt: 2 put: ((mantissa bitAnd: 7) bitShift: 29). ^newFloat! ! !Float class methodsFor: 'instance creation'! readFrom: aStream "Answer a new Float as described on the stream, aStream." ^(super readFrom: aStream) asFloat! ! !Float class methodsFor: 'instance creation' stamp: 'nice 3/15/2008 00:54'! readFrom: aStream ifFail: aBlock "Answer a new Float as described on the stream, aStream." ^(super readFrom: aStream ifFail: [^aBlock value]) asFloat! ! ArrayedCollection variableWordSubclass: #FloatArray instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Collections-Arrayed'! !FloatArray commentStamp: '' prior: 0! FloatArrays store 32bit IEEE floating point numbers.! !FloatArray methodsFor: '*tools-inspector' stamp: 'ar 9/27/2005 18:33'! inspectorClass "Answer the class of the inspector to be used on the receiver. Called by inspect; use basicInspect to get a normal (less useful) type of inspector." ^OrderedCollectionInspector! ! !FloatArray methodsFor: 'accessing' stamp: 'ar 2/2/2001 15:47'! at: index ^Float fromIEEE32Bit: (self basicAt: index)! ! !FloatArray methodsFor: 'accessing' stamp: 'ar 2/2/2001 15:47'! at: index put: value value isFloat ifTrue:[self basicAt: index put: value asIEEE32BitWord] ifFalse:[self at: index put: value asFloat]. ^value! ! !FloatArray methodsFor: 'accessing' stamp: 'ar 11/2/1998 12:19'! defaultElement "Return the default element of the receiver" ^0.0! ! !FloatArray methodsFor: 'accessing' stamp: 'laza 3/24/2000 13:08'! length "Return the length of the receiver" ^self squaredLength sqrt! ! !FloatArray methodsFor: 'accessing' stamp: 'laza 3/24/2000 13:08'! squaredLength "Return the squared length of the receiver" ^self dot: self! ! !FloatArray methodsFor: 'arithmetic' stamp: 'nice 11/24/2007 00:10'! adaptToNumber: rcvr andSend: selector "If I am involved in arithmetic with a Number. If possible, convert it to a float and perform the (more efficient) primitive operation." selector == #+ ifTrue:[^self + rcvr]. selector == #* ifTrue:[^self * rcvr]. selector == #- ifTrue:[^self negated += rcvr]. selector == #/ ifTrue:[ "DO NOT USE TRIVIAL CODE ^self reciprocal * rcvr BECAUSE OF GRADUAL UNDERFLOW self should: (1.0e-39 / (FloatArray with: 1.0e-39)) first < 2." ^(self class new: self size withAll: rcvr) / self ]. ^super adaptToNumber: rcvr andSend: selector! ! !FloatArray methodsFor: 'arithmetic' stamp: 'laza 3/24/2000 13:07'! dot: aFloatVector "Primitive. Return the dot product of the receiver and the argument. Fail if the argument is not of the same size as the receiver." | result | "" self size = aFloatVector size ifFalse:[^self error:'Must be equal size']. result := 0.0. 1 to: self size do:[:i| result := result + ((self at: i) * (aFloatVector at: i)). ]. ^result! ! !FloatArray methodsFor: 'arithmetic' stamp: 'ar 9/7/2001 23:04'! negated ^self clone *= -1! ! !FloatArray methodsFor: 'arithmetic' stamp: 'ar 9/14/1998 22:33'! * anObject ^self clone *= anObject! ! !FloatArray methodsFor: 'arithmetic' stamp: 'ar 9/14/1998 22:49'! *= anObject ^anObject isNumber ifTrue:[self primMulScalar: anObject asFloat] ifFalse:[self primMulArray: anObject]! ! !FloatArray methodsFor: 'arithmetic' stamp: 'ar 9/14/1998 22:33'! + anObject ^self clone += anObject! ! !FloatArray methodsFor: 'arithmetic' stamp: 'ar 9/14/1998 22:48'! += anObject ^anObject isNumber ifTrue:[self primAddScalar: anObject asFloat] ifFalse:[self primAddArray: anObject]! ! !FloatArray methodsFor: 'arithmetic' stamp: 'ar 9/14/1998 22:33'! - anObject ^self clone -= anObject! ! !FloatArray methodsFor: 'arithmetic' stamp: 'ar 9/14/1998 22:49'! -= anObject ^anObject isNumber ifTrue:[self primSubScalar: anObject asFloat] ifFalse:[self primSubArray: anObject]! ! !FloatArray methodsFor: 'arithmetic' stamp: 'ar 9/14/1998 22:34'! / anObject ^self clone /= anObject! ! !FloatArray methodsFor: 'arithmetic' stamp: 'ar 10/7/1998 19:58'! /= anObject ^anObject isNumber ifTrue:[self primDivScalar: anObject asFloat] ifFalse:[self primDivArray: anObject]! ! !FloatArray methodsFor: 'arithmetic' stamp: 'yo 9/14/2004 17:12'! \\= other other isNumber ifTrue: [ 1 to: self size do: [:i | self at: i put: (self at: i) \\ other ]. ^ self. ]. 1 to: (self size min: other size) do: [:i | self at: i put: (self at: i) \\ (other at: i). ]. ! ! !FloatArray methodsFor: 'comparing' stamp: 'ar 5/3/2001 13:02'! hash | result | result := 0. 1 to: self size do:[:i| result := result + (self basicAt: i) ]. ^result bitAnd: 16r1FFFFFFF! ! !FloatArray methodsFor: 'comparing' stamp: 'ar 2/2/2001 15:47'! = aFloatArray | length | aFloatArray class = self class ifFalse: [^ false]. length := self size. length = aFloatArray size ifFalse: [^ false]. 1 to: self size do: [:i | (self at: i) = (aFloatArray at: i) ifFalse: [^ false]]. ^ true! ! !FloatArray methodsFor: 'converting' stamp: 'ar 9/14/1998 23:46'! asFloatArray ^self! ! !FloatArray methodsFor: 'primitives-plugin' stamp: 'ar 2/2/2001 15:47'! primAddArray: floatArray 1 to: self size do:[:i| self at: i put: (self at: i) + (floatArray at: i)].! ! !FloatArray methodsFor: 'primitives-plugin' stamp: 'ar 2/2/2001 15:47'! primAddScalar: scalarValue 1 to: self size do:[:i| self at: i put: (self at: i) + scalarValue].! ! !FloatArray methodsFor: 'primitives-plugin' stamp: 'ar 2/2/2001 15:47'! primDivArray: floatArray 1 to: self size do:[:i| self at: i put: (self at: i) / (floatArray at: i)].! ! !FloatArray methodsFor: 'primitives-plugin' stamp: 'ar 2/2/2001 15:47'! primDivScalar: scalarValue 1 to: self size do:[:i| self at: i put: (self at: i) / scalarValue].! ! !FloatArray methodsFor: 'primitives-plugin' stamp: 'ar 2/2/2001 15:47'! primMulArray: floatArray 1 to: self size do:[:i| self at: i put: (self at: i) * (floatArray at: i)].! ! !FloatArray methodsFor: 'primitives-plugin' stamp: 'ar 2/2/2001 15:47'! primMulScalar: scalarValue 1 to: self size do:[:i| self at: i put: (self at: i) * scalarValue].! ! !FloatArray methodsFor: 'primitives-plugin' stamp: 'ar 2/2/2001 15:47'! primSubArray: floatArray 1 to: self size do:[:i| self at: i put: (self at: i) - (floatArray at: i)].! ! !FloatArray methodsFor: 'primitives-plugin' stamp: 'ar 2/2/2001 15:47'! primSubScalar: scalarValue 1 to: self size do:[:i| self at: i put: (self at: i) - scalarValue].! ! !FloatArray methodsFor: 'primitives-plugin' stamp: 'jcg 6/12/2003 17:54'! sum ^ super sum! ! !FloatArray methodsFor: 'private' stamp: 'ar 10/9/1998 11:27'! replaceFrom: start to: stop with: replacement startingAt: repStart "Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive." super replaceFrom: start to: stop with: replacement startingAt: repStart! ! CollectionRootTest subclass: #FloatArrayTest uses: TCreationWithTest + TSequencedStructuralEqualityTest + TSequencedConcatenationTest + TSetArithmetic + TAsStringCommaAndDelimiterSequenceableTest + TPrintOnSequencedTest + TEmptyTest + TBeginsEndsWith + TCloneTest + TConvertTest - {#testAsByteArray. #integerCollectionWithoutEqualElements} + TConvertAsSortedTest + TConvertAsSetForMultiplinessIdentityTest - {#testAsIdentitySetWithEqualsElements. #testAsIdentitySetWithIdentityEqualsElements} + TCopyPartOfSequenceable + TCopyPartOfSequenceableForMultipliness + TCopySequenceableSameContents + TCopySequenceableWithOrWithoutSpecificElements + TCopySequenceableWithReplacement + TCopyTest + TIncludesWithIdentityCheckTest - {#testIdentityIncludesNonSpecificComportement} + TIndexAccess - {#testIdentityIndexOf. #testIdentityIndexOfIAbsent} + TIndexAccessForMultipliness - {#testIdentityIndexOfIAbsentDuplicate. #testIdentityIndexOfDuplicate} + TIterateSequencedReadableTest + TPutTest + TPutBasicTest + TReplacementSequencedTest + TSequencedElementAccessTest + TSortTest + TSubCollectionAccess instanceVariableNames: 'nonEmpty5ElementsNoDuplicate empty elementNotIn elementTwiceIn collectionWithEqualElements nonEmpty1Element collectionWithSameAtEndAndBegining collectionWith1TimeSubcollection collectionWith2TimeSubcollection collectionNotIncluded nonEmptySubcollection elementInNonEmpty replacementCollectionSameSize sortedCollection' classVariableNames: '' poolDictionaries: '' category: 'CollectionsTests-Arrayed'! !FloatArrayTest commentStamp: 'nice 5/30/2006 01:24' prior: 0! These tests are used to assert that FloatArrayPlugin has same results as Float asIEEE32BitWord! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:22'! aValue " return a value to put into nonEmpty" ^ elementNotIn ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:23'! anIndex " return an index in nonEmpty bounds" ^ 2! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:50'! anotherElementNotIn " return an element different of 'elementNotIn' not included in 'nonEmpty' " ^ elementNotIn ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 14:55'! anotherElementOrAssociationIn " return an element (or an association for Dictionary ) present in 'collection' " ^ self collection anyOne! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 14:56'! anotherElementOrAssociationNotIn " return an element (or an association for Dictionary )not present in 'collection' " ^ elementNotIn ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:24'! anotherValue " return a value ( not eual to 'aValue' ) to put into nonEmpty " ^ elementInNonEmpty ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 14:56'! collection ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 11:45'! collectionClass ^ FloatArray! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:55'! collectionMoreThan1NoDuplicates " return a collection of size > 1 without equal elements" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 12:05'! collectionMoreThan5Elements " return a collection including at least 5 elements" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:41'! collectionNotIncluded " return a collection for wich each element is not included in 'nonEmpty' " ^ collectionNotIncluded ifNil: [ collectionNotIncluded := (FloatArray new: 2) at:1 put: elementNotIn ; at: 2 put: elementNotIn ; yourself ].! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:39'! collectionWith1TimeSubcollection " return a collection including 'oldSubCollection' only one time " ^ collectionWith1TimeSubcollection ifNil: [ collectionWith1TimeSubcollection := collectionWithSameAtEndAndBegining , self oldSubCollection , collectionWithSameAtEndAndBegining ].! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:35'! collectionWith2TimeSubcollection " return a collection including 'oldSubCollection' two or many time " ^ collectionWith2TimeSubcollection ifNil: [ collectionWith2TimeSubcollection := self collectionWith1TimeSubcollection, self oldSubCollection ].! ! !FloatArrayTest methodsFor: 'requirements'! collectionWithCopy "return a collection of type 'self collectionWIithoutEqualsElements class' containing no elements equals ( with identity equality) but 2 elements only equals with classic equality" | result collection | collection := OrderedCollection withAll: self elementsCopyNonIdenticalWithoutEqualElements. collection add: collection first copy. result := self elementsCopyNonIdenticalWithoutEqualElements class withAll: collection. ^ result! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:50'! collectionWithCopyNonIdentical " return a collection that include elements for which 'copy' return a different object (this is not the case of SmallInteger)" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:44'! collectionWithElementsToRemove " return a collection of elements included in 'nonEmpty' " ^ nonEmptySubcollection ifNil: [ nonEmptySubcollection := (FloatArray new:2 ) at:1 put: self nonEmpty first ; at:2 put: self nonEmpty last ; yourself ]! ! !FloatArrayTest methodsFor: 'requirements'! collectionWithIdentical "return a collection of type : 'self collectionWIithoutEqualsElements class containing two elements equals ( with identity equality)" | result collection element | collection := OrderedCollection withAll: self elementsCopyNonIdenticalWithoutEqualElements. element := collection first. collection add: element. result := self elementsCopyNonIdenticalWithoutEqualElements class withAll: collection. ^ result! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:07'! collectionWithNonIdentitySameAtEndAndBegining " return a collection with elements at end and begining equals only with classic equality (they are not the same object). (others elements of the collection are not equal to those elements)" ^ collectionWithSameAtEndAndBegining ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:28'! collectionWithSameAtEndAndBegining " return a collection with elements at end and begining equals . (others elements of the collection are not equal to those elements)" ^ collectionWithSameAtEndAndBegining ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:02'! collectionWithSortableElements " return a collection elements that can be sorte ( understanding message ' < ' or ' > ')" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:01'! collectionWithoutEqualElements " return a collection without equal elements" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:25'! collectionWithoutEqualsElements " return a collection not including equal elements " ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 10:44'! collectionWithoutNilElements " return a collection that doesn't includes a nil element and that doesn't includes equal elements'" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:35'! elementInForElementAccessing " return an element inculded in 'moreThan4Elements'" ^ elementInNonEmpty ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:02'! elementInForIndexAccessing " return an element included in 'collectionMoreThan1NoDuplicates' " ^ elementInNonEmpty .! ! !FloatArrayTest methodsFor: 'requirements'! elementInForReplacement " return an element included in 'nonEmpty' " ^ self nonEmpty anyOne.! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:50'! elementNotIn "return an element not included in 'nonEmpty' " ^ elementNotIn ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:35'! elementNotInForElementAccessing " return an element not included in 'moreThan4Elements' " ^ elementNotIn ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:55'! elementNotInForIndexAccessing " return an element not included in 'collectionMoreThan1NoDuplicates' " ^ elementNotIn ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:45'! elementToAdd " return an element of type 'nonEmpy' elements'type' not yet included in nonEmpty" ^ elementNotIn ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:04'! elementsCopyNonIdenticalWithoutEqualElements " return a collection that does niot incllude equal elements ( classic equality ) all elements included are elements for which copy is not identical to the element " ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 10:45'! empty ^ empty ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 14:55'! firstCollection " return a collection that will be the first part of the concatenation" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:26'! firstIndex " return an index between 'nonEmpty' bounds that is < to 'second index' " ^2! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:23'! indexArray " return a Collection including indexes between bounds of 'nonEmpty' " ^ { 1. 4. 3.}! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:26'! indexInForCollectionWithoutDuplicates " return an index between 'collectionWithoutEqualsElements' bounds" ^ 2.! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:30'! indexInNonEmpty " return an index between bounds of 'nonEmpty' " ^ 3.! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:44'! moreThan3Elements " return a collection including atLeast 3 elements" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:36'! moreThan4Elements " return a collection including at leat 4 elements" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:26'! newElement "return an element that will be put in the collection in place of another" ^ elementNotIn ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 10:45'! nonEmpty ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 14:57'! nonEmpty1Element " return a collection of size 1 including one element" ^ nonEmpty1Element ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:11'! nonEmptyMoreThan1Element " return a collection that doesn't includes equal elements' and doesn't include nil elements'" ^nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:36'! oldSubCollection " return a subCollection included in collectionWith1TimeSubcollection . ex : subCollection := #( 2 3 4) and collectionWith1TimeSubcollection := #(1 2 3 4 5)" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:37'! replacementCollection " return a collection that will be used to replace 'oldSubcollection' in ' collectionWith1TimeSubcollection' " ^ collectionWithSameAtEndAndBegining ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:34'! replacementCollectionSameSize " return a collection of size (secondIndex - firstIndex + 1)" ^replacementCollectionSameSize ifNil: [ replacementCollectionSameSize := FloatArray new: (self secondIndex - self firstIndex + 1). 1 to: replacementCollectionSameSize size do: [ :i | replacementCollectionSameSize at:i put: elementInNonEmpty ]. replacementCollectionSameSize. ].! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 14:55'! secondCollection " return a collection that will be the second part of the concatenation" ^ collectionWithEqualElements ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:27'! secondIndex " return an index between 'nonEmpty' bounds that is > to 'first index' " ^self firstIndex +1! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 10:55'! sizeCollection "Answers a collection not empty" ^ nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:41'! sortedInAscendingOrderCollection " return a collection sorted in an acsending order" ^ sortedCollection ifNil: [ sortedCollection := ( FloatArray new: 3)at: 1 put: 1.0 ; at: 2 put: 2.0 ; at: 3 put: 3.0 ; yourself ] ! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:36'! subCollectionNotIn " return a collection for which at least one element is not included in 'moreThan4Elements' " ^ collectionNotIncluded ifNil: [ collectionNotIncluded := (FloatArray new: 2) at:1 put: elementNotIn ; at: 2 put: elementNotIn ; yourself ].! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 16:37'! unsortedCollection " retur a collection that is not yat sorted" ^nonEmpty5ElementsNoDuplicate ! ! !FloatArrayTest methodsFor: 'requirements'! valueArray " return a collection (with the same size than 'indexArray' )of values to be put in 'nonEmpty' at indexes in 'indexArray' " | result | result := Array new: self indexArray size. 1 to: result size do: [:i | result at:i put: (self aValue ). ]. ^ result.! ! !FloatArrayTest methodsFor: 'requirements' stamp: 'delaunay 5/14/2009 15:04'! withEqualElements ^ collectionWithEqualElements ! ! !FloatArrayTest methodsFor: 'running' stamp: 'delaunay 5/14/2009 16:40'! setUp empty := FloatArray new. elementInNonEmpty := 7.0. nonEmpty5ElementsNoDuplicate := (FloatArray new:5) at: 1 put: 1.5 ; at: 2 put: 2.5 ; at: 3 put: elementInNonEmpty ; at: 4 put: 4.5 ; at: 5 put: 5.5 ; yourself. elementNotIn := 999.0. elementTwiceIn := 2.3 . collectionWithEqualElements := (FloatArray new: 3) at: 1 put: 2.0 ; at: 2 put: 2.0 ; at: 3 put: 3.5 ; yourself. nonEmpty1Element := ( FloatArray new: 1) at:1 put: 1.2 ; yourself. collectionWithSameAtEndAndBegining := (FloatArray new: 3) at: 1 put: 2.0 ; at: 2 put: 1.0 ; at: 3 put: 2.0 copy ; yourself.! ! !FloatArrayTest methodsFor: 'test - creation'! testOfSize "self debug: #testOfSize" | aCol | aCol := self collectionClass ofSize: 3. self assert: (aCol size = 3). ! ! !FloatArrayTest methodsFor: 'test - creation'! testWith "self debug: #testWith" | aCol element | element := self collectionMoreThan5Elements anyOne. aCol := self collectionClass with: element. self assert: (aCol includes: element).! ! !FloatArrayTest methodsFor: 'test - creation'! testWithAll "self debug: #testWithAll" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection . aCol := self collectionClass withAll: collection . collection do: [ :each | self assert: (aCol occurrencesOf: each ) = ( collection occurrencesOf: each ) ]. self assert: (aCol size = collection size ).! ! !FloatArrayTest methodsFor: 'test - creation'! testWithWith "self debug: #testWithWith" | aCol collection element1 element2 | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 2 . element1 := collection at: 1. element2 := collection at:2. aCol := self collectionClass with: element1 with: element2 . self assert: (aCol occurrencesOf: element1 ) == ( collection occurrencesOf: element1). self assert: (aCol occurrencesOf: element2 ) == ( collection occurrencesOf: element2). ! ! !FloatArrayTest methodsFor: 'test - creation'! testWithWithWith "self debug: #testWithWithWith" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom:1 to: 3 . aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3). 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ].! ! !FloatArrayTest methodsFor: 'test - creation'! testWithWithWithWith "self debug: #testWithWithWithWith" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 4. aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3) with: ( collection at: 4). 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ].! ! !FloatArrayTest methodsFor: 'test - creation'! testWithWithWithWithWith "self debug: #testWithWithWithWithWith" | aCol collection | collection := self collectionMoreThan5Elements asOrderedCollection copyFrom: 1 to: 5 . aCol := self collectionClass with: (collection at:1) with: ( collection at:2 ) with: ( collection at: 3) with: (collection at: 4 ) with: ( collection at: 5 ). 1 to: 3 do: [ :i | self assert: ( aCol occurrencesOf: ( collection at: i ) ) = ( collection occurrencesOf: ( collection at: i ) ) ].! ! !FloatArrayTest methodsFor: 'test - equality'! testEqualSign "self debug: #testEqualSign" self deny: (self empty = self nonEmpty).! ! !FloatArrayTest methodsFor: 'test - equality'! testEqualSignIsTrueForNonIdenticalButEqualCollections "self debug: #testEqualSignIsTrueForNonIdenticalButEqualCollections" self assert: (self empty = self empty copy). self assert: (self empty copy = self empty). self assert: (self empty copy = self empty copy). self assert: (self nonEmpty = self nonEmpty copy). self assert: (self nonEmpty copy = self nonEmpty). self assert: (self nonEmpty copy = self nonEmpty copy).! ! !FloatArrayTest methodsFor: 'test - equality'! testEqualSignOfIdenticalCollectionObjects "self debug: #testEqualSignOfIdenticalCollectionObjects" self assert: (self empty = self empty). self assert: (self nonEmpty = self nonEmpty). ! ! !FloatArrayTest methodsFor: 'testing' stamp: 'nice 11/23/2007 23:53'! testArithmeticCoercion "This test is related to http://bugs.squeak.org/view.php?id=6782" self should: [3.0 / (FloatArray with: 2.0) = (FloatArray with: 1.5)]. self should: [3.0 * (FloatArray with: 2.0) = (FloatArray with: 6.0)]. self should: [3.0 + (FloatArray with: 2.0) = (FloatArray with: 5.0)]. self should: [3.0 - (FloatArray with: 2.0) = (FloatArray with: 1.0)].! ! !FloatArrayTest methodsFor: 'testing' stamp: 'nice 5/30/2006 03:17'! testFloatArrayPluginPrimitiveAt "if FloatArrayPlugin primitive are not here, this test is dumb. Otherwise, it will compare primitive and #fromIEEE32Bit:" #( "regular numbers no truncation or rounding" 2r0.0 2r1.0 2r1.1 2r1.00000000000000000000001 2r1.0e-10 2r1.1e-10 2r1.00000000000000000000001e-10 2r1.0e10 2r1.1e10 2r1.00000000000000000000001e10 "smallest float32 before gradual underflow" 2r1.0e-126 "biggest float32" 2r1.11111111111111111111111e127 "overflow" 2r1.11111111111111111111111e128 "gradual underflow" 2r0.11111111111111111111111e-126 2r0.00000000000000000000001e-126 "with rounding mode : tests on 25 bits" 2r1.0000000000000000000000001 2r1.0000000000000000000000010 2r1.0000000000000000000000011 2r1.0000000000000000000000100 2r1.0000000000000000000000101 2r1.0000000000000000000000110 2r1.0000000000000000000000111 2r1.1111111111111111111111001 2r1.1111111111111111111111010 2r1.1111111111111111111111011 2r1.1111111111111111111111101 2r1.1111111111111111111111110 2r1.1111111111111111111111111 "overflow" 2r1.1111111111111111111111110e127 "gradual underflow" 2r0.1111111111111111111111111e-126 2r0.1111111111111111111111110e-126 2r0.1111111111111111111111101e-126 2r0.1111111111111111111111011e-126 2r0.1111111111111111111111010e-126 2r0.1111111111111111111111001e-126 2r0.0000000000000000000000111e-126 2r0.0000000000000000000000110e-126 2r0.0000000000000000000000101e-126 2r0.0000000000000000000000011e-126 2r0.0000000000000000000000010e-126 2r0.0000000000000000000000001e-126 2r0.0000000000000000000000010000000000000000000000000001e-126 ) do: [:e | self assert: ((FloatArray with: e) at: 1) = (Float fromIEEE32Bit: ((FloatArray with: e) basicAt: 1)). self assert: ((FloatArray with: e negated) at: 1) = (Float fromIEEE32Bit: ((FloatArray with: e negated) basicAt: 1))]. "special cases" (Array with: Float infinity with: Float infinity negated with: Float negativeZero) do: [:e | self assert: ((FloatArray with: e) at: 1) = (Float fromIEEE32Bit: ((FloatArray with: e) basicAt: 1))]. "Cannot compare NaN" (Array with: Float nan) do: [:e | self assert: (Float fromIEEE32Bit: ((FloatArray with: e) basicAt: 1)) isNaN].! ! !FloatArrayTest methodsFor: 'testing' stamp: 'nice 5/30/2006 03:17'! testFloatArrayPluginPrimitiveAtPut "if FloatArrayPlugin primitive are not here, this test is dumb. Otherwise, it will compare primitive and #asIEEE32BitWord" #( "regular numbers no truncation or rounding" 2r0.0 2r1.0 2r1.1 2r1.00000000000000000000001 2r1.0e-10 2r1.1e-10 2r1.00000000000000000000001e-10 2r1.0e10 2r1.1e10 2r1.00000000000000000000001e10 "smallest float32 before gradual underflow" 2r1.0e-126 "biggest float32" 2r1.11111111111111111111111e127 "overflow" 2r1.11111111111111111111111e128 "gradual underflow" 2r0.11111111111111111111111e-126 2r0.00000000000000000000001e-126 "with rounding mode : tests on 25 bits" 2r1.0000000000000000000000001 2r1.0000000000000000000000010 2r1.0000000000000000000000011 2r1.0000000000000000000000100 2r1.0000000000000000000000101 2r1.0000000000000000000000110 2r1.0000000000000000000000111 2r1.1111111111111111111111001 2r1.1111111111111111111111010 2r1.1111111111111111111111011 2r1.1111111111111111111111101 2r1.1111111111111111111111110 2r1.1111111111111111111111111 "overflow" 2r1.1111111111111111111111110e127 "gradual underflow" 2r0.1111111111111111111111111e-126 2r0.1111111111111111111111110e-126 2r0.1111111111111111111111101e-126 2r0.1111111111111111111111011e-126 2r0.1111111111111111111111010e-126 2r0.1111111111111111111111001e-126 2r0.0000000000000000000000111e-126 2r0.0000000000000000000000110e-126 2r0.0000000000000000000000101e-126 2r0.0000000000000000000000011e-126 2r0.0000000000000000000000010e-126 2r0.0000000000000000000000001e-126 2r0.0000000000000000000000010000000000000000000000000001e-126 ) do: [:e | self assert: ((FloatArray with: e) basicAt: 1) = e asIEEE32BitWord. self assert: ((FloatArray with: e negated) basicAt: 1) = e negated asIEEE32BitWord]. "special cases" (Array with: Float infinity with: Float infinity negated with: Float negativeZero with: Float nan) do: [:e | self assert: ((FloatArray with: e) basicAt: 1) = e asIEEE32BitWord]. ! ! !FloatArrayTest methodsFor: 'tests - as identity set'! testAsIdentitySetWithoutIdentityEqualsElements | result collection | collection := self collectionWithCopy. result := collection asIdentitySet. " no elements should have been removed as no elements are equels with Identity equality" self assert: result size = collection size. collection do: [ :each | (collection occurrencesOf: each) = (result asOrderedCollection occurrencesOf: each) ]. self assert: result class = IdentitySet! ! !FloatArrayTest methodsFor: 'tests - as set tests'! testAsSetWithEqualsElements | result | result := self withEqualElements asSet. self withEqualElements do: [ :each | self assert: (result occurrencesOf: each) = 1 ]. self assert: result class = Set! ! !FloatArrayTest methodsFor: 'tests - as sorted collection'! testAsSortedArray | result collection | collection := self collectionWithSortableElements . result := collection asSortedArray. self assert: (result class includesBehavior: Array). self assert: result isSorted. self assert: result size = collection size! ! !FloatArrayTest methodsFor: 'tests - as sorted collection'! testAsSortedCollection | aCollection result | aCollection := self collectionWithSortableElements . result := aCollection asSortedCollection. self assert: (result class includesBehavior: SortedCollection). result do: [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. self assert: result size = aCollection size.! ! !FloatArrayTest methodsFor: 'tests - as sorted collection'! testAsSortedCollectionWithSortBlock | result tmp | result := self collectionWithSortableElements asSortedCollection: [:a :b | a > b]. self assert: (result class includesBehavior: SortedCollection). result do: [ :each | self assert: (self collectionWithSortableElements occurrencesOf: each) = (result occurrencesOf: each) ]. self assert: result size = self collectionWithSortableElements size. tmp:=result at: 1. result do: [:each| self assert: tmp>=each. tmp:=each]. ! ! !FloatArrayTest methodsFor: 'tests - at put'! testAtPut "self debug: #testAtPut" self nonEmpty at: self anIndex put: self aValue. self assert: (self nonEmpty at: self anIndex) = self aValue. ! ! !FloatArrayTest methodsFor: 'tests - at put'! testAtPutOutOfBounds "self debug: #testAtPutOutOfBounds" self should: [self empty at: self anIndex put: self aValue] raise: Error ! ! !FloatArrayTest methodsFor: 'tests - at put'! testAtPutTwoValues "self debug: #testAtPutTwoValues" self nonEmpty at: self anIndex put: self aValue. self nonEmpty at: self anIndex put: self anotherValue. self assert: (self nonEmpty at: self anIndex) = self anotherValue.! ! !FloatArrayTest methodsFor: 'tests - begins ends with'! testsBeginsWith self assert: (self nonEmpty beginsWith:(self nonEmpty copyUpTo: self nonEmpty size)). self assert: (self nonEmpty beginsWith:(self nonEmpty )). self deny: (self nonEmpty beginsWith:(self nonEmpty copyWith:self nonEmpty first)).! ! !FloatArrayTest methodsFor: 'tests - begins ends with'! testsBeginsWithEmpty self deny: (self nonEmpty beginsWith:(self empty)). self deny: (self empty beginsWith:(self nonEmpty )). ! ! !FloatArrayTest methodsFor: 'tests - begins ends with'! testsEndsWith self assert: (self nonEmpty endsWith:(self nonEmpty copyWithoutFirst)). self assert: (self nonEmpty endsWith:(self nonEmpty )). self deny: (self nonEmpty endsWith:(self nonEmpty copyWith:self nonEmpty first)).! ! !FloatArrayTest methodsFor: 'tests - begins ends with'! testsEndsWithEmpty self deny: (self nonEmpty endsWith:(self empty )). self deny: (self empty endsWith:(self nonEmpty )). ! ! !FloatArrayTest methodsFor: 'tests - comma and delimiter'! testAsCommaStringEmpty self assert: self empty asCommaString = ''. self assert: self empty asCommaStringAnd = ''. ! ! !FloatArrayTest methodsFor: 'tests - comma and delimiter'! testAsCommaStringMore "self assert: self oneTwoThreeItemCol asCommaString = '1, 2, 3'. self assert: self oneTwoThreeItemCol asCommaStringAnd = '1, 2 and 3' " | result resultAnd index allElementsAsString | result:= self nonEmpty asCommaString . resultAnd:= self nonEmpty asCommaStringAnd . index := 1. (result findBetweenSubStrs: ',' )do: [:each | index = 1 ifTrue: [self assert: each= ((self nonEmpty at:index)asString)] ifFalse: [self assert: each= (' ',(self nonEmpty at:index) asString)]. index:=index+1 ]. "verifying esultAnd :" allElementsAsString:=(resultAnd findBetweenSubStrs: ',' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size ) ifTrue: [ i = 1 ifTrue:[self assert: (allElementsAsString at:i)=((self nonEmpty at:i) asString)] ifFalse:[self assert: (allElementsAsString at:i)=(' ',(self nonEmpty at:i) asString)] ]. i=(allElementsAsString size) ifTrue:[ i = 1 ifTrue:[self assert: (allElementsAsString at:i)=( (self nonEmpty at:i ) asString ,' and ', (self nonEmpty at: ( i + 1) ) asString )] ifFalse:[self assert: (allElementsAsString at:i)=( ' ' , (self nonEmpty at:i ) asString ,' and ', (self nonEmpty at: ( i + 1) ) asString )] ]. ].! ! !FloatArrayTest methodsFor: 'tests - comma and delimiter'! testAsCommaStringOne "self assert: self oneItemCol asCommaString = '1'. self assert: self oneItemCol asCommaStringAnd = '1'." self assert: self nonEmpty1Element asCommaString = (self nonEmpty1Element first asString). self assert: self nonEmpty1Element asCommaStringAnd = (self nonEmpty1Element first asString). ! ! !FloatArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterEmpty | delim emptyStream | delim := ', '. emptyStream := ReadWriteStream on: ''. self empty asStringOn: emptyStream delimiter: delim. self assert: emptyStream contents = ''. ! ! !FloatArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterLastEmpty | delim emptyStream | delim := ', '. emptyStream := ReadWriteStream on: ''. self empty asStringOn: emptyStream delimiter: delim last:'and'. self assert: emptyStream contents = ''. ! ! !FloatArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterLastMore | delim multiItemStream result last allElementsAsString | delim := ', '. last := 'and'. result:=''. multiItemStream := ReadWriteStream on:result. self nonEmpty asStringOn: multiItemStream delimiter: ', ' last: last. allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString)]. i=(allElementsAsString size-1) ifTrue:[ self deny: (allElementsAsString at:i)=(last)asString]. i=(allElementsAsString size) ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:(i-1))asString)]. ]. ! ! !FloatArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterLastOne | delim oneItemStream result | delim := ', '. result:=''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim last: 'and'. oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)]. ! ! !FloatArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterMore | delim multiItemStream result index | "delim := ', '. multiItemStream := '' readWrite. self oneTwoThreeItemCol asStringOn: multiItemStream delimiter: ', '. self assert: multiItemStream contents = '1, 2, 3'." delim := ', '. result:=''. multiItemStream := ReadWriteStream on:result. self nonEmpty asStringOn: multiItemStream delimiter: ', '. index:=1. (result findBetweenSubStrs: ', ' )do: [:each | self assert: each= ((self nonEmpty at:index)asString). index:=index+1 ].! ! !FloatArrayTest methodsFor: 'tests - comma and delimiter'! testAsStringOnDelimiterOne | delim oneItemStream result | "delim := ', '. oneItemStream := '' readWrite. self oneItemCol asStringOn: oneItemStream delimiter: delim. self assert: oneItemStream contents = '1'." delim := ', '. result:=''. oneItemStream := ReadWriteStream on: result. self nonEmpty1Element asStringOn: oneItemStream delimiter: delim. oneItemStream do:[:each | self assert: each = (self nonEmpty1Element first asString)]. ! ! !FloatArrayTest methodsFor: 'tests - concatenation'! testConcatenation | result index | result:= self firstCollection,self secondCollection . "first part : " index := 1. self firstCollection do: [:each | self assert: (self firstCollection at: index)=each. index := index+1.]. "second part : " 1 to: self secondCollection size do: [:i | self assert: (self secondCollection at:i)= (result at:index). index:=index+1]. "size : " self assert: result size = (self firstCollection size + self secondCollection size).! ! !FloatArrayTest methodsFor: 'tests - concatenation'! testConcatenationWithEmpty | result | result:= self empty,self secondCollection . 1 to: self secondCollection size do: [:i | self assert: (self secondCollection at:i)= (result at:i). ]. "size : " self assert: result size = ( self secondCollection size).! ! !FloatArrayTest methodsFor: 'tests - converting'! assertNoDuplicates: aCollection whenConvertedTo: aClass | result | result := self collectionWithEqualElements asIdentitySet. self assert: (result class includesBehavior: IdentitySet). self collectionWithEqualElements do: [ :initial | self assert: (result occurrencesOf: initial) = 1 ]! ! !FloatArrayTest methodsFor: 'tests - converting'! assertNonDuplicatedContents: aCollection whenConvertedTo: aClass | result | result := aCollection perform: ('as' , aClass name) asSymbol. self assert: (result class includesBehavior: aClass). result do: [ :each | self assert: (aCollection occurrencesOf: each) = (result occurrencesOf: each) ]. ^ result! ! !FloatArrayTest methodsFor: 'tests - converting'! assertSameContents: aCollection whenConvertedTo: aClass | result | result := self assertNonDuplicatedContents: aCollection whenConvertedTo: aClass. self assert: result size = aCollection size! ! !FloatArrayTest methodsFor: 'tests - converting'! testAsArray "self debug: #testAsArray3" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Array! ! !FloatArrayTest methodsFor: 'tests - converting'! testAsBag self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Bag! ! !FloatArrayTest methodsFor: 'tests - converting'! testAsIdentitySet "test with a collection without equal elements :" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: IdentitySet. ! ! !FloatArrayTest methodsFor: 'tests - converting'! testAsOrderedCollection self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: OrderedCollection! ! !FloatArrayTest methodsFor: 'tests - converting'! testAsSet | | "test with a collection without equal elements :" self assertSameContents: self collectionWithoutEqualElements whenConvertedTo: Set. ! ! !FloatArrayTest methodsFor: 'tests - copy'! testCopyEmptyWith "self debug: #testCopyWith" | res element | element := self elementToAdd. res := self empty copyWith: element. self assert: res size = (self empty size + 1). self assert: (res includes: (element value))! ! !FloatArrayTest methodsFor: 'tests - copy'! testCopyEmptyWithout "self debug: #testCopyEmptyWithout" | res | res := self empty copyWithout: self elementToAdd. self assert: res size = self empty size. self deny: (res includes: self elementToAdd)! ! !FloatArrayTest methodsFor: 'tests - copy'! testCopyEmptyWithoutAll "self debug: #testCopyEmptyWithoutAll" | res | res := self empty copyWithoutAll: self collectionWithElementsToRemove. self assert: res size = self empty size. self collectionWithElementsToRemove do: [ :each | self deny: (res includes: each) ]! ! !FloatArrayTest methodsFor: 'tests - copy'! testCopyNonEmptyWith "self debug: #testCopyNonEmptyWith" | res element | element := self elementToAdd . res := self nonEmpty copyWith: element. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self assert: (res includes: (element value)). self nonEmpty do: [ :each | res includes: each ]! ! !FloatArrayTest methodsFor: 'tests - copy'! testCopyNonEmptyWithout "self debug: #testCopyNonEmptyWithout" | res anElementOfTheCollection | anElementOfTheCollection := self nonEmpty anyOne. res := (self nonEmpty copyWithout: anElementOfTheCollection). "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self deny: (res includes: anElementOfTheCollection). self nonEmpty do: [:each | (each = anElementOfTheCollection) ifFalse: [self assert: (res includes: each)]]. ! ! !FloatArrayTest methodsFor: 'tests - copy'! testCopyNonEmptyWithoutAll "self debug: #testCopyNonEmptyWithoutAll" | res | res := self nonEmpty copyWithoutAll: self collectionWithElementsToRemove. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self collectionWithElementsToRemove do: [ :each | self deny: (res includes: (each)) ]. self nonEmpty do: [ :each | (self collectionWithElementsToRemove includes: each) ifFalse: [ self assert: (res includes: each) ] ]! ! !FloatArrayTest methodsFor: 'tests - copy'! testCopyNonEmptyWithoutAllNotIncluded "self debug: #testCopyNonEmptyWithoutAllNotIncluded" | res | res := self nonEmpty copyWithoutAll: self collectionNotIncluded. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self nonEmpty do: [ :each | self assert: (res includes: each) ]! ! !FloatArrayTest methodsFor: 'tests - copy'! testCopyNonEmptyWithoutNotIncluded "self debug: #testCopyNonEmptyWithoutNotIncluded" | res | res := self nonEmpty copyWithout: self elementToAdd. "here we do not test the size since for a non empty set we would get a problem. Then in addition copy is not about duplicate management. The element should be in at the end." self nonEmpty do: [ :each | self assert: (res includes: each) ]! ! !FloatArrayTest methodsFor: 'tests - copy - clone'! testCopyCreatesNewObject "self debug: #testCopyCreatesNewObject" | copy | copy := self nonEmpty copy. self deny: self nonEmpty == copy. ! ! !FloatArrayTest methodsFor: 'tests - copy - clone'! testCopyEmpty "self debug: #testCopyEmpty" | copy | copy := self empty copy. self assert: copy isEmpty.! ! !FloatArrayTest methodsFor: 'tests - copy - clone'! testCopyNonEmpty "self debug: #testCopyNonEmpty" | copy | copy := self nonEmpty copy. self deny: copy isEmpty. self assert: copy size = self nonEmpty size. self nonEmpty do: [:each | copy includes: each]! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyAfter | result index collection | collection := self collectionWithoutEqualsElements . index:= self indexInForCollectionWithoutDuplicates . result := collection copyAfter: (collection at:index ). "verifying content: " (1) to: result size do: [:i | self assert: (collection at:(i + index ))=(result at: (i))]. "verify size: " self assert: result size = (collection size - index).! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyAfterEmpty | result | result := self empty copyAfter: self collectionWithoutEqualsElements first. self assert: result isEmpty. ! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyAfterLast | result index collection | collection := self collectionWithoutEqualsElements . index:= self indexInForCollectionWithoutDuplicates . result := collection copyAfterLast: (collection at:index ). "verifying content: " (1) to: result size do: [:i | self assert: (collection at:(i + index ))=(result at: (i))]. "verify size: " self assert: result size = (collection size - index).! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyAfterLastEmpty | result | result := self empty copyAfterLast: self collectionWithoutEqualsElements first. self assert: result isEmpty.! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyEmptyMethod | result | result := self collectionWithoutEqualsElements copyEmpty . self assert: result isEmpty . self assert: result class= self nonEmpty class.! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyFromTo | result index collection | collection := self collectionWithoutEqualsElements . index :=self indexInForCollectionWithoutDuplicates . result := collection copyFrom: index to: collection size . "verify content of 'result' : " 1 to: result size do: [:i | self assert: (result at:i)=(collection at: (i + index - 1))]. "verify size of 'result' : " self assert: result size = (collection size - index + 1).! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyUpTo | result index collection | collection := self collectionWithoutEqualsElements . index:= self indexInForCollectionWithoutDuplicates . result := collection copyUpTo: (collection at:index). "verify content of 'result' :" 1 to: result size do: [:i| self assert: (collection at:i)=(result at:i)]. "verify size of 'result' :" self assert: result size = (index-1). ! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyUpToEmpty | result | result := self empty copyUpTo: self collectionWithoutEqualsElements first. self assert: result isEmpty. ! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyUpToLast | result index collection | collection := self collectionWithoutEqualsElements . index:= self indexInForCollectionWithoutDuplicates . result := collection copyUpToLast: (collection at:index). "verify content of 'result' :" 1 to: result size do: [:i| self assert: (collection at:i)=(result at:i)]. "verify size of 'result' :" self assert: result size = (index-1).! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable'! testCopyUpToLastEmpty | result | result := self empty copyUpToLast: self collectionWithoutEqualsElements first. self assert: result isEmpty.! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable for multipliness'! testCopyAfterLastWithDuplicate | result element collection | collection := self collectionWithSameAtEndAndBegining . element := collection first. " collectionWithSameAtEndAndBegining first and last elements are equals. 'copyAfter:' should copy after the last occurence of element :" result := collection copyAfterLast: (element ). "verifying content: " self assert: result isEmpty. ! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable for multipliness'! testCopyAfterWithDuplicate | result element collection | collection := self collectionWithSameAtEndAndBegining . element := collection last. " collectionWithSameAtEndAndBegining first and last elements are equals. 'copyAfter:' should copy after the first occurence :" result := collection copyAfter: (element ). "verifying content: " 1 to: result size do: [:i | self assert: (collection at:(i + 1 )) = (result at: (i)) ]. "verify size: " self assert: result size = (collection size - 1).! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable for multipliness'! testCopyUpToLastWithDuplicate | result element collection | collection := self collectionWithSameAtEndAndBegining . element := collection first. " collectionWithSameAtEndAndBegining first and last elements are equals. 'copyUpToLast:' should copy until the last occurence :" result := collection copyUpToLast: (element ). "verifying content: " 1 to: result size do: [:i | self assert: (result at: i ) = ( collection at: i ) ]. self assert: result size = (collection size - 1). ! ! !FloatArrayTest methodsFor: 'tests - copying part of sequenceable for multipliness'! testCopyUpToWithDuplicate | result element collection | collection := self collectionWithSameAtEndAndBegining . element := collection last. " collectionWithSameAtEndAndBegining first and last elements are equals. 'copyUpTo:' should copy until the first occurence :" result := collection copyUpTo: (element ). "verifying content: " self assert: result isEmpty. ! ! !FloatArrayTest methodsFor: 'tests - copying same contents'! testReverse | result | result := self nonEmpty reverse . "verify content of 'result: '" 1 to: result size do: [:i | self assert: ((result at:i)=(self nonEmpty at:(self nonEmpty size-i+1)))]. "verify size of 'result' :" self assert: result size=self nonEmpty size.! ! !FloatArrayTest methodsFor: 'tests - copying same contents'! testReversed | result | result := self nonEmpty reversed . "verify content of 'result: '" 1 to: result size do: [:i | self assert: ((result at:i)=(self nonEmpty at:(self nonEmpty size-i+1)))]. "verify size of 'result' :" self assert: result size=self nonEmpty size.! ! !FloatArrayTest methodsFor: 'tests - copying same contents'! testShallowCopy | result | result := self nonEmpty shallowCopy . "verify content of 'result: '" 1 to: self nonEmpty size do: [:i | self assert: ((result at:i)=(self nonEmpty at:i))]. "verify size of 'result' :" self assert: result size=self nonEmpty size.! ! !FloatArrayTest methodsFor: 'tests - copying same contents'! testShallowCopyEmpty | result | result := self empty shallowCopy . self assert: result isEmpty .! ! !FloatArrayTest methodsFor: 'tests - copying same contents'! testShuffled | result | result := self nonEmpty shuffled . "verify content of 'result: '" result do: [:each | self assert: (self nonEmpty occurrencesOf: each)=(result occurrencesOf: each)]. "verify size of 'result' :" self assert: result size=self nonEmpty size.! ! !FloatArrayTest methodsFor: 'tests - copying same contents'! testSortBy " can only be used if the collection tested can include sortable elements :" | result tmp | self shouldnt: [ self collectionWithSortableElements ] raise: Error. self shouldnt: [self collectionWithSortableElements anyOne < self collectionWithSortableElements anyOne] raise: Error. result := self collectionWithSortableElements sortBy: [ :a :b | a < b ]. "verify content of 'result' : " result do: [ :each | (self collectionWithSortableElements occurrencesOf: each) = (result occurrencesOf: each) ]. tmp := result first. result do: [ :each | self assert: each >= tmp. tmp := each ]. "verify size of 'result' :" self assert: result size = self collectionWithSortableElements size! ! !FloatArrayTest methodsFor: 'tests - copying with or without'! testCopyWithFirst | index element result | index:= self indexInNonEmpty . element:= self nonEmpty at: index. result := self nonEmpty copyWithFirst: element. self assert: result size = (self nonEmpty size + 1). self assert: result first = element . 2 to: result size do: [ :i | self assert: (result at: i) = ( self nonEmpty at: ( i - 1 ))].! ! !FloatArrayTest methodsFor: 'tests - copying with or without'! testCopyWithSequenceable | result index element | index := self indexInNonEmpty . element := self nonEmpty at: index. result := self nonEmpty copyWith: (element ). self assert: result size = (self nonEmpty size + 1). self assert: result last = element . 1 to: (result size - 1) do: [ :i | self assert: (result at: i) = ( self nonEmpty at: ( i ))].! ! !FloatArrayTest methodsFor: 'tests - copying with or without'! testCopyWithoutFirst | result | result := self nonEmpty copyWithoutFirst. self assert: result size = (self nonEmpty size - 1). 1 to: result size do: [:i | self assert: (result at: i)= (self nonEmpty at: (i + 1))].! ! !FloatArrayTest methodsFor: 'tests - copying with or without'! testCopyWithoutIndex | result index | index := self indexInNonEmpty . result := self nonEmpty copyWithoutIndex: index . "verify content of 'result:'" 1 to: result size do: [:i | i<( index ) ifTrue: [self assert: ((result at:i )= (self nonEmpty at:i))]. i>=( index ) ifTrue: [self assert: (result at:i )= (self nonEmpty at:(i+1))]]. "verify size of result : " self assert: result size=(self nonEmpty size -1).! ! !FloatArrayTest methodsFor: 'tests - copying with or without'! testForceToPaddingStartWith | result element | element := self nonEmpty at: self indexInNonEmpty . result := self nonEmpty forceTo: (self nonEmpty size+2) paddingStartWith: ( element ). "verify content of 'result' : " 1 to: 2 do: [:i | self assert: ( element ) = ( result at:(i) ) ]. 3 to: result size do: [:i | self assert: ( result at:i ) = ( self nonEmpty at:(i-2) ) ]. "verify size of 'result' :" self assert: result size = (self nonEmpty size + 2).! ! !FloatArrayTest methodsFor: 'tests - copying with or without'! testForceToPaddingWith | result element | element := self nonEmpty at: self indexInNonEmpty . result := self nonEmpty forceTo: (self nonEmpty size+2) paddingWith: ( element ). "verify content of 'result' : " 1 to: self nonEmpty size do: [:i | self assert: ( self nonEmpty at: i ) = ( result at:(i) ). ]. (result size - 1) to: result size do: [:i | self assert: ( result at:i ) = ( element ) ]. "verify size of 'result' :" self assert: result size = (self nonEmpty size + 2).! ! !FloatArrayTest methodsFor: 'tests - copying with replacement'! firstIndexesOf: subCollection in: collection " return an OrderedCollection with the first indexes of the occurrences of subCollection in collection " | tmp result currentIndex | tmp:= collection. result:= OrderedCollection new. currentIndex := 1. [tmp isEmpty ]whileFalse: [ (tmp beginsWith: subCollection) ifTrue: [ result add: currentIndex. 1 to: subCollection size do: [:i | tmp := tmp copyWithoutFirst. currentIndex := currentIndex + 1] ] ifFalse: [ tmp := tmp copyWithoutFirst. currentIndex := currentIndex +1. ] ]. ^ result. ! ! !FloatArrayTest methodsFor: 'tests - copying with replacement'! testCopyReplaceAllWith1Occurence | result firstIndexesOfOccurrence index endPartIndexResult endPartIndexCollection | result := self collectionWith1TimeSubcollection copyReplaceAll: self oldSubCollection with: self replacementCollection . "detecting indexes of olSubCollection" firstIndexesOfOccurrence := self firstIndexesOf: self oldSubCollection in: self collectionWith1TimeSubcollection . index:= firstIndexesOfOccurrence at: 1. "verify content of 'result' : " "first part of 'result'' : '" 1 to: (index -1) do: [ :i | self assert: (self collectionWith1TimeSubcollection at:i)=(result at: i) ]. " middle part containing replacementCollection : " index to: (index + self replacementCollection size-1) do: [ :i | self assert: ( result at: i )=(self replacementCollection at: ( i - index + 1 )) ]. " end part :" endPartIndexResult := index + self replacementCollection size . endPartIndexCollection := index + self oldSubCollection size . 1 to: (result size - endPartIndexResult - 1 ) do: [ :i | self assert: (result at: ( endPartIndexResult + i - 1 ) ) = (self collectionWith1TimeSubcollection at: ( endPartIndexCollection + i - 1 ) ). ]. ! ! !FloatArrayTest methodsFor: 'tests - copying with replacement'! testCopyReplaceAllWithManyOccurence | result firstIndexesOfOccurrence resultBetweenPartIndex collectionBetweenPartIndex diff | " testing fixture here as this method may be not used for collection that can't contain equals element :" self shouldnt: [self collectionWith2TimeSubcollection ]raise: Error. self assert: (self howMany: self oldSubCollection in: self collectionWith2TimeSubcollection ) = 2. " test :" diff := self replacementCollection size - self oldSubCollection size. result := self collectionWith2TimeSubcollection copyReplaceAll: self oldSubCollection with: self replacementCollection . "detecting indexes of olSubCollection" firstIndexesOfOccurrence := self firstIndexesOf: self oldSubCollection in: self collectionWith2TimeSubcollection . " verifying that replacementCollection has been put in places of oldSubCollections " firstIndexesOfOccurrence do: [ :each | (firstIndexesOfOccurrence indexOf: each) = 1 ifTrue: [ each to: self replacementCollection size do: [ :i | self assert: (result at: i) = ( self replacementCollection at: ( i - each + 1 ) ) ]. ] ifFalse:[ (each + diff) to: self replacementCollection size do: [ :i | self assert: (result at: i) = ( self replacementCollection at: ( i - each + 1 ) ) ]. ]. ]. " verifying that the 'between' parts correspond to the initial collection : " 1 to: firstIndexesOfOccurrence size do: [ :i | i = 1 " specific comportement for the begining of the collection :" ifTrue: [ 1 to: ((firstIndexesOfOccurrence at: i) - 1 ) do: [ :j | self assert: (result at: i) = (self collectionWith2TimeSubcollection at: i) ] ] " between parts till the end : " ifFalse: [ resultBetweenPartIndex := (firstIndexesOfOccurrence at: (i -1)) + self replacementCollection size. collectionBetweenPartIndex := (firstIndexesOfOccurrence at: (i -1)) + self oldSubCollection size. 1 to: ( firstIndexesOfOccurrence at: i) - collectionBetweenPartIndex - 1 do: [ :j | self assert: (result at: (resultBetweenPartIndex + i - 1)) = (self collectionWith2TimeSubcollection at: (collectionBetweenPartIndex +i - 1)) ] ] ]. "final part :" 1 to: (self collectionWith2TimeSubcollection size - (firstIndexesOfOccurrence last + self oldSubCollection size ) ) do: [ :i | self assert: ( result at:(firstIndexesOfOccurrence last + self replacementCollection size -1) + i ) = ( self collectionWith2TimeSubcollection at:(firstIndexesOfOccurrence last + self oldSubCollection size -1) + i ) . ]! ! !FloatArrayTest methodsFor: 'tests - copying with replacement'! testCopyReplaceFromToWith | result indexOfSubcollection lastIndexOfOldSubcollection lastIndexOfReplacementCollection | indexOfSubcollection := (self firstIndexesOf: self oldSubCollection in: self collectionWith1TimeSubcollection) at: 1. lastIndexOfOldSubcollection := indexOfSubcollection + self oldSubCollection size -1. lastIndexOfReplacementCollection := indexOfSubcollection + self replacementCollection size -1. result := self collectionWith1TimeSubcollection copyReplaceFrom: indexOfSubcollection to: lastIndexOfOldSubcollection with: self replacementCollection . "verify content of 'result' : " "first part of 'result' " 1 to: (indexOfSubcollection - 1) do: [ :i | self assert: (self collectionWith1TimeSubcollection at:i) = (result at: i) ]. " middle part containing replacementCollection : " (indexOfSubcollection ) to: ( lastIndexOfReplacementCollection ) do: [ :i | self assert: (result at: i)=(self replacementCollection at: (i - indexOfSubcollection +1)) ]. " end part :" 1 to: (result size - lastIndexOfReplacementCollection ) do: [ :i | self assert: (result at: ( lastIndexOfReplacementCollection + i ) ) = (self collectionWith1TimeSubcollection at: ( lastIndexOfOldSubcollection + i ) ). ]. ! ! !FloatArrayTest methodsFor: 'tests - copying with replacement'! testCopyReplaceFromToWithInsertion | result indexOfSubcollection | indexOfSubcollection := (self firstIndexesOf: self oldSubCollection in: self collectionWith1TimeSubcollection) at: 1. result := self collectionWith1TimeSubcollection copyReplaceFrom: indexOfSubcollection to: ( indexOfSubcollection - 1 ) with: self replacementCollection . "verify content of 'result' : " "first part of 'result'' : '" 1 to: (indexOfSubcollection -1) do: [ :i | self assert: (self collectionWith1TimeSubcollection at:i)=(result at: i) ]. " middle part containing replacementCollection : " indexOfSubcollection to: (indexOfSubcollection + self replacementCollection size-1) do: [ :i | self assert: ( result at: i )=(self replacementCollection at: ( i - indexOfSubcollection +1 )) ]. " end part :" (indexOfSubcollection + self replacementCollection size) to: (result size) do: [:i| self assert: (result at: i)=(self collectionWith1TimeSubcollection at: (i-self replacementCollection size))]. " verify size: " self assert: result size=(self collectionWith1TimeSubcollection size + self replacementCollection size). ! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAfter "self debug: #testAfter" self assert: (self moreThan4Elements after: (self moreThan4Elements at: 1)) = (self moreThan4Elements at: 2). self should: [ self moreThan4Elements after: (self moreThan4Elements at: self moreThan4Elements size) ] raise: Error. self should: [ self moreThan4Elements after: self elementNotInForElementAccessing ] raise: Error! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAfterIfAbsent "self debug: #testAfterIfAbsent" self assert: (self moreThan4Elements after: (self moreThan4Elements at: 1) ifAbsent: [ 33 ]) = (self moreThan4Elements at: 2). self assert: (self moreThan4Elements after: (self moreThan4Elements at: self moreThan4Elements size) ifAbsent: [ 33 ]) == 33. self assert: (self moreThan4Elements after: self elementNotInForElementAccessing ifAbsent: [ 33 ]) = 33! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAt "self debug: #testAt" " self assert: (self accessCollection at: 1) = 1. self assert: (self accessCollection at: 2) = 2. " | index | index := self moreThan4Elements indexOf: self elementInForElementAccessing. self assert: (self moreThan4Elements at: index) = self elementInForElementAccessing! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAtAll "self debug: #testAtAll" " self flag: #theCollectionshouldbe102030intheFixture. self assert: (self accessCollection atAll: #(2 1)) first = self accessCollection second. self assert: (self accessCollection atAll: #(2)) first = self accessCollection second." | result | result := self moreThan4Elements atAll: #(2 1 2 ). self assert: (result at: 1) = (self moreThan4Elements at: 2). self assert: (result at: 2) = (self moreThan4Elements at: 1). self assert: (result at: 3) = (self moreThan4Elements at: 2). self assert: (self moreThan4Elements atAll: #()) = self moreThan4Elements species new! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAtIfAbsent "self debug: #testAt" | absent | absent := false. self moreThan4Elements at: self moreThan4Elements size + 1 ifAbsent: [ absent := true ]. self assert: absent = true. absent := false. self moreThan4Elements at: self moreThan4Elements size ifAbsent: [ absent := true ]. self assert: absent = false! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAtLast "self debug: #testAtLast" | index | self assert: (self moreThan4Elements atLast: 1) = self moreThan4Elements last. "tmp:=1. self do: [:each | each =self elementInForIndexAccessing ifTrue:[index:=tmp]. tmp:=tmp+1]." index := self moreThan4Elements indexOf: self elementInForElementAccessing. self assert: (self moreThan4Elements atLast: index) = (self moreThan4Elements at: self moreThan4Elements size - index + 1)! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAtLastError "self debug: #testAtLast" self should: [ self moreThan4Elements atLast: self moreThan4Elements size + 1 ] raise: Error! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAtLastIfAbsent "self debug: #testAtLastIfAbsent" self assert: (self moreThan4Elements atLast: 1 ifAbsent: [ nil ]) = self moreThan4Elements last. self assert: (self moreThan4Elements atLast: self moreThan4Elements size + 1 ifAbsent: [ 222 ]) = 222! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAtOutOfBounds "self debug: #testAtOutOfBounds" self should: [ self moreThan4Elements at: self moreThan4Elements size + 1 ] raise: Error. self should: [ self moreThan4Elements at: -1 ] raise: Error! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAtPin "self debug: #testAtPin" self assert: (self moreThan4Elements atPin: 2) = self moreThan4Elements second. self assert: (self moreThan4Elements atPin: 99) = self moreThan4Elements last. self assert: (self moreThan4Elements atPin: -99) = self moreThan4Elements first! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAtRandom | result | result := self nonEmpty atRandom . self assert: (self nonEmpty includes: result).! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testAtWrap "self debug: #testAt" " self assert: (self accessCollection at: 1) = 1. self assert: (self accessCollection at: 2) = 2. " | index | index := self moreThan4Elements indexOf: self elementInForElementAccessing. self assert: (self moreThan4Elements atWrap: index) = self elementInForElementAccessing. self assert: (self moreThan4Elements atWrap: index + self moreThan4Elements size) = self elementInForElementAccessing. self assert: (self moreThan4Elements atWrap: index - self moreThan4Elements size) = self elementInForElementAccessing. self assert: (self moreThan4Elements atWrap: 1 + self moreThan4Elements size) = (self moreThan4Elements at: 1)! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testBefore "self debug: #testBefore" self assert: (self moreThan4Elements before: (self moreThan4Elements at: 2)) = (self moreThan4Elements at: 1). self should: [ self moreThan4Elements before: (self moreThan4Elements at: 1) ] raise: Error. self should: [ self moreThan4Elements before: 66 ] raise: Error! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testBeforeIfAbsent "self debug: #testBefore" self assert: (self moreThan4Elements before: (self moreThan4Elements at: 1) ifAbsent: [ 99 ]) = 99. self assert: (self moreThan4Elements before: (self moreThan4Elements at: 2) ifAbsent: [ 99 ]) = (self moreThan4Elements at: 1)! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testFirstSecondThird "self debug: #testFirstSecondThird" self assert: self moreThan4Elements first = (self moreThan4Elements at: 1). self assert: self moreThan4Elements second = (self moreThan4Elements at: 2). self assert: self moreThan4Elements third = (self moreThan4Elements at: 3). self assert: self moreThan4Elements fourth = (self moreThan4Elements at: 4)! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testLast "self debug: #testLast" self assert: self moreThan4Elements last = (self moreThan4Elements at: self moreThan4Elements size)! ! !FloatArrayTest methodsFor: 'tests - element accessing'! testMiddle "self debug: #testMiddle" self assert: self moreThan4Elements middle = (self moreThan4Elements at: self moreThan4Elements size // 2 + 1)! ! !FloatArrayTest methodsFor: 'tests - empty'! testIfEmpty self nonEmpty ifEmpty: [ self assert: false] . self empty ifEmpty: [ self assert: true] . ! ! !FloatArrayTest methodsFor: 'tests - empty'! testIfEmptyifNotEmpty self assert: (self empty ifEmpty: [true] ifNotEmpty: [false]). self assert: (self nonEmpty ifEmpty: [false] ifNotEmpty: [true]). ! ! !FloatArrayTest methodsFor: 'tests - empty'! testIfEmptyifNotEmptyDo "self debug #testIfEmptyifNotEmptyDo" self assert: (self empty ifEmpty: [true] ifNotEmptyDo: [:s | false]). self assert: (self nonEmpty ifEmpty: [false] ifNotEmptyDo: [:s | true]). self assert: (self nonEmpty ifEmpty: [false] ifNotEmptyDo: [:s | s]) == self nonEmpty.! ! !FloatArrayTest methodsFor: 'tests - empty'! testIfNotEmpty self empty ifNotEmpty: [self assert: false]. self nonEmpty ifNotEmpty: [self assert: true]. self assert: (self nonEmpty ifNotEmpty: [:s | s ]) = self nonEmpty ! ! !FloatArrayTest methodsFor: 'tests - empty'! testIfNotEmptyDo self empty ifNotEmptyDo: [:s | self assert: false]. self assert: (self nonEmpty ifNotEmptyDo: [:s | s]) == self nonEmpty ! ! !FloatArrayTest methodsFor: 'tests - empty'! testIfNotEmptyDoifNotEmpty self assert: (self empty ifNotEmptyDo: [:s | false] ifEmpty: [true]). self assert: (self nonEmpty ifNotEmptyDo: [:s | s] ifEmpty: [false]) == self nonEmpty! ! !FloatArrayTest methodsFor: 'tests - empty'! testIfNotEmptyifEmpty self assert: (self empty ifNotEmpty: [false] ifEmpty: [true]). self assert: (self nonEmpty ifNotEmpty: [true] ifEmpty: [false]). ! ! !FloatArrayTest methodsFor: 'tests - empty'! testIsEmpty self assert: (self empty isEmpty). self deny: (self nonEmpty isEmpty).! ! !FloatArrayTest methodsFor: 'tests - empty'! testIsEmptyOrNil self assert: (self empty isEmptyOrNil). self deny: (self nonEmpty isEmptyOrNil).! ! !FloatArrayTest methodsFor: 'tests - empty'! testNotEmpty self assert: (self nonEmpty notEmpty). self deny: (self empty notEmpty).! ! !FloatArrayTest methodsFor: 'tests - equality'! testEqualSignForSequenceableCollections "self debug: #testEqualSign" self deny: (self nonEmpty = self nonEmpty asSet). self deny: (self nonEmpty reversed = self nonEmpty). self deny: (self nonEmpty = self nonEmpty reversed).! ! !FloatArrayTest methodsFor: 'tests - equality'! testHasEqualElements "self debug: #testHasEqualElements" self deny: (self empty hasEqualElements: self nonEmpty). self deny: (self nonEmpty hasEqualElements: self nonEmpty asSet). self deny: (self nonEmpty reversed hasEqualElements: self nonEmpty). self deny: (self nonEmpty hasEqualElements: self nonEmpty reversed).! ! !FloatArrayTest methodsFor: 'tests - equality'! testHasEqualElementsIsTrueForNonIdenticalButEqualCollections "self debug: #testHasEqualElementsIsTrueForNonIdenticalButEqualCollections" self assert: (self empty hasEqualElements: self empty copy). self assert: (self empty copy hasEqualElements: self empty). self assert: (self empty copy hasEqualElements: self empty copy). self assert: (self nonEmpty hasEqualElements: self nonEmpty copy). self assert: (self nonEmpty copy hasEqualElements: self nonEmpty). self assert: (self nonEmpty copy hasEqualElements: self nonEmpty copy).! ! !FloatArrayTest methodsFor: 'tests - equality'! testHasEqualElementsOfIdenticalCollectionObjects "self debug: #testHasEqualElementsOfIdenticalCollectionObjects" self assert: (self empty hasEqualElements: self empty). self assert: (self nonEmpty hasEqualElements: self nonEmpty). ! ! !FloatArrayTest methodsFor: 'tests - fixture'! howMany: subCollection in: collection " return an integer representing how many time 'subCollection' appears in 'collection' " | tmp nTime | tmp:= collection. nTime:= 0. [tmp isEmpty ]whileFalse: [ (tmp beginsWith: subCollection) ifTrue: [ nTime := nTime + 1. 1 to: subCollection size do: [:i | tmp := tmp copyWithoutFirst.] ] ifFalse: [tmp := tmp copyWithoutFirst.] ]. ^ nTime. ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0CopyTest self shouldnt: [ self empty ]raise: Error. self assert: self empty size = 0. self shouldnt: [ self nonEmpty ]raise: Error. self assert: (self nonEmpty size = 0) not. self shouldnt: [ self collectionWithElementsToRemove ]raise: Error. self assert: (self collectionWithElementsToRemove size = 0) not. self collectionWithElementsToRemove do: [:each | self assert: ( self nonEmpty includes: each)]. self shouldnt: [ self elementToAdd ]raise: Error. self deny: (self nonEmpty includes: self elementToAdd ). self shouldnt: [ self collectionNotIncluded ]raise: Error. self collectionNotIncluded do: [ :each | self deny: (self nonEmpty includes: each) ]! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureAsSetForIdentityMultiplinessTest "a collection (of elements for which copy is not identical ) without equal elements:" | element res | self shouldnt: [ self elementsCopyNonIdenticalWithoutEqualElements ]raise: Error. element := self elementsCopyNonIdenticalWithoutEqualElements anyOne. self deny: element copy == element . res := true. self elementsCopyNonIdenticalWithoutEqualElements detect: [ :each | (self elementsCopyNonIdenticalWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureAsStringCommaAndDelimiterTest self shouldnt: [self nonEmpty] raise:Error . self deny: self nonEmpty isEmpty. self shouldnt: [self empty] raise:Error . self assert: self empty isEmpty. self shouldnt: [self nonEmpty1Element ] raise:Error . self assert: self nonEmpty1Element size=1.! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureBeginsEndsWithTest self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self assert: self nonEmpty size>1. self shouldnt: [self empty ] raise: Error. self assert: self empty isEmpty.! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureCloneTest self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty. ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureConverAsSortedTest self shouldnt: [self collectionWithSortableElements ] raise: Error. self deny: self collectionWithSortableElements isEmpty .! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureCopyPartOfForMultipliness self shouldnt: [self collectionWithSameAtEndAndBegining ] raise: Error. self assert: self collectionWithSameAtEndAndBegining first = self collectionWithSameAtEndAndBegining last. self assert: self collectionWithSameAtEndAndBegining size > 1. 1 to: self collectionWithSameAtEndAndBegining size do: [:i | (i > 1 ) & (i < self collectionWithSameAtEndAndBegining size) ifTrue: [ self deny: (self collectionWithSameAtEndAndBegining at:i) = (self collectionWithSameAtEndAndBegining first)]. ]! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureCopyPartOfSequenceableTest self shouldnt: [self collectionWithoutEqualsElements ] raise: Error. self collectionWithoutEqualsElements do: [:each | self assert: (self collectionWithoutEqualsElements occurrencesOf: each)=1]. self shouldnt: [self indexInForCollectionWithoutDuplicates ] raise: Error. self assert: self indexInForCollectionWithoutDuplicates >0 & self indexInForCollectionWithoutDuplicates < self collectionWithoutEqualsElements size. self shouldnt: [self empty] raise: Error. self assert: self empty isEmpty .! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureCopySameContentsTest self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [self empty ] raise: Error. self assert: self empty isEmpty. ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureCopyWithOrWithoutSpecificElementsTest self shouldnt: [self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty . self shouldnt: [self indexInNonEmpty ] raise: Error. self assert: self indexInNonEmpty > 0. self assert: self indexInNonEmpty <= self nonEmpty size.! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureCopyWithReplacementTest self shouldnt: [self replacementCollection ]raise: Error. self shouldnt: [self oldSubCollection] raise: Error. self shouldnt: [self collectionWith1TimeSubcollection ]raise: Error. self assert: (self howMany: self oldSubCollection in: self collectionWith1TimeSubcollection ) = 1. ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureCreationWithTest self shouldnt: [ self collectionMoreThan5Elements ] raise: Error. self assert: self collectionMoreThan5Elements size >= 5.! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureEmptyTest self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty.! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureIncludeTest | elementIn | self shouldnt: [ self nonEmpty ]raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self elementNotIn ]raise: Error. elementIn := true. self nonEmpty detect: [ :each | each = self elementNotIn ] ifNone: [ elementIn := false ]. self assert: elementIn = false. self shouldnt: [ self anotherElementNotIn ]raise: Error. elementIn := true. self nonEmpty detect: [ :each | each = self anotherElementNotIn ] ifNone: [ elementIn := false ]. self assert: elementIn = false. self shouldnt: [ self empty ] raise: Error. self assert: self empty isEmpty. ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureIncludeWithIdentityTest | element | self shouldnt: [ self collectionWithCopyNonIdentical ]raise: Error. element := self collectionWithCopyNonIdentical anyOne. self deny: element == element copy. ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureIndexAccessFotMultipliness self shouldnt: [ self collectionWithSameAtEndAndBegining ] raise: Error. self assert: self collectionWithSameAtEndAndBegining first = self collectionWithSameAtEndAndBegining last. self assert: self collectionWithSameAtEndAndBegining size > 1. 1 to: self collectionWithSameAtEndAndBegining size do: [ :i | i > 1 & (i < self collectionWithSameAtEndAndBegining size) ifTrue: [ self deny: (self collectionWithSameAtEndAndBegining at: i) = self collectionWithSameAtEndAndBegining first ] ]! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureIndexAccessTest | res collection element | self shouldnt: [ self collectionMoreThan1NoDuplicates ] raise: Error. self assert: self collectionMoreThan1NoDuplicates size >1. res := true. self collectionMoreThan1NoDuplicates detect: [ :each | (self collectionMoreThan1NoDuplicates occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false. self shouldnt: [ self elementInForIndexAccessing ] raise: Error. self assert: ( (collection := self collectionMoreThan1NoDuplicates )includes: (element:= self elementInForIndexAccessing)). self shouldnt: [ self elementNotInForIndexAccessing ] raise: Error. self deny: (self collectionMoreThan1NoDuplicates includes: self elementNotInForIndexAccessing)! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureIterateSequencedReadableTest | res | self shouldnt: self nonEmptyMoreThan1Element raise: Error. self assert: self nonEmptyMoreThan1Element size > 1. self shouldnt: self empty raise: Error. self assert: self empty isEmpty . res := true. self nonEmptyMoreThan1Element detect: [ :each | (self nonEmptyMoreThan1Element occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false.! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixturePrintTest self shouldnt: [self nonEmpty ] raise: Error.! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixturePutOneOrMoreElementsTest self shouldnt: self aValue raise: Error. self shouldnt: self indexArray raise: Error. self indexArray do: [ :each| self assert: each class = SmallInteger. self assert: (each>=1 & each<= self nonEmpty size). ]. self assert: self indexArray size = self valueArray size. self shouldnt: self empty raise: Error. self assert: self empty isEmpty . self shouldnt: self nonEmpty raise: Error. self deny: self nonEmpty isEmpty.! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixturePutTest self shouldnt: self aValue raise: Error. self shouldnt: self anotherValue raise: Error. self shouldnt: self anIndex raise: Error. self nonEmpty isDictionary ifFalse:[self assert: (self anIndex >=1 & self anIndex <= self nonEmpty size).]. self shouldnt: self empty raise: Error. self assert: self empty isEmpty . self shouldnt: self nonEmpty raise: Error. self deny: self nonEmpty isEmpty.! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureSequencedConcatenationTest self shouldnt: self empty raise: Exception. self assert: self empty isEmpty. self shouldnt: self firstCollection raise: Exception. self shouldnt: self secondCollection raise: Exception! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureSequencedElementAccessTest self shouldnt: [ self moreThan4Elements ] raise: Error. self assert: self moreThan4Elements size >= 4. self shouldnt: [ self subCollectionNotIn ] raise: Error. self subCollectionNotIn detect: [ :each | (self moreThan4Elements includes: each) not ] ifNone: [ self assert: false ]. self shouldnt: [ self elementNotInForElementAccessing ] raise: Error. self deny: (self moreThan4Elements includes: self elementNotInForElementAccessing). self shouldnt: [ self elementInForElementAccessing ] raise: Error. self assert: (self moreThan4Elements includes: self elementInForElementAccessing)! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureSetAritmeticTest self shouldnt: [ self collection ] raise: Error. self deny: self collection isEmpty. self shouldnt: [ self nonEmpty ] raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: [ self anotherElementOrAssociationNotIn ] raise: Error. self collection isDictionary ifTrue: [ self deny: (self collection associations includes: self anotherElementOrAssociationNotIn key) ] ifFalse: [ self deny: (self collection includes: self anotherElementOrAssociationNotIn) ]. self shouldnt: [ self collectionClass ] raise: Error! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureSubcollectionAccessTest self shouldnt: [ self moreThan3Elements ] raise: Error. self assert: self moreThan3Elements size > 2! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureTConvertAsSetForMultiplinessTest "a collection with equal elements:" | res | self shouldnt: [ self withEqualElements] raise: Error. res := true. self withEqualElements detect: [ :each | (self withEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = true. ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0FixtureTConvertTest "a collection of number without equal elements:" | res | self shouldnt: [ self collectionWithoutEqualElements ]raise: Error. res := true. self collectionWithoutEqualElements detect: [ :each | (self collectionWithoutEqualElements occurrencesOf: each) > 1 ] ifNone: [ res := false ]. self assert: res = false. ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0SortingArrayedTest | tmp sorted | " an unsorted collection of number " self shouldnt: [ self unsortedCollection ]raise: Error. self unsortedCollection do:[:each | each isNumber]. sorted := true. self unsortedCollection pairsDo: [ :each1 :each2 | each2 < each1 ifTrue: [ sorted := false]. ]. self assert: sorted = false. " a collection of number sorted in an ascending order" self shouldnt: [ self sortedInAscendingOrderCollection ]raise: Error. self sortedInAscendingOrderCollection do:[:each | each isNumber]. tmp:= self sortedInAscendingOrderCollection at:1. self sortedInAscendingOrderCollection do: [: each | self assert: (each>= tmp). tmp:=each] ! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0TSequencedStructuralEqualityTest self shouldnt: [self nonEmpty at: 1] raise: Error. "Ensures #nonEmpty is sequenceable"! ! !FloatArrayTest methodsFor: 'tests - fixture'! test0TStructuralEqualityTest self shouldnt: [self empty] raise: Error. self shouldnt: [self nonEmpty] raise: Error. self assert: self empty isEmpty. self deny: self nonEmpty isEmpty.! ! !FloatArrayTest methodsFor: 'tests - fixture'! testOFixtureReplacementSequencedTest self shouldnt: self nonEmpty raise: Error. self deny: self nonEmpty isEmpty. self shouldnt: self elementInForReplacement raise: Error. self assert: (self nonEmpty includes: self elementInForReplacement ) . self shouldnt: self newElement raise: Error. self shouldnt: self firstIndex raise: Error. self assert: (self firstIndex >= 1 & self firstIndex <= self nonEmpty size). self shouldnt: self secondIndex raise: Error. self assert: (self secondIndex >= 1 & self secondIndex <= self nonEmpty size). self assert: self firstIndex <=self secondIndex . self shouldnt: self replacementCollection raise: Error. self shouldnt: self replacementCollectionSameSize raise: Error. self assert: (self secondIndex - self firstIndex +1)= self replacementCollectionSameSize size ! ! !FloatArrayTest methodsFor: 'tests - includes'! testIncludesAllOfAllThere "self debug: #testIncludesAllOfAllThere'" self assert: (self empty includesAllOf: self empty). self assert: (self nonEmpty includesAllOf: { self nonEmpty anyOne }). self assert: (self nonEmpty includesAllOf: self nonEmpty).! ! !FloatArrayTest methodsFor: 'tests - includes'! testIncludesAllOfNoneThere "self debug: #testIncludesAllOfNoneThere'" self deny: (self empty includesAllOf: self nonEmpty ). self deny: (self nonEmpty includesAllOf: { self elementNotIn. self anotherElementNotIn })! ! !FloatArrayTest methodsFor: 'tests - includes'! testIncludesAnyOfAllThere "self debug: #testIncludesAnyOfAllThere'" self deny: (self nonEmpty includesAnyOf: self empty). self assert: (self nonEmpty includesAnyOf: { self nonEmpty anyOne }). self assert: (self nonEmpty includesAnyOf: self nonEmpty).! ! !FloatArrayTest methodsFor: 'tests - includes'! testIncludesAnyOfNoneThere "self debug: #testIncludesAnyOfNoneThere'" self deny: (self nonEmpty includesAnyOf: self empty). self deny: (self nonEmpty includesAnyOf: { self elementNotIn. self anotherElementNotIn })! ! !FloatArrayTest methodsFor: 'tests - includes'! testIncludesElementIsNotThere "self debug: #testIncludesElementIsNotThere" self deny: (self nonEmpty includes: self elementNotIn). self assert: (self nonEmpty includes: self nonEmpty anyOne). self deny: (self empty includes: self elementNotIn)! ! !FloatArrayTest methodsFor: 'tests - includes'! testIncludesElementIsThere "self debug: #testIncludesElementIsThere" self assert: (self nonEmpty includes: self nonEmpty anyOne).! ! !FloatArrayTest methodsFor: 'tests - including with identity'! testIdentityIncludes " test the comportement in presence of elements 'includes' but not 'identityIncludes' " " can not be used by collections that can't include elements for wich copy doesn't return another instance " | collection element | collection := self collectionWithCopyNonIdentical. element := collection anyOne copy. self deny: (collection identityIncludes: element)! ! !FloatArrayTest methodsFor: 'tests - index access'! testIndexOf "self debug: #testIndexOf" | tmp index collection | collection := self collectionMoreThan1NoDuplicates. tmp := collection size. collection reverseDo: [ :each | each = self elementInForIndexAccessing ifTrue: [ index := tmp ]. tmp := tmp - 1 ]. self assert: (collection indexOf: self elementInForIndexAccessing) = index! ! !FloatArrayTest methodsFor: 'tests - index access'! testIndexOfIfAbsent "self debug: #testIndexOfIfAbsent" | collection | collection := self collectionMoreThan1NoDuplicates. self assert: (collection indexOf: collection first ifAbsent: [ 33 ]) = 1. self assert: (collection indexOf: self elementNotInForIndexAccessing ifAbsent: [ 33 ]) = 33! ! !FloatArrayTest methodsFor: 'tests - index access'! testIndexOfStartingAt "self debug: #testLastIndexOf" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection first. self assert: (collection indexOf: element startingAt: 2 ifAbsent: [ 99 ]) = 99. self assert: (collection indexOf: element startingAt: 1 ifAbsent: [ 99 ]) = 1. self assert: (collection indexOf: self elementNotInForIndexAccessing startingAt: 1 ifAbsent: [ 99 ]) = 99! ! !FloatArrayTest methodsFor: 'tests - index access'! testIndexOfStartingAtIfAbsent "self debug: #testLastIndexOf" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection first. self assert: (collection indexOf: element startingAt: 2 ifAbsent: [ 99 ]) = 99. self assert: (collection indexOf: element startingAt: 1 ifAbsent: [ 99 ]) = 1. self assert: (collection indexOf: self elementNotInForIndexAccessing startingAt: 1 ifAbsent: [ 99 ]) = 99! ! !FloatArrayTest methodsFor: 'tests - index access'! testIndexOfSubCollectionStartingAt "self debug: #testIndexOfIfAbsent" | subcollection index collection | collection := self collectionMoreThan1NoDuplicates. subcollection := self collectionMoreThan1NoDuplicates. index := collection indexOfSubCollection: subcollection startingAt: 1. self assert: index = 1. index := collection indexOfSubCollection: subcollection startingAt: 2. self assert: index = 0! ! !FloatArrayTest methodsFor: 'tests - index access'! testIndexOfSubCollectionStartingAtIfAbsent "self debug: #testIndexOfIfAbsent" | index absent subcollection collection | collection := self collectionMoreThan1NoDuplicates. subcollection := self collectionMoreThan1NoDuplicates. absent := false. index := collection indexOfSubCollection: subcollection startingAt: 1 ifAbsent: [ absent := true ]. self assert: absent = false. absent := false. index := collection indexOfSubCollection: subcollection startingAt: 2 ifAbsent: [ absent := true ]. self assert: absent = true! ! !FloatArrayTest methodsFor: 'tests - index access'! testLastIndexOf "self debug: #testLastIndexOf" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection first. self assert: (collection lastIndexOf: element) = 1. self assert: (collection lastIndexOf: self elementNotInForIndexAccessing) = 0! ! !FloatArrayTest methodsFor: 'tests - index access'! testLastIndexOfIfAbsent "self debug: #testIndexOfIfAbsent" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection first. self assert: (collection lastIndexOf: element ifAbsent: [ 99 ]) = 1. self assert: (collection lastIndexOf: self elementNotInForIndexAccessing ifAbsent: [ 99 ]) = 99! ! !FloatArrayTest methodsFor: 'tests - index access'! testLastIndexOfStartingAt "self debug: #testLastIndexOf" | element collection | collection := self collectionMoreThan1NoDuplicates. element := collection last. self assert: (collection lastIndexOf: element startingAt: collection size ifAbsent: [ 99 ]) = collection size. self assert: (collection lastIndexOf: element startingAt: collection size - 1 ifAbsent: [ 99 ]) = 99. self assert: (collection lastIndexOf: self elementNotInForIndexAccessing startingAt: collection size ifAbsent: [ 99 ]) = 99! ! !FloatArrayTest methodsFor: 'tests - index accessing for multipliness'! testIndexOfDuplicate "self debug: #testIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'indexOf: should return the position of the first occurrence :'" self assert: (collection indexOf: element) = 1! ! !FloatArrayTest methodsFor: 'tests - index accessing for multipliness'! testIndexOfIfAbsentDuplicate "self debug: #testIndexOfIfAbsent" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'indexOf:ifAbsent: should return the position of the first occurrence :'" self assert: (collection indexOf: element ifAbsent: [ 55 ]) = 1! ! !FloatArrayTest methodsFor: 'tests - index accessing for multipliness'! testIndexOfStartingAtDuplicate "self debug: #testLastIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'indexOf:ifAbsent:startingAt: should return the position of the first occurrence :'" self assert: (collection indexOf: element startingAt: 1 ifAbsent: [ 55 ]) = 1. self assert: (collection indexOf: element startingAt: 2 ifAbsent: [ 55 ]) = collection size! ! !FloatArrayTest methodsFor: 'tests - index accessing for multipliness'! testLastIndexOfDuplicate "self debug: #testLastIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection first. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'lastIndexOf: should return the position of the last occurrence :'" self assert: (collection lastIndexOf: element) = collection size! ! !FloatArrayTest methodsFor: 'tests - index accessing for multipliness'! testLastIndexOfIfAbsentDuplicate "self debug: #testIndexOfIfAbsent" "self debug: #testLastIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection first. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'lastIndexOf: should return the position of the last occurrence :'" self assert: (collection lastIndexOf: element ifAbsent: [ 55 ]) = collection size! ! !FloatArrayTest methodsFor: 'tests - index accessing for multipliness'! testLastIndexOfStartingAtDuplicate "self debug: #testLastIndexOf" | collection element | collection := self collectionWithSameAtEndAndBegining. element := collection last. " floatCollectionWithSameAtEndAndBegining first and last elements are equals 'lastIndexOf:ifAbsent:startingAt: should return the position of the last occurrence :'" self assert: (collection lastIndexOf: element startingAt: collection size ifAbsent: [ 55 ]) = collection size. self assert: (collection lastIndexOf: element startingAt: collection size - 1 ifAbsent: [ 55 ]) = 1! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testAllButFirstDo | result | result:= OrderedCollection new. self nonEmptyMoreThan1Element allButFirstDo: [:each | result add: each]. 1 to: (result size) do: [:i| self assert: (self nonEmptyMoreThan1Element at:(i +1))=(result at:i)]. self assert: result size=(self nonEmptyMoreThan1Element size-1).! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testAllButLastDo | result | result:= OrderedCollection new. self nonEmptyMoreThan1Element allButLastDo: [:each | result add: each]. 1 to: (result size) do: [:i| self assert: (self nonEmptyMoreThan1Element at:(i ))=(result at:i)]. self assert: result size=(self nonEmptyMoreThan1Element size-1).! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testCollectFromTo | result | result:=self nonEmptyMoreThan1Element collect: [ :each | each ] from: 1 to: (self nonEmptyMoreThan1Element size - 1). 1 to: result size do: [ :i | self assert: (self nonEmptyMoreThan1Element at: i) = (result at: i) ]. self assert: result size = (self nonEmptyMoreThan1Element size - 1)! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testDetectSequenced " testing that detect keep the first element returning true for sequenceable collections " | element result | element := self nonEmptyMoreThan1Element at:1. result:=self nonEmptyMoreThan1Element detect: [:each | each notNil ]. self assert: result = element. ! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testDo! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFindFirst | element result | element := self nonEmptyMoreThan1Element at:1. result:=self nonEmptyMoreThan1Element findFirst: [:each | each =element]. self assert: result=1. ! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFindFirstNotIn | result | result:=self empty findFirst: [:each | true]. self assert: result=0. ! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFindLast | element result | element := self nonEmptyMoreThan1Element at:self nonEmptyMoreThan1Element size. result:=self nonEmptyMoreThan1Element findLast: [:each | each =element]. self assert: result=self nonEmptyMoreThan1Element size. ! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFindLastNotIn | result | result:=self empty findFirst: [:each | true]. self assert: result=0. ! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testFromToDo | result | result:= OrderedCollection new. self nonEmptyMoreThan1Element from: 1 to: (self nonEmptyMoreThan1Element size -1) do: [:each | result add: each]. 1 to: (self nonEmptyMoreThan1Element size -1) do: [:i| self assert: (self nonEmptyMoreThan1Element at:i )=(result at:i)]. self assert: result size=(self nonEmptyMoreThan1Element size-1).! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testKeysAndValuesDo "| result | result:= OrderedCollection new. self nonEmptyMoreThan1Element keysAndValuesDo: [:i :value| result add: (value+i)]. 1 to: result size do: [:i| self assert: (result at:i)=((self nonEmptyMoreThan1Element at:i)+i)]" | indexes elements | indexes:= OrderedCollection new. elements := OrderedCollection new. self nonEmptyMoreThan1Element keysAndValuesDo: [:i :value| indexes add: (i). elements add: value]. (1 to: self nonEmptyMoreThan1Element size )do: [ :i | self assert: (indexes at: i) = i. self assert: (elements at: i) = (self nonEmptyMoreThan1Element at: i). ]. self assert: indexes size = elements size. self assert: indexes size = self nonEmptyMoreThan1Element size . ! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testKeysAndValuesDoEmpty | result | result:= OrderedCollection new. self empty keysAndValuesDo: [:i :value| result add: (value+i)]. self assert: result isEmpty .! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testPairsCollect | index result | index:=0. result:=self nonEmptyMoreThan1Element pairsCollect: [:each1 :each2 | self assert: ( self nonEmptyMoreThan1Element indexOf: each2 ) = (index := index + 2). (self nonEmptyMoreThan1Element indexOf: each2) = ((self nonEmptyMoreThan1Element indexOf: each1) + 1). ]. result do: [:each | self assert: each = true]. ! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testPairsDo | index | index:=1. self nonEmptyMoreThan1Element pairsDo: [:each1 :each2 | self assert:(self nonEmptyMoreThan1Element at:index)=each1. self assert:(self nonEmptyMoreThan1Element at:(index+1))=each2. index:=index+2]. self nonEmptyMoreThan1Element size odd ifTrue:[self assert: index=self nonEmptyMoreThan1Element size] ifFalse:[self assert: index=(self nonEmptyMoreThan1Element size+1)].! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testReverseDo | result | result:= OrderedCollection new. self nonEmpty reverseDo: [: each | result add: each]. 1 to: result size do: [:i| self assert: (result at: i)=(self nonEmpty at:(self nonEmpty size-i+1))].! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testReverseDoEmpty | result | result:= OrderedCollection new. self empty reverseDo: [: each | result add: each]. self assert: result isEmpty .! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testReverseWithDo | secondCollection result index | result:= OrderedCollection new. index := self nonEmptyMoreThan1Element size + 1. secondCollection:= self nonEmptyMoreThan1Element copy. self nonEmptyMoreThan1Element reverseWith: secondCollection do: [:a :b | self assert: (self nonEmptyMoreThan1Element indexOf: a ) = (index := index - 1 ). result add: (a = b)]. 1 to: result size do: [:i| self assert: (result at:i)=(true)]. self assert: result size = self nonEmptyMoreThan1Element size.! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithCollect | result newCollection index collection | index := 0. collection := self nonEmptyMoreThan1Element . newCollection := collection copy. result:=collection with: newCollection collect: [:a :b | self assert: (collection indexOf: a ) = ( index := index + 1). self assert: (a = b). b]. 1 to: result size do:[: i | self assert: (result at:i)= (collection at: i)]. self assert: result size = collection size.! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithCollectError self should: [self nonEmptyMoreThan1Element with: self empty collect:[:a :b | ]] raise: Error.! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithDo | secondCollection result index | result:= OrderedCollection new. secondCollection:= self nonEmptyMoreThan1Element copy. index := 0. self nonEmptyMoreThan1Element with: secondCollection do: [:a :b | self assert: (self nonEmptyMoreThan1Element indexOf: a) = ( index := index + 1). result add: (a =b)]. 1 to: result size do: [:i| self assert: (result at:i)=(true)]. self assert: result size = self nonEmptyMoreThan1Element size.! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithDoError self should: [self nonEmptyMoreThan1Element with: self empty do:[:a :b | ]] raise: Error.! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithIndexCollect | result index collection | index := 0. collection := self nonEmptyMoreThan1Element . result := collection withIndexCollect: [:each :i | self assert: i = (index := index + 1). self assert: i = (collection indexOf: each) . each] . 1 to: result size do:[: i | self assert: (result at:i)= (collection at: i)]. self assert: result size = collection size.! ! !FloatArrayTest methodsFor: 'tests - iterate on sequenced reable collections'! testWithIndexDo "| result | result:=Array new: self nonEmptyMoreThan1Element size. self nonEmptyMoreThan1Element withIndexDo: [:each :i | result at:i put:(each+i)]. 1 to: result size do:[: i | self assert: (result at:i)= ((self nonEmptyMoreThan1Element at: i) + i)]" | indexes elements | indexes:= OrderedCollection new. elements := OrderedCollection new. self nonEmptyMoreThan1Element withIndexDo: [:value :i | indexes add: (i). elements add: value]. (1 to: self nonEmptyMoreThan1Element size )do: [ :i | self assert: (indexes at: i) = i. self assert: (elements at: i) = (self nonEmptyMoreThan1Element at: i). ]. self assert: indexes size = elements size. self assert: indexes size = self nonEmptyMoreThan1Element size . ! ! !FloatArrayTest methodsFor: 'tests - printing'! testPrintElementsOn | aStream result allElementsAsString | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printElementsOn: aStream . allElementsAsString:=(result findBetweenSubStrs: ' ' ). 1 to: allElementsAsString size do: [:i | self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString). ].! ! !FloatArrayTest methodsFor: 'tests - printing'! testPrintNameOn | aStream result | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printNameOn: aStream . Transcript show: result asString. self nonEmpty class name first isVowel ifTrue:[ self assert: aStream contents =('an ',self nonEmpty class name ) ] ifFalse:[self assert: aStream contents =('a ',self nonEmpty class name)].! ! !FloatArrayTest methodsFor: 'tests - printing'! testPrintOn | aStream result allElementsAsString | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printOn: aStream . allElementsAsString:=(result findBetweenSubStrs: ' ' ). 1 to: allElementsAsString size do: [:i | i=1 ifTrue:[ self accessCollection class name first isVowel ifTrue:[self assert: (allElementsAsString at:i)='an' ] ifFalse:[self assert: (allElementsAsString at:i)='a'].]. i=2 ifTrue:[self assert: (allElementsAsString at:i)=self accessCollection class name]. i>2 ifTrue:[self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString).]. ].! ! !FloatArrayTest methodsFor: 'tests - printing'! testPrintOnDelimiter | aStream result allElementsAsString | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printOn: aStream delimiter: ', ' . allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString). ].! ! !FloatArrayTest methodsFor: 'tests - printing'! testPrintOnDelimiterLast | aStream result allElementsAsString | result:=''. aStream:= ReadWriteStream on: result. self nonEmpty printOn: aStream delimiter: ', ' last: 'and'. allElementsAsString:=(result findBetweenSubStrs: ', ' ). 1 to: allElementsAsString size do: [:i | i<(allElementsAsString size-1 ) ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:i)asString)]. i=(allElementsAsString size-1) ifTrue:[ self deny: (allElementsAsString at:i)=('and')asString]. i=(allElementsAsString size) ifTrue: [self assert: (allElementsAsString at:i)=((self nonEmpty at:(i-1))asString)]. ].! ! !FloatArrayTest methodsFor: 'tests - printing'! testStoreOn " for the moment work only for collection that include simple elements such that Integer" "| string str result cuttedResult index elementsAsStringExpected elementsAsStringObtained tmp | string := ''. str := ReadWriteStream on: string. elementsAsStringExpected := OrderedCollection new. elementsAsStringObtained := OrderedCollection new. self nonEmpty do: [ :each | elementsAsStringExpected add: each asString]. self nonEmpty storeOn: str. result := str contents . cuttedResult := ( result findBetweenSubStrs: ';' ). index := 1. cuttedResult do: [ :each | index = 1 ifTrue: [ self assert: (each beginsWith: ( tmp := '((' , self nonEmpty class asString , ' new) add: ' )). tmp := each copyFrom: ( tmp size + 1) to: ( each size ). elementsAsStringObtained add: tmp. index := index + 1. ] ifFalse: [ index < cuttedResult size ifTrue:[self assert: (each beginsWith: ( tmp:= ' add: ' )). tmp := each copyFrom: ( tmp size + 1) to: ( each size ). elementsAsStringObtained add: tmp. index := index + 1.] ifFalse: [self assert: ( each = ' yourself)' ) ]. ] ]. elementsAsStringExpected do: [ :each | self assert: (elementsAsStringExpected occurrencesOf: each ) = ( elementsAsStringObtained occurrencesOf: each) ]" ! ! !FloatArrayTest methodsFor: 'tests - puting with indexes'! testAtAllIndexesPut self nonEmpty atAllPut: self aValue. self nonEmpty do:[ :each| self assert: each = self aValue]. ! ! !FloatArrayTest methodsFor: 'tests - puting with indexes'! testAtAllPut | | self nonEmpty atAll: self indexArray put: self aValue.. self indexArray do: [:i | self assert: (self nonEmpty at: i)=self aValue ]. ! ! !FloatArrayTest methodsFor: 'tests - puting with indexes'! testAtAllPutAll | valueArray | valueArray := self valueArray . self nonEmpty atAll: self indexArray putAll: valueArray . 1 to: self indexArray size do: [:i | self assert: (self nonEmpty at:(self indexArray at: i))= (valueArray at:i) ]! ! !FloatArrayTest methodsFor: 'tests - puting with indexes'! testAtLastPut | result index | index := self indexArray anyOne. result := self nonEmpty atLast: index put: self aValue. self assert: (self nonEmpty at: (self nonEmpty size +1 - index)) = self aValue .! ! !FloatArrayTest methodsFor: 'tests - puting with indexes'! testAtWrapPut "self debug: #testAtWrapPut" | index | index := self indexArray anyOne. self nonEmpty atWrap: 0 put: self aValue. self assert: (self nonEmpty at:(self nonEmpty size))=self aValue. self nonEmpty atWrap: (self nonEmpty size+1) put: self aValue. self assert: (self nonEmpty at:(1))=self aValue. self nonEmpty atWrap: (index ) put: self aValue. self assert: (self nonEmpty at: index ) = self aValue. self nonEmpty atWrap: (self nonEmpty size+index ) put: self aValue . self assert: (self nonEmpty at:(index ))=self aValue .! ! !FloatArrayTest methodsFor: 'tests - puting with indexes'! testFromToPut | collection index | index := self indexArray anyOne. collection := self nonEmpty copy. collection from: 1 to: index put: self aValue.. 1 to: index do: [:i | self assert: (collection at: i)= self aValue]. (index +1) to: collection size do: [:i | self assert: (collection at:i)= (self nonEmpty at:i)].! ! !FloatArrayTest methodsFor: 'tests - puting with indexes'! testSwapWith "self debug: #testSwapWith" | result index | index := self indexArray anyOne. result:= self nonEmpty copy . result swap: index with: 1. self assert: (result at: index) = (self nonEmpty at:1). self assert: (result at: 1) = (self nonEmpty at: index). ! ! !FloatArrayTest methodsFor: 'tests - replacing'! testReplaceAllWith | result collection oldElement newElement | collection := self nonEmpty . result := collection copy. oldElement := self elementInForReplacement . newElement := self newElement . result replaceAll: oldElement with: newElement . 1 to: collection size do: [: each | ( collection at: each ) = oldElement ifTrue: [ self assert: ( result at: each ) = newElement ]. ].! ! !FloatArrayTest methodsFor: 'tests - replacing'! testReplaceFromToWith | result collection replacementCollection firstIndex secondIndex | collection := self nonEmpty . replacementCollection := self replacementCollectionSameSize . firstIndex := self firstIndex . secondIndex := self secondIndex . result := collection copy. result replaceFrom: firstIndex to: secondIndex with: replacementCollection . "verify content of 'result' : " "first part of 'result'' : '" 1 to: ( firstIndex - 1 ) do: [ :i | self assert: (collection at:i ) = ( result at: i ) ]. " middle part containing replacementCollection : " ( firstIndex ) to: ( firstIndex + replacementCollection size - 1 ) do: [ :i | self assert: ( result at: i ) = ( replacementCollection at: ( i - firstIndex +1 ) ) ]. " end part :" ( firstIndex + replacementCollection size) to: (result size) do: [:i| self assert: ( result at: i ) = ( collection at: ( secondIndex + 1 - ( firstIndex + replacementCollection size ) + i ) ) ]. ! ! !FloatArrayTest methodsFor: 'tests - replacing'! testReplaceFromToWithStartingAt | result repStart collection replacementCollection firstIndex secondIndex | collection := self nonEmpty . result := collection copy. replacementCollection := self replacementCollectionSameSize . firstIndex := self firstIndex . secondIndex := self secondIndex . repStart := replacementCollection size - ( secondIndex - firstIndex + 1 ) + 1. result replaceFrom: firstIndex to: secondIndex with: replacementCollection startingAt: repStart . "verify content of 'result' : " "first part of 'result'' : '" 1 to: ( firstIndex - 1 ) do: [ :i | self assert: ( collection at:i ) = ( result at: i ) ]. " middle part containing replacementCollection : " ( firstIndex ) to: ( replacementCollection size - repStart +1 ) do: [:i| self assert: (result at: i)=( replacementCollection at: ( repStart + ( i -firstIndex ) ) ) ]. " end part :" ( firstIndex + replacementCollection size ) to: ( result size ) do: [ :i | self assert: ( result at: i ) = ( collection at: ( secondIndex + 1 - ( firstIndex + replacementCollection size ) + i ) ) ].! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! containsAll: union of: one andOf: another self assert: (one allSatisfy: [:each | union includes: each]). self assert: (another allSatisfy: [:each | union includes: each])! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! numberOfSimilarElementsInIntersection ^ self collection occurrencesOf: self anotherElementOrAssociationIn! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! testDifference "Answer the set theoretic difference of two collections." "self debug: #testDifference" self assert: (self collection difference: self collection) isEmpty. self assert: (self empty difference: self collection) isEmpty. self assert: (self collection difference: self empty) = self collection ! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! testDifferenceWithNonNullIntersection "Answer the set theoretic difference of two collections." "self debug: #testDifferenceWithNonNullIntersection" " #(1 2 3) difference: #(2 4) -> #(1 3)" | res overlapping | overlapping := self collectionClass with: self anotherElementOrAssociationNotIn with: self anotherElementOrAssociationIn. res := self collection difference: overlapping. self deny: (res includes: self anotherElementOrAssociationIn). overlapping do: [ :each | self deny: (res includes: each) ]! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! testDifferenceWithSeparateCollection "Answer the set theoretic difference of two collections." "self debug: #testDifferenceWithSeparateCollection" | res separateCol | separateCol := self collectionClass with: self anotherElementOrAssociationNotIn. res := self collection difference: separateCol. self deny: (res includes: self anotherElementOrAssociationNotIn). self assert: res = self collection. res := separateCol difference: self collection. self deny: (res includes: self collection anyOne). self assert: res = separateCol! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! testIntersectionBasic "self debug: #testIntersectionBasic" | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). self deny: inter isEmpty. self assert: (inter includes: self anotherElementOrAssociationIn value)! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! testIntersectionEmpty "self debug: #testIntersectionEmpty" | inter | inter := self empty intersection: self empty. self assert: inter isEmpty. inter := self empty intersection: self collection . self assert: inter = self empty. ! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! testIntersectionItself "self debug: #testIntersectionItself" self assert: (self collection intersection: self collection) = self collection. ! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! testIntersectionTwoSimilarElementsInIntersection "self debug: #testIntersectionBasic" | inter | inter := self collection intersection: (self collectionClass with: self anotherElementOrAssociationIn). self assert: (self collection occurrencesOf: self anotherElementOrAssociationIn) = self numberOfSimilarElementsInIntersection. self assert: (inter includes: self anotherElementOrAssociationIn value)! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! testUnion "self debug: #testUnionOfEmpties" | union | union := self empty union: self nonEmpty. self containsAll: union of: self empty andOf: self nonEmpty. union := self nonEmpty union: self empty. self containsAll: union of: self empty andOf: self nonEmpty. union := self collection union: self nonEmpty. self containsAll: union of: self collection andOf: self nonEmpty.! ! !FloatArrayTest methodsFor: 'tests - set arithmetic'! testUnionOfEmpties "self debug: #testUnionOfEmpties" self assert: (self empty union: self empty) isEmpty. ! ! !FloatArrayTest methodsFor: 'tests - sorting'! testIsSorted self assert: [ self sortedInAscendingOrderCollection isSorted ]. self deny: [ self unsortedCollection isSorted ]! ! !FloatArrayTest methodsFor: 'tests - sorting'! testIsSortedBy self assert: (self sortedInAscendingOrderCollection isSortedBy: [:a :b | ab]). ! ! !FloatArrayTest methodsFor: 'tests - sorting'! testSort | result tmp | result := self unsortedCollection sort. tmp := result at: 1. result do: [:each | self assert: each>=tmp. tmp:= each. ].! ! !FloatArrayTest methodsFor: 'tests - sorting'! testSortUsingSortBlock | result tmp | result := self unsortedCollection sort: [:a :b | a>b]. tmp := result at: 1. result do: [:each | self assert: each<=tmp. tmp:= each. ].! ! !FloatArrayTest methodsFor: 'tests - subcollections access'! testAllButFirst "self debug: #testAllButFirst" | abf col | col := self moreThan3Elements. abf := col allButFirst. self deny: abf first = col first. self assert: abf size + 1 = col size! ! !FloatArrayTest methodsFor: 'tests - subcollections access'! testAllButFirstNElements "self debug: #testAllButFirst" | abf col | col := self moreThan3Elements. abf := col allButFirst: 2. 1 to: abf size do: [ :i | self assert: (abf at: i) = (col at: i + 2) ]. self assert: abf size + 2 = col size! ! !FloatArrayTest methodsFor: 'tests - subcollections access'! testAllButLast "self debug: #testAllButLast" | abf col | col := self moreThan3Elements. abf := col allButLast. self deny: abf last = col last. self assert: abf size + 1 = col size! ! !FloatArrayTest methodsFor: 'tests - subcollections access'! testAllButLastNElements "self debug: #testAllButFirst" | abf col | col := self moreThan3Elements. abf := col allButLast: 2. 1 to: abf size do: [ :i | self assert: (abf at: i) = (col at: i) ]. self assert: abf size + 2 = col size! ! !FloatArrayTest methodsFor: 'tests - subcollections access'! testFirstNElements "self debug: #testFirstNElements" | result | result := self moreThan3Elements first: self moreThan3Elements size - 1. 1 to: result size do: [ :i | self assert: (result at: i) = (self moreThan3Elements at: i) ]. self assert: result size = (self moreThan3Elements size - 1). self should: [ self moreThan3Elements first: self moreThan3Elements size + 1 ] raise: Error! ! !FloatArrayTest methodsFor: 'tests - subcollections access'! testLastNElements "self debug: #testLastNElements" | result | result := self moreThan3Elements last: self moreThan3Elements size - 1. 1 to: result size do: [ :i | self assert: (result at: i) = (self moreThan3Elements at: i + 1) ]. self assert: result size = (self moreThan3Elements size - 1). self should: [ self moreThan3Elements last: self moreThan3Elements size + 1 ] raise: Error! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FloatArrayTest class uses: TCreationWithTest classTrait + TSequencedStructuralEqualityTest classTrait + TSequencedConcatenationTest classTrait + TSetArithmetic classTrait + TAsStringCommaAndDelimiterSequenceableTest classTrait + TPrintOnSequencedTest classTrait + TEmptyTest classTrait + TBeginsEndsWith classTrait + TCloneTest classTrait + TConvertTest classTrait + TConvertAsSortedTest classTrait + TConvertAsSetForMultiplinessIdentityTest classTrait + TCopyPartOfSequenceable classTrait + TCopyPartOfSequenceableForMultipliness classTrait + TCopySequenceableSameContents classTrait + TCopySequenceableWithOrWithoutSpecificElements classTrait + TCopySequenceableWithReplacement classTrait + TCopyTest classTrait + TIncludesWithIdentityCheckTest classTrait + TIndexAccess classTrait + TIndexAccessForMultipliness classTrait + TIterateSequencedReadableTest classTrait + TPutTest classTrait + TPutBasicTest classTrait + TReplacementSequencedTest classTrait + TSequencedElementAccessTest classTrait + TSortTest classTrait + TSubCollectionAccess classTrait instanceVariableNames: ''! ClassTestCase subclass: #FloatTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Numbers'! !FloatTest commentStamp: 'fbs 3/8/2004 22:13' prior: 0! I provide a test suite for Float values. Examine my tests to see how Floats should behave, and see how to use them.! !FloatTest methodsFor: 'IEEE 754' stamp: 'nice 5/30/2006 02:34'! test32bitGradualUnderflow "method asIEEE32BitWord did not respect IEEE gradual underflow" | conv expected exponentPart | "IEEE 32 bits Float have 1 bit sign/8 bit exponent/23 bits of mantissa after leading 1 2r1.mmmmmmmmmmmmmmmmmmmmmmm * (2 raisedTo: 2reeeeeeee-127) * sign except when 2reeeeeeee isZero, which is a gradual underflow: 2r0.mmmmmmmmmmmmmmmmmmmmmmm * (2 raisedTo: 2r00000000-126) * sign and when 2reeeeeeee = 255, which is infinity if mantissa all zero or nan otherwise" "case 1: This example is the first gradual underflow case" conv := 2r0.11111111111111111111111e-126 asIEEE32BitWord. "expected float encoded as sign/exponent/mantissa (whithout leading 1 or 0)" exponentPart := 0. expected := exponentPart bitOr: 2r11111111111111111111111. self assert: expected = conv. "case 2: smallest number" conv := 2r0.00000000000000000000001e-126 asIEEE32BitWord. expected := exponentPart bitOr: 2r1. self assert: expected = conv. "case 3: round to nearest even also in underflow cases... here round to upper" conv := 2r0.000000000000000000000011e-126 asIEEE32BitWord. expected := exponentPart bitOr: 2r10. self assert: expected = conv. "case 4: round to nearest even also in underflow cases... here round to lower" conv := 2r0.000000000000000000000101e-126 asIEEE32BitWord. expected := exponentPart bitOr: 2r10. self assert: expected = conv. "case 5: round to nearest even also in underflow cases... here round to upper" conv := 2r0.0000000000000000000001011e-126 asIEEE32BitWord. expected := exponentPart bitOr: 2r11. self assert: expected = conv. ! ! !FloatTest methodsFor: 'IEEE 754' stamp: 'nice 5/30/2006 00:07'! test32bitRoundingMode "method asIEEE32BitWord did not respect IEEE default rounding mode" | conv expected exponentPart | "IEEE 32 bits Float have 1 bit sign/8 bit exponent/23 bits of mantissa after leading 1 2r1.mmmmmmmmmmmmmmmmmmmmmmm * (2 raisedTo: 2reeeeeeee-127) * sign except when 2reeeeeeee isZero, which is a gradual underflow: 2r0.mmmmmmmmmmmmmmmmmmmmmmm * (2 raisedTo: 2r00000000-127) * sign and when 2reeeeeeee = 255, which is infinity if mantissa all zero or nan otherwise" "This example has two extra bits in mantissa for testing rounding mode case 1: should obviously round to upper" conv := 2r1.0000000000000000000000111e25 asIEEE32BitWord. "expected float encoded as sign/exponent/mantissa (whithout leading 1)" exponentPart := 25+127 bitShift: 23. "127 is 2r01111111 or 16r7F" expected := exponentPart bitOr: 2r10. self assert: expected = conv. "case 2: exactly in the mid point of two 32 bit float: round toward nearest even (to upper)" conv := 2r1.0000000000000000000000110e25 asIEEE32BitWord. expected := exponentPart bitOr: 2r10. self assert: expected = conv. "case 3: exactly in the mid point of two 32 bit float: round toward nearest even (to lower)" conv := 2r1.0000000000000000000000010e25 asIEEE32BitWord. expected := exponentPart bitOr: 2r0. self assert: expected = conv. "case 4: obviously round to upper" conv := 2r1.0000000000000000000000011e25 asIEEE32BitWord. expected := exponentPart bitOr: 2r1. self assert: expected = conv. ! ! !FloatTest methodsFor: 'IEEE 754' stamp: 'al 6/22/2008 11:52'! testNaN5 self assert: ((Float nan asIEEE32BitWord printPaddedWith: $0 to: 32 base: 2) copyFrom: 2 to: 9) = '11111111'. self assert: (Float fromIEEE32Bit: (Integer readFrom: '01111111110000000000000000000000' readStream base: 2)) isNaN! ! !FloatTest methodsFor: 'NaN behavior' stamp: 'sd 6/5/2005 08:31'! testNaN1 "FloatTest new testNaN1" self assert: Float nan == Float nan. self deny: Float nan = Float nan. "a NaN is not equal to itself." ! ! !FloatTest methodsFor: 'NaN behavior' stamp: 'dtl 10/1/2004 18:26'! testNaN2 "Two NaN values are always considered to be different. On an little-endian machine (32 bit Intel), Float nan is 16rFFF80000 16r00000000. On a big-endian machine (PowerPC), Float nan is 16r7FF80000 16r00000000. Changing the bit pattern of the first word of a NaN produces another value that is still considered equal to NaN. This test should work on both little endian and big endian machines. However, it is not guaranteed to work on future 64 bit versions of Squeak, for which Float may have different internal representations." "FloatTest new testNaN2" | nan1 nan2 | nan1 := Float nan copy. nan2 := Float nan copy. "test two instances of NaN with the same bit pattern" self deny: nan1 = nan2. self deny: nan1 == nan2. self deny: nan1 = nan1. self assert: nan1 == nan1. "change the bit pattern of nan1" self assert: nan1 size == 2. self assert: (nan1 at: 2) = 0. nan1 at: 1 put: (nan1 at: 1) + 999. self assert: nan1 isNaN. self assert: nan2 isNaN. self deny: (nan1 at: 1) = (nan2 at: 1). "test two instances of NaN with different bit patterns" self deny: nan1 = nan2. self deny: nan1 == nan2. self deny: nan1 = nan1. self assert: nan1 == nan1 ! ! !FloatTest methodsFor: 'NaN behavior' stamp: 'sd 6/5/2005 08:32'! testNaN3 "FloatTest new testNaN3" | set item identitySet | set := Set new. set add: (item := Float nan). self deny: (set includes: item). identitySet := IdentitySet new. identitySet add: (item := Float nan). self assert: (identitySet includes: item). "as a NaN is not equal to itself, it can not be retrieved from a set" ! ! !FloatTest methodsFor: 'NaN behavior' stamp: 'sd 6/5/2005 08:32'! testNaN4 "FloatTest new testNaN4" | dict | dict := Dictionary new. dict at: Float nan put: #NaN. self deny: (dict includes: Float nan). "as a NaN is not equal to itself, it can not be retrieved when it is used as a dictionary key" ! ! !FloatTest methodsFor: 'NaN behavior' stamp: 'nice 3/14/2008 23:42'! testNaNisLiteral self deny: Float nan isLiteral description: 'there is no literal representation of NaN'! ! !FloatTest methodsFor: 'NaN behavior' stamp: 'GabrielOmarCotelli 5/23/2009 20:38'! testReciprocal self assert: 1.0 reciprocal = 1.0; assert: 2.0 reciprocal = 0.5; assert: -1.0 reciprocal = -1.0; assert: -2.0 reciprocal = -0.5. self should: [ 0.0 reciprocal ] raise: ZeroDivide! ! !FloatTest methodsFor: 'characterization' stamp: 'nice 6/11/2009 20:47'! testCharacterization "Test the largest finite representable floating point value" self assert: Float fmax successor = Float infinity. self assert: Float infinity predecessor = Float fmax. self assert: Float fmax negated predecessor = Float infinity negated. self assert: Float infinity negated successor = Float fmax negated. "Test the smallest positive representable floating point value" self assert: Float fmin predecessor = 0.0. self assert: 0.0 successor = Float fmin. self assert: Float fmin negated successor = 0.0. self assert: 0.0 predecessor = Float fmin negated. "Test the relative precision" self assert: Float one + Float epsilon > Float one. self assert: Float one + Float epsilon = Float one successor. self assert: Float one + (Float epsilon / Float radix) = Float one. "Test maximum and minimum exponent" self assert: Float fmax exponent = Float emax. self assert: Float fminNormalized exponent = Float emin. Float denormalized ifTrue: [ self assert: Float fminDenormalized exponent = (Float emin + 1 - Float precision)]. "Alternative tests for maximum and minimum" self assert: (Float radix - Float epsilon) * (Float radix raisedTo: Float emax) = Float fmax. self assert: Float epsilon * (Float radix raisedTo: Float emin) = Float fmin. "Test sucessors and predecessors" self assert: Float one predecessor successor = Float one. self assert: Float one successor predecessor = Float one. self assert: Float one negated predecessor successor = Float one negated. self assert: Float one negated successor predecessor = Float one negated. self assert: Float infinity successor = Float infinity. self assert: Float infinity negated predecessor = Float infinity negated. self assert: Float nan predecessor isNaN. self assert: Float nan successor isNaN. "SPECIFIC FOR IEEE 754 double precision - 64 bits" self assert: Float fmax hex = '7FEFFFFFFFFFFFFF'. self assert: Float fminDenormalized hex = '0000000000000001'. self assert: Float fminNormalized hex = '0010000000000000'. self assert: 0.0 hex = '0000000000000000'. self assert: Float negativeZero hex = '8000000000000000'. self assert: Float one hex = '3FF0000000000000'. self assert: Float infinity hex = '7FF0000000000000'. self assert: Float infinity negated hex = 'FFF0000000000000'.! ! !FloatTest methodsFor: 'infinity behavior' stamp: 'nice 7/14/2009 09:32'! testHugeIntegerCloseTo "This is a test for bug http://bugs.squeak.org/view.php?id=7368" "FloatTest new testHugeIntegerCloseTo" self deny: (1.0 closeTo: 200 factorial). self deny: (200 factorial closeTo: 1.0). self assert: (Float infinity closeTo: 200 factorial) = (200 factorial closeTo: Float infinity).! ! !FloatTest methodsFor: 'infinity behavior' stamp: 'sd 6/5/2005 08:30'! testInfinity1 "FloatTest new testInfinity1" | i1 i2 | i1 := 10000 exp. i2 := 1000000000 exp. self assert: i1 isInfinite & i2 isInfinite & (i1 = i2). "All infinities are equal. (This is a very substantial difference to NaN's, which are never equal." ! ! !FloatTest methodsFor: 'infinity behavior' stamp: 'sd 6/5/2005 08:30'! testInfinity2 "FloatTest new testInfinity2" | i1 i2 | i1 := 10000 exp. i2 := 1000000000 exp. i2 := 0 - i2. " this is entirely ok. You can compute with infinite values." self assert: i1 isInfinite & i2 isInfinite & i1 positive & i2 negative. self deny: i1 = i2. "All infinities are signed. Negative infinity is not equal to Infinity" ! ! !FloatTest methodsFor: 'infinity behavior' stamp: 'nice 10/17/2007 23:54'! testInfinityCloseTo "This is a test for bug http://bugs.squeak.org/view.php?id=6729:" "FloatTest new testInfinityCloseTo" self deny: (Float infinity closeTo: Float infinity negated). self deny: (Float infinity negated closeTo: Float infinity).! ! !FloatTest methodsFor: 'printing' stamp: 'nice 10/11/2008 21:45'! testStoreBase16 "This bug was reported in mantis http://bugs.squeak.org/view.php?id=6695" self assert: (20.0 storeStringBase: 16) = '16r14.0' description: 'the radix prefix should not be omitted, except in base 10'! ! !FloatTest methodsFor: 'testing - arithmetic' stamp: 'st 9/20/2004 17:04'! testContinuedFractions self assert: (Float pi asApproximateFractionAtOrder: 1) = (22/7). self assert: (Float pi asApproximateFractionAtOrder: 3) = (355/113)! ! !FloatTest methodsFor: 'testing - arithmetic' stamp: 'GabrielOmarCotelli 6/6/2009 17:14'! testDivide self assert: 1.5 / 2.0 = 0.75. self assert: 2.0 / 1 = 2.0. self should: [ 2.0 / 0 ] raise: ZeroDivide. self should: [ 2.0 / 0.0 ] raise: ZeroDivide. self should: [ 1.2 / Float negativeZero ] raise: ZeroDivide. self should: [ 1.2 / (1.3 - 1.3) ] raise: ZeroDivide ! ! !FloatTest methodsFor: 'testing - arithmetic' stamp: 'nice 12/1/2007 17:59'! testRaisedTo "this is a test related to http://bugs.squeak.org/view.php?id=6781" self should: [0.0 raisedTo: -1] raise: ZeroDivide. self should: [0.0 raisedTo: -1.0] raise: ZeroDivide.! ! !FloatTest methodsFor: 'testing - conversion' stamp: 'nice 7/24/2008 02:04'! testFloatRounded "5000000000000001 asFloat has an exact representation (no round off error). It should round to nearest integer without loosing bits. This is a no regression test on http://bugs.squeak.org/view.php?id=7134" | x y int r | "This is a preamble asserting exactness of representation and quality of various conversions" int := 5000000000000001. x := int asFloat. y := (5 asFloat squared squared squared squared timesTwoPower: 15) + 1. self assert: x = y. self assert: x asTrueFraction = int. "this one should be true for any float in order to conform to ISO/IEC 10967-2" self assert: x rounded = x asTrueFraction rounded. self assert: x negated rounded = x negated asTrueFraction rounded. "a random test" r := Random new. 10000 timesRepeat: [ x := r next * 1.9999e16 + 1.0e12 . self assert: x rounded = x asTrueFraction rounded. self assert: x negated rounded = x negated asTrueFraction rounded]! ! !FloatTest methodsFor: 'testing - conversion' stamp: 'nice 4/26/2006 05:21'! testFloatTruncated "(10 raisedTo: 16) asFloat has an exact representation (no round off error). It should convert back to integer without loosing bits. This is a no regression test on http://bugs.impara.de/view.php?id=3504" | x y int r | int := 10 raisedTo: 16. x := int asFloat. y := (5 raisedTo: 16) asFloat timesTwoPower: 16. self assert: x = y. self assert: x asInteger = int. "this one should be true for any float" self assert: x asInteger = x asTrueFraction asInteger. "a random test" r := Random new. 10000 timesRepeat: [ x := r next * 1.9999e16 + 1.0e12 . self assert: x truncated = x asTrueFraction truncated]! ! !FloatTest methodsFor: 'testing - conversion' stamp: 'nice 5/7/2006 16:22'! testFractionAsFloat "use a random test" | r m frac err collec | r := Random new seed: 1234567. m := (2 raisedTo: 54) - 1. 200 timesRepeat: [ frac := ((r nextInt: m) * (r nextInt: m) + 1) / ((r nextInt: m) * (r nextInt: m) + 1). err := (frac - frac asFloat asTrueFraction) * frac reciprocal * (1 bitShift: 52). self assert: err < (1/2)]. collec := #(16r10000000000000 16r1FFFFFFFFFFFFF 1 2 16r20000000000000 16r20000000000001 16r3FFFFFFFFFFFFF 16r3FFFFFFFFFFFFE 16r3FFFFFFFFFFFFD). collec do: [:num | collec do: [:den | frac := Fraction numerator: num denominator: den. err := (frac - frac asFloat asTrueFraction) * frac reciprocal * (1 bitShift: 52). self assert: err <= (1/2)]].! ! !FloatTest methodsFor: 'testing - conversion' stamp: 'nice 1/10/2007 02:29'! testFractionAsFloat2 "test rounding to nearest even" self assert: ((1<<52)+0+(1/4)) asFloat asTrueFraction = ((1<<52)+0). self assert: ((1<<52)+0+(1/2)) asFloat asTrueFraction = ((1<<52)+0). self assert: ((1<<52)+0+(3/4)) asFloat asTrueFraction = ((1<<52)+1). self assert: ((1<<52)+1+(1/4)) asFloat asTrueFraction = ((1<<52)+1). self assert: ((1<<52)+1+(1/2)) asFloat asTrueFraction = ((1<<52)+2). self assert: ((1<<52)+1+(3/4)) asFloat asTrueFraction = ((1<<52)+2).! ! !FloatTest methodsFor: 'testing - conversion' stamp: 'nice 5/6/2006 22:13'! testIntegerAsFloat "assert IEEE 754 round to nearest even mode is honoured" self deny: 16r1FFFFFFFFFFFF0801 asFloat = 16r1FFFFFFFFFFFF0800 asFloat. "this test is on 65 bits" self deny: 16r1FFFFFFFFFFFF0802 asFloat = 16r1FFFFFFFFFFFF0800 asFloat. "this test is on 64 bits" self assert: 16r1FFFFFFFFFFF1F800 asFloat = 16r1FFFFFFFFFFF20000 asFloat. "nearest even is upper" self assert: 16r1FFFFFFFFFFFF0800 asFloat = 16r1FFFFFFFFFFFF0000 asFloat. "nearest even is lower" ! ! !FloatTest methodsFor: 'testing - conversion' stamp: 'nice 3/14/2008 23:59'! testReadFromManyDigits "A naive algorithm may interpret these representations as Infinity or NaN. This is http://bugs.squeak.org/view.php?id=6982" | s1 s2 | s1 := '1' , (String new: 321 withAll: $0) , '.0e-321'. s2 := '0.' , (String new: 320 withAll: $0) , '1e321'. self assert: (Number readFrom: s1) = 1. self assert: (Number readFrom: s2) = 1.! ! !FloatTest methodsFor: 'testing - conversion' stamp: 'dtl 9/18/2004 12:40'! testStringAsNumber "This covers parsing in Number>>readFrom:" | aFloat | aFloat := '10r-12.3456' asNumber. self assert: -12.3456 = aFloat. aFloat := '10r-12.3456e2' asNumber. self assert: -1234.56 = aFloat. aFloat := '10r-12.3456d2' asNumber. self assert: -1234.56 = aFloat. aFloat := '10r-12.3456q2' asNumber. self assert: -1234.56 = aFloat. aFloat := '-12.3456q2' asNumber. self assert: -1234.56 = aFloat. aFloat := '12.3456q2' asNumber. self assert: 1234.56 = aFloat. ! ! !FloatTest methodsFor: 'testing compare' stamp: 'nice 7/19/2009 19:24'! testCloseTo self deny: (Float nan closeTo: Float nan) description: 'NaN isn''t close to anything'. self deny: (Float nan closeTo: 1.0) description: 'NaN isn''t close to anything'. self deny: (1.0 closeTo: Float nan) description: 'NaN isn''t close to anything'. self deny: (-1.0 closeTo: 1.0). self deny: (1.0 closeTo: Float infinity). self assert: (Float infinity closeTo: Float infinity) description: 'since they are =, they also are closeTo:'. self assert: (1.0/3.0 closeTo: 1/3). self assert: (1.0e-8 closeTo: 0). self assert: (0 closeTo: 1.0e-8). self assert: (1+1.0e-8 closeTo: 1.0). self assert: (1000000001.0 closeTo: 1000000000.0). self deny: (1000000001 closeTo: 1000000000) description: 'exact representation are considered closeTo: only if equal'.! ! !FloatTest methodsFor: 'testing compare' stamp: 'nice 5/30/2008 01:23'! testComparison "test equality when Float conversion loose bits" | a b c | a := 16r1FFFFFFFFFFFFF1. b := 16r1FFFFFFFFFFFFF3. c := a asFloat. self assert: ((a = c) & (b = c)) ==> (a = b). "Test equality when Float conversion exact" self assert: 16r1FFFFFFFFFFFFF = 16r1FFFFFFFFFFFFF asFloat. self assert: 16r1FFFFFFFFFFFFF = 16r1FFFFFFFFFFFFF asFloat asInteger. "Test inequality when Float conversion loose bits" self assert: (((1 bitShift: 54)+1)/(1 bitShift: 54)) > 1. self assert: (((1 bitShift: 54)+1)/(1 bitShift: 54)) > 1.0. self assert: (((1 bitShift: 54)-1)/(1 bitShift: 54)) < 1. self assert: (((1 bitShift: 54)-1)/(1 bitShift: 54)) < 1.0. "Test exact vs inexact arithmetic" (1 to: 100) do: [:i | i isPowerOfTwo ifTrue: [self assert: (1/i) = (1/i) asFloat] ifFalse: [self deny: (1/i) = (1/i) asFloat]]. "Test overflow (compare to infinity)" a := (11 raisedTo: 400) / 2. b := (13 raisedTo: 400) / 2. c := a asFloat. self assert: ((a = c) & (b = c)) ==> (a = b). "every integer is smaller than infinity" self assert: a < Float infinity. self assert: a > Float infinity negated. "Test underflow" self deny: 1 / (11 raisedTo: 400) = 0. self deny: 1 / (11 raisedTo: 400) = 0.0. "Test hash code" self assert: ((Set new: 3) add: 3; add: 3.0; size) = ((Set new: 4) add: 3; add: 3.0; size).! ! !FloatTest methodsFor: 'testing compare' stamp: 'nice 7/10/2009 22:27'! testComparisonWhenPrimitiveFails "This is related to http://bugs.squeak.org/view.php?id=7361" self deny: 0.5 < (1/4). self deny: 0.5 < (1/2). self assert: 0.5 < (3/4). self deny: 0.5 <= (1/4). self assert: 0.5 <= (1/2). self assert: 0.5 <= (3/4). self assert: 0.5 > (1/4). self deny: 0.5 > (1/2). self deny: 0.5 > (3/4). self assert: 0.5 >= (1/4). self assert: 0.5 >= (1/2). self deny: 0.5 >= (3/4). self deny: 0.5 = (1/4). self assert: 0.5 = (1/2). self deny: 0.5 = (3/4). self assert: 0.5 ~= (1/4). self deny: 0.5 ~= (1/2). self assert: 0.5 ~= (3/4).! ! !FloatTest methodsFor: 'tests' stamp: 'nice 6/11/2009 01:36'! testHash self assert: (2 = 2.0) ==> (2 hash = 2.0 hash). self assert: (1/2 = 0.5) ==> ((1/2) hash = 0.5 hash). self shouldnt: [Float nan hash] raise: Error. self shouldnt: [Float infinity hash] raise: Error.! ! !FloatTest methodsFor: 'zero behavior' stamp: 'md 4/16/2003 15:02'! testIsZero self assert: 0.0 isZero. self deny: 0.1 isZero.! ! !FloatTest methodsFor: 'zero behavior' stamp: 'sd 6/5/2005 08:33'! testZero1 "FloatTest new testZero1" self assert: Float negativeZero = 0 asFloat. self assert: (Float negativeZero at: 1) ~= (0 asFloat at: 1). "The negative zero has a bit representation that is different from the bit representation of the positive zero. Nevertheless, both values are defined to be equal." ! ! !FloatTest methodsFor: 'zero behavior' stamp: 'nice 3/23/2008 16:00'! testZeroSignificandAsInteger "This is about http://bugs.squeak.org/view.php?id=6990" self assert: 0.0 significandAsInteger = 0! ! ArithmeticError subclass: #FloatingPointException instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Exceptions-Kernel'! Model subclass: #FontChooser instanceVariableNames: 'title selectedFontIndex fontList fontListStrings target getSelector setSelector pointSize fontStyleList selectedFontStyleIndex weightValue slantValue stretchValue pointSizeList' classVariableNames: '' poolDictionaries: '' category: 'FreeType-UI'! !FontChooser methodsFor: 'accessing' stamp: 'tween 8/4/2007 13:44'! getSelector "Answer the value of getSelector" ^ getSelector! ! !FontChooser methodsFor: 'accessing' stamp: 'tween 8/4/2007 20:16'! getSelector: aSelectorSymbolOrFont "Set the value of getSelector" getSelector := aSelectorSymbolOrFont! ! !FontChooser methodsFor: 'accessing' stamp: 'tween 8/4/2007 13:44'! setSelector: anObject "Set the value of setSelector" setSelector := anObject! ! !FontChooser methodsFor: 'accessing' stamp: 'tween 8/4/2007 13:44'! target "Answer the value of target" ^ target! ! !FontChooser methodsFor: 'accessing' stamp: 'tween 8/4/2007 13:44'! target: anObject "Set the value of target" target := anObject! ! !FontChooser methodsFor: 'accessing' stamp: 'tween 8/4/2007 13:44'! title: anObject "Set the value of title" title := anObject! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 13:46'! apply | font | target ifNotNil:[ setSelector ifNotNil:[ font := self selectedFont. font ifNotNil:[ target perform: setSelector with: font]]].! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 10:35'! categoryList ^OrderedCollection new "add: self allCategoryLabel; addAll: preferences categoryNames asSortedCollection; add: self searchResultsCategoryLabel;" addAll: (TextStyle actualTextStyles keysSortedSafely); yourself.! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 9/8/2007 15:14'! fontList fontList ifNotNil:[^fontList]. ^fontList := LogicalFontManager current allFamilies! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/16/2007 22:30'! fontListStrings ^fontListStrings ifNil:[ fontListStrings := self fontList collect:[:each | each familyName]]! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/19/2007 16:22'! fontStyleList | family | family := self selectedFontFamily. family ifNotNil:[^fontStyleList := family members asSortedCollection]. ^#()! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/17/2007 00:15'! fontStyleListStrings "names of simulated styles are enclosed in parenthesis" ^self fontStyleList collect: [:fontFamilyMember | | s | s := fontFamilyMember styleName. fontFamilyMember simulated ifTrue:[s := '(', s, ')']. s]! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 10:27'! initialize super initialize. title := 'Choose A Font'.! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 15:23'! pointSize ^pointSize ifNil: [pointSize := 10.0]! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 17:34'! pointSize: aNumber pointSize := aNumber. self changed: #pointSize! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 23:50'! pointSizeList ^pointSizeList ifNil:[ pointSizeList := (1 to: 256) collect: [:each | each asString padded: #left to: 3 with: $ ]]! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/18/2007 11:18'! selectedFont | font style | font := self unemphasizedSelectedFont. font ifNil:[^nil]. style := self fontStyleList at: self selectedFontStyleIndex ifAbsent:[nil]. style ifNil:[^nil]. (style isKindOf: TextStyleAsFontFamilyMember) ifTrue:[ ^font emphasized: style emphasisCode]. ^LogicalFont familyName: font familyName pointSize: pointSize stretchValue: style stretchValue weightValue: style weightValue slantValue: style slantValue ! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/16/2007 22:42'! selectedFontFamily | | ^self fontList at: self selectedFontIndex ifAbsent:[nil]. ! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/28/2007 00:20'! selectedFontIndex | font textStyleName family | selectedFontIndex ifNotNil: [^selectedFontIndex]. selectedFontIndex := 0. font := (getSelector isSymbol and:[target notNil]) ifTrue:[target perform: getSelector] ifFalse:[getSelector]. self setStyleValuesFrom: font. (font isKindOf: AbstractFont) ifTrue:[ pointSize := font pointSize. textStyleName := font textStyleName. family := self fontList detect:[:f | f familyName = textStyleName] ifNone:[]. selectedFontIndex := self fontList indexOf: family ifAbsent:[0]]. self selectedFontIndex: selectedFontIndex. ^selectedFontIndex! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/28/2007 00:11'! selectedFontIndex: anIndex | family member newStyleIndex | anIndex = 0 ifTrue: [^self]. selectedFontIndex := anIndex. "change the selected style to be the closest to the last user selected weight slant and stretch values. By user selected I mean that the user changed the style list selection, rather than a change being forced because a particular family didn't have that style" family := self fontList at: selectedFontIndex. member := family closestMemberWithStretchValue: stretchValue weightValue: weightValue slantValue: slantValue. newStyleIndex := self fontStyleList indexOf: member. selectedFontStyleIndex := newStyleIndex. self setPointSizeListFrom: member. self changed: #selectedFontIndex. self changed: #selectedFontStyleIndex.! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/19/2007 16:23'! selectedFontStyleIndex | family member | selectedFontStyleIndex ifNotNil: [ ^selectedFontStyleIndex := selectedFontStyleIndex min: self fontStyleList size]. family := self fontList at: selectedFontIndex ifAbsent:[^0]. member := family closestMemberWithStretchValue: stretchValue weightValue: weightValue slantValue: slantValue. selectedFontStyleIndex := self fontStyleList indexOf: member. ^selectedFontStyleIndex! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/18/2007 12:07'! selectedFontStyleIndex: anIndex | familyMember | anIndex = 0 ifTrue: [^self]. selectedFontStyleIndex := anIndex. familyMember := self fontStyleList at: anIndex. self setStyleValuesFrom: familyMember. self changed: #selectedFontStyleIndex! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 23:12'! selectedPointSize ^self selectedFont pointSize! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/28/2007 00:08'! selectedPointSizeIndex ^self pointSizeList indexOf: (pointSize reduce asString padded: #left to: 3 with: $ )! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/28/2007 00:06'! selectedPointSizeIndex: anIndex anIndex = 0 ifTrue: [^self]. pointSize := (self pointSizeList at: anIndex) withBlanksTrimmed asNumber. self changed: #pointSize! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/28/2007 00:12'! setPointSizeListFrom: aFontFamilyMember | style old new | old := pointSizeList. (aFontFamilyMember isKindOf: FontFamilyMemberAbstract) ifTrue:[ style := TextStyle named: aFontFamilyMember family familyName. style ifNotNil:[ new := style pointSizes collect: [:each | each reduce asString padded: #left to: 3 with: $ ]]]. new ifNil:[new := (1 to: 256) collect: [:each | each asString padded: #left to: 3 with: $ ]]. pointSizeList := new. old ~= new ifTrue:[self changed: #pointSizeList]! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/18/2007 13:49'! setStyleValuesFrom: aFont ((aFont isKindOf: LogicalFont) or:[aFont isKindOf: FontFamilyMemberAbstract]) ifTrue:[ weightValue := aFont weightValue. slantValue := aFont slantValue. stretchValue := aFont stretchValue] ifFalse:[ weightValue := (aFont emphasis bitAnd: 1) > 0 ifTrue:[700] ifFalse:[400]. slantValue := (aFont emphasis bitAnd: 2) > 0 ifTrue:[1] ifFalse:[0]. stretchValue := 5 "normal"]! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/18/2007 21:10'! unemphasizedSelectedFont |name font family | family := self fontList at: self selectedFontIndex ifAbsent:[nil]. family ifNil:[^nil]. (family isKindOf: TextStyleAsFontFamily) ifTrue:[^family textStyle fontOfPointSize: pointSize]. name := family familyName. font := LogicalFont familyName: name pointSize: pointSize stretchValue: 5 weightValue: 400 slantValue: 0. font realFont isTTCFont "true for FreeTypeFont" ifFalse: [font := font textStyle fontOfPointSize: pointSize]. ^font ! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'RobRothwell 12/15/2008 22:54'! updateFontList FreeTypeFontProvider current updateFromSystem.! ! !FontChooser methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 10:27'! windowTitle ^ title translated! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FontChooser class instanceVariableNames: ''! !FontChooser class methodsFor: 'as yet unclassified' stamp: 'tween 2/10/2008 11:13'! open " FontChooser open. " | instance morph | instance := self new. (morph := FontChooserMorph withModel: instance) openInWorld. ^morph! ! !FontChooser class methodsFor: 'as yet unclassified' stamp: 'RobRothwell 12/15/2008 23:21'! openWithWindowTitle: titleString for: anObject setSelector: setSelector getSelector: getSelector " FontChooser openWithWindowTitle: 'Choose the Menu Font' for: Preferences setSelector: #setMenuFontTo: getSelector: #standardMenuFont " | instance windowMorph world | instance := self new. instance title: titleString; target: anObject; setSelector: setSelector; getSelector: getSelector. world := self currentWorld. (windowMorph := FontChooserMorph withModel: instance) "position: self currentWorld primaryHand position;" position: ((World width-640)/2)@((World height-480)/2); extent: 640@480; openAsMorph. ^windowMorph " [windowMorph model notNil] whileTrue: [ world doOneCycle]. self halt. ^windowMorph result"! ! !FontChooser class methodsFor: 'as yet unclassified' stamp: 'tween 3/2/2008 10:43'! windowTitle: titleString for: anObject setSelector: setSelector getSelector: getSelector | instance answer | instance := self new. instance title: titleString; target: anObject; setSelector: setSelector; getSelector: getSelector. (answer := FontChooserMorph withModel: instance) position: self currentWorld primaryHand position; extent: 450@220; createWindow. ^answer! ! SystemWindow subclass: #FontChooserMorph instanceVariableNames: 'mainPanel fontPreviewPanel okButton cancelButton applyButton updateButton result pointSizeMorph pointSizeSlider fontListStylePanel styleList pointSizeList' classVariableNames: '' poolDictionaries: '' category: 'FreeType-UI'! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 20:28'! apply result := model selectedFont. model apply! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 13:49'! applyButton ^applyButton ifNil: [ applyButton := self basicButton label: ' Apply ' translated; target:self; actionSelector: #applyButtonClicked; setBalloonText: 'Click here to apply your selection without closing this dialog' translated]! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 13:49'! applyButtonClicked self apply. ! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 16:46'! basicButton | button | button := SimpleButtonMorph new. button borderWidth: 2; borderColor: #raised; on: #mouseEnter send: #value to: [button borderColor: self paneColor]; on: #mouseLeave send: #value to: [button borderColor: #raised]; "vResizing: #shrinkWrap;" useRoundedCorners; clipSubmorphs: true; color: self paneColor lighter; target: self model. ^button ! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 13:31'! cancelButton ^cancelButton ifNil: [ cancelButton := self basicButton label: ' Cancel ' translated; target:self; actionSelector: #cancelButtonClicked; setBalloonText: 'Click here to cancel and close this dialog' translated]! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 20:27'! cancelButtonClicked result :=nil. self delete ! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'RobRothwell 12/15/2008 23:11'! createWindow "Create the package loader window." | buttonBarHeight b | buttonBarHeight := Preferences standardDefaultTextFont height + 22. self addMorph: (self newFontList borderWidth: 0) frame: (0.0 @ 0.0 corner: 0.5 @ 0.4) . self addMorph: ((styleList := self newFontStyleList) borderWidth: 0) frame: (0.5 @ 0.0 corner: 0.9 @ 0.4). self addMorph: (pointSizeList := self newPointSizeList borderWidth:0) frame: (0.9 @ 0.0 corner: 1.0 @ 0.4). self addMorph: (self fontPreviewPanel borderWidth: 0) fullFrame: (LayoutFrame fractions: (0@0.4 corner: 1.0@1.0) offsets: (0@0 corner: 0@buttonBarHeight negated)). self addMorph: (applyButton:=self applyButton) fullFrame: (LayoutFrame fractions: (0@1.0 corner: 0.25@1.0) offsets: (10@(buttonBarHeight negated + 2) corner: -10@-4)). applyButton color: self paneColor darker. self addMorph: (okButton :=self okButton) fullFrame: (LayoutFrame fractions: (0.25@1.0 corner: 0.50@1.0) offsets: (10@(buttonBarHeight negated + 2) corner: -10@-4)). okButton color: self paneColor darker. self addMorph: (cancelButton :=self cancelButton) fullFrame: (LayoutFrame fractions: (0.50@1.0 corner: 0.75@1.0) offsets: (10@(buttonBarHeight negated + 2) corner: -10@-4)). cancelButton color: self paneColor darker. self addMorph: (updateButton:=self updateButton) fullFrame: (LayoutFrame fractions: (0.75@1.0 corner: 1.0@1.0) offsets: (10@(buttonBarHeight negated + 2) corner: -10@-4)). updateButton color: self paneColor darker. self addMorph: (b :=Morph new) fullFrame: (LayoutFrame fractions: (0@1.0 corner: 1.0@1.0) offsets: (4@buttonBarHeight negated - 4 corner: 0@0)). b color: self paneColor lighter. updateButton comeToFront. " applyButton comeToFront." okButton comeToFront. cancelButton comeToFront. self on: #mouseEnter send: #paneTransition: to: self. self on: #mouseLeave send: #paneTransition: to: self! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 20:25'! delete model := nil. super delete ! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 11:24'! fontPreviewPanel ^fontPreviewPanel ifNil: [fontPreviewPanel := ScrollPane new color: Color white; borderInset; vResizing: #spaceFill; hResizing: #spaceFill. fontPreviewPanel scroller on: #mouseEnter send: #value: to: [:event | event hand newKeyboardFocus: fontPreviewPanel scroller]; on: #keyStroke send: #keyPressed: to: self. fontPreviewPanel.]! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 3/2/2008 19:16'! initializeLabelArea super initializeLabelArea. collapseBox hide. " need to keep collapseBox for title bar to display correctly?" expandBox delete. menuBox delete. expandBox := nil. collapseBox := nil.! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 23:29'! initializeWithModel: aFontChooser self model: aFontChooser; clipSubmorphs: true; setLabel: self model windowTitle; name: 'FontChooser'. self updatePreview! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 13:43'! newFontList | answer fon max | answer := PluggableListMorph on: self model list: #fontListStrings selected: #selectedFontIndex changeSelected: #selectedFontIndex:. fon := answer font. max := 20. model fontList do:[:each | max := max max: (fon widthOfStringOrText: each familyName)]. answer color: Color white; borderInset; vResizing: #spaceFill; hResizing: #spaceFill; "hResizing: #rigid;" width: max + answer scrollBarThickness + (fon widthOfStringOrText: ' '); yourself. ^answer! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 13:13'! newFontPointSizeField | answer | answer := (PluggableTextMorph on: self text: #pointSizeString accept: #pointSizeString:) acceptOnCR: true; hideVScrollBarIndefinitely: true; color: Color gray veryMuchLighter; borderColor: #inset; vResizing: #rigid; hResizing: #spaceFill; width: (TextStyle defaultFont widthOfString: '99999999.99'); height: TextStyle defaultFont height + 6; "wrapFlag: true;" "autoFit: false;" "margins: 2@2;" "borderWidth: 1;" "contents: model pointSize asString;" yourself. ^answer! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 13:14'! newFontPointSizeLabel ^StringMorph contents: 'Point size:' translated.! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'PeterHugossonMiller 9/3/2009 01:33'! newFontPreviewInnerPanel | sample i c f | sample := String new writeStream. f := model selectedFont. f isNil ifTrue:[^TextMorph new contents:''; yourself]. f isSymbolFont ifFalse:[ sample nextPutAll: 'the quick brown fox jumps over the lazy dog' ;cr; nextPutAll: 'THE QUICK BROWN FOX JUMPS OVER THE LAZY DOG.' ;cr]. i := 0. 33 to: 255 do:[:ci | sample nextPut: (c:=Character value: ci). i := i + 1. (('@Z`z' includes:c) or:[i = 30]) ifTrue:[i :=0. sample cr]]. sample := sample contents asText. "(f weightValue >= 700) ifTrue:[sample addAttribute: TextEmphasis bold]. (f slantValue ~= 0) ifTrue:[sample addAttribute: TextEmphasis italic]." ^TextMorph new contents: sample; beAllFont: f; yourself! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 13:13'! newFontSizePanel ^Morph new borderWidth: 1; borderColor: Color black; hResizing: #spaceFill; vResizing: #shrinkwrap; color: Color transparent; layoutPolicy: TableLayout new; cellInset: 0; listCentering: #topLeft; listDirection: #leftToRight; cellPositioning: #leftCenter; clipSubmorphs: true; "addMorphBack: self newFontEmphasisBoldButton; addMorphBack: self newFontEmphasisItalicButton;" addMorphBack: self newFontPointSizeLabel; addMorphBack: (pointSizeMorph := self newFontPointSizeField) ! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 13:42'! newFontStyleList | answer fon max | answer := PluggableListMorph on: self model list: #fontStyleListStrings selected: #selectedFontStyleIndex changeSelected: #selectedFontStyleIndex:. fon := answer font. max := fon widthOfStringOrText: 'Condensed Extra Bold Oblique' "long, but not the longest". model fontStyleList do:[:fontFamilyMember | max := max max: (fon widthOfStringOrText: fontFamilyMember styleName)]. answer color: Color white; borderInset; vResizing: #spaceFill; hResizing: #spaceFill; "hResizing: #rigid;" width: max + answer scrollBarThickness + (fon widthOfStringOrText: ' '); yourself. ^answer! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 23:22'! newPointSizeList | answer | answer := PluggableListMorph on: self model list: #pointSizeList selected: #selectedPointSizeIndex changeSelected: #selectedPointSizeIndex:. answer color: Color white; borderInset; vResizing: #spaceFill; hResizing: #spaceFill; yourself. ^answer! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 13:22'! newSeparator ^BorderedMorph new borderWidth: 2; borderColor: Color transparent; color: self paneColor; hResizing: #rigid; width: 5; vResizing: #spaceFill; yourself! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 13:31'! okButton ^okButton ifNil: [ okButton := self basicButton label: ' OK ' translated; target:self; actionSelector: #okButtonClicked; setBalloonText: 'Click here to close this dialog, and accept your selection' translated]! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 13:37'! okButtonClicked self apply. self delete ! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 17:19'! openAsMorph ^self createWindow openAsIsIn: self currentWorld! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 22:58'! paneColor ^Color blue muchLighter! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 22:47'! pointSizeSlider: aNumber (aNumber < 1 or:[ aNumber > 1024]) ifTrue:[^self]. pointSizeMorph ifNotNil:[ pointSizeMorph setText: aNumber asString asText; hasUnacceptedEdits: false]. model pointSize: aNumber! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 17:33'! pointSizeString ^model pointSize asString! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 22:27'! pointSizeString: aText | s n| s := aText asString withBlanksTrimmed. s isEmpty ifTrue:[^self]. (s detect:[:c | c isDigit not and:[c ~= $.]] ifNone:[]) ifNotNil:[^self]. [n := s asNumber asFloat] on: Error do:[:e | ^self]. (n < 1 or:[ n > 1024]) ifTrue:[^self]. pointSizeMorph ifNotNil:[pointSizeMorph hasUnacceptedEdits: false]. model pointSize: n! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 3/2/2008 19:16'! replaceBoxes super replaceBoxes. collapseBox hide. " need to keep collapseBox for title bar to display correctly?" ! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 20:28'! result ^result! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/28/2007 00:02'! update: aSymbol super update: aSymbol. aSymbol == #selectedFontIndex ifTrue: [ styleList ifNotNil:[styleList updateList]. pointSizeList ifNotNil:[pointSizeList updateList]. self updatePreview]. aSymbol == #selectedFontStyleIndex ifTrue: [ self updatePreview]. aSymbol == #pointSize ifTrue: [ pointSizeList ifNotNil:[pointSizeList selectionIndex: model selectedPointSizeIndex]. self updatePreview]. aSymbol == #pointSizeList ifTrue: [ pointSizeList ifNotNil:[pointSizeList updateList]. self updatePreview].! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'RobRothwell 12/15/2008 22:57'! updateButton ^updateButton ifNil: [ updateButton := self basicButton label: ' Update ' translated; target:self; actionSelector: #updateButtonClicked; setBalloonText: 'Click here to rescan Font Folder and update the font list' translated]! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'RobRothwell 12/15/2008 23:01'! updateButtonClicked self updateFontList. ! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'RobRothwell 12/15/2008 22:55'! updateFontList model updateFontList! ! !FontChooserMorph methodsFor: 'as yet unclassified' stamp: 'tween 8/27/2007 23:26'! updatePreview Cursor wait showWhile: [ self fontPreviewPanel hScrollBarValue: 0; vScrollBarValue: 0. self fontPreviewPanel scroller removeAllMorphs. self fontPreviewPanel scroller addMorphBack: self newFontPreviewInnerPanel]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FontChooserMorph class instanceVariableNames: ''! !FontChooserMorph class methodsFor: 'as yet unclassified' stamp: 'tween 8/4/2007 10:24'! withModel: aFontChooser ^self new initializeWithModel: aFontChooser; yourself.! ! Object subclass: #FontFamilyAbstract instanceVariableNames: 'familyName members' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FontFamilyAbstract methodsFor: 'accessing' stamp: 'tween 8/18/2007 13:46'! familyName "Answer the value of familyName" ^ familyName! ! !FontFamilyAbstract methodsFor: 'accessing' stamp: 'tween 8/18/2007 13:46'! familyName: anObject "Set the value of familyName" familyName := anObject! ! !FontFamilyAbstract methodsFor: 'accessing' stamp: 'tween 8/18/2007 13:47'! members "Answer the value of members" ^ members! ! !FontFamilyAbstract methodsFor: 'member lookup' stamp: 'tween 8/18/2007 13:50'! closestMemberWithStretchValue: stretchValue weightValue: weightValue slantValue: slantValue "answer the member that has weight, slant and stretch values that most closely match those given by stretchValue, weightValue, and slantValue" ^(self members asSortedCollection:[:a :b | a isCloserMatchThan: b toStretch: stretchValue weight: weightValue slant: slantValue]) first. ! ! !FontFamilyAbstract methodsFor: 'printing' stamp: 'tween 9/7/2007 19:36'! printOn: aStream aStream nextPutAll: self class name asString; nextPut: $ ; nextPutAll: self familyName printString! ! Object subclass: #FontFamilyMemberAbstract instanceVariableNames: 'family styleName' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FontFamilyMemberAbstract methodsFor: 'accessing' stamp: 'tween 8/25/2007 14:22'! family ^family! ! !FontFamilyMemberAbstract methodsFor: 'accessing' stamp: 'tween 8/25/2007 14:22'! family: aFontFamily family := aFontFamily! ! !FontFamilyMemberAbstract methodsFor: 'accessing' stamp: 'tween 9/8/2007 13:24'! slantValue self subclassResponsibility! ! !FontFamilyMemberAbstract methodsFor: 'accessing' stamp: 'tween 9/8/2007 13:24'! stretchValue self subclassResponsibility! ! !FontFamilyMemberAbstract methodsFor: 'accessing' stamp: 'tween 8/18/2007 13:41'! styleName "Answer the value of styleName" ^ styleName! ! !FontFamilyMemberAbstract methodsFor: 'accessing' stamp: 'tween 8/18/2007 13:41'! styleName: anObject "Set the value of styleName" styleName := anObject! ! !FontFamilyMemberAbstract methodsFor: 'accessing' stamp: 'tween 9/8/2007 13:24'! weightValue self subclassResponsibility! ! !FontFamilyMemberAbstract methodsFor: 'comparing' stamp: 'tween 8/18/2007 13:42'! closenessVector ^self closenessVectorForStretch: self stretchValue slant: self slantValue weight: self weightValue! ! !FontFamilyMemberAbstract methodsFor: 'comparing' stamp: 'tween 9/29/2007 13:00'! closenessVectorForStretch: stretch slant: slant weight: weight | normalizedSlant | normalizedSlant := slant. normalizedSlant ~= 0 ifTrue:[ "treat italic and oblique as though they were they same" normalizedSlant := LogicalFont slantItalic]. ^{(stretch - LogicalFont stretchRegular) * 11. slant * 7. ((weight - LogicalFont weightRegular) / 100) * 5}! ! !FontFamilyMemberAbstract methodsFor: 'comparing' stamp: 'tween 8/18/2007 13:43'! isCloserMatchThan: otherMember toStretch: inputStretch weight: inputWeight slant: inputSlant | inputVector vector otherVector distance otherDistance dotProduct otherDotProduct | inputVector := self closenessVectorForStretch: inputStretch slant: inputSlant weight: inputWeight. vector := self closenessVector. otherVector := otherMember closenessVector. distance := (((inputVector first - vector first) raisedTo: 2) + ((inputVector second - vector second) raisedTo: 2) + ((inputVector third - vector third) raisedTo: 2)) sqrt. otherDistance := (((inputVector first - otherVector first) raisedTo: 2) + ((inputVector second - otherVector second) raisedTo: 2) + ((inputVector third - otherVector third) raisedTo: 2)) sqrt. distance < otherDistance ifTrue:[^true]. distance > otherDistance ifTrue:[^false]. dotProduct := (inputVector first * vector first) + (inputVector second * vector second) + (inputVector third * vector third). otherDotProduct := (inputVector first * otherVector first) + (inputVector second * otherVector second) + (inputVector third * otherVector third). dotProduct > otherDotProduct ifTrue:[^true]. dotProduct < otherDotProduct ifTrue:[^false]. vector first > otherVector first ifTrue:[^true]. vector first < otherVector first ifTrue:[^false]. vector second > otherVector second ifTrue:[^true]. vector second < otherVector second ifTrue:[^false]. vector third > otherVector third ifTrue:[^true]. vector third < otherVector third ifTrue:[^false]. ^false ! ! !FontFamilyMemberAbstract methodsFor: 'converting' stamp: 'tween 9/8/2007 13:25'! asLogicalFontOfPointSize: pointSize ^LogicalFont familyName: self family familyName pointSize: pointSize stretchValue: self stretchValue weightValue: self weightValue slantValue: self slantValue! ! Object subclass: #FontProviderAbstract instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FontProviderAbstract commentStamp: 'tween 3/14/2007 22:59' prior: 0! Abstract superClass for fontProviders examples of possible fontProviders are StrikeFontProvider FreeTypeFontProvider Win32NativeFontProvider ! !FontProviderAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 22:00'! families self subclassResponsibility! ! !FontProviderAbstract methodsFor: 'font lookup' stamp: 'tween 3/16/2007 17:57'! fontFor: aLogicalFont ^nil! ! Object subclass: #FontSet instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Fonts'! !FontSet commentStamp: '' prior: 0! FontSet provides a mechanism for storing a set of fonts as a class that can be conveniently filedOut, filedIn, and installed as a TextStyle. The most common use is... Find a font you like. Use BitFont to convert a bunch of sizes to data files named, eg, LovelyNN.BF Use FontSet convertFontsNamed: 'Lovely' to produce a FontSet named Lovely. FileOut that FontSet for later use. Use Lovely installAsTextStyle to make all sizes available in a TextStyle named #Lovely in the TextConstants dictionary. Use ctrl-k in any text pane to select the new Lovely style for that paragraph. Then use cmd-1 through 5 or cmd-k to set the point-size for any selection. ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FontSet class instanceVariableNames: ''! !FontSet class methodsFor: 'as yet unclassified' stamp: 'di 9/15/97 12:01'! convertFontsNamed: familyName "FontSet convertFontsNamed: 'Palatino' " ^ self convertFontsNamed: familyName inDirectoryNamed: ''! ! !FontSet class methodsFor: 'compiling' stamp: 'sma 12/29/1999 11:48'! acceptsLoggingOfCompilation "Dont log sources for my subclasses, so as not to waste time and space storing printString versions of the string literals." ^ self == FontSet! ! !FontSet class methodsFor: 'compiling' stamp: 'lr 7/4/2009 10:42'! compileFont: strikeFont | tempName literalString header sizeStr familyName | tempName := 'FontTemp.sf2'. strikeFont writeAsStrike2named: tempName. literalString := (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: tempName) binary) contents fullPrintString. sizeStr := strikeFont pointSize asString. familyName := strikeFont name first: (strikeFont name findLast: [ :x | x isDigit not ]). header := 'size' , sizeStr , ' ^ self fontNamed: ''' , familyName , sizeStr , ''' fromMimeLiteral: '. self class compile: header , literalString classified: 'fonts' notifying: nil. FileDirectory default deleteFileNamed: tempName! ! !FontSet class methodsFor: 'converting' stamp: 'lr 7/4/2009 10:42'! convertFontsNamed: familyName inDirectoryNamed: dirName "FontSet convertFontsNamed: 'Tekton' inDirectoryNamed: 'Tekton Fonts' " "This utility is for use after you have used BitFont to produce data files for the fonts you wish to use. It will read the BitFont files and build a fontset class from them. If one already exists, the sizes that can be found will be overwritten." "For this utility to work as is, the BitFont data files must be named 'familyNN.BF', and must reside in the directory named by dirName (use '' for the current directory)." "Check first for matching file names and usable FontSet class name." | allFontNames fontSet dir | dir := dirName isEmpty ifTrue: [ FileDirectory default ] ifFalse: [ FileDirectory default directoryNamed: dirName ]. allFontNames := dir fileNamesMatching: familyName , '##.BF'. allFontNames isEmpty ifTrue: [ ^ self error: 'No files found like ' , familyName , 'NN.BF' ]. fontSet := self fontSetClass: familyName. allFontNames do: [ :each | Transcript cr; show: each. fontSet compileFont: (StrikeFont new readFromBitFont: (dir fullNameFor: each)) ]! ! !FontSet class methodsFor: 'converting' stamp: 'lr 7/4/2009 10:42'! convertTextStyleNamed: aString | style fontSet | (style := TextStyle named: aString) ifNil: [ ^ self error: 'unknown text style ' , aString ]. fontSet := self fontSetClass: aString. style fontArray do: [ :each | fontSet compileFont: each ]! ! !FontSet class methodsFor: 'filein/out' stamp: 'sma 12/29/1999 11:49'! fileOut "FileOut and then change the properties of the file so that it won't be treated as text by, eg, email attachment facilities" super fileOut. (FileStream oldFileNamed: self name , '.st') setFileTypeToObject; close! ! !FontSet class methodsFor: 'installing' stamp: 'damiencassou 5/30/2008 14:51'! fontNamed: fontName fromLiteral: aString "NOTE -- THIS IS AN OBSOLETE METHOD THAT MAY CAUSE ERRORS. The old form of fileOut for FontSets produced binary literal strings which may not be accurately read in systems with support for international character sets. If possible, file the FontSet out again from a system that produces the newer MIME encoding (current def of compileFont:), and uses the corresponding altered version of this method. If this is not easy, then file the fontSet into an older system (3.7 or earlier), assume it is called FontSetZork... execute FontSetZork installAsTextStyle. copy the compileFont: method from this system into that older one. remove the class FontSetZork. Execute: FontSet convertTextStyleNamed: 'Zork', and see that it creates a new FontSetZork. FileOut the new class FontSetZork. The resulting file should be able to be read into this system. " ^ StrikeFont new name: fontName; readFromStrike2Stream: aString asByteArray readStream! ! !FontSet class methodsFor: 'installing' stamp: 'di 1/24/2005 11:13'! fontNamed: fontName fromMimeLiteral: aString "This method allows a font set to be captured as sourcecode in a subclass. The string literals will presumably be created by printing, eg, (FileStream readOnlyFileNamed: 'Palatino24.sf2') contentsOfEntireFile, and following the logic in compileFont: to encode and add a heading. See the method installAsTextStyle to see how this can be used." ^ StrikeFont new name: fontName; readFromStrike2Stream: (Base64MimeConverter mimeDecodeToBytes: aString readStream)! ! !FontSet class methodsFor: 'installing' stamp: 'alain.plantec 2/6/2009 17:03'! installAsDefault "FontSetNewYork installAsDefault" (self confirm: 'Do you want to install' translated, ' ''' , self fontName , ''' as default font?' translated) ifFalse: [^ self]. self installAsTextStyle. "TextConstants at: #OldDefaultTextStyle put: TextStyle default." TextConstants at: #DefaultTextStyle put: (TextStyle named: self fontName). ListParagraph initialize. "rbb 2/18/2005 13:20 - How should this change for UIManger, if at all?" PopUpMenu initialize. "SelectionMenu notify: 'The old text style has been saved as ''OldDefaultTextStyle''.'"! ! !FontSet class methodsFor: 'installing' stamp: 'lr 7/4/2009 10:42'! installAsTextStyle "FontSetNewYork installAsTextStyle" | selectors | (TextConstants includesKey: self fontName) ifTrue: [ (self confirm: self fontName , ' is already defined in TextConstants. Do you want to replace that definition?') ifFalse: [ ^ self ] ]. selectors := (self class selectors select: [ :s | s beginsWith: 'size' ]) asSortedCollection. TextConstants at: self fontName put: (TextStyle fontArray: (selectors collect: [ :each | self perform: each ]))! ! !FontSet class methodsFor: 'installing' stamp: 'nk 8/31/2004 09:23'! size: pointSize fromLiteral: aString "This method allows a font set to be captured as sourcecode in a subclass. The string literals will presumably be created by printing, eg, (FileStream readOnlyFileNamed: 'Palatino24.sf2') contentsOfEntireFile, and then pasting into a browser after a heading like, eg, size24 ^ self size: 24 fromLiteral: '--unreadable binary data--' See the method installAsTextStyle to see how this can be used." "This method is old and for backward compatibility only. please use fontNamed:fromLiteral: instead." self flag: #bob. "used in Alan's projects" ^(StrikeFont new) name: self fontName , (pointSize < 10 ifTrue: ['0' , pointSize printString] ifFalse: [pointSize printString]); readFromStrike2Stream: ((RWBinaryOrTextStream with: aString) reset; binary); yourself! ! !FontSet class methodsFor: 'private' stamp: 'sma 12/29/1999 12:58'! fontCategory ^ 'Graphics-Fonts' asSymbol! ! !FontSet class methodsFor: 'private' stamp: 'RAA 6/20/2000 13:29'! fontName self flag: #bob. "temporary hack until I figure out what's happening here" (self name beginsWith: superclass name) ifFalse: [^self name]. ^ (self name copyFrom: superclass name size + 1 to: self name size) asSymbol! ! !FontSet class methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! fontSetClass: aString | className fontSet | className := (self name , (aString select: [ :c | c isAlphaNumeric ]) capitalized) asSymbol. fontSet := Smalltalk at: className ifAbsentPut: [ self subclass: className instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: self fontCategory ]. (fontSet inheritsFrom: self) ifFalse: [ ^ self error: 'The name ' , className , ' is already in use' ]. ^ fontSet! ! Notification subclass: #FontSubstitutionDuringLoading instanceVariableNames: 'familyName pixelSize' classVariableNames: '' poolDictionaries: '' category: 'System-Support'! !FontSubstitutionDuringLoading commentStamp: '' prior: 0! signaled by font loading code when reading a DiskProxy that calls for a missing font.! !FontSubstitutionDuringLoading methodsFor: 'accessing' stamp: 'nk 11/8/2004 15:04'! defaultAction familyName ifNil: [ familyName := 'NoName' ]. pixelSize ifNil: [ pixelSize := 12 ]. ^((familyName beginsWith: 'Comic') ifTrue: [ TextStyle named: (Preferences standardEToysFont familyName) ] ifFalse: [ TextStyle default ]) fontOfSize: pixelSize.! ! !FontSubstitutionDuringLoading methodsFor: 'accessing' stamp: 'nk 11/8/2004 15:01'! familyName "Answer the value of familyName" ^ familyName! ! !FontSubstitutionDuringLoading methodsFor: 'accessing' stamp: 'nk 11/8/2004 15:01'! familyName: anObject "Set the value of familyName" familyName := anObject! ! !FontSubstitutionDuringLoading methodsFor: 'accessing' stamp: 'nk 11/8/2004 15:01'! pixelSize "Answer the value of pixelSize" ^ pixelSize! ! !FontSubstitutionDuringLoading methodsFor: 'accessing' stamp: 'nk 11/8/2004 15:01'! pixelSize: anObject "Set the value of pixelSize" pixelSize := anObject! ! !FontSubstitutionDuringLoading methodsFor: 'accessing' stamp: 'nk 11/8/2004 16:55'! printOn: aStream super printOn: aStream. aStream nextPut: $(; nextPutAll: familyName; nextPut: $-; print: pixelSize; nextPut: $).! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FontSubstitutionDuringLoading class instanceVariableNames: ''! !FontSubstitutionDuringLoading class methodsFor: 'instance creation' stamp: 'nk 11/8/2004 15:07'! forFamilyName: aName pixelSize: aSize ^(self new) familyName: aName; pixelSize: aSize; yourself.! ! TestCase subclass: #FontTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-Multilingual'! !FontTest commentStamp: 'tak 3/11/2005 14:31' prior: 0! I am mainly a test for fallback font. FontTest buildSuite run! !FontTest methodsFor: 'testing' stamp: 'sd 2/4/2008 21:10'! testDisplay "self debug: #testDisplay" | text font bb destPoint width | text := 'test' asText. font := TextStyle default fontOfSize: 21. text addAttribute: (TextFontReference toFont: font). bb := (Form extent: 100 @ 30) getCanvas privatePort. bb combinationRule: Form paint. font installOn: bb foregroundColor: Color black backgroundColor: Color white. destPoint := font displayString: text on: bb from: 1 to: 4 at: 0@0 kern: 1. width := text inject: 0 into: [:max :char | max + (font widthOf: char)]. self assert: destPoint x = (width + 4). "bb destForm asMorph openInHand." ! ! !FontTest methodsFor: 'testing' stamp: 'sd 2/4/2008 21:10'! testFallback "self debug: #testFallback" | text font bb destPoint | text := (Character value: 257) asString asText. font := TextStyle default fontOfSize: 21. text addAttribute: (TextFontReference toFont: font). bb := (Form extent: 100 @ 30) getCanvas privatePort. bb combinationRule: Form paint. font installOn: bb foregroundColor: Color black backgroundColor: Color white. destPoint := font displayString: text on: bb from: 1 to: 1 at: 0@0 kern: 1. "bb destForm asMorph openInHand." self assert: destPoint x = ((font widthOf: $?) + 1). ! ! !FontTest methodsFor: 'testing' stamp: 'tak 12/21/2004 18:02'! testMultistringFont "self debug: #testMultistringFont" | text p style height width | [(TextStyle default fontArray at: JapaneseEnvironment leadingChar) ifNil: [^ self]] ifError: [:err :rcvr | ^ self]. text := ((#(20983874 20983876 20983878 ) collect: [:e | e asCharacter]) as: String) asText. p := MultiNewParagraph new. style := TextStyle default. p compose: text style: style from: 1 in: (0 @ 0 corner: 100 @ 100). "See CompositionScanner>>setActualFont: & CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide:" height := style defaultFont height + style leading. width := text inject: 0 into: [:tally :next | tally + (style defaultFont widthOf: next)]. p adjustRightX. self assert: p extent = (width @ height). "Display getCanvas paragraph: p bounds: (10 @ 10 extent: 100 @ 100) color: Color black"! ! !FontTest methodsFor: 'testing' stamp: 'tak 12/21/2004 14:50'! testParagraph "self debug: #testParagraph" | text p style height width | text := 'test' asText. p := MultiNewParagraph new. style := TextStyle default. p compose: text style: style from: 1 in: (0 @ 0 corner: 100 @ 100). "See CompositionScanner>>setActualFont: & CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide:" height := style defaultFont height + style leading. width := text inject: 0 into: [:tally :next | tally + (style defaultFont widthOf: next)]. p adjustRightX. self assert: p extent = (width @ height)! ! !FontTest methodsFor: 'testing' stamp: 'tak 12/21/2004 17:19'! testParagraphFallback "self debug: #testParagraphFallback" | text p style height width e expect | e := (Character value: 257) asString. text := ('test' , e , e , e , e , 'test') asText. expect := 'test????test'. p := MultiNewParagraph new. style := TextStyle default. p compose: text style: style from: 1 in: (0 @ 0 corner: 100 @ 100). "See CompositionScanner>>setActualFont: & CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide:" height := style defaultFont height + style leading. width := expect inject: 0 into: [:tally :next | tally + (style defaultFont widthOf: next)]. p adjustRightX. self assert: p extent = (width @ height). "Display getCanvas paragraph: p bounds: (10 @ 10 extent: 100 @ 100) color: Color black"! ! !FontTest methodsFor: 'testing' stamp: 'sd 2/4/2008 21:11'! testResetAfterEmphasized "self debug: #testResetAfterEmphasized" | normal derivative | normal := TextStyle defaultFont. derivative := normal emphasized: 3. self assert: (normal derivativeFonts at: 3) == derivative. normal reset. self assert: normal derivativeFonts isEmpty ! ! DisplayMedium subclass: #Form instanceVariableNames: 'bits width height depth offset' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Display Objects'! !Form commentStamp: 'ls 1/4/2004 17:16' prior: 0! A rectangular array of pixels, used for holding images. All pictures, including character images are Forms. The depth of a Form is how many bits are used to specify the color at each pixel. The actual bits are held in a Bitmap, whose internal structure is different at each depth. Class Color allows you to deal with colors without knowing how they are actually encoded inside a Bitmap. The supported depths (in bits) are 1, 2, 4, 8, 16, and 32. The number of actual colors at these depths are: 2, 4, 16, 256, 32768, and 16 million. Forms are indexed starting at 0 instead of 1; thus, the top-left pixel of a Form has coordinates 0@0. Forms are combined using BitBlt. See the comment in class BitBlt. Forms that repeat many times to fill a large destination are InfiniteForms. colorAt: x@y Returns the abstract Color at this location displayAt: x@y shows this form on the screen displayOn: aMedium at: x@y shows this form in a Window, a Form, or other DisplayMedium fillColor: aColor Set all the pixels to the color. edit launch an editor to change the bits of this form. pixelValueAt: x@y The encoded color. The encoding depends on the depth. ! ]style[(223 6 62 5 374 6 11 23 64 12 40 5 337)f1,f1LBitmap Definition;,f1,f1LColor Definition;,f1,f1LBitBlt Definition;,f1,f1LBitBlt Comment;,f1,f1LInfiniteForm Definition;,f1,f1RColor;,f1! !Form methodsFor: '*morphic' stamp: 'ar 7/8/2006 21:01'! iconOrThumbnailOfSize: aNumberOrPoint "Answer an appropiate form to represent the receiver" ^ self scaledIntoFormOfSize: aNumberOrPoint! ! !Form methodsFor: '*morphic' stamp: 'ar 7/8/2006 21:01'! scaledIntoFormOfSize: aNumberOrPoint "Scale and center the receiver into a form of a given size" | extent scale scaledForm result | extent := aNumberOrPoint asPoint. extent = self extent ifTrue: [^ self]. (self height isZero or: [self width isZero]) ifTrue: [^ Form extent: extent depth: self depth]. scale := extent y / self height min: extent x / self width. scaledForm := self magnify: self boundingBox by: scale smoothing: 8. result := Form extent: extent depth: 32. result getCanvas translucentImage: scaledForm at: extent - scaledForm extent // 2. ^ result ! ! !Form methodsFor: 'accessing'! bits "Answer the receiver's Bitmap containing its bits." ^ bits! ! !Form methodsFor: 'accessing' stamp: 'ar 5/17/2001 15:41'! bitsSize | pixPerWord | depth == nil ifTrue: [depth := 1]. pixPerWord := 32 // self depth. ^ width + pixPerWord - 1 // pixPerWord * height! ! !Form methodsFor: 'accessing'! bits: aBitmap "Reset the Bitmap containing the receiver's bits." bits := aBitmap! ! !Form methodsFor: 'accessing' stamp: 'tk 3/9/97'! center "Note that offset is ignored here. Are we really going to embrace offset? " ^ (width @ height) // 2! ! !Form methodsFor: 'accessing' stamp: 'ar 5/28/2000 12:03'! defaultCanvasClass "Return the default canvas used for drawing onto the receiver" ^Display defaultCanvasClass! ! !Form methodsFor: 'accessing' stamp: 'ar 5/17/2001 15:45'! depth ^ depth < 0 ifTrue:[0-depth] ifFalse:[depth]! ! !Form methodsFor: 'accessing'! depth: bitsPerPixel (bitsPerPixel > 32 or: [(bitsPerPixel bitAnd: bitsPerPixel-1) ~= 0]) ifTrue: [self halt: 'bitsPerPixel must be 1, 2, 4, 8, 16 or 32']. depth := bitsPerPixel! ! !Form methodsFor: 'accessing' stamp: 'ar 5/27/2000 16:56'! displayScreen "Return the display screen the receiver is allocated on. Forms in general are Squeak internal and not allocated on any particular display." ^nil! ! !Form methodsFor: 'accessing'! extent ^ width @ height! ! !Form methodsFor: 'accessing'! form "Answer the receiver's form. For vanilla Forms, this degenerates to self. Makes several methods that operate on both Forms and MaskedForms much more straightforward. 6/1/96 sw" ^ self! ! !Form methodsFor: 'accessing' stamp: 'ar 5/28/2000 12:03'! getCanvas "Return a Canvas that can be used to draw onto the receiver" ^self defaultCanvasClass on: self! ! !Form methodsFor: 'accessing' stamp: 'ar 5/28/2000 00:48'! hasBeenModified "Return true if something *might* have been drawn into the receiver" ^(bits == nil or:[bits class == ByteArray]) not "Read the above as: If the receiver has forgotten its contents (bits == nil) or is still hibernated it can't be modified."! ! !Form methodsFor: 'accessing' stamp: 'ar 5/28/2000 00:48'! hasBeenModified: aBool "Change the receiver to reflect the modification state" aBool ifTrue:[^self unhibernate]. self shouldPreserveContents ifTrue:[self hibernate] ifFalse:[bits := nil]! ! !Form methodsFor: 'accessing'! height ^ height! ! !Form methodsFor: 'accessing' stamp: 'ar 5/17/2001 15:50'! nativeDepth "Return the 'native' depth of the receiver, e.g., including the endianess" ^depth! ! !Form methodsFor: 'accessing' stamp: 'ar 2/16/2000 22:00'! offset ^offset ifNil:[0@0]! ! !Form methodsFor: 'accessing'! offset: aPoint offset := aPoint! ! !Form methodsFor: 'accessing'! size "Should no longer be used -- use bitsSize instead. length of variable part of instance." ^ super size! ! !Form methodsFor: 'accessing'! width ^ width! ! !Form methodsFor: 'analyzing' stamp: 'jm 12/5/97 19:48'! colorsUsed "Return a list of the Colors this form uses." | tallies tallyDepth usedColors | tallies := self tallyPixelValues. tallyDepth := (tallies size log: 2) asInteger. usedColors := OrderedCollection new. tallies doWithIndex: [:count :i | count > 0 ifTrue: [ usedColors add: (Color colorFromPixelValue: i - 1 depth: tallyDepth)]]. ^ usedColors asArray ! ! !Form methodsFor: 'analyzing' stamp: 'ar 5/17/2001 15:40'! dominantColor | tally max maxi | self depth > 16 ifTrue: [^(self asFormOfDepth: 16) dominantColor]. tally := self tallyPixelValues. max := maxi := 0. tally withIndexDo: [:n :i | n > max ifTrue: [max := n. maxi := i]]. ^ Color colorFromPixelValue: maxi - 1 depth: self depth! ! !Form methodsFor: 'analyzing'! innerPixelRectFor: pv orNot: not "Return a rectangle describing the smallest part of me that includes all pixels of value pv. Note: If orNot is true, then produce a copy that includes all pixels that are DIFFERENT from the supplied (background) value" | xTally yTally | xTally := self xTallyPixelValue: pv orNot: not. yTally := self yTallyPixelValue: pv orNot: not. ^ ((xTally findFirst: [:t | t>0]) - 1) @ ((yTally findFirst: [:t | t>0]) - 1) corner: (xTally findLast: [:t | t>0])@(yTally findLast: [:t | t>0])! ! !Form methodsFor: 'analyzing' stamp: 'ar 5/17/2001 15:40'! pixelCompare: aRect with: otherForm at: otherLoc "Compare the selected bits of this form (those within aRect) against those in a similar rectangle of otherFrom. Return the sum of the absolute value of the differences of the color values of every pixel. Obviously, this is most useful for rgb (16- or 32-bit) pixels but, in the case of 8-bits or less, this will return the sum of the differing bits of the corresponding pixel values (somewhat less useful)" | pixPerWord temp | pixPerWord := 32//self depth. (aRect left\\pixPerWord = 0 and: [aRect right\\pixPerWord = 0]) ifTrue: ["If word-aligned, use on-the-fly difference" ^ (BitBlt current toForm: self) copy: aRect from: otherLoc in: otherForm fillColor: nil rule: 32]. "Otherwise, combine in a word-sized form and then compute difference" temp := self copy: aRect. temp copy: aRect from: otherLoc in: otherForm rule: 21. ^ (BitBlt current toForm: temp) copy: aRect from: otherLoc in: nil fillColor: (Bitmap with: 0) rule: 32 " Dumb example prints zero only when you move over the original rectangle... | f diff | f := Form fromUser. [Sensor anyButtonPressed] whileFalse: [diff := f pixelCompare: f boundingBox with: Display at: Sensor cursorPoint. diff printString , ' ' displayAt: 0@0] "! ! !Form methodsFor: 'analyzing' stamp: 'ar 5/17/2001 15:42'! primCountBits "Count the non-zero pixels of this form." self depth > 8 ifTrue: [^(self asFormOfDepth: 8) primCountBits]. ^ (BitBlt current toForm: self) fillColor: (Bitmap with: 0); destRect: (0@0 extent: width@height); combinationRule: 32; copyBits! ! !Form methodsFor: 'analyzing' stamp: 'ar 5/17/2001 15:37'! rectangleEnclosingPixelsNotOfColor: aColor "Answer the smallest rectangle enclosing all the pixels of me that are different from the given color. Useful for extracting a foreground graphic from its background." | cm slice copyBlt countBlt top bottom newH left right | "map the specified color to 1 and all others to 0" cm := Bitmap new: (1 bitShift: (self depth min: 15)). cm primFill: 1. cm at: (aColor indexInMap: cm) put: 0. "build a 1-pixel high horizontal slice and BitBlts for counting pixels of interest" slice := Form extent: width@1 depth: 1. copyBlt := (BitBlt current toForm: slice) sourceForm: self; combinationRule: Form over; destX: 0 destY: 0 width: width height: 1; colorMap: cm. countBlt := (BitBlt current toForm: slice) fillColor: (Bitmap with: 0); destRect: (0@0 extent: slice extent); combinationRule: 32. "scan in from top and bottom" top := (0 to: height) detect: [:y | copyBlt sourceOrigin: 0@y; copyBits. countBlt copyBits > 0] ifNone: [^ 0@0 extent: 0@0]. bottom := (height - 1 to: top by: -1) detect: [:y | copyBlt sourceOrigin: 0@y; copyBits. countBlt copyBits > 0]. "build a 1-pixel wide vertical slice and BitBlts for counting pixels of interest" newH := bottom - top + 1. slice := Form extent: 1@newH depth: 1. copyBlt := (BitBlt current toForm: slice) sourceForm: self; combinationRule: Form over; destX: 0 destY: 0 width: 1 height: newH; colorMap: cm. countBlt := (BitBlt current toForm: slice) fillColor: (Bitmap with: 0); destRect: (0@0 extent: slice extent); combinationRule: 32. "scan in from left and right" left := (0 to: width) detect: [:x | copyBlt sourceOrigin: x@top; copyBits. countBlt copyBits > 0]. right := (width - 1 to: left by: -1) detect: [:x | copyBlt sourceOrigin: x@top; copyBits. countBlt copyBits > 0]. ^ left@top corner: (right + 1)@(bottom + 1) ! ! !Form methodsFor: 'analyzing' stamp: 'jm 6/18/1999 18:41'! tallyPixelValues "Answer a Bitmap whose elements contain the number of pixels in this Form with the pixel value corresponding to their index. Note that the pixels of multiple Forms can be tallied together using tallyPixelValuesInRect:into:." ^ self tallyPixelValuesInRect: self boundingBox into: (Bitmap new: (1 bitShift: (self depth min: 15))) " Move a little rectangle around the screen and print its tallies... | r tallies nonZero | Cursor blank showWhile: [ [Sensor anyButtonPressed] whileFalse: [r := Sensor cursorPoint extent: 10@10. Display border: (r expandBy: 2) width: 2 rule: Form reverse fillColor: nil. tallies := (Display copy: r) tallyPixelValues. nonZero := (1 to: tallies size) select: [:i | (tallies at: i) > 0] thenCollect: [:i | (tallies at: i) -> (i-1)]. nonZero printString , ' ' displayAt: 0@0. Display border: (r expandBy: 2) width: 2 rule: Form reverse fillColor: nil]] " ! ! !Form methodsFor: 'analyzing' stamp: 'ar 5/28/2000 12:09'! tallyPixelValuesInRect: destRect into: valueTable "Tally the selected pixels of this Form into valueTable, a Bitmap of depth 2^depth similar to a color map. Answer valueTable." (BitBlt current toForm: self) sourceForm: self; "src must be given for color map ops" sourceOrigin: 0@0; tallyMap: valueTable; combinationRule: 33; destRect: destRect; copyBits. ^ valueTable " Move a little rectangle around the screen and print its tallies... | r tallies nonZero | Cursor blank showWhile: [ [Sensor anyButtonPressed] whileFalse: [r := Sensor cursorPoint extent: 10@10. Display border: (r expandBy: 2) width: 2 rule: Form reverse fillColor: nil. tallies := (Display copy: r) tallyPixelValues. nonZero := (1 to: tallies size) select: [:i | (tallies at: i) > 0] thenCollect: [:i | (tallies at: i) -> (i-1)]. nonZero printString , ' ' displayAt: 0@0. Display border: (r expandBy: 2) width: 2 rule: Form reverse fillColor: nil]] "! ! !Form methodsFor: 'analyzing' stamp: 'ar 5/28/2000 12:09'! xTallyPixelValue: pv orNot: not "Return an array of the number of pixels with value pv by x-value. Note that if not is true, then this will tally those different from pv." | cm slice countBlt copyBlt | cm := self newColorMap. "Map all colors but pv to zero" not ifTrue: [cm atAllPut: 1]. "... or all but pv to one" cm at: pv+1 put: 1 - (cm at: pv+1). slice := Form extent: 1@height. copyBlt := (BitBlt current destForm: slice sourceForm: self halftoneForm: nil combinationRule: Form over destOrigin: 0@0 sourceOrigin: 0@0 extent: 1 @ slice height clipRect: slice boundingBox) colorMap: cm. countBlt := (BitBlt current toForm: slice) fillColor: (Bitmap with: 0); destRect: (0@0 extent: slice extent); combinationRule: 32. ^ (0 to: width-1) collect: [:x | copyBlt sourceOrigin: x@0; copyBits. countBlt copyBits]! ! !Form methodsFor: 'analyzing' stamp: 'ar 5/28/2000 12:09'! yTallyPixelValue: pv orNot: not "Return an array of the number of pixels with value pv by y-value. Note that if not is true, then this will tally those different from pv." | cm slice copyBlt countBlt | cm := self newColorMap. "Map all colors but pv to zero" not ifTrue: [cm atAllPut: 1]. "... or all but pv to one" cm at: pv+1 put: 1 - (cm at: pv+1). slice := Form extent: width@1. copyBlt := (BitBlt current destForm: slice sourceForm: self halftoneForm: nil combinationRule: Form over destOrigin: 0@0 sourceOrigin: 0@0 extent: slice width @ 1 clipRect: slice boundingBox) colorMap: cm. countBlt := (BitBlt current toForm: slice) fillColor: (Bitmap with: 0); destRect: (0@0 extent: slice extent); combinationRule: 32. ^ (0 to: height-1) collect: [:y | copyBlt sourceOrigin: 0@y; copyBits. countBlt copyBits]! ! !Form methodsFor: 'bordering' stamp: 'ar 5/17/2001 15:42'! borderFormOfWidth: borderWidth sharpCorners: sharpen "Smear this form around and then subtract the original to produce an outline. If sharpen is true, then cause right angles to be outlined by right angles (takes an additional diagonal smears ANDed with both horizontal and vertical smears)." | smearForm bigForm smearPort all cornerForm cornerPort nbrs | self depth > 1 ifTrue: [self halt]. "Only meaningful for B/W forms." bigForm := self deepCopy. all := bigForm boundingBox. smearForm := Form extent: self extent. smearPort := BitBlt current toForm: smearForm. sharpen ifTrue: [cornerForm := Form extent: self extent. cornerPort := BitBlt current toForm: cornerForm]. nbrs := (0@0) fourNeighbors. 1 to: borderWidth do: [:i | "Iterate to get several layers of 'skin'" nbrs do: [:d | "Smear the self in 4 directions to grow each layer of skin" smearPort copyForm: bigForm to: d rule: Form under]. sharpen ifTrue: ["Special treatment to smear sharp corners" nbrs with: ((2 to: 5) collect: [:i2 | nbrs atWrap: i2]) do: [:d1 :d2 | "Copy corner points diagonally" cornerPort copyForm: bigForm to: d1+d2 rule: Form over. "But only preserve if there were dots on either side" cornerPort copyForm: bigForm to: d1+d1+d2 rule: Form and. cornerPort copyForm: bigForm to: d1+d2+d2 rule: Form and. smearPort copyForm: cornerForm to: 0@0 rule: Form under]. ]. bigForm copy: all from: 0@0 in: smearForm rule: Form over. ]. "Now erase the original shape to obtain the outline" bigForm copy: all from: 0@0 in: self rule: Form erase. ^ bigForm! ! !Form methodsFor: 'bordering'! borderWidth: anInteger "Set the width of the border for the receiver to be anInteger and paint it using black as the border color." self border: self boundingBox width: anInteger fillColor: Color black! ! !Form methodsFor: 'bordering'! borderWidth: anInteger color: aMask "Set the width of the border for the receiver to be anInteger and paint it using aMask as the border color." self border: self boundingBox width: anInteger fillColor: aMask! ! !Form methodsFor: 'bordering'! borderWidth: anInteger fillColor: aMask "Set the width of the border for the receiver to be anInteger and paint it using aMask as the border color." self border: self boundingBox width: anInteger fillColor: aMask! ! !Form methodsFor: 'bordering' stamp: 'ar 5/28/2000 12:07'! border: rect width: borderWidth rule: rule fillColor: fillColor "Paint a border whose rectangular area is defined by rect. The width of the border of each side is borderWidth. Uses fillColor for drawing the border." | blt | blt := (BitBlt current toForm: self) combinationRule: rule; fillColor: fillColor. blt sourceOrigin: 0@0. blt destOrigin: rect origin. blt width: rect width; height: borderWidth; copyBits. blt destY: rect corner y - borderWidth; copyBits. blt destY: rect origin y + borderWidth. blt height: rect height - borderWidth - borderWidth; width: borderWidth; copyBits. blt destX: rect corner x - borderWidth; copyBits! ! !Form methodsFor: 'bordering' stamp: 'di 10/21/2001 09:39'! shapeBorder: aColor width: borderWidth "A simplified version for shapes surrounded by transparency (as SketchMorphs). Note also this returns a new form that may be larger, and does not affect the original." | shapeForm borderForm newForm | newForm := Form extent: self extent + (borderWidth*2) depth: self depth. newForm fillColor: Color transparent. self displayOn: newForm at: (0@0) + borderWidth. "First identify the shape in question as a B/W form" shapeForm := (newForm makeBWForm: Color transparent) reverse. "Now find the border of that shape" borderForm := shapeForm borderFormOfWidth: borderWidth sharpCorners: false. "Finally use that shape as a mask to paint the border with color" ^ newForm fillShape: borderForm fillColor: aColor! ! !Form methodsFor: 'bordering'! shapeBorder: aColor width: borderWidth interiorPoint: interiorPoint sharpCorners: sharpen internal: internal "Identify the shape (region of identical color) at interiorPoint, and then add an outline of width=borderWidth and color=aColor. If sharpen is true, then cause right angles to be outlined by right angles. If internal is true, then produce a border that lies within the identified shape. Thus one can put an internal border around the whole background, thus effecting a normal border around every other foreground image." | shapeForm borderForm interiorColor | "First identify the shape in question as a B/W form" interiorColor := self colorAt: interiorPoint. shapeForm := (self makeBWForm: interiorColor) reverse findShapeAroundSeedBlock: [:form | form pixelValueAt: interiorPoint put: 1]. "Reverse the image to grow the outline inward" internal ifTrue: [shapeForm reverse]. "Now find the border fo that shape" borderForm := shapeForm borderFormOfWidth: borderWidth sharpCorners: sharpen. "Finally use that shape as a mask to paint the border with color" self fillShape: borderForm fillColor: aColor! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/15/2001 16:16'! balancedPatternFor: aColor "Return the pixel word for representing the given color on the receiver" self hasNonStandardPalette ifTrue:[^self bitPatternFor: aColor] ifFalse:[^aColor balancedPatternForDepth: self depth]! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/15/2001 16:16'! bitPatternFor: aColor "Return the pixel word for representing the given color on the receiver" aColor isColor ifFalse:[^aColor bitPatternForDepth: self depth]. self hasNonStandardPalette ifTrue:[^Bitmap with: (self pixelWordFor: aColor)] ifFalse:[^aColor bitPatternForDepth: self depth]! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/15/2001 16:16'! colormapFromARGB "Return a ColorMap mapping from canonical ARGB space into the receiver. Note: This version is optimized for Squeak forms." | map nBits | self hasNonStandardPalette ifTrue:[^ColorMap mappingFromARGB: self rgbaBitMasks]. self depth <= 8 ifTrue:[ map := Color colorMapIfNeededFrom: 32 to: self depth. map size = 512 ifTrue:[nBits := 3]. map size = 4096 ifTrue:[nBits := 4]. map size = 32768 ifTrue:[nBits := 5]. ^ColorMap shifts: (Array with: 3 * nBits - 24 with: 2 * nBits - 16 with: 1 * nBits - 8 with: 0) masks: (Array with: (1 << nBits) - 1 << (24 - nBits) with: (1 << nBits) - 1 << (16 - nBits) with: (1 << nBits) - 1 << (8 - nBits) with: 0) colors: map]. self depth = 16 ifTrue:[ ^ColorMap shifts: #(-9 -6 -3 0) masks: #(16rF80000 16rF800 16rF8 0)]. self depth = 32 ifTrue:[ ^ColorMap shifts: #(0 0 0 0) masks: #(16rFF0000 16rFF00 16rFF 16rFF000000)]. self error:'Bad depth'! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/17/2001 15:42'! colormapIfNeededForDepth: destDepth "Return a colormap for displaying the receiver at the given depth, or nil if no colormap is needed." self depth = destDepth ifTrue: [^ nil]. "not needed if depths are the same" ^ Color colorMapIfNeededFrom: self depth to: destDepth ! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/16/2001 22:23'! colormapIfNeededFor: destForm "Return a ColorMap mapping from the receiver to destForm." (self hasNonStandardPalette or:[destForm hasNonStandardPalette]) ifTrue:[^self colormapFromARGB mappingTo: destForm colormapFromARGB] ifFalse:[^self colormapIfNeededForDepth: destForm depth]! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/15/2001 16:16'! colormapToARGB "Return a ColorMap mapping from the receiver into canonical ARGB space." self hasNonStandardPalette ifTrue:[^self colormapFromARGB inverseMap]. self depth <= 8 ifTrue:[ ^ColorMap shifts: #(0 0 0 0) masks: #(16rFF0000 16rFF00 16rFF 16rFF000000) colors: (Color colorMapIfNeededFrom: self depth to: 32)]. self depth = 16 ifTrue:[ ^ColorMap shifts: #( 9 6 3 0) masks: #(16r7C00 16r3E0 16r1F 0)]. self depth = 32 ifTrue:[ ^ColorMap shifts: #(0 0 0 0) masks: #(16rFF0000 16rFF00 16rFF 16rFF000000)]. self error:'Bad depth'! ! !Form methodsFor: 'color mapping'! makeBWForm: foregroundColor "Map this form into a B/W form with 1's in the foreground regions." | bwForm map | bwForm := Form extent: self extent. map := self newColorMap. "All non-foreground go to 0's" map at: (foregroundColor indexInMap: map) put: 1. bwForm copyBits: self boundingBox from: self at: 0@0 colorMap: map. ^ bwForm! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/17/2001 15:40'! mapColors: oldColorBitsCollection to: newColorBits "Make all pixels of the given color in this Form to the given new color." "Warnings: This method modifies the receiver. It may lose some color accuracy on 32-bit Forms, since the transformation uses a color map with only 15-bit resolution." | map | self depth < 16 ifTrue: [map := (Color cachedColormapFrom: self depth to: self depth) copy] ifFalse: [ "use maximum resolution color map" "source is 16-bit or 32-bit RGB; use colormap with 5 bits per color component" map := Color computeRGBColormapFor: self depth bitsPerColor: 5]. oldColorBitsCollection do:[ :oldColor | map at: oldColor put: newColorBits]. (BitBlt current toForm: self) sourceForm: self; sourceOrigin: 0@0; combinationRule: Form over; destX: 0 destY: 0 width: width height: height; colorMap: map; copyBits. ! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/17/2001 15:38'! mapColor: oldColor to: newColor "Make all pixels of the given color in this Form to the given new color." "Warnings: This method modifies the receiver. It may lose some color accuracy on 32-bit Forms, since the transformation uses a color map with only 15-bit resolution." | map | map := (Color cachedColormapFrom: self depth to: self depth) copy. map at: (oldColor indexInMap: map) put: (newColor pixelWordForDepth: self depth). (BitBlt current toForm: self) sourceForm: self; sourceOrigin: 0@0; combinationRule: Form over; destX: 0 destY: 0 width: width height: height; colorMap: map; copyBits. ! ! !Form methodsFor: 'color mapping' stamp: 'ar 12/14/2001 18:11'! maskingMap "Return a color map that maps all colors except transparent to words of all ones. Used to create a mask for a Form whose transparent pixel value is zero." ^Color maskingMap: self depth! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/17/2001 15:41'! newColorMap "Return an uninitialized color map array appropriate to this Form's depth." ^ Bitmap new: (1 bitShift: (self depth min: 15)) ! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/15/2001 16:16'! pixelValueFor: aColor "Return the pixel word for representing the given color on the receiver" self hasNonStandardPalette ifTrue:[^self colormapFromARGB mapPixel: (aColor pixelValueForDepth: 32)] ifFalse:[^aColor pixelValueForDepth: self depth]! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/15/2001 16:16'! pixelWordFor: aColor "Return the pixel word for representing the given color on the receiver" | basicPattern | self hasNonStandardPalette ifFalse:[^aColor pixelWordForDepth: self depth]. basicPattern := self pixelValueFor: aColor. self depth = 32 ifTrue:[^basicPattern] ifFalse:[^aColor pixelWordFor: self depth filledWith: basicPattern]! ! !Form methodsFor: 'color mapping' stamp: 'di 10/16/2001 15:23'! reducedPaletteOfSize: nColors "Return an array of colors of size nColors, such that those colors represent well the pixel values actually found in this form." | threshold tallies colorTallies dist delta palette cts top cluster | tallies := self tallyPixelValues. "An array of tallies for each pixel value" threshold := width * height // 500. "Make an array of (color -> tally) for all tallies over threshold" colorTallies := Array streamContents: [:s | tallies withIndexDo: [:v :i | v >= threshold ifTrue: [s nextPut: (Color colorFromPixelValue: i-1 depth: depth) -> v]]]. "Extract a set of clusters by picking the top tally, and then removing all others whose color is within dist of it. Iterate the process, adjusting dist until we get nColors." dist := 0.2. delta := dist / 2. [cts := colorTallies copy. palette := Array streamContents: [:s | [cts isEmpty] whileFalse: [top := cts detectMax: [:a | a value]. cluster := cts select: [:a | (a key diff: top key) < dist]. s nextPut: top key -> (cluster detectSum: [:a | a value]). cts := cts copyWithoutAll: cluster]]. palette size = nColors or: [delta < 0.001]] whileFalse: [palette size > nColors ifTrue: [dist := dist + delta] ifFalse: [dist := dist - delta]. delta := delta / 2]. ^ palette collect: [:a | a key] ! ! !Form methodsFor: 'color mapping' stamp: 'ar 5/27/2000 20:14'! rgbaBitMasks "Return the masks for specifying the R,G,B, and A components in the receiver" self depth <= 8 ifTrue:[^#(16rFF0000 16rFF00 16rFF 16rFF000000)]. self depth = 16 ifTrue:[^#(16r7C00 16r3E0 16r1F 16r0)]. self depth = 32 ifTrue:[^#(16rFF0000 16rFF00 16rFF 16rFF000000)]. self error:'Bad depth for form'! ! !Form methodsFor: 'converting' stamp: 'jm 11/12/97 19:28'! as8BitColorForm "Simple conversion of zero pixels to transparent. Force it to 8 bits." | f map | f := ColorForm extent: self extent depth: 8. self displayOn: f at: self offset negated. map := Color indexedColors copy. map at: 1 put: Color transparent. f colors: map. f offset: self offset. ^ f ! ! !Form methodsFor: 'converting' stamp: 'RAA 8/14/2000 10:13'! asCursorForm ^ self as: StaticForm! ! !Form methodsFor: 'converting' stamp: 'ar 6/16/2002 17:44'! asFormOfDepth: d | newForm | d = self depth ifTrue:[^self]. newForm := Form extent: self extent depth: d. (BitBlt current toForm: newForm) colorMap: (self colormapIfNeededFor: newForm); copy: (self boundingBox) from: 0@0 in: self fillColor: nil rule: Form over. ^newForm! ! !Form methodsFor: 'converting' stamp: 'ar 5/17/2001 15:39'! asGrayScale "Assume the receiver is a grayscale image. Return a grayscale ColorForm computed by extracting the brightness levels of one color component. This technique allows a 32-bit Form to be converted to an 8-bit ColorForm to save space while retaining a full 255 levels of gray. (The usual colormapping technique quantizes to 8, 16, or 32 levels, which loses information.)" | f32 srcForm result map bb grays | self depth = 32 ifFalse: [ f32 := Form extent: width@height depth: 32. self displayOn: f32. ^ f32 asGrayScale]. self unhibernate. srcForm := Form extent: (width * 4)@height depth: 8. srcForm bits: bits. result := ColorForm extent: width@height depth: 8. map := Bitmap new: 256. 2 to: 256 do: [:i | map at: i put: i - 1]. map at: 1 put: 1. "map zero pixel values to near-black" bb := (BitBlt current toForm: result) sourceForm: srcForm; combinationRule: Form over; colorMap: map. 0 to: width - 1 do: [:dstX | bb sourceRect: (((dstX * 4) + 2)@0 extent: 1@height); destOrigin: dstX@0; copyBits]. "final BitBlt to zero-out pixels that were truely transparent in the original" map := Bitmap new: 512. map at: 1 put: 16rFF. (BitBlt current toForm: result) sourceForm: self; sourceRect: self boundingBox; destOrigin: 0@0; combinationRule: Form erase; colorMap: map; copyBits. grays := (0 to: 255) collect: [:brightness | Color gray: brightness asFloat / 255.0]. grays at: 1 put: Color transparent. result colors: grays. ^ result ! ! !Form methodsFor: 'converting' stamp: 'ar 11/7/1999 20:29'! asMorph ^ImageMorph new image: self! ! !Form methodsFor: 'converting' stamp: 'ar 2/7/2004 18:16'! asSourceForm ^self! ! !Form methodsFor: 'converting' stamp: 'marcus.denker 9/14/2008 21:16'! colorReduced "Return a color-reduced ColorForm version of the receiver, if possible, or the receiver itself if not." | tally tallyDepth colorCount newForm cm oldPixelValues newFormColors nextColorIndex c | tally := self tallyPixelValues asArray. tallyDepth := (tally size log: 2) asInteger. colorCount := 0. tally do: [:n | n > 0 ifTrue: [colorCount := colorCount + 1]]. (tally at: 1) = 0 ifTrue: [colorCount := colorCount + 1]. "include transparent" colorCount > 256 ifTrue: [^ self]. "cannot reduce" newForm := self formForColorCount: colorCount. "build an array of just the colors used, and a color map to translate old pixel values to their indices into this color array" cm := Bitmap new: tally size. oldPixelValues := self colormapIfNeededForDepth: 32. newFormColors := Array new: colorCount. newFormColors at: 1 put: Color transparent. nextColorIndex := 2. 2 to: cm size do: [:i | (tally at: i) > 0 ifTrue: [ oldPixelValues isNil ifTrue: [c := Color colorFromPixelValue: i - 1 depth: tallyDepth] ifFalse: [c := Color colorFromPixelValue: (oldPixelValues at: i) depth: 32]. newFormColors at: nextColorIndex put: c. cm at: i put: nextColorIndex - 1. "pixel values are zero-based indices" nextColorIndex := nextColorIndex + 1]]. "copy pixels into new ColorForm, mapping to new pixel values" newForm copyBits: self boundingBox from: self at: 0@0 clippingBox: self boundingBox rule: Form over fillColor: nil map: cm. newForm colors: newFormColors. newForm offset: offset. ^ newForm ! ! !Form methodsFor: 'converting' stamp: 'di 10/16/2001 19:23'! copyWithColorsReducedTo: nColors "Note: this has not been engineered. There are better solutions in the literature." | palette colorMap pc closest | palette := self reducedPaletteOfSize: nColors. colorMap := (1 to: (1 bitShift: depth)) collect: [:i | pc := Color colorFromPixelValue: i-1 depth: depth. closest := palette detectMin: [:c | c diff: pc]. closest pixelValueForDepth: depth]. ^ self deepCopy copyBits: self boundingBox from: self at: 0@0 colorMap: (colorMap as: Bitmap) ! ! !Form methodsFor: 'converting' stamp: 'ar 7/23/1999 17:04'! orderedDither32To16 "Do an ordered dithering for converting from 32 to 16 bit depth." | ditherMatrix ii out inBits outBits index pv dmv r di dmi dmo g b pvOut outIndex | self depth = 32 ifFalse:[^self error:'Must be 32bit for this']. ditherMatrix := #( 0 8 2 10 12 4 14 6 3 11 1 9 15 7 13 5). ii := (0 to: 31) collect:[:i| i]. out := Form extent: self extent depth: 16. inBits := self bits. outBits := out bits. index := outIndex := 0. pvOut := 0. 0 to: self height-1 do:[:y| 0 to: self width-1 do:[:x| pv := inBits at: (index := index + 1). dmv := ditherMatrix at: (y bitAnd: 3) * 4 + (x bitAnd: 3) + 1. r := pv bitAnd: 255. di := r * 496 bitShift: -8. dmi := di bitAnd: 15. dmo := di bitShift: -4. r := dmv < dmi ifTrue:[ii at: 2+dmo] ifFalse:[ii at: 1+dmo]. g := (pv bitShift: -8) bitAnd: 255. di := g * 496 bitShift: -8. dmi := di bitAnd: 15. dmo := di bitShift: -4. g := dmv < dmi ifTrue:[ii at: 2+dmo] ifFalse:[ii at: 1+dmo]. b := (pv bitShift: -16) bitAnd: 255. di := b * 496 bitShift: -8. dmi := di bitAnd: 15. dmo := di bitShift: -4. b := dmv < dmi ifTrue:[ii at: 2+dmo] ifFalse:[ii at: 1+dmo]. pvOut := (pvOut bitShift: 16) + (b bitShift: 10) + (g bitShift: 5) + r. (x bitAnd: 1) = 1 ifTrue:[ outBits at: (outIndex := outIndex+1) put: pvOut. pvOut := 0]. ]. (self width bitAnd: 1) = 1 ifTrue:[ outBits at: (outIndex := outIndex+1) put: (pvOut bitShift: -16). pvOut := 0]. ]. ^out! ! !Form methodsFor: 'copying' stamp: 'RAA 9/28/1999 11:20'! blankCopyOf: aRectangle scaledBy: scale ^ self class extent: (aRectangle extent * scale) truncated depth: depth! ! !Form methodsFor: 'copying' stamp: 'ar 6/9/2000 18:59'! contentsOfArea: aRect "Return a new form which derives from the portion of the original form delineated by aRect." ^self contentsOfArea: aRect into: (self class extent: aRect extent depth: depth).! ! !Form methodsFor: 'copying' stamp: 'ar 6/9/2000 19:00'! contentsOfArea: aRect into: newForm "Return a new form which derives from the portion of the original form delineated by aRect." ^ newForm copyBits: aRect from: self at: 0@0 clippingBox: newForm boundingBox rule: Form over fillColor: nil! ! !Form methodsFor: 'copying' stamp: 'ar 5/28/2000 12:08'! copyBits: sourceForm at: destOrigin translucent: factor "Make up a BitBlt table and copy the bits with the given colorMap." (BitBlt current destForm: self sourceForm: sourceForm halftoneForm: nil combinationRule: 30 destOrigin: destOrigin sourceOrigin: 0@0 extent: sourceForm extent clipRect: self boundingBox) copyBitsTranslucent: ((0 max: (factor*255.0) asInteger) min: 255) " | f f2 f3 | f := Form fromUser. f2 := Form fromDisplay: (0@0 extent: f extent). f3 := f2 deepCopy. 0.0 to: 1.0 by: 1.0/32 do: [:t | f3 := f2 deepCopy. f3 copyBits: f at: 0@0 translucent: t. f3 displayAt: 0@0. (Delay forMilliseconds: 100) wait]. "! ! !Form methodsFor: 'copying' stamp: 'ar 5/28/2000 12:08'! copyBits: sourceRect from: sourceForm at: destOrigin clippingBox: clipRect rule: rule fillColor: aForm "Make up a BitBlt table and copy the bits." (BitBlt current destForm: self sourceForm: sourceForm fillColor: aForm combinationRule: rule destOrigin: destOrigin sourceOrigin: sourceRect origin extent: sourceRect extent clipRect: clipRect) copyBits! ! !Form methodsFor: 'copying' stamp: 'ar 5/28/2000 12:08'! copyBits: sourceRect from: sourceForm at: destOrigin clippingBox: clipRect rule: rule fillColor: aForm map: map "Make up a BitBlt table and copy the bits. Use a colorMap." ((BitBlt current destForm: self sourceForm: sourceForm fillColor: aForm combinationRule: rule destOrigin: destOrigin sourceOrigin: sourceRect origin extent: sourceRect extent clipRect: clipRect) colorMap: map) copyBits! ! !Form methodsFor: 'copying' stamp: 'ar 5/28/2000 12:08'! copyBits: sourceRect from: sourceForm at: destOrigin colorMap: map "Make up a BitBlt table and copy the bits with the given colorMap." ((BitBlt current destForm: self sourceForm: sourceForm halftoneForm: nil combinationRule: Form over destOrigin: destOrigin sourceOrigin: sourceRect origin extent: sourceRect extent clipRect: self boundingBox) colorMap: map) copyBits! ! !Form methodsFor: 'copying'! copy: aRect "Return a new form which derives from the portion of the original form delineated by aRect." | newForm | newForm := self class extent: aRect extent depth: depth. ^ newForm copyBits: aRect from: self at: 0@0 clippingBox: newForm boundingBox rule: Form over fillColor: nil! ! !Form methodsFor: 'copying' stamp: 'ar 5/28/2000 12:08'! copy: destRectangle from: sourcePt in: sourceForm rule: rule "Make up a BitBlt table and copy the bits." (BitBlt current toForm: self) copy: destRectangle from: sourcePt in: sourceForm fillColor: nil rule: rule! ! !Form methodsFor: 'copying'! copy: sourceRectangle from: sourceForm to: destPt rule: rule ^ self copy: (destPt extent: sourceRectangle extent) from: sourceRectangle topLeft in: sourceForm rule: rule! ! !Form methodsFor: 'copying' stamp: 'jm 2/27/98 09:35'! deepCopy ^ self shallowCopy bits: bits copy; offset: offset copy ! ! !Form methodsFor: 'copying' stamp: 'tk 8/19/1998 16:11'! veryDeepCopyWith: deepCopier "Return self. I am immutable in the Morphic world. Do not record me." ^ self! ! !Form methodsFor: 'display box access'! boundingBox ^ Rectangle origin: 0 @ 0 corner: width @ height! ! !Form methodsFor: 'display box access'! computeBoundingBox ^ Rectangle origin: 0 @ 0 corner: width @ height! ! !Form methodsFor: 'displaying' stamp: 'ar 2/13/2001 22:13'! displayInterpolatedIn: aRectangle on: aForm "Display the receiver on aForm, using interpolation if necessary. Form fromUser displayInterpolatedOn: Display. Note: When scaling we attempt to use bilinear interpolation based on the 3D engine. If the engine is not there then we use WarpBlt. " | engine adjustedR | self extent = aRectangle extent ifTrue:[^self displayOn: aForm at: aRectangle origin]. Smalltalk at: #B3DRenderEngine ifPresent:[:engineClass| engine := (engineClass defaultForPlatformOn: aForm)]. engine ifNil:[ "We've got no bilinear interpolation. Use WarpBlt instead" (WarpBlt current toForm: aForm) sourceForm: self destRect: aRectangle; combinationRule: 3; cellSize: 2; warpBits. ^self ]. "Otherwise use the 3D engine for our purposes" "there seems to be a slight bug in B3D which the following adjusts for" adjustedR := (aRectangle withRight: aRectangle right + 1) translateBy: 0@1. engine viewport: adjustedR. engine material: ((Smalltalk at: #B3DMaterial) new emission: Color white). engine texture: self. engine render: ((Smalltalk at: #B3DIndexedQuadMesh) new plainTextureRect). engine finish.! ! !Form methodsFor: 'displaying' stamp: 'ar 2/13/2001 22:12'! displayInterpolatedOn: aForm "Display the receiver on aForm, using interpolation if necessary. Form fromUser displayInterpolatedOn: Display. Note: When scaling we attempt to use bilinear interpolation based on the 3D engine. If the engine is not there then we use WarpBlt. " | engine | self extent = aForm extent ifTrue:[^self displayOn: aForm]. Smalltalk at: #B3DRenderEngine ifPresent:[:engineClass| engine := (engineClass defaultForPlatformOn: aForm)]. engine ifNil:[ "We've got no bilinear interpolation. Use WarpBlt instead" (WarpBlt current toForm: aForm) sourceForm: self destRect: aForm boundingBox; combinationRule: 3; cellSize: 2; warpBits. ^self ]. "Otherwise use the 3D engine for our purposes" engine viewport: aForm boundingBox. engine material: ((Smalltalk at: #B3DMaterial) new emission: Color white). engine texture: self. engine render: ((Smalltalk at: #B3DIndexedQuadMesh) new plainTextureRect). engine finish.! ! !Form methodsFor: 'displaying'! displayOnPort: port at: location port copyForm: self to: location rule: Form over! ! !Form methodsFor: 'displaying' stamp: 'ar 5/14/2001 23:33'! displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: rule fillColor: aForm aDisplayMedium copyBits: self boundingBox from: self at: aDisplayPoint + self offset clippingBox: clipRectangle rule: rule fillColor: aForm map: (self colormapIfNeededFor: aDisplayMedium). ! ! !Form methodsFor: 'displaying'! displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: alignmentPoint with: relativePoint rule: ruleInteger fillColor: aForm "Graphically, it means nothing to scale a Form by floating point values. Because scales and other display parameters are kept in floating point to minimize round off errors, we are forced in this routine to round off to the nearest integer." | absolutePoint scale magnifiedForm | absolutePoint := displayTransformation applyTo: relativePoint. absolutePoint := absolutePoint x asInteger @ absolutePoint y asInteger. displayTransformation noScale ifTrue: [magnifiedForm := self] ifFalse: [scale := displayTransformation scale. scale := scale x @ scale y. (1@1 = scale) ifTrue: [scale := nil. magnifiedForm := self] ifFalse: [magnifiedForm := self magnify: self boundingBox by: scale]]. magnifiedForm displayOn: aDisplayMedium at: absolutePoint - alignmentPoint clippingBox: clipRectangle rule: ruleInteger fillColor: aForm! ! !Form methodsFor: 'displaying' stamp: 'ar 5/17/2001 15:40'! displayResourceFormOn: aForm "a special display method for blowing up resource thumbnails" | engine tx cmap blitter | self extent = aForm extent ifTrue:[^self displayOn: aForm]. Smalltalk at: #B3DRenderEngine ifPresentAndInMemory: [:engineClass | engine := engineClass defaultForPlatformOn: aForm]. engine ifNil:[ "We've got no bilinear interpolation. Use WarpBlt instead" (WarpBlt current toForm: aForm) sourceForm: self destRect: aForm boundingBox; combinationRule: 3; cellSize: 2; warpBits. ^self ]. tx := self asTexture. (blitter := BitBlt current toForm: tx) sourceForm: self; destRect: aForm boundingBox; sourceOrigin: 0@0; combinationRule: Form paint. "map transparency to current World background color" (World color respondsTo: #pixelWordForDepth:) ifTrue: [ cmap := Bitmap new: (self depth <= 8 ifTrue: [1 << self depth] ifFalse: [4096]). cmap at: 1 put: (tx pixelWordFor: World color). blitter colorMap: cmap. ]. blitter copyBits. engine viewport: aForm boundingBox. engine material: ((Smalltalk at: #B3DMaterial) new emission: Color white). engine texture: tx. engine render: ((Smalltalk at: #B3DIndexedQuadMesh) new plainTextureRect). engine finish. "the above, using bilinear interpolation doesn't leave transparent pixel values intact" (WarpBlt current toForm: aForm) sourceForm: self destRect: aForm boundingBox; combinationRule: Form and; colorMap: (Color maskingMap: self depth); warpBits.! ! !Form methodsFor: 'displaying' stamp: 'ar 3/2/2001 21:32'! displayScaledOn: aForm "Display the receiver on aForm, scaling if necessary. Form fromUser displayScaledOn: Display. " self extent = aForm extent ifTrue:[^self displayOn: aForm]. (WarpBlt current toForm: aForm) sourceForm: self destRect: aForm boundingBox; combinationRule: Form paint; cellSize: 2; warpBits.! ! !Form methodsFor: 'displaying' stamp: 'ar 5/28/2000 12:08'! drawLine: sourceForm from: beginPoint to: endPoint clippingBox: clipRect rule: anInteger fillColor: aForm "Refer to the comment in DisplayMedium|drawLine:from:to:clippingBox:rule:mask:." | dotSetter | "set up an instance of BitBlt for display" dotSetter := BitBlt current destForm: self sourceForm: sourceForm fillColor: aForm combinationRule: anInteger destOrigin: beginPoint sourceOrigin: 0 @ 0 extent: sourceForm extent clipRect: clipRect. dotSetter drawFrom: beginPoint to: endPoint! ! !Form methodsFor: 'displaying' stamp: 'ar 5/28/2000 12:08'! paintBits: sourceForm at: destOrigin translucent: factor "Make up a BitBlt table and copy the bits with the given colorMap." (BitBlt current destForm: self sourceForm: sourceForm halftoneForm: nil combinationRule: 31 destOrigin: destOrigin sourceOrigin: 0@0 extent: sourceForm extent clipRect: self boundingBox) copyBitsTranslucent: ((0 max: (factor*255.0) asInteger) min: 255) " | f f2 f3 | f := Form fromUser. f replaceColor: f peripheralColor withColor: Color transparent. f2 := Form fromDisplay: (0@0 extent: f extent). f3 := f2 deepCopy. 0.0 to: 1.0 by: 1.0/32 do: [:t | f3 := f2 deepCopy. f3 paintBits: f at: 0@0 translucent: t. f3 displayAt: 0@0. (Delay forMilliseconds: 100) wait]. "! ! !Form methodsFor: 'filein/out' stamp: 'ar 2/24/2001 22:41'! comeFullyUpOnReload: smartRefStream bits isForm ifFalse:[^self]. "make sure the resource gets loaded afterwards" ResourceCollector current ifNil:[^self]. ResourceCollector current noteResource: bits replacing: self. ! ! !Form methodsFor: 'filein/out' stamp: 'di 8/5/1998 11:37'! hibernate "Replace my bitmap with a compactly encoded representation (a ByteArray). It is vital that BitBlt and any other access to the bitmap (such as writing to a file) not be used when in this state. Since BitBlt will fail if the bitmap size is wrong (not = bitsSize), we do not allow replacement by a byteArray of the same (or larger) size." "NOTE: This method copies code from Bitmap compressToByteArray so that it can nil out the old bits during the copy, thus avoiding 2x need for extra storage." | compactBits lastByte | (bits isMemberOf: Bitmap) ifFalse: [^ self "already hibernated or weird state"]. compactBits := ByteArray new: (bits size*4) + 7 + (bits size//1984*3). lastByte := bits compress: bits toByteArray: compactBits. lastByte < (bits size*4) ifTrue: [bits := nil. "Let GC reclaim the old bits before the copy if necessary" bits := compactBits copyFrom: 1 to: lastByte]! ! !Form methodsFor: 'filein/out' stamp: 'ar 3/3/2001 16:16'! objectForDataStream: refStream | prj repl | prj := refStream project. prj ifNil:[^super objectForDataStream: refStream]. ResourceCollector current ifNil:[^super objectForDataStream: refStream]. repl := ResourceCollector current objectForDataStream: refStream fromForm: self. ^repl! ! !Form methodsFor: 'filein/out' stamp: 'di 3/15/1999 14:50'! printOn: aStream aStream nextPutAll: self class name; nextPut: $(; print: width; nextPut: $x; print: height; nextPut: $x; print: depth; nextPut: $). ! ! !Form methodsFor: 'filein/out' stamp: 'mu 8/17/2003 00:44'! readAttributesFrom: aBinaryStream | offsetX offsetY | depth := aBinaryStream next. (self depth isPowerOfTwo and: [self depth between: 1 and: 32]) ifFalse: [self error: 'invalid depth; bad Form file?']. width := aBinaryStream nextWord. height := aBinaryStream nextWord. offsetX := aBinaryStream nextWord. offsetY := aBinaryStream nextWord. offsetX > 32767 ifTrue: [offsetX := offsetX - 65536]. offsetY > 32767 ifTrue: [offsetY := offsetY - 65536]. offset := Point x: offsetX y: offsetY. ! ! !Form methodsFor: 'filein/out' stamp: 'mu 8/17/2003 00:43'! readBitsFrom: aBinaryStream bits := Bitmap newFromStream: aBinaryStream. bits size = self bitsSize ifFalse: [self error: 'wrong bitmap size; bad Form file?']. ^ self ! ! !Form methodsFor: 'filein/out' stamp: 'mu 8/17/2003 00:44'! readFrom: aBinaryStream "Reads the receiver from the given binary stream with the format: depth, extent, offset, bits." self readAttributesFrom: aBinaryStream. self readBitsFrom: aBinaryStream! ! !Form methodsFor: 'filein/out' stamp: 'jm 3/27/98 16:54'! readFromOldFormat: aBinaryStream "Read a Form in the original ST-80 format." | w h offsetX offsetY newForm theBits pos | self error: 'this method must be updated to read into 32-bit word bitmaps'. w := aBinaryStream nextWord. h := aBinaryStream nextWord. offsetX := aBinaryStream nextWord. offsetY := aBinaryStream nextWord. offsetX > 32767 ifTrue: [offsetX := offsetX - 65536]. offsetY > 32767 ifTrue: [offsetY := offsetY - 65536]. newForm := Form extent: w @ h offset: offsetX @ offsetY. theBits := newForm bits. pos := 0. 1 to: w + 15 // 16 do: [:j | 1 to: h do: [:i | theBits at: (pos := pos+1) put: aBinaryStream nextWord]]. newForm bits: theBits. ^ newForm ! ! !Form methodsFor: 'filein/out' stamp: 'ar 2/24/2001 22:39'! replaceByResource: aForm "Replace the receiver by some resource that just got loaded" (self extent = aForm extent and:[self depth = aForm depth]) ifTrue:[ bits := aForm bits. ].! ! !Form methodsFor: 'filein/out' stamp: 'nk 12/31/2003 16:06'! store15To24HexBitsOn:aStream | buf i lineWidth | "write data for 16-bit form, optimized for encoders writing directly to files to do one single file write rather than 12. I'm not sure I understand the significance of the shifting pattern, but I think I faithfully translated it from the original" lineWidth := 0. buf := String new: 12. bits do: [:word | i := 0. "upper pixel" buf at: (i := i + 1) put: ((word bitShift: -27) bitAnd: 15) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -32) bitAnd: 8) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -22) bitAnd: 15) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -27) bitAnd: 8) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -17) bitAnd: 15) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -22) bitAnd: 8) asHexDigit. "lower pixel" buf at: (i := i + 1) put: ((word bitShift: -11) bitAnd: 15) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -16) bitAnd: 8) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -6) bitAnd: 15) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -11) bitAnd: 8) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -1) bitAnd: 15) asHexDigit. buf at: (i := i + 1) put: ((word bitShift: -6) bitAnd: 8) asHexDigit. aStream nextPutAll: buf. lineWidth := lineWidth + 12. lineWidth > 100 ifTrue: [ aStream cr. lineWidth := 0 ]. "#( 31 26 21 15 10 5 ) do:[:startBit | ]" ].! ! !Form methodsFor: 'filein/out'! store32To24HexBitsOn:aStream ^self storeBits:20 to:0 on:aStream.! ! !Form methodsFor: 'filein/out'! storeBits:startBit to:stopBit on:aStream bits storeBits:startBit to:stopBit on:aStream.! ! !Form methodsFor: 'filein/out' stamp: 'laza 3/29/2004 12:21'! storeBitsOn:aStream base:anInteger bits do: [:word | anInteger = 10 ifTrue: [aStream space] ifFalse: [aStream crtab: 2]. word storeOn: aStream base: anInteger]. ! ! !Form methodsFor: 'filein/out'! storeHexBitsOn:aStream ^self storeBits:28 to:0 on:aStream.! ! !Form methodsFor: 'filein/out'! storeOn: aStream self storeOn: aStream base: 10! ! !Form methodsFor: 'filein/out'! storeOn: aStream base: anInteger "Store the receiver out as an expression that can be evaluated to recreate a Form with the same contents as the original." self unhibernate. aStream nextPut: $(. aStream nextPutAll: self species name. aStream crtab: 1. aStream nextPutAll: 'extent: '. self extent printOn: aStream. aStream crtab: 1. aStream nextPutAll: 'depth: '. self depth printOn: aStream. aStream crtab: 1. aStream nextPutAll: 'fromArray: #('. self storeBitsOn:aStream base:anInteger. aStream nextPut: $). aStream crtab: 1. aStream nextPutAll: 'offset: '. self offset printOn: aStream. aStream nextPut: $). ! ! !Form methodsFor: 'filein/out' stamp: 'ar 3/3/2001 15:50'! unhibernate "If my bitmap has been compressed into a ByteArray, then expand it now, and return true." | resBits | bits isForm ifTrue:[ resBits := bits. bits := Bitmap new: self bitsSize. resBits displayResourceFormOn: self. ^true]. bits == nil ifTrue:[bits := Bitmap new: self bitsSize. ^true]. (bits isMemberOf: ByteArray) ifTrue: [bits := Bitmap decompressFromByteArray: bits. ^ true]. ^ false! ! !Form methodsFor: 'filein/out' stamp: 'mu 8/17/2003 00:35'! writeAttributesOn: file self unhibernate. file nextPut: depth. file nextWordPut: width. file nextWordPut: height. file nextWordPut: ((self offset x) >=0 ifTrue: [self offset x] ifFalse: [self offset x + 65536]). file nextWordPut: ((self offset y) >=0 ifTrue: [self offset y] ifFalse: [self offset y + 65536]). ! ! !Form methodsFor: 'filein/out' stamp: 'ar 6/16/2002 17:53'! writeBMPfileNamed: fName "Display writeBMPfileNamed: 'display.bmp'" BMPReadWriter putForm: self onFileNamed: fName! ! !Form methodsFor: 'filein/out' stamp: 'mu 8/17/2003 00:35'! writeBitsOn: file bits writeOn: file! ! !Form methodsFor: 'filein/out' stamp: 'sw 2/20/2002 15:37'! writeJPEGfileNamed: fileName "Write a JPEG file to the given filename using default settings" self writeJPEGfileNamed: fileName progressive: false " Display writeJPEGfileNamed: 'display.jpeg' Form fromUser writeJPEGfileNamed: 'yourPatch.jpeg' "! ! !Form methodsFor: 'filein/out' stamp: 'sw 2/20/2002 15:29'! writeJPEGfileNamed: fileName progressive: aBoolean "Write a JPEG file to the given filename using default settings. Make it progressive or not, depending on the boolean argument" JPEGReadWriter2 putForm: self quality: -1 "default" progressiveJPEG: aBoolean onFileNamed: fileName " Display writeJPEGfileNamed: 'display.jpeg' progressive: false. Form fromUser writeJPEGfileNamed: 'yourPatch.jpeg' progressive: true "! ! !Form methodsFor: 'filein/out' stamp: 'mu 8/17/2003 00:36'! writeOn: file "Write the receiver on the file in the format depth, extent, offset, bits." self writeAttributesOn: file. self writeBitsOn: file! ! !Form methodsFor: 'filein/out' stamp: 'di 7/6/1998 23:00'! writeOnMovie: file "Write just my bits on the file." self unhibernate. bits writeUncompressedOn: file! ! !Form methodsFor: 'filein/out' stamp: 'tk 2/19/1999 07:30'! writeUncompressedOn: file "Write the receiver on the file in the format depth, extent, offset, bits. Warning: Caller must put header info on file!! Use writeUncompressedOnFileNamed: instead." self unhibernate. file binary. file nextPut: depth. file nextWordPut: width. file nextWordPut: height. file nextWordPut: ((self offset x) >=0 ifTrue: [self offset x] ifFalse: [self offset x + 65536]). file nextWordPut: ((self offset y) >=0 ifTrue: [self offset y] ifFalse: [self offset y + 65536]). bits writeUncompressedOn: file! ! !Form methodsFor: 'filling' stamp: 'di 2/19/1999 07:07'! anyShapeFill "Fill the interior of the outermost outlined region in the receiver, a 1-bit deep form. Typically the resulting form is used with fillShape:fillColor: to paint a solid color. See also convexShapeFill:" | shape | "Draw a seed line around the edge and fill inward from the outside." shape := self findShapeAroundSeedBlock: [:f | f borderWidth: 1]. "Reverse so that this becomes solid in the middle" shape := shape reverse. "Finally erase any bits from the original so the fill is only elsewhere" shape copy: shape boundingBox from: self to: 0@0 rule: Form erase. ^ shape! ! !Form methodsFor: 'filling'! bitPatternForDepth: suspectedDepth "Only called when a Form is being used as a fillColor. Use a Pattern or InfiniteForm instead for this purpose. Interpret me as an array of (32/depth) Color pixelValues. BitBlt aligns the first element of this array with the top scanline of the destinationForm, the second with the second, and so on, cycling through the color array as necessary. 6/18/96 tk" ^ self! ! !Form methodsFor: 'filling' stamp: 'di 9/11/1998 16:25'! convexShapeFill: aMask "Fill the interior of the outtermost outlined region in the receiver. The outlined region must not be concave by more than 90 degrees. Typically aMask is Color black, to produce a solid fill. then the resulting form is used with fillShape: to paint a solid color. See also anyShapeFill" | destForm tempForm | destForm := Form extent: self extent. destForm fillBlack. tempForm := Form extent: self extent. (0@0) fourNeighbors do: [:dir | "Smear self in all 4 directions, and AND the result" self displayOn: tempForm at: (0@0) - self offset. tempForm smear: dir distance: (dir dotProduct: tempForm extent) abs. tempForm displayOn: destForm at: 0@0 clippingBox: destForm boundingBox rule: Form and fillColor: nil]. destForm displayOn: self at: 0@0 clippingBox: self boundingBox rule: Form over fillColor: aMask! ! !Form methodsFor: 'filling' stamp: 'di 10/17/2001 10:09'! eraseShape: bwForm "use bwForm as a mask to clear all pixels where bwForm has 1's" ((BitBlt current destForm: self sourceForm: bwForm fillColor: nil combinationRule: Form erase1bitShape "Cut a hole in the picture with my mask" destOrigin: bwForm offset sourceOrigin: 0@0 extent: self extent clipRect: self boundingBox) colorMap: (Bitmap with: 0 with: 16rFFFFFFFF)) copyBits. ! ! !Form methodsFor: 'filling'! fillFromXColorBlock: colorBlock "Horizontal Gradient Fill. Supply relative x in [0.0 ... 1.0] to colorBlock, and paint each pixel with the color that comes back" | xRel | 0 to: width-1 do: [:x | xRel := x asFloat / (width-1) asFloat. self fill: (x@0 extent: 1@height) fillColor: (colorBlock value: xRel)] " ((Form extent: 100@100 depth: Display depth) fillFromXColorBlock: [:x | Color r: x g: 0.0 b: 0.5]) display "! ! !Form methodsFor: 'filling' stamp: 'ar 5/17/2001 15:38'! fillFromXYColorBlock: colorBlock "General Gradient Fill. Supply relative x and y in [0.0 ... 1.0] to colorBlock, and paint each pixel with the color that comes back" | poker yRel xRel | poker := BitBlt current bitPokerToForm: self. 0 to: height-1 do: [:y | yRel := y asFloat / (height-1) asFloat. 0 to: width-1 do: [:x | xRel := x asFloat / (width-1) asFloat. poker pixelAt: x@y put: ((colorBlock value: xRel value: yRel) pixelWordForDepth: self depth)]] " | d | ((Form extent: 100@20 depth: Display depth) fillFromXYColorBlock: [:x :y | d := 1.0 - (x - 0.5) abs - (y - 0.5) abs. Color r: d g: 0 b: 1.0-d]) display "! ! !Form methodsFor: 'filling'! fillFromYColorBlock: colorBlock "Vertical Gradient Fill. Supply relative y in [0.0 ... 1.0] to colorBlock, and paint each pixel with the color that comes back" | yRel | 0 to: height-1 do: [:y | yRel := y asFloat / (height-1) asFloat. self fill: (0@y extent: width@1) fillColor: (colorBlock value: yRel)] " ((Form extent: 100@100 depth: Display depth) fillFromYColorBlock: [:y | Color r: y g: 0.0 b: 0.5]) display "! ! !Form methodsFor: 'filling' stamp: 'ar 5/28/2000 12:08'! fill: aRectangle rule: anInteger fillColor: aForm "Replace a rectangular area of the receiver with the pattern described by aForm according to the rule anInteger." (BitBlt current toForm: self) copy: aRectangle from: 0@0 in: nil fillColor: aForm rule: anInteger! ! !Form methodsFor: 'filling' stamp: 'ar 5/17/2001 15:38'! findShapeAroundSeedBlock: seedBlock "Build a shape that is black in any region marked by seedBlock. SeedBlock will be supplied a form, in which to blacken various pixels as 'seeds'. Then the seeds are smeared until there is no change in the smear when it fills the region, ie, when smearing hits a black border and thus goes no further." | smearForm previousSmear all count smearPort | self depth > 1 ifTrue: [self halt]. "Only meaningful for B/W forms." all := self boundingBox. smearForm := Form extent: self extent. smearPort := BitBlt current toForm: smearForm. seedBlock value: smearForm. "Blacken seeds to be smeared" smearPort copyForm: self to: 0@0 rule: Form erase. "Clear any in black" previousSmear := smearForm deepCopy. count := 1. [count = 10 and: "check for no change every 10 smears" [count := 1. previousSmear copy: all from: 0@0 in: smearForm rule: Form reverse. previousSmear isAllWhite]] whileFalse: [smearPort copyForm: smearForm to: 1@0 rule: Form under. smearPort copyForm: smearForm to: -1@0 rule: Form under. "After horiz smear, trim around the region border" smearPort copyForm: self to: 0@0 rule: Form erase. smearPort copyForm: smearForm to: 0@1 rule: Form under. smearPort copyForm: smearForm to: 0@-1 rule: Form under. "After vert smear, trim around the region border" smearPort copyForm: self to: 0@0 rule: Form erase. count := count+1. count = 9 ifTrue: "Save penultimate smear for comparison" [previousSmear copy: all from: 0@0 in: smearForm rule: Form over]]. "Now paint the filled region in me with aHalftone" ^ smearForm! ! !Form methodsFor: 'filling' stamp: 'ar 5/14/2001 23:46'! floodFill2: aColor at: interiorPoint "Fill the shape (4-connected) at interiorPoint. The algorithm is based on Paul Heckbert's 'A Seed Fill Algorithm', Graphic Gems I, Academic Press, 1990. NOTE: This is a less optimized variant for flood filling which is precisely along the lines of Heckbert's algorithm. For almost all cases #floodFill:at: will be faster (see the comment there) but this method is left in both as reference and as a fallback if such a strange case is encountered in reality." | peeker poker stack old new x y top x1 x2 dy left goRight | peeker := BitBlt current bitPeekerFromForm: self. poker := BitBlt current bitPokerToForm: self. stack := OrderedCollection new: 50. "read old pixel value" old := peeker pixelAt: interiorPoint. "compute new value" new := self pixelValueFor: aColor. old = new ifTrue:[^self]. "no point, is there?!!" x := interiorPoint x. y := interiorPoint y. (y >= 0 and:[y < height]) ifTrue:[ stack addLast: {y. x. x. 1}. "y, left, right, dy" stack addLast: {y+1. x. x. -1}]. [stack isEmpty] whileFalse:[ top := stack removeLast. y := top at: 1. x1 := top at: 2. x2 := top at: 3. dy := top at: 4. y := y + dy. "Segment of scanline (y-dy) for x1 <= x <= x2 was previously filled. Now explore adjacent pixels in scanline y." x := x1. [x >= 0 and:[(peeker pixelAt: x@y) = old]] whileTrue:[ poker pixelAt: x@y put: new. x := x - 1]. goRight := x < x1. left := x+1. (left < x1 and:[y-dy >= 0 and:[y-dy < height]]) ifTrue:[stack addLast: {y. left. x1-1. 0-dy}]. goRight ifTrue:[x := x1 + 1]. [ goRight ifTrue:[ [x < width and:[(peeker pixelAt: x@y) = old]] whileTrue:[ poker pixelAt: x@y put: new. x := x + 1]. (y+dy >= 0 and:[y+dy < height]) ifTrue:[stack addLast: {y. left. x-1. dy}]. (x > (x2+1) and:[y-dy >= 0 and:[y-dy >= 0]]) ifTrue:[stack addLast: {y. x2+1. x-1. 0-dy}]]. [(x := x + 1) <= x2 and:[(peeker pixelAt: x@y) ~= old]] whileTrue. left := x. goRight := true. x <= x2] whileTrue. ]. ! ! !Form methodsFor: 'filling' stamp: 'di 10/20/2001 10:09'! floodFillMapFrom: sourceForm to: scanlineForm mappingColorsWithin: dist to: centerPixVal "This is a helper routine for floodFill. It's written for clarity (scanning the entire map using colors) rather than speed (which would require hacking rgb components in the nieghborhood of centerPixVal. Note that some day a better proximity metric would be (h s v) where tolerance could be reduced in hue." | colorMap centerColor | scanlineForm depth = 32 ifFalse: [self error: 'depth 32 assumed']. "First get a modifiable identity map" colorMap := (Color cachedColormapFrom: sourceForm depth to: scanlineForm depth) copy. centerColor := Color colorFromPixelValue: (centerPixVal bitOr: 16rFFe6) depth: scanlineForm depth. "Now replace all entries that are close to the centerColor" 1 to: colorMap size do: [:i | ((Color colorFromPixelValue: ((colorMap at: i) bitOr: 16rFFe6) depth: scanlineForm depth) diff: centerColor) <= dist ifTrue: [colorMap at: i put: centerPixVal]]. ^ colorMap! ! !Form methodsFor: 'filling' stamp: 'di 10/20/2001 22:03'! floodFill: aColor at: interiorPoint Preferences areaFillsAreVeryTolerant ifTrue: [^ self floodFill: aColor at: interiorPoint tolerance: 0.2]. Preferences areaFillsAreTolerant ifTrue: [^ self floodFill: aColor at: interiorPoint tolerance: 0.1]. ^ self floodFill: aColor at: interiorPoint tolerance: 0 ! ! !Form methodsFor: 'filling' stamp: 'di 10/20/2001 08:47'! floodFill: aColor at: interiorPoint tolerance: tolerance "Fill the shape (4-connected) at interiorPoint. The algorithm is based on Paul Heckbert's 'A Seed Fill Algorithm', Graphic Gems I, Academic Press, 1990. NOTE (ar): This variant has been heavily optimized to prevent the overhead of repeated calls to BitBlt. Usually this is a really big winner but the runtime now depends a bit on the complexity of the shape to be filled. For extremely complex shapes (say, a Hilbert curve) with very few pixels to fill it can be slower than #floodFill2:at: since it needs to repeatedly read the source bits. However, in all practical cases I found this variant to be 15-20 times faster than anything else. Further note (di): I have added a feature that allows this routine to fill areas of approximately constant color (such as photos, scans, and jpegs). It does this by computing a color map for the peeker that maps all colors close to 'old' into colors identical to old. This mild colorblindness achieves the desired effect with no further change or degradation of the algorithm. tolerance should be 0 (exact match), or a value corresponding to those returned by Color>>diff:, with 0.1 being a reasonable starting choice." | peeker poker stack old new x y top x1 x2 dy left goRight span spanBits w box debug | debug := false. "set it to true to see the filling process" box := interiorPoint extent: 1@1. span := Form extent: width@1 depth: 32. spanBits := span bits. peeker := BitBlt current toForm: span. peeker sourceForm: self; combinationRule: 3; width: width; height: 1. "read old pixel value" peeker sourceOrigin: interiorPoint; destOrigin: interiorPoint x @ 0; width: 1; copyBits. old := spanBits at: interiorPoint x + 1. "compute new value (take care since the algorithm will fail if old = new)" new := self privateFloodFillValue: aColor. old = new ifTrue: [^ box]. tolerance > 0 ifTrue: ["Set up color map for approximate fills" peeker colorMap: (self floodFillMapFrom: self to: span mappingColorsWithin: tolerance to: old)]. poker := BitBlt current toForm: self. poker fillColor: aColor; combinationRule: 3; width: width; height: 1. stack := OrderedCollection new: 50. x := interiorPoint x. y := interiorPoint y. (y >= 0 and:[y < height]) ifTrue:[ stack addLast: {y. x. x. 1}. "y, left, right, dy" stack addLast: {y+1. x. x. -1}]. [stack isEmpty] whileFalse:[ debug ifTrue:[self displayOn: Display]. top := stack removeLast. y := top at: 1. x1 := top at: 2. x2 := top at: 3. dy := top at: 4. y := y + dy. debug ifTrue:[ (Line from: (x1-1)@y to: (x2+1)@y withForm: (Form extent: 1@1 depth: 8) fillWhite) displayOn: Display]. "Segment of scanline (y-dy) for x1 <= x <= x2 was previously filled. Now explore adjacent pixels in scanline y." peeker sourceOrigin: 0@y; destOrigin: 0@0; width: width; copyBits. "Note: above is necessary since we don't know where we'll end up filling" x := x1. w := 0. [x >= 0 and:[(spanBits at: x+1) = old]] whileTrue:[ w := w + 1. x := x - 1]. w > 0 ifTrue:[ "overwrite pixels" poker destOrigin: x+1@y; width: w; copyBits. box := box quickMerge: ((x+1@y) extent: w@1)]. goRight := x < x1. left := x+1. (left < x1 and:[y-dy >= 0 and:[y-dy < height]]) ifTrue:[stack addLast: {y. left. x1-1. 0-dy}]. goRight ifTrue:[x := x1 + 1]. [ goRight ifTrue:[ w := 0. [x < width and:[(spanBits at: x+1) = old]] whileTrue:[ w := w + 1. x := x + 1]. w > 0 ifTrue:[ "overwrite pixels" poker destOrigin: (x-w)@y; width: w; copyBits. box := box quickMerge: ((x-w@y) extent: w@1)]. (y+dy >= 0 and:[y+dy < height]) ifTrue:[stack addLast: {y. left. x-1. dy}]. (x > (x2+1) and:[y-dy >= 0 and:[y-dy >= 0]]) ifTrue:[stack addLast: {y. x2+1. x-1. 0-dy}]]. [(x := x + 1) <= x2 and:[(spanBits at: x+1) ~= old]] whileTrue. left := x. goRight := true. x <= x2] whileTrue. ]. ^box! ! !Form methodsFor: 'filling' stamp: 'di 10/17/2001 10:10'! shapeFill: aColor interiorPoint: interiorPoint "Identify the shape (region of identical color) at interiorPoint, and then fill that shape with the new color, aColor : modified di's original method such that it returns the bwForm, for potential use by the caller" | bwForm interiorPixVal map ppd color ind | self depth = 1 ifTrue: [^ self shapeFill: aColor seedBlock: [:form | form pixelValueAt: interiorPoint put: 1]]. "First map this form into a B/W form with 0's in the interior region." "bwForm := self makeBWForm: interiorColor." "won't work for two whites" interiorPixVal := self pixelValueAt: interiorPoint. bwForm := Form extent: self extent. map := Bitmap new: (1 bitShift: (self depth min: 12)). "Not calling newColorMap. All non-foreground go to 0. Length is 2 to 4096." ppd := self depth. "256 long color map in depth 8 is not one of the following cases" 3 to: 5 do: [:bitsPerColor | (2 raisedTo: bitsPerColor*3) = map size ifTrue: [ppd := bitsPerColor*3]]. "ready for longer maps than 512" ppd <= 8 ifTrue: [map at: interiorPixVal+1 put: 1] ifFalse: [interiorPixVal = 0 ifFalse: [color := Color colorFromPixelValue: interiorPixVal depth: self depth. ind := color pixelValueForDepth: ppd. map at: ind+1 put: 1] ifTrue: [map at: 1 put: 1]]. bwForm copyBits: self boundingBox from: self at: 0@0 colorMap: map. bwForm reverse. "Make interior region be 0's" "Now fill the interior region and return that shape" bwForm := bwForm findShapeAroundSeedBlock: [:form | form pixelValueAt: interiorPoint put: 1]. "Finally use that shape as a mask to flood the region with color" self eraseShape: bwForm. self fillShape: bwForm fillColor: aColor. ^ bwForm! ! !Form methodsFor: 'filling' stamp: 'ar 5/17/2001 15:38'! shapeFill: aColor seedBlock: seedBlock self depth > 1 ifTrue: [self error: 'This call only meaningful for B/W forms']. (self findShapeAroundSeedBlock: seedBlock) displayOn: self at: 0@0 clippingBox: self boundingBox rule: Form under fillColor: aColor ! ! !Form methodsFor: 'image manipulation' stamp: 'ar 5/17/2001 15:40'! replaceColor: oldColor withColor: newColor "Replace one color with another everywhere is this form" | cm newInd target ff | self depth = 32 ifTrue: [cm := (Color cachedColormapFrom: 16 to: 32) copy] ifFalse: [cm := Bitmap new: (1 bitShift: (self depth min: 15)). 1 to: cm size do: [:i | cm at: i put: i - 1]]. newInd := newColor pixelValueForDepth: self depth. cm at: (oldColor pixelValueForDepth: (self depth min: 16))+1 put: newInd. target := newColor isTransparent ifTrue: [ff := Form extent: self extent depth: depth. ff fillWithColor: newColor. ff] ifFalse: [self]. (BitBlt current toForm: target) sourceForm: self; sourceOrigin: 0@0; combinationRule: Form paint; destX: 0 destY: 0 width: width height: height; colorMap: cm; copyBits. newColor = Color transparent ifTrue: [target displayOn: self].! ! !Form methodsFor: 'image manipulation' stamp: 'ar 5/28/2000 12:09'! smear: dir distance: dist "Smear any black pixels in this form in the direction dir in Log N steps" | skew bb | bb := BitBlt current destForm: self sourceForm: self fillColor: nil combinationRule: Form under destOrigin: 0@0 sourceOrigin: 0@0 extent: self extent clipRect: self boundingBox. skew := 1. [skew < dist] whileTrue: [bb destOrigin: dir*skew; copyBits. skew := skew+skew]! ! !Form methodsFor: 'image manipulation' stamp: 'LB 8/26/2002 18:08'! stencil "return a 1-bit deep, black-and-white stencil of myself" | canvas | canvas := FormCanvas extent: self extent depth: 1. canvas fillColor: (Color white). canvas stencil: self at: 0@0 sourceRect: (Rectangle origin: 0@0 corner: self extent) color: Color black. ^ canvas form ! ! !Form methodsFor: 'image manipulation' stamp: 'jm 6/30/1999 15:36'! trimBordersOfColor: aColor "Answer a copy of this Form with each edge trimmed in to the first pixel that is not of the given color. (That is, border strips of the given color are removed)." | r | r := self rectangleEnclosingPixelsNotOfColor: aColor. ^ self copy: r ! ! !Form methodsFor: 'initialization' stamp: 'ar 5/17/2001 22:54'! allocateForm: extentPoint "Allocate a new form which is similar to the receiver and can be used for accelerated blts" ^Form extent: extentPoint depth: self nativeDepth! ! !Form methodsFor: 'initialization' stamp: 'ar 5/26/2000 00:46'! finish "If there are any pending operations on the receiver complete them. Do not return before all modifications have taken effect."! ! !Form methodsFor: 'initialization' stamp: 'ar 5/26/2000 00:45'! flush "If there are any pending operations on the receiver start doing them. In time, they will show up on the receiver but not necessarily immediately after this method returns."! ! !Form methodsFor: 'initialization'! fromDisplay: aRectangle "Create a virtual bit map from a user specified rectangular area on the display screen. Reallocates bitmap only if aRectangle ~= the receiver's extent." (width = aRectangle width and: [height = aRectangle height]) ifFalse: [self setExtent: aRectangle extent depth: depth]. self copyBits: (aRectangle origin extent: self extent) from: Display at: 0 @ 0 clippingBox: self boundingBox rule: Form over fillColor: nil! ! !Form methodsFor: 'initialization' stamp: 'ar 5/28/2000 18:45'! shutDown "The system is going down. Try to preserve some space" self hibernate! ! !Form methodsFor: 'initialization' stamp: 'ar 6/16/2002 18:39'! swapEndianness "Swap from big to little endian pixels and vice versa" depth := 0 - depth.! ! !Form methodsFor: 'other' stamp: 'ar 12/12/2003 18:24'! fixAlpha "Fix the alpha channel if the receiver is 32bit" | bb | self depth = 32 ifFalse:[^self]. bb := BitBlt toForm: self. bb combinationRule: 40 "fixAlpha:with:". bb copyBits.! ! !Form methodsFor: 'other' stamp: 'jm 9/27/97 21:02'! formForColorCount: colorCount "Return a ColorForm of sufficient depth to represent the given number of colors. The maximum number of colors is 256." colorCount > 256 ifTrue: [^ self error: 'too many colors']. colorCount > 16 ifTrue: [^ ColorForm extent: self extent depth: 8]. colorCount > 4 ifTrue: [^ ColorForm extent: self extent depth: 4]. colorCount > 2 ifTrue: [^ ColorForm extent: self extent depth: 2]. ^ ColorForm extent: self extent depth: 1 ! ! !Form methodsFor: 'other' stamp: 'jm 1/6/98 10:37'! primPrintHScale: hScale vScale: vScale landscape: aBoolean "On platforms that support it, this primitive prints the receiver, assumed to be a Form, to the default printer." "(Form extent: 10@10) primPrintHScale: 1.0 vScale: 1.0 landscape: true" self primitiveFailed ! ! !Form methodsFor: 'other' stamp: 'RAA 1/30/2002 16:42'! relativeTextAnchorPosition ^nil "so forms can be in TextAnchors"! ! !Form methodsFor: 'other' stamp: 'alain.plantec 5/30/2008 13:28'! setAsBackground "Set this form as a background image." | world newColor | world := self currentWorld. newColor := InfiniteForm with: self. self rememberCommand: (Command new cmdWording: 'set background to a picture' translated; undoTarget: world selector: #color: argument: world color; redoTarget: world selector: #color: argument: newColor). world color: newColor! ! !Form methodsFor: 'pixel access' stamp: 'ar 5/17/2001 15:42'! colorAt: aPoint "Return the color in the pixel at the given point. " ^ Color colorFromPixelValue: (self pixelValueAt: aPoint) depth: self depth ! ! !Form methodsFor: 'pixel access' stamp: 'ar 5/14/2001 23:46'! colorAt: aPoint put: aColor "Store a Color into the pixel at coordinate aPoint. " self pixelValueAt: aPoint put: (self pixelValueFor: aColor). "[Sensor anyButtonPressed] whileFalse: [Display colorAt: Sensor cursorPoint put: Color red]" ! ! !Form methodsFor: 'pixel access' stamp: 'ar 5/17/2001 15:39'! isTransparentAt: aPoint "Return true if the receiver is transparent at the given point." self depth = 1 ifTrue: [^ false]. "no transparency at depth 1" ^ (self pixelValueAt: aPoint) = (self pixelValueFor: Color transparent) ! ! !Form methodsFor: 'pixel access' stamp: 'ar 5/28/2000 12:08'! pixelValueAt: aPoint "Return the raw pixel value at the given point. This pixel value depends on the receiver's depth. Typical clients use colorAt: to get a Color. " ^ (BitBlt current bitPeekerFromForm: self) pixelAt: aPoint ! ! !Form methodsFor: 'pixel access' stamp: 'ar 5/28/2000 12:08'! pixelValueAt: aPoint put: pixelValue "Store the given raw pixel value at the given point. Typical clients use colorAt:put: to store a color. " (BitBlt current bitPokerToForm: self) pixelAt: aPoint put: pixelValue. ! ! !Form methodsFor: 'postscript generation' stamp: 'ar 5/17/2001 15:36'! bitsPerComponent ^self depth <= 8 ifTrue:[self depth] ifFalse:[8]. ! ! !Form methodsFor: 'postscript generation' stamp: 'mpw 11/14/1999 22:22'! bytesPerRow ^ self numComponents * self paddedWidth * self bitsPerComponent / 8.! ! !Form methodsFor: 'postscript generation' stamp: 'ar 5/17/2001 15:39'! decodeArray ^self depth <= 8 ifTrue:['[1 0]'] ifFalse:['[0 1 0 1 0 1 ]']. ! ! !Form methodsFor: 'postscript generation' stamp: 'ar 5/17/2001 15:43'! numComponents ^self depth <= 8 ifTrue:[1] ifFalse:[3]. ! ! !Form methodsFor: 'postscript generation'! paddedWidth ^ (self width + (self rowPadding-1)// self rowPadding) * self rowPadding.! ! !Form methodsFor: 'postscript generation' stamp: 'nk 12/31/2003 15:46'! printPostscript: aStream operator: operator aStream preserveStateDuring: [:inner | inner rectclip: (0 @ 0 extent: width @ height). self setColorspaceOn: inner. inner print: '[ '; cr; print: '/ImageType 1'; cr; print: '/ImageMatrix [1 0 0 1 0 0]'; cr; print: '/MultipleDataSources false'; cr; print: '/DataSource level1 { { currentfile '; write: self bytesPerRow; print: ' string readhexstring pop }} bind { currentfile /ASCIIHexDecode filter } ifelse'; cr; print: '/Width '; write: self paddedWidth; cr; print: '/Height '; write: self height; cr; print: '/Decode '; print: self decodeArray; cr; print: '/BitsPerComponent '; write: self bitsPerComponent; cr; print: 'makeDict '; print: operator; cr. self storePostscriptHexOn: inner. inner print: $>; cr. inner cr]. aStream cr! ! !Form methodsFor: 'postscript generation' stamp: 'mpw 11/15/1999 08:34'! rowPadding ^ 32 // self depth! ! !Form methodsFor: 'postscript generation'! setColorspaceOn:aStream self numComponents = 1 ifTrue:[aStream print:'/DeviceGray setcolorspace 0 setgray'; cr.] ifFalse:[aStream print:'/DeviceRGB setcolorspace'; cr.].! ! !Form methodsFor: 'postscript generation' stamp: 'nk 12/31/2003 15:46'! storePostscriptHexOn: inner self depth <= 8 ifTrue: [self storeHexBitsOn: inner]. self depth = 16 ifTrue: [self store15To24HexBitsOn: inner]. self depth = 32 ifTrue: [self store32To24HexBitsOn: inner]! ! !Form methodsFor: 'resources' stamp: 'ar 12/9/2002 16:04'! readNativeResourceFrom: byteStream | img aStream | (byteStream isKindOf: FileStream) ifTrue:[ "Ugly, but ImageReadWriter will send #reset which is implemented as #reopen and we may not be able to do so." aStream := RWBinaryOrTextStream with: byteStream contents. ] ifFalse:[ aStream := byteStream. ]. img := [ImageReadWriter formFromStream: aStream] on: Error do:[:ex| nil]. img ifNil:[^nil]. (img isColorForm and:[self isColorForm]) ifTrue:[ | cc | cc := img colors. img colors: nil. img displayOn: self. img colors: cc. ] ifFalse:[ img displayOn: self. ]. img := nil.! ! !Form methodsFor: 'resources' stamp: 'nk 7/30/2004 17:53'! readResourceFrom: aStream "Store a resource representation of the receiver on aStream. Must be specific to the receiver so that no code is filed out." | bitsSize msb | (aStream next: 4) asString = self resourceTag ifFalse: [aStream position: aStream position - 4. ^self readNativeResourceFrom: aStream]. width := aStream nextNumber: 4. height := aStream nextNumber: 4. depth := aStream nextNumber: 4. bitsSize := aStream nextNumber: 4. bitsSize = 0 ifFalse: [bits := aStream next: bitsSize. ^self]. msb := (aStream nextNumber: 4) = 1. bitsSize := aStream nextNumber: 4. bits := Bitmap new: self bitsSize. (Form extent: width @ height depth: depth bits: (aStream next: bitsSize * 4)) displayOn: self. msb = SmalltalkImage current isBigEndian ifFalse: [Bitmap swapBytesIn: bits from: 1 to: bits size]! ! !Form methodsFor: 'resources' stamp: 'ar 2/27/2001 14:56'! resourceTag ^'FORM'! ! !Form methodsFor: 'resources' stamp: 'sd 9/30/2003 13:41'! storeResourceOn: aStream "Store a resource representation of the receiver on aStream. Must be specific to the receiver so that no code is filed out." self hibernate. aStream nextPutAll: self resourceTag asByteArray. "tag" aStream nextNumber: 4 put: width. aStream nextNumber: 4 put: height. aStream nextNumber: 4 put: depth. (bits isMemberOf: ByteArray) ifFalse:[ "must store bitmap" aStream nextNumber: 4 put: 0. "tag" aStream nextNumber: 4 put: (SmalltalkImage current isBigEndian ifTrue:[1] ifFalse:[0]). ]. aStream nextNumber: 4 put: bits size. aStream nextPutAll: bits. ! ! !Form methodsFor: 'scaling, rotation' stamp: 'ar 5/14/2001 23:33'! flipBy: direction centerAt: aPoint "Return a copy of the receiver flipped either #vertical or #horizontal." | newForm quad | newForm := self class extent: self extent depth: depth. quad := self boundingBox innerCorners. quad := (direction = #vertical ifTrue: [#(2 1 4 3)] ifFalse: [#(4 3 2 1)]) collect: [:i | quad at: i]. (WarpBlt current toForm: newForm) sourceForm: self; colorMap: (self colormapIfNeededFor: newForm); combinationRule: 3; copyQuad: quad toRect: newForm boundingBox. newForm offset: (self offset flipBy: direction centerAt: aPoint). ^ newForm " [Sensor anyButtonPressed] whileFalse: [((Form fromDisplay: (Sensor cursorPoint extent: 130@66)) flipBy: #vertical centerAt: 0@0) display] " "Consistency test... | f f2 p | [Sensor anyButtonPressed] whileFalse: [f := Form fromDisplay: ((p := Sensor cursorPoint) extent: 31@41). Display fillBlack: (p extent: 31@41). f2 := f flipBy: #vertical centerAt: 0@0. (f2 flipBy: #vertical centerAt: 0@0) displayAt: p] " ! ! !Form methodsFor: 'scaling, rotation' stamp: 'tpr 9/28/2004 17:00'! magnifyBy: scale "Answer a Form created as a scaling of the receiver. Scale may be a Float or even a Point, and may be greater or less than 1.0." ^ self magnify: self boundingBox by: scale smoothing: (scale < 1 ifTrue: [2] ifFalse: [1])! ! !Form methodsFor: 'scaling, rotation'! magnify: aRectangle by: scale "Answer a Form created as a scaling of the receiver. Scale may be a Float, and may be greater or less than 1.0." ^ self magnify: aRectangle by: scale smoothing: 1 "Dynamic test... [Sensor anyButtonPressed] whileFalse: [(Display magnify: (Sensor cursorPoint extent: 31@41) by: 5@3) display] " "Scaling test... | f cp | f := Form fromDisplay: (Rectangle originFromUser: 100@100). Display restoreAfter: [Sensor waitNoButton. [Sensor anyButtonPressed] whileFalse: [cp := Sensor cursorPoint. (f magnify: f boundingBox by: (cp x asFloat@cp y asFloat)/f extent) display]] " "Consistency test... | f f2 p | [Sensor anyButtonPressed] whileFalse: [f := Form fromDisplay: ((p := Sensor cursorPoint) extent: 31@41). Display fillBlack: (p extent: 31@41). f2 := f magnify: f boundingBox by: 5@3. (f2 shrink: f2 boundingBox by: 5@3) displayAt: p] " ! ! !Form methodsFor: 'scaling, rotation' stamp: 'tpr 9/28/2004 17:00'! magnify: aRectangle by: scale smoothing: cellSize "Answer a Form created as a scaling of the receiver. Scale may be a Float or even a Point, and may be greater or less than 1.0." | newForm | newForm := self blankCopyOf: aRectangle scaledBy: scale. (WarpBlt current toForm: newForm) sourceForm: self; colorMap: (self colormapIfNeededFor: newForm); cellSize: cellSize; "installs a new colormap if cellSize > 1" combinationRule: 3; copyQuad: aRectangle innerCorners toRect: newForm boundingBox. ^ newForm "Dynamic test... [Sensor anyButtonPressed] whileFalse: [(Display magnify: (Sensor cursorPoint extent: 131@81) by: 0.5 smoothing: 2) display] " "Scaling test... | f cp | f := Form fromDisplay: (Rectangle originFromUser: 100@100). Display restoreAfter: [Sensor waitNoButton. [Sensor anyButtonPressed] whileFalse: [cp := Sensor cursorPoint. (f magnify: f boundingBox by: (cp x asFloat@cp y asFloat)/f extent smoothing: 2) display]] "! ! !Form methodsFor: 'scaling, rotation'! rotateBy: deg "Rotate the receiver by the indicated number of degrees." "rot is the destination form, bit enough for any angle." ^ self rotateBy: deg smoothing: 1 " | a f | f := Form fromDisplay: (0@0 extent: 200@200). a := 0. [Sensor anyButtonPressed] whileFalse: [((Form fromDisplay: (Sensor cursorPoint extent: 130@66)) rotateBy: (a := a+5)) display]. f display "! ! !Form methodsFor: 'scaling, rotation' stamp: 'wiz 1/22/2006 01:15'! rotateBy: direction centerAt: aPoint "Return a rotated copy of the receiver. direction = #none, #right, #left, or #pi" | newForm quad rot scale | direction == #none ifTrue: [^ self]. scale := (direction = #pi ifTrue: [width@height] ifFalse: [height@width]) / self extent . newForm := self blankCopyOf: self boundingBox scaledBy: scale. quad := self boundingBox innerCorners. rot := #(right pi left) indexOf: direction. (WarpBlt current toForm: newForm) sourceForm: self; colorMap: (self colormapIfNeededFor: newForm); combinationRule: 3; copyQuad: ((1+rot to: 4+rot) collect: [:i | quad atWrap: i]) toRect: newForm boundingBox. newForm offset: (self offset rotateBy: direction centerAt: aPoint). ^ newForm " [Sensor anyButtonPressed] whileFalse: [((Form fromDisplay: (Sensor cursorPoint extent: 130@66)) rotateBy: #left centerAt: 0@0) display] " "Consistency test... | f f2 p | [Sensor anyButtonPressed] whileFalse: [f := Form fromDisplay: ((p := Sensor cursorPoint) extent: 31@41). Display fillBlack: (p extent: 31@41). f2 := f rotateBy: #left centerAt: 0@0. (f2 rotateBy: #right centerAt: 0@0) displayAt: p] " ! ! !Form methodsFor: 'scaling, rotation' stamp: 'ar 3/1/2006 23:04'! rotateBy: deg magnify: scale smoothing: cellSize "Rotate the receiver by the indicated number of degrees and magnify. scale can be a Point to make for interesting 3D effects " "rot is the destination form, big enough for any angle." | side rot warp r1 pts p bigSide | side := 1 + self extent r asInteger. bigSide := (side asPoint * scale) rounded. rot := self blankCopyOf: self boundingBox scaledBy: ( bigSide / self extent ). warp := (WarpBlt current toForm: rot) sourceForm: self; colorMap: (self colormapIfNeededFor: rot); cellSize: cellSize; "installs a new colormap if cellSize > 1" combinationRule: Form paint. r1 := (0@0 extent: side@side) align: (side@side)//2 with: self boundingBox center. "Rotate the corners of the source rectangle." pts := r1 innerCorners collect: [:pt | p := pt - r1 center. (r1 center x asFloat + (p x asFloat*deg degreeCos) + (p y asFloat*deg degreeSin)) @ (r1 center y asFloat - (p x asFloat*deg degreeSin) + (p y asFloat*deg degreeCos))]. warp copyQuad: pts toRect: rot boundingBox. ^ rot " | a f | f := Form fromDisplay: (0@0 extent: 200@200). a := 0. [Sensor anyButtonPressed] whileFalse: [((Form fromDisplay: (Sensor cursorPoint extent: 130@66)) rotateBy: (a := a+5) magnify: 0.75@2 smoothing: 2) display]. f display "! ! !Form methodsFor: 'scaling, rotation' stamp: 'tpr 9/28/2004 16:55'! rotateBy: deg smoothing: cellSize "Rotate the receiver by the indicated number of degrees." ^self rotateBy: deg magnify: 1 smoothing: cellSize " | a f | f := Form fromDisplay: (0@0 extent: 200@200). a := 0. [Sensor anyButtonPressed] whileFalse: [((Form fromDisplay: (Sensor cursorPoint extent: 130@66)) rotateBy: (a := a+5) smoothing: 2) display]. f display "! ! !Form methodsFor: 'scaling, rotation' stamp: 'RAA 7/13/2000 12:09'! scaledToSize: newExtent | scale | newExtent = self extent ifTrue: [^self]. scale := newExtent x / self width min: newExtent y / self height. ^self magnify: self boundingBox by: scale smoothing: 2. ! ! !Form methodsFor: 'scaling, rotation'! shrink: aRectangle by: scale | scalePt | scalePt := scale asPoint. ^ self magnify: aRectangle by: (1.0 / scalePt x asFloat) @ (1.0 / scalePt y asFloat)! ! !Form methodsFor: 'testing' stamp: 'ar 5/15/2001 16:14'! hasNonStandardPalette "Return true if the receiver has a non-standard palette. Non-standard means that RGBA components may be located at positions differing from the standard Squeak RGBA layout at the receiver's depth." ^false! ! !Form methodsFor: 'testing' stamp: 'ar 7/21/2007 21:37'! isAllWhite "Answer whether all bits in the receiver are white" | word | self unhibernate. word := Color white pixelWordForDepth: self depth. 1 to: bits size do: [:i | (bits at: i) = word ifFalse: [^ false]]. ^ true! ! !Form methodsFor: 'testing' stamp: 'ar 5/17/2001 15:46'! isBigEndian "Return true if the receiver contains big endian pixels, meaning the left-most pixel is stored in the most significant bits of a word." ^depth > 0! ! !Form methodsFor: 'testing' stamp: 'ar 5/28/2000 14:58'! isBltAccelerated: ruleInteger for: sourceForm "Return true if the receiver can perform accelerated blts operations by itself" ^false! ! !Form methodsFor: 'testing' stamp: 'ar 5/28/2000 15:04'! isDisplayScreen ^false! ! !Form methodsFor: 'testing' stamp: 'ar 5/27/2000 16:54'! isExternalForm ^false! ! !Form methodsFor: 'testing' stamp: 'ar 5/28/2000 14:58'! isFillAccelerated: ruleInteger for: aColor "Return true if the receiver can perform accelerated fill operations by itself" ^false! ! !Form methodsFor: 'testing' stamp: 'ar 10/30/2000 23:23'! isForm ^true! ! !Form methodsFor: 'testing' stamp: 'ar 5/17/2001 15:47'! isLittleEndian "Return true if the receiver contains little endian pixels, meaning the left-most pixel is stored in the least significant bits of a word." ^depth < 0! ! !Form methodsFor: 'testing' stamp: 'RAA 8/14/2000 10:00'! isStatic ^false! ! !Form methodsFor: 'testing' stamp: 'ar 2/10/2004 17:18'! isTranslucent "Answer whether this form may be translucent" ^self depth = 32! ! !Form methodsFor: 'testing' stamp: 'ar 5/28/2000 14:58'! shouldPreserveContents "Return true if the receiver should preserve it's contents when flagged to be clean. Most forms can not be trivially restored by some drawing operation but some may." ^true! ! !Form methodsFor: 'transitions' stamp: 'ar 5/17/2001 15:42'! fadeImageCoarse: otherImage at: topLeft "Display fadeImageCoarse: (Form fromDisplay: (40@40 extent: 300@300)) reverse at: 40@40" | pix j d | d := self depth. ^ self fadeImage: otherImage at: topLeft indexAndMaskDo: [:i :mask | i=1 ifTrue: [pix := (1 bitShift: d) - 1. 1 to: 8//d-1 do: [:q | pix := pix bitOr: (pix bitShift: d*4)]]. i <= 16 ifTrue: [j := i-1//4+1. (0 to: 28 by: 4) do: [:k | mask bits at: j+k put: ((mask bits at: j+k) bitOr: (pix bitShift: i-1\\4*d))]. "mask display." true] ifFalse: [false]]! ! !Form methodsFor: 'transitions' stamp: 'ar 5/17/2001 15:41'! fadeImageFine: otherImage at: topLeft "Display fadeImageFine: (Form fromDisplay: (40@40 extent: 300@300)) reverse at: 40@40" | pix j ii d | d := self depth. ^ self fadeImage: otherImage at: topLeft indexAndMaskDo: [:i :mask | i=1 ifTrue: [pix := (1 bitShift: d) - 1. 1 to: 8//d-1 do: [:q | pix := pix bitOr: (pix bitShift: d*4)]]. i <= 16 ifTrue: [ii := #(0 10 2 8 7 13 5 15 1 11 3 9 6 12 4 14) at: i. j := ii//4+1. (0 to: 28 by: 4) do: [:k | mask bits at: j+k put: ((mask bits at: j+k) bitOr: (pix bitShift: ii\\4*d))]. true] ifFalse: [false]]! ! !Form methodsFor: 'transitions'! fadeImageHorFine: otherImage at: topLeft "Display fadeImageHorFine: (Form fromDisplay: (10@10 extent: 300@300)) reverse at: 10@10" ^ self fadeImage: otherImage at: topLeft indexAndMaskDo: [:i :mask | mask fill: (0@(i-1) extent: mask width@1) fillColor: Color black. mask fill: (0@(i-1+16) extent: mask width@1) fillColor: Color black. (i*2) <= mask width]! ! !Form methodsFor: 'transitions'! fadeImageHor: otherImage at: topLeft "Display fadeImageHor: (Form fromDisplay: (10@10 extent: 300@300)) reverse at: 10@10" ^ self fadeImage: otherImage at: topLeft indexAndMaskDo: [:i :mask | mask fill: (0@(mask height//2-i) extent: mask width@(i*2)) fillColor: Color black. (i*2) <= mask width]! ! !Form methodsFor: 'transitions'! fadeImageSquares: otherImage at: topLeft "Display fadeImageSquares: (Form fromDisplay: (40@40 extent: 300@300)) reverse at: 40@40" ^ self fadeImage: otherImage at: topLeft indexAndMaskDo: [:i :mask | mask fill: ((16-i) asPoint extent: (i*2) asPoint) fillColor: Color black. i <= 16]! ! !Form methodsFor: 'transitions' stamp: 'ar 5/17/2001 15:39'! fadeImageVert: otherImage at: topLeft "Display fadeImageVert: (Form fromDisplay: (10@10 extent: 300@300)) reverse at: 10@10" | d | d := self depth. ^ self fadeImage: otherImage at: topLeft indexAndMaskDo: [:i :mask | mask fill: ((mask width//2//d-i*d)@0 extent: i*2*d@mask height) fillColor: Color black. i <= (mask width//d)]! ! !Form methodsFor: 'transitions' stamp: 'jm 5/21/1998 23:46'! fadeImage: otherImage at: topLeft indexAndMaskDo: indexAndMaskBlock "This fade uses halftones as a blending hack. Zeros in the halftone produce the original image (self), and ones in the halftone produce the 'otherImage'. IndexAndMaskBlock gets evaluated prior to each cycle, and the resulting boolean determines whether to continue cycling." | index imageRect maskForm resultForm | imageRect := otherImage boundingBox. resultForm := self copy: (topLeft extent: imageRect extent). maskForm := Form extent: 32@32. index := 0. [indexAndMaskBlock value: (index := index+1) value: maskForm] whileTrue: [maskForm reverse. resultForm copyBits: imageRect from: resultForm at: 0@0 clippingBox: imageRect rule: Form over fillColor: maskForm. maskForm reverse. resultForm copyBits: imageRect from: otherImage at: 0@0 clippingBox: imageRect rule: Form under fillColor: maskForm. self copyBits: imageRect from: resultForm at: topLeft clippingBox: self boundingBox rule: Form over fillColor: nil. Display forceDisplayUpdate]! ! !Form methodsFor: 'transitions' stamp: 'jm 6/1/1998 10:55'! pageImage: otherImage at: topLeft corner: corner "Produce a page-turning illusion that gradually reveals otherImage located at topLeft in this form. Corner specifies which corner, as 1=topLeft, 2=topRight, 3=bottomRight, 4=bottomLeft." | bb maskForm resultForm delta maskLoc maskRect stepSize cornerSel smallRect | stepSize := 10. bb := otherImage boundingBox. resultForm := self copy: (topLeft extent: bb extent). maskForm := Form extent: ((otherImage width min: otherImage height) + stepSize) asPoint. "maskLoc := starting loc rel to topLeft" otherImage width > otherImage height ifTrue: ["wide image; motion is horizontal." (corner between: 2 and: 3) not ifTrue: ["motion is to the right" delta := 1@0. maskLoc := bb topLeft - (corner = 1 ifTrue: [maskForm width@0] ifFalse: [maskForm width@stepSize])] ifFalse: ["motion is to the left" delta := -1@0. maskLoc := bb topRight - (corner = 2 ifTrue: [0@0] ifFalse: [0@stepSize])]] ifFalse: ["tall image; motion is vertical." corner <= 2 ifTrue: ["motion is downward" delta := 0@1. maskLoc := bb topLeft - (corner = 1 ifTrue: [0@maskForm height] ifFalse: [stepSize@maskForm height])] ifFalse: ["motion is upward" delta := 0@-1. maskLoc := bb bottomLeft - (corner = 3 ifTrue: [stepSize@0] ifFalse: [0@0])]]. "Build a solid triangle in the mask form" (Pen newOnForm: maskForm) in: [:p | corner even "Draw 45-degree line" ifTrue: [p place: 0@0; turn: 135; go: maskForm width*3//2] ifFalse: [p place: 0@(maskForm height-1); turn: 45; go: maskForm width*3//2]]. maskForm smear: delta negated distance: maskForm width. "Copy the mask to full resolution for speed. Make it be the reversed so that it can be used for ORing in the page-corner color" maskForm := (Form extent: maskForm extent depth: otherImage depth) copyBits: maskForm boundingBox from: maskForm at: 0@0 colorMap: (Bitmap with: 16rFFFFFFFF with: 0). "Now move the triangle maskForm across the resultForm selecting the triangular part of otherImage to display, and across the resultForm, selecting the part of the original image to erase." cornerSel := #(topLeft topRight bottomRight bottomLeft) at: corner. 1 to: (otherImage width + otherImage height // stepSize)+1 do: [:i | "Determine the affected square" maskRect := (maskLoc extent: maskForm extent) intersect: bb. ((maskLoc x*delta x) + (maskLoc y*delta y)) < 0 ifTrue: [smallRect := 0@0 extent: (maskRect width min: maskRect height) asPoint. maskRect := smallRect align: (smallRect perform: cornerSel) with: (maskRect perform: cornerSel)]. "AND otherForm with triangle mask, and OR into result" resultForm copyBits: bb from: otherImage at: 0@0 clippingBox: maskRect rule: Form over fillColor: nil. resultForm copyBits: maskForm boundingBox from: maskForm at: maskLoc clippingBox: maskRect rule: Form erase fillColor: nil. resultForm copyBits: maskForm boundingBox from: maskForm at: maskLoc clippingBox: maskRect rule: Form under fillColor: Color lightBrown. "Now update Display in a single BLT." self copyBits: maskRect from: resultForm at: topLeft + maskRect topLeft clippingBox: self boundingBox rule: Form over fillColor: nil. Display forceDisplayUpdate. maskLoc := maskLoc + (delta*stepSize)] " 1 to: 4 do: [:corner | Display pageImage: (Form fromDisplay: (10@10 extent: 200@300)) reverse at: 10@10 corner: corner] " ! ! !Form methodsFor: 'transitions' stamp: 'ar 5/28/2000 12:12'! pageWarp: otherImage at: topLeft forward: forward "Produce a page-turning illusion that gradually reveals otherImage located at topLeft in this form. forward == true means turn pages toward you, else away. [ignored for now]" | pageRect oldPage nSteps buffer p leafRect sourceQuad warp oldBottom d | pageRect := otherImage boundingBox. oldPage := self copy: (pageRect translateBy: topLeft). (forward ifTrue: [oldPage] ifFalse: [otherImage]) border: pageRect widthRectangle: (Rectangle left: 0 right: 2 top: 1 bottom: 1) rule: Form over fillColor: Color black. oldBottom := self copy: ((pageRect bottomLeft + topLeft) extent: (pageRect width@(pageRect height//4))). nSteps := 8. buffer := Form extent: otherImage extent + (0@(pageRect height//4)) depth: self depth. d := pageRect topLeft + (0@(pageRect height//4)) - pageRect topRight. 1 to: nSteps-1 do: [:i | forward ifTrue: [buffer copy: pageRect from: otherImage to: 0@0 rule: Form over. p := pageRect topRight + (d * i // nSteps)] ifFalse: [buffer copy: pageRect from: oldPage to: 0@0 rule: Form over. p := pageRect topRight + (d * (nSteps-i) // nSteps)]. buffer copy: oldBottom boundingBox from: oldBottom to: pageRect bottomLeft rule: Form over. leafRect := pageRect topLeft corner: p x @ (pageRect bottom + p y). sourceQuad := Array with: pageRect topLeft with: pageRect bottomLeft + (0@p y) with: pageRect bottomRight with: pageRect topRight - (0@p y). warp := (WarpBlt current toForm: buffer) clipRect: leafRect; sourceForm: (forward ifTrue: [oldPage] ifFalse: [otherImage]); combinationRule: Form paint. warp copyQuad: sourceQuad toRect: leafRect. self copy: buffer boundingBox from: buffer to: topLeft rule: Form over. Display forceDisplayUpdate]. buffer copy: pageRect from: otherImage to: 0@0 rule: Form over. buffer copy: oldBottom boundingBox from: oldBottom to: pageRect bottomLeft rule: Form over. self copy: buffer boundingBox from: buffer to: topLeft rule: Form over. Display forceDisplayUpdate. " 1 to: 4 do: [:corner | Display pageWarp: (Form fromDisplay: (10@10 extent: 200@300)) reverse at: 10@10 forward: false] " ! ! !Form methodsFor: 'transitions' stamp: 'jm 5/21/1998 23:46'! slideImage: otherImage at: topLeft delta: delta "Display slideImage: (Form fromDisplay: (40@40 extent: 300@300)) reverse at: 40@40 delta: 3@-4" | bb nSteps clipRect | bb := otherImage boundingBox. clipRect := topLeft extent: otherImage extent. nSteps := 1. delta x = 0 ifFalse: [nSteps := nSteps max: (bb width//delta x abs) + 1]. delta y = 0 ifFalse: [nSteps := nSteps max: (bb height//delta y abs) + 1]. 1 to: nSteps do: [:i | self copyBits: bb from: otherImage at: delta*(i-nSteps) + topLeft clippingBox: clipRect rule: Form paint fillColor: nil. Display forceDisplayUpdate]! ! !Form methodsFor: 'transitions' stamp: 'jm 6/18/1998 12:57'! wipeImage: otherImage at: topLeft clippingBox: clipBox rectForIndex: rectForIndexBlock | i clipRect t rectOrList waitTime | i := 0. clipRect := topLeft extent: otherImage extent. clipBox ifNotNil: [clipRect := clipRect intersect: clipBox]. [rectOrList := rectForIndexBlock value: (i := i + 1). rectOrList == nil] whileFalse: [ t := Time millisecondClockValue. rectOrList asOrderedCollection do: [:r | self copyBits: r from: otherImage at: topLeft + r topLeft clippingBox: clipRect rule: Form over fillColor: nil]. Display forceDisplayUpdate. waitTime := 3 - (Time millisecondClockValue - t). waitTime > 0 ifTrue: ["(Delay forMilliseconds: waitTime) wait"]]. ! ! !Form methodsFor: 'transitions' stamp: 'jm 10/16/97 15:21'! wipeImage: otherImage at: topLeft delta: delta "Display wipeImage: (Form fromDisplay: (40@40 extent: 300@300)) reverse at: 40@40 delta: 0@-2" self wipeImage: otherImage at: topLeft delta: delta clippingBox: nil. ! ! !Form methodsFor: 'transitions' stamp: 'jm 10/16/97 15:17'! wipeImage: otherImage at: topLeft delta: delta clippingBox: clipBox | wipeRect bb nSteps | bb := otherImage boundingBox. wipeRect := delta x = 0 ifTrue: [delta y = 0 ifTrue: [nSteps := 1. bb "allow 0@0"] ifFalse: [ nSteps := bb height//delta y abs + 1. "Vertical movement" delta y > 0 ifTrue: [bb topLeft extent: bb width@delta y] ifFalse: [bb bottomLeft+delta extent: bb width@delta y negated]]] ifFalse: [nSteps := bb width//delta x abs + 1. "Horizontal movement" delta x > 0 ifTrue: [bb topLeft extent: delta x@bb height] ifFalse: [bb topRight+delta extent: delta x negated@bb height]]. ^ self wipeImage: otherImage at: topLeft clippingBox: clipBox rectForIndex: [:i | i <= nSteps ifTrue: [wipeRect translateBy: (delta* (i-1))] ifFalse: [nil]]! ! !Form methodsFor: 'transitions' stamp: 'di 3/2/98 09:14'! zoomInTo: otherImage at: topLeft "Display zoomInTo: (Form fromDisplay: (40@40 extent: 300@300)) reverse at: 40@40" ^ self zoomIn: true orOutTo: otherImage at: topLeft vanishingPoint: otherImage extent//2+topLeft! ! !Form methodsFor: 'transitions' stamp: 'di 1/28/1999 09:20'! zoomIn: goingIn orOutTo: otherImage at: topLeft vanishingPoint: vp "Display zoomInTo: (Form fromDisplay: (40@40 extent: 300@300)) reverse at: 40@40. Display zoomOutTo: (Form fromDisplay: (40@40 extent: 300@300)) reverse at: 40@40." | nSteps j bigR lilR minTime startTime lead | nSteps := 16. minTime := 500. "milliseconds" startTime := Time millisecondClockValue. ^ self wipeImage: otherImage at: topLeft clippingBox: nil rectForIndex: [:i | "i runs from 1 to nsteps" i > nSteps ifTrue: [nil "indicates all done"] ifFalse: ["If we are going too fast, delay for a bit" lead := startTime + (i-1*minTime//nSteps) - Time millisecondClockValue. lead > 10 ifTrue: [(Delay forMilliseconds: lead) wait]. "Return an array with the difference rectangles for this step." j := goingIn ifTrue: [i] ifFalse: [nSteps+1-i]. bigR := vp - (vp*(j)//nSteps) corner: vp + (otherImage extent-vp*(j)//nSteps). lilR := vp - (vp*(j-1)//nSteps) corner: vp + (otherImage extent-vp*(j-1)//nSteps). bigR areasOutside: lilR]]! ! !Form methodsFor: 'transitions' stamp: 'di 3/2/98 09:15'! zoomOutTo: otherImage at: topLeft "Display zoomOutTo: (Form fromDisplay: (40@40 extent: 300@300)) reverse at: 40@40" ^ self zoomIn: false orOutTo: otherImage at: topLeft vanishingPoint: otherImage extent//2+topLeft! ! !Form methodsFor: 'private' stamp: 'tk 3/13/2000 15:21'! hackBits: bitThing "This method provides an initialization so that BitBlt may be used, eg, to copy ByteArrays and other non-pointer objects efficiently. The resulting form looks 4 wide, 8 deep, and bitThing-size-in-words high." width := 4. depth := 8. bitThing class isBits ifFalse: [self error: 'bitThing must be a non-pointer object']. bitThing class isBytes ifTrue: [height := bitThing basicSize // 4] ifFalse: [height := bitThing basicSize]. bits := bitThing! ! !Form methodsFor: 'private'! initFromArray: array "Fill the bitmap from array. If the array is shorter, then cycle around in its contents until the bitmap is filled." | ax aSize array32 i j word16 | ax := 0. aSize := array size. aSize > bits size ifTrue: ["backward compatibility with old 16-bit bitmaps and their forms" array32 := Array new: height * (width + 31 // 32). i := j := 0. 1 to: height do: [:y | 1 to: width+15//16 do: [:x16 | word16 := array at: (i := i + 1). x16 odd ifTrue: [array32 at: (j := j+1) put: (word16 bitShift: 16)] ifFalse: [array32 at: j put: ((array32 at: j) bitOr: word16)]]]. ^ self initFromArray: array32]. 1 to: bits size do: [:index | (ax := ax + 1) > aSize ifTrue: [ax := 1]. bits at: index put: (array at: ax)]! ! !Form methodsFor: 'private' stamp: 'ar 12/19/2000 16:23'! privateFloodFillValue: aColor "Private. Compute the pixel value in the receiver's depth but take into account implicit color conversions by BitBlt." | f1 f2 bb | f1 := Form extent: 1@1 depth: depth. f2 := Form extent: 1@1 depth: 32. bb := BitBlt toForm: f1. bb fillColor: aColor; destRect: (0@0 corner: 1@1); combinationRule: 3; copyBits. bb := BitBlt toForm: f2. bb sourceForm: f1; sourceOrigin: 0@0; destRect: (0@0 corner: 1@1); combinationRule: 3; copyBits. ^f2 pixelValueAt: 0@0.! ! !Form methodsFor: 'private' stamp: '6/9/97 16:10 di'! setExtent: extent depth: bitsPerPixel "Create a virtual bit map with the given extent and bitsPerPixel." width := extent x asInteger. width < 0 ifTrue: [width := 0]. height := extent y asInteger. height < 0 ifTrue: [height := 0]. depth := bitsPerPixel. bits := Bitmap new: self bitsSize! ! !Form methodsFor: 'private' stamp: 'ar 5/28/2000 15:49'! setExtent: extent depth: bitsPerPixel bits: bitmap "Create a virtual bit map with the given extent and bitsPerPixel." width := extent x asInteger. width < 0 ifTrue: [width := 0]. height := extent y asInteger. height < 0 ifTrue: [height := 0]. depth := bitsPerPixel. (bits isNil or:[self bitsSize = bitmap size]) ifFalse:[^self error:'Bad dimensions']. bits := bitmap! ! !Form methodsFor: 'private' stamp: 'ar 10/30/2000 23:22'! setResourceBits: aForm "Private. Really. Used for setting the 'resource bits' when externalizing some form" bits := aForm.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Form class instanceVariableNames: ''! !Form class methodsFor: 'bmp file reading' stamp: 'ar 6/16/2002 17:41'! fromBMPFile: aBinaryStream "Obsolete" ^self fromBinaryStream: aBinaryStream.! ! !Form class methodsFor: 'bmp file reading' stamp: 'ar 6/16/2002 17:41'! fromBMPFileNamed: fileName "Obsolete" ^self fromFileNamed: fileName ! ! !Form class methodsFor: 'examples'! exampleBorder "Form exampleBorder" "This example demonstrates the border finding algorithm. Start by having the user sketch on the screen (end with option-click) and then select a rectangular area of the screen which includes all of the area to be filled. Finally, (with crosshair cursor), the user points at the interior of the region to be outlined, and the region begins with that place as its seed." | f r interiorPoint | Form exampleSketch. "sketch a little area with an enclosed region" r := Rectangle fromUser. f := Form fromDisplay: r. Cursor crossHair showWhile: [interiorPoint := Sensor waitButton - r origin]. Cursor execute showWhile: [f shapeBorder: Color blue width: 2 interiorPoint: interiorPoint sharpCorners: false internal: false]. f displayOn: Display at: r origin ! ! !Form class methodsFor: 'examples'! exampleEdits "In Form category editing are messages edit and bitEdit that make it possible to create editors on instances of Form. This is the general form editor: | f | f := Form fromUser. f edit. This is the general bit editor: | f | f := Form fromUser. f bitEdit."! ! !Form class methodsFor: 'examples'! exampleMagnify | f m | f := Form fromUser. m := f magnify: f boundingBox by: 5 @ 5. m displayOn: Display at: Sensor waitButton "Form exampleMagnify."! ! !Form class methodsFor: 'examples'! exampleShrink | f s | f := Form fromUser. s := f shrink: f boundingBox by: 2 @ 5. s displayOn: Display at: Sensor waitButton "Form exampleShrink."! ! !Form class methodsFor: 'examples'! exampleSketch "This is a simple drawing algorithm to get a sketch on the display screen. Draws whenever mouse button down. Ends with option-click." | aPen color | aPen := Pen new. color := 0. [Sensor yellowButtonPressed] whileFalse: [aPen place: Sensor cursorPoint; color: (color := color + 1). [Sensor redButtonPressed] whileTrue: [aPen goto: Sensor cursorPoint]]. Sensor waitNoButton. "Form exampleSketch"! ! !Form class methodsFor: 'examples'! exampleSpaceFill "Form exampleSpaceFill" "This example demonstrates the area filling algorithm. Starts by having the user sketch on the screen (ended by option-click) and then select a rectangular area of the screen which includes all of the area to be filled. Finally, (with crosshair cursor), the user points at the interior of some region to be filled, and the filling begins with that place as its seed." | f r interiorPoint | Form exampleSketch. "sketch a little area with an enclosed region" r := Rectangle fromUser. f := Form fromDisplay: r. Cursor crossHair showWhile: [interiorPoint := Sensor waitButton - r origin]. Cursor execute showWhile: [f shapeFill: Color gray interiorPoint: interiorPoint]. f displayOn: Display at: r origin ! ! !Form class methodsFor: 'examples'! makeStar "See the similar example in OpaqueForm" | sampleForm pen | sampleForm := Form extent: 50@50. "Make a form" pen := Pen newOnForm: sampleForm. pen place: 24@50; turn: 18. "Draw a 5-pointed star on it." 1 to: 5 do: [:i | pen go: 19; turn: 72; go: 19; turn: -144]. ^ sampleForm " Form makeStar follow: [Sensor cursorPoint] while: [Sensor noButtonPressed] "! ! !Form class methodsFor: 'examples' stamp: 'tk 7/4/2000 12:08'! toothpaste: diam "Display restoreAfter: [Form toothpaste: 30]" "Draws wormlike lines by laying down images of spheres. See Ken Knowlton, Computer Graphics, vol. 15 no. 4 p352. Draw with mouse button down; terminate by option-click." | facade ball filter point queue port color q colors colr colr2 | colors := Display depth = 1 ifTrue: [Array with: Color black] ifFalse: [Color red wheel: 12]. facade := Form extent: diam@diam offset: (diam//-2) asPoint. (Form dotOfSize: diam) displayOn: facade at: (diam//2) asPoint clippingBox: facade boundingBox rule: Form under fillColor: Color white. #(1 2 3) do: [:x | "simulate facade by circles of gray" (Form dotOfSize: x*diam//5) displayOn: facade at: (diam*2//5) asPoint clippingBox: facade boundingBox rule: Form under fillColor: (Color perform: (#(black gray lightGray) at: x)). "facade displayAt: 50*x@50"]. ball := Form dotOfSize: diam. color := 8. [ true ] whileTrue: [port := BitBlt current toForm: Display. "Expand 1-bit forms to any pixel depth" port colorMap: (Bitmap with: 0 with: 16rFFFFFFFF). queue := OrderedCollection new: 32. 16 timesRepeat: [queue addLast: -20@-20]. Sensor waitButton. Sensor yellowButtonPressed ifTrue: [^ self]. filter := Sensor cursorPoint. colr := colors atWrap: (color := color + 5). "choose increment relatively prime to colors size" colr2 := colr alphaMixed: 0.3 with: Color white. [Sensor redButtonPressed or: [queue size > 0]] whileTrue: [filter := filter * 4 + Sensor cursorPoint // 5. point := Sensor redButtonPressed ifTrue: [filter] ifFalse: [-20@-20]. port copyForm: ball to: point rule: Form paint fillColor: colr. (q := queue removeFirst) == nil ifTrue: [^ self]. "exit" Display depth = 1 ifTrue: [port copyForm: facade to: q rule: Form erase] ifFalse: [port copyForm: facade to: q rule: Form paint fillColor: colr2]. Sensor redButtonPressed ifTrue: [queue addLast: point]]]. ! ! !Form class methodsFor: 'examples'! xorHack: size "Display restoreAfter: [Form xorHack: 256]" "Draw a smiley face or stick figure, and end with option-click. Thereafter image gets 'processed' as long as you have button down. If you stop at just the right time, you'll see you figure upside down, and at the end of a full cycle, you'll see it perfectly restored. Dude -- this works in color too!!" | rect form i bb | rect := 5@5 extent: size@size. Display fillWhite: rect; border: (rect expandBy: 2) width: 2. Display border: (rect topRight - (0@2) extent: rect extent*2 + 4) width: 2. Form exampleSketch. form := Form fromDisplay: rect. bb := form boundingBox. i := 0. [Sensor yellowButtonPressed] whileFalse: [[Sensor redButtonPressed] whileTrue: [i := i + 1. (Array with: 0@1 with: 0@-1 with: 1@0 with: -1@0) do: [:d | form copyBits: bb from: form at: d clippingBox: bb rule: Form reverse fillColor: nil]. form displayAt: rect topLeft. i+2\\size < 4 ifTrue: [(Delay forMilliseconds: 300) wait]]. (form magnify: form boundingBox by: 2@2) displayAt: rect topRight + (2@0). Sensor waitButton].! ! !Form class methodsFor: 'file list services' stamp: 'nk 6/12/2004 12:56'! fileReaderServicesForDirectory: aFileDirectory ^{ self serviceImageImportDirectory. self serviceImageImportDirectoryWithSubdirectories. }! ! !Form class methodsFor: 'file list services' stamp: 'nk 7/16/2003 18:01'! fileReaderServicesForFile: fullName suffix: suffix ^((ImageReadWriter allTypicalFileExtensions add: '*'; add: 'form'; yourself) includes: suffix) ifTrue: [ self services ] ifFalse: [#()] ! ! !Form class methodsFor: 'file list services' stamp: 'alain.plantec 5/30/2008 13:32'! openImageInWindow: fullName "Handle five file formats: GIF, JPG, PNG, Form storeOn: (run coded), and BMP. Fail if file format is not recognized." | image myStream | myStream := (FileStream readOnlyFileNamed: fullName) binary. image := self fromBinaryStream: myStream. myStream close. Project current resourceManager addResource: image url: (FileDirectory urlForFileNamed: fullName) asString. (World drawingClass withForm: image) openInWorld! ! !Form class methodsFor: 'file list services' stamp: 'GabrielOmarCotelli 6/4/2009 20:42'! serviceImageAsBackground "Answer a service for setting the desktop background from a given graphical file's contents" ^ SimpleServiceEntry provider: self label: 'use graphic as background' selector: #setBackgroundFromImageFileNamed: description: 'use the graphic as the background for the desktop' buttonLabel: 'background'! ! !Form class methodsFor: 'file list services' stamp: 'nk 6/12/2004 13:16'! serviceImageImportDirectory "Answer a service for reading a graphic into ImageImports" ^(SimpleServiceEntry provider: self label: 'import all images from this directory' selector: #importImageDirectory: description: 'Load all graphics found in this directory, adding them to the ImageImports repository.' buttonLabel: 'import dir') argumentGetter: [ :fileList | fileList directory ]; yourself ! ! !Form class methodsFor: 'file list services' stamp: 'nk 6/12/2004 13:15'! serviceImageImportDirectoryWithSubdirectories "Answer a service for reading all graphics from a directory and its subdirectories into ImageImports" ^(SimpleServiceEntry provider: self label: 'import all images from here and subdirectories' selector: #importImageDirectoryWithSubdirectories: description: 'Load all graphics found in this directory and its subdirectories, adding them to the ImageImports repository.' buttonLabel: 'import subdirs') argumentGetter: [ :fileList | fileList directory ]; yourself ! ! !Form class methodsFor: 'file list services' stamp: 'sw 2/17/2002 01:39'! serviceImageImports "Answer a service for reading a graphic into ImageImports" ^ SimpleServiceEntry provider: self label: 'read graphic into ImageImports' selector: #importImage: description: 'Load a graphic, placing it in the ImageImports repository.' buttonLabel: 'import'! ! !Form class methodsFor: 'file list services' stamp: 'sw 2/17/2002 00:31'! serviceOpenImageInWindow "Answer a service for opening a graphic in a window" ^ SimpleServiceEntry provider: self label: 'open graphic in a window' selector: #openImageInWindow: description: 'open a graphic file in a window' buttonLabel: 'open'! ! !Form class methodsFor: 'file list services' stamp: 'sd 2/1/2002 21:43'! services ^ Array with: self serviceImageImports with: self serviceOpenImageInWindow with: self serviceImageAsBackground ! ! !Form class methodsFor: 'file list services' stamp: 'GabrielOmarCotelli 6/4/2009 20:42'! setBackgroundFromImageFileNamed: aFileName (self fromFileNamed: aFileName) setAsBackground! ! !Form class methodsFor: 'filein/out' stamp: 'nk 6/12/2004 12:47'! importImage: fullName "Import the given image file and store the resulting Form in the default Imports. The image is named with the short filename up to the first period, possibly with additions from the directory path to make it unique." Imports default importImageFromFileNamed: fullName. ! ! !Form class methodsFor: 'filein/out' stamp: 'nk 6/12/2004 13:08'! importImageDirectory: dir "Import the given image file and store the resulting Form in the default Imports. The image is named with the short filename up to the first period, possibly with additions from the directory path to make it unique." Imports default importImageDirectory: dir ! ! !Form class methodsFor: 'filein/out' stamp: 'nk 6/12/2004 12:55'! importImageDirectoryWithSubdirectories: dir "Import the given image file and store the resulting Form in the default Imports. The image is named with the short filename up to the first period, possibly with additions from the directory path to make it unique." Imports default importImageDirectoryWithSubdirectories: dir ! ! !Form class methodsFor: 'initialization' stamp: 'GabrielOmarCotelli 6/4/2009 20:34'! unload FileServices unregisterFileReader: self ! ! !Form class methodsFor: 'initialize-release' stamp: 'GabrielOmarCotelli 6/4/2009 20:34'! initialize FileServices registerFileReader: self! ! !Form class methodsFor: 'instance creation' stamp: 'ar 5/28/2000 12:07'! dotOfSize: diameter "Create a form which contains a round black dot." | radius form bb rect centerX centerY centerYBias centerXBias radiusSquared xOverY maxy dx | radius := diameter//2. form := self extent: diameter@diameter offset: (0@0) - (radius@radius). bb := (BitBlt current toForm: form) sourceX: 0; sourceY: 0; combinationRule: Form over; fillColor: Color black. rect := form boundingBox. centerX := rect center x. centerY := rect center y. centerYBias := rect height odd ifTrue: [0] ifFalse: [1]. centerXBias := rect width odd ifTrue: [0] ifFalse: [1]. radiusSquared := (rect height asFloat / 2.0) squared - 0.01. xOverY := rect width asFloat / rect height asFloat. maxy := rect height - 1 // 2. "First do the inner fill, and collect x values" 0 to: maxy do: [:dy | dx := ((radiusSquared - (dy * dy) asFloat) sqrt * xOverY) truncated. bb destX: centerX - centerXBias - dx destY: centerY - centerYBias - dy width: dx + dx + centerXBias + 1 height: 1; copyBits. bb destY: centerY + dy; copyBits]. ^ form " Time millisecondsToRun: [1 to: 20 do: [:i | (Form dotOfSize: i) displayAt: (i*20)@(i*20)]] "! ! !Form class methodsFor: 'instance creation' stamp: 'jm 3/27/98 16:27'! extent: extentPoint "Answer an instance of me with a blank bitmap of depth 1." ^ self extent: extentPoint depth: 1 ! ! !Form class methodsFor: 'instance creation' stamp: 'jm 3/27/98 16:36'! extent: extentPoint depth: bitsPerPixel "Answer an instance of me with blank bitmap of the given dimensions and depth." ^ self basicNew setExtent: extentPoint depth: bitsPerPixel ! ! !Form class methodsFor: 'instance creation' stamp: 'ar 10/9/1998 23:44'! extent: extentPoint depth: bitsPerPixel bits: aBitmap "Answer an instance of me with blank bitmap of the given dimensions and depth." ^ self basicNew setExtent: extentPoint depth: bitsPerPixel bits: aBitmap! ! !Form class methodsFor: 'instance creation' stamp: 'jm 3/27/98 16:35'! extent: extentPoint depth: bitsPerPixel fromArray: anArray offset: offsetPoint "Answer an instance of me with a pixmap of the given depth initialized from anArray." ^ (self extent: extentPoint depth: bitsPerPixel) offset: offsetPoint; initFromArray: anArray ! ! !Form class methodsFor: 'instance creation' stamp: 'jm 3/27/98 16:33'! extent: extentPoint fromArray: anArray offset: offsetPoint "Answer an instance of me of depth 1 with bitmap initialized from anArray." ^ (self extent: extentPoint depth: 1) offset: offsetPoint; initFromArray: anArray ! ! !Form class methodsFor: 'instance creation' stamp: 'jm 3/27/98 16:28'! extent: extentPoint fromStipple: fourNibbles "Answer an instance of me with bitmap initialized from a repeating 4x4 bit stipple encoded in a 16-bit constant." | nibble | ^ (self extent: extentPoint depth: 1) initFromArray: ((1 to: 4) collect: [:i | nibble := (fourNibbles bitShift: -4*(4-i)) bitAnd: 16rF. 16r11111111 * nibble]) "fill 32 bits with each 4-bit nibble" ! ! !Form class methodsFor: 'instance creation' stamp: 'jm 3/27/98 16:26'! extent: extentPoint offset: offsetPoint "Answer an instance of me with a blank bitmap of depth 1." ^ (self extent: extentPoint depth: 1) offset: offsetPoint ! ! !Form class methodsFor: 'instance creation' stamp: 'nk 7/7/2003 18:19'! fromBinaryStream: aBinaryStream "Read a Form or ColorForm from given file, using the first byte of the file to guess its format. Currently handles: GIF, uncompressed BMP, and both old and new DisplayObject writeOn: formats, JPEG, and PCX. Return nil if the file could not be read or was of an unrecognized format." | firstByte | aBinaryStream binary. firstByte := aBinaryStream next. firstByte = 1 ifTrue: [ "old Squeakform format" ^ self new readFromOldFormat: aBinaryStream]. firstByte = 2 ifTrue: [ "new Squeak form format" ^ self new readFrom: aBinaryStream]. "Try for JPG, GIF, or PCX..." "Note: The following call closes the stream." ^ ImageReadWriter formFromStream: aBinaryStream ! ! !Form class methodsFor: 'instance creation'! fromDisplay: aRectangle "Answer an instance of me with bitmap initialized from the area of the display screen defined by aRectangle." ^ (self extent: aRectangle extent depth: Display depth) fromDisplay: aRectangle! ! !Form class methodsFor: 'instance creation'! fromDisplay: aRectangle using: oldForm "Like fromDisplay: only if oldForm is the right size, copy into it and answer it instead." ((oldForm ~~ nil) and: [oldForm extent = aRectangle extent]) ifTrue: [oldForm fromDisplay: aRectangle. ^ oldForm] ifFalse: [^ self fromDisplay: aRectangle]! ! !Form class methodsFor: 'instance creation' stamp: 'alain.plantec 5/30/2008 13:31'! fromFileNamed: fileName "Read a Form or ColorForm from the given file." | file form | file := (FileStream readOnlyFileNamed: fileName) binary. form := self fromBinaryStream: file. Project current resourceManager addResource: form url: (FileDirectory urlForFileNamed: file name) asString. file close. ^ form! ! !Form class methodsFor: 'instance creation'! fromUser "Answer an instance of me with bitmap initialized from the area of the display screen designated by the user. The grid for selecting an area is 1@1." ^self fromUser: 1 @ 1! ! !Form class methodsFor: 'instance creation' stamp: 'ar 3/1/2006 22:50'! fromUser: gridPoint "Answer an instance of me with bitmap initialized from the area of the display screen designated by the user. The grid for selecting an area is aPoint. Ensures that the returned form has positive extent." | rect | rect := Rectangle fromUser: gridPoint. ^ self fromDisplay: (rect origin extent: (rect extent max: gridPoint))! ! !Form class methodsFor: 'instance creation' stamp: 'jm 12/5/97 19:32'! fromUserWithExtent: anExtent "Answer an instance of me with bitmap initialized from the area of the display screen whose origin is designated by the user and whose size is anExtent" ^ self fromDisplay: (Rectangle originFromUser: anExtent) "(Form fromUserWithExtent: 50@50) displayAt: 10@10"! ! !Form class methodsFor: 'mode constants'! and "Answer the integer denoting the logical 'and' combination rule." ^1! ! !Form class methodsFor: 'mode constants'! blend "Answer the integer denoting BitBlt's alpha blend combination rule." ^24! ! !Form class methodsFor: 'mode constants' stamp: 'di 12/31/1998 14:02'! blendAlpha "Answer the integer denoting BitBlt's blend-with-constant-alpha rule." ^ 30! ! !Form class methodsFor: 'mode constants'! erase "Answer the integer denoting mode erase." ^4! ! !Form class methodsFor: 'mode constants'! erase1bitShape "Answer the integer denoting mode erase." ^ 26! ! !Form class methodsFor: 'mode constants'! oldErase1bitShape "Answer the integer denoting mode erase." ^ 17! ! !Form class methodsFor: 'mode constants'! oldPaint "Answer the integer denoting the 'paint' combination rule." ^16! ! !Form class methodsFor: 'mode constants'! over "Answer the integer denoting mode over." ^3! ! !Form class methodsFor: 'mode constants'! paint "Answer the integer denoting the 'paint' combination rule." ^25! ! !Form class methodsFor: 'mode constants' stamp: 'di 12/31/1998 14:02'! paintAlpha "Answer the integer denoting BitBlt's paint-with-constant-alpha rule." ^ 31! ! !Form class methodsFor: 'mode constants'! reverse "Answer the integer denoting mode reverse." ^6! ! !Form class methodsFor: 'mode constants'! under "Answer the integer denoting mode under." ^7! ! !Form class methodsFor: 'shut down' stamp: 'ar 5/28/2000 23:35'! shutDown "Form shutDown" "Compress all instances in the system. Will decompress on demand..." Form allInstancesDo: [:f | f hibernate]. ColorForm allInstancesDo: [:f | f hibernate].! ! !Form class methodsFor: 'utils' stamp: 'stephane.ducasse 7/10/2009 16:15'! showFormsAcrossTopOfScreen: aFormList "Display the given array of forms across the top of the screen, wrapping to subsequent lines if needed. Useful for example for looking at sets of rotations and animations. 6/10/96 sw" "self showFormsAcrossTopOfScreen: {Cursor currentCursor asCursorForm}" | position maxHeight screenBox ceiling | position := 20. maxHeight := 0. ceiling := 0. screenBox := Display boundingBox. aFormList do: [:elem | elem displayAt: (position @ ceiling). maxHeight := maxHeight max: elem boundingBox height. position := position + elem boundingBox width + 5. position > (screenBox right - 100) ifTrue: [position := 20. ceiling := ceiling + maxHeight + 10. maxHeight := 0]]! ! !Form class methodsFor: 'utils' stamp: 'stephane.ducasse 7/10/2009 16:25'! showFormsDictAcrossTopOfScreen: formDict "Display the given Dictionary of forms across the top of the screen, wrapping to subsequent lines if needed. Beneath each, put the name of the associated key." " | dict methods | dict := Dictionary new. methods := MenuIcons class selectors select: [:each | '*Icon' match: each asString]. methods do: [:each | dict at: each put: (MenuIcons perform: each)]. self showFormsDictAcrossTopOfScreen: dict" | position maxHeight screenBox ceiling elem box h labelWidth keyString | position := 20. maxHeight := 0. ceiling := 0. screenBox := Display boundingBox. formDict associationsDo: [:assoc | (elem := assoc value) displayAt: (position @ ceiling). box := elem boundingBox. h := box height. keyString := (assoc key isString) ifTrue: [assoc key] ifFalse: [assoc key printString]. keyString displayAt: (position @ (ceiling + h)). labelWidth := TextStyle default defaultFont widthOfString: keyString. maxHeight := maxHeight max: h. position := position + (box width max: labelWidth) + 5. position > (screenBox right - 100) ifTrue: [position := 20. ceiling := ceiling + maxHeight + 15. maxHeight := 0]]! ! Canvas subclass: #FormCanvas instanceVariableNames: 'origin clipRect form port shadowColor' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'! !FormCanvas commentStamp: '' prior: 0! Note that when shadowDrawing is true, shadowStipple may be either a color, for a solid shadow of the given color, or it may be a stipple used to simulate gray shading when the display cannot support alpha blending.! !FormCanvas methodsFor: '*Polymorph-Widgets' stamp: 'gvc 3/21/2008 16:37'! fillRectangle: aRectangle basicFillStyle: aFillStyle "Fill the given rectangle with the given, non-composite, fill style." | pattern | self shadowColor ifNotNil: [^self fillRectangle: aRectangle color: aFillStyle asColor]. (aFillStyle isKindOf: InfiniteForm) ifTrue: [ ^self infiniteFillRectangle: aRectangle fillStyle: aFillStyle ]. (aFillStyle isSolidFill) ifTrue:[^self fillRectangle: aRectangle color: aFillStyle asColor]. "We have a very special case for filling with infinite forms" (aFillStyle isBitmapFill and:[aFillStyle origin = (0@0)]) ifTrue:[ pattern := aFillStyle form. (aFillStyle direction = (pattern width @ 0) and:[aFillStyle normal = (0@pattern height)]) ifTrue:[ "Can use an InfiniteForm" ^self fillRectangle: aRectangle color: (InfiniteForm with: pattern)]. ]. "Use a BalloonCanvas instead" self balloonFillRectangle: aRectangle fillStyle: aFillStyle.! ! !FormCanvas methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 3/16/2009 13:36'! balloonFillRectangle: aRectangle fillStyle: aFillStyle self asBalloonCanvas fillRectangle: aRectangle basicFillStyle: aFillStyle! ! !FormCanvas methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 3/21/2008 16:38'! fillRectangle: aRectangle fillStyle: aFillStyle "Fill the given rectangle. Double-dispatched via the fill style." aFillStyle fillRectangle: aRectangle on: self! ! !FormCanvas methodsFor: '*Polymorph-Widgets-override' stamp: 'gvc 10/7/2008 14:02'! infiniteFillRectangle: aRectangle fillStyle: aFillStyle | additionalOffset rInPortTerms clippedPort targetTopLeft clipOffset ex | "this is a bit of a kludge to get the form to be aligned where I *think* it should be. something better is needed, but not now" additionalOffset := 0@0. ex := aFillStyle form extent. rInPortTerms := (aRectangle intersect: aFillStyle boundingBox) translateBy: origin. clippedPort := port clippedBy: rInPortTerms. targetTopLeft := clippedPort clipRect topLeft truncateTo: ex. clipOffset := rInPortTerms topLeft - targetTopLeft. additionalOffset := (clipOffset \\ ex) - ex. ^aFillStyle displayOnPort: clippedPort offsetBy: additionalOffset ! ! !FormCanvas methodsFor: 'accessing' stamp: 'ar 5/28/2000 17:11'! allocateForm: extentPoint "Allocate a new form which is similar to the receiver" ^form allocateForm: extentPoint! ! !FormCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 14:06'! clipRect "Return the currently active clipping rectangle" ^ clipRect translateBy: origin negated! ! !FormCanvas methodsFor: 'accessing' stamp: 'ar 12/31/2001 03:26'! contentsOfArea: aRectangle into: aForm | bb | self flush. bb := BitBlt toForm: aForm. bb sourceForm: form; combinationRule: Form over; sourceX: (aRectangle left + origin x); sourceY: (aRectangle top + origin y); width: aRectangle width; height: aRectangle height; copyBits. ^aForm! ! !FormCanvas methodsFor: 'accessing'! depth ^ form depth ! ! !FormCanvas methodsFor: 'accessing'! extent ^ form extent! ! !FormCanvas methodsFor: 'accessing'! form ^ form! ! !FormCanvas methodsFor: 'accessing' stamp: 'ar 6/22/1999 14:10'! origin "Return the current origin for drawing operations" ^ origin! ! !FormCanvas methodsFor: 'accessing' stamp: 'ar 2/17/2000 00:26'! shadowColor ^shadowColor! ! !FormCanvas methodsFor: 'accessing' stamp: 'ar 2/17/2000 00:26'! shadowColor: aColor shadowColor := aColor! ! !FormCanvas methodsFor: 'converting' stamp: 'ar 2/17/2000 00:17'! asShadowDrawingCanvas "Note: This is sort of an optimization here since since the logic is all there" ^self copy shadowColor: (Color black alpha: 0.5)! ! !FormCanvas methodsFor: 'converting' stamp: 'ar 2/17/2000 00:16'! asShadowDrawingCanvas: aColor "Note: This is sort of an optimization here since since the logic is all there" ^self copy shadowColor: aColor! ! !FormCanvas methodsFor: 'copying' stamp: 'jm 8/2/97 14:00'! copy "Make a copy the receiver on the same underlying Form but with its own grafPort." ^ self clone resetGrafPort ! ! !FormCanvas methodsFor: 'copying' stamp: 'ar 6/17/1999 02:51'! copyClipRect: aRectangle ^ self copyOrigin: origin clipRect: (aRectangle translateBy: origin) ! ! !FormCanvas methodsFor: 'copying' stamp: 'ar 6/17/1999 02:52'! copyOffset: aPoint ^ self copyOrigin: origin + aPoint clipRect: clipRect! ! !FormCanvas methodsFor: 'copying' stamp: 'ar 6/17/1999 02:52'! copyOffset: aPoint clipRect: sourceClip "Make a copy of me offset by aPoint, and further clipped by sourceClip, a rectangle in the un-offset coordinates" ^ self copyOrigin: aPoint + origin clipRect: ((sourceClip translateBy: origin) intersect: clipRect)! ! !FormCanvas methodsFor: 'copying' stamp: 'ar 6/17/1999 02:52'! copyOrigin: aPoint clipRect: aRectangle "Return a copy of this canvas with the given origin. The clipping rectangle of this canvas is the intersection of the given rectangle and the receiver's current clipping rectangle. This allows the clipping rectangles of nested clipping morphs to be composed." ^ self copy setOrigin: aPoint clipRect: (clipRect intersect: aRectangle)! ! !FormCanvas methodsFor: 'drawing' stamp: 'ar 5/14/2000 15:50'! fillColor: c "Note: This always fills, even if the color is transparent." self setClearColor: c. port fillRect: form boundingBox offset: origin.! ! !FormCanvas methodsFor: 'drawing' stamp: 'ar 5/14/2001 23:34'! line: pt1 to: pt2 brushForm: brush | offset | offset := origin. self setPaintColor: Color black. port sourceForm: brush; fillColor: nil; sourceRect: brush boundingBox; colorMap: (brush colormapIfNeededFor: form); drawFrom: (pt1 + offset) to: (pt2 + offset)! ! !FormCanvas methodsFor: 'drawing' stamp: 'ar 2/16/2000 22:07'! line: pt1 to: pt2 width: w color: c | offset | offset := origin - (w // 2) asPoint. self setFillColor: c. port width: w; height: w; drawFrom: (pt1 + offset) to: (pt2 + offset)! ! !FormCanvas methodsFor: 'drawing' stamp: 'yo 1/23/2003 17:50'! paragraph3: para bounds: bounds color: c | scanner | self setPaintColor: c. scanner := (port clippedBy: (bounds translateBy: origin)) displayScannerForMulti: para foreground: (self shadowColor ifNil:[c]) background: Color transparent ignoreColorChanges: self shadowColor notNil. para displayOnTest: (self copyClipRect: bounds) using: scanner at: origin+ bounds topLeft. ! ! !FormCanvas methodsFor: 'drawing' stamp: 'di 9/12/2001 21:38'! paragraph: para bounds: bounds color: c | scanner | self setPaintColor: c. scanner := (port clippedBy: (bounds translateBy: origin)) displayScannerFor: para foreground: (self shadowColor ifNil:[c]) background: Color transparent ignoreColorChanges: self shadowColor notNil. para displayOn: (self copyClipRect: bounds) using: scanner at: origin+ bounds topLeft. ! ! !FormCanvas methodsFor: 'drawing'! point: pt color: c form colorAt: (pt + origin) put: c.! ! !FormCanvas methodsFor: 'drawing' stamp: 'ar 9/9/2000 22:18'! render: anObject "Do some 3D operations with the object if possible" ^self asBalloonCanvas render: anObject! ! !FormCanvas methodsFor: 'drawing-general' stamp: 'ar 12/30/2001 18:58'! roundCornersOf: aMorph in: bounds during: aBlock aMorph wantsRoundedCorners ifFalse:[^aBlock value]. (self seesNothingOutside: (CornerRounder rectWithinCornersOf: bounds)) ifTrue: ["Don't bother with corner logic if the region is inside them" ^ aBlock value]. CornerRounder roundCornersOf: aMorph on: self in: bounds displayBlock: aBlock borderWidth: aMorph borderWidthForRounding corners: aMorph roundedCorners! ! !FormCanvas methodsFor: 'drawing-images' stamp: 'tpr 9/15/2004 10:27'! stencil: stencilForm at: aPoint sourceRect: sourceRect color: aColor "Flood this canvas with aColor wherever stencilForm has non-zero pixels" self setPaintColor: aColor. port colorMap: stencilForm maskingMap. port stencil: stencilForm at: aPoint + origin sourceRect: sourceRect.! ! !FormCanvas methodsFor: 'drawing-images' stamp: 'ar 12/30/2001 16:36'! warpImage: aForm transform: aTransform at: extraOffset sourceRect: sourceRect cellSize: cellSize "Warp the given using the appropriate transform and offset." | tfm | tfm := (MatrixTransform2x3 withOffset: origin) composedWithLocal: aTransform. ^self privateWarp: aForm transform: tfm at: extraOffset sourceRect: sourceRect cellSize: cellSize! ! !FormCanvas methodsFor: 'drawing-ovals' stamp: 'RAA 11/6/2000 15:21'! balloonFillOval: aRectangle fillStyle: aFillStyle borderWidth: bw borderColor: bc self asBalloonCanvas fillOval: aRectangle fillStyle: aFillStyle borderWidth: bw borderColor: bc! ! !FormCanvas methodsFor: 'drawing-ovals' stamp: 'di 5/25/2001 01:40'! fillOval: r color: fillColor borderWidth: borderWidth borderColor: borderColor | rect | "draw the border of the oval" rect := (r translateBy: origin) truncated. (borderWidth = 0 or: [borderColor isTransparent]) ifFalse:[ self setFillColor: borderColor. (r area > 10000 or: [fillColor isTranslucent]) ifTrue: [port frameOval: rect borderWidth: borderWidth] ifFalse: [port fillOval: rect]]. "faster this way" "fill the inside" fillColor isTransparent ifFalse: [self setFillColor: fillColor. port fillOval: (rect insetBy: borderWidth)]. ! ! !FormCanvas methodsFor: 'drawing-ovals' stamp: 'RAA 11/6/2000 16:42'! fillOval: aRectangle fillStyle: aFillStyle borderWidth: bw borderColor: bc "Fill the given oval." self flag: #bob. "this and its siblings could be moved up to Canvas with the right #balloonFillOval:..." self shadowColor ifNotNil: [^self fillOval: aRectangle color: aFillStyle asColor borderWidth: bw borderColor: bc]. (aFillStyle isBitmapFill and:[aFillStyle isKindOf: InfiniteForm]) ifTrue:[ self flag: #fixThis. ^self fillOval: aRectangle color: aFillStyle borderWidth: bw borderColor: bc]. (aFillStyle isSolidFill) ifTrue:[ ^self fillOval: aRectangle color: aFillStyle asColor borderWidth: bw borderColor: bc]. "Use a BalloonCanvas instead" self balloonFillOval: aRectangle fillStyle: aFillStyle borderWidth: bw borderColor: bc! ! !FormCanvas methodsFor: 'drawing-polygons' stamp: 'ar 6/18/1999 08:57'! drawPolygon: vertices color: aColor borderWidth: bw borderColor: bc "Generalize for the BalloonCanvas" ^self drawPolygon: vertices fillStyle: aColor borderWidth: bw borderColor: bc! ! !FormCanvas methodsFor: 'drawing-polygons' stamp: 'ar 12/6/2000 14:59'! drawPolygon: vertices fillStyle: aFillStyle borderWidth: bw borderColor: bc "Use a BalloonCanvas" self asBalloonCanvas drawPolygon: vertices asArray fillStyle: (self shadowColor ifNil:[aFillStyle]) borderWidth: bw borderColor: bc! ! !FormCanvas methodsFor: 'drawing-rectangles' stamp: 'ar 5/14/2000 15:50'! frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth borderColor: borderColor | rect | rect := r translateBy: origin. "draw the border of the rectangle" borderColor isTransparent ifFalse:[ self setFillColor: borderColor. (r area > 10000 or: [fillColor isTranslucent]) ifTrue: [ port frameRect: rect borderWidth: borderWidth. ] ifFalse: ["for small rectangles, it's faster to fill the entire outer rectangle than to compute and fill the border rects" port fillRect: rect offset: origin]]. "fill the inside" fillColor isTransparent ifFalse: [self setFillColor: fillColor. port fillRect: (rect insetBy: borderWidth) offset: origin].! ! !FormCanvas methodsFor: 'drawing-rectangles' stamp: 'ar 2/16/2000 22:07'! frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth topLeftColor: topLeftColor bottomRightColor: bottomRightColor | w h rect | "First use quick code for top and left borders and fill" self frameAndFillRectangle: r fillColor: fillColor borderWidth: borderWidth borderColor: topLeftColor. "Now use slow code for bevelled bottom and right borders" bottomRightColor isTransparent ifFalse: [ borderWidth isNumber ifTrue: [w := h := borderWidth] ifFalse: [w := borderWidth x. h := borderWidth y]. rect := r translateBy: origin. self setFillColor: bottomRightColor. port frameRectRight: rect width: w; frameRectBottom: rect height: h]. ! ! !FormCanvas methodsFor: 'drawing-support' stamp: 'ar 6/17/1999 03:02'! clipBy: aRectangle during: aBlock "Set a clipping rectangle active only during the execution of aBlock. Note: In the future we may want to have more general clip shapes - not just rectangles" ^aBlock value: (self copyClipRect: aRectangle)! ! !FormCanvas methodsFor: 'drawing-support' stamp: 'ar 10/18/2004 00:05'! transformBy: aDisplayTransform clippingTo: aClipRect during: aBlock smoothing: cellSize "Note: This method has been originally copied from TransformationMorph." | innerRect patchRect sourceQuad warp start subCanvas | (aDisplayTransform isPureTranslation) ifTrue:[ ^aBlock value: (self copyOffset: aDisplayTransform offset negated truncated clipRect: aClipRect) ]. "Prepare an appropriate warp from patch to innerRect" innerRect := aClipRect. patchRect := (aDisplayTransform globalBoundsToLocal: innerRect) truncated. sourceQuad := (aDisplayTransform sourceQuadFor: innerRect) collect: [:p | p - patchRect topLeft]. warp := self warpFrom: sourceQuad toRect: innerRect. warp cellSize: cellSize. "Render the submorphs visible in the clipping rectangle, as patchForm" start := (self depth = 1 and: [self isShadowDrawing not]) "If this is true B&W, then we need a first pass for erasure." ifTrue: [1] ifFalse: [2]. start to: 2 do: [:i | "If i=1 we first make a shadow and erase it for opaque whites in B&W" subCanvas := self class extent: patchRect extent depth: self depth. i=1 ifTrue: [subCanvas shadowColor: Color black. warp combinationRule: Form erase] ifFalse: [self isShadowDrawing ifTrue: [subCanvas shadowColor: self shadowColor]. warp combinationRule: Form paint]. subCanvas translateBy: patchRect topLeft negated during:[:offsetCanvas| aBlock value: offsetCanvas]. warp sourceForm: subCanvas form; warpBits. warp sourceForm: nil. subCanvas := nil "release space for next loop"] ! ! !FormCanvas methodsFor: 'drawing-support' stamp: 'ar 6/17/1999 03:02'! translateBy: delta during: aBlock "Set a translation only during the execution of aBlock." ^aBlock value: (self copyOffset: delta)! ! !FormCanvas methodsFor: 'drawing-support' stamp: 'ar 6/17/1999 02:55'! translateTo: newOrigin clippingTo: aRectangle during: aBlock "Set a new origin and clipping rectangle only during the execution of aBlock." aBlock value: (self copyOrigin: newOrigin clipRect: aRectangle)! ! !FormCanvas methodsFor: 'drawing-text' stamp: 'ar 2/5/2002 19:03'! drawString: aString from: firstIndex to: lastIndex at: aPoint font: fontOrNil color: c | font | port colorMap: nil. font := fontOrNil ifNil: [TextStyle defaultFont]. port combinationRule: Form paint. font installOn: port foregroundColor: (self shadowColor ifNil:[c]) backgroundColor: Color transparent. font displayString: aString on: port from: firstIndex to: lastIndex at: (origin + aPoint) kern: 0.! ! !FormCanvas methodsFor: 'drawing-text' stamp: 'ar 2/5/2002 19:03'! drawString: aString from: firstIndex to: lastIndex in: bounds font: fontOrNil color: c | font portRect | port colorMap: nil. portRect := port clipRect. port clipByX1: bounds left + origin x y1: bounds top + origin y x2: bounds right + origin x y2: bounds bottom + origin y. font := fontOrNil ifNil: [TextStyle defaultFont]. port combinationRule: Form paint. font installOn: port foregroundColor: (self shadowColor ifNil:[c]) backgroundColor: Color transparent. font displayString: aString asString on: port from: firstIndex to: lastIndex at: (bounds topLeft + origin) kern: 0. port clipRect: portRect.! ! !FormCanvas methodsFor: 'drawing-text' stamp: 'tween 3/10/2009 08:05'! drawString: aString from: firstIndex to: lastIndex in: bounds font: fontOrNil color: c underline: underline underlineColor: uc strikethrough: strikethrough strikethroughColor: sc | font portRect endPoint | port colorMap: nil. portRect := port clipRect. port clipByX1: bounds left + origin x y1: bounds top + origin y x2: bounds right + origin x y2: bounds bottom + origin y. font := fontOrNil ifNil: [TextStyle defaultFont]. port combinationRule: Form paint. font installOn: port foregroundColor: (self shadowColor ifNil:[c]) backgroundColor: Color transparent. endPoint := font displayString: aString asString on: port from: firstIndex to: lastIndex at: (bounds topLeft + origin) kern: 0. underline ifTrue:[ font installOn: port foregroundColor: (self shadowColor ifNil:[uc]) backgroundColor: Color transparent. font displayUnderlineOn: port from: (bounds topLeft + origin + (0@font ascent)) to: endPoint. ]. port clipRect: portRect.! ! !FormCanvas methodsFor: 'initialization' stamp: 'ar 5/27/2000 21:51'! finish "If there are any pending operations on the receiver complete them. Do not return before all modifications have taken effect." form finish! ! !FormCanvas methodsFor: 'initialization' stamp: 'ar 2/17/2000 00:21'! reset origin := 0@0. "origin of the top-left corner of this cavas" clipRect := (0@0 corner: 10000@10000). "default clipping rectangle" self shadowColor: nil.! ! !FormCanvas methodsFor: 'other' stamp: 'ar 11/11/1998 22:57'! asBalloonCanvas ^(BalloonCanvas on: form) setOrigin: origin clipRect: clipRect! ! !FormCanvas methodsFor: 'other'! flushDisplay Display deferUpdates: false; forceDisplayUpdate.! ! !FormCanvas methodsFor: 'other'! forceToScreen:rect ^Display forceToScreen:rect. ! ! !FormCanvas methodsFor: 'other'! showAt: pt ^ form displayAt: pt! ! !FormCanvas methodsFor: 'other' stamp: 'ar 5/28/2000 12:09'! showAt: pt invalidRects: updateRects | blt | blt := (BitBlt current toForm: Display) sourceForm: form; combinationRule: Form over. updateRects do: [:rect | blt sourceRect: rect; destOrigin: rect topLeft + pt; copyBits]! ! !FormCanvas methodsFor: 'other' stamp: 'ar 5/28/2000 12:12'! warpFrom: sourceQuad toRect: destRect ^ (WarpBlt current toForm: port destForm) combinationRule: Form paint; sourceQuad: sourceQuad destRect: (destRect translateBy: origin); clipRect: clipRect! ! !FormCanvas methodsFor: 'printing' stamp: 'ar 5/28/2000 17:07'! printOn: aStream super printOn: aStream. aStream nextPutAll:' on: '; print: form.! ! !FormCanvas methodsFor: 'testing' stamp: 'ar 2/17/2000 00:24'! isShadowDrawing ^ self shadowColor notNil! ! !FormCanvas methodsFor: 'testing' stamp: 'ar 6/22/1999 14:08'! isVisible: aRectangle "Optimization" (aRectangle right + origin x) < clipRect left ifTrue: [^ false]. (aRectangle left + origin x) > clipRect right ifTrue: [^ false]. (aRectangle bottom + origin y) < clipRect top ifTrue: [^ false]. (aRectangle top + origin y) > clipRect bottom ifTrue: [^ false]. ^ true ! ! !FormCanvas methodsFor: 'private' stamp: 'ar 5/14/2001 23:34'! image: aForm at: aPoint sourceRect: sourceRect rule: rule "Draw the portion of the given Form defined by sourceRect at the given point using the given BitBlt combination rule." port colorMap: (aForm colormapIfNeededFor: form); fillColor: nil. port image: aForm at: aPoint + origin sourceRect: sourceRect rule: rule.! ! !FormCanvas methodsFor: 'private' stamp: 'ar 8/8/2001 14:21'! image: aForm at: aPoint sourceRect: sourceRect rule: rule alpha: sourceAlpha "Draw the portion of the given Form defined by sourceRect at the given point using the given BitBlt combination rule." port colorMap: (aForm colormapIfNeededFor: form); fillColor: nil. port image: aForm at: aPoint + origin sourceRect: sourceRect rule: rule alpha: sourceAlpha.! ! !FormCanvas methodsFor: 'private' stamp: 'pavel.krivanek 11/21/2008 16:55'! portClass "Return the class used as port" ^ UIManager default grafPort! ! !FormCanvas methodsFor: 'private' stamp: 'RAA 12/17/2000 13:24'! privateClipRect ^clipRect! ! !FormCanvas methodsFor: 'private' stamp: 'RAA 12/17/2000 13:25'! privatePort ^port! ! !FormCanvas methodsFor: 'private' stamp: 'yo 6/18/2004 15:11'! privateWarp: aForm transform: aTransform at: extraOffset sourceRect: sourceRect cellSize: cellSize "Warp the given using the appropriate transform and offset." | globalRect sourceQuad warp tfm | tfm := aTransform. globalRect := tfm localBoundsToGlobal: sourceRect. sourceQuad := (tfm sourceQuadFor: globalRect) collect:[:p| p - sourceRect topLeft]. extraOffset ifNotNil:[globalRect := globalRect translateBy: extraOffset]. warp := (WarpBlt current toForm: port destForm) combinationRule: Form paint; sourceQuad: sourceQuad destRect: (globalRect origin corner: globalRect corner+(1@1)); clipRect: port clipRect. warp cellSize: cellSize. warp sourceForm: aForm. warp warpBits! ! !FormCanvas methodsFor: 'private' stamp: 'ar 5/25/2000 17:25'! resetGrafPort "Private!! Create a new grafPort for a new copy." port := self portClass toForm: form. port clipRect: clipRect. ! ! !FormCanvas methodsFor: 'private' stamp: 'tpr 9/15/2004 10:28'! setClearColor: aColor "Install a new clear color - e.g., a color is used for clearing the background" | clearColor | clearColor := aColor ifNil:[Color transparent]. clearColor isColor ifFalse:[ (clearColor isKindOf: InfiniteForm) ifFalse:[^self error:'Cannot install color']. ^port fillPattern: clearColor; combinationRule: Form over]. "Okay, so clearColor really *is* a color" port sourceForm: nil. port combinationRule: Form over. port fillPattern: clearColor. self depth = 8 ifTrue:[ "Use a stipple pattern" port fillColor: (form balancedPatternFor: clearColor)]. ! ! !FormCanvas methodsFor: 'private' stamp: 'tpr 9/15/2004 10:28'! setFillColor: aColor "Install a new color used for filling." | screen patternWord fillColor | fillColor := self shadowColor ifNil:[aColor]. fillColor ifNil:[fillColor := Color transparent]. fillColor isColor ifFalse:[ (fillColor isKindOf: InfiniteForm) ifFalse:[^self error:'Cannot install color']. ^port fillPattern: fillColor; combinationRule: Form over]. "Okay, so fillColor really *is* a color" port sourceForm: nil. fillColor isTranslucent ifFalse:[ port combinationRule: Form over. port fillPattern: fillColor. self depth = 8 ifTrue:[ "In 8 bit depth it's usually a good idea to use a stipple pattern" port fillColor: (form balancedPatternFor: fillColor)]. ^self]. "fillColor is some translucent color" self depth > 8 ifTrue:[ "BitBlt setup for alpha masked transfer" port fillPattern: fillColor. self depth = 16 ifTrue:[port alphaBits: fillColor privateAlpha; combinationRule: 30] ifFalse:[port combinationRule: Form blend]. ^self]. "Can't represent actual transparency -- use stipple pattern" screen := Color translucentMaskFor: fillColor alpha depth: self depth. patternWord := form pixelWordFor: fillColor. port fillPattern: (screen collect: [:maskWord | maskWord bitAnd: patternWord]). port combinationRule: Form paint. ! ! !FormCanvas methodsFor: 'private' stamp: 'ar 5/25/2000 17:25'! setForm: aForm self reset. form := aForm. port := self portClass toForm: form. ! ! !FormCanvas methodsFor: 'private' stamp: 'ar 6/22/1999 14:06'! setOrigin: aPoint clipRect: aRectangle origin := aPoint. clipRect := aRectangle. port clipRect: aRectangle. ! ! !FormCanvas methodsFor: 'private' stamp: 'tpr 9/15/2004 10:28'! setPaintColor: aColor "Install a new color used for filling." | paintColor screen patternWord | paintColor := self shadowColor ifNil:[aColor]. paintColor ifNil:[paintColor := Color transparent]. paintColor isColor ifFalse:[ (paintColor isKindOf: InfiniteForm) ifFalse:[^self error:'Cannot install color']. ^port fillPattern: paintColor; combinationRule: Form paint]. "Okay, so paintColor really *is* a color" port sourceForm: nil. (paintColor isTranslucent) ifFalse:[ port fillPattern: paintColor. port combinationRule: Form paint. self depth = 8 ifTrue:[ port fillColor: (form balancedPatternFor: paintColor)]. ^self]. "paintColor is translucent color" self depth > 8 ifTrue:[ "BitBlt setup for alpha mapped transfer" port fillPattern: paintColor. self depth = 16 ifTrue:[port alphaBits: paintColor privateAlpha; combinationRule: 31] ifFalse:[port combinationRule: Form blend]. ^self]. "Can't represent actual transparency -- use stipple pattern" screen := Color translucentMaskFor: paintColor alpha depth: self depth. patternWord := form pixelWordFor: paintColor. port fillPattern: (screen collect: [:maskWord | maskWord bitAnd: patternWord]). port combinationRule: Form paint ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FormCanvas class instanceVariableNames: ''! !FormCanvas class methodsFor: 'instance creation'! extent: aPoint ^ self extent: aPoint depth: Display depth ! ! !FormCanvas class methodsFor: 'instance creation'! extent: extent depth: depth ^ self new setForm: (Form extent: extent depth: depth)! ! !FormCanvas class methodsFor: 'instance creation' stamp: 'nk 7/4/2003 10:11'! extent: extent depth: depth origin: aPoint clipRect: aRectangle ^ self new setForm: (Form extent: extent depth: depth); setOrigin: aPoint clipRect: aRectangle; yourself! ! !FormCanvas class methodsFor: 'instance creation' stamp: 'jm 8/2/97 13:54'! on: aForm ^ self new setForm: aForm ! ! !FormCanvas class methodsFor: 'testing' stamp: 'ar 12/31/2001 02:26'! test1 "FormCanvas test1" | canvas | canvas := FormCanvas extent: 200@200. canvas fillColor: (Color black). canvas line: 10@10 to: 50@30 width: 1 color: (Color red). canvas frameRectangle: ((20@20) corner: (120@120)) width: 4 color: (Color green). canvas point: 100@100 color: (Color black). canvas drawString: 'Hello, World!!' at: 40@40 font: nil color: (Color cyan). canvas fillRectangle: ((10@80) corner: (31@121)) color: (Color magenta). canvas fillOval: ((10@80) corner: (31@121)) color: (Color cyan). canvas frameOval: ((40@80) corner: (61@121)) color: (Color blue). canvas frameOval: ((70@80) corner: (91@121)) width: 3 color: (Color red alpha: 0.2). canvas fillRectangle: ((130@30) corner: (170@80)) color: (Color lightYellow). canvas showAt: 0@0. ! ! !FormCanvas class methodsFor: 'testing' stamp: 'ar 12/31/2001 02:26'! test2 "FormCanvas test2" | baseCanvas p | baseCanvas := FormCanvas extent: 200@200. p := Sensor cursorPoint. [Sensor anyButtonPressed] whileFalse: [ baseCanvas translateBy: (Sensor cursorPoint - p) during:[:canvas| canvas fillColor: Color white. canvas line: 10@10 to: 50@30 width: 1 color: Color red. canvas frameRectangle: ((20@20) corner: (120@120)) width: 4 color: Color green. canvas point: 100@100 color: Color black. canvas drawString: 'Hello, World!!' at: 40@40 font: nil color: Color cyan. canvas fillRectangle: ((10@80) corner: (31@121)) color: Color magenta. canvas fillOval: ((10@80) corner: (31@121)) color: Color cyan. canvas frameOval: ((40@80) corner: (61@121)) color: Color blue. canvas frameOval: ((70@80) corner: (91@121)) width: 3 color: Color red. canvas fillRectangle: ((130@30) corner: (170@80)) color: Color lightYellow. canvas showAt: 0@0]]. ! ! !FormCanvas class methodsFor: 'testing' stamp: 'ar 12/31/2001 02:25'! test3 "FormCanvas test3" | baseCanvas | baseCanvas := FormCanvas extent: 200@200. baseCanvas fillColor: Color white. baseCanvas translateBy: 10@10 during:[:canvas| canvas shadowColor: (Color black alpha: 0.5). canvas line: 10@10 to: 50@30 width: 1 color: Color red. canvas frameRectangle: ((20@20) corner: (120@120)) width: 4 color: Color green. canvas point: 100@100 color: Color black. canvas drawString: 'Hello, World!!' at: 40@40 font: nil color: Color cyan. canvas fillRectangle: ((10@80) corner: (31@121)) color: Color magenta. canvas fillOval: ((10@80) corner: (31@121)) color: Color cyan. canvas frameOval: ((40@80) corner: (61@121)) color: Color blue. canvas frameOval: ((70@80) corner: (91@121)) width: 3 color: Color red. canvas fillRectangle: ((130@30) corner: (170@80)) color: Color lightYellow. canvas showAt: 0@0. ].! ! StrikeFont subclass: #FormSetFont instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Fonts'! !FormSetFont commentStamp: '' prior: 0! FormSetFonts are designed to capture individual images as character forms for imbedding in normal text. While most often used to insert an isolated glyph in some text, the code is actually desinged to support an entire user-defined font. The TextAttribute subclass TextFontReference is specifically designed for such in-line insertion of exceptional fonts in normal text.! !FormSetFont methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! fromFormArray: formArray asciiStart: asciiStart ascent: ascentVal | height width x badChar | type := 2. name := 'aFormFont'. minAscii := asciiStart. maxAscii := minAscii + formArray size - 1. ascent := ascentVal. subscript := superscript := emphasis := 0. height := width := 0. maxWidth := 0. formArray do: [ :f | width := width + f width. maxWidth := maxWidth max: f width. height := height max: f height + f offset y ]. badChar := (Form extent: 7 @ height) borderWidth: 1. width := width + badChar width. descent := height - ascent. pointSize := height. glyphs := Form extent: width @ height depth: formArray first depth. xTable := Array new: maxAscii + 3 withAll: 0. x := 0. formArray doWithIndex: [ :f :i | f displayOn: glyphs at: x @ 0. xTable at: minAscii + i + 1 put: (x := x + f width) ]. badChar displayOn: glyphs at: x @ 0. xTable at: maxAscii + 3 put: x + badChar width. characterToGlyphMap := nil! ! !FormSetFont methodsFor: 'as yet unclassified'! reset "Ignored by FormSetFonts"! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FormSetFont class instanceVariableNames: ''! !FormSetFont class methodsFor: 'examples' stamp: 'ar 1/15/2001 18:38'! copy: charForm toClipBoardAs: char ascent: ascent Clipboard clipboardText: (Text string: char asString attribute: (TextFontReference toFont: (FormSetFont new fromFormArray: (Array with: charForm) asciiStart: char asciiValue ascent: ascent))) " The S in the Squeak welcome window was installed by doing the following in a workspace (where the value of, eg, charForm will persist through BitEdit... f _ TextStyle default fontAt: 4. oldS _ f characterFormAt: $S. charForm _ Form extent: oldS extent depth: 8. oldS displayOn: charForm. charForm bitEdit. ...Play around with the BitEditor, then accept and close... FormSetFont copy: charForm toClipBoardAs: $S ascent: f ascent. ...Then do a paste into the Welcome window "! ! !FormSetFont class methodsFor: 'examples' stamp: 'lr 7/4/2009 10:42'! example "FormSetFont example" "Lets the user select a (small) area of the screen to represent the character A, then copies 'A' to the clipboard with that as the letter form. Thereafter, a paste operation will imbed that character in any text." | charForm | charForm := Form fromUser. self copy: charForm toClipBoardAs: $A ascent: charForm height! ! Form subclass: #FormStub instanceVariableNames: 'locator' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Display Objects'! !FormStub methodsFor: 'accessing' stamp: 'ar 2/24/2001 22:02'! locator ^locator! ! !FormStub methodsFor: 'accessing' stamp: 'ar 2/24/2001 22:02'! locator: aString locator := aString! ! !FormStub methodsFor: 'filein/out' stamp: 'ar 2/27/2001 21:36'! objectForDataStream: refStream "Force me into outPointers so that I get notified about startup" refStream replace: self with: self. ^self! ! ClassTestCase subclass: #FormTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'GraphicsTests-Primitives'! !FormTest commentStamp: 'ar 7/21/2007 21:39' prior: 0! Various tests for class form.! !FormTest methodsFor: 'tests' stamp: 'ar 7/21/2007 21:41'! testIsAllWhite "self run: #testIsAllWhite" "Make sure #isAllWhite works for all bit depths" | form | #(-32 -16 -8 -4 -2 -1 1 2 4 8 16 32) do:[:d| form := Form extent: 16@16 depth: d. form fillBlack. self deny: form isAllWhite. form fillWhite. self assert: form isAllWhite. ]. ! ! Number subclass: #Fraction instanceVariableNames: 'numerator denominator' classVariableNames: '' poolDictionaries: '' category: 'Kernel-Numbers'! !Fraction commentStamp: '' prior: 0! Fraction provides methods for dealing with fractions like 1/3 as fractions (not as 0.33333...). All public arithmetic operations answer reduced fractions (see examples). instance variables: 'numerator denominator ' Examples: (note the parentheses required to get the right answers in Smalltalk and Squeak): (2/3) + (2/3) (2/3) + (1/2) "answers shows the reduced fraction" (2/3) raisedToInteger: 5 "fractions also can have exponents" ! !Fraction methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:58'! * aNumber "Answer the result of multiplying the receiver by aNumber." | d1 d2 | aNumber isFraction ifTrue: [d1 := numerator gcd: aNumber denominator. d2 := denominator gcd: aNumber numerator. (d2 = denominator and: [d1 = aNumber denominator]) ifTrue: [^ numerator // d1 * (aNumber numerator // d2)]. ^ Fraction numerator: numerator // d1 * (aNumber numerator // d2) denominator: denominator // d2 * (aNumber denominator // d1)]. ^ aNumber adaptToFraction: self andSend: #*! ! !Fraction methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:58'! + aNumber "Answer the sum of the receiver and aNumber." | n d d1 d2 | aNumber isFraction ifTrue: [d := denominator gcd: aNumber denominator. n := numerator * (d1 := aNumber denominator // d) + (aNumber numerator * (d2 := denominator // d)). d1 := d1 * d2. n := n // (d2 := n gcd: d). (d := d1 * (d // d2)) = 1 ifTrue: [^ n]. ^ Fraction numerator: n denominator: d]. ^ aNumber adaptToFraction: self andSend: #+! ! !Fraction methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:58'! - aNumber "Answer the difference between the receiver and aNumber." aNumber isFraction ifTrue: [^ self + aNumber negated]. ^ aNumber adaptToFraction: self andSend: #-! ! !Fraction methodsFor: 'arithmetic' stamp: 'di 11/6/1998 13:58'! / aNumber "Answer the result of dividing the receiver by aNumber." aNumber isFraction ifTrue: [^self * aNumber reciprocal]. ^ aNumber adaptToFraction: self andSend: #/! ! !Fraction methodsFor: 'arithmetic'! negated "Refer to the comment in Number|negated." ^ Fraction numerator: numerator negated denominator: denominator! ! !Fraction methodsFor: 'comparing' stamp: 'nice 3/28/2006 23:37'! < aNumber aNumber isFraction ifTrue: [^ numerator * aNumber denominator < (aNumber numerator * denominator)]. ^ aNumber adaptToFraction: self andCompare: # 0 ifTrue: [b := b bitShift: exponent] ifFalse: [a := a bitShift: exponent negated]. q := a quo: b. r := a - (q * b). hq := q highBit. "check for gradual underflow, in which case we should use less bits" floatExponent := exponent + hq - 1. n := floatExponent > -1023 ifTrue: [54] ifFalse: [54 + floatExponent + 1022]. hq > n ifTrue: [exponent := exponent + hq - n. r := (q bitAnd: (1 bitShift: hq - n) - 1) * b + r. q := q bitShift: n - hq]. hq < n ifTrue: [exponent := exponent + hq - n. q1 := (r bitShift: n - hq) quo: b. q := (q bitShift: n - hq) bitAnd: q1. r := (r bitShift: n - hq) - (q1 * b)]. "check if we should round upward. The case of exact half (q bitAnd: 1) isZero not & (r isZero) will be handled by Integer>>asFloat" ((q bitAnd: 1) isZero or: [r isZero]) ifFalse: [q := q + 1]. ^ (self positive ifTrue: [q asFloat] ifFalse: [q asFloat negated]) timesTwoPower: exponent! ! !Fraction methodsFor: 'converting'! asFraction "Answer the receiver itself." ^self! ! !Fraction methodsFor: 'converting'! isFraction ^ true! ! !Fraction methodsFor: 'mathematical functions' stamp: 'LC 4/22/1998 14:03'! raisedToInteger: anInteger "See Number | raisedToInteger:" anInteger = 0 ifTrue: [^ 1]. anInteger < 0 ifTrue: [^ self reciprocal raisedToInteger: anInteger negated]. ^ Fraction numerator: (numerator raisedToInteger: anInteger) denominator: (denominator raisedToInteger: anInteger)! ! !Fraction methodsFor: 'mathematical functions' stamp: 'LC 4/22/1998 14:05'! squared "See Fraction (Number) | squared" ^ Fraction numerator: numerator squared denominator: denominator squared! ! !Fraction methodsFor: 'printing'! printOn: aStream aStream nextPut: $(. numerator printOn: aStream. aStream nextPut: $/. denominator printOn: aStream. aStream nextPut: $). ! ! !Fraction methodsFor: 'printing' stamp: 'laza 3/29/2004 12:56'! printOn: aStream base: base aStream nextPut: $(. numerator printOn: aStream base: base. aStream nextPut: $/. denominator printOn: aStream base: base. aStream nextPut: $). ! ! !Fraction methodsFor: 'printing' stamp: 'laza 3/29/2004 13:25'! storeOn: aStream base: base aStream nextPut: $(. numerator storeOn: aStream base: base. aStream nextPut: $/. denominator storeOn: aStream base: base. aStream nextPut: $). ! ! !Fraction methodsFor: 'self evaluating' stamp: 'apb 4/20/2006 18:41'! isSelfEvaluating ^ true! ! !Fraction methodsFor: 'truncation and round off'! truncated "Refer to the comment in Number|truncated." ^numerator quo: denominator! ! !Fraction methodsFor: 'private'! denominator ^denominator! ! !Fraction methodsFor: 'private'! numerator ^numerator! ! !Fraction methodsFor: 'private' stamp: 'GabrielOmarCotelli 5/23/2009 20:36'! reciprocal numerator abs = 1 ifTrue: [^denominator * numerator]. ^self class numerator: denominator denominator: numerator! ! !Fraction methodsFor: 'private'! reduced | gcd numer denom | numerator = 0 ifTrue: [^0]. gcd := numerator gcd: denominator. numer := numerator // gcd. denom := denominator // gcd. denom = 1 ifTrue: [^numer]. ^Fraction numerator: numer denominator: denom! ! !Fraction methodsFor: 'private' stamp: 'tfei 4/12/1999 12:45'! setNumerator: n denominator: d d = 0 ifTrue: [^(ZeroDivide dividend: n) signal] ifFalse: [numerator := n asInteger. denominator := d asInteger abs. "keep sign in numerator" d < 0 ifTrue: [numerator := numerator negated]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Fraction class instanceVariableNames: ''! !Fraction class methodsFor: 'instance creation' stamp: 'di 8/31/1999 10:16'! numerator: numInteger denominator: denInteger "Answer an instance of me (numInteger/denInteger). NOTE: This primitive initialization method will not reduce improper fractions, so normal usage should be coded as, eg, (Fraction numerator: a denominator: b) reduced or, more simply, as a / b." ^self new setNumerator: numInteger denominator: denInteger! ! ClassTestCase subclass: #FractionTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'KernelTests-Numbers'! !FractionTest methodsFor: 'tests - printing' stamp: 'laza 3/30/2004 09:28'! testFractionPrinting self assert: (353/359) printString = '(353/359)'. self assert: ((2/3) printStringBase: 2) = '(10/11)'. self assert: ((2/3) storeStringBase: 2) = '(2r10/2r11)'. self assert: ((5/7) printStringBase: 3) = '(12/21)'. self assert: ((5/7) storeStringBase: 3) = '(3r12/3r21)'. self assert: ((11/13) printStringBase: 4) = '(23/31)'. self assert: ((11/13) storeStringBase: 4) = '(4r23/4r31)'. self assert: ((17/19) printStringBase: 5) = '(32/34)'. self assert: ((17/19) storeStringBase: 5) = '(5r32/5r34)'. self assert: ((23/29) printStringBase: 6) = '(35/45)'. self assert: ((23/29) storeStringBase: 6) = '(6r35/6r45)'. self assert: ((31/37) printStringBase: 7) = '(43/52)'. self assert: ((31/37) storeStringBase: 7) = '(7r43/7r52)'. self assert: ((41/43) printStringBase: 8) = '(51/53)'. self assert: ((41/43) storeStringBase: 8) = '(8r51/8r53)'. self assert: ((47/53) printStringBase: 9) = '(52/58)'. self assert: ((47/53) storeStringBase: 9) = '(9r52/9r58)'. self assert: ((59/61) printStringBase: 10) = '(59/61)'. self assert: ((59/61) storeStringBase: 10) = '(59/61)'. self assert: ((67/71) printStringBase: 11) = '(61/65)'. self assert: ((67/71) storeStringBase: 11) = '(11r61/11r65)'. self assert: ((73/79) printStringBase: 12) = '(61/67)'. self assert: ((73/79) storeStringBase: 12) = '(12r61/12r67)'. self assert: ((83/89) printStringBase: 13) = '(65/6B)'. self assert: ((83/89) storeStringBase: 13) = '(13r65/13r6B)'. self assert: ((97/101) printStringBase: 14) = '(6D/73)'. self assert: ((97/101) storeStringBase: 14) = '(14r6D/14r73)'. self assert: ((103/107) printStringBase: 15) = '(6D/72)'. self assert: ((103/107) storeStringBase: 15) = '(15r6D/15r72)'. self assert: ((109/113) printStringBase: 16) = '(6D/71)'. self assert: ((109/113) storeStringBase: 16) = '(16r6D/16r71)'. self assert: ((127/131) printStringBase: 17) = '(78/7C)'. self assert: ((127/131) storeStringBase: 17) = '(17r78/17r7C)'. self assert: ((137/139) printStringBase: 18) = '(7B/7D)'. self assert: ((137/139) storeStringBase: 18) = '(18r7B/18r7D)'. self assert: ((149/151) printStringBase: 19) = '(7G/7I)'. self assert: ((149/151) storeStringBase: 19) = '(19r7G/19r7I)'. self assert: ((157/163) printStringBase: 20) = '(7H/83)'. self assert: ((157/163) storeStringBase: 20) = '(20r7H/20r83)'. self assert: ((167/173) printStringBase: 21) = '(7K/85)'. self assert: ((167/173) storeStringBase: 21) = '(21r7K/21r85)'. self assert: ((179/181) printStringBase: 22) = '(83/85)'. self assert: ((179/181) storeStringBase: 22) = '(22r83/22r85)'. self assert: ((191/193) printStringBase: 23) = '(87/89)'. self assert: ((191/193) storeStringBase: 23) = '(23r87/23r89)'. self assert: ((197/199) printStringBase: 24) = '(85/87)'. self assert: ((197/199) storeStringBase: 24) = '(24r85/24r87)'. self assert: ((211/223) printStringBase: 25) = '(8B/8N)'. self assert: ((211/223) storeStringBase: 25) = '(25r8B/25r8N)'. self assert: ((227/229) printStringBase: 26) = '(8J/8L)'. self assert: ((227/229) storeStringBase: 26) = '(26r8J/26r8L)'. self assert: ((233/239) printStringBase: 27) = '(8H/8N)'. self assert: ((233/239) storeStringBase: 27) = '(27r8H/27r8N)'. self assert: ((241/251) printStringBase: 28) = '(8H/8R)'. self assert: ((241/251) storeStringBase: 28) = '(28r8H/28r8R)'. self assert: ((257/263) printStringBase: 29) = '(8P/92)'. self assert: ((257/263) storeStringBase: 29) = '(29r8P/29r92)'. self assert: ((269/271) printStringBase: 30) = '(8T/91)'. self assert: ((269/271) storeStringBase: 30) = '(30r8T/30r91)'. self assert: ((277/281) printStringBase: 31) = '(8T/92)'. self assert: ((277/281) storeStringBase: 31) = '(31r8T/31r92)'. self assert: ((283/293) printStringBase: 32) = '(8R/95)'. self assert: ((283/293) storeStringBase: 32) = '(32r8R/32r95)'. self assert: ((307/311) printStringBase: 33) = '(9A/9E)'. self assert: ((307/311) storeStringBase: 33) = '(33r9A/33r9E)'. self assert: ((313/317) printStringBase: 34) = '(97/9B)'. self assert: ((313/317) storeStringBase: 34) = '(34r97/34r9B)'. self assert: ((331/337) printStringBase: 35) = '(9G/9M)'. self assert: ((331/337) storeStringBase: 35) = '(35r9G/35r9M)'. self assert: ((347/349) printStringBase: 36) = '(9N/9P)'. self assert: ((347/349) storeStringBase: 36) = '(36r9N/36r9P)'. self assert: ((-2/3) printStringBase: 2) = '(-10/11)'. self assert: ((-2/3) storeStringBase: 2) = '(-2r10/2r11)'. self assert: ((5/-7) printStringBase: 3) = '(-12/21)'. self assert: ((5/-7) storeStringBase: 3) = '(-3r12/3r21)'. ! ! !FractionTest methodsFor: 'tests - sinuses' stamp: 'sd 3/4/2004 21:13'! testDegreeCos "self run: #testDegreeCos" self shouldnt: [ (4/3) degreeCos] raise: Error. self assert: (1/3) degreeCos printString = '0.999983076857744'! ! !FractionTest methodsFor: 'tests - sinuses' stamp: 'sd 3/5/2004 14:54'! testDegreeSin "self run: #testDegreeSin" self shouldnt: [ (4/3) degreeSin] raise: Error. self assert: (1/3) degreeSin printString = '0.005817731354993834'.! ! !FractionTest methodsFor: 'tests - sinuses' stamp: 'GabrielOmarCotelli 5/23/2009 20:19'! testReciprocal self assert: (1/2) reciprocal = 2; assert: (3/4) reciprocal = (4/3); assert: (-1/3) reciprocal = -3; assert: (-3/5) reciprocal = (-5/3)! ! Object subclass: #FreeTypeCache instanceVariableNames: 'maximumSize used fontTable fifo' classVariableNames: '' poolDictionaries: 'FreeTypeCacheConstants' category: 'FreeType-Cache'! !FreeTypeCache methodsFor: 'add-remove' stamp: 'tween 8/10/2006 19:34'! atFont: aFreeTypeFont charCode: charCodeInteger type: typeFlag | entry charCodeTable typeTable | (charCodeTable := fontTable at: aFreeTypeFont ifAbsent:[]) ifNotNil:[ (typeTable := charCodeTable at: charCodeInteger ifAbsent:[]) ifNotNil:[ (entry := typeTable at: typeFlag ifAbsent:[]) ifNotNil:[ fifo moveDown: entry. ^entry object]]]. self error: 'Not found'! ! !FreeTypeCache methodsFor: 'add-remove' stamp: 'tween 8/10/2006 21:20'! atFont: aFreeTypeFont charCode: charCodeInteger type: typeFlag ifAbsentPut: aBlock | charCodeTable typeTable entry v vSize | charCodeTable := fontTable at: aFreeTypeFont ifAbsentPut:[self dictionaryClass new: 60]. typeTable := charCodeTable at: charCodeInteger ifAbsentPut:[self dictionaryClass new: 10]. entry := typeTable at: typeFlag ifAbsent:[]. entry ifNotNil:[ fifo moveDown: entry. ^entry object]. v := aBlock value. vSize := self sizeOf: v. (maximumSize notNil and:[vSize > maximumSize]) ifTrue:[^v]. used := used + vSize. entry := (self fifoEntryClass new font: aFreeTypeFont; charCode: charCodeInteger; type: typeFlag; object: v; yourself). typeTable at: typeFlag put: entry. fifo addLast: entry. maximumSize ifNotNil:[self shrinkTo: maximumSize]. ^v ! ! !FreeTypeCache methodsFor: 'add-remove' stamp: 'tween 8/10/2006 21:20'! atFont: aFreeTypeFont charCode: charCodeInteger type: typeFlag put: anObject | charCodeTable typeTable anObjectSize oldEntry oldEntrySize entry | anObjectSize := self sizeOf: anObject. (maximumSize notNil and:[anObjectSize > maximumSize]) ifTrue:[^anObject]. (charCodeTable := fontTable at: aFreeTypeFont ifAbsentPut:[self dictionaryClass new: 60]) ifNotNil:[ (typeTable := charCodeTable at: charCodeInteger ifAbsentPut:[self dictionaryClass new: 10]) ifNotNil:[ oldEntry := typeTable at: typeFlag ifAbsent:[]. oldEntrySize := (oldEntry isNil ifTrue:[0] ifFalse:[self sizeOf: oldEntry object]). entry := (self fifoEntryClass new font: aFreeTypeFont; charCode: charCodeInteger; type: typeFlag; object: anObject; yourself). typeTable at: typeFlag put: entry]]. used := used + anObjectSize - oldEntrySize. oldEntry ifNotNil: [fifo remove: oldEntry]. fifo addLast: entry. maximumSize ifNotNil:[self shrinkTo: maximumSize]. ^anObject ! ! !FreeTypeCache methodsFor: 'add-remove' stamp: 'tween 8/10/2006 13:40'! removeAll fontTable := self dictionaryClass new: 100. fifo := self fifoClass new. used := 0. ! ! !FreeTypeCache methodsFor: 'add-remove' stamp: 'tween 8/10/2006 15:03'! removeAllForFont: aFreeTypeFont | toRemove d | (fontTable includesKey: aFreeTypeFont) ifFalse:[^self]. toRemove := IdentitySet new. fifo do:[:entry | entry font = aFreeTypeFont ifTrue:[toRemove add: entry]]. toRemove do:[:entry | fifo remove: entry. d := (fontTable at: entry font) at: entry charCode. d removeKey: entry type. used := used - (self sizeOf: entry object) ]. ! ! !FreeTypeCache methodsFor: 'add-remove' stamp: 'tween 8/10/2006 15:28'! removeAllForType: typeFlag | toRemove d | toRemove := IdentitySet new. fifo do:[:entry | entry type = typeFlag ifTrue:[toRemove add: entry]]. toRemove do:[:entry | fifo remove: entry. d := (fontTable at: entry font) at: entry charCode. d removeKey: entry type. used := used - (self sizeOf: entry object) ]. ! ! !FreeTypeCache methodsFor: 'initialization' stamp: 'alain.plantec 5/28/2009 09:54'! initialize super initialize. maximumSize := self class defaultMaximumSize. fontTable := self dictionaryClass new: 100. used := 0. fifo := self fifoClass new ! ! !FreeTypeCache methodsFor: 'public' stamp: 'tween 8/10/2006 12:56'! maximumSize: anIntegerOrNil maximumSize := anIntegerOrNil. maximumSize ifNotNil:[ used > maximumSize ifTrue:["shrink" self shrinkTo: maximumSize]]! ! !FreeTypeCache methodsFor: 'public' stamp: 'tween 8/10/2006 13:46'! report "answer a description of the current state of the cache" | usedPercent | usedPercent := maximumSize isNil ifTrue:[0] ifFalse:[(used * 100 / maximumSize) asFloat rounded]. ^usedPercent asString,'% Full (maximumSize: ', maximumSize asString, ' , used: ', used asString,')'! ! !FreeTypeCache methodsFor: 'public' stamp: 'tween 8/10/2006 15:14'! sizeOf: anObject ^(anObject isKindOf: Form) ifTrue:[(anObject bitsSize * 4) + 32] ifFalse:[4] ! ! !FreeTypeCache methodsFor: 'private' stamp: 'tween 8/10/2006 13:20'! dictionaryClass ^Dictionary! ! !FreeTypeCache methodsFor: 'private' stamp: 'tween 8/10/2006 19:03'! fifoClass ^FreeTypeCacheLinkedList! ! !FreeTypeCache methodsFor: 'private' stamp: 'tween 8/10/2006 13:22'! fifoEntryClass ^FreeTypeCacheEntry! ! !FreeTypeCache methodsFor: 'private' stamp: 'tween 9/29/2007 20:10'! shrinkTo: newSize "if the used size is greater than newSize, then remove all the receiver's entries" used > newSize ifTrue:[self removeAll]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeCache class instanceVariableNames: 'current'! !FreeTypeCache class methodsFor: 'accessing' stamp: 'tween 8/10/2006 15:33'! clearCurrent " self clearCurrent. " current := nil! ! !FreeTypeCache class methodsFor: 'accessing' stamp: 'tween 8/10/2006 17:03'! current current isNil ifFalse:[^current]. ^current := self new! ! !FreeTypeCache class methodsFor: 'accessing' stamp: 'tween 8/10/2006 09:30'! defaultMaximumSize "answer the default maximumSize in bytes" ^1024*5000 "5 Megabytes"! ! !FreeTypeCache class methodsFor: 'accessing' stamp: 'tween 8/10/2006 15:45'! initialize " self initialize. " Smalltalk addToShutDownList: self. "should it be at a particular place in the list?"! ! !FreeTypeCache class methodsFor: 'accessing' stamp: 'tween 8/10/2006 15:45'! shutDown: quitting (current notNil and: [self clearCacheOnShutdown]) ifTrue:[self current removeAll]! ! !FreeTypeCache class methodsFor: 'system shutdown' stamp: 'tween 8/10/2006 15:44'! clearCacheOnShutdown "answer true if the cache should be cleared on image shutdown" ^true! ! SharedPool subclass: #FreeTypeCacheConstants instanceVariableNames: '' classVariableNames: 'FreeTypeCacheGlyph FreeTypeCacheGlyphLCD FreeTypeCacheGlyphMono FreeTypeCacheLinearWidth FreeTypeCacheWidth' poolDictionaries: '' category: 'FreeType-Cache'! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeCacheConstants class instanceVariableNames: ''! !FreeTypeCacheConstants class methodsFor: 'class initialization' stamp: 'tween 3/31/2007 21:31'! initialize " FreeTypeCacheConstants initialize " FreeTypeCacheWidth := 0. FreeTypeCacheGlyph := 100. "start at 100 and allow room for 64 subpixel positioned glyphs" FreeTypeCacheGlyphLCD := 200. "start at 200 and allow room for 64 subpixel positioned glyphs" FreeTypeCacheGlyphMono := 3. FreeTypeCacheLinearWidth := 4 ! ! Link subclass: #FreeTypeCacheEntry instanceVariableNames: 'font charCode type object previousLink' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Cache'! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 13:16'! charCode "Answer the value of charCode" ^ charCode! ! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 13:16'! charCode: anObject "Set the value of charCode" charCode := anObject! ! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 13:16'! font "Answer the value of font" ^ font! ! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 13:16'! font: anObject "Set the value of font" font := anObject! ! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 14:55'! object "Answer the value of object" ^ object! ! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 14:55'! object: anObject "Set the value of object" object := anObject! ! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 17:56'! previousLink "Answer the value of previousLink" ^ previousLink! ! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 17:56'! previousLink: anObject "Set the value of previousLink" previousLink := anObject! ! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 13:16'! type "Answer the value of type" ^ type! ! !FreeTypeCacheEntry methodsFor: 'accessing' stamp: 'tween 8/10/2006 13:16'! type: anObject "Set the value of type" type := anObject! ! !FreeTypeCacheEntry methodsFor: 'comparing' stamp: 'tween 8/10/2006 14:58'! = aFreeTypeCacheEntry "equailty based on font,charcode, type, object, but not nextLink" (aFreeTypeCacheEntry isKindOf: FreeTypeCacheEntry) ifFalse:[^false]. ^font = aFreeTypeCacheEntry font and: [ charCode = aFreeTypeCacheEntry charCode and: [type = aFreeTypeCacheEntry type and:[object = aFreeTypeCacheEntry object]]]! ! !FreeTypeCacheEntry methodsFor: 'comparing' stamp: 'tween 8/10/2006 13:34'! hash ^charCode hash! ! LinkedList subclass: #FreeTypeCacheLinkedList instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Cache'! !FreeTypeCacheLinkedList methodsFor: 'adding' stamp: 'tween 8/10/2006 18:47'! add: link after: otherLink "Add otherLink after link in the list. Answer aLink." | savedLink | savedLink := otherLink nextLink. otherLink nextLink: link. link nextLink: savedLink. savedLink == nil ifFalse:[savedLink previousLink: link]. link previousLink: otherLink. ^link. ! ! !FreeTypeCacheLinkedList methodsFor: 'adding' stamp: 'tween 8/10/2006 18:47'! add: link before: otherLink | savedLink | firstLink == otherLink ifTrue: [^ self addFirst: link]. otherLink ifNotNil:[ savedLink := otherLink previousLink. link nextLink: otherLink. link previousLink: savedLink. otherLink previousLink: link. savedLink == nil ifFalse:[savedLink nextLink: link]]. ^ self errorNotFound: otherLink! ! !FreeTypeCacheLinkedList methodsFor: 'adding' stamp: 'tween 8/10/2006 18:52'! addFirst: aLink "Add aLink to the beginning of the receiver's list. Answer aLink." self isEmpty ifTrue: [^lastLink :=firstLink := aLink]. aLink nextLink: firstLink. aLink previousLink: nil. firstLink == nil ifFalse: [firstLink previousLink: aLink]. firstLink := aLink. ^aLink! ! !FreeTypeCacheLinkedList methodsFor: 'adding' stamp: 'tween 8/10/2006 18:52'! addLast: aLink "Add aLink to the end of the receiver's list. Answer aLink." self isEmpty ifTrue: [^firstLink := lastLink := aLink]. aLink previousLink: lastLink. aLink nextLink: nil. lastLink == nil ifFalse: [lastLink nextLink: aLink]. lastLink := aLink. ^aLink! ! !FreeTypeCacheLinkedList methodsFor: 'removing' stamp: 'tween 8/10/2006 18:48'! remove: aLink ifAbsent: aBlock | prev next | prev := aLink previousLink. next := aLink nextLink. prev == nil ifFalse: [prev nextLink: next]. next == nil ifFalse: [next previousLink: prev]. aLink == firstLink ifTrue:[firstLink := next]. aLink == lastLink ifTrue:[lastLink := prev]. aLink nextLink: nil. aLink previousLink: nil. ^aLink! ! !FreeTypeCacheLinkedList methodsFor: 'removing' stamp: 'tween 8/10/2006 21:06'! removeFirst "Remove the first element and answer it. If the receiver is empty, create an error notification." | oldLink | self emptyCheck. oldLink := firstLink. oldLink previousLink: nil. lastLink == firstLink ifTrue:[ lastLink := firstLink := nil. oldLink nextLink: nil. ^oldLink]. firstLink := oldLink nextLink. firstLink == nil ifTrue:[firstLink := lastLink := nil] ifFalse:[firstLink previousLink: nil]. oldLink nextLink: nil. ^oldLink! ! !FreeTypeCacheLinkedList methodsFor: 'removing' stamp: 'tween 8/10/2006 21:09'! removeLast "Remove the first element and answer it. If the receiver is empty, create an error notification." | oldLink | self emptyCheck. oldLink := lastLink. oldLink nextLink: nil. lastLink == firstLink ifTrue:[ lastLink := firstLink := nil. oldLink previousLink: nil. ^oldLink]. lastLink := oldLink previousLink. lastLink == nil ifTrue:[firstLink := lastLink := nil] ifFalse:[lastLink nextLink: nil]. oldLink previousLink: nil. ^oldLink! ! !FreeTypeCacheLinkedList methodsFor: 'reordering' stamp: 'tween 3/31/2007 12:31'! moveDown: aLink | e1 e2 e3 e4 | (e3 := aLink nextLink) ifNil:[^self]. e2 := aLink. e4 := e3 nextLink. e1 := e2 previousLink. "swap e2 & e3" e1 ifNotNil:[e1 nextLink: e2]. e2 nextLink: e3. e3 nextLink: e4. e4 ifNotNil:[e4 previousLink: e3]. e3 previousLink: e2. e2 previousLink: e1 ! ! TestCase subclass: #FreeTypeCacheTest instanceVariableNames: 'cache cache1K fullCache font1 font1XGlyph font1ZGlyph font1YGlyph font2 font3' classVariableNames: '' poolDictionaries: 'FreeTypeCacheConstants' category: 'FreeTypeTests-cache'! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 3/23/2007 08:07'! setUp cache := FreeTypeCache new. font1 := FreeTypeFont basicNew. font2 := FreeTypeFont basicNew. font3 := FreeTypeFont basicNew. font1XGlyph := (GlyphForm extent: 100@100 depth: 32) advance: 100; linearAdvance: 10000; yourself. font1YGlyph := (GlyphForm extent: 100@100 depth: 32) advance: 100; linearAdvance: 10000; yourself. font1ZGlyph := (GlyphForm extent: 100@100 depth: 32) advance: 100; linearAdvance: 10000; yourself. fullCache := FreeTypeCache new. fullCache maximumSize: (10*(fullCache sizeOf: font1YGlyph)).. 1 to: 10 do:[:i | fullCache atFont: font1 charCode: i type: FreeTypeCacheGlyph put: font1YGlyph]. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 10:29'! testConstants | constants | constants := {FreeTypeCacheWidth. FreeTypeCacheGlyphMono. FreeTypeCacheGlyphLCD.FreeTypeCacheGlyph}. self assert: constants asSet size = constants size. "no 2 have same value" self assert: (constants detect:[:x | x isNil] ifNone:[]) isNil. "no value is nil" ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 9/29/2007 20:02'! testEntriesRemovedFIFO | | cache maximumSize: 10*(cache sizeOf: font1XGlyph). 1 to: 10 do:[:i | cache atFont: font1 charCode: (1000-i) type: FreeTypeCacheGlyph put: font1XGlyph]. self validateCollections: cache. 11 to:1000 do:[:i | cache atFont: font1 charCode: (1000-i) type: FreeTypeCacheGlyph put: font1XGlyph. self validateSizes: cache. self validateCollections: cache. "i-9 to: i do:[:i2 | self shouldnt: [cache atFont: font1 charCode: 1000-i2 type: FreeTypeCacheGlyph] raise: Error]." self should: [cache atFont: font1 charCode: 1000-(i-10) type: FreeTypeCacheGlyph] raise: Error]. self validateSizes: cache. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 11:19'! testFailedGet | | self should: [cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph] raise: Error. self assert: (cache instVarNamed: #fontTable) isEmpty. self assert: (cache instVarNamed: #used) = 0. self validateSizes: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 14:57'! testFreeTypeCacheEntry | f f2 f3 | f := FreeTypeCacheEntry new. f charCode: 1; font: font1; type: FreeTypeCacheGlyph; object: font1XGlyph. f2 := FreeTypeCacheEntry new. f2 charCode: 2; font: font1; type: FreeTypeCacheGlyphLCD; object: font1XGlyph. f nextLink: f2. self assert: f ~= f2. self assert: f nextLink = f2 . f3 := f copy. f3 nextLink: nil. self assert: f = f3. "equality not based on nextLink"! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 13:41'! testInstanceInitialization self assert: (cache instVarNamed: #maximumSize) = FreeTypeCache defaultMaximumSize. self assert: (cache instVarNamed: #used) = 0. self assert: (cache instVarNamed: #fontTable) class = cache dictionaryClass. self assert: (cache instVarNamed: #fontTable) isEmpty. self assert: (cache instVarNamed: #fifo) class = cache fifoClass. self assert: (cache instVarNamed: #fifo) isEmpty. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 9/29/2007 20:05'! testMaximumSizeRespectedOnIfAbsentPut | | cache maximumSize: (cache sizeOf: font1XGlyph). cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph ifAbsentPut: font1XGlyph. self validateSizes: cache. self validateCollections: cache. cache atFont: font1 charCode: $Y asInteger type: FreeTypeCacheGlyph ifAbsentPut: font1XGlyph. self assert: (cache instVarNamed:#used) = 0. "cache has been cleared on reaching max size" self validateSizes: cache. self validateCollections: cache. self should: [cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph] raise: Error. self should: [cache atFont: font1 charCode: $Y asInteger type: FreeTypeCacheGlyph] raise: Error. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 9/29/2007 20:06'! testMaximumSizeRespectedOnPut | | cache maximumSize: (cache sizeOf: font1XGlyph). cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph put: font1XGlyph. self validateSizes: cache. self validateCollections: cache. cache atFont: font1 charCode: $Y asInteger type: FreeTypeCacheGlyph put: font1XGlyph. self assert: (cache instVarNamed:#used) = 0. "cache has been cleared on reaching max size" self validateSizes: cache. self validateCollections: cache. self should: [cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph] raise: Error. self should: [cache atFont: font1 charCode: $Y asInteger type: FreeTypeCacheGlyph] raise: Error. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 15:52'! testNormalGetIfAbsentPut | u g r | cache maximumSize: nil. u := cache instVarNamed: #used. r := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph ifAbsentPut: [font1XGlyph]. self assert: (r isKindOf: GlyphForm). self assert: (cache instVarNamed: #used) > u. "grown" self validateSizes: cache. g := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph. self assert: g == font1XGlyph. self validateSizes: cache. self validateCollections: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 3/31/2007 12:26'! testNormalGetIfAbsentPutTwice | u g r | cache maximumSize: nil. u := cache instVarNamed: #used. r := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph ifAbsentPut: [font1XGlyph]. r := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph ifAbsentPut: [font1XGlyph]. self assert: (r isKindOf: GlyphForm). self assert: (cache instVarNamed: #used) > u. "grown" self validateSizes: cache. g := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph. self assert: g == font1XGlyph. self validateSizes: cache. self validateCollections: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 3/31/2007 12:26'! testNormalGetIfAbsentPutTwiceIntoNonEmptyCache | u g r | cache maximumSize: nil. u := cache instVarNamed: #used. r := cache atFont: font1 charCode: $Z asInteger type: FreeTypeCacheGlyph ifAbsentPut: [font1XGlyph]. r := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph ifAbsentPut: [font1XGlyph]. r := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph ifAbsentPut: [font1XGlyph]. self assert: (r isKindOf: GlyphForm). self assert: (cache instVarNamed: #used) > u. "grown" self validateSizes: cache. g := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph. self assert: g == font1XGlyph. self validateSizes: cache. self validateCollections: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 12:47'! testNormalPutGet | u g | cache maximumSize: nil. u := cache instVarNamed: #used. cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph put: font1XGlyph. self assert: (cache instVarNamed: #used) > u. "grown" self validateSizes: cache. g := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph. self assert: g == font1XGlyph. self validateSizes: cache. self validateCollections: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 3/31/2007 12:21'! testNormalPutGetTwice | u g | cache maximumSize: nil. u := cache instVarNamed: #used. cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph put: font1XGlyph. self assert: (cache instVarNamed: #used) > u. "grown" self validateSizes: cache. g := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph. g := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph. self assert: g == font1XGlyph. self validateSizes: cache. self validateCollections: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 15:12'! testNormalPutGetWidth | u g | cache maximumSize: nil. u := cache instVarNamed: #used. cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheWidth put: 100. self assert: (cache instVarNamed: #used) > u. "grown" self validateSizes: cache. g := cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheWidth. self assert: g = 100. self validateSizes: cache. self validateCollections: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 14:41'! testPutSameElementTwice | | cache maximumSize: nil. cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph put: font1XGlyph. self assert: (cache instVarNamed: #used) = (cache sizeOf: font1XGlyph). self validateSizes: cache. self validateCollections: cache. cache atFont: font1 charCode: $X asInteger type: FreeTypeCacheGlyph put: font1XGlyph. self assert: (cache instVarNamed: #used) = (cache sizeOf: font1XGlyph). self validateSizes: cache. self validateCollections: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 13:05'! testRemoveAll | m fifo fontTable | m := fullCache instVarNamed: #maximumSize. fifo := fullCache instVarNamed: #fifo. fontTable := fullCache instVarNamed: #fontTable. fullCache removeAll. self assert: (fullCache instVarNamed: #fifo) isEmpty. self assert: (fullCache instVarNamed: #fontTable) isEmpty. self assert: (fullCache instVarNamed: #used) = 0. self assert: m = (fullCache instVarNamed: #maximumSize). self assert: fifo class = (fullCache instVarNamed: #fifo) class. self assert: fontTable class = (fullCache instVarNamed: #fontTable) class. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 14:21'! testRemoveAllForFont | fifo | fullCache maximumSize: nil. 1 to: 100 do:[:i | fullCache atFont: font1 charCode: i type: 1 put: font1XGlyph]. 1 to: 100 do:[:i | fullCache atFont: font2 charCode: i type: 2 put: font1YGlyph]. 1 to: 100 do:[:i | fullCache atFont: font3 charCode: i type: 3 put: font1ZGlyph]. fifo := fullCache instVarNamed: #fifo. self assert: (fifo detect:[:each | each font = font1] ifNone:[]) notNil. self assert: (fifo detect:[:each | each font = font2] ifNone:[]) notNil. self assert: (fifo detect:[:each | each font = font3] ifNone:[]) notNil. fullCache removeAllForFont: font1. self validateSizes: fullCache. self validateCollections: fullCache. fifo := (fullCache instVarNamed: #fifo). self assert: (fifo detect:[:each | each font = font1] ifNone:[]) isNil. self assert: (fifo detect:[:each | each font = font2] ifNone:[]) notNil. self assert: (fifo detect:[:each | each font = font2] ifNone:[]) notNil. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 15:29'! testRemoveAllForType | fifo | fullCache maximumSize: nil. 1 to: 100 do:[:i | fullCache atFont: font1 charCode: i type: 1 put: font1XGlyph]. 1 to: 100 do:[:i | fullCache atFont: font2 charCode: i type: 2 put: font1YGlyph]. 1 to: 100 do:[:i | fullCache atFont: font3 charCode: i type: 3 put: font1ZGlyph]. fifo := fullCache instVarNamed: #fifo. self assert: (fifo detect:[:each | each type = 1] ifNone:[]) notNil. self assert: (fifo detect:[:each | each type = 2] ifNone:[]) notNil. self assert: (fifo detect:[:each | each type = 3] ifNone:[]) notNil. fullCache removeAllForType: 1. self validateSizes: fullCache. self validateCollections: fullCache. fifo := (fullCache instVarNamed: #fifo). self assert: (fifo detect:[:each | each type = 1] ifNone:[]) isNil. self assert: (fifo detect:[:each | each type = 2] ifNone:[]) notNil. self assert: (fifo detect:[:each | each type = 3] ifNone:[]) notNil. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 13:52'! testReport self assert: fullCache report = '100% Full (maximumSize: 400320 , used: 400320)'. fullCache maximumSize: 800640. self assert: fullCache report = '50% Full (maximumSize: 800640 , used: 400320)'. self assert: cache report = '0% Full (maximumSize: 5120000 , used: 0)'. cache maximumSize: nil. self assert: cache report = '0% Full (maximumSize: nil , used: 0)'. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 12:48'! testSetMaximumSize cache maximumSize: 0. self assert: (cache instVarNamed: #maximumSize) = 0. cache maximumSize: 99999999999999999. self assert: (cache instVarNamed: #maximumSize) = 99999999999999999. cache maximumSize: nil. "unbounded" self assert: (cache instVarNamed: #maximumSize) = nil. self validateSizes: cache. self validateCollections: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 12:48'! testSetMaximumSizeGrow | u m | u := fullCache instVarNamed: #used. m := fullCache instVarNamed: #maximumSize. fullCache maximumSize: m * 2 . "grow" self assert: u = (fullCache instVarNamed: #used). self validateSizes: cache. self validateCollections: cache! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 9/29/2007 20:07'! testSetMaximumSizeShrink | m | m := fullCache instVarNamed: #maximumSize. fullCache maximumSize: m // 2 . "shrink" self assert: (fullCache instVarNamed: #used) = 0. "cache is cleared when used > maximumSize" self validateSizes: fullCache. self validateCollections: fullCache. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 12:48'! testSetMaximumSizeUnbounded | u | u := fullCache instVarNamed: #used. fullCache maximumSize: nil. "unbounded" self assert: u = (fullCache instVarNamed: #used). self validateSizes: cache. self validateCollections: cache ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 09:24'! testSingleton self assert: FreeTypeCache current class = FreeTypeCache. self assert: FreeTypeCache current == FreeTypeCache current. ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 3/31/2007 12:12'! validateCollections: aFreeTypeCache "check that the fifo list entries match the fontTable dict hierarchy" | fontTable fontTableEntries fifo lastLink | fontTable := aFreeTypeCache instVarNamed: #fontTable. fifo := aFreeTypeCache instVarNamed: #fifo. lastLink := (fifo instVarNamed:#lastLink). fontTableEntries := Set new. fontTable keysAndValuesDo:[:k1 :v1 | v1 keysAndValuesDo:[:k2 :v2 | v2 keysAndValuesDo:[:k3 :v3 | fontTableEntries add: v3 ]]]. self assert: fifo size = fontTableEntries size. self assert: (fifo asSet = fontTableEntries). self assert: (lastLink isNil or:[lastLink nextLink isNil]) ! ! !FreeTypeCacheTest methodsFor: 'as yet unclassified' stamp: 'tween 8/10/2006 15:04'! validateSizes: aFreeTypeCache "check that the used, maximumSize, and caches entries are valid" | fontTable calcSize max used | fontTable := aFreeTypeCache instVarNamed: #fontTable. used := aFreeTypeCache instVarNamed: #used. max := aFreeTypeCache instVarNamed: #maximumSize. calcSize := 0. fontTable do:[:charCodeTable | charCodeTable do:[:typeTable | typeTable do:[:entry | calcSize := calcSize + (aFreeTypeCache sizeOf: entry object)]]]. self assert: calcSize = used. self assert: (max isNil or:[used <= max]) ! ! FreeTypeFileInfoAbstract subclass: #FreeTypeEmbeddedFileInfo instanceVariableNames: 'fileContents baseName' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FreeTypeEmbeddedFileInfo methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:21'! baseName "Answer the value of baseName" ^ baseName! ! !FreeTypeEmbeddedFileInfo methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:19'! baseName: anObject "Set the value of baseName" baseName := anObject! ! !FreeTypeEmbeddedFileInfo methodsFor: 'accessing' stamp: 'tween 9/29/2007 08:21'! familyGroupName ^familyGroupName ! ! !FreeTypeEmbeddedFileInfo methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:19'! fileContents "Answer the value of fileContents" ^ fileContents! ! !FreeTypeEmbeddedFileInfo methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:19'! fileContents: anObject "Set the value of fileContents" fileContents := anObject! ! !FreeTypeEmbeddedFileInfo methodsFor: 'accessing' stamp: 'tween 7/28/2007 12:43'! fileSize ^fileContents size! ! !FreeTypeEmbeddedFileInfo methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:16'! locationType "Answer the value of locationType" ^ #embedded! ! !FreeTypeEmbeddedFileInfo methodsFor: 'printing' stamp: 'tween 8/16/2007 01:08'! printOn: aStream "super printOn: aStream." aStream nextPutAll: '{', self locationType asString,'}'; nextPutAll: '(' , fileContents size asString, ' bytes )'; nextPutAll: '[',index asString,'] '; nextPutAll: familyName asString; nextPutAll: ' - ', styleName asString; nextPutAll: ' - ', postscriptName asString; nextPutAll: ' ',(bold ifTrue:['B'] ifFalse:['']); nextPutAll: ' ',(italic ifTrue:['I'] ifFalse:['']); nextPutAll: ' ',(fixedWidth ifTrue:['Monospaced'] ifFalse:['']); nextPutAll: ' ',(stretchValue asString); nextPutAll: ' ',(weightValue asString); cr! ! !FreeTypeEmbeddedFileInfo methodsFor: 'testing' stamp: 'tween 7/16/2007 00:31'! isEmbedded ^true! ! FT2Handle subclass: #FreeTypeExternalMemory instanceVariableNames: 'bytes' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Base'! !FreeTypeExternalMemory methodsFor: 'accessing' stamp: 'tween 8/12/2006 08:40'! bytes ^bytes! ! !FreeTypeExternalMemory methodsFor: 'accessing' stamp: 'tween 8/12/2006 08:40'! bytes: aByteArray bytes := aByteArray! ! !FreeTypeExternalMemory methodsFor: 'primitives' stamp: 'tween 8/12/2006 10:25'! primCopyToExternalMemory: aByteArray "copy aByteArray into newly allocated, external memory, and store the address of that memory in the receiver's handle" ^self primitiveFailed! ! !FreeTypeExternalMemory methodsFor: 'primitives' stamp: 'tween 8/12/2006 10:24'! primDestroyHandle ^self primitiveFailed! ! !FreeTypeExternalMemory methodsFor: 'validation' stamp: 'tween 8/12/2006 10:25'! validate self isValid ifFalse: [ bytes ifNotNil:[ [self primCopyToExternalMemory: bytes] on: FT2Error do:[:e |"need to do something here?"]. self isValid ifTrue:[self class register: self]]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeExternalMemory class instanceVariableNames: ''! !FreeTypeExternalMemory class methodsFor: 'instance creation' stamp: 'tween 8/12/2006 08:42'! bytes: aByteArray | answer | answer := self basicNew bytes: aByteArray; yourself. ^answer! ! FT2Face subclass: #FreeTypeFace instanceVariableNames: 'filename index fileContentsExternalMemory valid hasKerning' classVariableNames: '' poolDictionaries: '' category: 'FreeType-Fonts'! !FreeTypeFace methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:44'! familyName ^super familyName ifNil:['?']! ! !FreeTypeFace methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:44'! fileContentsExternalMemory: aFreeTypeExternalMemory fileContentsExternalMemory := aFreeTypeExternalMemory! ! !FreeTypeFace methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:44'! fileContentsExternalMemoryBytes ^fileContentsExternalMemory ifNotNil:[fileContentsExternalMemory bytes]! ! !FreeTypeFace methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:44'! filename ^filename! ! !FreeTypeFace methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:44'! filename: aString filename := aString! ! !FreeTypeFace methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:44'! index ^index! ! !FreeTypeFace methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:44'! index: anInteger index := anInteger! ! !FreeTypeFace methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:44'! styleName ^super styleName ifNil:['']! ! !FreeTypeFace methodsFor: 'caching' stamp: 'tween 3/31/2007 16:36'! releaseCachedState hasKerning := nil. self destroyHandle. ! ! !FreeTypeFace methodsFor: 'initialize-release' stamp: 'tween 3/16/2007 12:44'! actAsExecutor super actAsExecutor. filename := ''.! ! !FreeTypeFace methodsFor: 'initialize-release' stamp: 'tween 3/16/2007 12:53'! beNull super beNull. valid := nil ! ! !FreeTypeFace methodsFor: 'testing' stamp: 'tween 3/16/2007 12:44'! hasFamilyName ^super familyName notNil! ! !FreeTypeFace methodsFor: 'testing' stamp: 'tween 3/31/2007 14:52'! hasKerning ^hasKerning ifNil:[ [hasKerning := self primHasKerning = 64] on: Error do:[:e | hasKerning := false]. hasKerning]! ! !FreeTypeFace methodsFor: 'testing' stamp: 'tween 3/16/2007 12:44'! hasStyleName ^super styleName notNil! ! !FreeTypeFace methodsFor: 'testing' stamp: 'tween 3/31/2007 16:18'! isValid ^valid ifNil:[valid := super isValid]! ! !FreeTypeFace methodsFor: 'validation' stamp: 'tween 3/16/2007 12:44'! create "create me in the FT2Plugin. This gets my handle, and loads the fields" fileContentsExternalMemory isNil ifTrue:[ self newFaceFromFile: (self class fontPathFor: filename) index: index] ifFalse:[ self newFaceFromExternalMemory: fileContentsExternalMemory index: index]. self loadFields ! ! !FreeTypeFace methodsFor: 'validation' stamp: 'tween 3/17/2007 12:21'! newFaceFromExternalMemory: aFreeTypeExternalMemory index: anInteger | answer | valid := nil. answer := super newFaceFromExternalMemory: aFreeTypeExternalMemory index: anInteger. valid := super isValid. ^answer ! ! !FreeTypeFace methodsFor: 'validation' stamp: 'tween 3/17/2007 12:19'! newFaceFromFile: fileName index: anInteger | answer | valid := nil. answer := super newFaceFromFile: fileName index: anInteger. valid := super isValid. ^answer ! ! !FreeTypeFace methodsFor: 'validation' stamp: 'tween 3/16/2007 12:44'! primNewFaceFromExternalMemory: aFreeTypeExternalMemory size: anInteger index: anInteger2 ^self primitiveFailed! ! !FreeTypeFace methodsFor: 'validation' stamp: 'tween 3/16/2007 12:44'! validate "If the receiver is not valid (has a nil handle), then create the receiver to obtain a handle and load the receiver's fields" self isValid ifFalse: [self create]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeFace class instanceVariableNames: ''! !FreeTypeFace class methodsFor: 'font dirs' stamp: 'tween 3/16/2007 12:44'! fontPathFor: aFilename "aFilename is local. Try hard to return a valid path to be handed to freetype library" "temporary solution ;-)" ^(FileDirectory default directoryNamed: 'Fonts') fullPathFor: aFilename! ! !FreeTypeFace class methodsFor: 'font dirs' stamp: 'tween 3/16/2007 12:44'! rememberFontDir: aDirecory! ! !FreeTypeFace class methodsFor: 'instance creation' stamp: 'tween 3/16/2007 12:44'! fromBytes: aByteArray index: anInteger "share alike instances" self allInstancesDo: [:inst | (inst fileContentsExternalMemoryBytes = aByteArray and: [inst index = anInteger]) ifTrue: [^inst "validate"]]. ^(self basicNew) fileContentsExternalMemory: (FreeTypeExternalMemory bytes: aByteArray); index: anInteger; yourself! ! !FreeTypeFace class methodsFor: 'instance creation' stamp: 'tween 3/16/2007 12:44'! fromFile: aFileName index: anInteger "share alike instances" ^FileDirectory splitName: aFileName to: [:dir :fname | self rememberFontDir: dir. self allInstancesDo: [:inst | (inst filename = aFileName and: [inst index = anInteger]) ifTrue: [^inst "validate"]]. (self basicNew) filename: aFileName; index: anInteger; yourself]! ! FreeTypeFileInfoAbstract subclass: #FreeTypeFileInfo instanceVariableNames: 'absoluteOrRelativePath absolutePath locationType modificationTime fileSize' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/15/2007 18:29'! absoluteOrRelativePath "Answer the value of absoluteOrRelativePath" ^ absoluteOrRelativePath! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/15/2007 18:29'! absoluteOrRelativePath: anObject "Set the value of absoluteOrRelativePath" absoluteOrRelativePath := anObject! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/16/2007 04:26'! absolutePath "Answer the value of absolutePath" ^ absolutePath! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/16/2007 04:26'! absolutePath: anObject "Set the value of absolutePath" absolutePath := anObject! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 8/12/2007 16:53'! baseName ^(FileDirectory baseNameFor: (FileDirectory localNameFor: absolutePath))! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 9/29/2007 08:22'! familyGroupName ^familyGroupName! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/16/2007 00:55'! fileSize "Answer the value of fileSize" ^ fileSize! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/16/2007 00:55'! fileSize: anObject "Set the value of fileSize" fileSize := anObject! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/15/2007 17:31'! locationType "Answer the value of locationType" ^ locationType! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/15/2007 17:31'! locationType: anObject "Set the value of locationType" locationType := anObject! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/16/2007 01:14'! modificationTime "Answer the value of modificationTime" ^ modificationTime! ! !FreeTypeFileInfo methodsFor: 'accessing' stamp: 'tween 3/16/2007 01:14'! modificationTime: anObject "Set the value of modificationTime" modificationTime := anObject! ! !FreeTypeFileInfo methodsFor: 'printing' stamp: 'tween 8/16/2007 01:08'! printOn: aStream "super printOn: aStream." aStream nextPutAll: familyGroupName asString, '::',styleNameExtracted asString, ' '; nextPutAll: (locationType = #absolute ifTrue:[''] ifFalse:['{',locationType asString,'}']); nextPutAll: absoluteOrRelativePath asString; nextPutAll: '[',index asString,'] '; nextPutAll: familyName asString; nextPutAll: ' - ', styleName asString; nextPutAll: ' - ', postscriptName asString; nextPutAll: ' ',(bold ifTrue:['B'] ifFalse:['']); nextPutAll: ' ',(italic ifTrue:['I'] ifFalse:['']); nextPutAll: ' ',(fixedWidth ifTrue:['Monospaced'] ifFalse:['']); nextPutAll: ' ',(stretchValue asString); nextPutAll: ' ',(weightValue asString); cr! ! Object subclass: #FreeTypeFileInfoAbstract instanceVariableNames: 'index familyName styleName postscriptName bold italic fixedWidth numFaces familyGroupName slant slantValue weight stretch weightValue stretchValue styleNameExtracted upright' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! bold "Answer the value of bold" ^ bold! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! bold: anObject "Set the value of bold" bold := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 9/8/2007 22:34'! extractAttributesFromNames "derive values for the receiver's style(italic), weight, and stretch inst vars. Also set the familyGroupName and styleNameExtracted" | p | p:= FreeTypeNameParser new familyNameIn: self validFamilyName; styleNameIn: self validStyleName; italicFlag: italic; boldFlag: bold; parse. familyGroupName := p familyName. slant := p extractedSlant. slantValue := p extractedSlantValue. weight := p extractedWeight. weightValue := p extractedWeightValue. stretch := p extractedStretch. stretchValue := p extractedStretchValue. upright := p extractedUpright. styleNameExtracted := ''. stretch ifNotNil:[ styleNameExtracted := styleNameExtracted ,stretch]. (weight notNil "and:[weight asLowercase ~= 'medium']") ifTrue:[ styleNameExtracted := styleNameExtracted , ' ', weight]. slant ifNotNil:[ styleNameExtracted := styleNameExtracted , ' ', slant]. styleNameExtracted := styleNameExtracted withBlanksTrimmed. styleNameExtracted ifEmpty: [ styleNameExtracted := upright ifNil:['Regular']]. ! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! familyGroupName "Answer the value of familyGroupName" ^ familyGroupName! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! familyName "Answer the value of familyName" ^ familyName! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! familyName: anObject "Set the value of familyName" familyName := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! fixedWidth "Answer the value of fixedWidth" ^ fixedWidth! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! fixedWidth: anObject "Set the value of fixedWidth" fixedWidth := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! index "Answer the value of index" ^ index! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! index: anObject "Set the value of index" index := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 9/29/2007 10:42'! isBolderThan: val ^self weightValue >= val! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 9/29/2007 10:41'! isItalicOrOblique ^self slantValue > 0! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! italic "Answer the value of italic" ^ italic! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! italic: anObject "Set the value of italic" italic := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! numFaces "Answer the value of numFaces" ^ numFaces! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! numFaces: anObject "Set the value of numFaces" numFaces := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! postscriptName "Answer the value of postscriptName" ^ postscriptName! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! postscriptName: anObject "Set the value of postscriptName" postscriptName := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:59'! slant "Answer the value of slant" ^ slant! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 21:39'! slantValue ^slantValue! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/11/2007 14:22'! stretch "Answer the value of stretch" ^ stretch! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 01:04'! stretchValue "Answer the value of stretchValue" ^ stretchValue! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 01:04'! stretchValue: anObject "Set the value of stretchValue" stretchValue := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:59'! style "Answer the value of slant" ^ slant! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! styleName "Answer the value of styleName" ^ styleName! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 7/16/2007 00:20'! styleName: anObject "Set the value of styleName" styleName := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/12/2007 19:27'! styleNameExtracted ^styleNameExtracted! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 9/8/2007 23:23'! styleNameWithItalicForcedToBe: aString | answer | answer := ''. stretch ifNotNil:[ answer := answer ,stretch]. (weight notNil "and:[weight asLowercase ~= 'medium']") ifTrue:[ answer := answer , ' ', weight]. answer := answer , ' ', aString. answer := answer withBlanksTrimmed. ^answer ! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:59'! styleNameWithWeightForcedToBe: aString | answer | answer := ''. stretch ifNotNil:[ answer := answer ,stretch]. answer := answer , ' ', aString. slant ifNotNil:[ answer := answer , ' ', slant]. answer := answer withBlanksTrimmed. ^answer ! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 02:31'! styleNameWithWeightForcedToBe: aString italicForcedToBe: aString2 | answer | answer := ''. stretch ifNotNil:[ answer := answer ,stretch]. answer := answer , ' ', aString. answer := answer , ' ', aString2. answer := answer withBlanksTrimmed. ^answer ! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 9/1/2007 18:38'! validFamilyName "answer the receiver's familyName, or an alternative name to use if the familyName is invalid for some reason" (familyName copyWithout: $? ) ifEmpty:[ "workaround problem with FreeType 2.2.1 and MS Gothic, MS Mincho where familyName is not read correctly. This may be fixed in later versions of FreeType" self baseName asUppercase = 'MSGOTHIC' ifTrue:[ index = 0 ifTrue:[^'MS Gothic']. index = 1 ifTrue:[^'MS PGothic']. index = 2 ifTrue:[^'MS UI Gothic']]. self baseName asUppercase = 'MSMINCHO' ifTrue:[ index = 0 ifTrue:[^'MS Mincho']. index = 1 ifTrue:[^'MS PMincho']. ^self baseName asUppercase, ' ', index asString]]. ^familyName! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/12/2007 17:06'! validStyleName "answer the receiver's styleName, or an alternative name to use if the styleName is invalid for some reason" | answer | (styleName copyWithout: $? ) ifEmpty:[ "workaround problem with FreeType 2.2.1 and MS Gothic, MS Mincho where familyName is not read correctly. This may be fixed in later versions of FreeType" answer := ''. italic ifTrue:[answer := answer , 'Italic ']. bold ifTrue:[answer := answer, 'Bold ']. (italic or:[bold]) not ifTrue:[answer := answer, 'Regular ']. ^answer withBlanksTrimmed]. ^styleName! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/11/2007 14:22'! weight "Answer the value of weight" ^ weight! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 01:04'! weightValue "Answer the value of weightValue" ^ weightValue! ! !FreeTypeFileInfoAbstract methodsFor: 'accessing' stamp: 'tween 8/16/2007 01:04'! weightValue: anObject "Set the value of weightValue" weightValue := anObject! ! !FreeTypeFileInfoAbstract methodsFor: 'testing' stamp: 'tween 7/16/2007 00:31'! isEmbedded ^false! ! AbstractFont subclass: #FreeTypeFont instanceVariableNames: 'face pointSize simulatedEmphasis pixelSize widthAndKernedWidthCache cachedHeight cachedAscent cachedDescent subPixelPositioned symbolFont' classVariableNames: '' poolDictionaries: 'FT2Constants FreeTypeCacheConstants' category: 'FreeType-Fonts'! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 7/15/2007 22:00'! clearCachedMetrics widthAndKernedWidthCache := cachedHeight := cachedAscent := cachedDescent := subPixelPositioned := nil! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 9/29/2007 09:44'! defaultSimulatedItalicSlant ^0.22! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 3/17/2007 11:27'! depth ^ 32.! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 3/17/2007 11:33'! face "Validate, and answer, the receiver's face" ^face validate! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 3/17/2007 11:34'! face: aFace face := aFace! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 3/31/2007 11:57'! hash ^pointSize hash! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 3/17/2007 11:44'! maxAscii "should have default in AbstractFont" ^SmallInteger maxVal! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 3/17/2007 11:44'! minAscii "should have default in AbstractFont" ^0! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 8/27/2007 10:02'! postscriptName ^self face postscriptName! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 3/17/2007 11:47'! setFace: aFreetypeFace pointSize: anInteger face := aFreetypeFace. pointSize := anInteger.! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 9/29/2007 09:43'! simulatedBoldStrength "Answer the amount by which glyphs need to be emboldened/lightened according to the receiver's simulated emphasis and the face's real emphasis" | bold faceBold | self isSimulated ifFalse:[^0]. bold := self isSimulatedBold. faceBold := face isBold. (bold and: [faceBold not]) ifTrue:[^self pixelSize/24]. ^0! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 9/29/2007 09:42'! simulatedEmphasis "Answer the simulatedEmphasis. This is 0 - normal (no simulatedEmphasis, or simulated regular). 1 - bold 2 - italic 3 - bold & italic" ^simulatedEmphasis ifNil:[0]! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 9/29/2007 09:43'! simulatedEmphasis: anIntegerOrNil "Set the simulatedEmphasis. This is nil - no simulated emphasis 0 - normal (simulated regular). 1 - bold 2 - italic 3 - bold & italic" simulatedEmphasis := anIntegerOrNil! ! !FreeTypeFont methodsFor: 'accessing' stamp: 'tween 9/29/2007 09:44'! simulatedItalicSlant "Answer the slant that needs to be added to italicize/un-italicize glyphs according to the receiver's simulated emphasis and the face's real emphasis" | italic faceItalic | self isSimulated ifFalse:[^0]. italic := self isSimulatedItalic. faceItalic := face isItalic. (italic and: [faceItalic not]) ifTrue:[^self defaultSimulatedItalicSlant]. ^0! ! !FreeTypeFont methodsFor: 'displaying' stamp: 'tween 9/1/2007 10:32'! displayLineGlyphOn: aDisplayContext from: startPoint to: endPoint | oldCombinationRule oldHalftoneForm originalColorMap clr depth foreColorVal foreColorAlpha glyph width height startPointX startPointY endPointX endPointY foreColor | oldCombinationRule := aDisplayContext combinationRule . oldHalftoneForm := aDisplayContext halftoneForm . originalColorMap := aDisplayContext colorMap. clr := (foreColor := aDisplayContext lastFontForegroundColor ifNil:[Color black asNontranslucentColor]) pixelValueForDepth: 32. depth := aDisplayContext destForm depth. foreColorVal := clr bitAnd: 16rFFFFFF. foreColorAlpha := (clr bitAnd: 16rFF000000) >> 24. depth <= 8 ifTrue:[ aDisplayContext colorMap: (aDisplayContext cachedFontColormapFrom:32 to: depth)] ifFalse:[ aDisplayContext colorMap: nil]. startPointX := startPoint x truncated. startPointY := startPoint y. endPointX := endPoint x ceiling. endPointY := endPoint y. width := endPointX - startPointX. height := endPointY - startPointY. glyph := (Form extent: width@height depth: 32) fillWhite. "we could cache a big white glyph somewhere to save having to create this. Clipping will make only a part of it display" aDisplayContext sourceForm: glyph. aDisplayContext destOrigin: startPointX@startPointY. aDisplayContext width: width. aDisplayContext height: height. aDisplayContext sourceOrigin: 0@0; halftoneForm: nil. (FreeTypeSettings current bitBltSubPixelAvailable and: [depth >= 8]) ifTrue:[ aDisplayContext combinationRule: 41. aDisplayContext copyBitsColor: foreColorVal alpha: foreColorAlpha gammaTable: FreeTypeSettings current gammaTable ungammaTable: FreeTypeSettings current gammaInverseTable] ifFalse:[ glyph fillWithColor: foreColor. aDisplayContext combinationRule: (depth <= 8 ifTrue: [Form paint] ifFalse: [34]). aDisplayContext copyBits]. aDisplayContext colorMap: originalColorMap; combinationRule: oldCombinationRule; halftoneForm: oldHalftoneForm. ! ! !FreeTypeFont methodsFor: 'displaying' stamp: 'tween 3/17/2007 11:30'! displayStrikeoutOn: aDisplayContext from: baselineStartPoint to: baselineEndPoint | top bottom strikeoutThickness s e | "the strikeout size/position for TrueType fonts should really come from the TT:=OS2 table. This needs to be read by the plugin when the face is created. For now, we use the underlineThickness, and 1/4 of the ascender from the baseline" strikeoutThickness := (self face underlineThickness * self pixelSize / self face unitsPerEm). top := ((self face ascender / 4) * self pixelSize / self face unitsPerEm) negated - (strikeoutThickness/2). top := top rounded. bottom := top + strikeoutThickness ceiling. s := baselineStartPoint + (0@top). e := baselineEndPoint + (0@bottom). self displayLineGlyphOn: aDisplayContext from: s to: e ! ! !FreeTypeFont methodsFor: 'displaying' stamp: 'tween 3/17/2007 11:30'! displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta ^self displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: aPoint y + self ascent! ! !FreeTypeFont methodsFor: 'displaying' stamp: 'tween 4/5/2007 09:32'! displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY | glyph depth foreColorVal foreColorAlpha originalColorMap clr subPixelPosition widthAndKernedWidth char nextChar floatDestX destX destY offset gammaTable gammaInverseTable useRule41 | useRule41 := FreeTypeSettings current bitBltSubPixelAvailable and: [aBitBlt destForm depth >= 8]. depth := aBitBlt destForm depth. originalColorMap := aBitBlt colorMap. clr := (aBitBlt lastFontForegroundColor ifNil:[Color black asNontranslucentColor]) pixelValueForDepth: 32. useRule41 ifTrue:[ foreColorVal := clr bitAnd: 16rFFFFFF. foreColorAlpha := (clr bitAnd: 16rFF000000) >> 24. gammaTable := FreeTypeSettings current gammaTable. gammaInverseTable := FreeTypeSettings current gammaInverseTable.] ifFalse:[ foreColorVal := clr]. depth <= 8 ifTrue:[ aBitBlt colorMap: (aBitBlt cachedFontColormapFrom:32 to: depth)] ifFalse:[ aBitBlt colorMap: nil]. destX := aPoint x. destY := baselineY. floatDestX := aPoint x. widthAndKernedWidth := Array new: 2. startIndex to: stopIndex do: [:i | subPixelPosition := ((floatDestX \\ 1) roundTo: "1/64" 0.015625) * 64. subPixelPosition = 64 ifTrue:[ subPixelPosition := 0. destX := destX + 1]. char := aString at: i. glyph := self glyphOf: char destDepth: depth colorValue: foreColorVal subpixelPosition: subPixelPosition. aBitBlt sourceForm: glyph. offset := glyph offset. aBitBlt destX: destX + offset x. aBitBlt destY: destY + offset y. aBitBlt width: glyph width. aBitBlt height: glyph height. useRule41 ifTrue:[ aBitBlt copyBitsColor: foreColorVal alpha: foreColorAlpha gammaTable: gammaTable ungammaTable: gammaInverseTable] ifFalse:[ aBitBlt copyBits]. nextChar := (i + 1 <= stopIndex) ifTrue:[aString at: i + 1] ifFalse:[nil]. self widthAndKernedWidthOfLeft: char right: nextChar into: widthAndKernedWidth. floatDestX := floatDestX + (widthAndKernedWidth at: 2) + kernDelta. destX := floatDestX ]. aBitBlt colorMap: originalColorMap. ^ destX @ destY ! ! !FreeTypeFont methodsFor: 'displaying' stamp: 'tween 3/17/2007 11:32'! displayUnderlineOn: aDisplayContext from: baselineStartPoint to: baselineEndPoint | underlineTop underlineBottom underlineThickness s e | underlineThickness := (self face underlineThickness * self pixelSize / self face unitsPerEm). underlineTop := (self face underlinePosition * self pixelSize / self face unitsPerEm) negated - (underlineThickness/2). underlineTop := underlineTop rounded + 1. "needs the +1 , possibly because glyph origins are moved down by 1 so that their baselines line up with strike fonts" underlineBottom := underlineTop + underlineThickness ceiling. s := baselineStartPoint + (0@underlineTop). e := baselineEndPoint + (0@(underlineBottom)). self displayLineGlyphOn: aDisplayContext from: s to: e! ! !FreeTypeFont methodsFor: 'displaying' stamp: 'tween 4/5/2007 08:15'! installOn: aBitBlt foregroundColor: foreColor backgroundColor: backColor | | "fcolor := foreColor pixelValueForDepth: 32." aBitBlt installFreeTypeFont: self foregroundColor: foreColor backgroundColor: backColor. ! ! !FreeTypeFont methodsFor: 'glyph lookup' stamp: 'tween 9/1/2007 09:54'! characterFormAt: aCharacter FreeTypeSettings current forceNonSubPixelDuring:[ ^self glyphOf: aCharacter destDepth: 32 colorValue: (Color black pixelValueForDepth: 32) subpixelPosition: 0]! ! !FreeTypeFont methodsFor: 'glyph lookup' stamp: 'tween 4/4/2007 19:13'! glyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub | | ^FreeTypeCache current atFont: self charCode: aCharacter asUnicode asInteger type: ((1+sub) << 32) + aColorValue ifAbsentPut: [ FreeTypeGlyphRenderer current glyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub font: self] ! ! !FreeTypeFont methodsFor: 'glyph lookup' stamp: 'tween 9/1/2007 15:35'! glyphOf: aCharacter destDepth: destDepth colorValue: aColorValue subpixelPosition: sub "sub can be between 0 and 63 and denotes the sub-pixel position of the glyph" | validSub | validSub := self isSubPixelPositioned ifTrue: [((sub asInteger max: 0) min: 63) "bitAnd: 2r111000"] ifFalse:[0]. ^(destDepth >=8 and:[FreeTypeSettings current subPixelAntiAliasing]) ifTrue:[ self subGlyphOf: aCharacter colorValue: aColorValue mono: FreeTypeSettings current monoHinting subpixelPosition: validSub] ifFalse:[ (destDepth >= 8 and:[FreeTypeSettings current bitBltSubPixelAvailable]) ifTrue:[ self mode41GlyphOf: aCharacter colorValue: aColorValue mono: FreeTypeSettings current monoHinting subpixelPosition: validSub] ifFalse:[ self glyphOf: aCharacter colorValue: aColorValue mono: FreeTypeSettings current monoHinting subpixelPosition: validSub]]! ! !FreeTypeFont methodsFor: 'glyph lookup' stamp: 'tween 4/4/2007 19:14'! mode41GlyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub | | ^FreeTypeCache current atFont: self charCode: aCharacter asUnicode asInteger type: (FreeTypeCacheGlyph + sub) ifAbsentPut: [ FreeTypeGlyphRenderer current mode41GlyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub font: self] ! ! !FreeTypeFont methodsFor: 'glyph lookup' stamp: 'tween 4/4/2007 19:13'! subGlyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub | | ^FreeTypeCache current atFont: self charCode: aCharacter asUnicode asInteger type: FreeTypeCacheGlyphLCD + sub ifAbsentPut: [ FreeTypeGlyphRenderer current subGlyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub font: self] ! ! !FreeTypeFont methodsFor: 'initialize-release' stamp: 'tween 3/17/2007 11:39'! initialize: aFont self face: aFont face.! ! !FreeTypeFont methodsFor: 'initialize-release' stamp: 'tween 3/17/2007 11:45'! releaseCachedState face releaseCachedState. FreeTypeCache current removeAllForFont: self.! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 4/3/2007 17:22'! ascent | asc desc h | cachedAscent ifNotNil:[^cachedAscent]. asc := self basicAscent. desc := self descent. h := self height. asc + desc < h ifFalse:[^cachedAscent := asc]. "height is greater than asc+desc, adjust ascent to include the difference" ^cachedAscent := h - desc ! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 3/26/2007 13:14'! basicAscent ^(self face ascender * self pixelSize // self face unitsPerEm). ! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 4/3/2007 17:24'! descent ^cachedDescent ifNil:[ cachedDescent := ((self face descender * self pixelSize // self face unitsPerEm) negated) ]! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 3/17/2007 11:28'! descentKern "should have default in AbstractFont" ^0! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'michael.rueger 2/5/2009 17:03'! getLinearWidthOf: aCharacter | em glyph la charCode | aCharacter < $ ifTrue: [^self getLinearWidthOf: $ ]. charCode := aCharacter asUnicode asInteger. (self face charmaps includes:'unic') ifTrue:[ (self isSymbolFont and:[charCode >= 16r20 and: [charCode <= 16rFF ] ]) ifTrue:[charCode := charCode + 16rF000]] ifFalse:[ (self face charmaps includes:'armn') ifTrue:[ "select apple roman char map, and map character from unicode to mac encoding" self face setCharMap:'armn'. charCode := aCharacter unicodeToMacRoman asUnicode asInteger. "check this!!"]]. em := self pixelSize. face validate. face setPixelWidth: em height: em. [face loadCharacter: charCode flags: (LoadNoBitmap bitOr: (LoadIgnoreTransform bitOr: "FreeTypeSettings current hintingFlags" 2 "no hinting"))] on: FT2Error do:[:e | face loadGlyph: 0 flags: (LoadNoBitmap bitOr: (LoadIgnoreTransform bitOr: FreeTypeSettings current hintingFlags "no hinting")) ]. glyph := face glyph. la := glyph linearHorizontalAdvance. la isZero ifTrue:[ "FreeType 2.2.1 sometimes screws up when getting metrics, Maybe the bug is in the plugin? For example Calibri pixel size 13 gives linearAdvance x of zero !! We try again at double the size, and half the result" em := self pixelSize * 2. face validate. face setPixelWidth: em height: em. face loadCharacter: charCode flags:(LoadNoBitmap bitOr: (LoadIgnoreTransform bitOr: "FreeTypeSettings current hintingFlags" 2 "no hinting")). "load glyph metrics" glyph := face glyph. la := glyph linearHorizontalAdvance / 2.0]. ^la ! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'michael.rueger 2/5/2009 17:03'! getWidthOf: aCharacter "Glyphs are either 1 or 8 bit deep. For 32 bpp we use 8 bits, otherwise 1" | em glyph hintingFlags flags charCode | aCharacter < $ ifTrue: [^self getWidthOf: $ ]. charCode := aCharacter asUnicode asInteger. (self face charmaps includes:'unic') ifTrue:[ (self isSymbolFont and:[charCode >= 16r20 and: [charCode <= 16rFF ] ]) ifTrue:[charCode := charCode + 16rF000]] ifFalse:[ (self face charmaps includes:'armn') ifTrue:[ "select apple roman char map, and map character from unicode to mac encoding" self face setCharMap:'armn'. charCode := aCharacter unicodeToMacRoman asUnicode asInteger. "check this!!"]]. em := self pixelSize. face validate. face isValid ifFalse:[^0]. face setPixelWidth: em height: em. hintingFlags := FreeTypeSettings current hintingFlags. flags := LoadNoBitmap bitOr:( LoadIgnoreTransform bitOr: hintingFlags). [face loadCharacter: charCode flags: flags. ] on:FT2Error do:[:e | "character not in map?"^0]. glyph := face glyph. "When not hinting FreeType sets the advance to the truncated linearAdvance. The characters appear squashed together. Rounding is probably better, so we answer the rounded linear advance here" ^self subPixelPositioned ifTrue:[ glyph roundedPixelLinearAdvance x] ifFalse:[ glyph advance x]. ! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 4/3/2007 17:25'! height ^cachedHeight ifNil:[ cachedHeight := (self face height * self pixelSize / self face unitsPerEm) ceiling ]! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 4/3/2007 16:42'! hintedKerningLeft: leftChar right: rightChar ^(self linearKerningLeft: leftChar right: rightChar) rounded! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 3/31/2007 23:08'! hintedWidthOf: aCharacter "retrieve advance width for character. try to use cached glyph if possible" | charCode answer | charCode := aCharacter asUnicode asInteger. answer := FreeTypeCache current atFont: self charCode: charCode type: FreeTypeCacheWidth ifAbsentPut: [self getWidthOf: aCharacter]. ^answer ! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 7/15/2007 21:59'! kerningLeft: leftChar right: rightChar ^self isSubPixelPositioned ifTrue: [self linearKerningLeft: leftChar right: rightChar] ifFalse:[self hintedKerningLeft: leftChar right: rightChar]! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 3/17/2007 11:43'! lineGrid ^self height! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'michael.rueger 2/5/2009 17:04'! linearKerningLeft: leftChar right: rightChar | f l r | f := self face. f hasKerning ifFalse:[^0]. l := leftChar asUnicode. r := rightChar asUnicode. (self face charmaps includes:'unic') ifTrue:[ self isSymbolFont ifTrue:[ (l asInteger >= 16r20 and:[l asInteger <= 16rFF ]) ifTrue:[l := (Character value: l asInteger + 16rF000) asUnicode]. (r asInteger >= 16r20 and:[ r asInteger <= 16rFF ]) ifTrue:[r := (Character value: r asInteger + 16rF000) asUnicode]]] ifFalse:[ (self face charmaps includes:'armn') ifTrue:[ "select apple roman char map, and map characters from unicode to mac encoding" self face setCharMap:'armn'. (l asInteger >= 16r20 and:[l asInteger <= 16rFF ]) ifTrue:[l := (Character value: l asInteger) unicodeToMacRoman]. (r asInteger >= 16r20 and:[ r asInteger <= 16rFF ]) ifTrue:[r := (Character value: r asInteger) unicodeToMacRoman]]]. ^(f kerningLeft: l right: r) x asFloat * self pixelSize / f unitsPerEm! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 3/31/2007 20:18'! linearWidthOf: aCharacter "retrieve linear advance width for character. try to use cached glyph if possible. This is the scaled, unrounded advance width." | charCode answer | charCode := aCharacter asUnicode asInteger. answer := FreeTypeCache current atFont: self charCode: charCode type: FreeTypeCacheLinearWidth ifAbsentPut: [self getLinearWidthOf: aCharacter]. ^answer ! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 3/31/2007 11:38'! pixelSize ^pixelSize ifNil:[pixelSize := super pixelSize rounded]! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 3/17/2007 11:45'! pointSize ^pointSize! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 3/17/2007 11:45'! pointSize: aSize pointSize := aSize! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 4/2/2007 22:10'! widthAndKernedWidthCache ^widthAndKernedWidthCache ifNil:[widthAndKernedWidthCache := Dictionary new]! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 4/2/2007 22:11'! widthAndKernedWidthOfLeft: leftCharacter right: rightCharacterOrNil into: aTwoElementArray "Set the first element of aTwoElementArray to the width of leftCharacter and the second element to the width of left character when kerned with rightCharacterOrNil. Answer the receiver We use a widthAndKernedWidthCache to store these values for speed" | privateArray | privateArray := (self widthAndKernedWidthCache at: leftCharacter ifAbsentPut:[Dictionary new]) at: (rightCharacterOrNil ifNil:[0 asCharacter]) ifAbsentPut:[ super widthAndKernedWidthOfLeft: leftCharacter right: rightCharacterOrNil into: (Array new: 2)]. "We can't answer privateArray, we MUST copy its elements into aTwoElementArray" aTwoElementArray at: 1 put: (privateArray at: 1); at: 2 put: (privateArray at: 2). ^aTwoElementArray! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 7/15/2007 22:00'! widthOf: aCharacter "retrieve advance width for character. try to use cached glyph if possible" ^self isSubPixelPositioned ifTrue:[self linearWidthOf: aCharacter] ifFalse: [self hintedWidthOf: aCharacter] ! ! !FreeTypeFont methodsFor: 'measuring' stamp: 'tween 7/4/2009 12:58'! widthOfString: aString from: startIndex to: stopIndex "Measure the length of the given string between start and stop index. Currently this allows for the right side bearing of the last char, but does not allow for the left side bearing of the first char. We really need a new method - boundingBoxOfString that allows for both. Senders of this will also need to know the LSB of the first char, and position their text accordingly" | char nextChar resultX glyph a subPixelPosition | a := Array new: 2. "FreeTypeSettings current hinting ifFalse:[ ^self linearWidthOfString: aString from: startIndex to: stopIndex]." resultX := 0. startIndex to: stopIndex do:[:i | char := aString at: i. nextChar := (i + 1 <= stopIndex) ifTrue:[ aString at: i + 1] ifFalse:[nil]. self widthAndKernedWidthOfLeft: char right: nextChar into: a. resultX := resultX + (a at:2). i = stopIndex ifTrue:[ subPixelPosition := (((resultX \\ 1) roundTo: "1/64" 0.015625) * 64) asInteger. subPixelPosition = 64 ifTrue:[ subPixelPosition := 0. resultX := resultX + 1 ]. subPixelPosition := (subPixelPosition max: 0) min: 63. glyph := self glyphOf: char colorValue: 0 mono: FreeTypeSettings current monoHinting subpixelPosition: subPixelPosition. glyph ifNotNil:[ "currently the glyph is too wide. This is to allow for some extra space to ensure the glyph is not clipped when it is produced. Either make the width accurate, or hold the RSB value separately, or hold an accurate width separately" resultX := resultX "+ 2" + glyph offset x "negated" + (glyph width - (a at: 2) "glyph linearAdvance x floor")]]]. ^resultX ceiling ! ! !FreeTypeFont methodsFor: 'notifications' stamp: 'tween 4/3/2007 16:48'! pixelsPerInchChanged "the TextStyle pixels per inch setting has changed" pixelSize := nil. widthAndKernedWidthCache := nil. FreeTypeCache current removeAllForFont: self.! ! !FreeTypeFont methodsFor: 'printing' stamp: 'tween 3/17/2007 11:45'! printOn: aStream aStream nextPutAll: self class name; nextPut: $(; print: face familyName; space; print: face styleName; space; print: pointSize; nextPut: $)! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 3/29/2007 13:48'! hasDistinctGlyphsForAll: asciiString "Answer true if the receiver has glyphs for all the characters in asciiString and no single glyph is shared by more than one character, false otherwise. The default behaviour is to answer true, but subclasses may reimplement" | setOfIndices i | self face isValid ifFalse:[^false]. setOfIndices := Set new. asciiString asSet do:[:c | (i := self face primGetCharIndex: c asInteger) = 0 ifTrue:[^false] ifFalse:[ (setOfIndices includes: i) ifTrue:[^false] ifFalse:[setOfIndices add: i]]]. ^true! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 3/29/2007 13:28'! hasGlyphsForAll: asciiString "Answer true if the receiver has glyphs for all the characters in asciiString, false otherwise. The default behaviour is to answer true, but subclasses may reimplement" self face isValid ifFalse:[^false]. asciiString do:[:c | (self face primGetCharIndex: c asInteger) = 0 ifTrue:[^false]]. ^true! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 9/29/2007 09:49'! isBold ^(simulatedEmphasis == nil and:[self face isBold]) or:[self isSimulatedBold]! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 3/17/2007 11:41'! isFixedWidth ^self face isFixedWidth ! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 9/29/2007 09:48'! isItalic ^(simulatedEmphasis == nil and:[self face isItalic]) or:[self isSimulatedItalic]! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 9/29/2007 09:49'! isRegular ^(simulatedEmphasis == nil and:[self face isRegular]) or: [self isSimulatedRegular]! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 9/29/2007 09:41'! isSimulated ^simulatedEmphasis notNil! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 9/29/2007 09:42'! isSimulatedBold ^self simulatedEmphasis anyMask: 1! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 9/29/2007 09:45'! isSimulatedItalic ^self simulatedEmphasis anyMask: 2! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 9/29/2007 09:45'! isSimulatedRegular ^simulatedEmphasis = 0! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 7/15/2007 21:55'! isSubPixelPositioned "Answer true if the receiver is currently using subpixel positioned glyphs, false otherwise. This affects how padded space sizes are calculated when composing text. Currently, only FreeTypeFonts are subPixelPositioned, and only when not Hinted" ^self subPixelPositioned! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 8/1/2007 01:08'! isSymbolFont | charmaps | symbolFont ifNotNil:[^symbolFont]. self face isValid ifFalse:[^false]. charmaps := self face charmaps. (charmaps includes: 'symb') ifTrue:[^symbolFont := true]."MS Symbol font" ^symbolFont := false! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 3/17/2007 11:42'! isTTCFont "not really - look for senders of this" ^true! ! !FreeTypeFont methodsFor: 'testing' stamp: 'tween 7/15/2007 21:57'! subPixelPositioned "Answer true if the receiver is currently using subpixel positioned glyphs, false otherwise. This affects how padded space sizes are calculated when composing text." | settings | ^subPixelPositioned ifNil:[ settings := FreeTypeSettings current. subPixelPositioned := settings hinting not or:[settings lightHinting]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeFont class instanceVariableNames: ''! !FreeTypeFont class methodsFor: 'instance creation' stamp: 'tween 6/10/2009 12:12'! forLogicalFont: aLogicalFont fileInfo: aFreeTypeFileInfoAbstract | pointSize index | pointSize := aLogicalFont pointSize. index := aFreeTypeFileInfoAbstract index. ^aFreeTypeFileInfoAbstract isEmbedded ifTrue:[ self fromBytes: aFreeTypeFileInfoAbstract fileContents pointSize: pointSize index: index] ifFalse:[ self fromFile: "aFreeTypeFileInfoAbstract absolutePath" (FreeTypeFontProvider current absolutePathFor: aFreeTypeFileInfoAbstract absoluteOrRelativePath locationType: aFreeTypeFileInfoAbstract locationType) pointSize: pointSize index: index]! ! !FreeTypeFont class methodsFor: 'instance creation' stamp: 'tween 7/16/2007 00:33'! fromBytes: aByteArray pointSize: anInteger index: i ^self new setFace: (FreeTypeFace fromBytes: aByteArray index: i) pointSize: anInteger; yourself! ! !FreeTypeFont class methodsFor: 'instance creation' stamp: 'marcus.denker 12/16/2008 11:17'! fromFile: aFileName pointSize: anInteger index: i ^self new setFace: (FreeTypeFace fromFile: aFileName index: i) pointSize: anInteger; yourself! ! !FreeTypeFont class methodsFor: 'instance creation' stamp: 'tween 9/29/2007 07:43'! new ^super new! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 21:42'! profileHintedComposition " self profileHintedComposition " | t f m text | Preferences enable: #HintingNone. Preferences enable: #HintingLight. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. TimeProfileBrowser onBlock: [ 2 timesRepeat:[m justified; leftFlush]]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 23:01'! profileHintedDisplayCached " self profileHintedDisplayCached " | t f m text canvas | Preferences enable: #HintingNone. Preferences enable: #HintingLight. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. canvas := (FormCanvas on: (Form extent: 1000@1000 depth: 32)). m drawOn: canvas. "this fills the cache" TimeProfileBrowser onBlock: [ 2 timesRepeat: [m drawOn: canvas ]]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 23:31'! profileHintedDisplayCachedUsingMode34 " self profileHintedDisplayCachedUsingMode34 " | t f m text canvas | Preferences enable: #HintingNone. Preferences enable: #HintingLight. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. FreeTypeSettings current pretendBitBltSubPixelUnavailableDuring:[ canvas := (FormCanvas on: (Form extent: 1000@1000 depth: 32)). m drawOn: canvas. "this fills the cache" TimeProfileBrowser onBlock: [ 2 timesRepeat: [m drawOn: canvas ]]]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/3/2007 08:50'! profileHintedWidthOfString " self profileHintedWidthOfString " | t f string | Preferences enable: #HintingNone. Preferences enable: #HintingLight. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. string := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' . TimeProfileBrowser onBlock: [ 200 timesRepeat:[f widthOfString: string]]. ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/3/2007 08:50'! profileHintedWidthOfStringCached " self profileHintedWidthOfStringCached " | t f string | Preferences enable: #HintingNone. Preferences enable: #HintingLight. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. string := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' . f widthOfString: string. "this fills any caches" TimeProfileBrowser onBlock: [ 200 timesRepeat:[f widthOfString: string]]. ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/3/2007 08:54'! profileHintedWidthOfStringCachedMulti " self profileHintedWidthOfStringCachedMulti " | t f string | Preferences enable: #HintingNone. Preferences enable: #HintingLight. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. string := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' , 1000 asCharacter asString. f widthOfString: string. "this fills any caches" TimeProfileBrowser onBlock: [ 200 timesRepeat:[f widthOfString: string]]. ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/3/2007 08:55'! profileHintedWidthOfStringMulti " self profileHintedWidthOfStringMulti " | t f string | Preferences enable: #HintingNone. Preferences enable: #HintingLight. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. string := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' , 1000 asCharacter asString. TimeProfileBrowser onBlock: [ 200 timesRepeat:[f widthOfString: string]]. ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 18:56'! profileUnhinted " self profileUnhinted " | t f m text | t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. TimeProfileBrowser onBlock: [m justified; leftFlush]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 21:43'! profileUnhintedComposition " self profileUnhintedComposition " | t f m text | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. TimeProfileBrowser onBlock: [ 2 timesRepeat:[m justified; leftFlush]]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 23:32'! profileUnhintedCompositionMulti " self profileUnhintedCompositionMulti " | t f m text | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := ('Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' , 1000 asCharacter asString) asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. TimeProfileBrowser onBlock: [ 2 timesRepeat:[m justified; leftFlush]]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 22:42'! profileUnhintedDisplay " self profileUnhintedDisplay " | t f m text canvas | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. canvas := (FormCanvas on: (Form extent: 1000@1000 depth: 32)). TimeProfileBrowser onBlock: [ 2 timesRepeat: [m drawOn: canvas ]]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 22:43'! profileUnhintedDisplayCached " self profileUnhintedDisplayCached " | t f m text canvas | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. canvas := (FormCanvas on: (Form extent: 1000@1000 depth: 32)). m drawOn: canvas. "this fills the cache" TimeProfileBrowser onBlock: [ 2 timesRepeat: [m drawOn: canvas ]]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 23:41'! profileUnhintedDisplayCachedMulti " self profileUnhintedDisplayCachedMulti " | t f m text canvas | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := ('Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' , 1000 asCharacter asString) asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. canvas := (FormCanvas on: (Form extent: 1000@1000 depth: 32)). m drawOn: canvas. "this fills the cache" TimeProfileBrowser onBlock: [ 2 timesRepeat: [m drawOn: canvas ]]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/2/2007 23:40'! profileUnhintedDisplayMulti " self profileUnhintedDisplayMulti " | t f m text canvas | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. m := TextMorph new. m width: 200; height: 200. m backgroundColor: Color white. text := ('Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' , 1000 asCharacter asString) asText. text addAttribute: (TextFontReference toFont: f). m contents: text. m openInWorld. canvas := (FormCanvas on: (Form extent: 1000@1000 depth: 32)). TimeProfileBrowser onBlock: [ 2 timesRepeat: [m drawOn: canvas ]]. m delete ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/3/2007 08:51'! profileUnhintedWidthOfString " self profileUnhintedWidthOfString " | t f string | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. string := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' . TimeProfileBrowser onBlock: [ 200 timesRepeat:[f widthOfString: string]]. ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/3/2007 08:51'! profileUnhintedWidthOfStringCached " self profileUnhintedWidthOfStringCached " | t f string | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. string := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' . f widthOfString: string. "this fills any caches" TimeProfileBrowser onBlock: [ 200 timesRepeat:[f widthOfString: string]]. ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/3/2007 08:52'! profileUnhintedWidthOfStringCachedMulti " self profileUnhintedWidthOfStringCachedMulti " | t f string | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. string := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' , 1000 asCharacter asString. f widthOfString: string. "this fills any caches" TimeProfileBrowser onBlock: [ 200 timesRepeat:[f widthOfString: string]]. ! ! !FreeTypeFont class methodsFor: 'profiling' stamp: 'tween 4/3/2007 08:53'! profileUnhintedWidthOfStringMulti " self profileUnhintedWidthOfStringMulti " | t f string | Preferences enable: #HintingLight. Preferences enable: #HintingNone. "cache is now clear" t := TextStyle named: 'Arial'. f := t fontOfPointSize: 12. string := 'Welcome to the finale version of 3.9 of 7 of November 2006 You will find more recent versions at http://www.squeak.org/ This image will be used to produce other distributions such as a developer image and a fun with Squeak image. We hope that you will really appreciate this version and that Squeak will help you making your projects reality. You can also participate to Squeak at different kinds of levels. This can be as simple as: - asking questions in the beginner list (beginners@lists.squeakfoundation.org) or in the dev list (squeak-dev@lists.squeakfoundation.org) - answering questions - finding and reporting bugs at: http://bugs.impara.de - fixing them, testing fixes and commenting them - writing tests for uncovered parts - helping for the website - creating new cool products, frameworks, applications in squeak - writing articles.... We wish you a lot of fun and we would like to thanks all the persons that participated to make this release a really good one. We know who you are!! Stephane Ducasse and Marcus Denker stephane.ducasse@free.fr and denker@iam.unibe.ch' , 1000 asCharacter asString. TimeProfileBrowser onBlock: [ 200 timesRepeat:[f widthOfString: string]]. ! ! FontFamilyAbstract subclass: #FreeTypeFontFamily instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FreeTypeFontFamily methodsFor: 'accessing' stamp: 'tween 8/25/2007 14:26'! addMember: aFreeTypeFontFamilyMember aFreeTypeFontFamilyMember family: self. members add: aFreeTypeFontFamilyMember! ! !FreeTypeFontFamily methodsFor: 'accessing' stamp: 'tween 8/16/2007 22:58'! addMembersFromFileInfos: aCollectionOfFreeTypeFileInfo | member | aCollectionOfFreeTypeFileInfo do:[:aFileInfo | member := FreeTypeFontFamilyMember fromFileInfo: aFileInfo. (self memberWithStyleName: member styleName) ifNil:[self addMember: member]]. ! ! !FreeTypeFontFamily methodsFor: 'accessing' stamp: 'tween 8/16/2007 22:59'! memberWithStyleName: aString ^members detect:[:each | each styleName = aString] ifNone:[] ! ! !FreeTypeFontFamily methodsFor: 'initialize-release' stamp: 'tween 8/16/2007 20:44'! initialize super initialize. members := OrderedCollection new.! ! !FreeTypeFontFamily methodsFor: 'simulated members' stamp: 'tween 9/29/2007 12:57'! addSimulatedMembers | membersBySlantAndStretch heaviest membersByWeightAndStretch regular oblique | membersBySlantAndStretch := Dictionary new. members do:[:each| (membersBySlantAndStretch at: {each slantValue. each stretchValue} ifAbsentPut:[OrderedCollection new]) add: each]. membersBySlantAndStretch keysAndValuesDo:[:key :col | heaviest := col ifNotEmpty:[col first]. col do:[:each | heaviest weightValue < each weightValue ifTrue:[heaviest := each]]. (heaviest weightValue between: (LogicalFont weightRegular - 50) and: (LogicalFont weightMedium + 50)) ifTrue:[ members add: heaviest asSimulatedBold]]. membersByWeightAndStretch := Dictionary new. members do:[:each| | normalizedWeight | normalizedWeight := each weightValue. each weightValue = LogicalFont weightMedium ifTrue:[normalizedWeight := LogicalFont weightRegular]. "regular and medium weights are used interchangeably. For example, FreeSans has Regular-weightMedium(500), and Oblique-weightRegular(400). We don't want to simulate oblique-weightMedium(500) when a real Oblique-weightMedium(500) exists, so we normalize any weightMedium(500) values to weightRegular(400) to prevent this happening" (membersByWeightAndStretch at: {normalizedWeight. each stretchValue} ifAbsentPut:[OrderedCollection new]) add: each]. membersByWeightAndStretch keysAndValuesDo:[:key :col | regular := col detect: [:each | each slantValue = 0] ifNone:[]. oblique := col detect:[:each | each slantValue > 0] ifNone:[]. "oblique or italic" (oblique isNil and:[regular notNil]) ifTrue:[ regular simulated ifTrue:[members add: regular asSimulatedBoldOblique] ifFalse:[ members add: regular asSimulatedOblique]]]! ! !FreeTypeFontFamily methodsFor: 'simulated members' stamp: 'tween 8/18/2007 22:22'! rebuildSimulatedMembers "FOR TESTING ONLY" members := members reject:[:each| each simulated]. self addSimulatedMembers.! ! FontFamilyMemberAbstract subclass: #FreeTypeFontFamilyMember instanceVariableNames: 'fileInfo stretchName stretchValue weightName weightValue slantName slantValue simulated' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:46'! fileInfo "Answer the value of fileInfo" ^ fileInfo! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:46'! fileInfo: anObject "Set the value of fileInfo" fileInfo := anObject! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! simulated "Answer the value of simulated" ^ simulated! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! simulated: anObject "Set the value of simulated" simulated := anObject! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! slantName "Answer the value of slantName" ^ slantName! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! slantName: anObject "Set the value of slantName" slantName := anObject! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! slantValue "Answer the value of slantValue" ^ slantValue! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! slantValue: anObject "Set the value of slantValue" slantValue := anObject! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! stretchName "Answer the value of stretchName" ^ stretchName! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! stretchName: anObject "Set the value of stretchName" stretchName := anObject! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! stretchValue "Answer the value of stretchValue" ^ stretchValue! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! stretchValue: anObject "Set the value of stretchValue" stretchValue := anObject! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! weightName "Answer the value of weightName" ^ weightName! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! weightName: anObject "Set the value of weightName" weightName := anObject! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! weightValue "Answer the value of weightValue" ^ weightValue! ! !FreeTypeFontFamilyMember methodsFor: 'accessing' stamp: 'tween 8/16/2007 20:29'! weightValue: anObject "Set the value of weightValue" weightValue := anObject! ! !FreeTypeFontFamilyMember methodsFor: 'comparing' stamp: 'tween 8/16/2007 23:23'! <= aFreeTypeFontFamilyMember ^self sortValue <= aFreeTypeFontFamilyMember sortValue! ! !FreeTypeFontFamilyMember methodsFor: 'comparing' stamp: 'tween 9/29/2007 12:51'! sortValue | v normalizedWeight | normalizedWeight := weightValue. normalizedWeight = LogicalFont weightMedium ifTrue:["sort medium and regular weights as though they were the same" normalizedWeight := LogicalFont weightRegular]. v :=self simulated ifTrue:[10000] ifFalse:[0]. v := v + (stretchValue * 1000). v := v + (normalizedWeight). v := v + (slantValue). ^v ! ! !FreeTypeFontFamilyMember methodsFor: 'copying' stamp: 'tween 9/29/2007 12:49'! asSimulatedBold ^self copy weightValue: LogicalFont weightBold; styleName: (fileInfo styleNameWithWeightForcedToBe: 'Bold'); simulated: true; yourself! ! !FreeTypeFontFamilyMember methodsFor: 'copying' stamp: 'tween 9/29/2007 12:50'! asSimulatedBoldOblique ^self copy slantValue: LogicalFont slantItalic; "treat italic and oblique the same" weightValue:LogicalFont weightBold; styleName: (fileInfo styleNameWithWeightForcedToBe: 'Bold' italicForcedToBe: 'Oblique'); simulated: true; yourself! ! !FreeTypeFontFamilyMember methodsFor: 'copying' stamp: 'tween 9/29/2007 12:50'! asSimulatedOblique ^self copy slantValue: LogicalFont slantItalic; "treat italic and oblique the same" styleName: (fileInfo styleNameWithItalicForcedToBe: 'Oblique'); simulated: true; yourself! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeFontFamilyMember class instanceVariableNames: ''! !FreeTypeFontFamilyMember class methodsFor: 'instance creation' stamp: 'tween 8/16/2007 21:39'! fromFileInfo: aFreeTypeFileInfo ^self new fileInfo: aFreeTypeFileInfo; simulated: false; styleName: aFreeTypeFileInfo styleNameExtracted; stretchName: aFreeTypeFileInfo stretch; stretchValue: aFreeTypeFileInfo stretchValue; weightName: aFreeTypeFileInfo weight; weightValue: aFreeTypeFileInfo weightValue; slantName: aFreeTypeFileInfo slant; slantValue: aFreeTypeFileInfo slantValue; yourself ! ! FontProviderAbstract subclass: #FreeTypeFontProvider instanceVariableNames: 'fileInfos fileInfoCache tempFileInfos embeddedFileInfoCache families tempFamilies' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FreeTypeFontProvider commentStamp: 'tween 3/15/2007 17:23' prior: 0! A FreeTypeFontProvider is xxxxxxxxx. Instance Variables fontInfoCache: fontInfos: fontInfoCache - xxxxx fontInfos - set of FreeTypeFontInfo. Info about all the fonts that are available ! !FreeTypeFontProvider methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:39'! addFileInfo: aFreeTypeFileInfo index: i fileInfos add: aFreeTypeFileInfo ! ! !FreeTypeFontProvider methodsFor: 'accessing' stamp: 'tween 7/28/2007 13:28'! addFirstFileInfo: aFreeTypeFileInfo index: i fileInfos addFirst: aFreeTypeFileInfo ! ! !FreeTypeFontProvider methodsFor: 'accessing' stamp: 'tween 8/12/2007 12:31'! addFromFileContents: bytes baseName: originalFileBaseName | i face numFaces info externalMem cachedInfo cachedNumFaces | i:= 0. [(cachedInfo := self validEmbeddedCachedInfoFor: bytes index: i) notNil] whileTrue:[ i = 0 ifTrue:[cachedNumFaces := cachedInfo numFaces]. self addFirstFileInfo: cachedInfo index: i. i := i + 1.]. (cachedNumFaces notNil and:[i >= cachedNumFaces]) ifTrue:[^self]. [externalMem := FreeTypeExternalMemory bytes: bytes. externalMem validate. face := FreeTypeFace basicNew fileContentsExternalMemory: externalMem . [ "we use the primNewFaceFromFile:index: method because we want to do this as fast as possible and we don't need the face registered because it will be explicitly destroyed later" face primNewFaceFromExternalMemory: externalMem size: bytes size index: i. face loadFields] on: FT2Error do:[:e | self failedToOpen:face index: i. ^externalMem destroyHandle.]. (face height notNil and:[face hasFamilyName and:[face hasStyleName and:[face isValid]]]) ifFalse:[ self failedToOpen:face index: i. ^externalMem destroyHandle.] ifTrue:[ numFaces isNil ifTrue:[numFaces := face numFaces]. info :=FreeTypeEmbeddedFileInfo new baseName: originalFileBaseName; fileContents: bytes; index: i; familyName: face familyName; styleName: face styleName; postscriptName: face postscriptName; bold: face isBold; italic: face isItalic; fixedWidth: face isFixedWidth; numFaces: numFaces; extractAttributesFromNames; yourself. self addFirstFileInfo: info index: i. self cacheEmbeddedFileInfo: info index: i. "Transcript show: 'from file : ', info asString." face destroyHandle. externalMem destroyHandle]. i := i + 1. i < numFaces "note, we use < rather than <= , because i is zero based"] whileTrue:[]. ! ! !FreeTypeFontProvider methodsFor: 'accessing' stamp: 'tween 7/28/2007 13:50'! cacheEmbeddedFileInfo: aFreeTypeEmbeddedFileInfo index: i (embeddedFileInfoCache at: {aFreeTypeEmbeddedFileInfo fileSize. i} ifAbsentPut:[Set new]) add: aFreeTypeEmbeddedFileInfo ! ! !FreeTypeFontProvider methodsFor: 'accessing' stamp: 'tween 3/16/2007 12:41'! cacheFileInfo: aFreeTypeFileInfo index: i (fileInfoCache at: {aFreeTypeFileInfo fileSize. i} ifAbsentPut:[Set new]) add: aFreeTypeFileInfo ! ! !FreeTypeFontProvider methodsFor: 'accessing' stamp: 'tween 7/15/2007 23:45'! fileInfosByFamilyAndGroup "Answer a Dictionary of Dictionaries of Sets. familyName->familyGroupName->Set(FreeTypeFileInfo) self current fileInfosByFamilyAndGroup " | answer family group | answer := Dictionary new. "file could be in fileInfos twice? need to only process once, need directory precedence?" fileInfos do:[:info | family := answer at: info familyName ifAbsentPut:[Dictionary new]. group := family at: info familyGroupName ifAbsentPut: [OrderedCollection new]. group detect:[:each| each bold = info bold and:[ each italic = info italic and:[each fixedWidth = info fixedWidth and:[ each postscriptName = info postscriptName and:[each styleName = info styleName]]]]] ifNone:[group add: info]]. ^answer ! ! !FreeTypeFontProvider methodsFor: 'error handling' stamp: 'tween 3/16/2007 12:04'! failedToOpen:face from: path index: i face destroyHandle. "Transcript cr; show: 'Failed : ', path asString, '[', i asString,']'." "remove all cache entries for path with index >= i" ! ! !FreeTypeFontProvider methodsFor: 'error handling' stamp: 'tween 7/28/2007 12:36'! failedToOpen:face index: i face destroyHandle. "Transcript cr; show: 'Failed : ', path asString, '[', i asString,']'." "remove all cache entries for path with index >= i" ! ! !FreeTypeFontProvider methodsFor: 'file paths' stamp: 'tween 3/15/2007 19:06'! absoluteOrRelativePathFor: absolutePath locationType: aSymbol "answer a relative path from an absolute path according to the location type aSymbol" | p | aSymbol = #absolute ifTrue:[^absolutePath]. aSymbol = #imageRelative ifTrue:[p := SmalltalkImage current imagePath]. aSymbol = #vmRelative ifTrue:[p := SmalltalkImage current vmPath]. (p notNil and:[absolutePath asLowercase beginsWith: p asLowercase]) ifTrue:[^absolutePath copyFrom: p size + 1 to: absolutePath size]. ^absolutePath ! ! !FreeTypeFontProvider methodsFor: 'file paths' stamp: 'tween 3/16/2007 11:02'! absolutePathFor: path locationType: aSymbol "answer an absolute path from an absolute or relative path according to the location type aSymbol" aSymbol = #imageRelative ifTrue:[^SmalltalkImage current imagePath, FileDirectory slash, path ]. aSymbol = #vmRelative ifTrue:[^SmalltalkImage current vmPath ", FileDirectory slash" , path]. ^path ! ! !FreeTypeFontProvider methodsFor: 'file paths' stamp: 'tween 4/28/2007 10:49'! getMacOSXFontFolderPaths "Answer the Mac OS X font folder paths. This needs some FFI code, but for the time being, we guess these and omit the user fonts folder" ^#('/System/Library/Fonts' '/Library/Fonts')! ! !FreeTypeFontProvider methodsFor: 'file paths' stamp: 'tween 4/13/2007 08:25'! getUnixFontFolderPaths "Answer the unix/linux font folder paths" ^#('/usr/share/fonts' '/usr/local/share/fonts')! ! !FreeTypeFontProvider methodsFor: 'file paths' stamp: 'tween 3/25/2007 14:48'! getWindowsFontFolderPath "Answer the windows font folder path. This is obtained through the Windows API if FFI is present, otherwise it is a guess !!" | externalLibraryClass externalTypeClass fun buff r | externalLibraryClass := Smalltalk at: #ExternalLibraryFunction ifAbsent:[]. externalTypeClass := Smalltalk at: #ExternalType ifAbsent:[]. (externalLibraryClass isNil or:[externalTypeClass isNil]) ifTrue:[^self guessWindowsFontFolderPath]. fun := externalLibraryClass name: 'SHGetFolderPathA' module: 'shfolder.dll' callType: 1 returnType: externalTypeClass long argumentTypes: { externalTypeClass long. externalTypeClass long. externalTypeClass long. externalTypeClass long. externalTypeClass char asPointerType}. buff := ByteArray new: 1024. [r := fun invokeWith: 0 with: "CSIDL:=FONTS" 16r0014 with: 0 with: 0 with: buff] on: Error do: [:e | "will get error if ffiplugin is missing" ^self guessWindowsFontFolderPath]. ^(buff copyFrom: 1 to: (buff indexOf: 0) - 1) asString ! ! !FreeTypeFontProvider methodsFor: 'file paths' stamp: 'tween 3/25/2007 14:25'! guessWindowsFontFolderPath "Guess the location of the Windows font folder" | possibles d | possibles := Set new. 'cdefghijklmnopqrstuvwxyz' do:[:drive | #('\windows\fonts' '\winnt\fonts') do:[:path | (d := FileDirectory on: drive asString, ':', path) exists ifTrue:[possibles add: d]]]. possibles := possibles asSortedCollection: [:a :b | a directoryEntry creationTime >= b directoryEntry creationTime]. possibles ifNotEmpty:[^possibles first pathName]. ^nil ! ! !FreeTypeFontProvider methodsFor: 'file paths' stamp: 'tween 4/28/2007 11:09'! platformAbsoluteDirectories | answer dir path | answer := OrderedCollection new. SmalltalkImage current platformName = 'Win32' ifTrue:[ path := self getWindowsFontFolderPath. (path notNil and:[(dir := FileDirectory on: path) exists]) ifTrue:[answer add: dir]]. SmalltalkImage current platformName = 'unix' ifTrue:[ self getUnixFontFolderPaths do:[:each | (dir := FileDirectory on: each) exists ifTrue:[answer add: dir]]]. SmalltalkImage current platformName = 'Mac OS' ifTrue:[ SmalltalkImage current osVersion asNumber >= 1000 ifTrue:["OS X" self getMacOSXFontFolderPaths do:[:each | (dir := FileDirectory on: each) exists ifTrue:[answer add: dir]]]]. ^answer! ! !FreeTypeFontProvider methodsFor: 'file paths' stamp: 'tween 3/26/2007 22:57'! platformImageRelativeDirectories | answer path fontDirectory | answer := OrderedCollection new. (path := SmalltalkImage current imagePath) ifNotEmpty:[ (path endsWith: FileDirectory slash) ifFalse:[path := path, FileDirectory slash]. (fontDirectory := FileDirectory on: path, 'Fonts') exists ifTrue:[answer addLast: fontDirectory]]. ^answer! ! !FreeTypeFontProvider methodsFor: 'file paths' stamp: 'tween 3/26/2007 22:58'! platformVMRelativeDirectories | answer path fontDirectory | answer := OrderedCollection new. (path := SmalltalkImage current vmPath) ifNotEmpty:[ (path endsWith: FileDirectory slash) ifFalse:[path := path, FileDirectory slash]. (fontDirectory := FileDirectory on: path, 'Fonts') exists ifTrue:[answer addLast: fontDirectory]]. ^answer! ! !FreeTypeFontProvider methodsFor: 'font families' stamp: 'tween 8/16/2007 20:39'! buildFamilies | familyNames family | families := Dictionary new. familyNames := (fileInfos collect:[:each | each familyGroupName]) asSet asSortedCollection asArray. familyNames do:[:familyName | family := self buildFamilyNamed: familyName. families at: familyName put: family]. ! ! !FreeTypeFontProvider methodsFor: 'font families' stamp: 'tween 8/16/2007 21:43'! buildFamilyNamed: aFamilyGroupName | infos family| family := FreeTypeFontFamily new familyName: aFamilyGroupName; yourself. infos := fileInfos select:[:each | each familyGroupName = aFamilyGroupName]. family addMembersFromFileInfos: infos. family addSimulatedMembers. ^family ! ! !FreeTypeFontProvider methodsFor: 'font families' stamp: 'tween 8/18/2007 14:19'! families ^tempFamilies ifNil:[families]! ! !FreeTypeFontProvider methodsFor: 'font lookup' stamp: 'tween 9/29/2007 10:48'! fontFor: aLogicalFont familyName: familyName | info answer simulatedSqueakEmphasis needsSimulatedBold needsSimulatedSlant squeakBoldEmphasis squeakItalicEmphasis | FT2Library current == nil ifTrue:[^nil]. info:= self fontInfoFor: aLogicalFont familyName: familyName. info ifNil:[^nil]. answer := FreeTypeFont forLogicalFont: aLogicalFont fileInfo: info. needsSimulatedBold := aLogicalFont isBoldOrBolder and:[(info isBolderThan: 500) not]. needsSimulatedSlant := aLogicalFont isItalicOrOblique and: [info isItalicOrOblique not]. (needsSimulatedBold or:[needsSimulatedSlant]) ifTrue:[ squeakBoldEmphasis := 1. squeakItalicEmphasis := 2. simulatedSqueakEmphasis := 0. needsSimulatedBold ifTrue:[ simulatedSqueakEmphasis := simulatedSqueakEmphasis + squeakBoldEmphasis]. needsSimulatedSlant ifTrue:[ simulatedSqueakEmphasis := simulatedSqueakEmphasis + squeakItalicEmphasis]. answer simulatedEmphasis: simulatedSqueakEmphasis]. answer face validate. answer face isValid ifFalse:[^nil]. "we may get this if startup causes text display BEFORE receiver has been updated from the system" ^answer! ! !FreeTypeFontProvider methodsFor: 'font lookup' stamp: 'tween 8/27/2007 11:33'! fontInfoFor: aLogicalFont familyName: familyName | family member | "use tempFileInfos if not nil, i.e. during an update" "^self fontInfoFor: aLogicalFont in: (tempFileInfos ifNil:[fileInfos]) " family := self families at: familyName ifAbsent:[]. family ifNil:[^nil]. member := family closestMemberWithStretchValue: aLogicalFont stretchValue weightValue: aLogicalFont weightValue slantValue: aLogicalFont slantValue. member ifNil:[^nil]. ^member fileInfo! ! !FreeTypeFontProvider methodsFor: 'initialize-release' stamp: 'DamienCassou 8/22/2009 15:14'! initialize super initialize. fileInfos := OrderedCollection new: 100. fileInfoCache := Dictionary new: 100. "keyed by file size" embeddedFileInfoCache := Dictionary new: 10. "keyed by file size" families := Dictionary new. ! ! !FreeTypeFontProvider methodsFor: 'loading and updating' stamp: 'tween 7/28/2007 14:22'! embedFilesInDirectory: aFileDirectory "embed all the files in aFileDirectory FreeTypeFontProvider current embedFilesInDirectory: (FileDirectory default directoryNamed: 'Fonts') " | filestream bytes basename | aFileDirectory fileNames do:[:filename | filestream := aFileDirectory fileNamed: filename. filestream binary. bytes := filestream contents. filestream close. basename := FileDirectory baseNameFor: filename. self addFromFileContents: bytes baseName: basename]. "update so that missing text styles are created." self updateFromSystem. "clear all the logicalFonts realFonts so that embedded fonts take precedence over external ones" LogicalFont allInstances do:[:logFont | logFont clearRealFont] ! ! !FreeTypeFontProvider methodsFor: 'loading and updating' stamp: 'tween 3/14/2007 23:17'! loadFromSystem self updateFromSystem. ! ! !FreeTypeFontProvider methodsFor: 'loading and updating' stamp: 'tween 3/29/2007 17:16'! updateFromDirectory: aDirectory locationType: aSymbol done: aSet "get info from fonts in aDirectory" (aSet includes: aDirectory) ifTrue:[^self]. aSet add: aDirectory. aDirectory entries do:[:each | each isDirectory ifFalse:[ "SUSE 10.2 has lots of files ending .gz that aren't fonts. We skip them to save time'" ((each name beginsWith:'.') or:[each name asLowercase endsWith:'.gz']) ifFalse:[ self updateFromFileEntry: each directory: aDirectory locationType: aSymbol]]]. aDirectory entries do:[:each | each isDirectory ifTrue:[ self updateFromDirectory: (aDirectory directoryNamed: each name) locationType: aSymbol done: aSet]]. ! ! !FreeTypeFontProvider methodsFor: 'loading and updating' stamp: 'tween 8/12/2007 12:31'! updateFromFileEntry: aDirectoryEntry directory: aFileDirectory locationType: aSymbol | i face numFaces cachedInfo info cachedNumFaces path | "(path findString: '\\') > 0 ifTrue:[self halt]." i:= 0. [(cachedInfo := self validCachedInfoFor: aDirectoryEntry directory: aFileDirectory index: i) notNil] whileTrue:[ i = 0 ifTrue:[cachedNumFaces := cachedInfo numFaces]. self addFileInfo: cachedInfo index: i. i := i + 1.]. (cachedNumFaces notNil and:[i >= cachedNumFaces]) ifTrue:[^self]. path := aFileDirectory fullNameFor: aDirectoryEntry name . [face := FreeTypeFace basicNew filename: path; index: i. ["we use the primNewFaceFromFile:index: method because we want to do this as fast as possible and we don't need the face registered because it will be explicitly destroyed later" face primNewFaceFromFile: path index: i. face loadFields] on: FT2Error do:[:e | ^self failedToOpen:face from: path index: i]. (face height notNil and:[face hasFamilyName and:[face hasStyleName and:[face isValid]]]) ifFalse:[^self failedToOpen:face from: path index: i] ifTrue:[ numFaces isNil ifTrue:[numFaces := face numFaces]. info :=FreeTypeFileInfo new absoluteOrRelativePath: (self absoluteOrRelativePathFor: path locationType: aSymbol); absolutePath: path; "used for quick lookup on same platform" locationType: aSymbol; index: i; fileSize: aDirectoryEntry fileSize; modificationTime: aDirectoryEntry modificationTime; familyName: face familyName; styleName: face styleName; postscriptName: face postscriptName; bold: face isBold; italic: face isItalic; fixedWidth: face isFixedWidth; numFaces: numFaces; extractAttributesFromNames; yourself. self addFileInfo: info index: i. self cacheFileInfo: info index: i. "Transcript show: 'from file : ', info asString." face destroyHandle]. i := i + 1. i < numFaces "note, we use < rather than <= , because i is zero based"] whileTrue:[]. ! ! !FreeTypeFontProvider methodsFor: 'loading and updating' stamp: 'tween 8/19/2007 16:57'! updateFromSystem | done platformDirs vmDirs imageDirs i | i := 0. tempFileInfos := fileInfos. "tempFileInfos will be used during update" tempFamilies := families. "tempFamilies will be used during update" fileInfos := OrderedCollection new: 100. 'FreeType' displayProgressAt: Display center from: 0 to: 3 during:[:mainBar | 'Updating cached file info' displayProgressAt: Display center from: 0 to: fileInfoCache size during:[:bar | fileInfoCache valuesDo:[:col | col copy do:[:each | | dir | dir := FileDirectory on: (FileDirectory dirPathFor: each absolutePath). (dir exists not or:[(dir isAFileNamed: (dir localNameFor: each absolutePath)) not]) ifTrue:[col remove: each]]. bar value: (i := i + 1).]]. mainBar value: 1. FT2Library current == nil ifFalse:[ "Add all the embedded file infos" embeddedFileInfoCache valuesDo:[:eachSet | eachSet do:[:each | fileInfos addFirst: each]]. done := Set new. "visited directories are tracked in done, so that they are not processed twice" platformDirs := self platformAbsoluteDirectories. vmDirs := self platformVMRelativeDirectories. imageDirs := self platformImageRelativeDirectories. i := 0. 'Loading font files' displayProgressAt: Display center from: 0 to: 3 during:[:bar | imageDirs do:[:each | self updateFromDirectory: each locationType: #imageRelative done: done ]. bar value: (i := i + 1). vmDirs do:[:each | self updateFromDirectory: each locationType: #vmRelative done: done ]. bar value: (i := i + 1). platformDirs do:[:each | self updateFromDirectory: each locationType: #absolute done: done ]. bar value: (i := i + 1) ]]. mainBar value: 2. i := 0. 'Calculating available font families' displayProgressAt: Display center from: 0 to: 1 during:[:bar | "self removeUnavailableTextStyles." "self addTextStylesWithPointSizes: #(8 10 12 15 24)." tempFileInfos := nil. self buildFamilies. tempFamilies := nil. bar value: (i := i + 1)]. mainBar value: 3]. LogicalFont allInstances do:[:each | each clearRealFont]. "in case they have a bad one" ! ! !FreeTypeFontProvider methodsFor: 'loading and updating' stamp: 'tween 3/17/2007 10:16'! validCachedInfoFor: aDirectoryEntry directory: aFileDirectory index: i "answer info from cache if the file on the disk has the same size/timestamp as the cached info, otherwise answer nil" | cacheEntry fileSize modificationTime path| fileSize := aDirectoryEntry fileSize. modificationTime := aDirectoryEntry modificationTime. cacheEntry := (fileInfoCache at: {fileSize. i} ifAbsentPut:[Set new]) detect:[:each | path := path ifNil:["only build path when needed" aFileDirectory fullNameFor: aDirectoryEntry name]. each modificationTime = modificationTime and: [(self absolutePathFor: each absoluteOrRelativePath locationType: each locationType) = path]] ifNone:[]. "cacheEntry ifNotNil:[Transcript cr; show: 'from cache : ', cacheEntry asString]." ^cacheEntry ! ! !FreeTypeFontProvider methodsFor: 'loading and updating' stamp: 'tween 7/28/2007 13:34'! validEmbeddedCachedInfoFor: bytes index: i "answer info from cache if the bytes are the same as the cached info, otherwise answer nil" | cacheEntry fileSize | fileSize := bytes size. cacheEntry := (embeddedFileInfoCache at: {fileSize. i} ifAbsentPut:[Set new]) detect:[:each | each fileContents = bytes] ifNone:[]. ^cacheEntry ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeFontProvider class instanceVariableNames: 'current'! !FreeTypeFontProvider class methodsFor: 'accessing' stamp: 'tween 3/23/2007 09:59'! current " current := nil. TimeProfileBrowser onBlock: [FreeTypeFontProvider current] " ^current ifNil:[ current := self new. current updateFromSystem]! ! !FreeTypeFontProvider class methodsFor: 'class initialization' stamp: 'tween 2/5/2008 22:42'! initialize " self initialize " Smalltalk removeFromStartUpList: self. Smalltalk addToStartUpList: self after: SecurityManager. "actually it needs to be before AutoStart" "ensure that other classes have also been initialized by forcefully initializing them now. It then does not matter which order they are initialized in during the package load" FT2Constants initialize. FreeTypeCache initialize. FreeTypeCacheConstants initialize. FreeTypeSettings initialize. "an instVar, pendingKernX, is added to both CharacterScanner and MultiCharacterScanner by the preamble of the package. However, some versions of the monticello loader don't run the preamble code. So, we check if the instVars have been added, and if not add them now" (CharacterScanner instVarNames includes: 'pendingKernX') ifFalse:[ Compiler evaluate: 'Object subclass: #CharacterScanner instanceVariableNames: ''destX lastIndex xTable destY stopConditions text textStyle alignment leftMargin rightMargin font line runStopIndex spaceCount spaceWidth emphasisCode kern indentationLevel wantsColumnBreaks pendingKernX'' classVariableNames: ''DefaultStopConditions NilCondition PaddedSpaceCondition SpaceCondition'' poolDictionaries: ''TextConstants'' category: ''Graphics-Text'' ']. (MultiCharacterScanner instVarNames includes: 'pendingKernX') ifFalse:[ Compiler evaluate: 'Object subclass: #MultiCharacterScanner instanceVariableNames: ''destX lastIndex xTable destY stopConditions text textStyle alignment leftMargin rightMargin font line runStopIndex spaceCount spaceWidth emphasisCode kern indentationLevel wantsColumnBreaks presentation presentationLine numOfComposition baselineY firstDestX pendingKernX'' classVariableNames: ''DefaultStopConditions NilCondition PaddedSpaceCondition SpaceCondition'' poolDictionaries: ''TextConstants'' category: ''Multilingual-Scanning'' ']. self current. "this creates an instance of me, and updates from the system"! ! !FreeTypeFontProvider class methodsFor: 'startup' stamp: 'torsten.bergmann 3/25/2009 04:56'! startUp: resuming (Preferences UpdateFontsAtImageStartup and: [resuming]) ifTrue:[ self current updateFromSystem]! ! AbstractFontSelectorDialogWindow subclass: #FreeTypeFontSelectorDialogWindow instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Polymorph-Widgets-Windows'! !FreeTypeFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 9/26/2008 16:01'! defaultFontFamilies "Answer the set of available fonts families that are supported in the font that they represent." |fonts defaultFont| defaultFont := TextStyle default fontOfPointSize: self theme listFont pointSize. fonts := (LogicalFontManager current allFamilies asSortedCollection: [:a :b | a familyName <= b familyName]) collect: [:ff | (ff closestMemberWithStretchValue: LogicalFont stretchRegular weightValue: LogicalFont weightRegular slantValue: LogicalFont slantRegular) asLogicalFontOfPointSize: self theme listFont pointSize]. ^fonts collect: [:f | |dispFont| dispFont := (f isSymbolFont or: [(f hasDistinctGlyphsForAll: f familyName) not]) ifTrue: [defaultFont] ifFalse: [f]. f familyName asText addAttribute: (TextFontReference toFont: dispFont)]! ! !FreeTypeFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:14'! matchingFont "Answer the font that matches the selections." |lf emp| self familyName ifNil: [^TextStyle defaultFont]. lf := LogicalFont familyName: self familyName pointSize: (self fontSize ifNil: [10]). emp := self isBold ifTrue: [TextEmphasis bold emphasisCode] ifFalse: [TextEmphasis normal emphasisCode]. self isItalic ifTrue: [emp := emp + TextEmphasis italic emphasisCode]. self isUnderlined ifTrue: [emp := emp + TextEmphasis underlined emphasisCode]. self isStruckOut ifTrue: [emp := emp + TextEmphasis struckOut emphasisCode]. lf := lf emphasis: emp. lf realFont ifNil: [^TextStyle defaultFont]. ^lf ! ! !FreeTypeFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:49'! newFontStyleButtonRowMorph "Answer a new font style button row morph." ^self newRow: { self newBoldButtonMorph. self newItalicButtonMorph}! ! !FreeTypeFontSelectorDialogWindow methodsFor: 'as yet unclassified' stamp: 'gvc 4/21/2009 17:26'! updateFromSelectedFont "Update our state based on the selected font." |font| font := self selectedFont ifNil: [TextStyle defaultFont]. fontFamilyIndex := (self fontFamilies indexOf: font familyName). fontSizeIndex := (self fontSizes indexOf: font pointSize). isBold := (font emphasis allMask: TextEmphasis bold emphasisCode). isItalic := (font emphasis allMask: TextEmphasis italic emphasisCode). self changed: #fontFamilyIndex; changed: #fontSizeIndex; changed: #isBold; changed: #isItalic. self textPreviewMorph ifNotNilDo: [:tp | tp font: self selectedFont. self changed: #previewText]! ! Object subclass: #FreeTypeGlyphRenderer instanceVariableNames: '' classVariableNames: '' poolDictionaries: 'FT2Constants' category: 'FreeType-GlyphRendering'! !FreeTypeGlyphRenderer commentStamp: 'tween 4/4/2007 09:48' prior: 0! This class produces glyphs for a FreeTypeFont. It can be subclassed to provide, for example, sub-pixel anti-aliased glyphs.! !FreeTypeGlyphRenderer methodsFor: 'public' stamp: 'tween 4/4/2007 10:35'! glyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub font: aFreeTypeFont | f | f := self renderGlyph: aCharacter depth: (monoBoolean ifTrue:[1] ifFalse:[8]) subpixelPosition: sub font: aFreeTypeFont. monoBoolean ifTrue:[ f := self fixBytesForMono: f. f := f asFormOfDepth: 8]. f := self convert8to32: f colorValue: aColorValue. ^f ! ! !FreeTypeGlyphRenderer methodsFor: 'public' stamp: 'tween 4/4/2007 20:53'! mode41GlyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub font: aFreeTypeFont | f | f := self renderGlyph: aCharacter depth: (monoBoolean ifTrue:[1] ifFalse:[8]) subpixelPosition: sub font: aFreeTypeFont. monoBoolean ifTrue:[ f := self fixBytesForMono: f. f := f asFormOfDepth: 32] ifFalse:[ f := self convert8To32: f]. ^f! ! !FreeTypeGlyphRenderer methodsFor: 'public' stamp: 'tween 4/4/2007 19:25'! subGlyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub font: aFreeTypeFont "the default renderer does not support sub-pixel anti-aliasing, so answer an ordinary glyph" ^self mode41GlyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub font: aFreeTypeFont ! ! !FreeTypeGlyphRenderer methodsFor: 'private' stamp: 'tween 4/4/2007 10:25'! convert8To32: aGlyphForm "convert aGlyphForm from the 8 bit deep form produced by FreeType, where each byte represents the intensity of a single pixel, to a 32 bit deep form" | w h s answer rowstart bytes word littleEndian shift v a colorVal | bytes := aGlyphForm bits. w := aGlyphForm width. h := aGlyphForm height. answer := aGlyphForm class extent: w@h depth: 32. answer offset: (aGlyphForm offset x) @(aGlyphForm offset y); advance: aGlyphForm advance; linearAdvance: aGlyphForm linearAdvance. s := w + 3 >> 2. littleEndian := aGlyphForm isLittleEndian. 0 to: h - 1 do: [:y | rowstart := (y * s)+1. 0 to: w - 1 do:[:x | word := bytes at: rowstart + (x//4). shift := 8* (littleEndian ifTrue:[x bitAnd: 3] ifFalse:[3-(x bitAnd: 3)]). v := word >>shift bitAnd: 16rFF. a := v > 0 ifTrue:[16rFF] ifFalse:[0]. colorVal := v + (v bitShift: 8) + (v bitShift: 16) + (a bitShift: 24). answer bits integerAt: (y*w)+(x+1) put: colorVal]]. ^answer! ! !FreeTypeGlyphRenderer methodsFor: 'private' stamp: 'tween 4/4/2007 21:24'! convert8to32: aGlyphForm colorValue: foreColorValue "convert from the 8 bit deep form produced by FreeType, where each byte represents the intensity of a single pixel, to a 32 bit deep form with pixels of color foreColorValue " | w h s answer rowstart bytes word littleEndian shift v a colorVal foreColorVal foreColorA foreColorR foreColorG foreColorB r g b | foreColorVal := foreColorValue. foreColorA := foreColorVal >> 24. foreColorR := foreColorVal >> 16 bitAnd: 16rFF. foreColorG := foreColorVal >> 8 bitAnd: 16rFF. foreColorB := foreColorVal bitAnd: 16rFF. bytes := aGlyphForm bits. w := aGlyphForm width. h := aGlyphForm height. answer := aGlyphForm class extent: w@h depth: 32. answer offset: (aGlyphForm offset x) @ (aGlyphForm offset y); advance: aGlyphForm advance; linearAdvance: aGlyphForm linearAdvance. s := w + 3 >> 2. littleEndian := aGlyphForm isLittleEndian. 0 to: h - 1 do: [:y | rowstart := (y * s)+1. 0 to: w - 1 do:[:x | word := bytes at: rowstart + (x//4). shift := 8* (littleEndian ifTrue:[x bitAnd: 3] ifFalse:[3-(x bitAnd: 3)]). v := word >>shift bitAnd: 16rFF. a := v > 0 ifTrue:[v * foreColorA // 16rFF] ifFalse:[0]. r := v > 0 ifTrue:[a * foreColorR // 16rFF] ifFalse:[0]. g := v > 0 ifTrue:[a * foreColorG // 16rFF] ifFalse:[0]. b := v > 0 ifTrue:[a * foreColorB // 16rFF] ifFalse:[0]. colorVal := (a bitShift: 24) + (r bitShift: 16) + (g bitShift: 8) + b. answer bits integerAt: (y*w)+(x+1) put: colorVal]]. ^answer! ! !FreeTypeGlyphRenderer methodsFor: 'private' stamp: 'tween 4/4/2007 10:28'! fixBytesForMono: aGlyphForm "On Windows, the bits in each byte are in reverse order, and inverted. i.e. 2r10100000 should be 2r11111010 to display correctly. This needs further investigation" | b newB bits | bits := aGlyphForm bits. 1 to: bits byteSize do:[:i | b := bits byteAt: i. newB := ((((((((b bitAnd: 2r10000000) bitShift: -7) bitOr: ((b bitAnd: 2r1000000) bitShift: -5)) bitOr: ((b bitAnd: 2r100000) bitShift: -3)) bitOr: ((b bitAnd: 2r10000) bitShift: -1)) bitOr: ((b bitAnd: 2r1000) bitShift: 1)) bitOr: ((b bitAnd: 2r100) bitShift: 3)) bitOr: ((b bitAnd: 2r10) bitShift: 5)) bitOr: ((b bitAnd: 2r1) bitShift: 7). bits byteAt: i put: (newB bitXor: 2r11111111)]. ^aGlyphForm! ! !FreeTypeGlyphRenderer methodsFor: 'private' stamp: 'michael.rueger 2/5/2009 17:03'! renderGlyph: aCharacter depth: depth subpixelPosition: sub font: aFreeTypeFont "Glyphs are either 1 or 8 bit deep. For 32 bpp we use 8 bits, otherwise 1" | em form glyph charCode slant extraWidth extraHeight boldExtra offsetX offsetY s synthBoldStrength hintingFlags flags face | charCode := aCharacter asUnicode asInteger. (aFreeTypeFont face charmaps includes:'unic') ifTrue:[ (aFreeTypeFont isSymbolFont and:[charCode >= 16r20 and: [charCode <= 16rFF ] ]) ifTrue:[charCode := charCode + 16rF000]] ifFalse:[ (aFreeTypeFont face charmaps includes:'armn') ifTrue:[ "select apple roman char map, and map character from unicode to mac encoding" aFreeTypeFont face setCharMap:'armn'. charCode := aCharacter unicodeToMacRoman asUnicode asInteger. "check this!!"]]. aCharacter < $ ifTrue: ["charCode := $ asUnicode asInteger" ^(GlyphForm extent: 0@0 depth: depth) advance: 0@0; linearAdvance: 0@0; offset:0@0; yourself ]. em := aFreeTypeFont pixelSize. [face := aFreeTypeFont face. face setPixelWidth: em height: em. hintingFlags := FreeTypeSettings current hintingFlags. flags := LoadNoBitmap bitOr:( LoadIgnoreTransform bitOr: hintingFlags). face loadCharacter:charCode flags: flags] on: FT2Error do:[:e | ^(GlyphForm extent: 0@0 depth: depth) advance: 0@0; linearAdvance: 0@0; offset:0@0; yourself]. glyph := face glyph. slant := aFreeTypeFont simulatedItalicSlant. extraWidth := (glyph height * slant) abs ceiling. synthBoldStrength := aFreeTypeFont simulatedBoldStrength. boldExtra := 4 * synthBoldStrength abs ceiling. extraWidth := extraWidth + boldExtra. sub > 0 ifTrue:[ extraWidth := extraWidth + 1]. extraHeight := boldExtra. form := GlyphForm extent: (glyph width + extraWidth + 1)@(glyph height + extraHeight+ 1) depth: depth. s := (glyph height-glyph hBearingY) * slant. s := s sign * (s abs ceiling). offsetX := glyph hBearingX negated + s + (boldExtra // 2) . offsetY := glyph height - glyph hBearingY + (boldExtra//2). synthBoldStrength ~= 0 ifTrue:[face emboldenOutline: synthBoldStrength]. face transformOutlineAngle: 0 scalePoint: 1@1 slant: slant. face translateOutlineBy: (offsetX+(sub/64))@offsetY. face renderGlyphIntoForm: form. form offset: (glyph hBearingX - s - (boldExtra // 2) ) @ (glyph hBearingY + 1 + (boldExtra / 2) ceiling ) negated. "When not hinting FreeType sets the advance to the truncated linearAdvance. The characters appear squashed together. Rounding is probably better, so we fix the advance here" aFreeTypeFont subPixelPositioned ifTrue:[ form advance: glyph roundedPixelLinearAdvance] ifFalse:[ form advance: glyph advance]. form linearAdvance: glyph linearAdvance. ^form! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeGlyphRenderer class instanceVariableNames: 'current'! !FreeTypeGlyphRenderer class methodsFor: 'accessing' stamp: 'tween 4/4/2007 09:50'! current: aKindOfFreeTypeGlyphRender current := aKindOfFreeTypeGlyphRender! ! !FreeTypeGlyphRenderer class methodsFor: 'instance creation' stamp: 'tween 4/4/2007 19:24'! current " FreeTypeGlyphRenderer current " ^current ifNil:[current := self new]! ! Object subclass: #FreeTypeNameParser instanceVariableNames: 'combinedName familyNameIn styleNameIn delimiters tokens extractedSlant extractedSlantValue extractedUpright extractedStretch extractedWeight italicFlag boldFlag extractedWeightValue extractedStretchValue' classVariableNames: '' poolDictionaries: '' category: 'FreeType-FontManager'! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/12/2007 20:14'! boldFlag: aBoolean boldFlag := aBoolean! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/16/2007 21:32'! extractedSlant ^extractedSlant! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/16/2007 21:33'! extractedSlantValue ^extractedSlantValue! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/12/2007 12:29'! extractedStretch ^extractedStretch! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/16/2007 00:55'! extractedStretchValue ^extractedStretchValue! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/16/2007 01:16'! extractedUpright ^extractedUpright! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/12/2007 12:29'! extractedWeight ^extractedWeight! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/16/2007 00:55'! extractedWeightValue ^extractedWeightValue! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/12/2007 00:14'! familyName ^combinedName withBlanksTrimmed! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/11/2007 18:06'! familyName: familyName familyNameIn := familyName. ! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/11/2007 23:39'! familyNameIn: familyName familyNameIn := familyName. ! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/12/2007 20:14'! italicFlag: aBoolean italicFlag := aBoolean! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/11/2007 18:06'! styleName: styleName styleNameIn := styleName. ! ! !FreeTypeNameParser methodsFor: 'accessing' stamp: 'tween 8/11/2007 23:39'! styleNameIn: styleName styleNameIn := styleName. ! ! !FreeTypeNameParser methodsFor: 'initialize-release' stamp: 'alain.plantec 5/28/2009 09:55'! initialize super initialize. delimiters := ',.-:='. Character separators do:[:c | delimiters := delimiters , c asString]. ! ! !FreeTypeNameParser methodsFor: 'known names' stamp: 'tween 8/16/2007 02:54'! italicAndObliqueNames ^self class italicAndObliqueNames! ! !FreeTypeNameParser methodsFor: 'known names' stamp: 'tween 8/16/2007 02:12'! italicNames ^self class italicNames! ! !FreeTypeNameParser methodsFor: 'known names' stamp: 'tween 8/25/2007 13:28'! normalNames ^self class normalNames ! ! !FreeTypeNameParser methodsFor: 'known names' stamp: 'tween 9/29/2007 11:41'! stretchNames ^self class stretchNames! ! !FreeTypeNameParser methodsFor: 'known names' stamp: 'tween 9/29/2007 11:41'! weightNames ^self class weightNames ! ! !FreeTypeNameParser methodsFor: 'parsing' stamp: 'tween 8/13/2007 23:02'! addStyleNameToCombinedName: aStyleString | lcCombined lcStyleName addStyle index | lcCombined := combinedName asLowercase. lcStyleName := aStyleString asLowercase. addStyle := true. (index := lcCombined findString: lcStyleName) > 0 ifTrue:[ (index = 1 or:[delimiters includes: (lcCombined at: index - 1)]) ifTrue:[ ((index + lcStyleName size > lcCombined size) or:[ delimiters includes: (lcCombined at: index + lcStyleName size) ]) ifTrue:["don't add the style to the combinedName, because it already contains it" addStyle := false]]]. addStyle ifTrue:[combinedName := combinedName , ' ', aStyleString]. ! ! !FreeTypeNameParser methodsFor: 'parsing' stamp: 'tween 9/29/2007 12:03'! extractSlant | matches start end | "match and remove last italic/oblique token" extractedSlant := nil. extractedSlantValue := LogicalFont slantRegular. "not italic or oblique" (self italicAndObliqueNames detect: [:each | (matches := self lastMatchValueSequence: {each}) notNil] ifNone:[]) ifNotNil:[ start := matches first second. end := matches last third. extractedSlant := combinedName copyFrom: start to: end. "extractedSlantValue := (self italicNames includes: extractedSlant asLowercase) ifTrue:[1] ifFalse:[2]." extractedSlantValue := LogicalFont slantItalic. "treat italic and oblique the same, as italic" [start > 1 and:[delimiters includes: (combinedName at: start - 1)]] "also remove delimiters before token" whileTrue:[start := start - 1]. [end < combinedName size and:[delimiters includes: (combinedName at: end + 1)]] "also remove delimiters after token" whileTrue:[end := end + 1]. combinedName := combinedName copyReplaceFrom: start to: end with: ' '.]. (extractedSlant isNil and:[italicFlag]) ifTrue:["no italic specified in familyName or styleName; force it to be 'Italic'" extractedSlant := 'Italic'. extractedSlantValue := LogicalFont slantItalic] ! ! !FreeTypeNameParser methodsFor: 'parsing' stamp: 'tween 9/29/2007 12:35'! extractStretch "match and remove last stretch tokens" | matches start end | extractedStretchValue := LogicalFont stretchRegular. (self stretchNames detect: [:each | matches := self lastMatchValueSequence: each allButFirst. matches ifNotNil:[extractedStretchValue := each first]. matches notNil] ifNone:[]) ifNotNil:[ start := matches first second. end := matches last third. extractedStretch := combinedName copyFrom: start to: end. [start > 1 and:[delimiters includes: (combinedName at: start - 1)]] "also remove delimiters before token" whileTrue:[start := start - 1]. [end < combinedName size and:[delimiters includes: (combinedName at: end + 1)]] "also remove delimiters after token" whileTrue:[end := end + 1]. combinedName := combinedName copyReplaceFrom: start to: end with: ' '. "re-tokenize" "tokens := self tokenize: combinedName delimiters: delimiters"]. ! ! !FreeTypeNameParser methodsFor: 'parsing' stamp: 'tween 8/14/2007 22:01'! extractUpright "extract from current combined name. answer new combinedName" | normalTok start end | normalTok := tokens reversed detect: [:tok | (self normalNames detect: [:str | str asLowercase = tok first asLowercase] ifNone:[]) notNil ] ifNone:[]. normalTok ifNotNil:[ "remove it from combinedName" start := normalTok second. end := normalTok third. extractedUpright := combinedName copyFrom: start to: end. [start > 1 and:[delimiters includes: (combinedName at: start - 1)]] whileTrue:[start := start - 1]. [end < combinedName size and:[delimiters includes: (combinedName at: end + 1)]] whileTrue:[end := end + 1]. combinedName := combinedName copyReplaceFrom: start to: end with: ' ']. ! ! !FreeTypeNameParser methodsFor: 'parsing' stamp: 'tween 9/29/2007 12:34'! extractWeight "match and remove last weight tokens" | matches start end | extractedWeightValue := LogicalFont weightRegular. (self weightNames detect: [:each | matches := self lastMatchValueSequence: each allButFirst. matches ifNotNil:[extractedWeightValue := each first]. matches notNil] ifNone:[]) ifNotNil:[ start := matches first second. end := matches last third. extractedWeight := combinedName copyFrom: start to: end. [start > 1 and:[delimiters includes: (combinedName at: start - 1)]] "also remove delimiters before token" whileTrue:[start := start - 1]. [end < combinedName size and:[delimiters includes: (combinedName at: end + 1)]] "also remove delimiters after token" whileTrue:[end := end + 1]. combinedName := combinedName copyReplaceFrom: start to: end with: ' '.]. (extractedWeight isNil and:[boldFlag]) ifTrue:["no weight specified in familyName or styleName; force it to be 'Bold'" extractedWeight := 'Bold'. extractedWeightValue := LogicalFont weightBold] ! ! !FreeTypeNameParser methodsFor: 'parsing' stamp: 'tween 8/11/2007 18:23'! lastMatchValueSequence: values "answer the last contiguous tokens that match pattern tokens, or nil if not found. matching is case insensitive " | answer nullToken match tok | nullToken := {''. nil. nil}. tokens size - values size + 1 to: 1 by: -1 do:[:ti | match := true. answer := Array new. 1 to: values size do:[:vi | tok := tokens at: ti + vi - 1 ifAbsent: [nullToken]. (match and: [tok first asLowercase = ( values at: vi) asLowercase]) ifFalse:[match := false] ifTrue:[answer := answer, {tok} ]]. match ifTrue:[^answer]]. ^nil ! ! !FreeTypeNameParser methodsFor: 'parsing' stamp: 'tween 8/16/2007 21:32'! parse | styleName | styleNameIn := self splitBadTokensIn: styleNameIn. combinedName := styleNameIn withBlanksTrimmed. tokens := self tokenize: combinedName. self extractUpright. styleName := combinedName. combinedName := familyNameIn withBlanksTrimmed. self addStyleNameToCombinedName: styleName.. tokens := self tokenize: combinedName. self extractSlant. tokens := self tokenize: combinedName. self extractStretch. tokens := self tokenize: combinedName. self extractWeight. ! ! !FreeTypeNameParser methodsFor: 'parsing' stamp: 'tween 8/14/2007 22:11'! splitBadTokensIn: aString "split tokens such as BoldOblique, that should be two words" | i str | str := aString. #( ('bold' 'oblique') ('bold' 'italic') ) do:[:pair | (i := str asLowercase findString: pair first, pair second startingAt: 1) > 0 ifTrue:[ str := (str first: i + pair first size - 1), ' ', (str last: (str size - (i + pair first size - 1)))]]. ^str! ! !FreeTypeNameParser methodsFor: 'parsing' stamp: 'tween 8/11/2007 18:08'! tokenize: aString "answer an OrderedCollection of {string. start. end} tuples. tokens are separated by $- $:= $, $. and whitespace" | tokens answer start | tokens := aString findTokens: delimiters keep: delimiters. answer := OrderedCollection new. start := 1. tokens do:[:tok | (delimiters includes: tok first) ifFalse:[answer add: {tok. start. start+tok size - 1}]. start := start + tok size]. ^answer! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeNameParser class instanceVariableNames: 'weightNames stretchNames obliqueNames normalNames italicNames'! !FreeTypeNameParser class methodsFor: 'known names' stamp: 'tween 8/16/2007 02:47'! italicAndObliqueNames ^self italicNames, self obliqueNames! ! !FreeTypeNameParser class methodsFor: 'known names' stamp: 'tween 9/30/2007 12:44'! italicNames "Answer a sequence of String tokens that indicate an italic font within a font family-style name" " TO RE-INITIALIZE... self instVarNamed: #italicNames put: nil. " italicNames ifNotNil:[^italicNames]. ^italicNames := #( 'ita' 'ital' 'italic' 'cursive' 'kursiv').! ! !FreeTypeNameParser class methodsFor: 'known names' stamp: 'tween 9/30/2007 12:44'! normalNames "Answer a sequence of String tokens that indicate a Regular (i.e. non-oblique, non-italic) font within a font family-style name" " TO RE-INITIALIZE... self instVarNamed: #normalNames put: nil. " normalNames ifNotNil:[^normalNames]. ^normalNames := #('Book' 'Normal' 'Regular' 'Roman' 'Upright').! ! !FreeTypeNameParser class methodsFor: 'known names' stamp: 'tween 9/30/2007 12:43'! obliqueNames "Answer a sequence of String tokens that indicate an oblique font within a font family-style name" " TO RE-INITIALIZE... self instVarNamed: #obliqueNames put: nil. " obliqueNames ifNotNil:[^obliqueNames]. ^obliqueNames := #( 'inclined' 'oblique' 'backslanted' 'backslant' 'slanted').! ! !FreeTypeNameParser class methodsFor: 'known names' stamp: 'tween 9/30/2007 12:42'! stretchNames "Answer a sequence of arrays. Each array has an integer stretch value as its first element (1 - 9). The remaining elements are String tokens which might appear within a font family-style name" " TO RE-INITIALIZE... self instVarNamed: #stretchNames put: nil. " stretchNames ifNotNil:[^stretchNames]. ^stretchNames := { {LogicalFont stretchExtraCompressed. 'extra'. 'compressed'}. {LogicalFont stretchExtraCompressed. 'extracompressed'}. {LogicalFont stretchExtraCompressed. 'ext'. 'compressed'}. {LogicalFont stretchExtraCompressed. 'extcompressed'}. {LogicalFont stretchUltraCompressed. 'ultra'. 'compressed'}. {LogicalFont stretchUltraCompressed. 'ultracompressed'}. {LogicalFont stretchUltraCondensed. 'ultra'. 'condensed'}. {LogicalFont stretchUltraCondensed. 'ultracondensed'}. {LogicalFont stretchUltraCondensed. 'ultra'. 'cond'}. {LogicalFont stretchUltraCondensed. 'ultracond'}. {LogicalFont stretchCompressed. 'compressed'}. {LogicalFont stretchExtraCondensed. 'extra'. 'condensed'}. {LogicalFont stretchExtraCondensed. 'extracondensed'}. {LogicalFont stretchExtraCondensed. 'ext'. 'condensed'}. {LogicalFont stretchExtraCondensed. 'extcondensed'}. {LogicalFont stretchExtraCondensed. 'extra'. 'cond'}. {LogicalFont stretchExtraCondensed. 'extracond'}. {LogicalFont stretchExtraCondensed. 'ext'. 'cond'}. {LogicalFont stretchExtraCondensed. 'extcond'}. {LogicalFont stretchNarrow. 'narrow'}. {LogicalFont stretchCompact. 'compact'}. {LogicalFont stretchSemiCondensed. 'semi'. 'condensed'}. {LogicalFont stretchSemiCondensed. 'semicondensed'}. {LogicalFont stretchSemiCondensed. 'semi'. 'cond'}. {LogicalFont stretchSemiCondensed. 'semicond'}. {LogicalFont stretchWide. 'wide'}. {LogicalFont stretchSemiExpanded. 'semi'. 'expanded'}. {LogicalFont stretchSemiExpanded. 'semiexpanded'}. {LogicalFont stretchSemiExtended. 'semi'. 'extended'}. {LogicalFont stretchSemiExtended. 'semiextended'}. {LogicalFont stretchExtraExpanded. 'extra'. 'expanded'}. {LogicalFont stretchExtraExpanded. 'extraexpanded'}. {LogicalFont stretchExtraExpanded. 'ext'. 'expanded'}. {LogicalFont stretchExtraExpanded. 'extexpanded'}. {LogicalFont stretchExtraExtended. 'extra'. 'extended'}. {LogicalFont stretchExtraExtended. 'extraextended'}. {LogicalFont stretchExtraExtended. 'ext'. 'extended'}. {LogicalFont stretchExtraExtended. 'extextended'}. {LogicalFont stretchUltraExpanded. 'ultra'. 'expanded'}. {LogicalFont stretchUltraExpanded. 'ultraexpanded'}. {LogicalFont stretchUltraExtended. 'ultra'. 'extended'}. {LogicalFont stretchUltraExtended. 'ultraextended'}. {LogicalFont stretchCondensed. 'condensed'}. {LogicalFont stretchCondensed. 'cond'}. {LogicalFont stretchExpanded. 'expanded'}. {LogicalFont stretchExtended. 'extended'} }. "search for them in the order given here" ! ! !FreeTypeNameParser class methodsFor: 'known names' stamp: 'tween 9/30/2007 12:41'! weightNames "Answer a sequence of arrays. Each array has an integer weight value as its first element. The remaining elements are String tokens which might appear within a font family-style name" " TO RE-INITIALIZE... self instVarNamed: #weightNames put: nil. " weightNames ifNotNil:[^weightNames]. ^weightNames := { {LogicalFont weightExtraThin. 'extra'. 'thin'}. {LogicalFont weightExtraThin.'extrathin'}. {LogicalFont weightExtraThin. 'ext'. 'thin'}. {LogicalFont weightExtraThin. 'extthin'}. {LogicalFont weightUltraThin.'ultra'. 'thin'}. {LogicalFont weightUltraThin.'ultrathin'}. {LogicalFont weightExtraLight. 'extra'. 'light'}. {LogicalFont weightExtraLight. 'extralight'}. {LogicalFont weightExtraLight. 'ext'. 'light'}. {LogicalFont weightExtraLight. 'extlight'}. {LogicalFont weightUltraLight. 'ultra'. 'light'}. {LogicalFont weightUltraLight. 'ultralight'}. {LogicalFont weightSemiBold. 'semi'. 'bold'}. {LogicalFont weightSemiBold. 'semibold'}. {LogicalFont weightDemiBold. 'demi'. 'bold'}. {LogicalFont weightDemiBold. 'demibold'}. {LogicalFont weightExtraBold. 'extra'. 'bold'}. {LogicalFont weightExtraBold. 'extrabold'}. {LogicalFont weightExtraBold. 'ext'. 'bold'}. {LogicalFont weightExtraBold. 'extbold'}. {LogicalFont weightUltraBold. 'ultra'. 'bold'}. {LogicalFont weightUltraBold. 'ultrabold'}. {LogicalFont weightExtraBlack. 'extra'. 'black'}. {LogicalFont weightExtraBlack. 'extrablack'}. {LogicalFont weightExtraBlack. 'ext'. 'black'}. {LogicalFont weightExtraBlack. 'extblack'}. {LogicalFont weightUltraBlack.'ultra'. 'black'}. {LogicalFont weightUltraBlack. 'ultrablack'}. {LogicalFont weightBold. 'bold'}. {LogicalFont weightThin.'thin'}. {LogicalFont weightLight. 'light'}. {LogicalFont weightMedium. 'medium'}. {LogicalFont weightBlack. 'black'}. {LogicalFont weightHeavy. 'heavy'}. {LogicalFont weightNord. 'nord'}. {LogicalFont weightDemi. 'demi'}. {LogicalFont weightUltra. 'ultra'}. } ! ! Object subclass: #FreeTypeSettings instanceVariableNames: 'gamma hinting lightHinting subPixelAntiAliasing forceAutoHinting lcdHinting lcdvHinting monoHinting bitBltSubPixelAvailable subPixelFilters forceNonSubPixelCount gammaTable gammaInverseTable' classVariableNames: '' poolDictionaries: 'FT2Constants FreeTypeCacheConstants' category: 'FreeType-Settings'! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 4/5/2007 08:17'! bitBltSubPixelAvailable "Answer true if the the subPixel combination rule is available, false otherwise. to test :- bitBltSubPixelAvailable := false. FreeTypeCache current removeAll. Smalltalk isMorphic ifTrue:[World restoreMorphicDisplay] " | form bitBlt color | bitBltSubPixelAvailable == nil ifFalse:[^bitBltSubPixelAvailable]. form := Form extent: 10@10 depth: 32. bitBlt := GrafPort toForm: form. bitBlt combinationRule: 41. bitBlt sourceForm: (Form extent: 5@5 depth: 32). bitBlt destOrigin: 1@1. bitBlt width: 5; height: 5. color := Color black asNontranslucentColor pixelValueForDepth: 32. [bitBlt copyBitsColor: (color bitAnd: 16rFFFFFF) alpha: (color bitAnd: 16rFF000000) >> 24 gammaTable: nil ungammaTable: nil] on: Error do:[:e | ^bitBltSubPixelAvailable := false]. #toDo. "need to check that rule 41 has done the right thing, and isn't someone elses new BitBlt rule" ^bitBltSubPixelAvailable := true ! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:04'! clearBitBltSubPixelAvailable bitBltSubPixelAvailable := nil.! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:03'! clearForceNonSubPixelCount forceNonSubPixelCount := nil. ! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:12'! defaultSubPixelFilterRatios ^#((1 3 5 3 1) (1 3 5 3 1) (1 3 5 3 1))! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:12'! forceAutoHinting ^forceAutoHinting ifNil:[forceAutoHinting := false]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:13'! forceNonSubPixelCount ^forceNonSubPixelCount ifNil:[forceNonSubPixelCount := 0]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:13'! forceNonSubPixelDuring: aBlock forceNonSubPixelCount ifNil:[forceNonSubPixelCount := 0]. forceNonSubPixelCount := forceNonSubPixelCount + 1. aBlock ensure:[forceNonSubPixelCount := forceNonSubPixelCount - 1]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:13'! gamma ^gamma ifNil:[gamma := 1.0]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:25'! gammaInverseTable ^gammaInverseTable! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:25'! gammaTable ^gammaTable! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'marcus.denker 11/29/2008 10:42'! glyphContrastPreferenceChanged " value between 1 and 100. 100 is highest contrast and maps to gamma 0.25 1 is lowest contrast and maps to gamma 2.22" | v g | v := (((Preferences GlyphContrast asNumber) min: 100) max: 1) asFloat. (v closeTo: 50.0) ifTrue:[g := 1.0] ifFalse:[ g := ((100 - v)+50/100.0) raisedTo: 2]. self setGamma: g. World restoreMorphicDisplay. ! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:13'! hinting ^hinting ifNil:[hinting := true]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:15'! hintingFlags | answer | answer := 0. self hinting ifTrue:[ self forceAutoHinting ifTrue:[answer := answer bitOr: 32 "forceAutoHinting"]. self lightHinting ifTrue:[answer := answer bitOr: LoadTargetLight]. self monoHinting ifTrue:[answer := answer bitOr: LoadTargetMono]. self lcdHinting ifTrue:[answer := answer bitOr: LoadTargetLCD]. self lcdvHinting ifTrue:[answer := answer bitOr: LoadTargetLCDV]] ifFalse:[answer := 2 "no hinting"]. ^answer! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'marcus.denker 11/29/2008 10:42'! hintingFullPreferenceChanged Preferences HintingFull ifTrue:[Preferences disable: #HintingNone; disable: #HintingLight; disable: #HintingNormal] ifFalse:[ (Preferences HintingNone or:[Preferences HintingLight or:[Preferences HintingNormal]]) ifFalse:[ "turn it back on again" ^Preferences enable: #HintingFull]]. monoHinting := Preferences HintingFull. lightHinting := Preferences HintingLight. hinting := monoHinting or:[lightHinting or:[Preferences HintingNormal]]. FreeTypeCache current removeAll. FreeTypeFont allSubInstances do:[:each | each clearCachedMetrics]. NewParagraph allSubInstances do:[:each | each composeAll]. World restoreMorphicDisplay. ! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'marcus.denker 11/29/2008 10:42'! hintingLightPreferenceChanged Preferences HintingLight ifTrue:[Preferences disable: #HintingFull; disable: #HintingNone; disable: #HintingNormal] ifFalse:[ (Preferences HintingFull or:[Preferences HintingNone or:[Preferences HintingNormal]]) ifFalse:[ "turn it back on again" ^Preferences enable: #HintingLight]]. monoHinting := Preferences HintingFull. lightHinting := Preferences HintingLight. hinting := monoHinting or:[lightHinting or:[Preferences HintingNormal]]. FreeTypeCache current removeAll. FreeTypeFont allSubInstances do:[:each | each clearCachedMetrics]. NewParagraph allSubInstances do:[:each | each composeAll]. World restoreMorphicDisplay. ! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'marcus.denker 11/29/2008 10:42'! hintingNonePreferenceChanged Preferences HintingNone ifTrue:[Preferences disable: #HintingFull; disable: #HintingLight; disable: #HintingNormal] ifFalse:[ (Preferences HintingFull or:[Preferences HintingLight or:[Preferences HintingNormal]]) ifFalse:[ "turn it back on again" ^Preferences enable: #HintingNone]]. monoHinting := Preferences HintingFull. lightHinting := Preferences HintingLight. hinting := monoHinting or:[lightHinting or:[Preferences HintingNormal]]. FreeTypeCache current removeAll. FreeTypeFont allSubInstances do:[:each | each clearCachedMetrics]. NewParagraph allSubInstances do:[:each | each composeAll]. World restoreMorphicDisplay.! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'marcus.denker 11/29/2008 10:43'! hintingNormalPreferenceChanged Preferences HintingNormal ifTrue:[Preferences disable: #HintingNone; disable: #HintingLight; disable: #HintingFull ] ifFalse:[ (Preferences HintingNone or:[Preferences HintingLight or:[Preferences HintingFull]]) ifFalse:[ "turn it back on again" ^Preferences enable: #HintingNormal]]. monoHinting := Preferences HintingFull. lightHinting := Preferences HintingLight. hinting := monoHinting or:[lightHinting or:[Preferences HintingNormal]]. FreeTypeCache current removeAll. FreeTypeFont allSubInstances do:[:each | each clearCachedMetrics]. NewParagraph allSubInstances do:[:each | each composeAll]. World restoreMorphicDisplay. ! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:15'! lcdHinting ^lcdHinting ifNil:[lcdHinting := false]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:15'! lcdvHinting ^lcdvHinting ifNil:[lcdvHinting := false]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:16'! lightHinting ^lightHinting ifNil:[lightHinting := true]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'marcus.denker 11/29/2008 10:43'! monitorTypeCRTPreferenceChanged Preferences MonitorTypeCRT ifTrue:[Preferences disable: #MonitorTypeLCD] ifFalse:[ Preferences MonitorTypeLCD ifFalse:[ "turn it back on again" ^Preferences enable: #MonitorTypeCRT]]. subPixelAntiAliasing := Preferences MonitorTypeLCD. World restoreMorphicDisplay. ! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'marcus.denker 11/25/2008 15:22'! monitorTypeLCDPreferenceChanged Preferences MonitorTypeLCD ifTrue:[Preferences disable: #MonitorTypeCRT] ifFalse:[ Preferences MonitorTypeCRT ifFalse:[ "turn it back on again" ^Preferences enable: #MonitorTypeLCD]]. subPixelAntiAliasing := Preferences MonitorTypeLCD. World restoreMorphicDisplay.! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:17'! monoHinting ^monoHinting ifNil:[monoHinting := false]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 4/2/2007 23:29'! pretendBitBltSubPixelUnavailableDuring: aBlock " For testing/profiling only. Answer true if the the subPixel combination rule is available, false otherwise. to test :- bitBltSubPixelAvailable := false. FreeTypeCache current removeAll. Smalltalk isMorphic ifTrue:[World restoreMorphicDisplay] " | old | old := bitBltSubPixelAvailable. [bitBltSubPixelAvailable := false. FreeTypeCache current removeAll. aBlock value. ] ensure:[ bitBltSubPixelAvailable := old. FreeTypeCache current removeAll.]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'marcus.denker 11/29/2008 10:41'! setGamma: aFloat (aFloat closeTo: self gamma) ifFalse:[ gamma := aFloat. (gamma closeTo: 1.0) ifTrue:[gammaTable := gammaInverseTable := nil] ifFalse:[ gammaTable := ByteArray new: 256. gammaInverseTable := ByteArray new: 256. 0 to: 255 do:[:i | | g ug | g := ((i / 255.0) raisedTo: (1.0/gamma)) * 255. ug := ((i / 255.0) raisedTo: gamma) * 255. g := (g rounded min: 255) max: 0 . ug := (ug rounded min: 255) max: 0 . gammaTable at: i + 1 put: g. gammaInverseTable at: i + 1 put: ug]]. World restoreMorphicDisplay]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'marcus.denker 11/29/2008 10:43'! setSubPixelFilter: ratiosArray "Set the subPixelFilters from ratiosArray. the ratiosArray can specify the red, green, and blue filter ratios separately. e.g. #((1 3 5 3 1) (1 4 7 4 1) (1 2 3 2 1)) or, as single set of ratios e.g. #(1 3 5 3 1)" | validArray newFilters | validArray := ratiosArray. (ratiosArray size = 5) ifTrue:[validArray := {ratiosArray. ratiosArray. ratiosArray}]. newFilters := self subPixelFiltersFromRatios: validArray. (newFilters = subPixelFilters) ifFalse:[ subPixelFilters := newFilters. FreeTypeCache current removeAllForType: FreeTypeCacheGlyphLCD. World restoreMorphicDisplay]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:20'! subPixelAntiAliasing self bitBltSubPixelAvailable ifFalse:[^false]. self forceNonSubPixelCount > 0 ifTrue:[^false]. ^subPixelAntiAliasing ifNil:[false]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:22'! subPixelFilters ^subPixelFilters ifNil:[subPixelFilters := self subPixelFiltersFromRatios: self defaultSubPixelFilterRatios]! ! !FreeTypeSettings methodsFor: 'accessing' stamp: 'tween 3/30/2007 18:22'! subPixelFiltersFromRatios: anArray "Convert the ratios in anArray to a similar array containing the filter proportions as floats. Example: if = #((1 3 5 3 1) (1 3 5 3 1) (1 3 5 3 1)) Then the answer is #(#(0.0769230769230769 0.2307692307692308 0.3846153846153846 0.2307692307692308 0.0769230769230769) #(0.0769230769230769 0.2307692307692308 0.3846153846153846 0.2307692307692308 0.0769230769230769) #(0.0769230769230769 0.2307692307692308 0.3846153846153846 0.2307692307692308 0.0769230769230769))" | r g b rRatios gRatios bRatios rsum gsum bsum rfilter gfilter bfilter blurR blurG blurB | r := "Color red luminance" 1.0 . g := "Color green luminance" 1.0 . b := "Color blue luminance"1.0 . blurR := anArray first. blurG := anArray second. blurB := anArray third. rRatios := blurR collect:[:i | r*i]. gRatios := blurG collect:[:i | g*i]. bRatios := blurB collect:[:i | b*i]. "rRatios := {g*blurR first . b*blurR second. r*blurR third. g*bl. b*blur*blur }. gRatios := {b*blur*blur. r*blur. g. b*blur. r*blur*blur}. bRatios := {r*blur*blur. g*blur. b. r*blur. g*blur*blur }." rsum := rRatios inject:0 into:[:t :i | t+i]. gsum := gRatios inject:0 into:[:t :i | t+i]. bsum := bRatios inject:0 into:[:t :i | t+i]. rfilter := rRatios collect:[:e | e / rsum]. gfilter := gRatios collect:[:e | e / gsum]. bfilter := bRatios collect:[:e | e / bsum]. ^{rfilter. gfilter. bfilter}! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeSettings class instanceVariableNames: 'current'! !FreeTypeSettings class methodsFor: 'class initialization' stamp: 'tween 8/31/2007 17:58'! initialize " self initialize " Smalltalk removeFromStartUpList: self. Smalltalk addToStartUpList: self . Smalltalk removeFromShutDownList: self. Smalltalk addToShutDownList: self. self initializePreferences! ! !FreeTypeSettings class methodsFor: 'class initialization' stamp: 'torsten.bergmann 3/25/2009 04:52'! initializePreferences "create preferences for all my settings if they are missing self initializePreferences " Preferences addBooleanPreference: #UpdateFontsAtImageStartup categories: {'FreeType'} default: true balloonHelp: 'Update font settings at image startup'. Preferences addBooleanPreference: #HintingFull categories: {'FreeType'} default: false balloonHelp: 'Changes glyph shapes so that their features are snapped to pixel boundaries. Glyphs are monochrome, with no anti-aliasing. This option changes the shapes the most.' projectLocal: false changeInformee: self changeSelector: #HintingFullPreferenceChanged. Preferences addBooleanPreference: #HintingNormal categories: {'FreeType'} default: false balloonHelp: 'Changes glyph shapes so that their features are snapped to pixel boundaries. Glyphs are anti-aliased' projectLocal: false changeInformee: self changeSelector: #HintingNormalPreferenceChanged. Preferences addBooleanPreference: #HintingLight categories: {'FreeType'} default: true balloonHelp: 'Changes glyph shapes so that their features are partially snapped to pixel boundaries. This option changes the shapes less than HintingFull, resulting in better shapes, but less contrast.' projectLocal: false changeInformee: self changeSelector: #HintingLightPreferenceChanged. Preferences addBooleanPreference: #HintingNone categories: {'FreeType'} default: false balloonHelp: 'Uses the original glyph shapes without snapping their features to pixel boundaries. This gives the best shapes, but with less contrast and more fuzziness.' projectLocal: false changeInformee: self changeSelector: #HintingNonePreferenceChanged. Preferences addPreference: #GlyphContrast categories: {'FreeType'} default: 50 balloonHelp: 'Change the contrast level for glyphs. This is an integer between 1 and 100. (the default value is 50)' projectLocal: false changeInformee: self changeSelector: #GlyphContrastPreferenceChanged viewRegistry: (Smalltalk at: #PreferenceViewRegistry ifPresent:[:c | c ofNumericPreferences]) . Preferences addPreference: #FreeTypeCacheSize categories: {'FreeType'} default: 5000 balloonHelp: 'The size of the cache in KBytes (default is 5000K)' projectLocal: false changeInformee: self changeSelector: #FreeTypeCacheSizePreferenceChanged viewRegistry: (Smalltalk at: #PreferenceViewRegistry ifPresent:[:c | c ofNumericPreferences]) ! ! !FreeTypeSettings class methodsFor: 'instance creation' stamp: 'tween 3/30/2007 17:54'! current current == nil ifFalse:[^current]. ^current := self new! ! !FreeTypeSettings class methodsFor: 'preferences notifications' stamp: 'tween 3/30/2007 19:06'! FreeTypeCacheSizePreferenceChanged FreeTypeCache current maximumSize: Preferences FreeTypeCacheSize * 1024 ! ! !FreeTypeSettings class methodsFor: 'preferences notifications' stamp: 'tween 3/30/2007 18:50'! GlyphContrastPreferenceChanged self current glyphContrastPreferenceChanged ! ! !FreeTypeSettings class methodsFor: 'preferences notifications' stamp: 'tween 3/30/2007 18:10'! HintingFullPreferenceChanged self current hintingFullPreferenceChanged ! ! !FreeTypeSettings class methodsFor: 'preferences notifications' stamp: 'tween 3/30/2007 18:10'! HintingLightPreferenceChanged self current hintingLightPreferenceChanged ! ! !FreeTypeSettings class methodsFor: 'preferences notifications' stamp: 'tween 3/30/2007 18:10'! HintingNonePreferenceChanged self current hintingNonePreferenceChanged ! ! !FreeTypeSettings class methodsFor: 'preferences notifications' stamp: 'tween 7/15/2007 22:35'! HintingNormalPreferenceChanged self current hintingNormalPreferenceChanged ! ! !FreeTypeSettings class methodsFor: 'preferences notifications' stamp: 'tween 3/30/2007 18:10'! MonitorTypeCRTPreferenceChanged self current monitorTypeCRTPreferenceChanged ! ! !FreeTypeSettings class methodsFor: 'preferences notifications' stamp: 'tween 3/30/2007 18:10'! MonitorTypeLCDPreferenceChanged self current monitorTypeLCDPreferenceChanged ! ! !FreeTypeSettings class methodsFor: 'shutdown' stamp: 'tween 8/31/2007 18:00'! shutDown: quitting self current clearBitBltSubPixelAvailable. self current clearForceNonSubPixelCount! ! !FreeTypeSettings class methodsFor: 'startup' stamp: 'tween 3/30/2007 18:03'! startUp: resuming resuming ifTrue:[ self current clearBitBltSubPixelAvailable; clearForceNonSubPixelCount]! ! FreeTypeGlyphRenderer subclass: #FreeTypeSubPixelAntiAliasedGlyphRenderer instanceVariableNames: '' classVariableNames: '' poolDictionaries: 'FT2Constants' category: 'FreeTypeSubPixelAntiAliasing-GlyphRendering'! !FreeTypeSubPixelAntiAliasedGlyphRenderer methodsFor: 'rendering' stamp: 'tween 4/4/2007 18:42'! filter: aGlyphForm "aGlyphForm should be 3x stretched 8 bit GlyphForm" | w h s answer rowstart bytes word littleEndian shift v a colorVal i prevG prevB r g b nextR nextG filters rfilter gfilter bfilter balR balG balB | "correctionFactor := 0.0 ." filters := FreeTypeSettings current subPixelFilters. rfilter := filters at: 1. gfilter := filters at: 2. bfilter := filters at: 3. bytes := aGlyphForm bits. w := aGlyphForm width. h := aGlyphForm height. answer := aGlyphForm class extent: ((aGlyphForm width / 3) ceiling + 2)@h depth: 32. answer offset: (aGlyphForm offset x / 3) rounded@(aGlyphForm offset y); advance: (aGlyphForm advance / 3) rounded; linearAdvance: aGlyphForm linearAdvance. s := w + 3 >> 2. littleEndian := aGlyphForm isLittleEndian. 0 to: h - 1 do: [:y | rowstart := (y * s)+1. prevG := prevB :=0. 0 to: w - 1 by: 3 do:[:x | 0 to: 2 do:[:subpixelindex | i := x + subpixelindex. word := bytes at: rowstart + (i//4). shift := -8* (littleEndian ifTrue:[i bitAnd: 3] ifFalse:[3-(i bitAnd: 3)]). v := (word bitShift: shift) bitAnd: 16rFF. subpixelindex = 0 ifTrue:[r := v]. subpixelindex = 1 ifTrue:[g := v]. subpixelindex = 2 ifTrue:[b := v]]. x >= (w-3) ifTrue:[nextR := nextG := 0] ifFalse:[ 0 to: 1 do:[:subpixelindex | i := x + 3 + subpixelindex. word := bytes at: rowstart + (i//4). shift := -8* (littleEndian ifTrue:[i bitAnd: 3] ifFalse:[3-(i bitAnd: 3)]). v := (word bitShift: shift) bitAnd: 16rFF. subpixelindex = 0 ifTrue:[nextR := v]. subpixelindex = 1 ifTrue:[nextG := v]]]. "balance r g b" balR := (prevG*(rfilter at: 1))+ (prevB*(rfilter at: 2))+ (r*(rfilter at: 3))+ (g*(rfilter at: 4))+ (b*(rfilter at: 5)). balG := (prevB*(gfilter at: 1))+ (r*(gfilter at: 2))+ (g*(gfilter at: 3))+ (b*(gfilter at: 4))+ (nextR*(gfilter at: 5)). balB := (r*(bfilter at: 1))+ (g*(bfilter at: 2))+ (b*(bfilter at: 3))+ (nextR*(bfilter at: 4))+ (nextG*(bfilter at: 5)). "luminance := (0.299*balR)+(0.587*balG)+(0.114*balB). balR := balR + ((luminance - balR)*correctionFactor). balG := balG + ((luminance - balG)*correctionFactor). balB := balB + ((luminance - balB)*correctionFactor)." balR := balR truncated. balR < 0 ifTrue:[balR := 0] ifFalse:[balR > 255 ifTrue:[balR := 255]]. balG := balG truncated. balG < 0 ifTrue:[balG := 0] ifFalse:[balG > 255 ifTrue:[balG := 255]]. balB := balB truncated. balB < 0 ifTrue:[balB := 0] ifFalse:[balB > 255 ifTrue:[balB := 255]]. a := balR + balG + balB > 0 ifTrue:[16rFF] ifFalse:[0]. colorVal := balB + (balG bitShift: 8) + (balR bitShift: 16) + (a bitShift: 24). answer bits integerAt: (y*answer width)+(x//3+1) put: colorVal. prevB := b. prevG := g. "remember the unbalanced values" ]]. ^answer! ! !FreeTypeSubPixelAntiAliasedGlyphRenderer methodsFor: 'rendering' stamp: 'michael.rueger 2/5/2009 17:03'! renderStretchedGlyph: aCharacter depth: depth subpixelPosition: sub font: aFreeTypeFont "Glyphs are either 1 or 8 bit deep. For 32 bpp we use 8 bits, otherwise 1" | em form glyph scaleX charCode slant extraWidth s offsetX offsetY synthBoldStrength boldExtra extraHeight hintingFlags flags face | charCode := aCharacter asUnicode asInteger. (aFreeTypeFont face charmaps includes:'unic') ifTrue:[ (aFreeTypeFont isSymbolFont and:[charCode >= 16r20 and: [charCode <= 16rFF ] ]) ifTrue:[charCode := charCode + 16rF000]] ifFalse:[ (aFreeTypeFont face charmaps includes:'armn') ifTrue:[ "select apple roman char map, and map character from unicode to mac encoding" aFreeTypeFont face setCharMap:'armn'. charCode := aCharacter unicodeToMacRoman asUnicode asInteger. "check this!!"]]. aCharacter < $ ifTrue: ["charCode := $ asUnicode asInteger" ^(GlyphForm extent: 0@0 depth: depth) advance: 0@0; linearAdvance: 0@0; offset:0@0; yourself ]. scaleX := 3. em := aFreeTypeFont pixelSize. [face := aFreeTypeFont face. face setPixelWidth: em height: em. hintingFlags := FreeTypeSettings current hintingFlags. flags := LoadNoBitmap bitOr:( LoadIgnoreTransform bitOr: hintingFlags). face loadCharacter:charCode flags: flags. ] on: FT2Error do:[:e | ^(GlyphForm extent: 0@0 depth: depth) advance: 0@0; linearAdvance: 0@0; offset:0@0; yourself]. glyph := face glyph. slant := aFreeTypeFont simulatedItalicSlant. synthBoldStrength := aFreeTypeFont simulatedBoldStrength. synthBoldStrength ~= 0 ifTrue:[face emboldenOutline: synthBoldStrength]. boldExtra := 4 * synthBoldStrength abs ceiling. face transformOutlineAngle: 0 scalePoint: scaleX@1 slant: slant. extraWidth := (glyph height * slant) abs ceiling. extraWidth := extraWidth + boldExtra. sub > 0 ifTrue:[ extraWidth := extraWidth + 3]. extraHeight := boldExtra. form := GlyphForm extent: ((glyph width + extraWidth "+ 6" + 1 + 2)*scaleX)@(glyph height +extraHeight + 1) depth: depth. s := (glyph height-glyph hBearingY) * slant. s := s sign * (s abs ceiling). offsetX := (glyph hBearingX negated + s + (boldExtra // 2) + 1) * scaleX . offsetY := glyph height - glyph hBearingY + (boldExtra//2). face translateOutlineBy: (offsetX+(sub*scaleX/64))@offsetY. face renderGlyphIntoForm: form. form offset: ((glyph hBearingX - s - 1 - (boldExtra // 2)) * scaleX)@ (glyph hBearingY + 1 + (boldExtra / 2) ceiling) negated. "When not hinting FreeType sets the advance to the truncated linearAdvance. The characters appear squashed together. Rounding is probably better, so we fix the advance here" aFreeTypeFont subPixelPositioned ifTrue:[ form advance: glyph roundedPixelLinearAdvance * (scaleX@1)] ifFalse:[ form advance: glyph advance x * scaleX@glyph advance y]. form linearAdvance: glyph linearAdvance. ^form! ! !FreeTypeSubPixelAntiAliasedGlyphRenderer methodsFor: 'rendering' stamp: 'tween 4/4/2007 18:43'! subGlyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub font: aFreeTypeFont | f | monoBoolean ifFalse:[ f := self renderStretchedGlyph: aCharacter depth: 8 subpixelPosition: sub font: aFreeTypeFont. f := self filter: f] ifTrue:[ f := self renderGlyph: aCharacter depth: 1 subpixelPosition: sub font: aFreeTypeFont. f := self fixBytesForMono: f. f := f asFormOfDepth: 32]. ^f! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! FreeTypeSubPixelAntiAliasedGlyphRenderer class instanceVariableNames: ''! !FreeTypeSubPixelAntiAliasedGlyphRenderer class methodsFor: 'class initialization' stamp: 'tween 4/4/2007 18:55'! initialize " self initialize " FreeTypeGlyphRenderer current: self new. Preferences addBooleanPreference: #MonitorTypeLCD categories: {'FreeType'} default: true balloonHelp: 'Choose this if you are using an LCD monitor.' projectLocal: false changeInformee: FreeTypeSettings changeSelector: #MonitorTypeLCDPreferenceChanged. Preferences addBooleanPreference: #MonitorTypeCRT categories: {'FreeType'} default: false balloonHelp: 'Choose this if you are using a CRT monitor (i.e. not LCD)' projectLocal: false changeInformee: FreeTypeSettings changeSelector: #MonitorTypeCRTPreferenceChanged. FreeTypeSettings MonitorTypeLCDPreferenceChanged! ! HierarchicalUrl subclass: #FtpUrl instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Network-Url'! !FtpUrl commentStamp: 'ls 6/15/2003 13:44' prior: 0! a reference to a file which may be downloaded by anonymous ftp . TODO: use the username and password, if specified ! !FtpUrl methodsFor: 'access' stamp: 'ls 7/24/1998 00:18'! pathString self path isEmpty ifTrue: [ ^'/' copy ]. ^String streamContents: [ :s | self path do: [ :p | s nextPut: $/. s nextPutAll: p ] ]! ! !FtpUrl methodsFor: 'downloading' stamp: 'PeterHugossonMiller 9/3/2009 01:34'! downloadUrl "Returns a http download url for the location defined by this url." | ans | ans := String new writeStream. ans nextPutAll: self schemeName. ans nextPutAll: '://'. ans nextPutAll: self authority. port ifNotNil: [ans nextPut: $:; print: port]. path do: [ :pathElem | ans nextPut: $/. ans nextPutAll: pathElem encodeForHTTP. ]. self query isNil ifFalse: [ ans nextPut: $?. ans nextPutAll: self query. ]. self fragment isNil ifFalse: [ ans nextPut: $#. ans nextPutAll: self fragment encodeForHTTP. ]. ^ans contents! ! !FtpUrl methodsFor: 'downloading' stamp: 'adrian_lienhard 7/18/2009 15:56'! retrieveContents "currently assumes directories end in /, and things that don't end in / are files. Also, doesn't handle errors real well...." | server contents pathString listing auth idx fileName serverName userName password | pathString := self pathString. pathString := pathString copyFrom: 2 to: pathString size. "remove the leading /" pathString last = $/ ifTrue:["directory?!!" fileName := nil. ] ifFalse:[ fileName := pathString copyFrom: (pathString lastIndexOf: $/)+1 to: pathString size. pathString := pathString copyFrom: 1 to: (pathString lastIndexOf: $/) - 1. ]. auth := self authority. idx := auth indexOf: $@. idx > 0 ifTrue:[ serverName := (auth copyFrom: idx+1 to: auth size). userName := (auth copyFrom: 1 to: idx-1). password := nil. ] ifFalse:[ serverName := auth. userName := 'anonymous'. password := 'user'. ]. server := ServerDirectory servers detect:[:s| s isTypeFTP and:[s server asLowercase = serverName asLowercase]] ifNone:[nil]. server ifNil:[ server := ServerDirectory new. server server: serverName. ] ifNotNil:[server := server copy reset]. server user: userName. password ifNotNil:[server password: password]. server directory: pathString. fileName == nil ifFalse:[ "a file" contents := (server getFileNamed: fileName). server sleep. ^MIMEDocument contentType: (MIMEDocument guessTypeFromName: self path last) content: contents]. "a directory?" listing := String streamContents: [ :stream | stream nextPutAll: '', self pathString, ''; cr. stream nextPutAll: '

Listing for ', self pathString, '

'; cr. stream nextPutAll: '