[etoys-dev] Etoys: Morphic-kfr.6.mcz

commits at source.squeak.org commits at source.squeak.org
Wed May 12 19:00:53 EDT 2010


Karl Ramberg uploaded a new version of Morphic to project Etoys:
http://source.squeak.org/etoys/Morphic-kfr.6.mcz

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

Name: Morphic-kfr.6
Author: kfr
Time: 13 May 2010, 12:59:15 am
UUID: 1e2dab4a-0285-2b45-ba5a-b00c7ac60ccb
Ancestors: Morphic-kfr.5

Remove classes from Morphic-Scripting (to Etoys-Scripting)

=============== Diff against Morphic-bf.4 ===============

Item was changed:
+ SystemOrganization addCategory: #'Morphic-Balloon'!
  SystemOrganization addCategory: #'Morphic-Basic'!
  SystemOrganization addCategory: #'Morphic-Books'!
  SystemOrganization addCategory: #'Morphic-Borders'!
  SystemOrganization addCategory: #'Morphic-Buttons'!
  SystemOrganization addCategory: #'Morphic-Components'!
  SystemOrganization addCategory: #'Morphic-Demo'!
  SystemOrganization addCategory: #'Morphic-Events'!
  SystemOrganization addCategory: #'Morphic-Experimental'!
+ SystemOrganization addCategory: #'Morphic-Explorer'!
  SystemOrganization addCategory: #'Morphic-Flaps'!
+ SystemOrganization addCategory: #'Morphic-Games'!
+ SystemOrganization addCategory: #'Morphic-Games-Chess'!
  SystemOrganization addCategory: #'Morphic-GeeMail'!
  SystemOrganization addCategory: #'Morphic-Kernel'!
  SystemOrganization addCategory: #'Morphic-Kernel-Tests'!
  SystemOrganization addCategory: #'Morphic-Layouts'!
  SystemOrganization addCategory: #'Morphic-Leds'!
+ SystemOrganization addCategory: #'Morphic-Mentoring'!
  SystemOrganization addCategory: #'Morphic-Menus'!
  SystemOrganization addCategory: #'Morphic-Models'!
  SystemOrganization addCategory: #'Morphic-Navigators'!
  SystemOrganization addCategory: #'Morphic-Outliner'!
- SystemOrganization addCategory: #'Morphic-PDA'!
  SystemOrganization addCategory: #'Morphic-Palettes'!
  SystemOrganization addCategory: #'Morphic-PartsBin'!
+ SystemOrganization addCategory: #'Morphic-PDA'!
+ SystemOrganization addCategory: #'Morphic-Pluggable Widgets'!
  SystemOrganization addCategory: #'Morphic-Postscript Canvases'!
  SystemOrganization addCategory: #'Morphic-Postscript Filters'!
  SystemOrganization addCategory: #'Morphic-Scripting'!
  SystemOrganization addCategory: #'Morphic-Scripting Support'!
  SystemOrganization addCategory: #'Morphic-Scripting Tiles'!
  SystemOrganization addCategory: #'Morphic-Stacks'!
  SystemOrganization addCategory: #'Morphic-Support'!
  SystemOrganization addCategory: #'Morphic-Text Support'!
  SystemOrganization addCategory: #'Morphic-Tile Scriptors'!
+ SystemOrganization addCategory: #'Morphic-TrueType'!
  SystemOrganization addCategory: #'Morphic-Undo'!
  SystemOrganization addCategory: #'Morphic-Widgets'!
  SystemOrganization addCategory: #'Morphic-Windows'!
  SystemOrganization addCategory: #'Morphic-Worlds'!
