not really known
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 
 
 
 

1 lines
32 KiB

'From etoys5.0 of 1 July 2012 [latest update: #2409] on 28 July 2012 at 4:03:37 pm'! !CalendarMorph methodsFor: 'building' stamp: 'bf 6/24/2012 18:06'! dayInitialsRow | newRow | newRow := self newRow. Week dayNames do: [:dayName| newRow addMorphBack: (TextMorph new contentsWrapped: dayName translated first asString; textColor: self labelsDefaultColor; autoFit: false; width: 30; centered; lock)] separatedBy: [newRow addMorphBack: AlignmentMorph newVariableTransparentSpacer]. ^newRow ! ! !ChronologyConstants class methodsFor: 'class initialization' stamp: 'bf 6/24/2012 17:26'! initialize "ChronologyConstants initialize" SqueakEpoch _ 2415386. "Julian day number of 1 Jan 1901" SecondsInDay _ 86400. SecondsInHour _ 3600. SecondsInMinute _ 60. NanosInSecond _ 10 raisedTo: 9. NanosInMillisecond _ 10 raisedTo: 6. DayNames _ #(Sunday Monday Tuesday Wednesday Thursday Friday Saturday) translatedNoop. MonthNames _ #(January February March April May June July August September October November December) translatedNoop. DaysInMonth _ #(31 28 31 30 31 30 31 31 30 31 30 31). ! ! !ColorTileMorph methodsFor: 'event handling' stamp: 'sw 4/25/2012 00:46'! mouseDownPriority "Answer the mouseDown priority." ^ 75! ! !CompoundTileMorph methodsFor: '*etoys-debugger' stamp: 'Richo 3/28/2012 13:02'! evaluateTestPart | condition | condition := testPart tiles at: 1 ifAbsent: [^ true]. ^ Compiler evaluate: condition codeString for: (condition associatedPlayer ifNil: [condition topEditor playerScripted]) logged: false! ! !EToyListenerMorph class methodsFor: 'parts bin' stamp: 'bf 7/26/2012 09:46'! descriptionForPartsBin ^ self partName: 'Listener' translatedNoop categories: #() documentation: 'A tool for receiving things from other Squeak users' translatedNoop! ! !EtoysDebugger methodsFor: 'initialization' stamp: 'sw 6/1/2012 16:55'! delete "If there is a highlighter associated with this debugger, delete it." highlighter ifNotNil: [:h | h stopStepping. h delete]! ! !EtoysDebugger methodsFor: 'evaluating' stamp: 'Richo 3/28/2012 13:03'! evaluateTest: test | tile | test testPart tiles isEmpty ifTrue: [next := test yesPart tiles at: 1 ifAbsent: [test nextTile]. next = test ifTrue: [^ self] ifFalse: [^ self evaluateNextTile]]. self highlight: test testPart. tile := test evaluateTestPart ifTrue: [test yesPart] ifFalse: [test noPart]. next := tile tiles at: 1 ifAbsent: [test nextTile]! ! !ExternalDropHandler class methodsFor: 'class initialization' stamp: 'sw 6/11/2012 17:09'! initialize "Class initialization: initialize the table of registered handlers." "ExternalDropHandler initialize" self resetRegisteredHandlers. self registerHandler: self defaultImageHandler; registerHandler: self defaultGZipHandler; registerHandler: self defaultProjectHandler; registerHandler: self defaultMidiHandler; registerHandler: self defaultMorphHandler.! ! !GetTextExporter methodsFor: 'private' stamp: 'bf 6/24/2012 22:22'! createExtraInformation | extras | extras := OrderedCollection new. #( 'ATTENTION TRANSLATORS!! This should be the name of your language as you would like it to appear in the Languages menu, e.g. "Español" or "English"' 'Language-Name' 'ATTENTION TRANSLATORS!! Put in the directionality of your language, that is "LTR" for left-to-right or "RTL" for right-to-left' 'Language-Direction' ) pairsDo: [:first :second | extras add: (Array with: '' with: first with: second). ]. ^ extras! ! !Morph methodsFor: 'menus' stamp: 'bf 6/24/2012 20:39'! addToggleItemsToHaloMenu: aMenu "Add standard true/false-checkbox items to the memu" #( (resistsRemovalString toggleResistsRemoval 'whether I should be resistant to easy deletion via the pink X handle') (stickinessString toggleStickiness 'whether I should be resistant to a drag done by mousing down on me') (lockedString lockUnlockMorph 'when "locked", I am inert to all user interactions') (hasClipSubmorphsString changeClipSubmorphs 'whether the parts of objects within me that are outside my bounds should be masked.') (hasDirectionHandlesString changeDirectionHandles 'whether direction handles are shown with the halo') (hasDragAndDropEnabledString changeDragAndDrop 'whether I am open to having objects dropped into me') ) translatedNoop do: [:trip | (Preferences eToyFriendly not or: [trip size = 3]) ifTrue: [ aMenu addUpdating: trip first action: trip second. aMenu balloonTextForLastItem: trip third translated ] ]. self couldHaveRoundedCorners ifTrue: [aMenu addUpdating: #roundedCornersString action: #toggleCornerRounding. aMenu balloonTextForLastItem: 'whether my corners should be rounded' translated]! ! !Morph methodsFor: '*MorphicExtras-menus' stamp: 'sw 8/16/2007 13:16'! addMiscExtrasTo: aMenu "Add a submenu of miscellaneous extra items to the menu." | realOwner realMorph subMenu | subMenu _ MenuMorph new defaultTarget: self. (Preferences eToyFriendly not and: [self isWorldMorph not and: [self renderedMorph isSystemWindow not]]) ifTrue: [subMenu add: 'put in a window' translated action: #embedInWindow]. self isWorldMorph ifFalse: [subMenu add: 'adhere to edge...' translated action: #adhereToEdge. subMenu addLine]. realOwner _ (realMorph _ self topRendererOrSelf) owner. (realOwner isKindOf: TextPlusPasteUpMorph) ifTrue: [subMenu add: 'GeeMail stuff...' translated subMenu: (realOwner textPlusMenuFor: realMorph)]. Preferences eToyFriendly ifFalse: [ subMenu add: 'add mouse up action' translated action: #addMouseUpAction; add: 'remove mouse up action' translated action: #removeMouseUpAction; add: 'hand me tiles to fire this button' translated action: #handMeTilesToFire. subMenu addLine. ]. Preferences eToyFriendly ifFalse: [ subMenu add: 'arrowheads on pen trails...' translated action: #setArrowheads. subMenu addLine. ]. subMenu defaultTarget: self topRendererOrSelf. (self isWorldMorph not and: [(self renderedMorph isSystemWindow) not]) ifTrue: [ subMenu add: 'draw new path' translated action: #definePath. subMenu add: 'follow existing path' translated action: #followPath. subMenu add: 'delete existing path' translated action: #deletePath. subMenu addLine. ]. self addGestureMenuItems: subMenu hand: ActiveHand. self isWorldMorph ifFalse: [subMenu add: 'balloon help for this object' translated action: #editBalloonHelpText]. subMenu submorphs isEmpty ifFalse: [ aMenu add: 'extras...' translated subMenu: subMenu ].! ! !NCTextMorphEditor methodsFor: 'menu commands' stamp: 'sw 3/15/2012 21:09'! spawn "Well, don't"! ! !OLPCVirtualSensor methodsFor: 'accessing' stamp: 'bf 6/24/2012 14:40'! primGetNextEvent: array | scale offset | super primGetNextEvent: array. Display isVirtualScreen ifFalse: [^self]. "scale mouse events" (array at: 1) = EventTypeMouse ifTrue:[ offset := Display displayOffset. scale := Display displayScale. array at: 3 put: ((array at: 3) - offset x * scale) truncated. array at: 4 put: ((array at: 4) - offset y * scale) truncated. ]. (array at: 1) = EventTypeDragDropFiles ifTrue:[ scale := Display displayScale. offset := Display displayOffset. array at: 4 put: ((array at: 4) - offset x * scale) truncated. array at: 5 put: ((array at: 5) - offset y * scale) truncated. ].! ! !PaintBoxMorph class methodsFor: 'class initialization' stamp: 'bf 6/24/2012 20:31'! initialize "PaintBoxMorph initialize" Prototype eventHandler: nil. Prototype focusMorph: nil. Prototype stampHolder clear. "clear stamps" Prototype delete. "break link to world, if any" Prototype initializeBrush. AllOnImage _ AllOffImage _ AllPressedImage _ nil. OriginalBounds _ nil. RecentColors _ nil. Preferences addPreference: #singlePixelNib categories: #(painting) default: false balloonHelp: 'when turned on, the smallest pen-size icon in the painting tool represents a single-pixel-wide painting nib; when turned off, that icon represents a three-pixel-wide pen' projectLocal: false changeInformee: PaintBoxMorph changeSelector: #smallestNibSizeChanged. self smallestNibSizeChanged.! ! !PaintBoxMorph class methodsFor: 'instance creation' stamp: 'sw 1/13/2012 01:15'! smallestNibSizeChanged "The user changed the size of the smallest nib in the paint box. Change the prototype(s) to reflect this change." | aWidth aButton | aWidth := Preferences singlePixelNib ifTrue: [1] ifFalse:[3]. self allInstancesDo: [:aPaintBox | aButton := aPaintBox submorphNamed: #brush1:. aButton arguments at: 3 put: (Form dotOfSize: aWidth). aButton doButtonAction]! ! !PasteUpMorph methodsFor: 'misc' stamp: 'sw 6/1/2012 15:45'! prepareToBeSaved "Prepare for export via the ReferenceStream mechanism" | exportDict soundKeyList players stepButton | super prepareToBeSaved. self deleteListeners. turtlePen _ nil. self isWorldMorph ifTrue: [self removeProperty: #scriptsToResume. soundKeyList _ Set new. (players _ self presenter reallyAllExtantPlayers) do: [:aPlayer | aPlayer slotInfo associationsDo: [:assoc | assoc value type == #Sound ifTrue: [soundKeyList add: (aPlayer instVarNamed: assoc key)]]]. players do: [:p | p allScriptEditors do: [:e | e deleteEtoysDebugger. stepButton := e submorphs first submorphs detect: [:m | (m isKindOf: ThreePhaseButtonMorph) and: [m actionSelector = #tryMe]] ifNone: [nil]. stepButton ifNotNil: [stepButton delete]. (e allMorphs select: [:m | m isKindOf: SoundTile]) do: [:aTile | soundKeyList add: aTile literal]]]. "I could of course decompile texutally coded scripts and find out the sounds used there...." (self allMorphs select: [:m | m isKindOf: SoundTile]) do: [:aTile | soundKeyList add: aTile literal]. soundKeyList removeAllFoundIn: SampledSound universalSoundKeys. soundKeyList removeAllSuchThat: [:aKey | (SampledSound soundLibrary includesKey: aKey) not]. soundKeyList isEmpty ifFalse: [exportDict _ Dictionary new. soundKeyList do: [:aKey | exportDict add: (SampledSound soundLibrary associationAt: aKey)]. self setProperty: #soundAdditions toValue: exportDict]. (submorphs select: [:m | m isKindOf: HighlightMorph]) do: [:m | m delete]]! ! !PasteUpMorph methodsFor: '*Etoys-viewing' stamp: 'sw 6/10/2012 23:34'! updateSubmorphThumbnails | thumbsUp itsThumbnail heightForThumbnails maxHeightToAvoidThumbnailing maxWidthForThumbnails | thumbsUp _ self alwaysShowThumbnail. heightForThumbnails _ self heightForThumbnails. maxHeightToAvoidThumbnailing _ self maxHeightToAvoidThumbnailing. maxWidthForThumbnails _ self maximumThumbnailWidth. self submorphs do: [:aMorph | thumbsUp ifTrue: [itsThumbnail _ aMorph representativeNoTallerThan: maxHeightToAvoidThumbnailing norWiderThan: maxWidthForThumbnails thumbnailHeight: heightForThumbnails. (aMorph == itsThumbnail) ifFalse: [self replaceSubmorph: aMorph by: itsThumbnail]] ifFalse: [(aMorph isKindOf: MorphThumbnail) ifTrue: [self replaceSubmorph: aMorph by: aMorph morphRepresented]]]. self invalidRect: self bounds! ! !Player methodsFor: 'scripts-standard' stamp: 'sw 6/10/2012 23:42'! append: aPlayer "Add aPlayer to the list of objects logically 'within' me. This is visually represented by its morph becoming my costume's last submorph. Also allow text to be appended." | aCostume | (aPlayer isNil or: [aPlayer == self]) ifTrue: [^self]. (aPlayer isText or: [aPlayer isString]) ifTrue: [self costume class == TextFieldMorph ifTrue: [^self costume append: aPlayer] ifFalse: [^self]]. (aCostume := self costume topRendererOrSelf) addMorphNearBack: aPlayer costume. aPlayer costume goHome. "assure it's in view" (aCostume isKindOf: PasteUpMorph) ifTrue: [self setCursor: (aCostume submorphs indexOf: aPlayer costume). aCostume updateSubmorphThumbnails] "also forces redraw"! ! !Player methodsFor: 'scripts-standard' stamp: 'sw 6/10/2012 23:39'! includeAtCursor: aPlayer "Add aPlayer to the list of objects logically 'within' me, at my current cursor position. ." | aCostume | (aPlayer isNil or: [aPlayer == self]) ifTrue: [^self]. (aPlayer isText or: [aPlayer isString]) ifTrue: [^ self costume class == TextFieldMorph ifTrue: [self costume append: aPlayer] ifFalse: [self]]. aCostume := self costume topRendererOrSelf. aPlayer costume goHome. "assure it's in view" (aCostume isKindOf: PasteUpMorph) ifTrue: [aCostume addMorph: aPlayer costume asElementNumber: self getCursor. aCostume updateSubmorphThumbnails] "also forces redraw" ifFalse: [aCostume addMorphBack: aPlayer. self setCursor: aCostume submorphs size]! ! !Player methodsFor: 'scripts-standard' stamp: 'sw 6/10/2012 23:45'! prepend: aPlayer "Add aPlayer to the list of objects logically 'within' me. This is visually represented by its morph becoming my costume's first submorph. Also allow text to be prepended." | aCostume | (aPlayer isNil or: [aPlayer == self]) ifTrue: [^self]. (aPlayer isText or: [aPlayer isString]) ifTrue: [^ self costume class == TextFieldMorph ifTrue: [self costume prepend: aPlayer] ifFalse: [self]]. (aCostume := self costume topRendererOrSelf) addMorphFront: aPlayer costume. aPlayer costume goHome. "assure it's in view" (aCostume isKindOf: PasteUpMorph) ifTrue: [self setCursor: (aCostume submorphs indexOf: aPlayer costume). aCostume updateSubmorphThumbnails]! ! !Player methodsFor: '*scratchconnect' stamp: 'ky 4/23/2012 21:20'! sensorUpdate: aString self costume renderedMorph sendScratchCommand: 'sensor-update ' , (aString convertToEncoding: 'UTF8')! ! !Preferences class methodsFor: 'persistence' stamp: 'kks 10/20/2010 21:15'! deletePersistedPreferences | d files | self ensurePersistedPreferencesAccessible ifFalse: [^self]. d := ExternalSettings preferenceDirectory ifNil: [^self]. files := d fileNamesMatching: '*', self persistedFileNameExtension. files size = 0 ifTrue: [^self]. (self confirm: ('This will remove {1} stored preferences. Are you sure?' translated format: {files size})) ifTrue: [files do: [:f | d deleteFileNamed: f]].! ! !QuickGuideMorph methodsFor: 'menu actions' stamp: 'tk 9/13/2010 11:12'! goToCardNamed: cardName | page inner | page _ pages detect: [:p | p guideName = cardName] ifNone: [nil]. page ifNotNil: [self goToPage: (self pageNumberOf: page). (inner := currentPage findA: BookMorph) ifNotNil: [ inner currentPage player ifNotNil: [ inner currentPage player runAllOpeningScripts]]]. ! ! !ScratchClientMorph methodsFor: 'scratch' stamp: 'ky 4/23/2012 21:23'! broadcast: aString | sendString | aString isEmptyOrNil ifTrue: [^ self]. sendString := (aString asString copyReplaceAll: '"' with: '""') convertToEncoding: 'UTF8'. self sendScratchCommand: 'broadcast "' , sendString , '" '! ! !ScratchClientMorph class methodsFor: 'scripting' stamp: 'ky 4/23/2012 21:27'! additionsToViewerCategoryScratchCommand "Answer further viewer additions relating to the Scratch Networking Protocol; these appear in the 'scratch command' category" ^ #('scratch command' #( #(#command #sendValues 'send my variables to Scratch') #(#command #broadcast: 'send a message to Scratch' #String) #(#command #updateSlider: 'sensor-update "slider" to Scratch' #Number) #(#command #updateLight: 'sensor-update "light" to Scratch' #Number) #(#command #updateSound: 'sensor-update "sound" to Scratch' #Number) #(#command #updateResistanceA: 'sensor-update "resistance-A" to Scratch' #Number) #(#command #updateResistanceB: 'sensor-update "resistance-B" to Scratch' #Number) #(#command #updateResistanceC: 'sensor-update "resistance-C" to Scratch' #Number) #(#command #updateResistanceD: 'sensor-update "resistance-D" to Scratch' #Number) #(#command #sensorUpdate: 'sensor-update ["name" value] to Scratch' #String) ) )! ! !ScratchClientMorph class methodsFor: 'parts bin' stamp: 'bf 6/25/2012 14:12'! descriptionForPartsBin ^ self partName: 'Scratch Client' categories: #('Tools' ) documentation: 'Scratch Networking Protocol Client'! ! !ScriptEditorMorph methodsFor: '*etoys-debugger' stamp: 'sw 6/1/2012 15:49'! deleteEtoysDebugger "If present, delete the currently-associated etoysDebugger." | aDebugger | aDebugger := self valueOfProperty: #etoysDebugger ifAbsent: [^ self]. aDebugger delete. "removes the highlighter from the world" self removeProperty: #etoysDebugger! ! !SketchMorph methodsFor: 'e-toy support' stamp: 'bf 6/23/2012 20:35'! rotationStyle: aSymbol "Set my rotation style to #normal, #leftRight, #upDown, or #none. Styles mean: #normal -- continuous 360 degree rotation #leftRight -- quantize angle to left or right facing #upDown -- quantize angle to up or down facing #none -- do not rotate Because my rendering code flips the form (see generateRotatedForm) we 'pre-flip' it here to preserve the same visual appearance. " | wasFlippedX wasFlippedY isFlippedX isFlippedY | wasFlippedX := rotationStyle == #leftRight and: [ self heading asSmallAngleDegrees < 0.0 ]. wasFlippedY := rotationStyle == #upDown and: [ self heading asSmallAngleDegrees abs > 90.0 ]. rotationStyle _ aSymbol. isFlippedX := rotationStyle == #leftRight and: [ self heading asSmallAngleDegrees < 0.0 ]. isFlippedY := rotationStyle == #upDown and: [ self heading asSmallAngleDegrees abs > 90.0 ]. wasFlippedX == isFlippedX ifFalse: [self form: (self form flipBy: #horizontal centerAt: self form center)]. wasFlippedY == isFlippedY ifFalse: [self form: (self form flipBy: #vertical centerAt: self form center)]. self layoutChanged. ! ! !SketchMorph methodsFor: 'geometry eToy' stamp: 'bf 6/23/2012 20:26'! setDirectionFrom: aPoint "This is called when changing the forward direction by the halo arrow. If rotationStyle is set to flipping, the rendering code flips the form (see generateRotatedForm). We 'pre-flip' it here because otherwise there would be no way to actually set the forward direction without having the object visually flip while doing so." | wasFlipped isFlipped | rotationStyle == #leftRight ifTrue: [wasFlipped := self heading asSmallAngleDegrees < 0.0 ]. rotationStyle == #upDown ifTrue: [wasFlipped := self heading asSmallAngleDegrees abs > 90.0 ]. super setDirectionFrom: aPoint. rotationStyle == #leftRight ifTrue: [isFlipped := self heading asSmallAngleDegrees < 0.0. wasFlipped == isFlipped ifFalse: [self form: (self form flipBy: #horizontal centerAt: self form center)]]. rotationStyle == #upDown ifTrue: [isFlipped := self heading asSmallAngleDegrees abs > 90.0. wasFlipped == isFlipped ifFalse: [self form: (self form flipBy: #vertical centerAt: self form center)]] ! ! !SugarLauncher methodsFor: 'datastore' stamp: 'bf 6/4/2012 15:06'! handleStream: tmpStream mimetype: mimetypeOrNil titled: title "tmpStream was opened from journal or other media. For simplicity, we re-use the file drop logic." ActiveHand lastEvent position: World center. [ [(ExternalDropHandler lookupExternalDropHandler: tmpStream) handle: tmpStream in: World dropEvent: ActiveHand lastEvent] ifError: [self inform: ('Cannot open {1}' translated format: {title})] ] ensure: [tmpStream ifNotNil: [tmpStream close]].! ! !SugarLauncher methodsFor: 'chooser' stamp: 'bf 6/4/2012 15:14'! chooser: chooserId response: objectIdOrPath self chooserDone: chooserId. WorldState addDeferredUIMessage: [ (objectIdOrPath beginsWith: '/') ifTrue: [ | path file title | path := objectIdOrPath utf8ToSqueak. file := FileStream readOnlyFileNamed: path. title := FileDirectory localNameFor: path. self handleStream: file mimetype: nil titled: title] ifFalse: [ | props title mimetype | props := self getProperties: objectIdOrPath. title := props at: 'title' ifAbsent: ['untitled' translated]. mimetype := props at: 'mime_type' ifAbsent: ['']. [self open: objectIdOrPath title: title mimetype: mimetype] on: SugarPropertiesNotification do: [:ex | ex resume: props]]].! ! !SugarLauncher methodsFor: 'chooser' stamp: 'bf 6/4/2012 14:59'! open: id title: titleString mimetype: mimeString | file | Utilities informUser: 'Opening journal entry' translated, String cr, (titleString copyReplaceAll: String lf with: String cr) during: [file := self getFile: id]. self handleStream: file mimetype: mimeString titled: titleString.! ! !ThreePhaseButtonMorph methodsFor: 'button' stamp: 'sw 1/13/2012 01:22'! doButtonAction "Perform the action of this button. Subclasses may override this method. The default behavior is to send the button's actionSelector to its target object with its arguments." | args | (target notNil and: [actionSelector notNil]) ifTrue: [args := actionSelector numArgs > arguments size ifTrue: [arguments copyWith: ActiveEvent] ifFalse: [arguments]. Cursor normal showWhile: [target perform: actionSelector withArguments: args]. target isMorph ifTrue: [target changed]]! ! !TimesRepeatTile methodsFor: 'localization' stamp: 'Richo 5/29/2012 18:11'! localeChanged "Hack to allow the times repeat to update when locale changes" self labelMorphs first contents: 'Repeat' translated. self labelMorphs second contents: (' ', ('times' translated), ' '). self labelMorphs third contents: 'Do' translated ! ! !TranslatedReceiverFinder methodsFor: 'accessing' stamp: 'bf 6/24/2012 18:17'! findWordsWith: aSymbol in: aMethodReference "Find words for translation with the symbol in a method. See LanguageEditorTest >>testFindTranslatedWords" "| message | message := MethodReference new setStandardClass: Morph class methodSymbol: #supplementaryPartsDescriptions. self new findWordsWith: #translatedNoop in: message" | messages keywords aParseNode | aParseNode := aMethodReference decompile. "Find from string literal" messages := Set new. self search: aSymbol messageNode: aParseNode addTo: messages. keywords := OrderedCollection new. messages select: [:aMessageNode | aMessageNode receiver isMemberOf: LiteralNode] thenDo: [:aMessageNode | (self stringsIn: aMessageNode receiver key addTo: keywords) ifFalse: [self symbolsIn: aMessageNode receiver key addTo: keywords]]. "Find from array literal" self arraySearch: aSymbol messageNode: aParseNode addTo: keywords. ^ keywords! ! !TranslatedReceiverFinder methodsFor: 'private' stamp: 'bf 6/24/2012 17:55'! stringsIn: aLiteral addTo: aCollection "deeply find strings in aLiteral, add them to aCollection, answer true if any found" | found | found := false. aLiteral literalStringsDo: [:literal | found := true. aCollection add: literal]. ^found! ! !TranslatedReceiverFinder methodsFor: 'private' stamp: 'bf 6/24/2012 17:52'! symbolsIn: aLiteral addTo: aCollection "if no strings were found in aLiteral, but it was marked as translatable, use the symbols" aLiteral isSymbol ifTrue: [aCollection add: aLiteral]. aLiteral isArray ifTrue: [ aLiteral do: [:each | self symbolsIn: each addTo: aCollection]]. ! ! !ViewerFlapTab methodsFor: 'accessing' stamp: 'sw 6/5/2012 22:56'! okayToResizeEasily "Answer whether it is appropriate to have the receiver be easily resized by the user from the halo" ^ false! ! !ViewerFlapTab methodsFor: 'accessing' stamp: 'sw 6/5/2012 22:46'! okayToRotateEasily "Answer whether it is appropriate for a rotation handle to be shown for the receiver. " ^ false! ! !WatcherWrapper methodsFor: 'initialization' stamp: 'sw 3/28/2012 15:05'! buildForPlayer: aPlayer getter: aGetter "Build up basic structure" | aColor interface | interface := Vocabulary eToyVocabulary methodInterfaceAt: aGetter ifAbsent: [nil]. self setProperty: #getter toValue: aGetter. variableName := interface ifNotNil: [interface wording] ifNil: [Utilities inherentSelectorForGetter: aGetter]. self player: aPlayer variableName: variableName. aColor := self detailedWatcherColor. self listDirection: #leftToRight; hResizing: #shrinkWrap; vResizing: #shrinkWrap; color: aColor; layoutInset: -1; borderWidth: 1; borderColor: aColor darker; listCentering: #center. self addMorphBack: (self buildReadout: aGetter)! ! !WatcherWrapper methodsFor: 'accessing' stamp: 'sw 3/28/2012 15:16'! getter "Answer the selector that serves as the getter for this watcher." ^ self valueOfProperty: #getter ifAbsent: [Utilities getterSelectorFor: variableName]! ! !WatcherWrapper methodsFor: 'accessing' stamp: 'sw 3/28/2012 15:18'! getterTilesForDrop "Answer getter tiles to use if there is an attempt to drop me onto a tile pad" | aCategoryViewer | aCategoryViewer _ CategoryViewer new initializeFor: player categoryChoice: #basic. ^ aCategoryViewer getterTilesFor: self getter type: self resultType! ! !WatcherWrapper methodsFor: 'accessing' stamp: 'sw 3/28/2012 15:16'! resultType "Answer the result type the receiver would produce." ^ player typeForSlotWithGetter: self getter! ! !WaveEditor methodsFor: 'initialization' stamp: 'bf 6/25/2012 11:20'! addControls | slider aWrapper m aButton | aWrapper := AlignmentMorph newRow. aWrapper color: Color transparent; borderWidth: 0; layoutInset: 0. aWrapper hResizing: #shrinkWrap; vResizing: #shrinkWrap; extent: 5 @ 5. aWrapper wrapCentering: #topLeft. aButton := self buttonName: 'X' action: #delete. aButton setBalloonText: 'Close WaveEditor' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Menu' translated action: #invokeMenu. aButton setBalloonText: 'Open a menu' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Play' translated action: #play. aButton setBalloonText: 'Play sound' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Play Before' translated action: #playBeforeCursor. aButton setBalloonText: 'Play before cursor' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Play After' translated action: #playAfterCursor. aButton setBalloonText: 'Play after cursor' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Play Loop' translated action: #playLoop. aButton setBalloonText: 'Play the loop' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Test' translated action: #playTestNote. aButton setBalloonText: 'Test the note' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Save' translated action: #saveInstrument. aButton setBalloonText: 'Save the sound' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Set Loop End' translated action: #setLoopEnd. aButton setBalloonText: 'Set loop end at cursor' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Set One Cycle' translated action: #setOneCycle. aButton setBalloonText: 'Set one cycle' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. aButton := self buttonName: 'Set Loop Start' translated action: #setLoopStart. aButton setBalloonText: 'Set the loop start at cursor' translated. aWrapper addMorphBack: aButton. aWrapper addTransparentSpacerOfSize: 4 @ 1. self addMorphBack: aWrapper. aWrapper := AlignmentMorph newRow. aWrapper color: self color; borderWidth: 0; layoutInset: 0. aWrapper hResizing: #spaceFill; vResizing: #rigid; extent: 5 @ 20; wrapCentering: #center; cellPositioning: #leftCenter. m := StringMorph new contents: 'Index: ' translated; font: Preferences standardEToysButtonFont. aWrapper addMorphBack: m. m := UpdatingStringMorph new target: graph; getSelector: #cursor; putSelector: #cursor:; font: Preferences standardEToysButtonFont; growable: false; width: 71; step. aWrapper addMorphBack: m. m := StringMorph new contents: 'Value: ' translated; font: Preferences standardEToysButtonFont. aWrapper addMorphBack: m. m := UpdatingStringMorph new target: graph; getSelector: #valueAtCursor; putSelector: #valueAtCursor:; font: Preferences standardEToysButtonFont; growable: false; width: 50; step. aWrapper addMorphBack: m. slider := SimpleSliderMorph new color: color; extent: 200 @ 10; target: self; actionSelector: #scrollTime:. aWrapper addMorphBack: slider. m := Morph new color: aWrapper color; extent: 10 @ 5. "spacer" aWrapper addMorphBack: m. m := UpdatingStringMorph new target: graph; getSelector: #startIndex; putSelector: #startIndex:; font: Preferences standardEToysButtonFont; width: 40; step. aWrapper addMorphBack: m. self addMorphBack: aWrapper! ! !WebCamMorph class methodsFor: 'scripting' stamp: 'bf 6/24/2012 20:38'! additionsToViewerCategories "Answer a list of (<categoryName> <list of category specs>) pairs that characterize the phrases this kind of morph wishes to add to various Viewer categories." ^ #( (#'camera' ( (slot resolution '160x120, 320x240 or 640x480' WebCamResolution readWrite Player getWebCamResolution Player setWebCamResolution:) (slot cameraIsOn 'Whether the camera is on/off' Boolean readWrite Player getWebCamIsOn Player setWebCamIsOn:) (slot useFrameSize 'Resize the player to match the camera''s frame size' Boolean readWrite Player getUseFrameSize Player setUseFrameSize:) (slot lastFrame 'A player with the last frame' Player readOnly Player getLastFrame unused unused) )) ) ! ! 'From etoys5.0 of 19 March 2012 [latest update: #2403] on 26 March 2012 at 10:16:06 pm'! | cont | (Smalltalk includesKey: #MorphExtensionPlus) ifFalse: [self inform: 'This project cannot be loaded into an older system.\Please use an OLPC Etoys compatible image.' translated withCRs. cont _ thisContext. [cont notNil] whileTrue: [ cont selector == #handleEvent: ifTrue: [cont return: nil]. cont _ cont sender. ]]! | cont | (Smalltalk includesKey: #CalendarMorph) ifFalse: [(self confirm: 'This project was created from a more recent\version of Etoys, and may not load or\work properly in an older system.\Ideally use Etoys 5.0 or newer\proceed anyway?' translated withCRs) ifFalse: [cont _ thisContext. [cont notNil] whileTrue: [ cont selector == #handleEvent: ifTrue: [cont return: nil]. cont _ cont sender. ]]]! ----End fileIn of a stream----! 'From etoys5.0 of 26 March 2012 [latest update: #2403] on 26 March 2012 at 11:16:46 pm'! | cont | (Smalltalk includesKey: #MorphExtensionPlus) ifFalse: [self inform: 'This project cannot be loaded into an older system.\Please use an OLPC Etoys compatible image.' translated withCRs. cont _ thisContext. [cont notNil] whileTrue: [ cont selector == #handleEvent: ifTrue: [cont return: nil]. cont _ cont sender. ]]! | cont | (Smalltalk includesKey: #CalendarMorph) ifFalse: [(self confirm: 'This project was created from a more recent\version of Etoys, and may not load or\work properly in an older system.\Ideally use Etoys 5.0 or newer\proceed anyway?' translated withCRs) ifFalse: [cont _ thisContext. [cont notNil] whileTrue: [ cont selector == #handleEvent: ifTrue: [cont return: nil]. cont _ cont sender. ]]]! ----End fileIn of a stream----! 'From etoys4.1 of 13 October 2010 [latest update: #2390] on 18 May 2011 at 6:42:04 pm'! | cont | (Smalltalk includesKey: #MorphExtensionPlus) ifFalse: [self inform: 'This project cannot be loaded into an older system.\Please use an OLPC Etoys compatible image.' translated withCRs. cont _ thisContext. [cont notNil] whileTrue: [ cont selector == #handleEvent: ifTrue: [cont return: nil]. cont _ cont sender. ]]! Player subclass: #Player192 instanceVariableNames: 'projectName' classVariableNames: '' poolDictionaries: '' category: 'UserObjects'! !Player192 methodsFor: 'access'! getProjectName ^ projectName! ! !Player192 methodsFor: 'access'! setProjectName: t1 projectName := t1! ! ----End fileIn of a stream----! ReleaseBuilderSqueakland new prepareReleaseImage.! ----QUIT----#(28 July 2012 4:04:43 pm) etoys.image priorSource: 30079!