[squeak-dev] The Trunk: EToys-nice.44.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Jan 3 14:58:00 UTC 2010


Nicolas Cellier uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-nice.44.mcz

==================== Summary ====================

Name: EToys-nice.44
Author: nice
Time: 3 January 2010, 3:57:37 am
UUID: d634b781-9768-4932-aeb6-322c2e465599
Ancestors: EToys-nice.43

move #basicType to EToys
remove some #or:or: #and:and: sends

=============== Diff against EToys-nice.43 ===============

Item was added:
+ ----- Method: Point>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type of the receiver"
+ 
+ 	^ #Point!

Item was added:
+ ----- Method: TextMorph>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type I hold"
+ 
+ 	"Number String Boolean player collection sound color etc"
+ 	^ #Text!

Item was changed:
  ----- Method: TilePadMorph>>morphToDropFrom: (in category 'miscellaneous') -----
  morphToDropFrom: aMorph 
  	"Given a morph being carried by the hand, which the hand is about to drop, answer the actual morph to be deposited.  Normally this would be just the morph itself, but several unusual cases arise, which this method is designed to service."
  
  	| vwr |
  	(aMorph isKindOf: WatcherWrapper)
  		ifTrue: [^ aMorph getterTilesForDrop].
  	^ ((self type capitalized = #Graphic)  "Special-case requested by Alan 4/30/05"
+ 		and: [(aMorph isKindOf: TileMorph) and: [aMorph resultType = #Player]])
- 		and: [aMorph isKindOf: TileMorph] and: [aMorph resultType = #Player])
  			ifFalse:
  				[aMorph]
  			ifTrue:
  				[vwr := CategoryViewer new initializeFor: aMorph associatedPlayer categoryChoice: #basic.
  				vwr getterTilesFor: (Utilities getterSelectorFor: #graphic)  type: #Graphic]!

Item was added:
+ ----- Method: StringHolder>>openSyntaxView (in category '*eToys-tiles') -----
+ openSyntaxView
+ 	"Open a syntax view on the current method"
+ 
+ 	| class selector |
+ 
+ 	(selector := self selectedMessageName) ifNotNil: [
+ 		class := self selectedClassOrMetaClass.
+ 		SyntaxMorph testClass: class andMethod: selector.
+ 	]!

Item was added:
+ ----- Method: Object>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type of the receiver"
+ 
+ 	^ #Object!

Item was added:
+ ----- Method: Number>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type of the receiver"
+ 
+ 	^ #Number!

Item was changed:
  ----- Method: PhraseTileMorph>>morphToDropInPasteUp: (in category 'mouse') -----
  morphToDropInPasteUp: aPasteUp
  	"Answer the morph to drop in aPasteUp, given that the receiver is the putative droppee"
  
  	| actualObject itsSelector aScriptor pos aWatcher op |
  
  	((actualObject := self actualObject) isNil or: [actualObject costume isInWorld not]) ifTrue: [^ self].
  	self isCommand ifFalse:  "Can't expand to a scriptor, but maybe launch a watcher..."
+ 		[^ (Preferences dropProducesWatcher
+ 			and: [(#(unknown command) includes: self resultType) not
+ 			and: [(op := self operatorTile operatorOrExpression) notNil
+ 			and: [op numArgs = 0
+ 			and: [(Vocabulary gettersForbiddenFromWatchers includes: op) not]]]])
- 		[^ (Preferences dropProducesWatcher and: [(#(unknown command) includes: self resultType) not] and:
- 			[(op := self operatorTile operatorOrExpression) notNil] and: [op numArgs = 0] and: [(Vocabulary gettersForbiddenFromWatchers includes: op) not])
  			ifTrue:
  				[aWatcher := WatcherWrapper new fancyForPlayer: self associatedPlayer getter: op.
  				aWatcher position: self position]
  			ifFalse:
  				[self]].
  
  	self justGrabbedFromViewer ifFalse: [^ self].
  	actualObject assureUniClass.
  	itsSelector := self userScriptSelector.
  	pos := self position.
  	aScriptor := itsSelector isEmptyOrNil
  		ifFalse:
  			[actualObject scriptEditorFor: itsSelector]
  		ifTrue:
  			["It's a system-defined selector; construct an anonymous scriptor around it"
  			actualObject newScriptorAround: self].
  	aScriptor ifNil:[^self].
  	(self hasOwner: aScriptor) ifTrue:[
  		aScriptor fullBounds. "force layout"
  		aScriptor position: pos - self position.
  	] ifFalse:[
  		aScriptor position: self position.
  	].
  	^ aScriptor!

Item was changed:
+ ----- Method: Number>>newTileMorphRepresentative (in category '*eToys-tiles') -----
- ----- Method: Number>>newTileMorphRepresentative (in category '*eToys-printing') -----
  newTileMorphRepresentative
  	^ TileMorph new addArrows; setLiteral: self; addSuffixIfCan
  !

Item was changed:
+ ----- Method: Player>>basicType (in category '*eToys-tiles') -----
- ----- Method: Player>>basicType (in category 'testing') -----
  basicType
  	"Answer a symbol representing the inherent type of the receiver"
  
  	^ #Player!

Item was changed:
  ----- Method: Player>>offerViewerMenuFor:event: (in category 'misc') -----
  offerViewerMenuFor: aViewer event: evt
  	"Put up the Viewer menu on behalf of the receiver.  If the shift key is held down, put up the alternate menu. The menu omits the 'add a new variable' item when in eToyFriendly mode, as per request from teachers using Squeakland in 2003 once the button for adding a new variable was added to the viewer"
  
  	| aMenu aWorld  |
+ 	(evt notNil and: [evt shiftPressed and: [Preferences eToyFriendly not]]) ifTrue:[
- 	(evt notNil and: [evt shiftPressed] and: [Preferences eToyFriendly not]) ifTrue:[
  		^ self offerAlternateViewerMenuFor: aViewer event: evt
  	].
  
  	aWorld := aViewer world.
  	aMenu := MenuMorph new defaultTarget: self.
  	aMenu title: self externalName.
  	aMenu addStayUpItem.
  	self costume renderedMorph offerCostumeViewerMenu: aMenu.
  
  	Preferences eToyFriendly ifFalse: "exclude this from squeakland-like UI "
  		[aMenu add: 'add a new variable' translated target: self action: #addInstanceVariable.
  		aMenu balloonTextForLastItem: 'Add a new variable to this object and all of its siblings.  You will be asked to supply a name for it.' translated].
  
  	aMenu add: 'add a new script' translated target: aViewer action: #newPermanentScript.
  	aMenu balloonTextForLastItem: 'Add a new script that will work for this object and all of its siblings' translated.
  	aMenu addLine.
  	self hasCostumeThatIsAWorld ifFalse:[
  	
  	aMenu add: 'grab me' translated target: self selector: #grabPlayerIn: argument: aWorld.
  	
  	aMenu balloonTextForLastItem: 'This will actually pick up the object this Viewer is looking at, and hand it to you.  Click the (left) button to drop it' translated.
  	].
  
  	aMenu add: 'reveal me' translated target: self selector: #revealPlayerIn: argument: aWorld.
  	aMenu balloonTextForLastItem: 'If you have misplaced the object that this Viewer is looking at, use this item to (try to) make it visible' translated.
  
  	aMenu addLine.
  	aMenu add: 'tile representing me' translated action: #tearOffTileForSelf.
  	aMenu add: 'add search pane' translated target: aViewer action: #addSearchPane.
  	Preferences eToyFriendly ifFalse:[
  	
  	aMenu addLine.
  	
  	aMenu add: 'more...' translated target: self selector: #offerAlternateViewerMenuFor:event: argumentList: {aViewer. evt}.
  	].
  
  	aMenu popUpEvent: evt in: aWorld
  !

Item was added:
+ ----- Method: Text>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type I hold"
+ 
+ 	"Number String Boolean player collection sound color etc"
+ 	^ #Text!

Item was changed:
+ ----- Method: String>>newTileMorphRepresentative (in category '*eToys-tiles') -----
- ----- Method: String>>newTileMorphRepresentative (in category '*eToys-*Morphic') -----
  newTileMorphRepresentative
  	^ TileMorph new setLiteral: self;addSuffixIfCan!

Item was changed:
+ ----- Method: Boolean>>newTileMorphRepresentative (in category '*eToys-tiles') -----
- ----- Method: Boolean>>newTileMorphRepresentative (in category '*eToys-*morphic') -----
  newTileMorphRepresentative
  	^ TileMorph new addArrows; setLiteral: self
  !

Item was added:
+ ----- Method: Color>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type of the receiver"
+ 
+ 	^ #Color!

Item was added:
+ ----- Method: ImageMorph>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type I hold"
+ 
+ 	"Number String Boolean player collection sound color etc"
+ 	^ #Image!

Item was changed:
+ ----- Method: Color>>newTileMorphRepresentative (in category '*eToys-tiles') -----
- ----- Method: Color>>newTileMorphRepresentative (in category '*eToys-other') -----
  newTileMorphRepresentative
  	^ ColorTileMorph new colorSwatchColor: self!

Item was changed:
+ ----- Method: NumericReadoutTile>>basicType (in category '*eToys-tiles') -----
- ----- Method: NumericReadoutTile>>basicType (in category 'testing') -----
  basicType
  	"Answer a symbol representing the inherent type I hold"
  
  	"Number String Boolean player collection sound color etc"
  	^ #Number!

Item was added:
+ ----- Method: String>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type of the receiver"
+ 
+ 	"Number String Boolean player collection sound color etc"
+ 	^ #String!

Item was added:
+ ----- Method: Boolean>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type of the receiver"
+ 
+ 	^ #Boolean!

Item was changed:
  ----- Method: Player>>acceptableScriptNameFrom:forScriptCurrentlyNamed: (in category 'scripts-kernel') -----
  acceptableScriptNameFrom: originalString forScriptCurrentlyNamed: currentName
  	"Produce an acceptable script name, derived from the current name, for the receiver.  This method will always return a valid script name that will be suitable for use in the given situation, though you might not like its beauty sometimes."
  
  	| aString stemAndSuffix proscribed stem suffix withoutColon currentNumArgs withColon |
  	withoutColon := originalString copyWithoutAll: {$:. $ }.
  	(currentName notNil and: [(currentName copyWithout: $:) = withoutColon])
  		ifTrue:
  			[^ currentName].  "viz. no change; otherwise, the #respondsTo: check gets in the way"
  
  	currentNumArgs := currentName ifNil: [0] ifNotNil: [currentName numArgs].
  	aString := withoutColon asIdentifier: false.  "get an identifier starting with a lowercase letter"
  	stemAndSuffix := aString stemAndNumericSuffix.
  	proscribed := #(self super thisContext costume costumes dependents #true #false size).
  
  	stem := stemAndSuffix first.
  	suffix := stemAndSuffix last.
  	withoutColon := aString asSymbol.
  	withColon := (withoutColon, ':') asSymbol.
  
  	[(proscribed includes: withoutColon)
+ 		or: [(self respondsTo: withoutColon)
+ 		or: [(self respondsTo: withColon)
+ 		or:	[(Smalltalk includesKey: withoutColon)
+ 		or: [(Smalltalk includesKey: withColon)]]]]]
- 		or: [self respondsTo: withoutColon]
- 		or: [self respondsTo: withColon]
- 		or:	[Smalltalk includesKey: withoutColon]
- 		or: [Smalltalk includesKey: withColon]]
  	whileTrue:
  		[suffix := suffix + 1.
  		withoutColon := (stem, suffix printString) asSymbol.
  		withColon := (withoutColon, ':') asSymbol].
  
  	^ currentNumArgs = 0
  		ifTrue:
  			[withoutColon]
  		ifFalse:
  			[withColon]!

Item was added:
+ ----- Method: Object>>newTileMorphRepresentative (in category '*eToys-tiles') -----
+ newTileMorphRepresentative
+ 	^ TileMorph new setLiteral: self!

Item was changed:
+ ----- Method: UndefinedObject>>newTileMorphRepresentative (in category '*eToys-tiles') -----
- ----- Method: UndefinedObject>>newTileMorphRepresentative (in category '*eToys-printing') -----
  newTileMorphRepresentative
  	^ UndescribedTile new!

Item was added:
+ ----- Method: SketchMorph>>basicType (in category '*eToys-tiles') -----
+ basicType
+ 	"Answer a symbol representing the inherent type I hold"
+ 
+ 	"Number String Boolean player collection sound color etc"
+ 	^ #Image!




More information about the Squeak-dev mailing list