- SystemOrganization addCategory: #'Morphic-Games'!
- SystemOrganization addCategory: #'Morphic-Games-Chess'!
- SystemOrganization addCategory: #'Morphic-Mentoring'!
- SystemOrganization addCategory: #'Morphic-Explorer'!
- SystemOrganization addCategory: #'Morphic-Pluggable Widgets'!
- SystemOrganization addCategory: #'Morphic-Balloon'!
- SystemOrganization addCategory: #'Morphic-TrueType'!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>context:playerScripted:topEditor: (in category 'initialization') -----
- context: c playerScripted: p topEditor: t
- 
- 	context _ c.
- 	playerScripted _ p.
- 	topEditor _ t.
- !

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>literal: (in category 'reconstituting scripting tiles ') -----
- literal: sexp
- 
- 	| type n lit s xComp yComp |
- 	type _ sexp attributeAt: #type ifAbsent: [].
- 	type ifNotNil: [type _ type asSymbol].
- 	(type == #Player or: [type == #Patch]) ifTrue: [
- 		n _ sexp attributeAt: #value ifAbsent: [].
- 		n ifNotNil: [
- 			n = 'self' ifTrue: [^ TileMorph new setToReferTo: playerScripted].
- 			n = 'nil' ifTrue: [^ TileMorph new setToReferTo: playerScripted presenter standardPlayer].
- 			^ TileMorph new setToReferTo: (context at: n asSymbol)
- 		].
- 		^ TileMorph new setToReferTo: World presenter standardPlayer
- 	].
- 	type == #String ifTrue: [
- 		lit _ sexp attributeAt: #value.
- 		^ (TileMorph new setLiteral: lit).
- 	].
- 	type == #Point ifTrue: [
- 		lit _ sexp attributeAt: #value.
- 		xComp _ lit copyFrom: 1 to: (lit indexOf: $@) - 1.
- 		yComp _ lit copyFrom: (lit indexOf: $@) + 1 to: lit size.
- 		
- 		lit _ xComp asNumber at yComp asNumber.
- 		^ (TileMorph new setLiteral: lit).
- 	].
- 	type == #Color ifTrue: [
- 		lit _ Color readFrom: (sexp attributeAt: #value).
- 		^ ColorTileMorph new colorSwatchColor: lit.
- 	].
- 	type == #Boolean ifTrue: [
- 		lit _ (sexp attributeAt: #value) = 'true'.
- 		^ TileMorph new addArrows; setLiteral: lit
- 
- 	].
- 	type == #Sound ifTrue: [
- 		lit _ sexp attributeAt: #value.
- 		^ SoundTile new literal: lit.
- 	].
- 	type == #ScriptName ifTrue: [
- 		lit _ sexp attributeAt: #value.
- 		^ ScriptNameTile new literal: lit asSymbol.
- 	].
- 	(type == #TrailStyle or: [type == #ButtonPhase or: [type == #BorderStyle or: [type == #EdgeMode or: [type == #PatchDisplayMode]]]]) ifTrue: [
- 		lit _ sexp attributeAt: #value.
- 		s _ SymbolListTile new.
- 		s choices: (Vocabulary allStandardVocabularies at: type) choices dataType: type.
- 		^ s setLiteral: lit asSymbol; addArrows.
- 	].
- 	(type == #Object or: [type == #Number]) ifTrue: [
- 		lit _ Number readFrom: (sexp attributeAt: #value).
- 		^ (TileMorph new setLiteral: lit) addArrows.
- 	].
- 	(type == #Graphic) ifTrue: [
- 		lit _ (context at: (sexp attributeAt: #value) asSymbol).
- 		^ (GraphicTile new setLiteral: lit).
- 	].
- 	(type == #Menu) ifTrue: [
- 		lit _ sexp attributeAt: #value.
- 		^ (MenuTile new setLiteral: lit).
- 	].
- !

Item was removed:
- ----- Method: ViewerEntry>>defaultColor (in category 'initialization') -----
- defaultColor
- 	"answer the default color/fill style for the receiver"
- 	^ Color
- 		r: 1.0
- 		g: 0.985
- 		b: 0.985!

Item was removed:
- CompoundTileMorph subclass: #TimesRepeatMorph
- 	instanceVariableNames: 'numberOfTimesToRepeatPart whatToRepeatPart'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!
- 
- !TimesRepeatMorph commentStamp: 'sw 1/11/2006 22:05' prior: 0!
- A variant on the CompoundTileMorph that allows a section of code to be executed as many times as a numeric-control-field indicates.  For reasons of sharing and history, the CompoundTileMorph continues to be the one for test/yes/no, and this subclass disregards those three areas and adds two of its own.!

Item was removed:
- ----- Method: TimesRepeatTile>>targetPartFor: (in category 'initialization') -----
- targetPartFor: aMorph
- 	"Return the row into which the given morph should be inserted."
- 
- 	| centerY |
- 	centerY _ aMorph fullBounds center y.
- 	{self numberOfTimesToRepeatPart, whatToRepeatPart} do: [:m |
- 		(centerY <= m bounds bottom) ifTrue: [^ m]].
- 	^ noPart
- !

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>functionSend:with:with: (in category 'reconstituting scripting tiles ') -----
- functionSend: sexp with: rcvr with: realSel
- 
- 	| p |
- 	p _ FunctionTile new.
- 	p operator: realSel pad: rcvr.
- 	^ p.
- !

Item was removed:
- ----- Method: FunctionTile classSide>>defaultNameStemForInstances (in category 'scripting') -----
- defaultNameStemForInstances
- 	"Answer a good default name stem to use for names of instances"
- 
- 	^ 'Function' translatedNoop!

Item was removed:
- ----- Method: SyntaxTestMethods>>wordyTestMethod (in category 'as yet unclassified') -----
- wordyTestMethod
- 
- 	self selfWrittenAsMe = 1 ifTrue: [
- 		self selfWrittenAsMy size.
- 		self selfWrittenAsIll stop.
- 		self selfWrittenAsIm large.
- 		self selfWrittenAsThis helps.
- 	].
- !

Item was removed:
- ----- Method: ViewerEntry>>entryType (in category 'access') -----
- entryType
- 	^ self viewerRow entryType!

Item was removed:
- ----- Method: TimesRepeatMorph>>targetPartFor: (in category 'initialization') -----
- targetPartFor: aMorph
- 	"Return the row into which the given morph should be inserted."
- 
- 	| centerY |
- 	centerY _ aMorph fullBounds center y.
- 	{numberOfTimesToRepeatPart, whatToRepeatPart} do: [:m |
- 		(centerY <= m bounds bottom) ifTrue: [^ m]].
- 	^ noPart
- !

Item was removed:
- ----- Method: PhraseWrapperMorph>>isPartsBin (in category 'parts bin') -----
- isPartsBin
- 	^ true!

Item was removed:
- ----- Method: TimesRepeatTile>>numberOfTimesToRepeatPart (in category 'access') -----
- numberOfTimesToRepeatPart
- 	"Answer the TilePadMorph which holds the tiles defining the number of times to repeat"
- 
- 	^ timesRow timesPad !

Item was removed:
- ----- Method: FunctionNameTile>>operator:wording:helpString: (in category 'initialization') -----
- operator: anOperator wording: aWording helpString: aHelpString
- 	"Set the operator as per aString, and add up/down arrows"
- 
- 	type _ #operator.
- 	operatorOrExpression _ anOperator asSymbol.
- 	operatorOrExpression = #grouped
- 		ifTrue:
- 			[self line1: ' ']
- 		ifFalse:
- 			[self line1: aWording].
- 	self addArrows..
- 	aHelpString ifNotNil: [submorphs last setBalloonText: aHelpString]!

Item was removed:
- ----- Method: ScriptingTileHolder>>mouseDown: (in category 'mouse handling') -----
- mouseDown: evt
- 	"Handle a mouse-down event."
- 
- 	| actualTile |
- 	actualTile := submorphs at: 1 ifAbsent: [^ self delete].  "Not expected to happen."
- 	actualTile unlock.
- 	self topRendererOrSelf delete.
- 	evt hand grabMorph: actualTile!

Item was removed:
- ----- Method: PhraseTileForTimesRepeat>>mouseDown: (in category 'mouse') -----
- mouseDown: evt 
- 	"Handle a mouse-down on the receiver"
- 
- 	| guyToTake catViewer |
- 	guyToTake _ TimesRepeatTile new.
- 	guyToTake setNamePropertyTo: 'Repeat Tile' translated.
- 	guyToTake position: evt position + (-25 at 8).
- 
- 	guyToTake formerPosition: ActiveHand position.
- 	"self startSteppingSelector: #trackDropZones."
- 	(catViewer := self ownerThatIsA: CategoryViewer) ifNotNil:
- 		[guyToTake setProperty: #newPermanentPlayer toValue: catViewer scriptedPlayer.
- 		guyToTake setProperty: #newPermanentScript toValue: true].
- 	guyToTake justGrabbedFromViewer: true.
- 
- 	^ evt hand grabMorph: guyToTake
- !

Item was removed:
- ----- Method: FunctionTile>>parseNodeWith: (in category 'code generation') -----
- parseNodeWith: encoder
- 
- 	| phrase player costume sel |
- 	sel _ submorphs first operatorOrExpression.
- 	sel == #random ifFalse: [^ self basicParseNodeWith: encoder].
- 	phrase _ self outermostMorphThat: [:m| m isKindOf: PhraseTileMorph].
- 	phrase ifNil: [^ self basicParseNodeWith: encoder].
- 
- 	player _ phrase associatedPlayer.
- 	player ifNil: [^ self basicParseNodeWith: encoder].
- 
- 	costume _ player costume.
- 	costume ifNil: [^ self basicParseNodeWith: encoder].
- 
- 	(player isKindOf: KedamaExamplerPlayer) ifTrue: [
- 		^ self kedamaParseNodeWith: encoder actualObject: player costume renderedMorph kedamaWorld player].
- 
- 	(costume renderedMorph isMemberOf: KedamaMorph) ifTrue: [
- 		^ self kedamaParseNodeWith: encoder actualObject: self].
- 
- 	^ self basicParseNodeWith: encoder.
- !

Item was removed:
- ----- Method: FunctionTile>>operator:wording:helpString:pad: (in category 'initialization') -----
- operator: opSymbol wording: aWording  helpString: aHelpString pad: aTilePadMorph
- 	"Set the operator and pad.  Builds and adds the four submorphs of the receiver -- function-name, left-paren, argument-pad, right-paren."
- 
- 	argumentPad := aTilePadMorph.
- 	self removeAllMorphs.
- 	self vResizing: #shrinkWrap.
- 	functionNameTile _ FunctionNameTile new.
- 	functionNameTile operator: opSymbol wording: aWording helpString: aHelpString.
- 	self addMorphFront: functionNameTile.
- 	self addMorphBack: (ImageMorph new image: (ScriptingSystem formAtKey: #LeftParenthesis)).
- 	self addMorphBack: aTilePadMorph.
- 	self addMorphBack: (ImageMorph new image: (ScriptingSystem formAtKey: #RightParenthesis))!

Item was removed:
- ----- Method: ScriptingTileHolder>>fixLayout (in category 'initialization') -----
- fixLayout
- 
- 	self allMorphsDo: [:m | m fixLayoutOfSubmorphs].
- !

Item was removed:
- ----- Method: ViewerEntry>>userSlotInformation (in category 'slot') -----
- userSlotInformation
- 	"If the receiver represents a user-defined slot, then return its info; if not, retun nil"
- 	| aSlotName info |
- 	((self entryType == #systemSlot) or: [self entryType == #userSlot])
- 		ifFalse:
- 			[^ nil].
- 	aSlotName _ self slotName.
- 	^ ((info _ self playerBearingCode slotInfo) includesKey: aSlotName)
- 		ifTrue:
- 			[info at: aSlotName]
- 		ifFalse:
- 			[nil]!

Item was removed:
- AlignmentMorph subclass: #TimesRow
- 	instanceVariableNames: 'timesPad'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!
- 
- !TimesRow commentStamp: 'sw 6/14/2007 19:15' prior: 0!
- A custom alignment morph that holds the "times' portion of a Times/Repeat complex!

Item was removed:
- ----- Method: ViewerEntry>>playerBearingCode (in category 'access') -----
- playerBearingCode
- 	^ owner owner scriptedPlayer!

Item was removed:
- ----- Method: PhraseTileForTest>>mouseDown: (in category 'mouse') -----
- mouseDown: evt 
- 	"Handle a mouse-down on the receiver"
- 
- 	| guyToTake catViewer |
- 	guyToTake _ CompoundTileMorph new.
- 	guyToTake setNamePropertyTo: 'TestTile' translated.
- 	guyToTake position: evt position + (-25 at 8).
- 
- 	guyToTake formerPosition: ActiveHand position.
- 	"self startSteppingSelector: #trackDropZones."
- 	(catViewer := self ownerThatIsA: CategoryViewer) ifNotNil:
- 		[guyToTake setProperty: #newPermanentPlayer toValue: catViewer scriptedPlayer.
- 		guyToTake setProperty: #newPermanentScript toValue: true].
- 	guyToTake justGrabbedFromViewer: true.
- 
- 	^ evt hand grabMorph: guyToTake
- !

Item was removed:
- ----- Method: FunctionNameTile>>removeFunction (in category 'menu commands') -----
- removeFunction
- 	"Remove the function-call... this is forwarded to owner."
- 
- 	^ owner removeFunction!

Item was removed:
- ----- Method: FunctionTile>>replaceSubmorph:by: (in category 'initialization') -----
- replaceSubmorph: existingMorph by: newMorph
- 	"Replace a submorph by a different morph.  If it's my pad, fix up my argumentPad inst var."
- 
- 	super replaceSubmorph: existingMorph by: newMorph.
- 	(newMorph isKindOf: TilePadMorph) ifTrue: [argumentPad := newMorph].
- !

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>context:playerScripted: (in category 'initialization') -----
- context: c playerScripted: p
- 
- 	context _ c.
- 	playerScripted _ p.
- !

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>specialSend:with:with: (in category 'reconstituting scripting tiles ') -----
- specialSend: sexp with: rcvr with: realSel
- 
- 	| p val |
- 	sexp elements size > 2 ifTrue: [
- 		val _ self fromSexp: sexp elements third.
- 	].
- 	realSel == #color:sees: ifTrue: [
- 		p _  PhraseTileMorph new 
- 				setOperator: #+
- 				type: #Boolean
- 				rcvrType: #Player
- 				argType: #Color.	"temp dummy"
- 		p justGrabbedFromViewer: false.
- 		p submorphs first addMorph: rcvr.
- 		p submorphs second delete.
- 		p addMorph: (ColorSeerTile new showPalette: false; colorSwatchColor: (val colorSwatch color)) behind: p submorphs first.
- 		p submorphs last setType: (sexp elements fourth attributeAt: #type ifAbsent: ['Number']) asSymbol.
- 		p submorphs last addMorph: (self fromSexp: sexp elements fourth).
- 		^ p.
- 	].
- !

Item was removed:
- ----- Method: CommandTilesMorph>>tileRows (in category 'miscellaneous') -----
- tileRows
- 
- 	^ Array with: self submorphs!

Item was removed:
- ----- Method: ViewerRow>>elementSymbol (in category 'access') -----
- elementSymbol
- 	^ elementSymbol!

Item was removed:
- CompoundTileMorph subclass: #TimesRepeatTile
- 	instanceVariableNames: 'timesRow whatToRepeatPart'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!
- 
- !TimesRepeatTile commentStamp: 'sw 6/15/2007 18:39' prior: 0!
- A variant on the CompoundTileMorph that allows a section of code to be executed as many times as a numeric-control-field indicates.  For reasons of sharing and history, the CompoundTileMorph continues to be the one for test/yes/no, and this subclass disregards those three areas and adds two of its own.  An associated class is the TimesRow -- see its class comment.!

Item was removed:
- ----- Method: FunctionTile>>rowOfRightTypeFor:forActor: (in category 'dropping/grabbing') -----
- rowOfRightTypeFor: aLayoutMorph forActor: aPlayer
- 	"Answer a phrase of the right type for the putative container"
- 
- 	| aTemporaryViewer aPhrase |
- 	aLayoutMorph demandsBoolean ifTrue:
- 		[aTemporaryViewer _ CategoryViewer new invisiblySetPlayer: aPlayer.
- 		aPhrase _ aTemporaryViewer booleanPhraseFromPhrase: self.
- 		aPhrase justGrabbedFromViewer: false.
- 		^ aPhrase].
- 	^ self!

Item was removed:
- ----- Method: ScriptingTileHolder>>unhibernate (in category 'initialization') -----
- unhibernate
- 
- 	self fixLayout.
- !

Item was removed:
- ----- Method: PhraseWrapperMorph>>repelsMorph:event: (in category 'dropping/grabbing') -----
- repelsMorph: aMorph event: ev
- 	^ (aMorph isKindOf: PhraseTileMorph) or:
- 		[aMorph hasProperty: #newPermanentScript]!

Item was removed:
- ----- Method: TimesRow>>timesPad (in category 'accessing') -----
- timesPad
- 	"Answer the TilePadMorph at the top of the tile tree for the times part."
- 
- 	^ timesPad!

Item was removed:
- ----- Method: TimesRepeatMorph>>labelMorphs (in category 'access') -----
- labelMorphs
- 
- 	| w |
- 	w := WriteStream on: (Array new: 3).
- 	w nextPut: self submorphs second submorphs first submorphs first.
- 	w nextPut: self submorphs second submorphs first submorphs fourth.
- 	w nextPut: self submorphs second submorphs third submorphs second.
- 	^ w contents.
- !

Item was removed:
- ----- Method: TimesRepeatTile>>labelMorphs (in category 'access') -----
- labelMorphs
- 	"Answer a list of the StringMorphs that constitute the user-visible labels in the receiver's interior -- in this case, the StringMorphs showing the words Repeat, times, and Do."
- 
- 	| w |
- 	w := WriteStream on: (Array new: 3).
- 	w nextPut: self submorphs second submorphs first submorphs first.
- 	w nextPut: self submorphs second submorphs first submorphs fourth.
- 	w nextPut: self submorphs second submorphs third submorphs second.
- 	^ w contents
- 
- "
- TimesRepeatTile new labelMorphs collect: [:m | m contents]
- "
- !

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>send: (in category 'reconstituting scripting tiles ') -----
- send: sexp
- 
- 	| rcvr type selNode realSel val p argType |
- 	rcvr _ self fromSexp: sexp elements second.
- 	type _ sexp attributeAt: #type ifAbsent: ['#Player'].
- 	selNode _ sexp elements first.
- 	realSel _ selNode attributeAt: #getter ifAbsent: [].
- 	realSel ifNotNil: [
- 		realSel _ Utilities getterSelectorFor: realSel.
- 		(rcvr isMemberOf: PhraseTileMorph) ifFalse: [rcvr bePossessive].
- 	] ifNil: [
- 		realSel _ (selNode attributeAt: #selector) asSymbol.
- 		"realSel ifNil: [self error: '']."
- 	].
- 	(#(getAngleTo: bounceOn: getDistanceTo: getPatchValueIn: getTurtleOf: getUphillIn: getRedComponentIn: getGreenComponentIn: getBlueComponentIn:) includes: realSel) ifTrue: [
- 		^ self specialKedamaSend: sexp with: rcvr with: realSel
- 	].
- 	(#(color:sees:) includes: realSel) ifTrue: [
- 		^ self specialSend: sexp with: rcvr with: realSel
- 	].
- 	((ScriptingSystem tableOfNumericFunctions collect: [:e | e second]) includes: realSel) ifTrue: [
- 		^ self functionSend: sexp with: rcvr with: realSel
- 	].
- 
- 	p _ PhraseTileMorph new
- 			setOperator: realSel
- 				type: type asSymbol
- 				rcvrType: #Player
- 				argType: #Number.
- 	p justGrabbedFromViewer: false.
- 	p submorphs first addMorph: rcvr.
- 	p submorphs first setType: (sexp elements second attributeAt: #type ifAbsent: ['Number']) asSymbol.
- 	sexp elements size = 2 ifTrue: [
- 		(p resultType == #Number and: [p submorphs second isMemberOf: TileMorph]) ifTrue: [
- 			p submorphs second addSuffixArrow.
- 		].
- 	].
- 	sexp elements size > 2 ifTrue: [
- 		val _ self fromSexp: sexp elements third.
- 		argType _ (sexp elements third attributeAt: #type ifAbsent: ['Number']) asSymbol.
- 		p submorphs third setType: argType.
- 		p submorphs third addMorph: val.
- 		(argType == #Number and: [val isMemberOf: TileMorph]) ifTrue: [val addSuffixArrow.
- 			(#(#+ #- #* #/ #'//' #'\\' #max: #min: #< #'<=' #= #'~=' #> #'>=' #isDivisibleBy:) includes: realSel) ifFalse: [p submorphs second addRetractArrowAnyway].
- 		].
- 	].
- 	^ p.
- !

Item was removed:
- ----- Method: FunctionTile>>initialize (in category 'initialization') -----
- initialize
- 	"initialize the state of the receiver"
- 
- 	super initialize.
- 	type := #function.
- 	self minHeight: 30; vResizing: #spaceFill; borderWidth: 0!

Item was removed:
- ----- Method: FunctionTile>>convertPrecedenceInParseNode:with: (in category 'code generation') -----
- convertPrecedenceInParseNode: message with: encoder
- 
- 	| e r w list |
- 	w _ WriteStream on: (Array new: 3).
- 	message receiver eToysExpFlattenOn: w.
- 	list _ w contents.
- 	e _ EToyExpressionTransformer2 new newNodeFromList: list encoder: encoder.
- 	r _ e transform.
- 	message receiver: r.
- 	^ message.
- !

Item was removed:
- ----- Method: FunctionTile classSide>>randomNumberTile (in category 'scripting') -----
- randomNumberTile
- 	"Answer a newly conjured-up random-number tile, suitable for handing to the user."
- 
- 	| functionPhrase argTile aPad |
- 	functionPhrase _ FunctionTile new.
- 	argTile := (Vocabulary vocabularyNamed: 'Number') defaultArgumentTile.
- 	aPad := TilePadMorph new setType: #Number.
- 	aPad addMorphBack: argTile.
- 	functionPhrase operator: #random pad: aPad.
- 	^ functionPhrase
- 
- 
- "
- FunctionTile randomNumberTile openInHand
- "!

Item was removed:
- ----- Method: ViewerEntry>>codePaneMenu:shifted: (in category 'menu') -----
- codePaneMenu: aMenu shifted: shifted
- 	^ aMenu 
- 		labels: 'menu
- eventually
- will
- be
- useful'
- 		lines: #(1)
- 		selections: #(beep flash beep flash beep)!

Item was removed:
- ----- Method: FunctionTile>>basicParseNodeWith: (in category 'code generation') -----
- basicParseNodeWith: encoder
- 	"Answer a message node for the receiver."
- 
- 	| sel rec ret |
- 	sel _ submorphs first operatorOrExpression.
- 	rec _ submorphs third parseNodeWith: encoder.
- 	ret _ MessageNode new
- 				receiver: rec
- 				selector: sel
- 				arguments: #()
- 				precedence: (sel precedence)
- 				from: encoder
- 				sourceRange: nil.
- 	^ self convertPrecedenceInParseNode: ret with: encoder.
- !

Item was removed:
- ----- Method: SyntaxTestMethods>>st76LeftArrowTest: (in category 'as yet unclassified') -----
- st76LeftArrowTest: foo
- 
- 	foo contentsGetz: foo contents asUppercase
- 	
- 	!

Item was removed:
- ----- Method: ViewerEntry>>slotName (in category 'slot') -----
- slotName
- 	"Assuming the receiver represents a slot, return its name"
- 
- 	^  self viewerRow elementSymbol!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>condition: (in category 'reconstituting scripting tiles ') -----
- condition: sexp
- 
- 	| p testPart yesPart noPart n |
- 	testPart _ self fromSexp: (sexp elements first).
- 	yesPart _ self fromSexp: (sexp elements second).
- 	noPart _ self fromSexp: (sexp elements third).
- 
- 	p _ CompoundTileMorph new.
- 	testPart = #() ifFalse: [
- 		p submorphs first submorphs last addNewRow addMorph: testPart.
- 	].
- 
- 	yesPart do: [:e |
- 		n _ p submorphs second submorphs last addNewRow.
- 		n addMorph: e.
- 	].
- 	noPart do: [:e |
- 		n _ p submorphs third submorphs last addNewRow.
- 		n addMorph: e.
- 	].
- 	^ p.
- !

Item was removed:
- TileMorph subclass: #FunctionTile
- 	instanceVariableNames: 'functionNameTile argumentPad'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!
- 
- !FunctionTile commentStamp: 'sw 6/10/2007 03:41' prior: 0!
- A scripting tile consisting of a function-name and an argument pad, and representing a call to a numeric function of a single argument.!

Item was removed:
- ----- Method: PhraseTileForTimesRepeat>>setupCostume (in category 'initialization') -----
- setupCostume
- 	"Set up the details that make up the receiver's appearance."
- 
- 	| stringMorph |
- 	stringMorph _ StringMorph new contents: 'Repeat' translated.
- 	stringMorph name: 'Repeat' translated.
- 	stringMorph font: Preferences standardEToysFont.
- 	self addMorphBack: stringMorph.
- 	self addMorphBack: (Morph new color: color;
- 			 extent: 15 @ 5).
- 
- 	stringMorph _ StringMorph new contents: 'Times' translated.
- 	stringMorph name: 'Times' translated.
- 	stringMorph font: Preferences standardEToysFont.
- 	self addMorphBack: stringMorph.
- 	self addMorphBack: (Morph new color: color;
- 			 extent: 15 @ 5).
- !

Item was removed:
- ----- Method: SyntaxTestMethods>>doAndCollect (in category 'as yet unclassified') -----
- doAndCollect
- 
- 	self do: [ :j | j isEmpty ifFalse: [j size]].
- 	self collect: [ :each | each asString withBlanksTrimmed].
- 	!

Item was removed:
- ----- Method: FunctionTile>>convertPrecedenceOfArgsInParseNode:with: (in category 'code generation') -----
- convertPrecedenceOfArgsInParseNode: message with: encoder
- 
- 	| e r w list |
- 	message arguments size > 0 ifTrue: [
- 		w _ WriteStream on: (Array new: 3).
- 		message arguments first  eToysExpFlattenOn: w.
- 		list _ w contents.
- 		e _ EToyExpressionTransformer2 new newNodeFromList: list encoder: encoder.
- 		r _ e transform.
- 		message arguments at: 1 put: r.
- 		^ message.
- 	] ifFalse: [
- 		^ message.
- 	].
- !

Item was removed:
- ----- Method: TimesRepeatTile>>sissComeFullyUpOnReloadFrom:to: (in category 'code generation') -----
- sissComeFullyUpOnReloadFrom: from to: to
- 
- 	whatToRepeatPart borderWidth: 0; layoutInset: 0; hResizing: #spaceFill;
- 		vResizing: #shrinkWrap;
- 		color: Color transparent;
- 		setNameTo: 'Script to repeat'.!

Item was removed:
- ----- Method: TimesRepeatTile>>storeCodeOn:indent: (in category 'code generation') -----
- storeCodeOn: aStream indent: tabCount
- 	"Store code representing the receiver on the stream, obeying the tab state."
- 
- 	aStream nextPutAll: '(('.
- 	self numberOfTimesToRepeatPart submorphs
- 		ifEmpty:
- 			[aStream nextPutAll: '0']
- 		ifNotEmpty:
- 			[self numberOfTimesToRepeatPart storeCodeOn: aStream indent: tabCount + 2].
- 	aStream nextPutAll: ' ) asInteger max: 0) timesRepeat:'.
- 	tabCount + 1 timesRepeat: [aStream tab].
- 	aStream nextPutAll: '['; cr.
- 	self storeCodeBlockFor: whatToRepeatPart on: aStream indent: tabCount + 2.
- 	aStream nextPut: $].
- !

Item was removed:
- ----- Method: ViewerEntry>>viewerRow (in category 'access') -----
- viewerRow
- 	"Answer the ViewerRow object, that contains the controls and the phraseTile"
- 	^ submorphs first!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>loop: (in category 'reconstituting scripting tiles ') -----
- loop: sexp
- 	"Answer a TimesRepeatTile derived from the s-expression provided."
- 
- 	| p test body whatToRepeatPart numberOfTimesToRepeatPart |
- 	"You can think of different loops, but for current Etoys, there is only one kind."
- 	"initial _ sexp elements detect: [:e | e keyword == #initial] ifNone: [nil].
- 	increment _ sexp elements detect: [:e | e keyword == #increment] ifNone: [nil]."
- 	test _ sexp elements detect: [:e | e keyword == #test] ifNone: [nil].
- 	body _ sexp elements detect: [:e | e keyword == #sequence] ifNone: [nil].
- 
- 	test _ self fromSexp: test elements first.
- 
- 	body _ self fromSexp: body.
- 	p _ TimesRepeatTile new.
- 	numberOfTimesToRepeatPart _ p numberOfTimesToRepeatPart.
- 	numberOfTimesToRepeatPart removeAllMorphs; addMorph: test.
- 	whatToRepeatPart _ p instVarNamed: 'whatToRepeatPart'.
- 	body do: [:b |
- 		whatToRepeatPart addNewRow addMorph: b.
- 	].
- 	^ p.
- !

Item was removed:
- ----- Method: FunctionNameTile>>storeCodeOn:indent: (in category 'code generation') -----
- storeCodeOn: aStream indent: tabCount 
- 	"Store the receiver's code on the stream, honoring indentation."
- 
- 	operatorOrExpression = #grouped
- 		ifTrue:
- 			[aStream nextPutAll: ' yourself']
- 		ifFalse:
- 			[super storeCodeOn: aStream indent: tabCount]!

Item was removed:
- ----- Method: PhraseTileForTest>>setupCostume (in category 'as yet unclassified') -----
- setupCostume
- 
- 	| stringMorph |
- 	stringMorph _ StringMorph new contents: 'Test' translated.
- 	stringMorph name: 'Test' translated.
- 	stringMorph font: Preferences standardEToysFont.
- 	self addMorphBack: stringMorph.
- 	self addMorphBack: (Morph new color: color;
- 			 extent: 15 @ 5).
- 
- 	stringMorph _ StringMorph new contents: 'Yes' translated.
- 	stringMorph name: 'Yes' translated.
- 	stringMorph font: Preferences standardEToysFont.
- 	self addMorphBack: stringMorph.
- 	self addMorphBack: (Morph new color: color;
- 			 extent: 15 @ 5).
- 
- 	stringMorph _ StringMorph new contents: 'No' translated.
- 	stringMorph name: 'No' translated.
- 	stringMorph font: Preferences standardEToysFont.
- 	self addMorphBack: stringMorph.
- 	self addMorphBack: (Morph new color: color;
- 			 extent: 15 @ 5).
- !

Item was removed:
- ----- Method: SyntaxTestMethods>>altStyleTester (in category 'as yet unclassified') -----
- altStyleTester
- 
- 	self doFirstThatWorks
- 		if: [self = 1] do: [self + 1];
- 		if: [self = 2] do: [self + 2];
- 		if: [self = 3] do: [self + 3];
- 		if: [self = 4] do: [self + 4];
- 		if: [true] do: [self + 5]
- 	
- 	!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>specialKedamaSend:with:with: (in category 'reconstituting scripting tiles ') -----
- specialKedamaSend: sexp with: rcvr with: realSel
- 
- 	| p val |
- 	val _ self fromSexp: sexp elements third.
- 	p _ self phraseForSpecialKedamaSend: realSel.
- 	p justGrabbedFromViewer: false.
- 	p submorphs first addMorph: rcvr.
- 	p submorphs second setArgumentDefaultTo: val actualObject.
- 	^ p
- !

Item was removed:
- PhraseTileMorph subclass: #PhraseTileForTimesRepeat
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!
- 
- !PhraseTileForTimesRepeat commentStamp: 'sw 12/19/2006 18:15' prior: 0!
- A place-holder for a Times-Repeat complex of etoy tiles.  Used in a Viewer; when the user drags one of these, he ends up with a fully-instantiated Times/Repeat complex of tiles in his hand; if he drops such a group on the desktop, a new script is created for the object associated with the Viewer in question, with the Times/Repeat as its initial contents.!

Item was removed:
- AlignmentMorph subclass: #PhraseWrapperMorph
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting'!
- 
- !PhraseWrapperMorph commentStamp: '<historical>' prior: 0!
- An alignment morph designed for use in scripting Viewers; it wraps a set of phrases in a category viewer, and repels attempts to drop phrases upon it.!

Item was removed:
- PhraseTileMorph subclass: #PhraseTileForTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!

Item was removed:
- ----- Method: TimesRow>>replaceSubmorph:by: (in category 'retract-arrow processing') -----
- replaceSubmorph: existingMorph by: newMorph
- 	"Replace a submorph by a different morph. Fix up my  inst vars as appropriate."
- 
- 	super replaceSubmorph: existingMorph by: newMorph.
- 	(newMorph isKindOf: TilePadMorph)
- 		ifTrue:
- 			[timesPad := newMorph]
- !

Item was removed:
- ----- Method: TimesRepeatMorph>>storeCodeOn:indent: (in category 'code generation') -----
- storeCodeOn: aStream indent: tabCount
- 	"Store code representing the receiver on the stream, obeying the tab state."
- 
- 	aStream nextPutAll: '(('.
- 	numberOfTimesToRepeatPart submorphs
- 		ifEmpty:
- 			[aStream nextPutAll: '0']
- 		ifNotEmpty:
- 			[numberOfTimesToRepeatPart storeCodeOn: aStream indent: tabCount + 2].
- 	aStream nextPutAll: ' ) asInteger max: 0) timesRepeat:'.
- 	tabCount + 1 timesRepeat: [aStream tab].
- 	aStream nextPutAll: '['; cr.
- 	self storeCodeBlockFor: whatToRepeatPart on: aStream indent: tabCount + 2.
- 	aStream nextPut: $].
- !

Item was removed:
- ----- Method: ScriptingTileHolder classSide>>around: (in category 'instance creation') -----
- around: aTile
- 	"Answer a new instance of the receiver, surrounding the given tile."
- 
- 	^ self new around: aTile!

Item was removed:
- ----- Method: ScriptingTileHolder>>initialize (in category 'initialization') -----
- initialize
- 	"initialize the state of the receiver"
- 
- 	super initialize.
- 	self hResizing: #shrinkWrap;
- 		vResizing: #shrinkWrap;
- 		borderWidth: 3;
- 		borderColor: Color green muchDarker;
- 		cellInset: 0; layoutInset: 0!

Item was removed:
- ----- Method: PhraseTileForTimesRepeat>>initialize (in category 'initialization') -----
- initialize
- 	"Initialize the receiver."
- 
- 	super initialize.
- 	self color: Color orange muchLighter.
- 	self
- 		hResizing: #shrinkWrap;
- 		vResizing: #shrinkWrap;
- 		borderWidth: 1;
- 		borderColor: ScriptingSystem standardTileBorderColor.
- 	self setupCostume
- !

Item was removed:
- ----- Method: ScriptingTileHolder>>localeChanged (in category 'initialization') -----
- localeChanged
- 
- 	self fixLayout.
- !

Item was removed:
- ----- Method: TimesRepeatTile>>sexpWith: (in category 'code generation') -----
- sexpWith: dictionary
- 	"Answer an SExpElement representing the receiver."
- 
- 	| n elements e |
- 	n _ SExpElement keyword: #loop.
- 	n attributeAt: #type put: 'repeat'.
- 	elements _ WriteStream on: (Array new: 3).
- 	e _ SExpElement keyword: #initial.
- 	e elements: (Array with: ((SExpElement keyword: #literal) attributeAt: #value put: '1'; yourself)).
- 	elements nextPut: e.
- 	e _ SExpElement keyword: #increment.
- 	e elements: (Array with: ((SExpElement keyword: #literal) attributeAt: #value put: '1'; yourself)).
- 	elements nextPut: e.
- 
- 	e _ SExpElement keyword: #test.
- 	self numberOfTimesToRepeatPart submorphs
- 		ifEmpty:
- 			[e elements: (Array with: ((SExpElement keyword: #literal) attributeAt: #value put: '0'; yourself))]
- 		ifNotEmpty:
- 			[e elements: (Array with: (self numberOfTimesToRepeatPart sexpWith: dictionary))].
- 
- 	elements nextPut: e.
- 	
- 	elements nextPut: (self sexpBlockFor: whatToRepeatPart with: dictionary).
- 	n elements: elements contents.
- 	^ n.
- 
- !

Item was removed:
- AlignmentMorph subclass: #ViewerEntry
- 	instanceVariableNames: 'helpPane'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>script: (in category 'reconstituting scripting tiles ') -----
- script: sexp
- 
- 	| scriptName params entry morphs row isTiles code |
- 	scriptName _ (sexp attributeAt: #scriptName) asSymbol.
- 	params _ sexp elements select: [:e | e keyword == #parameter].
- 
- 	entry _ playerScripted class permanentUserScriptFor: scriptName asSymbol player: playerScripted.
- 
- 	params _ params collect: [:e | Variable new name: (e attributeAt: #name) asSymbol type: (e attributeAt: #type) asSymbol].
- 	entry argumentVariables: params.
- 	topEditor _ entry instantiatedScriptEditorForPlayer: playerScripted.
- 
- 	isTiles _ (sexp attributeAt: #language ifAbsent: ['Squeak']) = 'Etoys'.
- 	isTiles ifTrue: [
- 		morphs _ self fromSexp: (sexp elements detect: [:e | e keyword == #sequence] ifNone: []).
- 		morphs do: [:e |
- 			row _ topEditor addNewRow.
- 			row addMorph: e.
- 		].
- 	] ifFalse: [
- 		code _ (sexp elements detect: [:e | e keyword == #code]) attributeAt: #value.
- 		playerScripted class compileSilently: code classified: 'scripts'.
- 		topEditor userScriptObject becomeTextuallyCoded.
- 		(topEditor submorphs copyFrom: 2 to: topEditor submorphs size) do: [:m | m delete].
- 		topEditor showSourceInScriptor.
- 	].
- 
- 	^ entry.
- !

Item was removed:
- ----- Method: PhraseTileForTest>>initialize (in category 'as yet unclassified') -----
- initialize
- 
- 	super initialize.
- 	self color: Color orange muchLighter.
- 	self
- 		hResizing: #shrinkWrap;
- 		vResizing: #shrinkWrap;
- 		borderWidth: 1;
- 		borderColor: ScriptingSystem standardTileBorderColor.
- 	self setupCostume.
- !

Item was removed:
- ----- Method: FunctionTile>>tileRows (in category 'dropping/grabbing') -----
- tileRows
- 	"Answer a list of tile rows -- in this case exactly one row -- representing the receiver."
- 
- 	^ Array with: (Array with: self)!

Item was removed:
- ----- Method: TimesRepeatMorph>>sexpWith: (in category 'code generation') -----
- sexpWith: dictionary
- 
- 	| n elements e |
- 	n _ SExpElement keyword: #loop.
- 	n attributeAt: #type put: 'repeat'.
- 	elements _ WriteStream on: (Array new: 3).
- 	e _ SExpElement keyword: #initial.
- 	e elements: (Array with: ((SExpElement keyword: #literal) attributeAt: #value put: '1'; yourself)).
- 	elements nextPut: e.
- 	e _ SExpElement keyword: #increment.
- 	e elements: (Array with: ((SExpElement keyword: #literal) attributeAt: #value put: '1'; yourself)).
- 	elements nextPut: e.
- 
- 	e _ SExpElement keyword: #test.
- 	numberOfTimesToRepeatPart submorphs
- 		ifEmpty:
- 			[e elements: (Array with: ((SExpElement keyword: #literal) attributeAt: #value put: '0'; yourself))]
- 		ifNotEmpty:
- 			[e elements: (Array with: (numberOfTimesToRepeatPart sexpWith: dictionary))].
- 
- 	elements nextPut: e.
- 	
- 	elements nextPut: (self sexpBlockFor: whatToRepeatPart with: dictionary).
- 	n elements: elements contents.
- 	^ n.
- 
- !

Item was removed:
- ----- Method: ScriptingTileHolder>>handlesMouseDown: (in category 'mouse handling') -----
- handlesMouseDown: evt
- 	"Do I want to receive mouseDown events (mouseDown:, mouseMove:, mouseUp:)?"
- 
- 	^ true!

Item was removed:
- ----- Method: TimesRow>>initialize (in category 'initialization') -----
- initialize
- 	"object initialization"
- 
- 	| repeatLabel |
- 	super initialize.
- 	self minCellSize: (2 at 16).
- 	self setNameTo: 'Times'.
- 	repeatLabel _ StringMorph  contents: 'Repeat' translated font:  Preferences standardEToysFont.
- 	self addMorphBack: repeatLabel.
- 	self vResizing: #shrinkWrap.
- 	self addTransparentSpacerOfSize: (6 at 5).
- 
- 	timesPad := TilePadMorph new setType: #Number.
- 	timesPad hResizing: #shrinkWrap; color: Color transparent.
- 	timesPad addMorphBack: (TileMorph new addArrows; setLiteral: 2; addSuffixArrow; yourself).
- 	timesPad borderWidth: 0; layoutInset: (1 at 0).
- 
- 	self addMorphBack: timesPad.
- 	self addMorphBack: (StringMorph  contents: (' ', ('times' translated), ' ') font: Preferences standardEToysFont).
- 	self addMorphBack: AlignmentMorph newVariableTransparentSpacer!

Item was removed:
- ----- Method: ScriptingTileHolder>>around: (in category 'initialization') -----
- around: aTileScriptingElement
- 	"Make the receiver surround the given item, either a TileMorph or a PhraseTileMorph or something like a CompoundTIleMorph."
- 
- 	self removeAllMorphs.
- 	self position: aTileScriptingElement position.
- 	self addMorph: aTileScriptingElement.
- 	aTileScriptingElement lock.
- !

Item was removed:
- AlignmentMorph subclass: #ScriptingTileHolder
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!
- 
- !ScriptingTileHolder commentStamp: 'sw 6/28/2007 17:18' prior: 0!
- Serves as a wrapper for a scripting-tile element that otherwise would be bare on the desktop.!

Item was removed:
- ----- Method: FunctionNameTile>>arrowAction: (in category 'arrows') -----
- arrowAction: delta 
- 	"Do what is appropriate when an arrow on the tile is pressed; delta will be +1 or -1"
- 
- 	| index operatorList |
- 	operatorList := self options second.
- 	index _ (operatorList indexOf: self value) + delta.
- 	self setOperator: (operatorList atWrap: index).
- 	self scriptEdited.
- 	self layoutChanged!

Item was removed:
- ----- Method: TimesRepeatTile>>parseNodeWith: (in category 'code generation') -----
- parseNodeWith: encoder
- 	"Answer a MessageNode representing the receiver."
- 
- 	| rec selector arg timesPart |
- 	rec _ (timesPart := self numberOfTimesToRepeatPart) submorphs
- 		ifEmpty:
- 			[encoder encodeLiteral: 0]
- 		ifNotEmpty:
- 			[timesPart parseNodeWith: encoder].
- 	selector _ #timesRepeat:.
- 	arg _ self blockNode: whatToRepeatPart with: encoder.
- 	^ MessageNode new
- 				receiver: rec
- 				selector: selector
- 				arguments: (Array with: arg)
- 				precedence: (selector precedence)
- 				from: encoder
- 				sourceRange: nil
- !

Item was removed:
- ----- Method: FunctionTile>>removeFunction (in category 'menu') -----
- removeFunction
- 	"Unwrap the receiver from its contents."
- 
- 	self removeFunctionWrapper
- 
- 	!

Item was removed:
- ----- Method: SyntaxTestMethods>>repeatExample (in category 'as yet unclassified') -----
- repeatExample
- 
- 	self
- 		repeatFor: (1 to: 50)
- 		doing: [ :i | i + 3]!

Item was removed:
- ----- Method: FunctionTile>>addCustomMenuItems:hand: (in category 'menu') -----
- addCustomMenuItems: aCustomMenu hand: aHandMorph
- 	"Add custom menu items to the menu"
- 
- 	super addCustomMenuItems: aCustomMenu hand: aHandMorph.
- 	self topEditor ifNotNil:
- 		[aCustomMenu add: 'remove function' translated action: #removeFunctionWrapper]!

Item was removed:
- ----- Method: TimesRepeatMorph>>parseNodeWith: (in category 'code generation') -----
- parseNodeWith: encoder
- 
- 	| rec selector arg |
- 	rec _ numberOfTimesToRepeatPart submorphs
- 		ifEmpty:
- 			[encoder encodeLiteral: 0]
- 		ifNotEmpty:
- 			[numberOfTimesToRepeatPart parseNodeWith: encoder].
- 	selector _ #timesRepeat:.
- 	arg _ self blockNode: whatToRepeatPart with: encoder.
- 	^ MessageNode new
- 				receiver: rec
- 				selector: selector
- 				arguments: (Array with: arg)
- 				precedence: (selector precedence)
- 				from: encoder
- 				sourceRange: nil.
- !

Item was removed:
- ----- Method: ViewerRow>>initialize (in category 'initialization') -----
- initialize
- 	super initialize.
- 	self layoutInset: 1!

Item was removed:
- ----- Method: ViewerEntry>>contentsSelection (in category 'contents') -----
- contentsSelection
- 	"Not well understood why this needs to be here!!"
- 	^ 1 to: 0!

Item was removed:
- ----- Method: FunctionTile>>booleanComparatorPhrase (in category 'dropping/grabbing') -----
- booleanComparatorPhrase
- 	"Answer a boolean-valued phrase derived from a retriever (e.g. 'car's heading'); this is in order to assure that tiles laid down in a TEST area will indeed produce a boolean result"
- 
- 	| outerPhrase rel  |
- 
- 	rel := Vocabulary numberVocabulary comparatorForSampleBoolean.
- 	outerPhrase := PhraseTileMorph new setOperator: rel type: #Boolean rcvrType: #Number argType: #Number.
- 	outerPhrase firstSubmorph addMorph: self.
- 	outerPhrase submorphs last addMorph: (ScriptingSystem tileForArgType: #Number).
- 
- 	outerPhrase submorphs second submorphs last setBalloonText: (ScriptingSystem helpStringForOperator: rel).    
- 	^ outerPhrase!

Item was removed:
- ----- Method: SyntaxTestMethods>>bobsplace:after:newLine: (in category 'as yet unclassified') -----
- bobsplace: letter after: before newLine: isNewLine 
- 	"Position this letter. Put its left edge where the previous letter's right 	edge is. Move down to the next line if isNewLine is true. Add some 	leading for condensed or expanded text."
- 
- 	before isNil
- 		ifTrue: [self selfWrittenAsIll march: letter to: leftMargin topRight]
- 		ifFalse: 
- 			[isNewLine 
- 				ifTrue: 
- 					[self selfWrittenAsIll march: letter
- 						to: leftMargin right @ (before bottom + 1)]
- 				ifFalse: [self selfWrittenAsIll march: letter to: before topRight]].
- 	^self!

Item was removed:
- ----- Method: FunctionNameTile>>options (in category 'choice of function') -----
- options
- 	"Answer the options of the tile for an arrow"
- 
- 	| aTable |
- 	aTable := ScriptingSystem tableOfNumericFunctions reversed.
- 
- 	^ Array with:
- 				(aTable collect: [:pr | pr first] ), #(grouped)
- 			with:
- 				(aTable collect: [:pr | pr second]), #(grouped)!

Item was removed:
- ----- Method: SyntaxTestMethods>>bobsplace2:after:newLine: (in category 'as yet unclassified') -----
- bobsplace2: letter after: before newLine: isNewLine 
- 	"Position this letter. Put its left edge where the previous letter's right edge is. Move down to the next line if isNewLine is true. Add some 	leading for condensed or expanded text."
- 
- 	(self doFirstThatWorks)
- 		if: [before isNil]
- 			do: [self selfWrittenAsIll march: letter to: leftMargin topRight];
- 		if: [isNewLine]
- 			do: 
- 				[self selfWrittenAsIll march: letter
- 					to: leftMargin right @ (before bottom + 1)];
- 		if: [true] do: [self selfWrittenAsIll march: letter to: before topRight]!

Item was removed:
- TileLikeMorph subclass: #CommandTilesMorph
- 	instanceVariableNames: 'morph playerScripted'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!
- 
- !CommandTilesMorph commentStamp: '<historical>' prior: 0!
- An entire Smalltalk statement in tiles.  A line of code.!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>specialAssign:with: (in category 'reconstituting scripting tiles ') -----
- specialAssign: sexp with: rcvr
- 
- 	| propertyName updating rhs patch p componentName |
- 	propertyName _ (sexp attributeAt: #property) asSymbol.
- 	updating _ sexp attributeAt: #updating ifAbsent: [nil].
- 	rhs _ self fromSexp: sexp elements last.
- 	(propertyName == #patchValueIn:) ifTrue: [
- 		patch _ self fromSexp: sexp elements second.
- 
- 		p _ PhraseTileMorph new
- 			setPixelValueRoot: propertyName asSymbol
- 				type: #command
- 				rcvrType: #Player
- 				argType: #Number
- 				vocabulary: self currentVocabulary.
- 		p justGrabbedFromViewer: false.
- 		updating ifNotNil: [p submorphs second value: updating].
- 		p submorphs first addMorph: rcvr.
- 		p submorphs third setType: (sexp elements last attributeAt: #type ifAbsent: [#Number]) asSymbol.
- 		p submorphs third addMorph: rhs.
- 		p submorphs second setPatchDefaultTo: patch actualObject.
- 		^ p.
- 	].
- 	(propertyName == #setRedComponentIn:) ifTrue: [componentName _ #red].
- 	(propertyName == #setGreenComponentIn:) ifTrue: [componentName _ #green].
- 	(propertyName == #setBlueComponentIn:) ifTrue: [componentName _ #blue].
- 
- 	(#(setRedComponentIn: setGreenComponentIn: setBlueComponentIn:) includes: propertyName) ifTrue: [
- 		patch _ self fromSexp: sexp elements second.
- 
- 		p _ PhraseTileMorph new
- 					setColorComponentRoot: propertyName
- 					componentName: componentName
- 					type: #command
- 					rcvrType: #Patch
- 					argType: #Number
- 					vocabulary: self currentVocabulary.
- 		p justGrabbedFromViewer: false.
- 		updating ifNotNil: [p submorphs second value: updating].
- 		p submorphs first addMorph: rcvr.
- 		p submorphs third setType: (sexp elements last attributeAt: #type ifAbsent: [#Number]) asSymbol.
- 		p submorphs third addMorph: rhs.
- 		p submorphs second setPatchDefaultTo: patch actualObject.
- 		^ p.
- 	].
- 
- !

Item was removed:
- ----- Method: FunctionTile>>removeFunctionWrapper (in category 'menu') -----
- removeFunctionWrapper
- 	"Remove the function wrapper"
- 	
- 	| myPad |
- 	(owner isNil or: [owner owner isNil]) ifTrue: [^ Beeper beep].  "Not in a line of script"
- 	myPad _ submorphs third.
- 	owner owner replaceSubmorph: owner by: myPad.
- 	myPad scriptEdited!

Item was removed:
- ----- Method: FunctionTile>>operator:pad: (in category 'initialization') -----
- operator: opSymbol pad: aTilePadMorph
- 	"Set the operator and pad.  Builds and adds the four submorphs of the receiver
- 		function-name, left-paren, argument-pad, right-paren."
- 
- 	| functionTriplet |
- 	functionTriplet := ScriptingSystem tableOfNumericFunctions  detect: [:triplet | triplet second = opSymbol].  "If none, error..."
- 	self operator: opSymbol wording: functionTriplet first  translated helpString: functionTriplet third translated pad: aTilePadMorph!

Item was removed:
- AlignmentMorph subclass: #ViewerRow
- 	instanceVariableNames: 'elementSymbol'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!

Item was removed:
- ----- Method: TimesRepeatTile>>initialize (in category 'initialization') -----
- initialize
- 	"Fully initialize the receiver."
- 
- 	| dummyColumn  timesRepeatColumn repeatRow separator placeHolder doLabel ephemerum |
- 	submorphs _ EmptyArray.
- 	bounds _ 0 at 0 corner: 50 at 40.
- 	self color: Color orange muchLighter.
- 
- 	self layoutPolicy: TableLayout new.
- 	self "border, and layout properties in alphabetical order..."
- 		borderColor: self color darker;
- 		borderWidth: 2; 
- 		cellSpacing: #none;
- 		cellPositioning: #topLeft;
- 		hResizing: #spaceFill;
- 		layoutInset: 0;
- 		listDirection: #leftToRight;
- 		rubberBandCells: true;
- 		vResizing: #shrinkWrap;
- 		wrapCentering: #none.
- 
- 	self setNameTo: 'Repeat Complex'.
- 
- 	dummyColumn _ AlignmentMorph newColumn.
- 	dummyColumn cellInset: 0; layoutInset: 0.
- 	dummyColumn width: 0.
- 	dummyColumn cellPositioning: #leftCenter.
- 	dummyColumn hResizing: #shrinkWrap; vResizing: #spaceFill.
- 	self addMorph: dummyColumn.
- 
- 	timesRepeatColumn _ AlignmentMorph newColumn.
- 	timesRepeatColumn setNameTo: 'Times Repeat'.
- 
- 	timesRepeatColumn cellPositioning: #topLeft.
- 	timesRepeatColumn hResizing: #spaceFill.
-  	timesRepeatColumn vResizing: #shrinkWrap.
- 	timesRepeatColumn layoutInset: 0.
- 	timesRepeatColumn borderWidth: 0.
- 	timesRepeatColumn color:  Color orange muchLighter.
- 
- 	timesRow _ TimesRow newRow color: color; layoutInset: 0.
- 	timesRepeatColumn addMorphBack: timesRow.
- 
- 	separator _ AlignmentMorph newRow color:  Color transparent.
- 	separator vResizing: #rigid; hResizing: #spaceFill; height: 2.
- 	separator borderWidth: 0.
- 	timesRepeatColumn addMorphBack: separator.
- 
- 	repeatRow _ AlignmentMorph newRow color: color; layoutInset: 0.
- 	repeatRow minCellSize: (2 at 16).
- 	repeatRow setNameTo: 'Repeat '.
- 	placeHolder _ Morph new.
- 	placeHolder beTransparent; extent: (8 at 0).
- 	repeatRow addMorphBack: placeHolder.
- 	repeatRow vResizing: #shrinkWrap.
- 	doLabel _ StringMorph  contents: 'Do' translated font: Preferences standardEToysFont.
- 	repeatRow addMorphBack: doLabel.
- 	repeatRow addMorphBack: (Morph new color: color; extent: 5 at 5).  "spacer"
- 	repeatRow addMorphBack: (whatToRepeatPart _ ScriptEditorMorph new borderWidth: 0; layoutInset: 0).
- 
- 	whatToRepeatPart hResizing: #spaceFill.
- 	whatToRepeatPart vResizing: #shrinkWrap.
- 	whatToRepeatPart color: Color transparent.
- 	whatToRepeatPart setNameTo: 'Script to repeat' translated.
- 	whatToRepeatPart addMorphBack: (ephemerum := Morph new height: 14) beTransparent.
- 
- 	timesRepeatColumn addMorphBack: repeatRow.
- 	
- 	self addMorphBack: timesRepeatColumn.
- 	self bounds: self fullBounds.
- 
- 	ephemerum delete!

Item was removed:
- ----- Method: SyntaxTestMethods>>makeRandomString (in category 'as yet unclassified') -----
- makeRandomString
- 
- 	| newString foo |
- 
- 	newString _ String new: Goal contents size.
- 	foo _ Goal contents size.
- 	^newString collect: [ :oldLetter | 'abcdefghijklmnopqrstuvwxyz' atRandom]
- !

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>variable: (in category 'reconstituting scripting tiles ') -----
- variable: sexp
- 
- 	| p |
- 	p _ ParameterTile new.
- 	p scriptEditor: topEditor.
- 	p line1: (sexp attributeAt: #type) translated.
- 	^ p.
- !

Item was removed:
- ----- Method: FunctionNameTile>>setOperator: (in category 'choice of function') -----
- setOperator: anOperatorSymbol
- 	"The user chose an entry with the given inherent operator symbol (this may differ from what the user sees in the pop-up or on the tile."
- 
- 	| aTable |
- 	operatorOrExpression := anOperatorSymbol.
- 	operatorOrExpression = #grouped
- 		ifTrue:
- 			[self line1: ' '.
- 			self setBalloonText: 'parenthesized' translated]
- 		ifFalse:
- 			[aTable := ScriptingSystem tableOfNumericFunctions.
- 			(aTable detect: [:m | m second = anOperatorSymbol] ifNone: [nil]) ifNotNilDo:
- 				[:aTriplet |
- 					self line1: aTriplet first translated.
- 					self setBalloonText: aTriplet third translated]].
- 	self addArrows.
- 	self scriptEdited.
- 	self layoutChanged!

Item was removed:
- ----- Method: FunctionNameTile>>grouped (in category 'menu commands') -----
- grouped
- 	"The user chose grouped from the menu.  Establish the special-case null function call."
- 
- 	self setOperator: #grouped!

Item was removed:
- ----- Method: ViewerRow>>entryType (in category 'access') -----
- entryType
- 	"Answer one of: #systemSlot #userSlot #systemScript #userScript"
- 
- 	^ self playerBearingCode elementTypeFor: elementSymbol vocabulary: self currentVocabulary!

Item was removed:
- ----- Method: FunctionNameTile>>showOptions (in category 'choice of function') -----
- showOptions
- 	"Put up a pop-up menu of options for the operator tile within me."
- 
- 	| aMenu aTable |
- 	aMenu := MenuMorph new defaultTarget: self.
- 	aTable := ScriptingSystem tableOfNumericFunctions.
- 	aTable do:
- 		[:triplet |
- 			aMenu add: triplet first translated target: self  selector:  #setOperator: argument: triplet second.
- 			triplet second = operatorOrExpression ifTrue:
- 				[aMenu lastItem color: Color red].
- 			aMenu balloonTextForLastItem: triplet third].
- 
- 	aMenu addTranslatedList:
- 		#(-
- 		('parentheses'  grouped 'enclose within parentheses')) translatedNoop.
- 	operatorOrExpression = #grouped ifTrue:
- 		[aMenu lastItem color: Color red].
- 
- 	(owner owner isKindOf: TilePadMorph) ifTrue:
- 		[aMenu addLine.
- 		operatorOrExpression = #grouped
- 			ifFalse:			
- 				[aMenu addTranslatedList:
- 					#(('remove function' removeFunction  'strip away the function call, leaving just its former argument in its place')) translatedNoop.]
- 			ifTrue:
- 				[aMenu addTranslatedList:
- 					#(('remove parentheses' removeFunction  'strip away the parenthesises')) translatedNoop]].
- 
- 	aMenu position: self position.
- 	aMenu invokeModal
- !

Item was removed:
- ----- Method: TimesRepeatMorph>>initialize (in category 'initialization') -----
- initialize
- 	"Fully initialize the receiver."
- 
- 	| dummyColumn timesRow  timesRepeatColumn repeatRow separator repeatLabel placeHolder doLabel ephemerum |
- 	submorphs _ EmptyArray.
- 	bounds _ 0 at 0 corner: 50 at 40.
- 	self color: Color orange muchLighter.
- 
- 	self layoutPolicy: TableLayout new.
- 	self "border, and layout properties in alphabetical order..."
- 		borderColor: self color darker;
- 		borderWidth: 2; 
- 		cellSpacing: #none;
- 		cellPositioning: #topLeft;
- 		hResizing: #spaceFill;
- 		layoutInset: 0;
- 		listDirection: #leftToRight;
- 		rubberBandCells: true;
- 		vResizing: #shrinkWrap;
- 		wrapCentering: #none.
- 
- 	self setNameTo: 'Repeat Complex'.
- 
- 	dummyColumn _ AlignmentMorph newColumn.
- 	dummyColumn cellInset: 0; layoutInset: 0.
- 	dummyColumn width: 0.
- 	dummyColumn cellPositioning: #leftCenter.
- 	dummyColumn hResizing: #shrinkWrap; vResizing: #spaceFill.
- 	self addMorph: dummyColumn.
- 
- 	timesRepeatColumn _ AlignmentMorph newColumn.
- 	timesRepeatColumn setNameTo: 'Times Repeat'.
- 
- 	timesRepeatColumn cellPositioning: #topLeft.
- 	timesRepeatColumn hResizing: #spaceFill.
-  	timesRepeatColumn vResizing: #shrinkWrap.
- 	timesRepeatColumn layoutInset: 0.
- 	timesRepeatColumn borderWidth: 0.
- 	timesRepeatColumn color:  Color orange muchLighter.
- 
- 	timesRow _ AlignmentMorph newRow color: color; layoutInset: 0.
- 	timesRow minCellSize: (2 at 16).
- 	timesRow setNameTo: 'Times'.
- 	repeatLabel _ StringMorph  contents: 'Repeat' translated font:  Preferences standardEToysFont.
- 	timesRow addMorphBack: repeatLabel.
- 	timesRow vResizing: #shrinkWrap.
- 	timesRow addMorphBack: (Morph new color: color; extent: 6 at 5).  "spacer"
- 
- 	numberOfTimesToRepeatPart := TilePadMorph new setType: #Number.
- 	numberOfTimesToRepeatPart hResizing: #shrinkWrap; color: Color transparent.
- 	numberOfTimesToRepeatPart addMorphBack: (TileMorph new addArrows; setLiteral: 2).
- 	numberOfTimesToRepeatPart borderWidth: 0; layoutInset: (1 at 0).
- 
- 	timesRow addMorphBack: numberOfTimesToRepeatPart.
- 	timesRow addMorphBack: (StringMorph  contents: ' times ' font: Preferences standardEToysFont).
- 	timesRow addMorphBack: AlignmentMorph newVariableTransparentSpacer.
- 	timesRepeatColumn addMorphBack: timesRow.
- 
- 	separator _ AlignmentMorph newRow color:  Color transparent.
- 	separator vResizing: #rigid; hResizing: #spaceFill; height: 2.
- 	separator borderWidth: 0.
- 	timesRepeatColumn addMorphBack: separator.
- 
- 	repeatRow _ AlignmentMorph newRow color: color; layoutInset: 0.
- 	repeatRow minCellSize: (2 at 16).
- 	repeatRow setNameTo: 'Repeat '.
- 	placeHolder _ Morph new.
- 	placeHolder beTransparent; extent: (8 at 0).
- 	repeatRow addMorphBack: placeHolder.
- 	repeatRow vResizing: #shrinkWrap.
- 	doLabel _ StringMorph  contents: 'Do' font: Preferences standardEToysFont.
- 	repeatRow addMorphBack: doLabel.
- 	repeatRow addMorphBack: (Morph new color: color; extent: 5 at 5).  "spacer"
- 	repeatRow addMorphBack: (whatToRepeatPart _ ScriptEditorMorph new borderWidth: 0; layoutInset: 0).
- 
- 	whatToRepeatPart hResizing: #spaceFill.
- 	whatToRepeatPart vResizing: #shrinkWrap.
- 	whatToRepeatPart color: Color transparent.
- 	whatToRepeatPart setNameTo: 'Script to repeat'.
- 	whatToRepeatPart addMorphBack: (ephemerum := Morph new height: 14) beTransparent.
- 
- 	timesRepeatColumn addMorphBack: repeatRow.
- 	
- 	self addMorphBack: timesRepeatColumn.
- 	self bounds: self fullBounds.
- 
- 	ephemerum delete!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>sequence: (in category 'reconstituting scripting tiles ') -----
- sequence: sexp
- 
- 	^ sexp elements collect: [:elem |
- 		self fromSexp: elem.
- 	].
- !

Item was removed:
- ----- Method: PhraseWrapperMorph classSide>>includeInNewMorphMenu (in category 'new-morph participation') -----
- includeInNewMorphMenu
- 	"Not to be instantiated from the menu"
- 	^ false!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder classSide>>context:playerScripted:topEditor: (in category 'as yet unclassified') -----
- context: c playerScripted: p topEditor: t
- 
- 	^ self new context: c playerScripted: p topEditor: t
- !

Item was removed:
- ----- Method: ViewerRow>>elementSymbol: (in category 'access') -----
- elementSymbol: aSymbol
- 	elementSymbol _ aSymbol!

Item was removed:
- ----- Method: ViewerRow>>playerBearingCode (in category 'access') -----
- playerBearingCode
- 	^ owner playerBearingCode!

Item was removed:
- ----- Method: ViewerEntry>>contents:notifying: (in category 'contents') -----
- contents: c notifying: k
- 	"later, spruce this up so that it can accept input such as new method source"
- 	| info |
- 	(info _ self userSlotInformation)
- 		ifNotNil:
- 			[info documentation: c.
- 			^ true].
- 	Beeper beep.
- 	^ false!

Item was removed:
- ----- Method: CommandTilesMorph>>setMorph: (in category 'initialization') -----
- setMorph: aMorph
- 	playerScripted _ aMorph playerScripted
- !

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>phraseForSpecialKedamaSend: (in category 'reconstituting scripting tiles ') -----
- phraseForSpecialKedamaSend: realSel
- 
- 	realSel == #getPatchValueIn: ifTrue: [
- 		^ PhraseTileMorph new setGetPixelOperator: realSel type: #Number rcvrType: #Player argType: #Patch.
- 	].
- 	realSel == #getAngleTo: ifTrue: [
- 		^ PhraseTileMorph new setAngleToOperator: realSel type: #Number rcvrType: #Player argType: #Player.
- 	].
- 	realSel == #bounceOn: ifTrue: [
- 		^ PhraseTileMorph new setBounceOnOperator: realSel type: #Boolean rcvrType: #Player argType: #Player.
- 	].
- 	realSel == #getDistanceTo: ifTrue: [
- 		^ PhraseTileMorph new setDistanceToOperator: realSel type: #Number rcvrType: #Player argType: #Player
- 	].
- 	realSel == #getTurtleOf: ifTrue: [
- 		^ PhraseTileMorph new setTurtleOfOperator: realSel type: #Player rcvrType: #Player argType: #Player
- 	].
- 	realSel == #getUphillIn: ifTrue: [
- 		^ PhraseTileMorph new setUpHillOperator: realSel type: #Number rcvrType: #Player argType: #Player
- 	].
- 	realSel == #getRedComponentIn: ifTrue: [
- 		^ PhraseTileMorph new setGetColorComponentOperator: realSel componentName: #red type: #Number rcvrType: #Player argType: #Patch
- 	].
- 	realSel == #getGreenComponentIn: ifTrue: [
- 		^ PhraseTileMorph new setGetColorComponentOperator: realSel componentName: #green type: #Number rcvrType: #Player argType: #Patch
- 	].
- 	realSel == #getBlueComponentIn: ifTrue: [
- 		^ PhraseTileMorph new setGetColorComponentOperator: realSel componentName: #blue type: #Number rcvrType: #Player argType: #Patch
- 	].
- 
- 	^ nil.
- !

Item was removed:
- ----- Method: ViewerEntry>>initialize (in category 'initialization') -----
- initialize
- "initialize the state of the receiver"
- 	super initialize.
- ""
- 	self layoutInset: 0!

Item was removed:
- ----- Method: PhraseTileForTimesRepeat>>addCommandFeedback: (in category 'hilighting') -----
- addCommandFeedback: evt
- 	"Add screen feedback showing what would be torn off in a drag"
- 
- 	| aMorph rect |
- 	(self owner owner isMemberOf: PhraseTileMorph) ifTrue: [self owner owner addCommandFeedback: evt. ^ self].
- 	rect _ self bounds.
- 	aMorph _ RectangleMorph new bounds: rect.
- 	aMorph beTransparent; borderWidth: 2; borderColor: (Color r: 1.0 g: 0.548 b: 0.452); lock.
- 	ActiveWorld addHighlightMorph: aMorph for: self outmostScriptEditor!

Item was removed:
- Object subclass: #ScriptEditorMorphBuilder
- 	instanceVariableNames: 'context playerScripted topEditor'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting'!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>assign: (in category 'reconstituting scripting tiles ') -----
- assign: sexp
- 
- 	| rcvr propertyName updating rhs p |
- 	rcvr _ self fromSexp: sexp elements first.
- 
- 	propertyName _ sexp attributeAt: #property ifAbsent: [self error: ''].
- 	propertyName _ propertyName asSymbol.
- 	(#(patchValueIn: setRedComponentIn: setGreenComponentIn: setBlueComponentIn:) includes: propertyName) ifTrue: [
- 		^ self specialAssign: sexp with: rcvr.
- 	].
- 
- 	updating _ sexp attributeAt: #updating ifAbsent: [nil].
- 	rhs _ self fromSexp: sexp elements last.
- 
- 	p _ PhraseTileMorph new
- 		setAssignmentRoot: propertyName asSymbol
- 			type: #command
- 			rcvrType: #Player
- 			argType: (sexp attributeAt: #type ifAbsent: [#Number]) asSymbol
- 			vocabulary: self currentVocabulary.
- 	p justGrabbedFromViewer: false.
- 	updating ifNotNil: [p  submorphs second value: updating].
- 	p submorphs first addMorph: rcvr.
- 	p submorphs third setType: (sexp elements last attributeAt: #type ifAbsent: [#Number]) asSymbol.
- 	p submorphs third addMorph: rhs.
- 	(rhs resultType == #Number and: [rhs isMemberOf: TileMorph]) ifTrue: [
- 		rhs addSuffixArrow.
- 	].
- 
- 	^ p.
- !

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>topEditor (in category 'e-toy support') -----
- topEditor
- 
- 	^ topEditor.
- !

Item was removed:
- TileMorph subclass: #FunctionNameTile
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Scripting Tiles'!
- 
- !FunctionNameTile commentStamp: 'sw 6/9/2007 22:25' prior: 0!
- An operator tile holding the name of a function; used in conjunction with a FunctionTile which is always its owner.!

Item was removed:
- ----- Method: PhraseTileForTest>>addCommandFeedback: (in category 'as yet unclassified') -----
- addCommandFeedback: evt
- 	"Add screen feedback showing what would be torn off in a drag"
- 
- 	| aMorph rect |
- 	(self owner owner isMemberOf: PhraseTileMorph) ifTrue: [self owner owner addCommandFeedback: evt. ^ self].
- 	rect _ self bounds.
- 	aMorph _ RectangleMorph new bounds: rect.
- 	aMorph beTransparent; borderWidth: 2; borderColor: (Color r: 1.0 g: 0.548 b: 0.452); lock.
- 	ActiveWorld addHighlightMorph: aMorph for: self outmostScriptEditor!

Item was removed:
- PasteUpMorph subclass: #SyntaxTestMethods
- 	instanceVariableNames: 'letterActors wild leftMargin rightMargin switch current jumpSwitch hotIndex'
- 	classVariableNames: 'Goal'
- 	poolDictionaries: ''
- 	category: 'Morphic-Tile Scriptors'!

Item was removed:
- ----- Method: FunctionTile>>storeCodeOn:indent: (in category 'code generation') -----
- storeCodeOn: aStream indent: tabCount 
- 	"Store the receiver's code on the stream, honoring indentation."
- 
- 	aStream nextPut: $(.
- 	aStream space.
- 	argumentPad storeCodeOn: aStream indent: tabCount.
- 	aStream nextPut: $).
- 	aStream space.
- 	functionNameTile storeCodeOn: aStream indent: tabCount!

Item was removed:
- ----- Method: ScriptEditorMorphBuilder>>fromSexp: (in category 'initialization') -----
- fromSexp: sexp
- 
- 	^ self perform: (sexp keyword copyWith: $:) asSymbol with: sexp.
- !

Item was removed:
- ----- Method: CommandTilesMorph>>initialize (in category 'initialization') -----
- initialize
- 
- 	super initialize.
- 	self wrapCentering: #center; cellPositioning: #leftCenter.
- 	self hResizing: #shrinkWrap.
- 	borderWidth _ 0.
- 	self layoutInset: 0.
- 	self extent: 5 at 5.  "will grow to fit"
- !

Item was removed:
- ----- Method: FunctionTile>>kedamaParseNodeWith:actualObject: (in category 'code generation') -----
- kedamaParseNodeWith: encoder actualObject: obj
- 
- 	| ret arg |
- 	arg _ submorphs third parseNodeWith: encoder.
- 	ret _ MessageNode new
- 				receiver: (encoder encodePlayer: obj)
- 				selector: #random:
- 				arguments: (Array with: arg)
- 				precedence: (#random: precedence)
- 				from: encoder
- 				sourceRange: nil.
- 	^  self convertPrecedenceOfArgsInParseNode: ret with: encoder.
- !

Item was removed:
- ----- Method: FunctionTile>>sexpWith: (in category 'code generation') -----
- sexpWith: dictionary
- 	| n elements sel |
- 	sel _ submorphs first operatorOrExpression.
- 	n _ SExpElement keyword: #send.
- 	n attributeAt: #type put: ((owner isMemberOf: TilePadMorph) ifTrue: [owner type] ifFalse: ['Number']).
- 	elements _ Array with: ((SExpElement keyword: #selector)
- 					attributeAt: #selector put: sel; yourself)
- 				with: (argumentPad sexpWith: dictionary).
- 	n elements: elements.
- 	^ n.
- !



More information about the etoys-dev mailing list