Etoys: Etoys-kfr.122.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

Etoys: Etoys-kfr.122.mcz

commits-2
Spam detection software, running on the system "europa.mgmt.inetu.net", has
identified this incoming email as possible spam.  The original message
has been attached to this so you can view it (if it isn't spam) or label
similar future email.  If you have any questions, see
the administrator of that system for details.

Content preview:  Karl Ramberg uploaded a new version of Etoys to project Etoys:
   http://source.squeak.org/etoys/Etoys-kfr.122.mcz ==================== Summary
   ==================== Name: Etoys-kfr.122 Author: kfr Time: 9 March 2012,
  12:00:51 pm UUID: f0cfbdc4-81fb-459b-8ae5-b4e6a942cd3e Ancestors: Etoys-kfr.121
   [...]

Content analysis details:   (6.5 points, 5.0 required)

 pts rule name              description
---- ---------------------- --------------------------------------------------
 3.5 BAYES_99               BODY: Bayesian spam probability is 99 to 100%
                            [score: 0.9939]
 0.0 MISSING_MID            Missing Message-Id: header
 1.2 INVALID_DATE           Invalid Date: header (not RFC 2822)
 1.1 DATE_IN_PAST_06_12     Date: is 6 to 12 hours before Received: date
 1.7 TVD_FUZZY_SYMBOL       BODY: TVD_FUZZY_SYMBOL
 3.8 TVD_STOCK1             BODY: TVD_STOCK1
 0.1 RDNS_NONE              Delivered to trusted network by a host with no rDNS
-4.8 AWL                    AWL: From: address is in the auto white-list



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

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

Name: Etoys-kfr.122
Author: kfr
Time: 9 March 2012, 12:00:51 pm
UUID: f0cfbdc4-81fb-459b-8ae5-b4e6a942cd3e
Ancestors: Etoys-kfr.121

Limits the choices for types for user-defined variables and for parameters for user-defined scripts.
Adds balloon help for items in the menu for a variable in a viewer.
Cleans up some symbol-list-type-related issues.
Reformulates a couple of recently-added UI elements into more translation-friendly formats.

=============== Diff against Etoys-kfr.121 ===============

Item was changed:
  ----- Method: DataType>>addWatcherItemsToMenu:forGetter: (in category '*Etoys-tiles') -----
  addWatcherItemsToMenu: aMenu forGetter: aGetter
  "Add watcher items to the menu if appropriate, provided the getter is not an odd-ball one for which a watcher makes no sense"
 
  (Vocabulary gettersForbiddenFromWatchers includes: aGetter) ifFalse:
  [aMenu add: 'simple watcher' translated selector: #tearOffUnlabeledWatcherFor: argument: aGetter.
+ aMenu balloonTextForLastItem: 'obtain an unlabeled readout which shows the value of this variable' translated.
+
  aMenu add: 'detailed watcher' translated selector: #tearOffFancyWatcherFor: argument: aGetter.
+ aMenu balloonTextForLastItem: 'obtain a labeled readout which shows the object name and the name and value of this variable' translated.
+
  aMenu add: 'attached watcher' translated selector: #tearOffAttachedWatcherFor: argument: aGetter.
+ aMenu balloonTextForLastItem: 'attach an unlabeled readout to the object which shows the value of this variable' translated.
+
  aMenu add: 'attached labeled watcher' translated selector: #tearOffAttachedLabeledWatcherFor: argument: aGetter.
+ aMenu balloonTextForLastItem: 'make a readout showing the name and value of this variable, and attach it to the object itself' translated.
+
  aMenu addLine]!

Item was changed:
  WatcherWrapper subclass: #FollowingWatcher
  instanceVariableNames: 'attachmentEdge offset'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Etoys-Scripting Support'!
 
+ !FollowingWatcher commentStamp: 'sw 3/7/2012 00:12' prior: 0!
- !FollowingWatcher commentStamp: 'sw 2/13/2012 18:55' prior: 0!
  A watcher that follows its watchee around.
 
+ attachmentEdge:  can be #left, #right #bottom, #top, #topLeft, #topRight, #bottomLeft, #bottomRight, #center)
- attachmentEdge:  can be #left, #right #bottom, #top, or #bottomRight.
- (missing items could obviously be added trivially if wanted)
 
  offset:  (x,y) offset from the nominal attachment point.!

Item was changed:
  ----- Method: FollowingWatcher>>addCustomMenuItems:hand: (in category 'accessing') -----
  addCustomMenuItems: aMenu hand: aHand
  "Add morph-specific items to a menu."
 
  aMenu addUpdating:  #attachmentEdgeString  action: #chooseAttachmentEdge.
+
+ aMenu add: ('offset (currently {1}' translated format: {offset printString}) action: #chooseOffset.
+ aMenu balloonTextForLastItem: 'fine-tune the position of this watcher relative to its chosen attachment edge' translated!
- aMenu add: ('offset' translated, ' (', 'currently' translated, ' ', offset printString, ')') action: #chooseOffset!

Item was changed:
  ----- Method: FollowingWatcher>>attachmentEdgeString (in category 'accessing') -----
  attachmentEdgeString
  "Answer a string to serve as the wording of the menu item inviting the use to choose the attachment edge."
 
+ ^ 'choose attachment edge (now {1})' translated format: {attachmentEdge asString translated}!
- ^ 'choose attachment edge'  translated, ' (', 'now' translated, ' ', attachmentEdge asString translated, ')'!

Item was changed:
  ----- Method: KedamaExamplerPlayer>>chooseSlotTypeFor: (in category 'player protocol') -----
  chooseSlotTypeFor: aGetter
+ "Let the user designate a type for the slot associated with the given getter.  Seemngly at the momentnot sent."
- "Let the user designate a type for the slot associated with the given getter"
 
  | typeChoices typeChosen slotName |
  slotName _ Utilities inherentSelectorForGetter: aGetter.
+ typeChoices _ Vocabulary typeChoicesForUserVariables.
- typeChoices _ Vocabulary typeChoices.
 
  typeChosen _ (SelectionMenu labelList: (typeChoices collect: [:t | t translated]) lines: #() selections: typeChoices) startUpWithCaption:
  ('Choose the TYPE
  for {1}
  (currently {2})' format: {slotName. (self slotInfoAt: slotName) type translated}).
  typeChosen isEmptyOrNil ifTrue: [^ self].
  (self typeForSlot: slotName) capitalized = typeChosen ifTrue: [^ self].
 
  (self slotInfoAt: slotName) type: typeChosen.
  self class allInstancesDo:   "allSubInstancesDo:"
  [:anInst | anInst instVarNamed: slotName asString put:
  (anInst valueOfType: typeChosen from: (anInst instVarNamed: slotName))].
  turtles setVectorSlotTypeFor: slotName typeChosen: typeChosen.
  sequentialStub ifNotNil: [sequentialStub setScalarSlotTypeFor: slotName typeChosen: typeChosen].
  self updateAllViewers. "does siblings too"
  !

Item was changed:
  ----- Method: ModifyVariableDialogMorph>>varType (in category 'accessing') -----
  varType
+ "Answer the symbol representing the chosen value type for the variable."
+
  ^ varTypeButton
  ifNil: [self targetPlayer typeForSlot: slot]
  ifNotNil: [:button|
+ Vocabulary typeChoicesForUserVariables
- Vocabulary typeChoices
  detect: [:each |
  each translated = button label]
  ifNone: [button label asSymbol]]!

Item was changed:
  ----- Method: NewVariableDialogMorph>>askUserForNewType (in category 'actions') -----
  askUserForNewType
+ "Put up a pop up offering the user a choice of valid types for user-defined variables."
+
  | typeChoices menuTitle |
+ typeChoices := Vocabulary typeChoicesForUserVariables.
- typeChoices := Vocabulary typeChoices asOrderedCollection.
- [self target renderedMorph defaultPatch]
- on:Exception
- do:[ typeChoices remove: #Patch ifAbsent: [typeChoices]].
  menuTitle := 'Choose the TYPE
  for {1}
  ' translated, '
  (currently {2})' translated format: {self varAcceptableName. self varType}.
  ^ UIManager
  chooseFrom: (typeChoices collect: [:t | t translated])
  values: typeChoices
  title: menuTitle!

Item was changed:
  ----- Method: NewVariableDialogMorph>>varType (in category 'accessing') -----
  varType
+ "Answer the symbol representing the chosen value type for the variable."
+
  ^ varTypeButton
  ifNil: [self targetPlayer initialTypeForSlotNamed: self varAcceptableName]
  ifNotNil: [:button|
+ Vocabulary typeChoicesForUserVariables
- Vocabulary typeChoices
  detect: [:each |
  each translated = button label]
  ifNone: [button label asSymbol]]!

Item was changed:
  ----- Method: Player>>changeParameterTypeFor: (in category 'costume') -----
  changeParameterTypeFor: aSelector
  "Change the parameter type for the given selector.  Not currently sent, since types are now set by direct manipulation in the Scriptor header.  If this were reinstated someday, there would probably be an issue about getting correct-looking Parameter tile(s) into the Scriptor header(s)"
 
  | current typeChoices typeChosen |
  current _ self typeforParameterFor: aSelector.
+ typeChoices _ Vocabulary typeChoicesForUserVariables.
- typeChoices _ Vocabulary typeChoices.
  typeChosen _ (SelectionMenu selections: typeChoices lines: #()) startUpWithCaption:
  ('Choose the TYPE
  for the parameter (currently {1})' translated format: {current}).
  self setParameterFor: aSelector toType: typeChosen
 
  !

Item was changed:
  ----- Method: Player>>offerGetterTiles: (in category 'slots-user') -----
  offerGetterTiles: slotName
  "For a player-type slot, offer to build convenient compound tiles that otherwise would be hard to get"
 
  | typeChoices typeChosen thePlayerThereNow slotChoices slotChosen getterTiles aCategoryViewer playerGetter |
  typeChoices := Vocabulary typeChoices.
  typeChosen := (SelectionMenu labelList: (typeChoices collect: [:t | t translated]) lines: #() selections: typeChoices)
  startUpWithCaption: ('Choose the TYPE
  of data to get from
  {1}''s {2}' translated format: {self externalName. slotName translated}).
  typeChosen isEmptyOrNil ifTrue: [^self].
  thePlayerThereNow := self perform: (Utilities getterSelectorFor: slotName).
  thePlayerThereNow
  ifNil: [thePlayerThereNow := self presenter standardPlayer].
  slotChoices := thePlayerThereNow slotNamesOfType: typeChosen.
  slotChoices isEmpty
+ ifTrue: [^self inform: 'sorry -- no variables of that type are available in this object' translated].
- ifTrue: [^self inform: 'sorry -- no slots of that type' translated].
  slotChoices _ slotChoices asSortedArray.
  slotChosen := (SelectionMenu labelList: (slotChoices collect: [:t | t translated]) selections: slotChoices)
  startUpWithCaption: ('Choose the datum
  you want to extract from {1}''s {2}' translated format: {self externalName. slotName translated}).
  slotChosen isEmptyOrNil ifTrue: [^self].
  "Now we want to tear off tiles of the form
  holder's valueAtCursor's foo"
  getterTiles := nil.
  aCategoryViewer := CategoryViewer new initializeFor: thePlayerThereNow
  categoryChoice: 'basic'.
  getterTiles := aCategoryViewer
  getterTilesFor: (Utilities getterSelectorFor: slotChosen)
  type: typeChosen.
  aCategoryViewer := CategoryViewer new initializeFor: self
  categoryChoice: 'basic'.
  playerGetter := aCategoryViewer
  getterTilesFor: (Utilities getterSelectorFor: slotName)
  type: #Player.
  getterTiles submorphs first acceptDroppingMorph: playerGetter event: nil. "the pad" "simulate a drop"
  getterTiles makeAllTilesGreen.
  getterTiles justGrabbedFromViewer: false.
  (getterTiles firstSubmorph)
  changeTableLayout;
  hResizing: #shrinkWrap;
  vResizing: #spaceFill.
  ActiveHand attachMorph: getterTiles!

Item was changed:
  ----- Method: Player>>slotInfoButtonHitFor:inViewer: (in category 'scripts-kernel') -----
  slotInfoButtonHitFor: aGetterSymbol inViewer: aViewer
  "The user made a gesture asking for slot menu for the given getter symbol in a viewer; put up the menu."
 
  | aMenu slotSym aType typeVocab |
 
  (#(+ - * /) includes: aGetterSymbol)
  ifTrue:
  [^ self inform: ('{1} is used for vector operations' translated format: {aGetterSymbol})].
 
  slotSym _ Utilities inherentSelectorForGetter: aGetterSymbol.
  aType _ self typeForSlotWithGetter: aGetterSymbol asSymbol.
  aMenu _ MenuMorph new defaultTarget: self.
- "interface := aViewer currentVocabulary methodInterfaceAt: aGetterSymbol ifAbsent: [nil].
- selector := interface isNil
- ifTrue: [slotSym asString]
- ifFalse: [interface selector]."
 
  aType = #Patch ifTrue: [
  aMenu add: 'grab morph' translated
  target: (self perform: aGetterSymbol)
  selector: #grabPatchMorph
  argument: #().
  aMenu addLine.
  ].
 
  (typeVocab _ Vocabulary vocabularyForType: aType) addWatcherItemsToMenu: aMenu forGetter: aGetterSymbol.
 
  (self slotInfo includesKey: slotSym)
  ifTrue:
  [typeVocab addUserSlotItemsTo: aMenu slotSymbol: slotSym.
- aMenu add: ('modify "{1}"' translated format: {slotSym}) selector: #changeSlotInfo: argument: slotSym.
  aMenu add: ('remove "{1}"' translated format: {slotSym}) selector: #removeSlotNamed: argument: slotSym.
+ aMenu balloonTextForLastItem: 'remove this variable from this object' translated.
+ aMenu add: ('modify "{1}"' translated format: {slotSym}) selector: #changeSlotInfo: argument: slotSym.
+ aMenu balloonTextForLastItem: 'change the name, type, and/or decimal places settings for this variable' translated.
+ aMenu addLine].
-
- ]
- ifFalse: [
- aMenu addLine.
- typeVocab addExtraItemsToMenu: aMenu forSlotSymbol: slotSym.  "e.g. Player type adds hand-me-tiles"].
 
+ typeVocab addExtraItemsToMenu: aMenu forSlotSymbol: slotSym.  "e.g. Player type adds hand-me-tiles".
+
  self addIdiosyncraticMenuItemsTo: aMenu forSlotSymol: slotSym.
 
  aMenu items isEmpty ifTrue:
  [aMenu add: 'ok' translated action: #yourself].
 
  aMenu popUpForHand: aViewer primaryHand in: aViewer world!

Item was changed:
  ----- Method: PlayerType>>addExtraItemsToMenu:forSlotSymbol: (in category 'tiles') -----
  addExtraItemsToMenu: aMenu forSlotSymbol: slotSym
  "If the receiver has extra menu items to add to the slot menu, here is its chance to do it"
 
+ aMenu add: 'tiles to get...' translated selector: #offerGetterTiles: argument: slotSym.
+ aMenu balloonTextForLastItem: 'useful shortcut for obtaining the value of a variable belonging to the player that is the current value of this player-valued variable'!
- aMenu add: 'tiles to get...' translated selector: #offerGetterTiles: argument: slotSym!

Item was changed:
  ----- Method: ScriptEditorMorph>>buttonRowForEditor (in category 'buttons') -----
  buttonRowForEditor
  "Answer a row of buttons that comprise the header at the top of the Scriptor"
 
  | aRow aString aStatusMorph aButton aTile aMorph goldBoxButton aBox |
  aRow _ AlignmentMorph newRow color: ScriptingSystem baseColor; layoutInset: 1.
  aRow hResizing: #spaceFill.
  aRow vResizing: #shrinkWrap.
  self addDismissButtonTo: aRow.
  aRow addTransparentSpacerOfSize: 9.
 
  "Player's name"
  aString _ playerScripted externalName.
  aMorph _ StringMorph contents: aString font: ScriptingSystem fontForTiles.
  aMorph setNameTo: 'title'.
  aRow addMorphBack: aMorph.
  aRow addTransparentSpacerOfSize: 6.
 
  "Script's name"
  aBox := AlignmentMorph newRow.
  aBox hResizing: #shrinkWrap; vResizing: #shrinkWrap.
  aBox color: (Color r: 0.839 g: 1.0 b: 0.806).
  aBox borderWidth: 1.
  aBox  borderColor: (Color r: 0.645 g: 0.774 b: 0.613).
  aButton _ UpdatingStringMorph new.
  aButton useStringFormat;
  target:  self;
  getSelector: #scriptTitle;
  setNameTo: 'script name';
  font: ScriptingSystem fontForNameEditingInScriptor;
  putSelector: #setScriptNameTo:;
  setProperty: #okToTextEdit toValue: true;
  step;
  yourself.
  aBox addMorph: aButton.
  aRow addMorphBack: aBox.
  aBox setBalloonText: 'Click here to edit the name of the script.' translated.
  "aRow addTransparentSpacerOfSize: 9."
  aRow addVariableTransparentSpacer.
 
  "Try It button"
  self hasParameter ifFalse:
  [aRow addMorphBack:
  ((ThreePhaseButtonMorph
  labelSymbol: #TryIt
  target: self
  actionSelector: #tryMe
  arguments: EmptyArray)
  actWhen: #whilePressed;
  balloonTextSelector: #tryMe).
  aRow addTransparentSpacerOfSize: 3].
 
  "Step button"
  self hasParameter ifFalse:
  [aRow addMorphBack: (aButton := ThreePhaseButtonMorph
  labelSymbol: #StepMe
  target: self
  actionSelector: #stepMe
  arguments: EmptyArray).
  aButton balloonTextSelector: #stepMe.
  aRow addTransparentSpacerOfSize: 3].
 
  "Status controller"
  self hasParameter
  ifTrue:
+ [aTile _ TypeListTile new choices: Vocabulary typeChoicesForUserVariables dataType: nil.
- [aTile _ TypeListTile new choices: Vocabulary typeChoices dataType: nil.
  aTile addArrows.
  aTile setLiteral: self typeForParameter.
  aRow addMorphBack: aTile.
  aTile borderColor: Color red.
  aTile color: ScriptingSystem uniformTileInteriorColor.
  aTile setBalloonText: 'Drag from here to get a parameter tile' translated.
  aTile addCaretsAsAppropriate: true]
  ifFalse:
  [aRow addMorphBack: (aStatusMorph _ self scriptInstantiation statusControlMorph)].
 
  "aRow addTransparentSpacerOfSize: 3."
  aRow addVariableTransparentSpacer.
 
  "Gold-box"
  aRow addMorphBack: (goldBoxButton _ IconicButton new).
  goldBoxButton borderWidth: 0;
  labelGraphic: (ScriptingSystem formAtKey: 'RoundGoldBox'); color: Color transparent;
  actWhen: #buttonDown;
  target: self;
  actionSelector: #offerGoldBoxMenu;
  shedSelvedge;
  setBalloonText: 'click here to get a palette of useful tiles to use in your script.' translated.
  aRow addTransparentSpacerOfSize: 6@1.
 
  "Menu Button"
  aButton _ self menuButton.
  aButton actionSelector: #offerScriptorMenu.
  aRow addMorphBack: aButton.
 
  (playerScripted existingScriptInstantiationForSelector: scriptName)
  ifNotNilDo:
  [:inst | inst updateStatusMorph: aStatusMorph].
  ^ aRow!

Item was changed:
  ----- Method: ScriptEditorMorphBuilder>>literal: (in category 'reconstituting scripting tiles ') -----
  literal: sexp
+ "Answer an appropriate tile morph reconstituted from the s-expression provided."
 
  | 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@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)
  setDecimalPlacesFromTypeIn: (sexp attributeAt: #value);
  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).
  ].
+
+ ((Vocabulary allStandardVocabularies select: [:m | m isKindOf: SymbolListType]) includesKey: type)
+ ifTrue:
+ [lit _ sexp attributeAt: #value.
+ s _ SymbolListTile new.
+ s choices: (Vocabulary allStandardVocabularies at: type) choices dataType: type.
+ ^ s setLiteral: lit asSymbol; addArrows]!
- !


_______________________________________________
etoys-dev mailing list
[hidden email]
http://lists.squeakland.org/mailman/listinfo/etoys-dev