-
Notifications
You must be signed in to change notification settings - Fork 11
/
Copy pathScratchOnIPad.cs
8777 lines (7051 loc) · 315 KB
/
ScratchOnIPad.cs
1
'From MIT Squeak 0.9.4 (June 1, 2003) [No updates present.] on 24 May 2023 at 11:58:39 pm'!Object subclass: #IPhoneMenu instanceVariableNames: 'menuItemsActions cSCAlertListDialog target iPhoneSemaphore menuDialog ' classVariableNames: '' poolDictionaries: '' category: 'iPhoneScratchSupport'!Object subclass: #IPhonePresentationSpaceKeyState instanceVariableNames: '' classVariableNames: 'CommandPressed ShiftPressed MaxUnclaimedKeystrokeSize ' poolDictionaries: '' category: 'Scratch-Proxy'!ObjectiveCSqueakProxy subclass: #IPhoneScratchProxy instanceVariableNames: 'projectPicked projectData scratchMorphic projectPickedRun startMutex microbitAccessor photoPickerQueue meshHandlingQueue workingMorph sensorAccessor projectOpenCount isInPresentation ' classVariableNames: 'ExitPresentationMode MouseClickProcessHandler SqueakProxy StopScratchProject ' poolDictionaries: '' category: 'Scratch-Proxy'!IPhoneScratchProxy class instanceVariableNames: 'isActive delegate '!Object subclass: #MorphicEvent instanceVariableNames: 'type timestamp cursorPoint buttons keyValue unicodeChar sourceHand reserved ' classVariableNames: '' poolDictionaries: '' category: 'Morphic-Support'!HandleMorph subclass: #NewHandleMorph instanceVariableNames: 'hand offset lastPointBlock waitingForClickInside startedAt ' classVariableNames: 'LastClosedAt ' poolDictionaries: '' category: 'Morphic-Widgets'!DialogBoxMorph subclass: #ScratchFileChooserDialog instanceVariableNames: 'scratchFrame list choosingFolder newFileTitle newFileName thumbnailFrameMorph thumbnailMorph authorLabelMorph authorMorph commentLabelMorph commentMorph readingScratchFile type newTitleBin forSave ' classVariableNames: 'LastFolderForType UserHomeFolder ' poolDictionaries: '' category: 'Scratch-UI-Dialogs'!ImageFrameMorph subclass: #ScratchFilePicker instanceVariableNames: 'directoryBarMorph contentsPaneMorph feedbackMorph scratchInfoClient currentDir extensions fetchInProgress showThumbnails thumbnailFetchProcess scratchServers scratchProjectFetcher lastUpMSecs wasSelected isDoubleClick sound finalSelection freezeFocus topBarMorph directoryBarArrowMorph loadedSampledSound initialParentDirectory forSave presetParentDirectory ' classVariableNames: '' poolDictionaries: '' category: 'Scratch-UI-Dialogs'!ScrollFrameMorph subclass: #ScrollFrameMorph2 instanceVariableNames: 'scrollBarStartInset scrollBarEndInset prevCursorPoint handlesMouseEvents ' classVariableNames: '' poolDictionaries: '' category: 'Scratch-UI-Support'!Object subclass: #SoiActivityIndicator instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ScratchOnIPad'!Object subclass: #SoiJobQueue instanceVariableNames: 'sharedQueue priority watcherProcess ' classVariableNames: '' poolDictionaries: '' category: 'ScratchOnIPad'!Object subclass: #SoiMIDISynth instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ScratchOnIPad'!SoiMIDISynth class instanceVariableNames: 'delegate '!Object subclass: #SoiMeshStats instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ScratchOnIPad'!SoiMeshStats class instanceVariableNames: 'connectionResults '!Object subclass: #SoiNotificationCenter instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ScratchOnIPad'!Object subclass: #SoiSettings instanceVariableNames: 'settingsDict ' classVariableNames: '' poolDictionaries: '' category: 'ScratchOnIPad'!SoiSettings class instanceVariableNames: 'default '!Object subclass: #SoiTouchCursor instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ScratchOnIPad'!SoiTouchCursor class instanceVariableNames: 'delegate '!Object subclass: #SoiUtils instanceVariableNames: '' classVariableNames: 'DefaultSprite ' poolDictionaries: '' category: 'ScratchOnIPad'!SoiUtils class instanceVariableNames: 'aboutMediaContents aboutMediaTitle aboutSamplesContents aboutSamplesTitle quarterModeBackgroundColor aboutContents aboutTitle quarterModeDrawExtent '!SimpleButtonMorph subclass: #ToggleButton instanceVariableNames: 'onForm offForm overForm disabledForm isMomentary toggleMode isOn isDisabled isOver wasOn alphaOn ignoreTransparentArea ' classVariableNames: '' poolDictionaries: '' category: 'Scratch-UI-Support'!!Object methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 00:14'!asFileDirectory ^ FileDirectory on: self asString! !!Object methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 15:48'!nslog self asString nslog! !!Object methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 15:48'!nslog: mark self asString nslog: mark! !!BlockContext methodsFor: '*ScratchOnIPad-activityIndication' stamp: 'mu 6/19/2014 22:29'!showIndicator ^ SoiActivityIndicator showWhile: self! !!Canvas methodsFor: 'drawing-images' stamp: 'mu 9/17/2014 13:33'!paintImage: aForm at: aPoint "Draw the given Form, which is assumed to be a Form or ColorForm following the convention that zero is the transparent pixel value." aForm ifNil: [^self]. self paintImage: aForm at: aPoint sourceRect: aForm boundingBox! !!Debugger methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/22/2014 21:17'!openNotifierContents: msgString label: label "Create and schedule a notifier view with the given label and message. A notifier view shows just the message or the first several lines of the stack, with a menu that allows the user to open a full debugger if so desired." "NOTE: When this method returns, a new process has been scheduled to run the windows, and thus this notifier, but the previous active porcess has not been suspended. The sender will do this." | msg topView p | Sensor flushKeyboard. savedCursor _ Cursor currentCursor. Cursor normal show. msg _ msgString. (label beginsWith: 'Space is low') ifTrue: [IPhoneScratchProxy isActive ifTrue: [IPhoneScratchProxy onVmSpaceIsLow. ^self]. msg _ self lowSpaceChoices, msgString]. Smalltalk isMorphic ifTrue: [self buildMorphicNotifierLabelled: label message: msg. ^ Project current spawnNewProcessIfThisIsUI: interruptedProcess]. Display fullScreen. topView _ self buildMVCNotifierViewLabel: label message: msg minSize: 350@((14 * 5) + 16 + self optionalButtonHeight). ScheduledControllers activeController ifNil: [p _ Display boundingBox center] ifNotNil: [p _ ScheduledControllers activeController view displayBox center]. topView controller openNoTerminateDisplayAt: (p max: (200@60)). ^ topView! !!Dictionary methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 6/1/2014 12:09'!at: key ifPresent: aBlock ifAbsent: absentBlock | v | v _ self at: key ifAbsent: [^ absentBlock value]. ^ aBlock value: v! !!FileDirectory methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 00:13'!asFileDirectory ^self! !!FileDirectory methodsFor: '*ScratchOnIPad' stamp: 'mu 4/28/2017 10:18'!asciiFileExists: filenameOrPath "Answer true if a file of the given name exists. The given name may be either a full path name or a local file within this directory." "FileDirectory default fileExists: Smalltalk sourcesName" | fName dir | FileDirectory splitName: filenameOrPath to: [:filePath :name | fName _ name. filePath isEmpty ifTrue: [dir _ self] ifFalse: [dir _ FileDirectory on: filePath]]. fName isUnicode ifTrue: [fName _ String withAll: fName asUTF8]. self isCaseSensitive ifTrue: [^ dir fileNames includes: fName] ifFalse: [^ dir fileNames anySatisfy: [:name| name sameAs: fName]]. ! !!FileDirectory methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 00:11'!belongTo: aFileDirectory ^aFileDirectory hasChild: self! !!FileDirectory methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 02:00'!exists | path | path := self pathName. ^ self directoryExists: path! !!FileDirectory methodsFor: '*ScratchOnIPad' stamp: 'mu 6/6/2014 00:16'!fileEntries ^ self entries reject: [:each | each isDirectory]! !!FileDirectory methodsFor: '*ScratchOnIPad' stamp: 'mu 4/30/2015 17:39'!hasChild: aFileDirectory | childPathName myPathName | childPathName := aFileDirectory pathNameTrimmed. myPathName := self pathNameTrimmed. childPathName size > myPathName size ifFalse: [^false]. ^childPathName beginsWith: myPathName! !!FileDirectory methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 00:24'!isDirectParentOf: childDir (self hasChild: childDir) ifFalse: [^false]. (childDir pathParts size - self pathParts size) = 1 ifTrue: [^true]. ^false! !!FileDirectory methodsFor: '*ScratchOnIPad' stamp: 'mu 6/6/2014 00:19'!latestFileMatches: matchString | candidates | candidates := self fileEntries select: [:each | matchString match: each name]. ^ (candidates sort: [:a :b | a creationTime < b creationTime]) lastOrNil! !!FileDirectory methodsFor: '*ScratchOnIPad' stamp: 'mu 4/30/2015 17:38'!pathNameTrimmed ^self pathName pathNameTrimmed! !!FileDirectory methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/7/2017 14:43'!fileExists: filenameOrPath "Answer true if a file of the given name exists. The given name may be either a full path name or a local file within this directory." "FileDirectory default fileExists: Smalltalk sourcesName" | fName dir utils nsFileName nsPathName result | (IPhoneScratchProxy isActive not or: [filenameOrPath isAsciiString]) ifTrue: [^self asciiFileExists: filenameOrPath]. FileDirectory splitName: filenameOrPath to: [:filePath :name | fName := name. filePath isEmpty ifTrue: [dir := self] ifFalse: [dir := FileDirectory on: filePath]]. fName isEmptyOrNil ifTrue: [^false]. utils := ObjectiveCBridge classObjectForName: 'SUYUtils'. nsFileName := fName asNSStringUTF8. nsPathName := dir pathName asNSStringUTF8. result := [utils fileExists: nsFileName inDirectory: nsPathName] ifError: [0]. nsFileName isNil ifFalse: [nsFileName release]. nsPathName isNil ifFalse: [nsPathName release]. ^result > 0! !!FileDirectory methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/11/2015 13:30'!setMacFileNamed: fileName type: typeString creator: creatorString "Set the Macintosh file type and creator info for the file with the given name. Fails if the file does not exist or if the type and creator type arguments are not strings of length 4. Does nothing on other platforms (where the underlying primitive is a noop)." "FileDirectory default setMacFileNamed: 'foo' type: 'TEXT' creator: 'ttxt'" [self primSetMacFileNamed: (self fullNameFor: fileName) type: typeString creator: creatorString] ifError: [] "Ignore the error - it is for OLD Mac OS, anyway"! !!Form methodsFor: '*ScratchOnIPad-override-fileIn/Out' stamp: 'mu 4/17/2017 13:15'!writeBMPFileNamed: fName "Display writeBMPfileNamed: 'display.bmp'" | fileName bhSize biSize biClrUsed bfOffBits rowBytes biSizeImage f colorValues rgb data | self unhibernate. depth = 2 ifTrue: [(self asFormOfDepth: 4) writeBMPFileNamed: fName. ^ self]. depth = 16 ifTrue: [(self asFormOfDepth: 32) writeBMPFileNamed: fName. ^ self]. (#(1 4 8 32) includes: depth) ifFalse: [self error: 'BMP file depth must be 1, 4, 8, or 32']. ((fileName _ fName) asLowercase endsWith: '.bmp') ifFalse: [fileName _ fName , '.bmp']. bhSize _ 14. "# bytes in file header" biSize _ 40. "info header size in bytes" biClrUsed _ depth = 32 ifTrue: [0] ifFalse: [1 << depth]. "number of color table entries" bfOffBits _ biSize + bhSize + (4*biClrUsed). rowBytes _ ((depth min: 24) * width + 31 // 32) * 4. biSizeImage _ height * rowBytes. f _ StandardFileStream newScratchFileNamed: fileName. f ifNil: [^ self]. f binary. "write the file header" f position: 0. f littleEndianUint16: 19778. "bfType = BM" f littleEndianUint32: bfOffBits + biSizeImage. "total file size in bytes" f littleEndianUint32: 0. "bfReserved" f littleEndianUint32: bfOffBits. "offset of bitmap data from start of hdr (and file)" "write the bitmap info header" f position: bhSize. f littleEndianUint32: biSize. "info header size in bytes" f littleEndianUint32: width. "biWidth" f littleEndianUint32: height. "biHeight" f littleEndianUint16: 1. "biPlanes" f littleEndianUint16: (depth min: 24). "biBitCount" f littleEndianUint32: 0. "biCompression" f littleEndianUint32: biSizeImage. "size of image section in bytes" f littleEndianUint32: 2800. "biXPelsPerMeter" f littleEndianUint32: 2800. "biYPelsPerMeter" f littleEndianUint32: biClrUsed. f littleEndianUint32: 0. "biClrImportant" biClrUsed > 0 ifTrue: [ "write color map; this works for ColorForms, too" colorValues _ self colormapIfNeededForDepth: 32. 1 to: biClrUsed do: [:i | rgb _ colorValues at: i. 0 to: 24 by: 8 do: [:j | f nextPut: (rgb >> j bitAnd: 16rFF)]]]. ' ==> ' displayProgressAt: Sensor cursorPoint from: 1 to: height during: [:bar | 1 to: height do: [:i | bar value: i. data _ (self copy: (0@(height-i) extent: width@1)) bits. depth = 32 ifTrue: [ 1 to: data size do: [:j | f littleEndianUint24: ((data at: j) bitAnd: 16rFFFFFF)]. 1 to: (data size*3)+3//4*4-(data size*3) do: [:j | f nextPut: 0 "pad to 32-bits"]] ifFalse: [ 1 to: data size do: [:j | f int32: (data at: j)]]]]. f position = (bfOffBits + biSizeImage) ifFalse: [self halt]. f close.! !!Cursor methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 9/15/2017 16:32'!showNotifying: tag while: aBlock | value | IPhoneScratchProxy isActive ifFalse: [^self showWhile: aBlock]. SoiTouchCursor show: tag. value := aBlock value. SoiTouchCursor hide. ^ value! !!IPhoneMenu methodsFor: 'initialize' stamp: 'mu 4/16/2014 23:36'!add: aString action: aSymbol ^self add: aString suffix: '' action: aSymbol! !!IPhoneMenu methodsFor: 'initialize' stamp: 'mu 4/28/2014 01:19'!add: aString suffix: suffix action: aSymbol | labelString buttonTitleOop | labelString := aString localized, suffix. menuItemsActions add: {aSymbol. labelString}."labelString nslog: 'menu added'." buttonTitleOop := labelString asNSStringUTF8. ObjectiveCBridge performSelectorOnMainThread: [menuDialog addButtonWithTitle: buttonTitleOop]. buttonTitleOop release.! !!IPhoneMenu methodsFor: 'initialize' stamp: 'mu 4/16/2014 23:36'!addWithEllipsis: aString action: aSymbol ^self add: aString suffix: '...' action: aSymbol! !!IPhoneMenu methodsFor: 'initialize' stamp: 'mu 4/18/2014 00:25'!initialize | menuDialogClassOop titleOop semaIndex | super initialize. menuItemsActions := OrderedCollection new. menuDialogClassOop _ ObjectiveCBridge classObjectForName: 'SUYMenuDialog'. titleOop := 'Menu' asNSString. iPhoneSemaphore := Semaphore new. semaIndex := Smalltalk registerExternalObject: iPhoneSemaphore. ObjectiveCBridge performSelectorOnMainThread: [menuDialog := menuDialogClassOop alloc initTitle: titleOop message: nil asObjc semaIndex: semaIndex]. titleOop release.! !!IPhoneMenu methodsFor: 'initialize' stamp: 'mu 6/21/2014 01:03'!showAndTarget: aTarget | resultIndex action | target := aTarget. ObjectiveCBridge performSelectorOnMainThread: [menuDialog showInView: IPhoneScratchProxy delegate scratchPlayView]. iPhoneSemaphore wait. Smalltalk unregisterExternalObject: iPhoneSemaphore. resultIndex := menuDialog resultIndex + 1. action := (menuItemsActions at: resultIndex ifAbsent: [ resultIndex asString nslog: 'no such menu item at:'. #(#yourself)]) first. ObjectiveCBridge performSelectorOnMainThread: [menuDialog release]. [target perform: action] fork. ! !!IPhonePresentationSpaceKeyState class methodsFor: 'testing' stamp: 'mu 5/10/2014 02:14'!isCommandPressed ^ CommandPressed = 1! !!IPhonePresentationSpaceKeyState class methodsFor: 'testing' stamp: 'mu 5/10/2014 02:14'!isShiftPressed ^ ShiftPressed = 1! !!IPhonePresentationSpaceKeyState class methodsFor: 'accessing' stamp: 'mu 5/10/2014 02:12'!commandPressed ^ CommandPressed! !!IPhonePresentationSpaceKeyState class methodsFor: 'accessing' stamp: 'mu 5/10/2014 02:12'!commandPressed: anInteger CommandPressed := anInteger! !!IPhonePresentationSpaceKeyState class methodsFor: 'accessing' stamp: 'mu 8/27/2014 23:47'!maxUnclaimedKeystrokeSize ^MaxUnclaimedKeystrokeSize! !!IPhonePresentationSpaceKeyState class methodsFor: 'accessing' stamp: 'mu 8/28/2014 00:17'!maxUnclaimedKeystrokeSize: anInteger MaxUnclaimedKeystrokeSize := anInteger.! !!IPhonePresentationSpaceKeyState class methodsFor: 'accessing' stamp: 'mu 5/10/2014 02:13'!shiftPressed ^ ShiftPressed! !!IPhonePresentationSpaceKeyState class methodsFor: 'accessing' stamp: 'mu 5/10/2014 02:12'!shiftPressed: anInteger ShiftPressed := anInteger! !!IPhonePresentationSpaceKeyState class methodsFor: 'class initialization' stamp: 'mu 8/28/2014 00:17'!initMaxUnclaimedKeystrokeSize MaxUnclaimedKeystrokeSize := 10.! !!IPhonePresentationSpaceKeyState class methodsFor: 'class initialization' stamp: 'mu 8/27/2014 23:47'!initialize "IPhonePresentationSpaceKeyState initialize" CommandPressed := ShiftPressed := 0. self initMaxUnclaimedKeystrokeSize! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-events' stamp: 'MU 4/1/2021 22:11'!onProjectOpened sensorAccessor := nil. microbitAccessor := nil. IPhoneScratchProxy delegate presentationSpace postOpen. self incrementProjectOpenCount. self showStartLog. self becomeActive! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-events' stamp: 'mu 7/24/2014 16:01'!onVmSpaceIsLow self basicRestartVm! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-events' stamp: 'mu 7/9/2014 22:34'!scratchDialogClosed: sender self class isActive ifFalse: [^self]. SoiNotificationCenter postNofification: 'ScratchDialogClosed'. self scratchMorphic enableInteractions! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-events' stamp: 'mu 7/9/2014 22:34'!scratchDialogOpened: sender self class isActive ifFalse: [^self]. SoiNotificationCenter postNofification: 'ScratchDialogOpened'. self scratchMorphic disableInteractions! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/3/2017 13:16'!openProjectForPresentation: pd runProject: runProject | projectFileName | projectFileName := pd asString. projectFileName isEmpty ifFalse: [^ self basicOpenProject: projectFileName]. self loadWhenAutoSavedProjectFound. self onProjectOpened.! !!IPhoneScratchProxy methodsFor: 'processing' stamp: 'mu 7/15/2014 17:19'!showStartLog [ ScratchTranslator primLanguage nslog: 'primLanguage'. "DisplayScreen actualScreenSize asString nslog: 'actualScreenSize'." SoiSettings helpDir asString nslog: 'helpDir'. ScratchFileChooserDialog userScratchProjectsDir asString nslog: 'userScratchProjectsDir'. ] fork.! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 7/4/2022 23:59'!becomeActive self becomeActiveAfter: 1000! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 11/4/2022 15:10'!becomeActiveAfter: msecs [(Delay forMilliseconds: msecs) wait. self restoreDisplay. self restoreMeshIfNeeded. 'Scratch' nslog: 'becomeActive'] fork.! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 1/26/2018 14:34'!becomeBackground [scratchMorphic ifNotNil: [scratchMorphic midiAllNotesOff]. SoundPlayer primSoundStop. 'Scratch' nslog: 'becomeBackground'] fork.! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/22/2014 21:19'!cleanUp | oldLeft newLeft | oldLeft := Smalltalk primBytesLeft. self clearWorkingMorph. newLeft := Smalltalk garbageCollect. {oldLeft. newLeft} nslog: '##cleanUp##'! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 6/10/2014 22:55'!clearWorkingMorph self workingMorph: nil. ! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 5/10/2014 02:15'!commandKeyStateChanged: keyStatus keyStatus nslog: 'commandKeyStateChanged:'. IPhonePresentationSpaceKeyState commandPressed: keyStatus! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 6/26/2014 01:29'!exitPresentationMode [ScratchPresenterMorph allInstancesDo: [:e | e exitPresentation]] fork! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 8/28/2014 00:06'!flushInputString: rawString | inputString | inputString := rawString asString. IPhonePresentationSpaceKeyState maxUnclaimedKeystrokeSize: (inputString size max: 10) ! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 5/17/2023 17:24'!getDevelopmentModeIndex self class isOnDevelopment ifTrue: [^ 1]. ^ 0! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 6/21/2014 00:22'!getFontScaleIndex ^SoiSettings default fontScaleIndex! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 8/1/2014 14:08'!getViewModeIndex scratchMorphic ifNil: [^1]. ^scratchMorphic getViewModeIndex! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/2/2014 19:39'!pickPhoto: pathName | pName scriptableScratchMorph | pName := pathName asString. (FileDirectory default fileExists: pName) ifFalse: [^self]. scriptableScratchMorph := self workingMorph. scriptableScratchMorph ifNil: [^self]. self photoPickerQueue defer: [ scriptableScratchMorph importImageNamed: pName. FileDirectory default deleteFileNamed: pName ifAbsent: []. ]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/24/2014 16:02'!restartVm [self basicRestartVm] fork! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 7/5/2022 00:41'!restoreDisplay World restoreDisplay.! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 11/4/2022 16:53'!restoreMeshIfNeeded | m | (m := self scratchMorphic) ifNil: [^self]. m isMeshHostingBroken ifTrue: [ self meshRun: 0. self meshRun: 1. ]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 8/7/2014 22:20'!scriptsAreRunning | running m | running := (m := self scratchMorphic) ifNotNil: [m isRunning] ifNil: [false]. ^running ifTrue: [1] ifFalse: [0]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 8/1/2014 11:55'!setFontScaleIndex: idx scratchMorphic ifNil: [^self]. scratchMorphic setFontScaleIndex: idx! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 8/1/2014 13:15'!setViewModeIndex: viewModeNumber [self basicSetViewModeIndex: viewModeNumber] fork! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 5/10/2014 02:14'!shiftKeyStateChanged: keyStatus keyStatus nslog: 'shiftKeyStateChanged:'. IPhonePresentationSpaceKeyState shiftPressed: keyStatus! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 7/13/2014 00:39'!isInPresentation ^ isInPresentation == true! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 7/13/2014 00:38'!isInPresentation: aBoolean isInPresentation := aBoolean! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'MU 10/27/2022 23:07'!meshHandlingQueue ^meshHandlingQueue ifNil: [meshHandlingQueue := SoiJobQueue new]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'MU 4/1/2021 22:11'!microbitAccessor ^microbitAccessor ifNil: [microbitAccessor := self class delegate microbitAccessor]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 7/2/2014 15:26'!photoPickerQueue ^photoPickerQueue ifNil: [photoPickerQueue := SoiJobQueue new]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 9/21/2018 14:34'!projectOpenCount ^projectOpenCount ifNil: [projectOpenCount := 0]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 6/8/2015 18:12'!sensorAccessor ^sensorAccessor ifNil: [sensorAccessor := self class delegate sensorAccessor]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 7/13/2014 00:35'!viewMode | m | ^(m := self scratchMorphic) ifNotNil: [m viewMode]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 6/6/2014 00:55'!workingMorph ^workingMorph! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 6/6/2014 00:55'!workingMorph: aMorph workingMorph := aMorph! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-private' stamp: 'mu 4/14/2017 17:34'!basicOpenProject: projectFileName | lowerFileName | scratchMorphic viewMode = #presentation ifTrue: [ExitPresentationMode := true]. (Delay forMilliseconds: 100) wait. ExitPresentationMode ifTrue: [(Delay forMilliseconds: 500) wait]. ExitPresentationMode ifTrue: [(Delay forSeconds: 1) wait]. ExitPresentationMode ifTrue: [(Delay forSeconds: 2) wait]. lowerFileName := projectFileName asLowercase. (lowerFileName endsWith: '.sb') ifTrue: [ scratchMorphic openScratchDroppedProjectNamed: projectFileName. ]. (lowerFileName endsWith: '.sprite') ifTrue: [ scratchMorphic importSpriteOrProject: projectFileName. ] ifFalse: [ scratchMorphic importMedia: projectFileName. ]. self onProjectOpened.! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-private' stamp: 'mu 8/1/2014 13:26'!basicRestartVm self scratchMorphic prepareBeforeRestart. SoiNotificationCenter postNofification: 'squeakVMSpaceIsLow'. Smalltalk snapshot: false andQuit: false! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-private' stamp: 'mu 6/29/2015 16:28'!basicSetViewModeIndex: viewModeNumber [scratchMorphic ifNil: [^self]. (World submorphs select: [:m | (m isKindOf: MenuMorph)]) do: [:e | e deleteIfPopUp]. scratchMorphic setViewModeIndex: viewModeNumber] fork! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-private' stamp: 'mu 9/21/2018 14:35'!incrementProjectOpenCount projectOpenCount := self projectOpenCount + 1. ! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-project-loading' stamp: 'mu 8/3/2014 21:19'!autoSavedProjectName ^'--AutoSaved--.sb'! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-project-loading' stamp: 'mu 8/3/2014 21:26'!deleteAutoSavedProject: autoSaveProjPath in: userScratchProjectsDir | projName tempDir | projName := self autoSavedProjectName. tempDir := SoiSettings tempDir. tempDir deleteFileNamed: projName. tempDir rename: autoSaveProjPath toBe: projName. "userScratchProjectsDir deleteFileNamed: autoSaveProjPath" ! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-project-loading' stamp: 'mu 8/3/2014 21:27'!loadWhenAutoSavedProjectFound | lastProjectStatus lastProjectPath userScratchProjectsDir autoSaveProjPath autoSaveProjExists | lastProjectStatus := SoiUtils readLastProjectStatus. lastProjectStatus ifNil: [^self]. lastProjectPath := lastProjectStatus first. userScratchProjectsDir := ScratchFileChooserDialog userScratchProjectsDir. autoSaveProjPath := userScratchProjectsDir pathName, FileDirectory slash, self autoSavedProjectName. autoSaveProjExists := userScratchProjectsDir fileExists: autoSaveProjPath. autoSaveProjExists ifTrue: [ scratchMorphic openAutoSavedProjectNamed: lastProjectPath. [self deleteAutoSavedProject: autoSaveProjPath in: userScratchProjectsDir] fork. ] ifFalse: [ (FileDirectory default fileExists: lastProjectPath) ifTrue: [scratchMorphic openScratchProjectNamed: lastProjectPath]. lastProjectPath nslog: '+++Former read'. ]. [scratchMorphic setViewModeIndex: lastProjectStatus second presenting: lastProjectStatus third running: lastProjectStatus fourth] fork. [SoiUtils deleteLastProjectStatus] fork.! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 10/28/2022 17:47'!meshIsRunning | running m | running := (m := self scratchMorphic) ifNotNil: [m isMeshRunning] ifNil: [false]. ^ running ifTrue: [1] ifFalse: [0]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 10/28/2022 17:38'!meshJoin: ipAddressString scratchMorphic ifNil: [^ self]. self meshHandlingQueue defer: [ scratchMorphic joinMesh: ipAddressString asString ]. ! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 10/28/2022 18:26'!meshJoined: ipAddressString scratchMorphic ifNil: [^ false]. ^ (scratchMorphic isMeshJoined: ipAddressString asString) ifTrue: [1] ifFalse: [0]! !!IPhoneScratchProxy methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 10/27/2022 23:09'!meshRun: runningMode scratchMorphic ifNil: [^ nil]. runningMode nslog: 'meshRun:'. runningMode = 0 ifTrue: [ self meshHandlingQueue defer: [scratchMorphic exitMesh] ]. runningMode = 1 ifTrue: [ self meshHandlingQueue defer: [scratchMorphic startMesh]. ].! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 6/1/2014 01:42'!isActive "IPhoneScratchProxy isActive" ^ isActive ifNil: [isActive := false].! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 5/30/2014 15:30'!isActive: aBoolean isActive := aBoolean! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 9/21/2018 14:37'!isFirstLaunch ^self current projectOpenCount = 0! !!IPhoneScratchProxy class methodsFor: 'accessing' stamp: 'mu 9/30/2017 22:48'!delegate delegate ifNil: [ | aUIApplicationClassOop | aUIApplicationClassOop := ObjectiveCObject findClassName: 'UIApplication'. ObjectiveCBridge performSelectorOnMainThread: [ delegate := aUIApplicationClassOop sharedApplication delegate. ] ]. ^delegate! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-event handling' stamp: 'mu 7/22/2014 21:18'!onVmSpaceIsLow | cur | self isActive ifFalse: [^self]. cur := self current. cur ifNotNil: [cur onVmSpaceIsLow]! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-exporting' stamp: 'mu 4/10/2017 16:50'!exportToCloud: resourcePath | mo | self isActive ifFalse: [^self]. mo := IPhoneScratchProxy current scratchMorphic. ObjectiveCBridge performSelectorOnMainThread: [ mo exportToCloud: resourcePath. ]! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-exporting' stamp: 'mu 4/28/2017 13:21'!exportToCloudIfNeeded: resourcePath (SoiUtils belongsToTemporary: resourcePath) ifFalse: [^false]. self exportToCloud: resourcePath. ^true! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/15/2014 16:02'!cleanUp | cur | self isActive ifFalse: [^self]. cur := self current. cur ifNotNil: [cur cleanUp]! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-opening' stamp: 'MU 5/16/2023 21:32'!prepareHelpers SoiMIDISynth initialize! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-opening' stamp: 'mu 5/14/2014 23:11'!prepareScratchFrameMorphBeforeOpen SqueakProxy scratchMorphic: ScratchFrameMorph allInstances first. SqueakProxy scratchMorphic setupTheLanguageOnThisDevice. ! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-override' stamp: 'MU 5/16/2023 21:43'!startUp (isActive := Smalltalk isiPhone) ifFalse: [^self]. delegate := nil. self alterMemorySettings. self prepareHelpers. StopScratchProject := false. ExitPresentationMode := false. SqueakProxy := (self forProtocolString: nil). self delegate setSqueakProxy: SqueakProxy squeakProxy. self prepareScratchFrameMorphBeforeOpen. self registerPublicMethods. MouseClickProcessHandler := [[SqueakProxy runUntilTerminateConditionBlock: [:value | false] ] ifError: [:err :rcvr | SqueakProxy error: 'Why? ', {err. rcvr} asString]] forkAt: Processor userInterruptPriority. SoiNotificationCenter postNofification: 'squeakVMReady'! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-registration' stamp: 'MU 5/15/2023 17:08'!registerPublicMethods SqueakProxy addSigViaString: 'chooseThisProject:runProject:' aSignature: 'v@:@i'; addSigViaString: 'shoutGo' aSignature: 'v@:'; addSigViaString: 'stopAll' aSignature: 'v@:'; addSigViaString: 'restoreDisplay' aSignature: 'v@:'; addSigViaString: 'becomeActive' aSignature: 'v@:'; addSigViaString: 'becomeActiveAfter:' aSignature: 'v@:i'; addSigViaString: 'becomeBackground' aSignature: 'v@:'; addSigViaString: 'setFontScaleIndex:' aSignature: 'v@:i'; addSigViaString: 'getFontScaleIndex' aSignature: 'i@:'; addSigViaString: 'pickPhoto:' aSignature: 'v@:@'; addSigViaString: 'flushInputString:' aSignature: 'v@:@'; addSigViaString: 'getViewModeIndex' aSignature: 'i@:'; addSigViaString: 'setViewModeIndex:' aSignature: 'v@:i'; addSigViaString: 'exitPresentationMode' aSignature: 'v@:'; addSigViaString: 'scriptsAreRunning' aSignature: 'i@:'; addSigViaString: 'commandKeyStateChanged:' aSignature: 'v@:i'; addSigViaString: 'shiftKeyStateChanged:' aSignature: 'v@:i'; addSigViaString: 'getDevelopmentModeIndex' aSignature: 'i@:'; addSigViaString: 'restartVm' aSignature: 'v@:'; addSigViaString: 'meshIsRunning' aSignature: 'i@:'; addSigViaString: 'meshRun:' aSignature: 'v@:i'; addSigViaString: 'meshJoin:' aSignature: 'v@:@'; addSigViaString: 'meshJoined:' aSignature: 'i@:@'! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 6/6/2014 00:49'!current ^SqueakProxy! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-accessing' stamp: 'MU 5/15/2023 18:03'!isActiveProduction ^ self isActive and: [self isOnDevelopment not] ! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 7/13/2014 00:43'!isInPresentation | cur | (cur := self current) ifNil: [^false]. ^cur isInPresentation! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 7/13/2014 00:43'!isInPresentation: aBoolean | cur | (cur := self current) ifNotNil: [cur isInPresentation: aBoolean]! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-accessing' stamp: 'MU 5/15/2023 16:52'!isOnDevelopment | sourceFiles | sourceFiles := SourceFiles. sourceFiles ifNil: [^false]. sourceFiles size < 2 ifTrue: [^false]. (sourceFiles at: 2 ifAbsent: []) ifNil: [^false]. ^true! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-accessing' stamp: 'MU 7/29/2022 16:15'!isOnMac self isActive ifFalse: [^false]. ^self delegate catalystMode > 0! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-accessing' stamp: 'MU 10/21/2022 16:26'!osVersion self isActive ifFalse: [^0]. ^self delegate osVersion! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-sensors' stamp: 'mu 6/19/2015 14:33'!localSensorValueAt: sensorName ifPresent: oneArgBlock | sa value | sa := self sensorAccessor. value := sensorName caseOf: { ['accX']-> [sa accX]. ['accY']-> [sa accY]. ['accZ']-> [sa accZ]. ['gyroX']-> [sa gyroX]. ['gyroY']-> [sa gyroY]. ['gyroZ']-> [sa gyroZ]. ['yaw']-> [sa yaw]. ['pitch']-> [sa pitch]. ['roll']-> [sa roll]. ['northHeading']->[sa northHeading]. ['brightness']->[sa brightness]. } otherwise: [nil]. value ifNotNil: [oneArgBlock value: value].! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-sensors' stamp: 'mu 6/8/2015 18:22'!sensorAccessor ^self current sensorAccessor! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-sensors' stamp: 'mu 6/8/2015 22:17'!sensorAccessorIsRunning | mode | mode := self sensorAccessor runningMode. ^mode > 0! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 4/1/2021 21:00'!microbitAccessor ^self current microbitAccessor! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 4/1/2021 21:55'!microbitAccessorIsRunning | mode | mode := self microbitAccessor runningMode. ^mode > 0! !!IPhoneScratchProxy class methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/8/2021 10:36'!microbitSensorValueAt: sensorName ifPresent: oneArgBlock | sa value | sa := self microbitAccessor. value := sensorName caseOf: { ['mb:accX']-> [sa accX]. ['mb:accY']-> [sa accY]. ['mb:accZ']-> [sa accZ]. ['mb:magX']-> [sa magX]. ['mb:magY']-> [sa magY]. ['mb:magZ']-> [sa magZ]. ['mb:northHeading']-> [sa compassBearingValue]. ['mb:temperature']-> [sa temperatureValue]. ['mb:buttonA']-> [sa buttonAValue]. ['mb:buttonB']-> [sa buttonBValue]. ['mb:uart']-> [ObjectiveCBridge asString: sa uartMessage]. ['mb:pin0']-> [sa pin0Value]. ['mb:pin1']-> [sa pin1Value]. ['mb:pin2']-> [sa pin2Value]. } otherwise: [ (sensorName beginsWith: 'mb:pin') ifTrue: [ | pinIndex | pinIndex := [(sensorName copyFrom: 7 to: sensorName size) asNumber] ifError: []. pinIndex ifNotNil: [sa pinValueAt: pinIndex]] ]. value ifNotNil: [oneArgBlock value: value].! !!InputSensor methodsFor: '*ScratchOnIPad' stamp: 'MU 4/5/2020 00:28'!fixTouchUpPositionIfNeededInto: eventBuffer | newX newY dist | lastTouchPosition ifNil: [^self]. newX := eventBuffer at: 3. newY := eventBuffer at: 4. dist := (newX@newY) dist: lastTouchPosition. (newX = 0 or: [dist < 9]) ifTrue: [eventBuffer at: 3 put: lastTouchPosition x. " mouse x " eventBuffer at: 4 put: lastTouchPosition y]. " mouse y " ! !!InputSensor methodsFor: '*ScratchOnIPad' stamp: 'mu 5/13/2014 22:39'!isIPhone ^IPhoneScratchProxy isActive ! !!InputSensor methodsFor: '*ScratchOnIPad' stamp: 'mu 6/19/2014 15:45'!isIgnorableTouch: firstTouch of: touchType "(touchType = 1 and: [(firstTouch at: 3) = 3]) ifTrue: [ touchType nslog: 'Bogus touch error touch down but phase is up'. ^true]." "Bogus touch error touch down but phase is up" (touchType = 3 and: [(firstTouch at: 3) = 3]) ifTrue: [^true]. "Bogus touch error touch moved but phase is up" (touchType = 2 and: [(touchDownWasSeen == true) not]) ifTrue: [^true]. "Bogus touch error touch up but never got touch down" touchType = 5 ifTrue: ["No idea, touch canceled because of incoming phone call, or other issue like memory If we do mouse up, then that is mouse down/up and triggers something yet the user didn't want that". ^true]. touchType = 4 ifTrue: [^true]. "No need to do anything?" ^false! !!InputSensor methodsFor: '*ScratchOnIPad' stamp: 'mu 5/13/2014 22:42'!processDoubleTap: evt with: touch | eventBuffer | touchDownWasSeen := true. eventBuffer := Array new: 8. eventBuffer at: 1 put: 1. " type " eventBuffer at: 2 put: Time millisecondClockValue. " timeStamp " eventBuffer at: 3 put: (touch at: 7) asInteger. " mouse x " eventBuffer at: 4 put: (touch at: 8) asInteger. " mouse y " lastTouchPosition := (eventBuffer at: 3)@(eventBuffer at: 4). eventBuffer at: 5 put: 4. " buttons " eventBuffer at: 6 put: 0. " modifiers " eventBuffer at: 7 put: 1. " reserved 1 -> double click " eventBuffer at: 8 put: (evt at: 8). " windowIndex " ^events addLast: eventBuffer.! !!InputSensor methodsFor: '*ScratchOnIPad' stamp: 'mu 5/13/2014 22:41'!processTouchDown: evt with: touch | eventBuffer | touchDownWasSeen := true. eventBuffer := Array new: 8. eventBuffer at: 1 put: 1. " type " eventBuffer at: 2 put: Time millisecondClockValue. " timeStamp " eventBuffer at: 3 put: (touch at: 7) asInteger. " mouse x " eventBuffer at: 4 put: (touch at: 8) asInteger. " mouse y " lastTouchPosition := (eventBuffer at: 3)@(eventBuffer at: 4). eventBuffer at: 5 put: 4. " buttons " eventBuffer at: 6 put: 0. " modifiers " eventBuffer at: 7 put: 0. " reserved1 " eventBuffer at: 8 put: (evt at: 8). " windowIndex " ^events addLast: eventBuffer.! !!InputSensor methodsFor: '*ScratchOnIPad' stamp: 'mu 5/13/2014 22:41'!processTouchMove: evt with: touch | eventBuffer | eventBuffer := Array new: 8. eventBuffer at: 1 put: 1. " type " eventBuffer at: 2 put: Time millisecondClockValue. " timeStamp " eventBuffer at: 3 put: (touch at: 7) asInteger. " mouse x " eventBuffer at: 4 put: (touch at: 8) asInteger. " mouse y " lastTouchPosition := (eventBuffer at: 3)@(eventBuffer at: 4). eventBuffer at: 5 put: 4. " buttons " eventBuffer at: 6 put: 0. " modifiers " eventBuffer at: 7 put: 0. " reserved1 " eventBuffer at: 8 put: (evt at: 8). " windowIndex " ^events addLast: eventBuffer.! !!InputSensor methodsFor: '*ScratchOnIPad' stamp: 'mu 5/13/2014 22:41'!processTouchUp: evt with: touch | eventBuffer | touchDownWasSeen := false. eventBuffer := Array new: 8. eventBuffer at: 1 put: 1. " type " eventBuffer at: 2 put: Time millisecondClockValue. " timeStamp " eventBuffer at: 3 put: (touch at: 7) asInteger. " mouse x " eventBuffer at: 4 put: (touch at: 8) asInteger. " mouse y " self fixTouchUpPositionIfNeededInto: eventBuffer. eventBuffer at: 5 put: 0. " buttons " eventBuffer at: 6 put: 0. " modifiers " eventBuffer at: 7 put: 0. " reserved1 " eventBuffer at: 8 put: (evt at: 8). " windowIndex " ^events addLast: eventBuffer.! !!InputSensor methodsFor: '*ScratchOnIPad' stamp: 'mu 5/13/2014 22:40'!processTwoFingerTap: evt with: touch | eventBuffer | touchDownWasSeen := true. eventBuffer := Array new: 8. eventBuffer at: 1 put: 1. " type " eventBuffer at: 2 put: Time millisecondClockValue. " timeStamp " eventBuffer at: 3 put: (touch at: 7) asInteger. " mouse x " eventBuffer at: 4 put: (touch at: 8) asInteger. " mouse y " lastTouchPosition := (eventBuffer at: 3)@(eventBuffer at: 4). eventBuffer at: 5 put: 4. " buttons " eventBuffer at: 6 put: 0. " modifiers " eventBuffer at: 7 put: 3. " reserved 3 -> two finger tap " eventBuffer at: 8 put: (evt at: 8). " windowIndex " ^events addLast: eventBuffer.! !!InputSensor methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/13/2014 22:42'!nextMorphicMouseEventFor: aHandMorph "Answer the next Morphic mouse event record (an array of 8 integers) and update the cursor position and button state. If there is no new record, answer a record with the current cursor position. A mouse event record is: <type=1><timestamp><x><y><button state><modifier key state>" | evtRec type oldButtons newButtons | self processMouseEvents. transitionevents size > 0 ifTrue: [ "answer the next button transition mouse event" evtRec _ transitionevents removeFirst. cursorpoint _ (evtRec at: 3)@(evtRec at: 4). buttonstate _ ((evtRec at: 6) bitShift: 3) bitOr: ((evtRec at: 5) bitAnd: 7). type _ (evtRec at: 5) > 0 ifTrue: [#mouseDown] ifFalse: [#mouseUp]. ^ MorphicEvent new setType: type timestamp: (evtRec at: 2) cursorPoint: (aHandMorph griddedPoint: cursorpoint) buttons: buttonstate keyValue: 0; reserved: (evtRec at: 7); setHand: aHandMorph]. oldButtons _ aHandMorph lastEvent buttons bitAnd: 7. newButtons _ buttonstate bitAnd: 7. type _ #mouseMove. ((oldButtons > 0) & (newButtons = 0)) ifTrue: [type _ #mouseUp]. ((oldButtons = 0) & (newButtons > 0)) ifTrue: [type _ #mouseDown]. ^ MorphicEvent new setType: type timestamp: Time millisecondClockValue cursorPoint: (aHandMorph griddedPoint: cursorpoint) buttons: buttonstate keyValue: 0; setHand: aHandMorph! !!InputSensor methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/19/2014 22:43'!processTouchEventType: evt | touch touches touchType touchCount | touchType := evt at: 3. touches := evt at: 4. touch := touches at: 1. touchCount := touch at: 4. (self isIgnorableTouch: touch of: touchType) ifTrue: [^self]. touchType caseOf: { [1]-> [ (touchCount = 2) ifTrue: [self processDoubleTap: evt with: touch] ifFalse: [ (touches size = 2) ifTrue: [self processTwoFingerTap: evt with: touch] ifFalse: [(touch at: 3) = 3 ifTrue: [self processTouchUp: evt with: touch] ifFalse: [self processTouchDown: evt with: touch] ] ] ]. [2]-> [self processTouchUp: evt with: touch]. [3]-> [self processTouchMove: evt with: touch]. }"typedef struct sqComplexEvent { int type; /* type of event; EventTypeComplex */ unsigned int timeStamp; /* time stamp */ /* the interpretation of the following fields depend on the type of the event */ int action; /* one of ComplexEventXXX (see below) */ usqInt objectPointer; /* used to point to object */ int unused1; /* */ int unused2; /* */ int unused3; /* */ int windowIndex; /* host window structure */ } sqComplexEvent;"" interpreterProxy->storePointerofObjectwithValue(0, storageArea, squeakMSTime); interpreterProxy->storePointerofObjectwithValue(1, storageArea, timeStamp); interpreterProxy->storePointerofObjectwithValue(2, storageArea, phase); interpreterProxy->storePointerofObjectwithValue(3, storageArea, tapCount); interpreterProxy->storePointerofObjectwithValue(4, storageArea, window); interpreterProxy->storePointerofObjectwithValue(5, storageArea, view); interpreterProxy->storePointerofObjectwithValue(6, storageArea, locationInViewX); interpreterProxy->storePointerofObjectwithValue(7, storageArea, locationInViewY); interpreterProxy->storePointerofObjectwithValue(8, storageArea, previousLocationInViewX); interpreterProxy->storePointerofObjectwithValue(9, storageArea, previousLocationInViewY); typedef enum { UITouchPhaseBegan, = 0 // whenever a finger touches the surface. UITouchPhaseMoved, 1 // whenever a finger moves on the surface. UITouchPhaseStationary, 2 // whenever a finger is touching the surface but hasn't moved since the previous event. UITouchPhaseEnded, 3 // whenever a finger leaves the surface. UITouchPhaseCancelled, 4 // whenever a touch doesn't end but we need to stop tracking (e.g. putting device to face)} EventTouchDown := 1. EventTouchUp := 2. EventTouchMoved := 3. EventTouchStationary := 4. EventTouchCancelled := 5."! !!InputSensor methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/13/2014 22:40'!shiftPressed "Answer true if the shift key is pressed." self isIPhone ifTrue: [^IPhonePresentationSpaceKeyState isShiftPressed]. ^ self modifiersAndButtons anyMask: 8! !!Integer methodsFor: '*ScratchOnIPad-arithmetic-override' stamp: 'mu 8/26/2014 13:39'!/ aNumber "Refer to the comment in Number / " | quoRem | aNumber isInteger ifTrue: [quoRem _ self digitDiv: aNumber abs "*****I've added abs here*****" neg: self negative ~~ aNumber negative. (quoRem at: 2) normalize = 0 ifTrue: [^ (quoRem at: 1) normalize] ifFalse: [^ self asFloat / aNumber]]. ^ aNumber adaptToInteger: self andSend: #/! !!Morph methodsFor: 'dropping/grabbing' stamp: 'mu 12/15/2014 22:54'!slideBackToFormerSituation: evt | slideForm formerOwner formerPosition aWorld startPoint endPoint trans | (formerOwner _ evt hand formerOwner) ifNil: [^ self]. formerPosition _ evt hand formerPosition. aWorld _ self world. trans _ formerOwner transformFromWorld. slideForm _ self imageForm offset: 0@0. startPoint _ evt hand fullBounds origin. endPoint _ trans localPointToGlobal: formerPosition. owner privateRemoveMorph: self. aWorld ifNotNil: [aWorld displayWorld]. slideForm slideFrom: startPoint to: endPoint nSteps: 12 delay: 15. formerOwner addMorph: self. self position: formerPosition. self justDroppedInto: formerOwner event: evt.! !!Morph methodsFor: '*ScratchOnIPad-enumeration' stamp: 'mu 7/9/2014 22:07'!allMorphsSatisfying: selectBlock do: aBlock ^ self allMorphsDo: [:each | (selectBlock value: each) ifTrue: [aBlock value: each] ].! !!Morph methodsFor: '*ScratchOnIPad-enumeration' stamp: 'mu 7/9/2014 22:08'!allToggleButtonsDo: aBlock self allMorphsSatisfying: [:each | each isKindOf: ToggleButton] do: aBlock! !!Morph methodsFor: '*ScratchOnIPad-enumeration' stamp: 'mu 5/30/2014 13:59'!deeplyFindSubMorphNamed: morphName self allMorphsDo: [:each | each externalName = morphName ifTrue: [^each] ]. ^nil! !!Morph methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 9/1/2014 12:24'!isToolTipMorph ^false! !!Morph methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/9/2014 12:05'!shouldBorderDrawOnDragging ^false! !!Morph methodsFor: '*ScratchOnIPad-balloon' stamp: 'mu 9/1/2014 12:36'!showBalloon: msg deleteAfter: seconds self showBalloon: msg. ScratchToolTipMorph toolTips size = 1 ifTrue: [ [(Delay forSeconds: seconds) wait. self deleteBalloon] fork. ]! !!Morph methodsFor: '*ScratchOnIPad-override-drawing' stamp: 'mu 5/1/2015 14:37'!fullBounds fullBounds ifNil: [ | fb | fb := self bounds. submorphs size > 0 ifTrue: [ submorphs do: [:m | m isHidden ifFalse: [ fb := fb quickMerge: m fullBounds]]]. fullBounds := fb. ]. ^ fullBounds! !!Morph methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 4/28/2018 14:22'!scrollFrame ^self ownerThatIsA: ScrollFrameMorph! !!Morph methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 4/28/2018 14:28'!scrollFrameDo: aBlock | scrollFrm | scrollFrm := self scrollFrame. ^scrollFrm ifNotNil: [aBlock value: scrollFrm]! !!BlockMorph methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/9/2014 12:12'!shouldBorderDrawOnDragging ^true! !!BlockMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'mu 7/29/2014 12:01'!rightButtonMenu | menu | menu _ CustomMenu new. IPhoneScratchProxy isActive ifFalse: [ menu add: 'help' action: #presentHelpScreen. ]. (owner isKindOf: ScratchBlockPaletteMorph) ifFalse: [ menu addLine. menu add: 'duplicate' action: #duplicate. (self owner isKindOf: BlockMorph) ifFalse: [ "we can't yet delete a blocks inside a script" menu add: 'delete' action: #delete]]. DebugMenu ifTrue: [ menu addLine. menu add: 'show tuples' action: #showTuples]. menu localize; invokeOn: self.! !!BlockMorph methodsFor: '*ScratchOnIPad-drawing-override' stamp: 'mu 9/1/2014 11:59'!updateCachedForm "Create a cached Form of this stack's appearance." | c offset | oldColor ifNotNil: [color _ oldColor]. c _ FormCanvas extent: self fullBounds extent depth: 32. ScratchTranslator isRTL ifTrue: [ offset _ scratchProc ifNil: [0@0] ifNotNil: [3@3]. c _ c copyOffset: (self fullBounds topLeft + offset) negated] ifFalse: [c _ c copyOffset: self topLeft negated]. self drawOn: c. self drawSubmorphsOn: c. cachedForm _ c form. lastLayoutTime _ Time millisecondClockValue. ^cachedForm! !!BlockMorph methodsFor: '*ScratchOnIPad-geometry-override' stamp: 'mu 8/6/2017 14:31'!containsPoint: aPoint | cform fbounds | cform := cachedForm ifNil: [self updateCachedForm]. fbounds := self fullBounds. fbounds ifNil: [^false]. ^ (fbounds containsPoint: aPoint) and: [(cform isTransparentAt: aPoint - fbounds origin) not]! !!BorderedMorph methodsFor: '*ScratchOnIPad-events' stamp: 'MU 4/9/2021 14:45'!ipadTextFieldFocused: boolean | nsString state | boolean ifFalse: [^self]. "Currently do not callback when focus is off" state := boolean ifTrue: ['true'] ifFalse: ['false']. nsString := state asNSStringUTF8. IPhoneScratchProxy delegate textMorphFocused: nsString. nsString release.! !!ArgMorph methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/9/2014 12:13'!shouldBorderDrawOnDragging ^true! !!ColorArgMorph methodsFor: '*ScratchOnIPad-override' stamp: 'MU 8/13/2022 11:01'!mouseUp: evt | w palette offset | showPalette ifNil: [showPalette _ true]. (w _ self world) ifNil: [^ self]. showPalette ifTrue: [ palette _ ImageMorph new form: ColorPalette. palette position: self bounds bottomLeft + (0@5). w addMorph: palette. w displayWorldSafely]. offset := (IPhoneScratchProxy isOnMac not) ifTrue: [20@-20] ifFalse: [0@0]. Cursor eyeDropper showNotifying: #eyeDropper while: [ Sensor waitButton. [Sensor anyButtonPressed] whileTrue: [ self color: (Display colorAt: Sensor cursorPoint + offset). w displayWorldSafely]]. palette ifNotNil: [palette delete].! !!CommandBlockMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'mu 7/29/2014 12:00'!rightButtonMenu | menu sFrame choice spec | menu _ CustomMenu new. IPhoneScratchProxy isActive ifFalse: [ menu add: 'help' action: #presentHelpScreen. ]. (owner isKindOf: ScratchBlockPaletteMorph) ifFalse: [ menu addLine. (#(+ - * / \\) includes: selector) ifTrue: [ #(+ - * / mod) with: #(+ - * / \\) do: [:s :op | menu add: s action: op]]. (#(< = >) includes: selector) ifTrue: [ #(< = >) do: [:op | menu add: op action: op]]. (#(& |) includes: selector) ifTrue: [ #(and or) with: #(& |) do: [:s :op | menu add: s action: op]]. menu addLine. menu add: 'duplicate' action: #duplicate. (self owner isKindOf: BlockMorph) ifFalse: [ "can't yet delete a blocks inside a script" menu add: 'delete' action: #delete]]. sFrame _ self ownerThatIsA: ScratchFrameMorph. (sFrame notNil and: [#(sensor: sensorPressed:) includes: selector]) ifTrue: [ menu addLine. menu add: 'show ScratchBoard watcher' action: #showSensorBoard. sFrame workPane scratchServer ifNil: [menu add: 'enable remote sensor connections' action: #enableRemoteSensors] ifNotNil: [menu add: 'disable remote sensor connections' action: #exitScratchSession]]. DebugMenu ifTrue: [ menu addLine. menu add: 'show tuples' action: #showTuples]. (choice _ menu localize; startUp) ifNil: [^ self]. (#(presentHelpScreen duplicate delete) includes: choice) ifTrue: [^ self perform: choice]. choice = #showSensorBoard ifTrue: [sFrame showSensorBoard. ^ self]. choice = #enableRemoteSensors ifTrue: [sFrame enableRemoteSensors. ^ self]. choice = #exitScratchSession ifTrue: [sFrame exitScratchSession. ^ self]. choice = #showTuples ifTrue: [^ self showTuples]. "change operator" spec _ '%n ', choice, ' %n'. '\\' = choice ifTrue: [spec _ ScratchTranslator translationFor: '%n mod %n']. '&' = choice ifTrue: [spec _ ScratchTranslator translationFor: '%b and %b']. '|' = choice ifTrue: [spec _ ScratchTranslator translationFor: '%b or %b']. self commandSpec: spec. self selector: choice.! !!CBlockMorph methodsFor: 'geometry' stamp: 'mu 12/15/2014 22:52'!containsPoint: aPoint | fm | fm := cachedForm ifNil: [self updateCachedForm]. ^ (self fullBounds containsPoint: aPoint) and: [(fm isTransparentAt: aPoint - self fullBounds origin) not]! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-geometry' stamp: 'mu 6/18/2014 17:16'!centerYOffset IPhoneScratchProxy isActive ifTrue: [^self ipadCenterYOffset]. ^5. "center on screen but disregard the shadow on the bottom"! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-geometry' stamp: 'mu 7/9/2014 21:37'!ipadCenterYOffset | offset padding | offset := self extent y // 2. padding := topEdgeForm height. offset := offset - padding. ^offset negated ! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/18/2014 17:18'!centerOnScreen "Center myself on the screen, if possible. Otherwise, adjust position so buttons are visible." | w | w _ self world. self extent: self extent. "force layout" self position: w center - (self extent // 2) + (0@(self centerYOffset)). "center on screen but disregard the shadow on the bottom" self bottom > w bottom ifTrue: [ self bottom: w bottom + 37. "make sure cancel button is on screen" self top > -2 ifTrue: [self top: -2]]. "make top flush with the top of the screen" (self top < -2 and: [self top > -34]) ifTrue: [ "if title bar partway off screen, move it all the way off" self top: -34].! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/22/2015 16:50'!iPhoneGetUserResponse | semaIndex classOop instance titleOop messageOop data result initialAnsNsString | iPhoneSemaphore _ Semaphore new. semaIndex := Smalltalk registerExternalObject: iPhoneSemaphore. classOop := ObjectiveCObject findClassName: 'SUYAlertDialog'. titleOop := iphoneTitle isNil ifFalse: [iphoneTitle asNSString] ifTrue: [nil asObjc]. messageOop := iphoneMessage isNil ifFalse: [iphoneMessage asNSString] ifTrue: [nil asObjc]. ObjectiveCBridge performSelectorOnMainThread: [ instance := classOop alloc. self isForRequest ifTrue: [initialAnsNsString := ( self valueOfProperty: #initialAnswer) asString asNSStringUTF8. instance initForRequestWithTitle: titleOop message: messageOop initialAnswer: initialAnsNsString cancel: cancelFlagR asObjc semaIndex: semaIndex] ifFalse: [instance initTitle: titleOop message: messageOop yes: yesFlagR asObjc no: noFlagR asObjc okay: okFlagR asObjc cancel: cancelFlagR asObjc semaIndex: semaIndex] ]. iPhoneSemaphore wait. Smalltalk unregisterExternalObject: iPhoneSemaphore. data := instance buttonPicked. data = -1 ifTrue: [result := #cancelled]. data >= 0 ifTrue: [result := data == 1]. self isForRequest ifTrue: [ result := result == true ifTrue: [ObjectiveCBridge asString: instance answerString] ifFalse: ['']. initialAnsNsString release. ]. titleOop ifNotNil: [titleOop release]. messageOop ifNotNil: [messageOop release]. instance release. ^result.! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/7/2014 10:38'!iPhoneTitle: aTitle iphoneTitle := aTitle. titleBin ifNotNil: [titleBin delete]. titleBin removeAllMorphs. self addMorphBack: titleBin! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/29/2014 11:34'!message: aMessage "Set my message/question text." self useMorphMessage ifFalse: [^self iPhoneMessage: aMessage localized]. self message: aMessage localized font: (ScratchFrameMorph getFont: #DialogBoxMessage).! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/29/2014 11:39'!message: aMessage details: aDetailsString font: aStrikeFont "Set and position my message/question text." | lines m | self useMorphMessage ifFalse: [^self iPhoneMessage: aMessage localized, '-', aDetailsString localized]. messageLineMorphs ifNotNil: [ messageLineMorphs submorphsDo: [:lineM | lineM delete]]. messageLineMorphs _ AlignmentMorph newColumn color: Color transparent; hResizing: #shrinkWrap; vResizing: #shrinkWrap; centering: #center. lines _ aMessage lines. 1 to: lines size do: [:n | m _ StringMorph contents: (lines at: n) font: aStrikeFont. messageLineMorphs addMorphBack: m]. lines _ aDetailsString lines. 1 to: lines size do: [:n | m _ StringMorph contents: (lines at: n) font: aStrikeFont. messageLineMorphs addMorphBack: m]. mainColumn addMorph: messageLineMorphs. self changed.! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/29/2014 11:39'!message: aMessage font: aStrikeFont "Set and position my message/question text." | lines m | self useMorphMessage ifFalse: [^self iPhoneMessage: aMessage localized]. messageLineMorphs ifNotNil: [ messageLineMorphs submorphsDo: [:lineM | lineM delete]]. messageLineMorphs _ AlignmentMorph newColumn color: Color transparent; hResizing: #shrinkWrap; vResizing: #shrinkWrap; centering: #center. lines _ aMessage lines. 1 to: lines size do: [:n | m _ StringMorph contents: (lines at: n) font: aStrikeFont. messageLineMorphs addMorphBack: m]. mainColumn addMorph: messageLineMorphs. self changed.! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/29/2014 11:23'!title: aString "Note: Title is actually two StringMorphs with the same contents and font: a gray shadow of the text with a white submorph of the same text, offset by a small amount." self useMorphTitle ifFalse: [^self iPhoneTitle: aString]. titleBin ifNotNil: [titleBin delete]. titleBin removeAllMorphs. titleMorph ifNotNil: [titleMorph delete]. titleMorph _ ShadowedStringMorph new contents: aString localized color: Color white font: (ScratchFrameMorph getFont: #DialogBoxTitle) kern: 1. titleBin addMorph: (AlignmentMorph newSpacer: Color transparent); addMorph: (Morph new extent: (5@5); color: Color transparent); addMorph: titleMorph; addMorph: (AlignmentMorph newSpacer: Color transparent). self addMorphBack: titleBin. self changed.! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 4/22/2015 15:33'!isForRequest ^(self valueOfProperty: #dialogType) == #request! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 6/6/2014 14:54'!isSticky IPhoneScratchProxy isActive ifTrue: [^true]. ^false! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/29/2014 11:35'!useMorphMessage ^self useMorphTitle! !!DialogBoxMorph methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/29/2014 11:23'!useMorphTitle ^IPhoneScratchProxy isActive not! !!DialogBoxMorph class methodsFor: 'instance creation' stamp: 'mu 4/22/2015 16:33'!request: questionString initialAnswer: defaultAnswerString | dialogBox | dialogBox _ self new title: '?'; withButtonsForYes: true no: true okay: false cancel: true; message: questionString. dialogBox setProperty: #dialogType toValue: #request. dialogBox setProperty: #initialAnswer toValue: defaultAnswerString. ^ dialogBox getUserResponse! !!DialogBoxMorph class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/15/2015 15:48'!inform: informationString title: titleString "Put up an instance of me to give the user an informational message and wait until they click the 'ok' button before proceeding." "DialogBoxMorph inform: 'Operation complete.' title: 'Status'" | dialogBox | dialogBox _ self new withButtonsForYes: false no: false okay: true cancel: false; title: titleString localized. dialogBox message: informationString localized font: (ScratchFrameMorph getFont: #DialogBoxMessage). ^ dialogBox getUserResponse! !!DialogBoxMorph class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/29/2015 14:41'!request: questionString ^self request: questionString initialAnswer: ''! !!ExpressionArgMorph methodsFor: '*ScratchOnIPad-override-drawing' stamp: 'MU 4/5/2020 10:27'!drawOn: aCanvas | darkerC right topY bottomY radius xInset c | isNumber ifFalse: [^ super drawOn: aCanvas]. darkerC _ Color gray. right _ self width - 2. topY _ bottomY _ radius _ self height // 2. self height even ifTrue: [topY _ bottomY - 1]. [topY >= 0] whileTrue: [ xInset _ radius - (radius squared - (radius - topY - 1) squared) sqrt rounded. self drawHLineFrom: xInset to: (xInset + 1) y: topY color: darkerC on: aCanvas. c _ (topY < 1) ifTrue: [darkerC] ifFalse: [Color white]. self drawHLineFrom: xInset + 1 to: right - (xInset + 1) y: topY color: c on: aCanvas. self drawHLineFrom: (right - (xInset + 1)) to: (right - xInset) y: topY color: darkerC on: aCanvas. self drawHLineFrom: xInset to: right - xInset y: bottomY color: Color white on: aCanvas. xInset = 0 ifTrue: [ self drawHLineFrom: xInset + 1 to: xInset + 2 y: topY color: Color white on: aCanvas. self drawHLineFrom: xInset to: xInset + 1 y: bottomY color: darkerC on: aCanvas. self drawHLineFrom: (right - (xInset + 1)) to: (right - xInset) y: bottomY color: darkerC on: aCanvas]. bottomY _ bottomY + 1. topY _ topY - 1].! !!HandMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/13/2014 22:32'!checkForDoubleClick: evt "Process the given mouse event to detect a click, double-click, or drag." | reserved t | reserved := evt reserved. reserved = 1 ifTrue: [ evt type nslog: 'handleDoubleClick: by reserved'. ^self handleDoubleClick: evt]. reserved = 2 ifTrue: [ evt type nslog: 'handleMouseHold: by reserved'. ^self handleMouseHold: evt]. t _ evt timestamp - firstClickEvent timestamp. clickState = #firstClickDown ifTrue: [ t > HoldTime ifTrue: [ evt type nslog: 'handleMouseHold: normal'. ^self handleMouseHold: firstClickEvent]. (((self transformEvent: evt) cursorPoint - firstClickEvent cursorPoint) r > 0) ifTrue: [ "consider it a drag if hand moves" clickState _ #idle. clickClient startDrag: firstClickEvent. ^ self resetClickState]. evt isMouseUp ifTrue: [ clickState _ #firstClickUp. ^ self]]. clickState = #firstClickUp ifTrue: [ evt isMouseDown ifTrue: [ evt type nslog: 'handleDoubleClick: normal'. ^self handleDoubleClick: firstClickEvent]. t > DoubleClickTime ifTrue: [ clickState _ #idle. clickClient click: firstClickEvent. ^ self resetClickState]].! !!HandMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/9/2014 00:06'!fullDrawOn: aCanvas "A HandMorph has unusual drawing requirements: 1. the hand itself (i.e., the cursor) appears in front of its submorphs 2. morphs being held by the hand cast a shadow on the world/morphs below The illusion is that the hand plucks up morphs and carries them above the world." "Note: This version caches an image of the morphs being held by the hand for better performance. This cache is invalidated if one of those morphs changes." | disableCaching subBnds cached | IPhoneScratchProxy isActive ifTrue: [^self simpleTouchDrawOn: aCanvas]. disableCaching _ false. disableCaching ifTrue: [self nonCachingFullDrawOn: aCanvas. ^ self]. submorphs isEmpty ifTrue: [cacheCanvas _ nil. ^ self drawOn: aCanvas]. "just draw the hand itself" subBnds _ Rectangle merging: (submorphs collect: [:m | m fullBounds]). self updateCacheCanvas: aCanvas. (cacheCanvas == nil or: [cachedCanvasHasHoles and: [cacheCanvas depth = 1]]) ifTrue: ["could not use caching due to translucency; do full draw" self nonCachingFullDrawOn: aCanvas. ^ self]. drawHalfSize ifNil: [drawHalfSize _ true]. drawHalfSize ifTrue: [ cached _ cacheCanvas form magnifyBy: 0.5. subBnds _ (self position + ((subBnds origin - self position) // 2)) extent: subBnds extent // 2] ifFalse: [cached _ cacheCanvas form]. "draw the shadow" aCanvas asShadowDrawingCanvas translateBy: self shadowOffset during:[:shadowCanvas| cachedCanvasHasHoles ifTrue: ["Have to draw the real shadow of the form" shadowCanvas paintImage: cached at: subBnds origin] ifFalse: ["Much faster if only have to shade the edge of a solid rectangle" (subBnds areasOutside: (subBnds translateBy: self shadowOffset negated)) do: [:r | shadowCanvas fillRectangle: r color: Color black]]]. "draw morphs in front of the shadow using the cached Form" cachedCanvasHasHoles ifTrue: [aCanvas paintImage: cached at: subBnds origin] ifFalse: [aCanvas drawImage: cached at: subBnds origin sourceRect: cached boundingBox]. self drawOn: aCanvas. "draw the hand itself in front of morphs"! !!HandMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/13/2014 22:33'!handleMouseDown: evt "Dispatch a mouseDown event." | p m localEvt rootForGrab aHalo | "if carrying morphs, just drop them" self hasSubmorphs ifTrue: [^ self dropMorphsEvent: evt]. clickState ~~ #idle ifTrue: [^ self checkForDoubleClick: evt]. (keyboardFocus notNil and: [Preferences noviceMode]) ifTrue: [ "clear keyboard focus if click is outside the focus morph (needed for Scratch)" p _ (keyboardFocus transformFromWorld) transform: evt cursorPoint. (keyboardFocus bounds containsPoint: p) ifFalse: [ self newKeyboardFocus: nil]]. m _ self recipientForMouseDown: (grid "Don't grid when determining recipient" ifNil: [evt] ifNotNil: [ "Should really use original cursorPoint, but this will do" evt copy setCursorPoint: Sensor cursorPoint]). m ifNotNil: [ (m isKindOf: SpriteHandleMorph) ifFalse: [SpriteHandleMorph vanish]. "needed for Scratch" (ScratchMenuTitleMorph menuBarIsActive) ifTrue: [ (m isKindOf: MenuItemMorph) ifTrue: [ScratchMenuTitleMorph deactivateMenuBar ] ifFalse: [ScratchMenuTitleMorph closeAllMenus ]]. aHalo _ self world haloMorphOrNil. (aHalo isNil or: [aHalo staysUpWhenMouseIsDownIn: m]) ifFalse: [self world abandonAllHalos]. m deleteBalloon. (m handlesMouseDown: evt) ifTrue: ["start a mouse transaction on m" (self newMouseFocus: m) ifNil: [^ self]. localEvt _ self transformEvent: evt. targetOffset _ localEvt cursorPoint - m position. evt reserved = 3 ifTrue: [ evt type nslog: '2 fingers tap: by reserved'. ]. m mouseDown: localEvt. clickState == #firstClickDown ifFalse: [ "ensure that at least one mouseMove: is reported for each mouse transaction:" (mouseDownMorph == m) ifTrue: [ m mouseMove: (localEvt copy setType: #mouseMove)]. (m handlesMouseOverDragging: localEvt) ifTrue: ["If m also handles dragOver, enter it in the list" dragOverMorphs add: m. mouseOverMorphs remove: m ifAbsent: []]]] ifFalse: ["grab m by the appropriate root" menuTargetOffset _ targetOffset _ evt cursorPoint. rootForGrab _ m rootForGrabOf: m. rootForGrab ifNotNil: [self grabMorph: rootForGrab]]. mouseOverTimes removeKey: m ifAbsent: []].! !!HandMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/13/2014 22:35'!handleMouseHold: evt clickClient ifNil: [^self]. clickState _ #idle. clickClient mouseHold: firstClickEvent. ^ self resetClickState! !!HandMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/16/2015 10:44'!handleMouseOver: evt | mList allMouseOvers leftMorphs enteredMorphs now t balloonHelpEnabled | owner ifNil: [^ self]. balloonHelpEnabled _ Preferences balloonHelpEnabled. "Start with a list consisting of the topmost unlocked morph in the innermost frame (pasteUp), and all of its containers in that frame." mList _ self mouseOverList: evt. now _ Time millisecondClockValue. "Make a list of all potential mouse-overs..." allMouseOvers _ mList select: [:m | (balloonHelpEnabled and: [m wantsBalloon]) or: "to start a timer" [m handlesMouseOver: (evt transformedBy: (m transformFrom: self))]]. "to send mouseEnter:" leftMorphs _ mouseOverMorphs select: [:m | (allMouseOvers includes: m) not]. enteredMorphs _ allMouseOvers select: [:m | (mouseOverMorphs includes: m) not]. "Notify and remove any mouse-overs that have just been left..." leftMorphs do: [:m | mouseOverMorphs remove: m. m wantsBalloon ifTrue: [m deleteBalloon]. m mouseLeave: (evt transformedBy: (m transformFrom: self)). mouseOverTimes removeKey: m ifAbsent: [] ]. "Add any new mouse-overs and send mouseEnter: and/or start timers..." enteredMorphs do: [:m | mouseOverMorphs add: m. dragOverMorphs remove: m ifAbsent: []. "Cant be in two places at once" (m handlesMouseOver: evt) ifTrue: [m mouseEnter: (evt transformedBy: (m transformFrom: self))]. m wantsBalloon ifTrue: [mouseOverTimes at: m put: now]]. mouseOverTimes keys do: [:m | "check pending timers for lingering" t _ mouseOverTimes at: m. (now < t "clock wrap" or: [now > (t + 400)]) ifTrue: [ "lingered for 0.4 seconds" mouseOverTimes removeKey: m. m owner ifNotNil: "Not deleted during linger (--it happens ;--)" [(balloonHelpEnabled and: [m wantsBalloon]) ifTrue: [m showBalloon: m balloonText deleteAfter: 5]]]].! !!HandMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/2/2014 20:16'!mouseOverList: evt rank: rank "With rank = 1, returns a list consisting of the topmost unlocked morph in the innermost frame (pasteUp), and all of its containers in that frame. With rank = 2, returns the smae kind of list, but rooted in the next lower rootmorph. This can be useful to get mouseOvers below an active halo." | p roots mList mm r | p _ evt cursorPoint. roots _ self world rootMorphsAt: p. "root morphs in world" roots size >= rank ifTrue: [mList _ (roots at: rank) unlockedMorphsAt: p. mList size > 0 ifTrue: ["NOTE: We really only want the top morph and all its owners" mm _ mList first. r _ roots at: rank. mList _ OrderedCollection new. [mm == r] whileFalse: [mm ifNil: [^mList]. mList addLast: mm. mm _ mm owner]. mList add: r]] ifFalse: [mList _ Array empty]. ^ mList! !!HandMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/27/2014 23:44'!recordUnclaimedKeystroke: evt unclaimedKeystrokes ifNil: [unclaimedKeystrokes _ OrderedCollection new]. unclaimedKeystrokes addLast: evt. [unclaimedKeystrokes size > self maxUnclaimedKeystrokeSize] whileTrue: [unclaimedKeystrokes removeFirst]. "keep only most recent N keystrokes"! !!HandMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/9/2014 02:37'!restoreSavedPatchOn: aCanvas "Clear the changed flag and restore the part of the given canvas under this hand from the previously saved patch. If necessary, handle the transition to using the hardware cursor." IPhoneScratchProxy isActive ifTrue: [^self ipadRestoreSavedPatchOn: aCanvas]. hasChanged _ false. savedPatch ifNotNil: [aCanvas drawImage: savedPatch at: savedPatch offset. ((userInitials size = 0) and: [(submorphs size = 0) and: [temporaryCursor == nil]]) ifTrue: [ "Make the transition to using hardware cursor. Clear savedPatch and report one final damage rectangle to erase the image of the software cursor." super invalidRect: (savedPatch offset extent: savedPatch extent + self shadowOffset). Cursor currentCursor == Cursor normal ifFalse: [Cursor normal show]. "show hardware cursor" savedPatch _ nil]].! !!HandMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/20/2014 15:50'!toolType: aStringOrNil self toolTypeChanged: aStringOrNil. toolType := aStringOrNil. aStringOrNil ifNil: [self showTemporaryCursor: nil].! !!HandMorph methodsFor: '*ScratchOnIPad' stamp: 'mu 5/13/2014 22:33'!handleDoubleClick: evt clickState _ #idle. clickClient doubleClick: evt. ^ self resetClickState! !!HandMorph methodsFor: '*ScratchOnIPad' stamp: 'mu 9/11/2017 20:46'!ipadRestoreSavedPatchOn: aCanvas | patchExtent | hasChanged := false. savedPatch ifNil: [^self]. IPhoneScratchProxy isInPresentation ifTrue: [^self]. patchExtent := savedPatch extent. (patchExtent x = 16 and: [patchExtent y = 16]) ifTrue: [^self]. super invalidRect: (savedPatch offset extent: patchExtent + self shadowOffset).! !!HandMorph methodsFor: '*ScratchOnIPad' stamp: 'mu 8/27/2014 23:48'!maxUnclaimedKeystrokeSize IPhoneScratchProxy isActive ifTrue: [^IPhonePresentationSpaceKeyState maxUnclaimedKeystrokeSize]. ^10! !!HandMorph methodsFor: '*ScratchOnIPad' stamp: 'mu 7/9/2014 14:10'!simpleTouchDrawOn: aCanvas | sz shadowForm subBnds | drawHalfSize ifNil: [drawHalfSize _ false]. sz := submorphs size. sz = 0 ifTrue: [^self]. subBnds := Rectangle merging: (submorphs collect: [:m | m fullBounds]). (sz = 1 and: [submorphs first shouldBorderDrawOnDragging]) ifTrue: [ ^ aCanvas frameRectangle: subBnds width: 2 color: Color orange. ]. shadowForm := self shadowForm. drawHalfSize ifTrue: [ subBnds := (self position + ((subBnds origin - self position) // 2)) extent: subBnds extent // 2. shadowForm := shadowForm magnifyBy: 0.5. ]. aCanvas asShadowDrawingCanvas translateBy: 0@0 during:[:shadowCanvas | shadowCanvas paintImage: shadowForm at: subBnds origin] ! !!HandMorph methodsFor: '*ScratchOnIPad' stamp: 'mu 6/20/2014 15:50'!toolTypeChanged: aStringOrNil IPhoneScratchProxy isActive ifFalse: [^self]. ! !!HandMorph class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/13/2015 15:05'!initialize "HandMorph initialize" PasteBuffer _ nil. DoubleClickTime _ 400. HoldTime _ 1200. NormalCursor _ ColorForm mappingWhiteToTransparentFrom: Cursor normal.! !!MediaItemMorph methodsFor: 'initialization' stamp: 'mu 9/1/2014 12:48'!buildRightSideMorph "Answers the part of MediaItemMorph that includes the label, the edit/copy or record/play buttons, etc. This includes everything but the sprite image, the number, and the horizontal divider." | e c bottom | rightMorph _ Morph new. rightMorph color: (Color transparent). nameMorph _ UpdatingStringFieldMorph new acceptWhenFocusLost: true; font: (ScratchFrameMorph getFont: #UpdatingStringField); rightJustify: ScratchTranslator isRTL; getSelector: #mediaName; putSelector: #mediaName:; position: (0@0); target: self. nameMorph width: (5 * nameMorph height) asInteger. rightMorph addMorphBack: nameMorph. infoMorph _ (StringMorph contents: (media infoString)) font: (ScratchFrameMorph getFont: #MediaItemInfo); position: nameMorph left + 2 @ (nameMorph bottom). rightMorph addMorph: infoMorph. media isSound ifTrue: [ self addPlayButton. playButton position: (nameMorph left)@(infoMorph bottom + 5). self addStopButton. stopButton position: playButton topRight + (7@0). deleteButton _ self getDeleteButton. rightMorph addMorph: deleteButton. deleteButton left: stopButton right + 7. bottom _ stopButton bottom. ] ifFalse: [ e _ self getEditButton. rightMorph addMorph: e. e position: nameMorph left@(infoMorph bottom + 5). c _ self getCopyButton. rightMorph addMorph: c. c position: e topRight + (7@0). deleteButton _ self getDeleteButton. rightMorph addMorph: deleteButton. deleteButton position: c right + 7. bottom _ c bottom]. nameMorph extent: (deleteButton right max: nameMorph width)@(nameMorph extent y). deleteButton position: (nameMorph right - deleteButton width)@(infoMorph bottom + 6). soundSizeMorph _ (StringMorph contents: '') font: (ScratchFrameMorph getFont: #MediaItemInfo); position: nameMorph right @ nameMorph bottom. rightMorph addMorph: soundSizeMorph. soundSizeMorph contents: media mediaSizeInKilobytes asString , ' KB'; position: ((nameMorph right - soundSizeMorph width) @ nameMorph bottom). rightMorph extent: nameMorph width@bottom.! !!MenuMorph methodsFor: '*ScratchOnIPad-override-control' stamp: 'mu 1/19/2018 15:54'!popUpAt: aPoint forHand: hand "Present this menu at the given point under control of the given hand." | selectedItem i yOffset sub delta | hand resetClickState. popUpOwner _ hand. originalEvent _ hand lastEvent. selectedItem _ self items detect: [:each | each == lastSelection] ifNone: [self items isEmpty ifTrue: [^ self] ifFalse: [self items first]]. "Note: items may not be laid out yet (I found them all to be at 0@0), so have to add up heights of items above the selected item." i _ 0. yOffset _ 0. [(sub _ self submorphs at: (i _ i + 1)) == selectedItem] whileFalse: [yOffset _ yOffset + sub height]. self position: aPoint - (2 @ (yOffset + 8)). self bounds right > hand worldBounds right ifTrue: [self position: self position - (self bounds width - 4 @ 0)]. delta _ self bounds amountToTranslateWithin: (hand worldBounds insetBy: 0@20). delta = (0 @ 0) ifFalse: [self position: self position + delta]. hand world addMorphFront: self; startSteppingSubmorphsOf: self. hand newMouseFocus: selectedItem. self changed! !!MorphicEvent methodsFor: '*ScratchOnIPad-override' stamp: 'MU 5/24/2023 22:21'!blueButtonPressed "Answer true if the blue mouse button is being pressed. This is the third mouse button or cmd+click on the Mac." ^ (buttons anyMask: 1) or: [IPhoneScratchProxy isOnDevelopment and: [IPhonePresentationSpaceKeyState isCommandPressed and: [self reserved = 1]]]! !!MorphicEvent methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/13/2014 22:37'!rightButtonPressed "Answer true if the right mouse button is pressed. On Mac's, this is sometimes reported as the blue button or control-red-button. On Windows, this this is mapped to the yellow button. Answer true for any of these cases." ^ (buttons anyMask: 3) or: [self redButtonPressed & self controlKeyPressed] or: [self reserved = 3] or: [IPhonePresentationSpaceKeyState isCommandPressed]! !!MorphicEvent methodsFor: '*ScratchOnIPad-override' stamp: 'MU 5/16/2023 12:30'!yellowButtonPressed "Answer true if the yellow mouse button is being pressed. This is the second mouse button or option+click on the Mac." ^ (buttons anyMask: 2) or: [IPhonePresentationSpaceKeyState isCommandPressed]! !!MorphicEvent methodsFor: '*ScratchOnIPad' stamp: 'mu 5/13/2014 22:38'!reserved ^reserved ifNil: [0]! !!MorphicEvent methodsFor: '*ScratchOnIPad' stamp: 'mu 5/13/2014 22:38'!reserved: flag reserved := flag! !!MultilineStringMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 9/14/2018 15:35'!indexForPoint: aPoint "Answer the character index for the given point in screen coordinates." "Note: This could be speeded up by doing a binary search for the character index, but it seems fast enough." | y lineNum x lineStart line xRanges pair | lines size = 0 ifTrue: [^ 1]. y _ aPoint y - (self top + self insetY). lineNum _ ((y // lineHeight) + 1) max: 1. lineNum > lines size ifTrue: [^ (self startOfLine: lineNum) + 1]. x _ (aPoint x - self left - (self offsetForLine: lineNum) x) min: self width. x < 0 ifTrue: [ "start of a line" lineNum = 1 ifTrue: [^ 1] ifFalse: [^ self startOfLine: lineNum]]. "search for character index" lineStart _ self startOfLine: lineNum. line _ lines at: lineNum. xRanges _ renderer xRangesFor: line. 1 to: line size do: [:i | pair _ xRanges at: i ifAbsent: [^ 1]. (x between: pair first and: pair second) ifTrue: [^ lineStart + i]]. "end of line" lineNum = lines size ifTrue: [^ lineStart + line size + 1] ifFalse: [^ lineStart + line size].! !!MultilineStringMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/18/2014 23:23'!keyboardFocusChange: aBoolean hasFocus = aBoolean ifTrue: [^ self]. self changed. aBoolean ifTrue: [ self selectAll. self startStepping] ifFalse: [ self stopStepping]. hasFocus := aBoolean. IPhoneScratchProxy isActive ifTrue: [self ipadTextFieldFocused: aBoolean]! !!ListMultilineStringMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/16/2017 13:12'!mouseDown: evt | list p ownerList i | self isInWorld ifFalse: [^ self]. "not editable in presentation mode" super mouseDown: evt. p _ evt cursorPoint. (list _ self ownerThatIsA: ScratchListMorph) ifNotNil: [list focusCell: owner]. ownerList _ self ownerThatIsA: ScratchListMorph. ((deleteMorph bounds expandBy: 6) containsPoint: p) ifTrue: [ (ownerList notNil) ifTrue: [ i _ ownerList indexOfCell: self owner. ownerList deleteLineAt: i. (ownerList listContents size > (i - 1)) ifTrue: [ownerList focusIndex: i] ifFalse: [ownerList focusIndex: i - 1]]].! !!NewHandleMorph methodsFor: '*ScratchOnIPad-override-all' stamp: 'mu 5/17/2023 14:38'!delete super delete. LastClosedAt _ Time totalSeconds! !!NewHandleMorph methodsFor: '*ScratchOnIPad-override-all' stamp: 'mu 5/17/2023 14:46'!initialize (LastClosedAt notNil and: [Time totalSeconds - LastClosedAt < 1]) ifTrue: [(Delay forSeconds: 1) wait]. startedAt _ Time totalSeconds. waitingForClickInside _ true. super initialize. Preferences noviceMode ifTrue: [self setBalloonText: 'stretch']! !!NewHandleMorph methodsFor: '*ScratchOnIPad-override-all' stamp: 'MU 5/16/2023 21:50'!step Sensor anyButtonPressed ifTrue: [waitingForClickInside _ false. self position: Sensor cursorPoint - (self extent // 2). pointBlock value: self center. ^ self]. (Time totalSeconds - startedAt) > 1 ifTrue: [waitingForClickInside _ false]. waitingForClickInside ifTrue: [(self containsPoint: Sensor cursorPoint) ifFalse: ["mouse wandered out before clicked" ^ self delete]] ifFalse: [lastPointBlock value: self center. ^ self delete]! !!ObjStream methodsFor: '*ScratchOnIPad-entry points-override' stamp: 'mu 9/14/2018 17:43'!readObjFrom: aStream showProgress: showProgress "Read the root object from the given binary stream. If showProgress is true, display a progress bar." | objCount | objects _ OrderedCollection new. stream _ aStream. self readFileHeader. firstPass _ true. objCount _ stream uint32. showProgress ifTrue: [ | hand | (hand := World hands lastOrNil) ifNotNil: [hand position: World center]. Utilities informUserDuring: [:progressBar | | msg | msg := 'Reading' translated, '...'. progressBar value: msg. 1 to: objCount do: [:i | objects addLast: self readObjectRecord]. progressBar value: msg, '..'. firstPass _ false. objects do: [:rec | self fixReferencesForObjectRecord: rec]. progressBar value: msg, '.'. objects do: [:rec | self initializeUserDefinedFields: rec]. progressBar value: 'Done' translated,'!!'. Delay waitMSecs: 200]] ifFalse: [ objCount timesRepeat: [objects addLast: self readObjectRecord]. firstPass _ false. objects do: [:rec | self fixReferencesForObjectRecord: rec]. objects do: [:rec | self initializeUserDefinedFields: rec]]. ^ objects first first! !!ObjectiveCBridge class methodsFor: '*ScratchOnIPad-logging' stamp: 'mu 4/10/2015 15:45'!lg: string | nsString results | nsString := string asNSStringUTF8. results := self callNSLog: nsString. nsString release. ^results! !!ObjectiveCBridge class methodsFor: '*ScratchOnIPad-NSInvocation' stamp: 'mu 4/10/2015 17:29'!nsInvocationSetBoolType: aMethodSignatureOop signed: signedBoolean index: index value: aValue ^self primitiveNSInvocationSetCType: aMethodSignatureOop externalAddress signed: signedBoolean index: index value: aValue! !!ObjectiveCBridge class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/10/2015 15:37'!setDataTypeForInstance: nsInvokeInstance argumentType: argumentType index: indexNumber value: argumentValue argumentType = 'c' ifTrue: [^self nsInvocationSetCType: nsInvokeInstance signed: true index: indexNumber value: argumentValue]. argumentType = 'C' ifTrue: [^self nsInvocationSetCType: nsInvokeInstance signed: false index: indexNumber value: argumentValue]. argumentType = 'i' ifTrue: [^self nsInvocationSetIntType: nsInvokeInstance signed: true index: indexNumber value: argumentValue]. argumentType = 'I' ifTrue: [^self nsInvocationSetIntType: nsInvokeInstance signed: false index: indexNumber value: argumentValue]. argumentType = 's' ifTrue: [^self nsInvocationSetShortType: nsInvokeInstance signed: true index: indexNumber value: argumentValue]. argumentType = 'S' ifTrue: [^self nsInvocationSetShortType: nsInvokeInstance signed: false index: indexNumber value: argumentValue]. argumentType = 'l' ifTrue: [^self nsInvocationSetLongType: nsInvokeInstance signed: true index: indexNumber value: argumentValue]. argumentType = 'L' ifTrue: [^self nsInvocationSetLongType: nsInvokeInstance signed: false index: indexNumber value: argumentValue]. argumentType = 'q' ifTrue: [^self nsInvocationSetLongLongType: nsInvokeInstance signed: true index: indexNumber value: argumentValue]. argumentType = 'Q' ifTrue: [^self nsInvocationSetLongLongType: nsInvokeInstance signed: false index: indexNumber value: argumentValue]. argumentType = 'd' ifTrue: [^self nsInvocationSetDoubleType: nsInvokeInstance index: indexNumber value: argumentValue]. argumentType = 'B' ifTrue: [^self nsInvocationSetBoolType: nsInvokeInstance signed: false index: indexNumber value: argumentValue]. argumentType = 'f' ifTrue: [^self nsInvocationSetFloatType: nsInvokeInstance index: indexNumber value: argumentValue]. argumentType = '*' ifTrue: [^self nsInvocationSetStringType: nsInvokeInstance index: indexNumber value: argumentValue]. argumentType = '@' ifTrue: [^self nsInvocationSetPointerType: nsInvokeInstance index: indexNumber value: argumentValue]. argumentType = '#' ifTrue: [^self nsInvocationSetPointerType: nsInvokeInstance index: indexNumber value: argumentValue]. argumentType = ':' ifTrue: [^self nsInvocationSetPointerType: nsInvokeInstance index: indexNumber value: argumentValue]. argumentType = '?' ifTrue: [^self nsInvocationSetPointerType: nsInvokeInstance index: indexNumber value: argumentValue]. argumentType = '^v' ifTrue: [^self nsInvocationSetVoidPointerType: nsInvokeInstance index: indexNumber value: argumentValue]. argumentType = '^@' ifTrue: [^self nsInvocationSetVoidPointerType: nsInvokeInstance index: indexNumber value: argumentValue]. argumentType first = ${ ifTrue: [^self nsInvocationSetStructureType: nsInvokeInstance index: indexNumber value: argumentValue]. self halt. ! !!ObjectiveCObject methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/7/2017 14:33'!error: aString "The default behavior for error: is the same as halt:. The code is replicated in order to avoid showing an extra level of message sending in the Debugger. This additional message is the one a subclass should override in order to change the error handling behavior." | handler | (handler _ Processor activeProcess errorHandler) notNil ifTrue: [handler value: aString value: self] ifFalse: [Debugger openContext: thisContext label: aString contents: thisContext shortStack. ^ self] "nil error: 'error message'."! !!OffscreenWorldMorph methodsFor: '*ScratchOnIPad' stamp: 'mu 9/30/2017 00:02'!projectModified! !!PaintCanvas methodsFor: '*ScratchOnIPad-override-stepping' stamp: 'mu 9/11/2015 12:01'!step | h screenP canvasP | h _ World activeHand. screenP _ h gridPointRaw. canvasP _ self screenToCanvas: screenP. moveOrStampForm ifNotNil: [ ((palette mode = #stamp) or: [(palette mode = #move) and: [h hasMouseFocus: self]]) ifTrue: [ | drOffset | selectionRect ifNotNil: [self canvasChanged: selectionRect]. drOffset := dragOffset ifNil: [0@0]. selectionRect _ canvasP - drOffset extent: moveOrStampForm extent. self canvasChanged: (selectionRect expandBy: 1)]]. "force redraw to show move/stamp feedback" (bounds containsPoint: screenP) ifFalse: [^ self]. palette mode = #move ifTrue: [ selectionRect ifNil: [h showTemporaryCursor: Cursor crossHair asXOCursorForm]. (selectionRect notNil and: [Sensor anyButtonPressed not]) ifTrue: [ (selectionRect containsPoint: canvasP) ifTrue: [h showTemporaryCursor: Cursor handOpen asXOCursorForm] ifFalse: [h showTemporaryCursor: Cursor crossHair asXOCursorForm]]]. palette mode = #text ifTrue: [ (self textHandleContainsPoint: canvasP) ifTrue: [h showTemporaryCursor: Cursor handOpen asXOCursorForm] ifFalse: [h showTemporaryCursor: Cursor normal asXOCursorForm]].! !!PaintFrame methodsFor: '*ScratchOnIPad-geometry' stamp: 'mu 6/18/2014 23:51'!ipadCenterYOffset ^ (self world height // 8) negated! !!PaintFrame methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/8/2017 00:31'!makeZoomBar | b t | zoomBar _ AlignmentMorph newRow color: Color transparent; centering: #bottomRight; vResizing: #shrinkWrap. #(out in) do: [:n | b _ ToggleButton onForm: (ScratchFrameMorph skinAt: ('paintZoom', n asString capitalized, 'Button')) offForm: (ScratchFrameMorph skinAt: ('paintZoom', n asString capitalized, 'Button')). b target: self; actionSelector: #scaleCanvas:; actWhen: #buttonDown; arguments: (Array with: n); borderWidth: 0; setProperty: #balloonText toValue: ('Zoom ', n asString) localized. zoomBar addMorphBack: b. #out = n ifTrue: [ #(1 2 4 8 16) do: [:scale | t _ ToggleButton onForm: (ScratchFrameMorph skinAt: ('zoom', scale asString, 'ButtonPressed')) offForm: (ScratchFrameMorph skinAt: ('zoom', scale asString, 'Button')). t target: self; actionSelector: #scaleCanvas:; actWhen: #buttonDown; arguments: (Array with: scale); setProperty: #balloonText toValue: scale asString, 'x'. zoomBar addMorphBack: t. zoomBar addMorphBack: (Morph new extent: 6@2; color: Color transparent)]]]. ^ zoomBar! !!PaintFrame class methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 7/8/2014 01:51'!defaultExtent IPhoneScratchProxy isActive ifFalse: [^800@490]. ^960@500! !!PaintFrame class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/6/2014 15:16'!new ^ super new withButtonsForYes: false no: false okay: true cancel: true; title: 'Paint Editor'; extent: self defaultExtent! !!PaintPalette methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/4/2014 00:21'!updateOptionsPane | options font s spacer form b formMorph colorToUse brushThumbnail n2 aColor2 fName | optionsPane removeAllMorphs. options _ AlignmentMorph newRow width: (optionsPane width - 16); height: (optionsPane height - 30); color: Color transparent; hResizing: #shrinkWrap; vResizing: #shrinkWrap; inset: 0. (#(paint erase line) includes: self mode) ifTrue: [ brushSizeMorph _ AlignmentMorph newRow centering: #center; color: Color transparent. font _ (StrikeFont fontName: 'VerdanaBold' size: 11). s _ (StringMorph contents: 'Brush size: ' localized). self mode = #erase ifTrue: [s contents: ('Eraser size' localized ,': ')]. s font: font; color: Color gray darker. brushSizeMorph addMorphBack: s. self mode = #erase ifTrue: [colorToUse _ Color transparent] ifFalse: [colorToUse _ self color1]. brushSizeMorph addMorphBack: (Morph new extent: 2@5; color: Color transparent). brushSizeMorph addMorphBack: (ImageMorph new form: (ScratchFrameMorph skinAt: #downArrow)). brushSizeMorph addMorphBack: (Morph new extent: 4@5; color: Color transparent). brushThumbnail _ Morph new extent: 30@30; color: Color transparent. n2 _ self brushSize. (n2 <= 6) ifTrue: [n2 _ n2 + 1]. (n2 == 29) ifTrue: [n2 _ 23]. (n2 == 47) ifTrue: [n2 _ 25]. (n2 == 75) ifTrue: [n2 _ 27]. brushIcon _ ImageMorph new form: (PaintCanvas brushCursorSize: n2 color: colorToUse scale: 1). brushIcon position: (15@15 - ((n2//2)@(n2//2))). brushThumbnail addMorphBack: brushIcon. brushSizeMorph addMorphBack: brushThumbnail. options addMorphBack: brushSizeMorph]. (#(oval rect) includes: self mode) ifTrue: [ b _ ToggleButton onForm: (ScratchFrameMorph skinAt: #paintOptionsButtonPressed) offForm: (ScratchFrameMorph skinAt: #paintOptionsButton). b target: self; actionSelector: #shapeFilling:; arguments: (Array with: true); toggleMode: false. self shapeFilling ifTrue: [b on]. (self mode = #oval) ifTrue: [form _ Form extent: 16@17 depth: 16. (FormCanvas on: form) fillOval: form boundingBox color: self color1. formMorph _ ImageMorph new form: form; position: 7@5] ifFalse: [form _ Form extent: 16@17 depth: 8. form fillColor: self color1. formMorph _ ImageMorph new form: form; position: 7@5]. b addMorph: formMorph. options addMorphBack: b. options addMorphBack: (Morph new extent: 5@2; color: Color transparent). b _ ToggleButton onForm: (ScratchFrameMorph skinAt: #paintOptionsButtonPressed) offForm: (ScratchFrameMorph skinAt: #paintOptionsButton). b target: self; actionSelector: #shapeFilling:; arguments: (Array with: false); toggleMode: false. self shapeFilling ifFalse: [b on]. (self mode = #oval) ifTrue: [form _ Form extent: 16@17 depth: 16. (FormCanvas on: form) frameOval: form boundingBox width: 2 color: self color1. formMorph _ ImageMorph new form: form; position: 7@5] ifFalse: [form _ Form extent: 16@17 depth: 8. form border: (0@0 extent: 16@17) width: 2 fillColor: self color1. formMorph _ ImageMorph new form: form; position: 7@5]. b addMorph: formMorph. options addMorphBack: b]. #fill = self mode ifTrue: [ fillStylePane _ AlignmentMorph newRow inset: 0; borderWidth: 0; color: Color transparent; vResizing: #shrinkWrap; hResizing: #shrinkWrap. spacer _ Morph new extent: 5@5; color: Color transparent. #(color hGradient vGradient rGradient) do: [:style | b _ ToggleButton onForm: (ScratchFrameMorph skinAt: #paintOptionsButtonPressed) offForm: (ScratchFrameMorph skinAt: #paintOptionsButton). b target: self; actionSelector: #fillStyle:; arguments: (Array with: style); toggleMode: false. form _ Form extent: 16@17 depth: 32. (style == #color) ifTrue: [form fillColor: self color1]. (style == #hGradient) ifTrue: [form fillFromXColorBlock: [:m | self color2 mixed: m with: self color1]]. (style == #vGradient) ifTrue: [form fillFromYColorBlock: [:m | self color2 mixed: m with: self color1]]. (style == #rGradient) ifTrue: [form fillRadialFromXColorBlock: [:m | self color2 mixed: m with: self color1] center: 8@8]. formMorph _ ImageMorph new form: form; position: 7@5. formMorph lock. b addMorph: formMorph. b off. (style == self fillStyle) ifTrue: [b on]. fillStylePane addMorphBack: spacer fullCopy. fillStylePane addMorphBack: b. b position: b left@ b top + 2]. fillStylePane addMorphBack: spacer fullCopy. options addMorphBack: fillStylePane]. #text = self mode ifTrue: [ font _ (StrikeFont fontName: 'VerdanaBold' size: 9). fName _ canvasMorph canvasTextBox font name. textFontMenu _ ImageMorph new form: (ScratchFrameMorph skinAt: #textFontMenu). textFontMorph _ StringMorph new. textFontMorph font: font. textFontMorph forceUnicodeRendering: true. textFontMorph contents: (textFontMorph stringWithEllipses: fName limitedToWidth: 109). textFontMenu addMorph: textFontMorph. textFontMorph position: 8@3. textSizeMenu _ ImageMorph new form: (ScratchFrameMorph skinAt: #textSizeMenu). textSizeMorph _ StringMorph contents: canvasMorph canvasTextBox font pointSize asString font: font. textSizeMenu addMorph: textSizeMorph. textSizeMorph position: 9@3. aColor2 _ self color1. (aColor2 == Color transparent) ifTrue: [aColor2 _ Color white]. canvasMorph textColor: aColor2. canvasMorph changed. options addMorphBack: textFontMenu; addMorphBack: (Morph new width: 8; height: 5; color: Color transparent); addMorphBack: textSizeMenu]. optionsPane addMorph: options. options position: (optionsPane left + (optionsPane width // 2) - (options width // 2))@(optionsPane top + (optionsPane height //2) - (options height // 2)).! !!PasteUpMorph methodsFor: 'misc' stamp: 'mu 12/15/2014 22:49'!drawInvalidAreasOn: aCanvas "Redraw the damaged areas of the given canvas and clear the damage list. Return a collection of the areas that were redrawn." | rectList c i n mm morphs rects rectToFill remnants rect | rectList _ self damageRecorder invalidRectsFullBounds: self viewBox. self damageRecorder reset. self updateTrailsForm. n _ self submorphs size. morphs _ OrderedCollection new: n*2. rects _ OrderedCollection new: n*2. rectList do: [:r | "Experimental top-down drawing -- Traverses top to bottom, stopping if the entire area is filled. If only a single rectangle remains, then continue with the reduced rectangle." rectToFill _ r. i _ 1. [rectToFill == nil or: [i > n]] whileFalse: [mm := submorphs at: i ifAbsent: [^rectList]. ((mm fullBounds intersects: r) and: [mm isHidden not]) ifTrue: [morphs addLast: mm. rects addLast: rectToFill. remnants _ mm areasRemainingToFill: rectToFill. remnants size = 1 ifTrue: [rectToFill _ remnants first]. remnants size = 0 ifTrue: [rectToFill _ nil]]. i _ i+1]. "Now paint from bottom to top, but using the reduced rectangles." rectToFill ifNotNil: [c _ self pseudoDraw: rectToFill on: aCanvas]. [morphs isEmpty] whileFalse: [(rect _ rects removeLast) == rectToFill ifFalse: [c _ aCanvas copyClipRect: (rectToFill _ rect)]. morphs removeLast fullDrawOn: c]. morphs reset. rects reset]. ^ rectList! !!PasteUpMorph methodsFor: '*ScratchOnIPad-override-dropping' stamp: 'mu 5/1/2015 14:41'!acceptDroppingMorph: aMorph event: evt aMorph submorphsDo: [:m | (m isKindOf: HaloMorph) ifTrue: [m delete]]. self addMorphFront: aMorph. self isPartsBin ifTrue: [ aMorph isPartsDonor: true. aMorph allMorphsDo: [:m | m stopStepping]] ifFalse: [ | w | w := self world ifNil: [World]. w startSteppingSubmorphsOf: aMorph].! !!ReporterBlockMorph methodsFor: '*ScratchOnIPad-override' stamp: 'MU 4/5/2020 21:49'!fixBlockLayout "Update the positions of my submorphs." | mList maxH h x y | blockLayoutNeeded ifFalse: [^ self]. cachedForm _ nil. cachedFeedbackForm _ nil. mList _ self nonControlFlowSubmorphs. maxH _ 0. mList do: [:m | (m isKindOf: ArgMorph) ifTrue: [m fixArgLayout]. (m isKindOf: BlockMorph) ifTrue: [m fixBlockLayout]. maxH _ maxH max: m height]. h _ (maxH + 4) max: 17. x _ isBoolean ifTrue: [14] ifFalse: [10]. (mList size > 0 and: [mList first isKindOf: StringMorph]) ifTrue: [x _ x + 2]. mList do: [:m | (m isKindOf: StringMorph) ifTrue: [m color: self labelColor]. y _ (h - m height) // 2. m position: self position + (x@y). x _ x + m width + 3]. x _ x + (isBoolean ifTrue: [1] ifFalse: [-4]). self extent: (x + 10) @ h. (self ownerThatIsA: ScratchBlockPaletteMorph) ifNotNil: [ (self ownerThatIsA: ScratchBlockPaletteMorph) fixLayout].! !!SampledSound methodsFor: '*ScratchOnIPad-initialization-override' stamp: 'mu 8/26/2014 15:01'!setSamples: anArray samplingRate: rate "Set my samples array to the given array with the given nominal sampling rate. Altering the rate parameter allows the sampled sound to be played back at different pitches." "Note: There are two ways to use sampled sound: (a) you can play them through once (supported by this method) or (b) you can make them the default waveform with which to play a musical score (supported by the class method defaultSampleTable:)." "Assume: anArray is either a SoundBuffer or a collection of signed 16-bit sample values." "(SampledSound samples: SampledSound coffeeCupClink samplingRate: 5000) play" "copy the array into a SoundBuffer if necessary" anArray class isWords ifTrue: [samples _ anArray] ifFalse: [samples _ SoundBuffer fromArray: anArray]. samplesSize _ samples size. samplesSize >= SmallInteger maxVal ifTrue: [ "this is unlikely..." self error: 'sample count must be under ', SmallInteger maxVal printString]. originalSamplingRate _ rate. initialCount := (self samplingRate = originalSamplingRate) ifTrue: [samplesSize] ifFalse: [ (samplesSize * self samplingRate) // originalSamplingRate. ]. self loudness: 1.0. self reset.! !!SampledSound class methodsFor: '*ScratchOnIPad-file reading' stamp: 'mu 9/3/2018 22:54'!convertMp3FromFileNamed: fileName | utils nsFileName result newPath | utils := ObjectiveCBridge classObjectForName: 'SUYUtils'. nsFileName := fileName asNSStringUTF8. result := utils saveAiffFromPath: nsFileName. nsFileName isNil ifFalse: [nsFileName release]. ObjectiveCBridge wrapWithAutoReleasePool: [newPath := result asString]. ^ newPath ! !!SampledSound class methodsFor: '*ScratchOnIPad-instance creation' stamp: 'mu 9/3/2018 22:26'!basicFromFileNamed: fileName "Read a sound from the file of the given name. The resulting sound may be a SampledSound (mono) or a MixedSound (stereo)." "(SampledSound fromFileNamed: 'test.aif') play" | f id snd | f _ (FileStream readOnlyFileNamed: fileName) binary. id _ (f next: 4) asString. f position: 0. id = 'RIFF' ifTrue: [snd _ self readWAVFrom: f]. id = 'FORM' ifTrue: [snd _ self readAIFFrom: f]. id = '.snd' ifTrue: [snd _ self readSNDFrom: f]. f close. snd ifNotNil: [^ snd]. snd ifNil: [self error: 'Unrecognized audio file format']. ^ snd! !!SampledSound class methodsFor: '*ScratchOnIPad-instance creation' stamp: 'mu 9/3/2018 22:44'!fromFileNamed: fileName | targetFileName | targetFileName := fileName. (targetFileName endsWith: '.mp3') ifTrue: [targetFileName := self convertMp3FromFileNamed: fileName]. ^self basicFromFileNamed: targetFileName! !!ScratchCloseDialog methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/29/2014 11:24'!useMorphTitle ^true! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-accessing-override' stamp: 'mu 4/10/2017 10:39'!type: t "Set the type of thing being opened/saved in the file dialog box, in order to include the appropriate shortcuts. Then add relevant shortcut buttons and set the directory. Types include: #background #costume #list #project #projectSummary #scriptSnapshot #sound #sprite #stageShot" type _ t. self addShortcutButtons. self addMoreActionButtons. self setDirectory: (ScratchFileChooserDialog getLastFolderForType: type forSave: self forSave). list setPresetParentDirectory. self onOpen! !!ScratchFileChooserDialog methodsFor: 'accessing' stamp: 'mu 6/13/2014 23:21'!redirectSavesToSampleFolder "Check to see if we are about to save into the Sample projects directory. If so, change the default location to the user's project folder." (ScratchFileChooserDialog lastFolderIsSampleProjectsFolder) ifTrue: [#redirect nslog: ScratchFileChooserDialog userScratchProjectsDir. self setDirectory: ScratchFileChooserDialog userScratchProjectsDir].! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-events' stamp: 'mu 9/7/2018 15:58'!onClose | prox | list ifNotNil: [list stopPlayingSound]. (prox := IPhoneScratchProxy current) ifNotNil: [ prox scratchDialogClosed: self. ]! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-events' stamp: 'mu 7/9/2014 22:33'!onOpen | prox | (prox := IPhoneScratchProxy current) ifNotNil: [ prox scratchDialogOpened: self. ]! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 5/30/2014 00:48'!forSave ^ forSave ifNil: [forSave := false]! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 6/18/2014 16:11'!isSticky self forSave ifTrue: [^false]. ^super isSticky! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-shortcuts-override' stamp: 'mu 5/30/2014 01:47'!myHome "My Home button was pressed." list currentDirectory: self class homeDir. list setPresetParentDirectory! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-shortcuts-override' stamp: 'mu 5/30/2014 01:50'!scratchBackgrounds "Scratch Backgrounds button was pressed." | backgrounds | backgrounds _ ScratchFileChooserDialog getDefaultFolderForType: #background forSave: self forSave. backgrounds ifNotNil: [list currentDirectory: backgrounds; setPresetParentDirectory].! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-shortcuts-override' stamp: 'mu 5/30/2014 01:50'!scratchCostumes "Scratch Costumes button was pressed." | costumes | costumes _ ScratchFileChooserDialog getDefaultFolderForType: #costume forSave: self forSave. costumes ifNotNil: [list currentDirectory: costumes; setPresetParentDirectory].! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-shortcuts-override' stamp: 'mu 5/30/2014 01:48'!scratchSounds "Scratch Sounds button was pressed." | sounds | sounds _ ScratchFileChooserDialog getDefaultFolderForType: #sound forSave: self forSave. sounds ifNotNil: [list currentDirectory: sounds; setPresetParentDirectory].! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-shortcuts-override' stamp: 'mu 5/30/2014 01:47'!userProjects "My Projects button was pressed." list currentDirectory: self class userScratchProjectsDir. list setPresetParentDirectory! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/28/2017 17:36'!addShortcutButtons "Add shortcut buttons for my type to the shortcutColumn." | spacer | spacer _ Morph new extent: 5@5; color: Color transparent. shortcutColumn removeAllMorphs. shortcutColumn addMorphBack: (self shortcutButtonLabel: self labelForHomeFolder action: #myHome icon: #folderHouseIcon). shortcutColumn addMorphBack: spacer fullCopy. #background = self type ifTrue: [ shortcutColumn addMorphBack: (self shortcutButtonLabel: 'Backgrounds' action: #scratchBackgrounds icon: #folderCatIcon)]. #costume = self type ifTrue: [ shortcutColumn addMorphBack: (self shortcutButtonLabel: 'Costumes' action: #scratchCostumes icon: #folderCatIcon)]. #project = self type ifTrue: [ self forSave ifFalse: [ shortcutColumn addMorphBack: (self shortcutButtonLabel: 'Examples' action: #sampleProjects icon: #folderCatIcon). shortcutColumn addMorphBack: spacer fullCopy. ]. shortcutColumn addMorphBack: (self shortcutButtonLabel: 'My Projects' action: #userProjects icon: #folderIcon). ]. #sound = self type ifTrue: [ shortcutColumn addMorphBack: (self shortcutButtonLabel: 'Sounds' action: #scratchSounds icon: #folderCatIcon)]. self forSave ifFalse: [ IPhoneScratchProxy isActive ifTrue: [ shortcutColumn addMorphBack: spacer fullCopy. shortcutColumn addMorphBack: (self shortcutButtonLabel: 'Inbox' action: #inboxProjects icon: #folderIcon). ] ]! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/30/2014 13:08'!createFileChooserLayout: allowNewFile "Create the file chooser dialog box." list _ ScratchFilePicker forSave: allowNewFile. self removeAllMorphs. bottomSpacer delete. bottomSpacer _ nil. mainColumn addMorphBack: list. self title: 'Open'. allowNewFile ifTrue: [ forSave := true. self title: 'Save As'. newFileTitle _ StringMorph new contents: 'New Filename:' localized, ' '; color: (Color gray: 0.3); font: (ScratchFrameMorph getFont: #FileChooserNewFileTitle). newFileName _ StringFieldMorph new font: (ScratchFrameMorph getFont: #FileChooserNewFilename); color: (Color r: (211/255) g: (214/255) b: (216/255)); width: 180. newTitleBin addMorphBack: newFileTitle; addMorphBack: (Morph new extent: (5@5); color: Color transparent); addMorphBack: newFileName; addMorphBack: (AlignmentMorph newSpacer: Color transparent). ScratchTranslator isRTL ifTrue: [newTitleBin submorphs reversed do: [:m | m delete. newTitleBin addMorphBack: m]]]. mainColumn addMorphBack: newTitleBin; addMorphBack: buttonRow. self addMorphBack: shortcutColumn; addMorphBack: mainColumn; addMorphBack: fileInfoColumn.! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-override' stamp: 'MU 4/24/2021 23:43'!createScratchFileChooserFor: aScratchFrameMorph saving: savingFlag "Create a Scratch file chooser dialog box with a project thumbnail and info box." | labelFont contentsFont commentFont thumbnailHolder | scratchFrame _ aScratchFrameMorph. readingScratchFile _ savingFlag not. list _ (ScratchFilePicker forSave: savingFlag) extensions: #(scratch sb hex). self removeAllMorphs. bottomSpacer delete. bottomSpacer _ nil. mainColumn addMorphBack: list. savingFlag ifFalse: [ self title: 'Open Project'. list scratchInfoClient: self]. labelFont _ (ScratchFrameMorph getFont: #FileChooserLabel). contentsFont _ (ScratchFrameMorph getFont: #FileChooserContents). commentFont _ (ScratchFrameMorph getFont: #FileChooserComment). savingFlag ifTrue: [ forSave := true. self title: 'Save Project'. newFileTitle _ StringMorph contents: ('New Filename:' localized, ' ') font: labelFont. newFileTitle color: (Color gray: 0.3). newFileName _ StringFieldMorph new contents: scratchFrame projectName; client: self; font: contentsFont; color: (Color r: (211/255) g: (214/255) b: (216/255)); width: 180. tabFields add: newFileName. newTitleBin addMorphBack: newFileTitle; addMorphBack: (Morph new extent: (5@5); color: Color transparent); addMorphBack: newFileName; addMorphBack: (AlignmentMorph newSpacer: Color transparent). ScratchTranslator isRTL ifTrue: [newTitleBin submorphs reversed do: [:m | m delete. newTitleBin addMorphBack: m]]]. mainColumn addMorphBack: (Morph new extent: (5@9); color: Color transparent); addMorphBack: newTitleBin. thumbnailHolder _ AlignmentMorph newColumn centering: #center; color: Color transparent. thumbnailFrameMorph _ ImageFrameMorph new initFromForm: (ScratchFrameMorph skinAt: #dialogThumbnailFrame). thumbnailFrameMorph extent: (170@130). thumbnailHolder addMorph: thumbnailFrameMorph. fileInfoColumn addMorphBack: thumbnailHolder; addMorphBack: (Morph new extent: (5@6); color: Color transparent). "spacer" thumbnailMorph _ ImageMorph new form: (Form extent: 160@120 depth: 1). thumbnailFrameMorph addMorphFront: (thumbnailMorph position: ((thumbnailFrameMorph position) + (5@5))). authorLabelMorph _ StringMorph contents: 'Project author:' localized font: labelFont. authorLabelMorph color: (Color gray: 0.3). fileInfoColumn addMorphBack: authorLabelMorph. savingFlag ifTrue: [authorMorph _ StringFieldMorph new useStringFieldFrame; contents: ''; font: contentsFont. tabFields add: authorMorph] ifFalse: [fileInfoColumn addMorphBack: (Morph new extent: (5@6); color: Color transparent). "spacer" authorMorph _ StringFieldMorph new color: Color transparent; borderWidth: 0; contents: ''; isEditable: false; font: contentsFont]. fileInfoColumn addMorphBack: authorMorph; addMorphBack: (Morph new extent: (5@6); color: Color transparent). "spacer" commentLabelMorph _ StringMorph contents: 'About this project:' localized font: labelFont. commentLabelMorph color: authorLabelMorph color. fileInfoColumn addMorphBack: commentLabelMorph. commentMorph _ ScrollingStringMorph new borderWidth: 0; contents: ''; font: commentFont; extent: (210@110). savingFlag ifTrue: [commentMorph backForm: (ScratchFrameMorph skinAt: #stringFieldFrame). tabFields add: commentMorph] ifFalse: [commentMorph isEditable: false]. fileInfoColumn addMorphBack: commentMorph. fileInfoColumn addMorphBack: buttonRow. self addMorphBack: shortcutColumn; addMorphBack: mainColumn; addMorphBack: fileInfoColumn. savingFlag ifTrue: [ self scratchInfo: scratchFrame projectInfo. thumbnailMorph form: scratchFrame workPane thumbnailForm. "default author field to login name if known; else author" (aScratchFrameMorph loginName size > 0) ifTrue: [authorMorph contents: aScratchFrameMorph loginName] ifFalse: [authorMorph contents: aScratchFrameMorph author]].! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/8/2014 23:53'!delete self isInWorld ifTrue: [self onClose]. super delete! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/18/2014 17:39'!getUserResponseForFolder "Wait for the user to respond, then answer the full path name of the chosen directory or #cancelled if the user cancels the operation. To make a FileDirectory from the response string use the method: FileDirectory on: <reponse>." "Details: This is invoked synchronously from the caller. In order to keep processing inputs and updating the screen while waiting for the user to respond, this method has its own version of the World's event loop." | w | self openInWorld. w _ self world. w activeHand newKeyboardFocus: (tabFields at: 1). self extent: self extent. "force layout" self position: w center - (self extent // 2) + (0@(self centerYOffset)). "center on screen but disregard the shadow on the bottom" (self top < -2 and: [self top > -34]) ifTrue: [self top: -34]. list getDirectoryContents. response _ #cancelled. "default response" done _ false. [done "or: [list model isFinalSelection]"] whileFalse: [w doOneCycle]. self delete. w doOneCycle. "erase myself from the screen" response = #cancelled ifTrue: [^ #cancelled] ifFalse: [^ list currentDirectory].! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/18/2014 17:39'!getUserResponseForNewFile "Wait for the user to respond, then answer the full path name of the new file or #cancelled if the user cancels the operation." "Details: This is invoked synchronously from the caller. In order to keep processing inputs and updating the screen while waiting for the user to respond, this method has its own version of the World's event loop." | w fn | self openInWorld. w _ self world. w activeHand newKeyboardFocus: (tabFields at: 1). self extent: self extent. "force layout" self position: w center - (self extent // 2) + (0@(self centerYOffset)). "center on screen but disregard the shadow on the bottom" newFileName ifNotNil: [w activeHand newKeyboardFocus: newFileName]. (self top < -2 and: [self top > -34]) ifTrue: [self top: -34]. list getDirectoryContents. [true] whileTrue: [ done _ false. [done] whileFalse: [w doOneCycle]. response = #cancelled ifTrue: [^ #cancelled]. thumbnailMorph ifNotNil: [ "save info in project" scratchFrame author: authorMorph contents withBlanksTrimmed. scratchFrame projectComment: commentMorph contents]. fn _ newFileName contents withBlanksTrimmed. fn size > 0 ifTrue: [ fn _ fn collect: [:ch | ('\/:' includes: ch) ifTrue: [$-] ifFalse: [ch]]. "replace directory delimiters with dashes" ^ list currentDirectory pathName, FileDirectory pathNameDelimiter asString, fn]. newFileTitle color: Color red. self openInWorld. w activeHand newKeyboardFocus: newFileName].! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/29/2014 22:55'!iphoneSampleProjectsInner | bundleClassOop mainBundleOop resourcePathOop projectOops dirName | bundleClassOop := ObjectiveCObject findClassName: 'NSBundle'. mainBundleOop := bundleClassOop mainBundle. resourcePathOop := mainBundleOop resourcePath. projectOops := 'Projects' asNSStringMacRoman. resourcePathOop := resourcePathOop stringByAppendingPathComponent: projectOops. projectOops release. dirName := resourcePathOop asString. (FileDirectory default directoryExists: dirName) ifTrue: [ list currentDirectory: (FileDirectory default directoryNamed: dirName). list setPresetParentDirectory ].! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/14/2014 13:45'!labelForHomeFolder "Answer the name to use for the home folder. This is the user name unless the home folder location has been overridden by an entry in the Scratch.ini file." | home delimiter | UserHomeFolder notNil ifTrue: [^ 'Home' localized]. home _ ScratchPlugin primGetFolderPathOrNil: 1. home ifNil: [^ 'Home' localized]. delimiter _ FileDirectory pathNameDelimiter asString. ^ UTF8 withAll: ((home findTokens: delimiter) last translated)! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-private' stamp: 'mu 4/28/2017 13:55'!addMoreActionButtons | paddingWidth spacer buttonMorph | IPhoneScratchProxy isActive ifFalse: [^self]. self forSave ifFalse: [^self]. self type = #project ifTrue: [^self]. paddingWidth := 50. spacer := Morph new extent: paddingWidth@5; color: Color transparent. buttonRow addMorphFront: spacer fullCopy. buttonMorph := (self buttonLabel: '' localized action: #cloudUpload). buttonMorph setFlatIcon: (ScratchFrameMorph skinAt: #cloudUpload). buttonRow addMorphFront: buttonMorph ! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-private' stamp: 'mu 4/10/2017 15:26'!cloudUpload self setDirectory: SoiSettings tempDir. response _ true. done _ true. self delete. World doOneCycle.! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-private' stamp: 'mu 5/11/2015 15:37'!redirectSaveDirectoryIfNeeded self class lastFolderIsReadonlyFolder ifTrue: [ #redirect nslog: ScratchFileChooserDialog userScratchProjectsDir. self setDirectory: ScratchFileChooserDialog userScratchProjectsDir].! !!ScratchFileChooserDialog methodsFor: '*ScratchOnIPad-shortcuts' stamp: 'mu 5/5/2015 23:05'!inboxProjects | inboxProjects | inboxProjects _ ScratchFileChooserDialog homeIndoxDir. inboxProjects ifNotNil: [list currentDirectory: inboxProjects; setPresetParentDirectory].! !!ScratchFileChooserDialog class methodsFor: 'accessing' stamp: 'mu 5/29/2014 21:52'!homeDir "Return the home directory for this user. By default, this is either provided by the OS via primGetFolderPath: but it can be overridden by adding a 'homedir=path' entry to the Scratch.ini folder." | homeDir | UserHomeFolder ifNotNil: [^ UserHomeFolder]. "provided by Scratch.ini" "try in order: documents folder, user home folder, Scratch folder" homeDir _ FileDirectory on: (ScratchPlugin primGetFolderPath: 3). "documents" (FileDirectory default directoryExists: homeDir pathName) ifFalse: [ homeDir _ FileDirectory on: (ScratchPlugin primGetFolderPath: 1)]. "home" (FileDirectory default directoryExists: homeDir pathName) ifFalse: [ homeDir _ FileDirectory default]. "Scratch folder (last resort)" ^ homeDir! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 00:53'!basicBundleDir | bundleClassOop mainBundleOop resourcePathOop dirName | bundleClassOop := ObjectiveCObject findClassName: 'NSBundle'. mainBundleOop := bundleClassOop mainBundle. resourcePathOop := mainBundleOop resourcePath. dirName := resourcePathOop asString. ^ FileDirectory on: dirName! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/29/2014 23:17'!basicBundleMediaSubFolder: subFolderName | bundleClassOop mainBundleOop resourcePathOop dirName mediaOops subFolderOops | bundleClassOop := ObjectiveCObject findClassName: 'NSBundle'. mainBundleOop := bundleClassOop mainBundle. resourcePathOop := mainBundleOop resourcePath. mediaOops := 'Media' asNSStringMacRoman. resourcePathOop := resourcePathOop stringByAppendingPathComponent: mediaOops. mediaOops release. subFolderOops := subFolderName asNSStringMacRoman. resourcePathOop := resourcePathOop stringByAppendingPathComponent: subFolderOops. subFolderOops release. dirName := resourcePathOop asString. (FileDirectory default directoryExists: dirName) ifFalse: [dirName nslog: 'subdir not exists:']. ^ FileDirectory on: dirName! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 00:54'!bundleDir | dir | ObjectiveCBridge wrapWithAutoReleasePool: [ dir := self basicBundleDir]. ^dir! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 01:00'!bundleMediaDir | dir | dir := self bundleDir directoryNamed: 'Media'. dir exists ifFalse: [ dir pathName nslog: 'bundleMediaDir not exist'. ]. ^dir! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/29/2014 23:18'!bundleMediaSubFolder: subFolderName | dir | ObjectiveCBridge wrapWithAutoReleasePool: [ dir := self basicBundleMediaSubFolder: subFolderName]. ^dir! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 4/30/2015 15:24'!homeIndoxDir | dir | dir := ScratchFileChooserDialog homeDir directoryNamed: 'Inbox'. ^dir! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/29/2014 23:24'!iphoneMediaSubFolderForType: type forSave: aBoolean | subFolderName | subFolderName := type caseOf: { [#background] -> ['Backgrounds']. [#costume] -> ['Costumes']. [#sprite] -> ['Costumes']. [#sound] -> ['Sounds']. } otherwise: []. subFolderName ifNil: [^self homeDir]. aBoolean ifTrue: [^self userMediaSubFolder: subFolderName]. ^ self bundleMediaSubFolder: subFolderName ! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 4/30/2015 17:56'!lastFolderIsHomeInboxFolder IPhoneScratchProxy isActive ifFalse: [^false]. ^self homeIndoxDir pathNameTrimmed = (self getLastFolderForType: #project) pathNameTrimmed ! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/11/2015 14:55'!lastFolderIsReadonlyFolder ^self lastFolderIsSampleProjectsFolder or: [self lastFolderIsHomeInboxFolder]! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/30/2014 16:31'!sampleProjectsDir | dir | dir := self bundleDir directoryNamed: 'Projects'. dir exists ifFalse: [ dir pathName nslog: 'bundleProjectsDir not exist'. ]. ^dir! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/29/2014 23:30'!userMediaDir | dir | dir := FileDirectory default directoryNamed: 'Media'. dir exists ifFalse: [ dir := [FileDirectory default createDirectory: 'Media'] ifError: [:ex | FileDirectory default]. ]. ^dir! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad' stamp: 'mu 5/29/2014 23:33'!userMediaSubFolder: subFolderName | userMediaDir dir | userMediaDir := self userMediaDir. dir := userMediaDir directoryNamed: subFolderName. dir exists ifFalse: [ dir := [self userMediaDir createDirectory: subFolderName] ifError: [:ex | self userMediaDir]. ]. ^dir! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/10/2014 01:04'!chooseSpriteCostumeFor: aScratchFrameMorph "ScratchFileChooserDialog chooseSpriteCostumeFor: nil" | m | ScratchFileChooserDialog deleteDuplicates. [m _ self new createFileChooserLayout: false; title: 'New Sprite'; showThumbnails: true; type: #costume; extensions: #(gif jpeg jpg bmp png sprite); scratchFrame: aScratchFrameMorph; listExtent: 550@300] showIndicator. ^ m getUserResponse! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/29/2014 23:14'!getDefaultFolderForType: type ^self getDefaultFolderForType: type forSave: false! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/29/2014 23:16'!getDefaultFolderForType: type forSave: aBoolean | mediaDir | (type = #project) ifTrue: [^ self userScratchProjectsDir]. IPhoneScratchProxy isActive ifTrue: [^self iphoneMediaSubFolderForType: type forSave: aBoolean]. (FileDirectory default directoryExists: 'Media') ifTrue: [ mediaDir _ FileDirectory default directoryNamed: 'Media'. #background = type ifTrue: [ (mediaDir directoryExists: 'Backgrounds') ifTrue: [ ^ mediaDir directoryNamed: 'Backgrounds']]. (#(costume sprite) includes: type) ifTrue: [ (mediaDir directoryExists: 'Costumes') ifTrue: [ ^ mediaDir directoryNamed: 'Costumes']]. #sound = type ifTrue: [ (mediaDir directoryExists: 'Sounds') ifTrue: [ ^ mediaDir directoryNamed: 'Sounds']]]. ^ self homeDir! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/30/2014 02:05'!getLastFolderForType: type ^self getLastFolderForType: type forSave: false! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/30/2014 02:04'!getLastFolderForType: type forSave: forSave "Return the last used folder for the given type. If this is the first time the type has been used, return the default folder for that type." | dir | dir _ LastFolderForType at: type ifAbsent: [nil]. dir ifNotNil: [ (dir isKindOf: FileDirectory) ifTrue: [(dir parentDirectory directoryExists: dir pathName) ifTrue: [^ dir]]]. ^ ScratchFileChooserDialog getDefaultFolderForType: type forSave: forSave! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/13/2014 23:25'!lastFolderIsSampleProjectsFolder "Return true if the last projects folder is the sample projects folder." | lastDirPath sampleProjectDirPath | IPhoneScratchProxy isActive ifTrue: [^self sampleProjectsDir hasChild: (self getLastFolderForType: #project)]. lastDirPath _ (self getLastFolderForType: #project) pathName. sampleProjectDirPath _ (FileDirectory default directoryNamed: 'Projects') pathName. ^ lastDirPath beginsWith: sampleProjectDirPath! !!ScratchFileChooserDialog class methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/30/2015 15:35'!saveScratchFileFor: aScratchFrameMorph "Choose a file for saving the current Scratch project file. Display the thumbnail and info string for the current project and allow the info string to be edited. Answer the full name of the file in which to save the project or #cancelled if the operation is cancelled." "ScratchFileChooserDialog saveScratchFileFor: nil" | m result | ScratchFileChooserDialog deleteDuplicates. m _ self new createScratchFileChooserFor: aScratchFrameMorph saving: true; type: #project; redirectSaveDirectoryIfNeeded. result _ m getUserResponseForNewFile. result = #cancelled ifTrue: [^ result]. (result asLowercase endsWith: '.sb') ifFalse: [result _ result, '.sb']. ^ result! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 5/30/2014 13:04'!forSave ^forSave ifNil: [forSave := false]! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 5/30/2014 13:04'!forSave: aBoolean forSave := aBoolean! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 9/7/2018 15:28'!loadedSampledSound ^loadedSampledSound ifNil: [loadedSampledSound := Dictionary new].! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 5/29/2014 22:50'!presetParentDirectory ^ presetParentDirectory! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 4/28/2018 14:55'!scrollFrame ^self contentsPaneMorph! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 5/29/2014 22:51'!setPresetParentDirectory presetParentDirectory := currentDir parentDirectory pathName! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-menu' stamp: 'mu 8/14/2014 03:15'!directoryMenuOnIPad "Present a drop-down menu of all directories in my current path." | menu pathParts prefix n choice s subDir | subDir := currentDir pathName copyReplaceAll: self presetParentDirectory with: ''. pathParts _ subDir findTokens: '/'. menu _ CustomMenu new. prefix _ ''. n _ 1. pathParts do: [:part | menu add: (UTF8 withAll:(prefix, part translated)) action: n. prefix _ prefix ,' '. n _ n + 1]. pathParts isEmpty ifTrue: [^self]. choice _ menu startUp: nil withCaption: nil at: (directoryBarMorph right - 117)@(directoryBarMorph top + 8). choice ifNil: [^ self]. s _ WriteStream on: String new. 1 to: choice do: [:i | s nextPutAll: (pathParts at: i). i < choice ifTrue: [s nextPut: currentDir pathNameDelimiter]]. self currentDirectory: (self presetParentDirectory, '/', s contents).! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-private' stamp: 'mu 4/30/2015 17:40'!directoryActionsPossibleInSandboxDocumentDir | curDir homeDir | IPhoneScratchProxy isActive ifFalse: [^true]. curDir := self currentDirectory asFileDirectory. homeDir := ScratchFileChooserDialog homeDir. (homeDir hasChild: curDir) ifTrue: [^true]. (curDir pathNameTrimmed = homeDir pathNameTrimmed) ifTrue: [^true]. ^false! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-private' stamp: 'mu 4/30/2015 15:30'!directoryCreationPossibleInSandboxDocumentDir ^self directoryActionsPossibleInSandboxDocumentDir and: [self isInHomeIndoxDir not]! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-private' stamp: 'mu 4/30/2015 17:40'!directoryParentMovePossibleIn: parentDirs | curDir | IPhoneScratchProxy isActive ifFalse: [^true]. curDir := self currentDirectory asFileDirectory. parentDirs do: [:each | (curDir hasChild: each) ifTrue: [^false]. (curDir pathNameTrimmed = each pathNameTrimmed) ifTrue: [^false]. ]. ^true! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-private' stamp: 'mu 7/8/2014 21:39'!enableCreateNewDirectoryButton: aBoolean | button | button := topBarMorph deeplyFindSubMorphNamed: #newDirectoryButton. button ifNil: [^self]. button setDisabled: aBoolean not! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-private' stamp: 'mu 7/8/2014 21:38'!enableMoveParentActionButtons: aBoolean | button barColor | button := topBarMorph deeplyFindSubMorphNamed: #parentDirectoryButton. button ifNotNil: [button setDisabled: aBoolean not]. barColor := aBoolean ifFalse: [Color gray] ifTrue: [(Color r: 0.306 g: 0.322 b: 0.322)]. directoryBarMorph setLabelColor: barColor.! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-private' stamp: 'mu 4/21/2015 20:11'!fileEntries ^contentsPaneMorph contents submorphs! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-private' stamp: 'mu 8/14/2014 14:06'!truncateString: objName | utf8str n ellipses s w eWidth limitWidth | eWidth _ (ScratchTranslator stringExtent: '...' font: directoryBarMorph label font) x. limitWidth _ 190 - eWidth. utf8str := UTF8 withAll: objName. n _ utf8str asUTF32. ellipses _ ScratchTranslator ellipsesSuffix asUTF32. 1 to: n size do: [:i | s _ n copyFrom: 1 to: i. w _ directoryBarMorph label stringWidth: (s asUTF32, ellipses). w > limitWidth ifTrue: [ ^ ((n copyFrom: 1 to: i - 1) asUTF32, ellipses) asUTF8]]. ^utf8str! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-private' stamp: 'mu 4/30/2015 15:16'!updateDirectoryActionButtons self enableMoveParentActionButtons: (self directoryParentMovePossibleIn: self forbiddenParentDirectories). self enableCreateNewDirectoryButton: (self directoryCreationPossibleInSandboxDocumentDir).! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/30/2014 13:54'!buildButtons "Build my directory bar, parent buttons, and new folder button." | b f | IPhoneScratchProxy isActive ifTrue: [^ self buildButtonsOnIPad]. topBarMorph _ AlignmentMorph newRow hResizing: #spaceFill; vResizing: #rigid; centering: #center; color: Color transparent. directoryBarArrowMorph _ ImageMorph new form: (ScratchFrameMorph skinAt: #directoryBarArrow). directoryBarMorph _ ResizableToggleButton2 new offForm: (ScratchFrameMorph skinAt: #directoryBar) onForm: (ScratchFrameMorph skinAt: #directoryBar); padding: 3@5. directoryBarMorph target: self; actionSelector: #directoryMenu; actWhen: #buttonUp. topBarMorph addMorphBack: (Morph new extent: (5@5); color: Color transparent); addMorphBack: directoryBarMorph. b _ ToggleButton onForm: (ScratchFrameMorph skinAt: #parentDirectoryButtonOn) offForm: (ScratchFrameMorph skinAt: #parentDirectoryButton). b target: self; actionSelector: #showParentDirectory; actWhen: #buttonUp; isMomentary: true. topBarMorph addMorphBack: (Morph new extent: (5@5); color: Color transparent); addMorphBack: (b position: self position + (252@16)). f _ ToggleButton onForm: (ScratchFrameMorph skinAt: #newFolderIconSelected) offForm: (ScratchFrameMorph skinAt: #newFolderIcon). f target: self; actionSelector: #newDirectory; actWhen: #buttonUp; isMomentary: true. topBarMorph addMorphBack: (Morph new extent: (5@5); color: Color transparent); addMorphBack: (f position: self position + (274@16)). directoryBarMorph label: (UTF8 withAll: '<directory>') font: (ScratchFrameMorph getFont: #FilePickerDirectoryName); leftJustifyInset: 9. self addMorphFront: (directoryBarArrowMorph position: self topLeft + ((b left - 32)@((50 - directoryBarArrowMorph height) // 2))). self addMorphBack: (topBarMorph position: self topLeft + (5@5)).! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 9/16/2014 15:42'!buildButtonsOnIPad "Build my directory bar, parent buttons, and new folder button." | b f | topBarMorph _ AlignmentMorph newRow hResizing: #spaceFill; vResizing: #rigid; centering: #center; color: Color transparent. directoryBarArrowMorph _ ImageMorph new form: (ScratchFrameMorph skinAt: #directoryBarArrow). directoryBarMorph _ ResizableToggleButton2 new offForm: (ScratchFrameMorph skinAt: #directoryBar) onForm: (ScratchFrameMorph skinAt: #directoryBar); padding: 3@5. directoryBarMorph target: self; actionSelector: #directoryMenu; actWhen: #buttonDown. topBarMorph addMorphBack: (Morph new extent: (5@5); color: Color transparent); addMorphBack: directoryBarMorph. b _ ToggleButton new onForm: (ScratchFrameMorph skinAt: #parentDirectoryButtonOn) offForm: (ScratchFrameMorph skinAt: #parentDirectoryButton) overForm: (ScratchFrameMorph skinAt: #parentDirectoryButtonOn) disabledForm: (ScratchFrameMorph skinAt: #parentDirectoryButtonDisabled). b setNameTo: #parentDirectoryButton. b target: self; actionSelector: #showParentDirectory; actWhen: #buttonDown; isMomentary: true. topBarMorph addMorphBack: (Morph new extent: ( 20@5); color: Color transparent); addMorphBack: (b position: self position + (267@16)). self forSave ifTrue: [ f _ ToggleButton new onForm: (ScratchFrameMorph skinAt: #newFolderIconSelected) offForm: (ScratchFrameMorph skinAt: #newFolderIcon) overForm: (ScratchFrameMorph skinAt: #newFolderIconSelected) disabledForm: (ScratchFrameMorph skinAt: #newFolderIconDisabled). f setNameTo: #newDirectoryButton. f target: self; actionSelector: #newDirectory; actWhen: #buttonDown; isMomentary: true. topBarMorph addMorphBack: (Morph new extent: (20@5); color: Color transparent); addMorphBack: (f position: self position + (289@16)). ]. directoryBarMorph label: (UTF8 withAll: '<directory>') font: (ScratchFrameMorph getFont: #FilePickerDirectoryName); leftJustifyInset: 9. self addMorphFront: (directoryBarArrowMorph position: self topLeft + ((b left - 32)@((50 - directoryBarArrowMorph height) // 2))). self addMorphBack: (topBarMorph position: self topLeft + (5@5)).! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/28/2018 15:05'!buildContentsPane "Build a scroll pane to hold the directory contents." contentsPaneMorph _ ScrollFrameMorph2 new color: self color; contents: (Morph new color: self color); showHorizontalScrollbar: false; hBarInset: 18; vBarInset: 18. contentsPaneMorph handlesMouseEvents: false. self addMorphBack: contentsPaneMorph.! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/14/2014 14:07'!currentDirectory: aDirectoryOrString "Set my current directory to the given FileDirectory or path String." | s | (currentDir isKindOf: ScratchServerDirectory) ifTrue: [ fetchInProgress _ false. currentDir stopFetching]. (aDirectoryOrString isKindOf: String) ifTrue: [currentDir _ FileDirectory on: aDirectoryOrString] ifFalse: [currentDir _ aDirectoryOrString]. currentDir pathParts isEmpty ifTrue: [s _ '/'] ifFalse: [s _ currentDir pathParts last]. s := s translated. "trim directory name to fit button, if necessary" s := self truncateString: s. s = '/' ifTrue: [s _ 'Computer']. directoryBarMorph label: (UTF8 withAll: s) font: (ScratchFrameMorph getFont: #FilePickerDirectoryName). directoryBarMorph width: contentsPaneMorph width - 160. directoryBarArrowMorph right: directoryBarMorph right - 9. lastUpMSecs _ 0. self getDirectoryContents. self updateDirectoryActionButtons! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/21/2014 01:47'!directoryMenu "Present a drop-down menu of all directories in my current path." | menu pathParts prefix n serverEntries choice s serverPath | IPhoneScratchProxy isActive ifTrue: [^ self directoryMenuOnIPad]. self navigationForbidden ifTrue: [^ self]. menu _ CustomMenu new. pathParts _ currentDir pathParts. prefix _ ''. n _ 1. pathParts do: [:part | menu add: prefix asUTF8, part action: n. prefix _ prefix ,' '. n _ n + 1]. pathParts isEmpty ifTrue: [menu add: 'Computer' action: (FileDirectory on: '') pathName]. self addDriveShortcuts: menu. "if opening a Scratch project, allow access to servers" scratchInfoClient ifNotNil: [ serverEntries _ ScratchFrameMorph scratchServers. serverEntries size > 0 ifTrue: [ menu addLine. serverEntries do: [:entry | menu add: entry first action: n. n _ n + 1]]]. choice _ menu startUp: nil withCaption: nil at: (directoryBarMorph right - 117)@(directoryBarMorph top + 8). choice ifNil: [^ self]. (choice isKindOf: String) ifTrue: [ choice = 'Computer' ifTrue: [^ self currentDirectory: ''] ifFalse: [^ self currentDirectory: choice contents]]. choice > pathParts size ifTrue: [ entry _ serverEntries at: choice - pathParts size. ^ self currentDirectory: (ScratchServerDirectory new serverName: (entry at: 2); path: (entry at: 3))]. s _ WriteStream on: String new. 1 to: choice do: [:i | s nextPutAll: (pathParts at: i). i < choice ifTrue: [s nextPut: currentDir pathNameDelimiter]]. (currentDir isKindOf: ScratchServerDirectory) ifTrue: [ serverPath _ '/', s contents. (serverPath endsWith: '/') ifFalse: [serverPath _ serverPath, '/']. self currentDirectory: (currentDir copy path: serverPath)] ifFalse: [ self currentDirectory: s contents].! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/1/2015 14:05'!forbiddenParentDirectories ^{ ScratchFileChooserDialog sampleProjectsDir. ScratchFileChooserDialog bundleMediaDir. ScratchFileChooserDialog homeDir. ScratchFileChooserDialog homeIndoxDir. }! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/30/2015 22:20'!getLocalDirectoryContents "Generate and layout the morphs in my contents pane from the files and folder in the current local directory." | allNames fileNames dirNames ext page | "make an alphabetized list of all files and directory names" fileNames _ currentDir fileNames. extensions ifNotNil: [ "filter out files without a matching extension" fileNames _ fileNames select: [:n | extensions includes: (FileDirectory extensionFor: n) asLowercase]]. fileNames _ fileNames sort: [:n1 :n2 | n1 caseInsensitiveLessOrEqual: n2]. dirNames _ self getLocalDirectoryNames. dirNames _ dirNames sort: [:n1 :n2 | n1 caseInsensitiveLessOrEqual: n2]. allNames _ dirNames , fileNames. allNames _ allNames reject: [:n | n endsWith: '_th.gif']. "suppress Scratch project thumbnails" allNames _ allNames reject: [:n | n beginsWith: '.']. "suppress hidden files on Mac OS X and Unix" allNames _ allNames reject: [:n | ext _ (FileDirectory extensionFor: n) asLowercase. #(app dll exe ini image changes) includes: ext]. allNames _ allNames reject: [:n | ScratchPlugin isHidden: (currentDir fullNameFor: n)]. "suppress hidden files/folders on Win32" currentDir pathName = FileDirectory default pathName ifTrue: [ allNames _ allNames reject: [:fn | #(help icons 'license.txt' locale plugins 'scratch.app' 'inbox') includes: fn asLowercase]]. showThumbnails ifTrue: [page _ self thumbnailStylePageFor: allNames] ifFalse: [page _ self listStylePageFor: allNames]. contentsPaneMorph contents: page. showThumbnails ifTrue: [self startThumbnailFetchProcess]. self changeSelectionIndexBy: 1.! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'MU 4/27/2021 23:30'!getScratchInfoFromFile "Answer the project info dictionary for the currently selected file. Answer the empty dictionary if no file is selected or if the file does not include a project info dictionary (e.g. if it is in an older Scratch file format)." | result fullName f version buf | result _ Dictionary new. self selectedFile ifNil: [^ result]. (self selectedFile endsWith: '.hex') ifTrue: [ ^self createMicrobitProjectMetaInfo]. fullName _ currentDir fullNameFor: self selectedFile. (FileDirectory default fileExists: fullName) ifFalse: [^ result]. [f _ (FileStream readOnlyFileNamed: fullName) binary] ifError: [^ result]. [ version _ ObjStream scratchFileVersionFrom: (f next: 10) asString. (version = 1) | (version = 2) ifTrue: [ buf _ f next: f uint32. result _ ObjStream new readObjFrom: (ReadStream on: buf)]. ] ifError: []. f close. ^ result! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/8/2022 23:13'!listStylePageFor: allNames "Answer a new contents page as a column of list style entries." | page dirNames morphsToAdd x y m | page _ Morph new color: self color; width: self width - 20. dirNames _ currentDir directoryNames asSet. morphsToAdd _ OrderedCollection new: 1000. x _ page left + 7. y _ page top + 5. allNames do: [:n | | isDir | isDir := dirNames includes: n. m _ ScratchFilePickerEntry new name: n dir: currentDir isDirectory: isDir shouldLocalize: (self shouldLocalize: n isDir: isDir); width: self width - 60; color: self color; borderWidth: 0; useRoundedCorners. morphsToAdd add: (m position: x@y). y _ y + m height]. page addAllMorphs: morphsToAdd. ^ page! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/19/2015 00:21'!mouseDown: evt "Record whether the mouse went down in the currently highlit entry (wasSelected) and if it should be considered a double-click. See mouseUp: for details." evt hand newKeyboardFocus: self. evt hand waitForClicksOrDrag: self event: evt. wasSelected _ self highlightEntryAt: evt cursorPoint. isDoubleClick _ (wasSelected and: [lastUpMSecs notNil and: [(Time millisecondClockValue - lastUpMSecs) < 1000]]).! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 9/16/2014 16:49'!showParentDirectory "Go to my parent directory." (self directoryParentMovePossibleIn: self forbiddenParentDirectories) ifFalse: [^self]. self navigationForbidden ifTrue: [^ self]. self currentDirectory: currentDir parentDirectory! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/8/2022 23:12'!thumbnailStylePageFor: allNames "Answer a new contents page as tableau of thumbnails." | page dirNames morphsToAdd leftMargin rightMargin x y m thumbnailCache f | page _ Morph new color: self color; width: self width - 20. dirNames _ currentDir directoryNames asSet. thumbnailCache _ ThumbnailCache new directory: currentDir. thumbnailCache readThumbnailFile; updateThumbnails. morphsToAdd _ OrderedCollection new: 1000. leftMargin _ page left + 7. rightMargin _ page width - 75. x _ leftMargin. y _ page top + 5. allNames do: [:n | | isDir | isDir := dirNames includes: n. m _ ScratchFilePickerImageEntry new name: n dir: currentDir isDirectory: isDir shouldLocalize: (self shouldLocalize: n isDir: isDir). m borderWidth: 0; useRoundedCorners. f _ thumbnailCache thumbnailFor: n. f ifNotNil: [m thumbnailForm: f]. morphsToAdd add: (m position: x@y). x _ x + m width. x > rightMargin ifTrue: [ x _ leftMargin. y _ y + m height]]. page addAllMorphs: morphsToAdd. ^ page! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-event handling' stamp: 'mu 5/1/2018 14:34'!doubleClick: evt isDoubleClick := true. self mouseUp: evt! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-event handling' stamp: 'mu 4/30/2015 16:40'!mouseHold: evt | menu highlightedEntry | "Smalltalk isiPhone ifFalse: [^super mouseHold: evt]." highlightedEntry := self selectedEntryOrNil. highlightedEntry ifNil: [^self]. (highlightedEntry isKindOf: ScratchFilePickerEntry) ifFalse: [^self]. self directoryActionsPossibleInSandboxDocumentDir ifFalse: [^self]. menu := CustomMenu new. ((highlightedEntry entryIsEmptyDirectory) or: [highlightedEntry entryIsFile]) ifTrue: [ menu add: 'Remove' action: #removeFileEntry. ]. self isInHomeIndoxDir ifFalse: [ menu addLine. menu add: 'Rename' action: #renameFileEntry. ]. menu localize. menu invokeOn: self at: World cursorPoint + (-90@15).! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/22/2015 14:52'!removeFileEntry | fileEntry nm lastIndex entries | fileEntry := self selectedEntryOrNil. nm := fileEntry entryName. lastIndex := nm findLast: [:e | e = $.]. lastIndex > 1 ifTrue: [nm := nm copyFrom: 1 to: lastIndex-1]. (DialogBoxMorph ask: ((UTF8 withAll: nm), String cr, 'Really remove?' localized)) ifFalse: [^self]. (fileEntry entryIsDirectory) ifTrue: [ [self currentDirectory deleteDirectory: fileEntry entryName] ifError: []. ] ifFalse: [ fileEntry highlight: false. currentDir deleteFileNamed: fileEntry entryName ifAbsent: []. ]. self currentDirectory: currentDir. entries := self fileEntries. entries size <= 1 ifTrue: [ scratchInfoClient ifNotNil: [scratchInfoClient scratchInfo: nil]]. ! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 6/15/2015 16:18'!renameFileEntry | fileEntry nm origSuffix lastIndex answer newFileName renamedEntry | fileEntry := self selectedEntryOrNil. nm := fileEntry entryName. origSuffix := ''. lastIndex := nm findLast: [:e | e = $.]. lastIndex > 1 ifTrue: [ origSuffix := nm copyFrom: lastIndex to: nm size. nm := nm copyFrom: 1 to: lastIndex - 1. ]. answer := DialogBoxMorph request: 'New name:' initialAnswer: (UTF8 withAll: nm). answer isEmpty ifTrue: [^ self]. newFileName := answer, origSuffix. (self currentDirectory fileExists: newFileName) ifTrue: [^DialogBoxMorph inform: 'The file already exists:' localized, ' ', (UTF8 withAll: answer)]. self currentDirectory rename: fileEntry entryName toBe: newFileName. self currentDirectory: currentDir. contentsPaneMorph contents submorphsDo: [:m | (m isKindOf: ScratchFilePickerEntry) ifTrue: [ (UTF8 withAll: m entryName) = newFileName ifTrue: [ renamedEntry := m ] ifFalse: [m highlight: false] ] ]. renamedEntry ifNotNil: [self highlightAndScrollToEntry: renamedEntry].! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 4/30/2015 17:40'!isInHomeIndoxDir ^ ScratchFileChooserDialog homeIndoxDir pathNameTrimmed = self currentDirectory asFileDirectory pathNameTrimmed! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/8/2022 23:12'!shouldLocalize: fileOrDirectoryName isDir: isDir | isAscii curDir | isAscii := fileOrDirectoryName isAsciiString. isAscii ifFalse: [^ false]. isDir ifTrue: [^ true]. curDir := self currentDirectory asFileDirectory. {ScratchFileChooserDialog sampleProjectsDir. ScratchFileChooserDialog bundleMediaDir} do: [:targetDir | (targetDir hasChild: curDir) ifTrue: [^true]. (curDir pathNameTrimmed = targetDir pathNameTrimmed) ifTrue: [^true]. ]. ^ false! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-event handling-override' stamp: 'mu 5/1/2018 14:35'!mouseMove: evt "If the user drags away from the original selection and comes back, don't consider it a virtual double-click." (self highlightEntryAt: evt cursorPoint) ifFalse: [isDoubleClick _ false]. scratchInfoClient ifNotNil: [self reportScratchProjectInfo]. contentsPaneMorph contents submorphs detect: [:m | (m isKindOf: ScratchFilePickerEntry) and: [m containsPoint: evt cursorPoint]] ifNone: [ self scrollFrameDo: [:scrollFrame | scrollFrame mouseMove: evt] ]! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-event handling-override' stamp: 'mu 9/7/2018 15:10'!mouseUp: evt "Handle a mouse up. If the mouse went down on an entry that was already selected, open that entry. (Like a double-click, but not sensitive to timing.) If the entry 'double-clicked' was a directory, open that directory. If it was a file, set finalSelection to true to cause the dialog to open the file." | singleClickOpensDirs playSelectedSound entry ext | self scrollFrameDo: [:scrollFrame | scrollFrame mouseUp: evt]. singleClickOpensDirs _ false. playSelectedSound _ true. lastUpMSecs _ Time millisecondClockValue. (sound notNil and: [sound isPlaying]) ifTrue: [ self stopPlayingSound. isDoubleClick _ false. wasSelected ifTrue: [playSelectedSound _ false]]. entry _ contentsPaneMorph contents submorphs detect: [:m | m containsPoint: evt cursorPoint] ifNone: [^ self]. entry entryIsDirectory ifTrue: [ singleClickOpensDirs | isDoubleClick ifTrue: [ self currentDirectory: (currentDir directoryNamed: entry entryName)]. ^ self]. ext _ FileDirectory extensionFor: entry entryName asLowercase. playSelectedSound _ (playSelectedSound & extensions notNil) and: [extensions includesAnyOf: #('wav' 'mp3')]. playSelectedSound & isDoubleClick not ifTrue: [ (extensions includes: ext) ifTrue: [ self startPlayingSound: (currentDir fullNameFor: entry entryName)]]. finalSelection _ isDoubleClick. finalSelection ifTrue: [(self ownerThatIsA: ScratchFileChooserDialog) yes].! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-accessing-override'!createMicrobitProjectMetaInfo | dict | dict := Dictionary new. dict at: 'comment' put: 'Copy this .hex file to micro:bit. Then open the corresponding project with Pyonkee. Now you can interact with micro:bit. (This program can be edited with MakeCode.)' translated. dict at: 'thumbnail' put: (ScratchFrameMorph skinAt: #uploadToMicrobit). ^dict! !!ScratchFilePicker methodsFor: '*ScratchOnIPad-accessing-override' stamp: 'mu 9/7/2018 15:32'!startPlayingSound: fullName "Attempt to play the sound with given name." self stopPlayingSound. SoundPlayer stopPlayerProcess. sound := self loadedSampledSound at: fullName ifAbsent: [ | loaded | loaded := [SampledSound fromFileNamed: fullName] ifError: [nil]. loaded ifNotNil: [self loadedSampledSound at: fullName put: loaded]. loaded. ]. sound ifNotNil: [ (sound respondsTo: #volume:) ifTrue: [sound volume: 1.0]. sound play].! !!ScratchFilePicker class methodsFor: '*ScratchOnIPad-instance creation' stamp: 'mu 5/30/2014 13:07'!forSave: savingFlag | inst | inst := self basicNew. inst forSave: savingFlag. inst initialize. ^inst! !!ScratchFilePickerEntry methodsFor: '*ScratchOnIPad-initialization' stamp: 'MU 4/25/2021 00:29'!name: aString dir: owningDirectory isDirectory: dirFlag shouldLocalize: localizeOrNot | icon m n | directory _ owningDirectory. entryName _ aString. entryIsDirectory _ dirFlag. entryIsDirectory ifTrue: [icon _ ScratchFrameMorph skinAt: #folderIcon] ifFalse: [icon _ ScratchFrameMorph skinAt: #fileIcon]. n _ dirFlag ifTrue: [entryName] ifFalse: [self fileNameFor: entryName]. localizeOrNot ifTrue: [n := n translated]. nameMorph _ StringMorph contents: (UTF8 withAll: n) font: (ScratchFrameMorph getFont: #FilePickerEntry). self addMorph: (nameMorph position: self position + (28@3)). m _ ImageMorph new form: icon. self addMorph: (m position: self position + (6@((nameMorph height - 6) // 2))). highlit _ false. self extent: 200@(nameMorph height + 6).! !!ScratchFilePickerEntry methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 4/21/2015 20:40'!entryIsEmptyDirectory ^self entryIsDirectory and: [ (FileDirectory on: (directory fullNameFor: self entryName)) entries isEmpty ]! !!ScratchFilePickerEntry methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 4/21/2015 20:36'!entryIsFile ^self entryIsDirectory not! !!ScratchFilePickerEntry methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 8/13/2014 23:10'!localizedEntryName ^ nameMorph contents asString! !!ScratchFilePickerEntry methodsFor: '*ScratchOnIPad-private' stamp: 'MU 4/25/2021 00:28'!fileNameFor: fullPathFileName | baseName | baseName := FileDirectory baseNameFor: entryName. (fullPathFileName endsWith: '.hex') ifTrue: [baseName := baseName, '.hex']. ^baseName! !!ScratchFilePickerImageEntry methodsFor: '*ScratchOnIPad-initialization' stamp: 'mu 8/14/2014 13:22'!name: aString dir: owningDirectory isDirectory: dirFlag shouldLocalize: localizeOrNot | n eWidth | self color: Color transparent. self extent: 125@110. directory _ owningDirectory. entryName _ aString. entryIsDirectory _ dirFlag. thumbnailReady _ false. thumbnailMorph _ ImageMorph new. entryIsDirectory ifTrue: [thumbnailMorph form: (ScratchFrameMorph skinAt: #bigFolderIcon)] ifFalse: [thumbnailMorph form: ((Form extent: 4@4 depth: 8) fillColor: Color transparent)]. thumbnailMorph top: self bottom - thumbnailMorph height - 23. thumbnailMorph left: self left + ((self width - thumbnailMorph width) // 2). n _ dirFlag ifTrue: [entryName] ifFalse: [FileDirectory baseNameFor: entryName]. localizeOrNot ifTrue: [n := n translated]. nameMorph _ StringMorph contents: '' font: (ScratchFrameMorph getFont: #FilePickerEntry). eWidth _ (ScratchTranslator stringExtent: '...' font: (ScratchFrameMorph getFont: #FilePickerEntryHighlighted)) x. nameMorph contents: (self truncateString: n). nameMorph bottom: self bottom - 2. self isHighlit ifTrue: [nameMorph left: self left + ((self width - nameMorph width - eWidth) // 2)] ifFalse: [nameMorph left: self left + ((self width - nameMorph width) // 2)]. self addMorph: nameMorph. self addMorph: thumbnailMorph.! !!ScratchFilePickerImageEntry methodsFor: '*ScratchOnIPad-initialization' stamp: 'mu 8/14/2014 13:25'!truncateString: objName | utf8str n ellipses s w | utf8str := UTF8 withAll: objName. n _ utf8str asUTF32. ellipses _ ScratchTranslator ellipsesSuffix asUTF32. 1 to: n size do: [:i | s _ n copyFrom: 1 to: i. w _ nameMorph stringWidth: (s asUTF32, ellipses). w > (self width - 3) ifTrue: [ ^ ((n copyFrom: 1 to: i - 1) asUTF32, ellipses) asUTF8]]. ^utf8str! !!ScratchFrameMorph methodsFor: 'iphone' stamp: 'mu 4/16/2014 00:38'!setupTheLanguageOnThisDevice | lang | lang _ ScratchTranslator guessLanguage. self setLanguage: lang. ! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-initialization' stamp: 'mu 7/3/2014 21:48'!reloadLogo (topPane findA: SketchMorph) form: (ScratchFrameMorph skinAt: #scratchLogo)! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-updating' stamp: 'mu 8/7/2014 22:28'!updateFontScale: newScale | tempJustSaved | ScratchTranslator renderScale = newScale ifTrue: [^self]. self stopAll. tempJustSaved _ justSaved. (workPane submorphs copyWith: workPane) do: [:m | (m isKindOf: ScriptableScratchMorph) ifTrue: [ m convertStacksToTuples]]. ScratchTranslator renderScale: newScale. viewerPane rebuildCategorySelectors. (workPane submorphs copyWith: workPane) do: [:m | (m isKindOf: ScriptableScratchMorph) ifTrue: [ m convertTuplesToStacks]]. self updatePanes. self view: scriptsPane target tab: scriptsPane tabPane currentTab category: viewerPane currentCategory. justSaved _ tempJustSaved.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu' stamp: 'mu 7/14/2014 14:41'!aboutApp self openAbout: SoiUtils aboutTitle contents: SoiUtils aboutContents! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu' stamp: 'mu 9/10/2014 10:57'!aboutMedia self openAbout: SoiUtils aboutMediaTitle contents: SoiUtils aboutMediaContents! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu' stamp: 'mu 7/14/2014 14:40'!aboutSamples self openAbout: SoiUtils aboutSamplesTitle contents: SoiUtils aboutSamplesContents! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu' stamp: 'mu 4/21/2017 15:08'!askStepSpeed | s q | s _ StringDialog askWithCancel: 'Step speed (milliseconds)' initialAnswer: '1'. q _ [s asNumber] ifError: [nil]. q ifNil: [^ 1]. q _ (q within: 0 and: 1000*60) truncated. ^q! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu' stamp: 'MU 5/29/2021 12:27'!ipadHelpMenu: aMenuTitleMorph | menu | menu := IPhoneMenu new. menu add: 'Help Page' action: #launchHelpPage. menu addLine. menu add: 'Video Tutorial' action: #launchVideoTutorialPage. menu addLine. menu add: 'micro:bit Connection Tutorial' action: #launchMicrobitConnectTutorialPage. menu addLine. menu add: SoiUtils aboutTitle action: #aboutApp. menu addLine. menu add: SoiUtils aboutSamplesTitle action: #aboutSamples. menu addLine. menu add: SoiUtils aboutMediaTitle action: #aboutMedia. menu showAndTarget: self.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu' stamp: 'MU 5/29/2021 12:28'!launchMicrobitConnectTutorialPage self launchHelpFile: 'video-mb.html'.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu' stamp: 'mu 7/14/2014 14:40'!openAbout: title contents: contents | dialogBox | IPhoneScratchProxy isActive ifFalse: [^self]. dialogBox _ DialogBoxMorph new title: title; withButtonsForYes: false no: false okay: true cancel: false. dialogBox message: contents font: (ScratchFrameMorph getFont: #AboutScratch). dialogBox getUserResponse.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu' stamp: 'mu 6/2/2014 15:32'!openSetFontScaleMenu | origRenderScale menu choice | origRenderScale := ScratchTranslator renderScale. origRenderScale nslog: 'ScratchTranslator renderScale'. menu _ CustomMenu new. #(1.3 1.4 1.5 1.6 1.7 1.8 1.9 2.0 2.1 2.2) do: [:n | | s | s _ n printString, 'x'. (n = origRenderScale) ifTrue: [s _ s, ' *']. menu add: s action: n]. choice _ menu startUp. choice ifNotNil: [ [SoiSettings applySetting: 'FontScale' to: choice] fork. self updateFontScale: choice. ].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'MU 7/29/2022 15:10'!addSensorsMenuTo: aMenuMorph IPhoneScratchProxy isOnMac ifTrue: [^self]. aMenuMorph addLine. IPhoneScratchProxy sensorAccessorIsRunning ifTrue: [aMenuMorph add: 'Stop Sensing' action: #stopSensing] ifFalse: [aMenuMorph add: 'Start Sensing' action: #startSensing].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'mu 7/29/2014 11:05'!helpMenu: aMenuTitleMorph | menu | IPhoneScratchProxy isActive ifTrue: [^self ipadHelpMenu: aMenuTitleMorph]. menu _ CustomMenu new. menu add: 'Help Page' action: #launchHelpPage. menu add: 'Help Screens' action: #launchAllHelpScreens. menu addLine. menu add: 'About Scratch' action: #aboutScratch. menu localize. #(1 2 3) do: [:n | menu labels at: n put: ((menu labels at: n) copyFrom: 1 to: (menu labels at: n) size - 1), ScratchTranslator ellipsesSuffix]. menu invokeOn: self at: aMenuTitleMorph bottomLeft + (0@10).! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'MU 7/29/2022 15:01'!iphoneEditMenu: aMenuTitleMorph | menu | menu _ IPhoneMenu new. menu add: 'Undelete' action: #undoTool. menu addLine. ScratchProcess blockHighlightMSecs <= 1 ifTrue: [menu add: 'Start Single Stepping' action: #toggleSingleStepping] ifFalse: [menu add: 'Stop Single Stepping' action: #toggleSingleStepping]. menu addWithEllipsis: 'Set Single Stepping' action: #setSingleStepping. menu addLine. menu addWithEllipsis: 'Compress Sounds' action: #compressSounds. menu addWithEllipsis: 'Compress Images' action: #compressImages. menu addLine. workPane showMotorBlocks ifTrue: [menu add: 'Hide Motor Blocks' action: #hideMotorBlocks] ifFalse: [menu add: 'Show Motor Blocks' action: #showMotorBlocks]. self addSensorsMenuTo: menu. menu addLine. IPhoneScratchProxy microbitAccessorIsRunning ifTrue: [menu add: 'Show micro:bit status' action: #showMicrobitPopup] ifFalse: [menu add: 'Connect to micro:bit' action: #connectToMicrobit]. menu showAndTarget: self.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'MU 5/15/2023 17:05'!iphoneFileMenu: aMenuTitleMorph | menu | menu _ IPhoneMenu new. menu add: 'New' action: #newScratchProject. menu addWithEllipsis: 'Open' action: #openScratchProject. menu add: 'Save' action: #saveScratchProjectNoDialog. menu addWithEllipsis: 'Save As' action: #saveScratchProject. menu addLine. menu addWithEllipsis: 'Import Project' action: #importScratchProject. menu addWithEllipsis: 'Export Sprite' action: #exportSprite. menu addWithEllipsis: 'Import from iCloud' action: #importFromCloud. menu addWithEllipsis: 'Export to iCloud' action: #exportToCloud. menu addLine. menu addWithEllipsis: 'Project Notes' action: #editNotes. Sensor shiftPressed ifTrue: [ menu addLine. menu addWithEllipsis: 'Write Project Summary' action: #writeSummaryFile. menu addWithEllipsis: 'Write Multiple Project Summaries' action: #writeMultipleSummaries. ]. IPhoneScratchProxy isOnDevelopment ifTrue: [ menu addLine. fillScreenFlag ifTrue: [ menu add: 'Exit User Mode' action: #fillScreenOff] ifFalse: [ menu add: 'Enter User Mode' action: #fillScreenOn. menu add: 'Save Image in User Mode' action: #saveImageForEndUser]. ]. menu add: 'Quit' action: #quitScratch. menu invokeOn: self at: aMenuTitleMorph bottomLeft + (0@10).! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'mu 9/10/2014 10:44'!iphoneLaunchHelpFileInner: aFilename | fileName filePath | fileName := aFilename asString. filePath := SoiSettings helpPathOfCurrentLanguage asString, FileDirectory slash, fileName. (FileDirectory default fileExists: filePath) ifFalse: [DialogBoxMorph inform: 'Help file not found.' localized. ^ self beep]. self ipadOpenWebViewFileURLOn: filePath. ! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'mu 7/3/2014 00:10'!saveImageForEndUser (self confirm: 'Close non-Scratch windows and save thisimage in end-user (fillScreen) mode?') ifFalse: [^ self]. self prepareRelease. ScratchFrameMorph isXO ifTrue: [Preferences useLargeFonts]. self setLanguage: 'en'. World submorphs do: [:m | (m isKindOf: SystemWindow) ifTrue: [m delete]]. self clearStage. Display newDepth: 32. self fillScreenOn. World doOneCycleNow. Smalltalk snapshot: true andQuit: true. self startup. Sensor useOSEvents: true.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'mu 4/24/2017 13:42'!setSingleStepping "Ask whether script should be single-stepped." | menu mSecs | menu _ CustomMenu new title: 'Single-step speed?'. menu add: 'Turbo speed' action: 0. menu add: 'Normal' action: 1. menu add: 'Flash blocks (fast)' action: 30. menu add: 'Flash blocks (slow)' action: 200. menu add: 'Flash blocks (very slow)' action: 1000. mSecs _ menu localize startUp. mSecs ifNil: [^ self]. ScratchProcess blockHighlightMSecs: mSecs.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu-override' stamp: 'mu 4/15/2017 23:35'!writeSummaryFile: fullFileName "Write a summary of this project to a file." | s sprites f fName | s _ WriteStream on: (String new: 10000). s nextPutAll: 'Project: ', self projectName; crlf. fullFileName size > 0 ifTrue: [s nextPutAll: 'Location: ', fullFileName; crlf]. (projectInfo includesKey: 'author') ifTrue: [ s nextPutAll: 'Author: ', (projectInfo at: 'author'); crlf]. (projectInfo includesKey: 'scratch-version') ifTrue: [ s nextPutAll: 'Scratch: ', (projectInfo at: 'scratch-version'); crlf]. (projectInfo includesKey: 'comment') ifTrue: [ s nextPutAll: 'Notes:'; crlf. (projectInfo at: 'comment') lines do: [:l | s nextPutAll: ' ', l; crlf]. s crlf]. (projectInfo includesKey: 'history') ifTrue: [ s nextPutAll: 'History:'; crlf. (projectInfo at: 'history') lines do: [:l | s nextPutAll: ' ', l; crlf]. s crlf]. self writeSummaryTotalsOn: s. s nextPutAll: '--------'; crlf. workPane printSummaryOn: s. sprites _ workPane submorphs select: [:m | m isKindOf: ScratchSpriteMorph]. sprites do: [:m | s skip: -2. "remove last crlf" s nextPutAll: '--------'; crlf. m printSummaryOn: s]. s nextPutAll: '--------'; crlf. ParagraphEditor clipboardTextPut: s contents asText. fName _ fullFileName. fullFileName size = 0 ifTrue: [ fName _ ScratchFileChooserDialog chooseNewFileDefault: self uniqueSummaryFileName title: 'File Name?' type: #projectSummary. fName = #cancelled ifTrue: [^ self]] ifFalse: [ fName _ self uniqueSummaryFileName]. fName size = 0 ifTrue: [^self]. (fName asLowercase endsWith: '.txt') ifFalse: [fName := fName, '.txt']. f _ StandardFileStream newScratchFileNamed: fName. f ifNil: [^ self]. f nextPutAll: s contents. f close. IPhoneScratchProxy exportToCloudIfNeeded: fName! !!ScratchFrameMorph methodsFor: 'menu/button actions' stamp: 'mu 7/10/2014 23:41'!addSpriteMorph self world activeHand toolType: nil. self paintingInProgress ifTrue: [^ self beep]. World doOneCycle. self basicAddSpriteMorph! !!ScratchFrameMorph methodsFor: 'menu/button actions' stamp: 'mu 9/9/2014 16:41'!launchVideoTutorialPage self launchHelpFile: 'video.html'.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-defaults' stamp: 'mu 6/29/2015 10:52'!shortcutButtonsSpec^{ {#language. 'Set language'. #languageMenu:. [:btn :row | btn arguments: {btn}]}. {#save. 'Save this project'. #saveScratchProjectNoDialog. [:btn :row | ]}. {#mail. 'Create a mail for sending this project'. #mailProject. [:btn :row | btn setProperty: #nextPaddingWidth toValue: 7]}. {#airDrop. 'Share this project by AirDrop'. #shareProject. [:btn :row | btn setProperty: #nextPaddingWidth toValue: 7]}. {#mesh. 'Share this project variables and events by Mesh protocol'. #openMeshMenu. [:btn :row | ]}.}.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-settings' stamp: 'mu 4/10/2015 12:43'!readFontScaleSetting: fontScale | scale | scale := fontScale asNumber. self updateFontScale: scale.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-settings' stamp: 'mu 4/10/2015 12:43'!readLangSetting: language | lang | lang := language ifNil: [ScratchTranslator guessLanguage]. self setLanguage: lang. lang nslog: 'lang'.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-override' stamp: 'MU 7/29/2022 15:25'!addServerCommandsTo: menu "Add Scratch server commands to the given menu." | disable endCmd | disable _ false. "make this true to disable this feature" disable ifTrue: [^ self]. menu addLine. (workPane scratchServer notNil and: [workPane scratchServer sessionInProgress]) ifTrue: [ menu add: 'Show IP Address' action: #showNetworkAddress. endCmd _ workPane scratchServer isHosting ifTrue: ['Stop Hosting Mesh'] ifFalse: ['Leave Mesh']. menu add: endCmd action: #exitScratchSession] ifFalse: [ menu add: 'Host Mesh' action: #startHostingScratchSession. menu add: 'Join Mesh' action: #joinScratchSession]. menu add: 'Cancel' action: #yourself.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-override' stamp: 'mu 5/6/2017 14:56'!importSpriteOrProject: fileNameOrData "Read the sprite or project file and merge into the current project." | data f importedStage defaultForm defaultSound oldName oldPosition | data _ fileNameOrData. (data isKindOf: String) ifTrue: [ "read the contents of a local file" "(FileDirectory default fileExists: fileNameOrData) ifFalse: [^ self]." f _ (FileStream readOnlyFileNamedOrNil: fileNameOrData). f ifNil: [^ self]. data _ f binary contentsOfEntireFile]. [importedStage _ self extractProjectFrom: data] ifError: [^ self]. "fix references to old stage" importedStage allMorphsDo: [:m | (m isKindOf: WatcherMorph) ifTrue: [m mapReceiver: importedStage to: workPane]. (m isKindOf: ScriptableScratchMorph) ifTrue: [ m blocksBin submorphs do: [:stack | (stack isKindOf: BlockMorph) ifTrue: [ stack blockSequence do: [:b | b mapReceiver: importedStage to: workPane]]]]]. "add global variables from importated stage to my stage" importedStage varNames do: [:v | workPane addVariable: v value: (importedStage getVar: v)]. "add imported stage scripts" importedStage blocksBin submorphs do: [:stack | (stack isKindOf: BlockMorph) ifTrue: [workPane addStack: stack fullCopy]]. "add imported background costumes and scripts to my stage, filtering out default items" defaultForm _ workPane defaultImageMedia form hibernate. defaultSound _ SoundMedia new sound. importedStage media do: [:media | (media isImage and: [media form hibernate bits ~= defaultForm bits]) ifTrue: [workPane addMediaItem: media]. (media isSound and: [media sound samples ~= defaultSound samples]) ifTrue: [workPane addMediaItem: media]]. importedStage submorphs do: [:m | (m isKindOf: ScratchSpriteMorph) ifTrue: [ oldName _ m objName. oldPosition _ m position - m owner position + (47@55). "jm: I am not sure why this offset is needed. It's the rotation center of the default costume..." self addAndView: m. "assigns a new name" m objName: oldName. m position: workPane topLeft + oldPosition]]. workPane layoutChanged.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-override' stamp: 'MU 5/9/2021 13:51'!installNewProject: newWorkpane "Called after creating or reading a new project to clear the process scheduler, pick an object to view, clear the library thumbnails, and perform other housekeeping." | viewTarget sb | self stopAll. IPhoneScratchProxy cleanUp. newWorkpane class = ScratchStageMorph ifFalse: [^ self inform: 'Incompatible Scratch file format']. "self exitScratchSession." workPane scratchServer ifNotNil: [ workPane scratchServer clearCaches. workPane scratchServer stage: newWorkpane. newWorkpane scratchServer: workPane scratchServer]. newWorkpane isQuarterSize: workPane isQuarterSize. newWorkpane bounds: workPane bounds. newWorkpane midiPortNum: workPane midiPortNum. workPane closeMIDI. "use the same sensorboard for the new project" sb _ workPane sensorBoard. newWorkpane submorphs do: [:m | (m isKindOf: SensorBoardMorph) ifTrue: [ sb position: m position. newWorkpane replaceSubmorph: m by: sb. sb tryToOpenPort]]. newWorkpane sensorBoard: sb. workPane owner replaceSubmorph: workPane by: newWorkpane. workPane _ newWorkpane. self fixByteReversedSounds. "fix sprite positions (backward compatability)" workPane submorphs do: [:m | (m isKindOf: WatcherMorph) ifTrue: [m convertFromOldWatcher]. (m respondsTo: #costume) ifTrue: [ m position: m position + m costume rotationCenter]. "fix up positions" m layoutChanged]. workPane layoutChanged. "reset timer" ScriptableScratchMorph resetTimer. "pick an object view, or view the background if there is no other" viewTarget _ workPane. workPane submorphs do: [:m | (m respondsTo: #scripts) ifTrue: [ m scripts size >= viewTarget scripts size ifTrue: [viewTarget _ m]]]. viewTarget viewBlocksAndScripts. "populate the sprites list if it is empty (backward compatability)" workPane sprites isEmpty ifTrue: [ workPane submorphs do: [:m | (m isKindOf: ScriptableScratchMorph) ifTrue: [workPane sprites addLast: m]]]. scriptsPane tabPane currentTab: 'Scripts'. libraryPane clearLibrary. workPane clearPenTrails. self updateProjectName. ScratchProcess blockHighlightMSecs: 1. ScratchPrompterMorph clearLastAnswer. (projectInfo at: 'isHosting' ifAbsent: [false]) ifTrue: [ self enableRemoteSensors]. (projectInfo at: 'hasMotorBlocks' ifAbsent: [false]) ifTrue: [ self showMotorBlocks]. (projectInfo at: 'isSensingLocal' ifAbsent: [false]) ifTrue: [ self startSensing]. (projectInfo at: 'isSensingMicrobit' ifAbsent: [false]) ifTrue: [ self connectToMicrobit] ifFalse: [self disconnectFromMicrobit]. (projectInfo includesKey: 'penTrails') ifTrue: [ workPane penTrailsForm: (projectInfo at: 'penTrails')]. Clipboard _ nil. World cleanseStepList. "make sure garbage collect can clean up the old sprites" Smalltalk garbageCollect. "get rid of old sprite instances" self world ifNotNil: [self world startSteppingSubmorphsOf: self]. ScriptableScratchMorph scratchOrigin: workPane center. justSaved _ true.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-override' stamp: 'mu 5/29/2015 15:07'!joinScratchSession "Join another Scratch user or a Scratch-compatible remote application." | server addrString ok | server _ ScratchServer new. server stage: workPane. workPane scratchServer: server. addrString _ DialogBoxMorph request: 'IP Address'. addrString size = 0 ifTrue: [^ self]. ok _ workPane scratchServer joinSessionAt: addrString. ok ifFalse: [DialogBoxMorph inform: 'Could not connect' localized, ': ' , addrString].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-override' stamp: 'MU 4/25/2021 00:12'!openScratchProject "Allow the user to select a project to open, then open that project." | response newProj | self closeMediaEditorsAndDialogs ifFalse: [^ self]. self stopAll. (justSaved or: [self projectIsEmpty]) ifFalse: [ "ask the user if they want to save the current project" response _ DialogBoxMorph askWithCancel: 'Save the current project?'. response = #cancelled ifTrue: [^ self]. response ifTrue: [self saveScratchProjectNoDialog]]. response _ ScratchFileChooserDialog openScratchFileFor: self. response = #cancelled ifTrue: [^ self]. (response isKindOf: String) ifTrue: [ "read the contents of a local file" (response endsWith: '.hex') ifTrue: [ ^ self shareMicrobitHexProjectNamed: response]. ^ self openScratchProjectNamed: response]. (response isKindOf: ByteArray) ifTrue: [ [projectInfo _ self extractInfoFrom: response] ifError: [projectInfo _ Dictionary new]. [newProj _ self extractProjectFrom: response] ifError: [^ self]. self installNewProject: newProj. projectDirectory _ ScratchFileChooserDialog getDefaultFolderForType: #project].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-override' stamp: 'MU 12/11/2020 14:57'!openScratchProjectNamed: fName "Open a Scratch project with the given name." | f projData newProj dir fn| self closeMediaEditorsAndDialogs ifFalse: [^ self]. fn _ fName. f _ FileStream readOnlyFileNamedOrNil: fn. f ifNil: ["try a different encoding, fixes a Firefox bug, -Jens" fn _ fName isoLatinToMac asUTF8. f _ FileStream readOnlyFileNamedOrNil: fn. f ifNil: [^ self inform: 'Could not read' withDetails: (UTF8 withAll: (FileDirectory localNameFor: fName))]].(FileStream fullName: fn) nslog: '@@@project file path:'. [ projData _ f binary contentsOfEntireFile. newProj _ self extractProjectFrom: projData. projectInfo _ self extractInfoFrom: projData. ] ifError: [:err :rcvr | ^ self inform: 'Could not read project; file may be damaged' withDetails: '(', err, ')']. dir _ FileDirectory dirPathFor: fn. projectDirectory _ FileDirectory on: dir. ScratchFileChooserDialog setLastFolderTo: projectDirectory forType: #project. projectName _ FileDirectory localNameFor: fn. self installNewProject: newProj. self initializeWatcherPositions. viewerPane updateContents.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-override' stamp: 'mu 5/11/2015 15:08'!saveScratchProjectNoDialog | fName dir | self closeMediaEditorsAndDialogs ifFalse: [^ self]. projectName ifNil: [projectName _ '']. fName _ self nameFromFileName: projectName. dir _ ScratchFileChooserDialog getLastFolderForType: #project. (fName size = 0 | (dir fileExists: fName , '.sb') not) ifTrue: [^ self saveScratchProject]. ScratchFileChooserDialog lastFolderIsReadonlyFolder ifTrue: [^ self saveScratchProject]. self updateLastHistoryEntryIfNeeded. projectName _ FileDirectory localNameFor: (fName, '.sb'). "ignore path, if any; save in the original project directory" projectDirectory _ dir. self updateHistoryProjectName: projectName op: 'save'. self writeScratchProject.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-override' stamp: 'mu 6/15/2015 17:46'!showNetworkAddress "Display my IP address. This is a temporary feature to allow connected multiple Scratch computers in a peer-to-peer configuration without the help of a presence server." | localAddr wanAddr msg | IPhoneScratchProxy isActive ifTrue: [ msg := SoiUtils localPrimaryIpV4Address. ] ifFalse: [ localAddr _ NetNameResolver localHostAddress. msg := NetNameResolver stringFromAddress: localAddr. ]. msg isNil ifTrue: [^DialogBoxMorph inform: 'No IP Address. Please check network settings']. wanAddr := nil." wanAddr := ScratchServer getIPAddressFromServer." (wanAddr notNil and: [wanAddr ~= localAddr]) ifTrue: [ msg := msg, String cr, 'Internet' localized, ': ', (NetNameResolver stringFromAddress: wanAddr)]. DialogBoxMorph inform: msg title: 'IP Address'.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-override' stamp: 'mu 7/10/2014 01:03'!surpriseSpriteMorph | fileName f el m e | self world activeHand toolType: nil. self paintingInProgress ifTrue: [^ self beep]. [fileName _ self nextSurpriseCostumeName] showIndicator. fileName ifNil: [ ^ self addAndView: ScratchFrameMorph defaultSprite fullCopy]. [f _ Form fromFileNamed: fileName] ifError: [^ self]. el _ ImageMedia new form: (ScratchFrameMorph scaledFormForPaintEditor: f). m _ ScratchSpriteMorph new soleCostume: el. el mediaName: (m unusedMediaNameFromBaseName: (FileDirectory localNameFor: fileName)). self addAndView: m. e _ (workPane extent - m extent) abs // 2. m referencePosition: ((e x negated) to: e x) atRandom @ ((e y negated) to: e y) atRandom.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/27/2015 12:27'!airDropProject self shareProjectDoing: [:projectFullPath | self airDropProject: projectFullPath ] onOverwriteConfirming: 'Before share the project, save it?' ! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/27/2015 12:42'!airDropProject: projectPath | delegate nsString | delegate := IPhoneScratchProxy delegate. nsString := projectPath asNSStringUTF8. delegate airDropProject: nsString. nsString release.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 5/8/2021 18:23'!connectToMicrobit IPhoneScratchProxy isActive ifFalse: [^self]. IPhoneScratchProxy microbitAccessor start! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 5/8/2021 18:23'!disconnectFromMicrobit IPhoneScratchProxy isActive ifFalse: [^self]. IPhoneScratchProxy microbitAccessor stop! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/7/2017 15:41'!exportToCloud self shareProjectDoing: [:projectFullPath | self exportToCloud: projectFullPath ] onOverwriteConfirming: 'Before share the project, save it?' ! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/7/2017 15:41'!exportToCloud: projectPath | delegate nsString | delegate := IPhoneScratchProxy delegate. nsString := projectPath asNSStringUTF8. delegate exportToCloud: nsString. nsString release.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/25/2014 23:01'!forceCloseMediaEditorsAndDialogs | mList mHasCancel | mList _ PaintFrame allInstances select: [:m | m isInWorld]. mList size > 0 ifTrue: [ mList size = 1 ifTrue: [mList first yes; delete] ifFalse: [mList do: [:m | m cancelled; delete]]. paintingInProgress _ false]. mList _ ScratchSoundRecorderDialogMorph allInstances select: [:m | m isInWorld]. mList size > 0 ifTrue: [ mList do: [:m | m cancelled; delete]]. mList _ DialogBoxMorph allInstances select: [:m | m isInWorld]. mList size > 0 ifTrue: [ mList do: [:m | mHasCancel _ false. m buttons do: [:b | b action = #cancelled ifTrue: [mHasCancel _ true]]. mHasCancel ifTrue: [m cancelled; delete] ifFalse: [m no; delete]]]. DialogBoxMorph subclassesDo: [:c | mList _ c allInstances select: [:m | m isInWorld]. mList size > 0 ifTrue: [ mList do: [:m | mHasCancel _ false. m buttons do: [:b | b action = #cancelled ifTrue: [mHasCancel _ true]]. mHasCancel ifTrue: [m cancelled; delete] ifFalse: [m no; delete]]]]. "subclass of a subclass of DialogBoxMorph" mList _ NewVariableDialog allInstances select: [:m | m isInWorld]. mList size > 0 ifTrue: [ mList do: [:m | m cancelled; delete]]. ^ true! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/7/2017 16:47'!importFromCloud | delegate | delegate := IPhoneScratchProxy delegate. delegate importFromCloud! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/3/2017 13:22'!importMedia: fileName | m | (m _ self viewerPane target) ifNil: [^ self]. m importMedia: fileName! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/2/2014 19:42'!ipadMailProject: projectPath | delegate nsString | delegate := IPhoneScratchProxy delegate. nsString := projectPath asNSStringUTF8. delegate mailProject: nsString. nsString release. ! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/1/2014 18:48'!ipadOpenWebViewFileURLOn: filePath | delegate nsString | filePath nslog: 'ipadOpenWebViewFileURLOn:'. delegate := IPhoneScratchProxy delegate. nsString := filePath asNSStringUTF8. delegate openHelp: nsString. nsString release.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/27/2015 12:28'!mailProject self shareProjectDoing: [:projectFullPath | self ipadMailProject: projectFullPath ] onOverwriteConfirming: 'Before mail the project, save it?' ! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 5/12/2017 12:01'!midiAllNotesOff workPane ifNotNil: [workPane midiAllNotesOff]! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/25/2014 23:42'!openAutoSavedProjectNamed: lastProjectPath | autoSaveProjPath origProjName | autoSaveProjPath := ScratchFileChooserDialog userScratchProjectsDir pathName, FileDirectory slash, '--AutoSaved--.sb'. origProjName := FileDirectory localNameFor: lastProjectPath. origProjName := self nameFromFileName: origProjName. (origProjName beginsWith: '--AutoSaved--') ifTrue: [origProjName := ''].origProjName nslog: '+--+AutoSave read'. self openScratchProjectNamed: autoSaveProjPath. self projectName: origProjName. justSaved := false.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 10/21/2022 16:37'!openMeshMenu | menu | IPhoneScratchProxy osVersion >= 14.0 ifTrue: [ ^ IPhoneScratchProxy delegate openMeshDialog. ]. menu := IPhoneMenu new. self addServerCommandsTo: menu. menu showAndTarget: self.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 8/29/2014 15:15'!prepareBeforeRestart | isRunning isInPresentation autoSaveProjName orgProjName lastProjPath | IPhoneScratchProxy isActive ifFalse: [^self]. isRunning := self isRunning. isInPresentation := IPhoneScratchProxy isInPresentation. isInPresentation ifTrue: [self exitPresentationMode] ifFalse: [self forceCloseMediaEditorsAndDialogs]. autoSaveProjName := '--AutoSaved--'. orgProjName := (self nameFromFileName: (projectName isEmptyOrNil ifTrue: [autoSaveProjName] ifFalse: [projectName])). lastProjPath := projectDirectory pathName, FileDirectory slash, (self fileNameFrom: orgProjName). SoiUtils writeLastProjectStatus: {lastProjPath. self getViewModeIndex. isInPresentation. isRunning}. justSaved ifTrue: [lastProjPath nslog: '#ONCE SAVED'. ^self]. self updateLastHistoryEntryIfNeeded. projectName := FileDirectory localNameFor: (self fileNameFrom: autoSaveProjName). projectDirectory := ScratchFileChooserDialog userScratchProjectsDir.{projectName. projectDirectory} nslog: '##project name/dir'. self updateHistoryProjectName: (self fileNameFrom: orgProjName) op: 'save'. self exitScratchSession. self silentWriteScratchProject ! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/3/2014 00:11'!prepareRelease SoiUtils prepareRelease! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 5/1/2017 22:12'!setFontScaleIndex: idx | scale | scale := SoiSettings default fontScaleAt: idx. SoiSettings applySetting: 'FontScale' to: scale. [self updateFontScale: scale] fork.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 4/27/2021 23:57'!shareMicrobitHexProjectNamed: fName IPhoneScratchProxy isActive ifFalse: [^self]. self airDropProject: fName! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 5/29/2015 16:15'!shareProject "Sensor shiftPressed ifTrue: [ ^ self openMeshMenu ]". self airDropProject! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/28/2017 11:27'!shareProjectDoing: aBlock onOverwriteConfirming: aString | pName dir projectFullPath willOverwrite | IPhoneScratchProxy isActive ifFalse: [^self]. self closeMediaEditorsAndDialogs ifFalse: [^self]. projectName ifNil: [projectName := '']. pName := self nameFromFileName: projectName. willOverwrite := false. dir := ScratchFileChooserDialog getLastFolderForType: #project. (dir fileExists: (self fileNameFrom: pName)) not ifTrue: [ DialogBoxMorph inform: 'Please save the project first'. self saveScratchProjectNoDialog ] ifFalse: [ (ScratchFileChooserDialog lastFolderIsSampleProjectsFolder not and: [justSaved not]) ifTrue: [ willOverwrite := DialogBoxMorph ask: aString. ] ]. willOverwrite ifTrue: [ self updateLastHistoryEntryIfNeeded. projectName _ FileDirectory localNameFor: (self fileNameFrom: pName). ScratchFileChooserDialog lastFolderIsReadonlyFolder ifTrue: [dir := ScratchFileChooserDialog userScratchProjectsDir]. projectDirectory _ dir. self updateHistoryProjectName: projectName op: 'save'. (self silentWriteScratchProject) ifFalse: [DialogBoxMorph inform: 'Failed saving the project'. ^'']. ]. pName := self nameFromFileName: projectName. "retake" projectFullPath := projectDirectory fullNameFor: (self fileNameFrom: pName). (projectDirectory fileExists: projectFullPath) ifTrue: [ aBlock value: projectFullPath ] ! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'MU 4/14/2021 22:58'!showMicrobitPopup IPhoneScratchProxy microbitAccessor openPopup! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 5/11/2015 16:10'!silentWriteScratchProject [ | oldScriptsTarget oldTab oldViewerCategory oldPosition saveError out | self stopAll. self world ifNotNil: [self world activeHand newKeyboardFocus: nil]. "terminates active editor" "share duplicate sounds and images" self canonicalizeSoundsBits: nil saveOriginal: false. self canonicalizeImagesQuality: nil saveOriginal: false. oldScriptsTarget _ scriptsPane target. oldTab _ scriptsPane tabPane currentTab. oldViewerCategory _ viewerPane currentCategory. scriptsPane target: nil. workPane updateSpritesList. oldPosition _ workPane position. workPane delete; position: 0@0. self updatePenPositions. ScriptableScratchMorph buildBlockSpecDictionary. workPane allMorphsDo: [:m | (m isKindOf: ScriptableScratchMorph) ifTrue: [ m blocksBin allMorphsDo: [:b | (b isKindOf: BlockMorph) ifTrue: [b stop]]. m convertStacksToTuples]]. saveError _ nil. [ out _ FileStream newFileNamed: (projectDirectory unusedNameStartingWith: 'tmp'). out ifNil: [saveError _ 'Folder may be locked or read-only'] ifNotNil: [ out binary. out nextPutAll: 'ScratchV02' asByteArray. self storeProjectInfoOn: out. ObjStream new storeObj: workPane on: out. out close]. ] ifError: [:err :rcvr | out ifNotNil: [ [ out close. projectDirectory deleteFileNamed: out localName. ] ifError: []]. "clean up, ignoring any errors" saveError _ err]. workPane allMorphsDo: [:m | (m isKindOf: ScriptableScratchMorph) ifTrue: [ m convertTuplesToStacks]]. self addMorph: (workPane position: oldPosition). oldScriptsTarget ifNil: [oldScriptsTarget _ workPane]. oldScriptsTarget viewBlocksAndScripts. scriptsPane tabPane currentTab: oldTab. viewerPane currentCategory: oldViewerCategory. self updatePenPositions. ] showIndicator. ^ saveError ifNil: [ justSaved _ true. "self fixLayout." projectDirectory deleteFileNamed: projectName. [projectDirectory rename: out localName toBe: projectName]ifError: [^false]. ScratchFileChooserDialog setLastFolderTo: projectDirectory forType: #project. projectDirectory setMacFileNamed: projectName type: 'STsb' creator: 'MITS'. true] ifNotNil: [false]! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 6/8/2015 18:27'!startSensing IPhoneScratchProxy sensorAccessor start! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 6/8/2015 18:27'!stopSensing IPhoneScratchProxy sensorAccessor stop! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-mode' stamp: 'mu 8/1/2014 16:51'!getLastViewModeIndex ^ self getViewModeIndexOf: lastViewMode! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-mode' stamp: 'mu 8/1/2014 16:51'!getViewModeIndex ^ self getViewModeIndexOf: self viewMode! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-mode' stamp: 'mu 8/1/2014 16:51'!getViewModeIndexOf: aSymbol ^ aSymbol caseOf: { [#quarter]->[0]. [#normal]->[1]. [#presentation]->[2]. } otherwise: [1]! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-mode' stamp: 'mu 8/1/2014 13:19'!setViewModeIndex: viewModeNumberviewModeNumber nslog: '##viewModeNumber##'. viewModeNumber caseOf: { [0]->[self enterQuarterMode]. [1]->[self enterNormalMode]. [2]->[self enterPresentationMode]. }! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-mode' stamp: 'mu 8/1/2014 17:50'!setViewModeIndex: viewModeNumber presenting: presenOrNot running: runningOrNot presenOrNot ifTrue: [ viewMode := viewModeNumber = 1 ifTrue: [#normal] ifFalse: [#quarter]. self enterPresentationMode. ] ifFalse: [ self setViewModeIndex: viewModeNumber ]. runningOrNot ifTrue: [self shoutGo]. SoiNotificationCenter postNofification: 'ScratchProjectReloaded'! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-private' stamp: 'mu 7/10/2014 20:58'!basicAddSpriteMorph | result f el m | result _ ScratchFileChooserDialog chooseSpriteCostumeFor: self. result = #cancelled ifTrue: [^ self]. (result asLowercase endsWith: '.sprite') ifTrue: [^ self importSpriteOrProject: result]. [f _ Form fromFileNamed: result] ifError: [^ self]. el _ ImageMedia new form: (ScratchFrameMorph scaledFormForPaintEditor: f). m _ ScratchSpriteMorph new soleCostume: el. el mediaName: (m unusedMediaNameFromBaseName: (FileDirectory localNameFor: result)). self addAndView: m! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-private' stamp: 'mu 7/23/2014 12:25'!fileNameFrom: aProjectName ^(aProjectName , '.sb')! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-private' stamp: 'mu 7/4/2014 00:03'!ipadSetDefaultSprite DefaultSprite := SoiUtils defaultSprite. DefaultSprite ifNotNil: [ DefaultSprite media do: [:each | each mediaNameLocalized] ]! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/16/2015 10:26'!addShortcutButtonsTo: rowMorph | buttonSpecs b | "spec: name, tool-tip, selector, optionalBehaviorBlock" buttonSpecs := self shortcutButtonsSpec. buttonSpecs do: [:spec | b _ ToggleButton onForm: (ScratchFrameMorph skinAt: (spec at: 1), 'ButtonOver' ifAbsent: []) offForm: (ScratchFrameMorph skinAt: (spec at: 1), 'Button' ifAbsent: []) overForm: (ScratchFrameMorph skinAt: (spec at: 1), 'ButtonOver' ifAbsent:[]). b target: self; actionSelector: (spec at: 3); setBalloonText: (spec at: 2) localized; actWhen: #buttonUp; ignoreTransparentArea: true; isMomentary: true. (spec at: 4) value: b value: rowMorph. rowMorph addMorphBack: b] separatedBy: [ | sepa paddingWidth | paddingWidth := b valueOfProperty: #nextPaddingWidth ifAbsent: [14]. sepa := Morph new extent: (paddingWidth@5); color: Color transparent. rowMorph addMorphBack: sepa ]. rowMorph addMorphBack: (Morph new extent: (15@5); color: Color transparent).! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/7/2017 14:55'!allBlocksString | s stacks | s _ WriteStream on: (String new: 10000). ((Array with: workPane), self scratchObjects) do: [:obj | obj convertTuplesToStacks. stacks _ obj blocksBin submorphs select: [:m | m isKindOf: BlockMorph]. stacks size > 0 ifTrue: [ s nextPutAll: 'All stacks for ', obj objName, ':'; cr; cr. stacks do: [:blocks | self printTupleList: blocks tupleSequence on: s. s cr; cr]. s cr]]. ^ s contents! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/19/2014 22:50'!enterNormalMode "Go into normal (full-stage) mode." (viewMode = #normal) ifTrue: [ self updateViewModeButtons. ^ self]. viewMode _ #normal. workPane isQuarterSize: false. workPane isInWorld ifTrue: [self fixLayout] ifFalse: [self exitPresentationMode]. self updatePanes. "self updateViewModeButtons."! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/13/2014 00:43'!enterPresentationMode "Go into presentation mode." | presenter | ScratchPlugin pluginAvailable ifFalse: [ self updateViewModeButtons. ^ self beep]. (viewMode = #presentation) ifTrue: [^ self]. [lastViewMode _ viewMode. viewMode _ #presentation. IPhoneScratchProxy isInPresentation: true. self closeDialogBoxes. workPane isQuarterSize: false. presenter _ ScratchPresenterMorph new frame: self. self delete. Display fillBlack." Smalltalk fullScreenMode: true."" World restoreDisplay." Display fillBlack. World assuredCanvas. "re-allocate canvas after entering full-screen mode" ((Display width >= 965) & (Display height >= 750)) ifTrue: [presenter beDoubleSize]. presenter extent: Display extent. World addMorphFront: presenter. World startSteppingSubmorphsOf: presenter. World activeHand newKeyboardFocus: nil. self updatePenPositions. self updateViewModeButtons.] showIndicator. World assuredCanvas. "re-allocate canvas after entering full-screen mode" World fullRepaintNeeded. World displayWorldSafely. [(Delay forMilliseconds: 300) wait. World restoreDisplay] fork.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/19/2014 22:50'!enterQuarterMode "Go into quarter stage mode." (viewMode = #quarter) ifTrue: [ self updateViewModeButtons. ^ self]. viewMode _ #quarter. workPane isQuarterSize: true. workPane isInWorld ifTrue: [self fixLayout] ifFalse: [self exitPresentationMode]. self updatePanes. "self updateViewModeButtons."! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/13/2014 00:44'!exitPresentationMode "Exit presentation mode." TakeOverScreen ifFalse: [ Smalltalk fullScreenMode: false. World restoreDisplay]. ScriptableScratchMorph doubleSize: false. self addMorphFront: workPane. self fixLayout. World addMorphFront: self. World startSteppingSubmorphsOf: self. World fullRepaintNeeded. self updatePenPositions. IPhoneScratchProxy isInPresentation: false. lastViewMode = #normal ifTrue: [^ self enterNormalMode]. lastViewMode = #quarter ifTrue: [^ self enterQuarterMode].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/3/2014 01:22'!extractProjectFrom: aByteArray "Answer a Scratch project (i.e. a ScratchStageMorph possibly containing sprites) from the given ByteArray. Answer nil if the project cannot be unpacked." | s version proj | s _ ReadStream on: aByteArray. version _ ObjStream scratchFileVersionFrom: (s next: 10) asString. version = 0 ifTrue: [ s position: 0. proj _ ObjStream new readObjFrom: s showProgress: true]. (version = 1) | (version = 2) ifTrue: [ s skip: s uint32. "skip header" proj _ ObjStream new readObjFrom: s showProgress: true]. proj class = ScratchStageMorph ifFalse: [ version > 2 ifTrue: [self error: 'Project created by a later version of Scratch'] ifFalse: [self error: 'Problem reading project.']. ^ nil]. ScriptableScratchMorph buildBlockSpecDictionary. [proj allMorphsDo: [:m | (m isKindOf: ScriptableScratchMorph) ifTrue: [ "covert to new blocks" m convertStacksToTuples. m convertTuplesToStacks]]] showIndicator. ^ proj! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/21/2014 15:17'!fixLayout | stageExtent xyReadout w | stageExtent _ workPane isQuarterSize ifTrue: [SoiUtils quarterModeDrawExtent] ifFalse: [workPane extent]. topPane position: self topLeft; width: self width; height: (menuPanel height + 0 max: logoMorph height + 10). stageFrame extent: stageExtent + (14@42); top: topPane bottom; right: self right. workPane position: stageFrame topLeft + (4@37). titlePane position: stageFrame topLeft + (0@1); width: stageFrame width - 6; height: 36. self fixProjectTitleMorphLayout. scriptsPane fixLayout. w _ (viewerPane catButtonsExtent x + 17) within: 40 and: (self width - (scriptsPane bareMinimumWidth + stageFrame width)). viewerPane position: topPane bottomLeft; width: w; height: self bottom - topPane bottom. scriptsPane position: viewerPane topRight; width: self width - (stageFrame width + viewerPane width); height: self bottom - topPane bottom; fixLayout. libraryPane position: stageFrame bottomLeft; width: (self right - scriptsPane right); height: self bottom - libraryPane top. menuPanel left: logoMorph right + 18; top: topPane top + ((topPane height - menuPanel height) // 2) + 2. viewModeButtonsPanel right: stageFrame right - 8; top: self top + 7. stageButtonsPanel position: (stageFrame left + 10)@(topPane bottom + 5); width: stageFrame width - 28; height: (workPane top - stageFrame top) - 8. xyReadout _ readoutPane submorphs at: 1. readoutPane width: xyReadout width + 23; height: xyReadout height + 15; position: stageFrame bottomRight - ((readoutPane width + 6)@3). xyReadout position: readoutPane position + (18@5). toolbarPanel left: (stageFrame left - 4 max: menuPanel right); top: self top + ((topPane height - toolbarPanel height) // 2) + 3. ((toolbarPanel right - 5) > viewModeButtonsPanel left) ifTrue: [toolbarPanel delete] ifFalse: [ (toolbarPanel owner = self) ifFalse: [ self addMorphFront: toolbarPanel]].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/11/2015 17:42'!fixProjectTitleMorphLayout | s eWidth limitWidth conts | projectName ifNil: [^self]. s := (self nameFromFileName: projectName). eWidth := (ScratchTranslator stringExtent: '...' font: projectTitleMorph font) x. limitWidth := titlePane width - 100 - eWidth. conts := projectTitleMorph truncatedString: s limitWidth: limitWidth. projectTitleMorph contents: conts.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/2/2014 16:25'!languageMenu: aToggleButtonMorph "Present a menu of possible languages for blocks." | bullet menu choice | ScratchTranslator canRenderUnicode ifFalse: [ "try to find a Unicode plugin in case this is the first use after startup" ScratchTranslator detectRenderPlugin]. bullet _ UTF8 withAll: '• '. menu _ CustomMenu new. ScratchTranslator languageNames do: [:lang | ((ScratchTranslator isoCodeForName: lang) = (ScratchTranslator currentLanguage)) ifTrue: [menu add: (bullet, lang) action: lang] ifFalse: [menu add: lang action: lang]]. choice _ menu startUp: nil withCaption: nil at: aToggleButtonMorph bottomLeft + (0@10). choice ifNil: [^ self]. self stopAll. self setLanguage: choice. self recordLanguage: (ScratchTranslator currentLanguage). self updateFontScale: SoiSettings default fontScale.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/13/2014 23:49'!nextSurpriseCostumeName "Answer a surprise costume name or nil if there are no costumes." "Details: Shuffle the list of available costume names and return them one at a time. When there are none left, generate a new shuffle. This avoids repeats." | dir ext | (shuffledCostumeNames isNil or: [shuffledCostumeNames size = 0]) ifTrue: [ shuffledCostumeNames _ OrderedCollection new: 1000. dir _ ScratchFileChooserDialog getDefaultFolderForType: #costume. dir allFileNamesDo: [:fn | (fn includesSubString: 'Letters') ifFalse: [ ext _ (FileDirectory extensionFor: fn) asLowercase. ((ext size > 0) and: [#(gif png jpg) includes: ext]) ifTrue: [shuffledCostumeNames add: fn]]]]. shuffledCostumeNames _ shuffledCostumeNames shuffledBy: Random new. shuffledCostumeNames size = 0 ifTrue: [^ nil] ifFalse: [^ shuffledCostumeNames removeFirst].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/2/2014 15:52'!processSettingsFile "Process settings from the Scratch.ini file." | settings | ScratchFileChooserDialog clearFolderCache. "clear homeDir and last folder cache" settings _ self readSettingsFile. settings at: 'Home' ifPresent: [:p | ScratchFileChooserDialog setHomeDir: p]. settings at: 'VisibleDrives' ifPresent: [:p | self class setVisibleDrives: p] ifAbsent:[self class setVisibleDrives: nil]. settings at: 'Language' ifPresent: [:p | self readLangSetting: p] ifAbsent:[self readLangSetting: nil]. settings at: 'FontScale' ifPresent: [:p | self readFontScaleSetting: p]. 'Menu' localized nslog: 'Menu localized'. 'New' localized nslog: 'New localized'.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/2/2014 15:34'!readSettingsFile "Read my settings file and answer a Dictionary of settings." "ScratchFrameMorph new readSettingsFile" ^SoiSettings default readSettingsFile! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/2/2014 15:32'!recordLanguage: aString "Record my language in the settings file." "ScratchFrameMorph new recordLanguage: 'English'" SoiSettings applySetting: 'Language' to: aString! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/3/2014 23:24'!setDefaultSprite "Look for default sprite in Media directory. If none found, use the DefaultCatSprite" | d f data importedProject fName | IPhoneScratchProxy isActive ifTrue: [^self ipadSetDefaultSprite]. DefaultSprite _ nil. "if dfault.sprite exists, use that" d _ ScratchFileChooserDialog getDefaultFolderForType: #costume. (d fileExists: 'default.sprite') ifTrue: [ f _ (FileStream readOnlyFileNamed: (d fullNameFor: 'default.sprite')) binary. f ifNotNil: [ data _ f contentsOfEntireFile. importedProject _ [self extractProjectFrom: data] ifError: [nil]. importedProject ifNil: [^ self]. importedProject submorphs do: [:m | (m isKindOf: ScratchSpriteMorph) ifTrue: [DefaultSprite _ m]. ^ self]]]. "if default image exists, use the image and add 'pop' sound" #(gif png jpg bmp) do: [:e | fName _ 'default.', e. (d fileExists: fName) ifTrue: [ DefaultSprite _ ScratchSpriteMorph new importMedia: (d fullNameFor: fName); addMediaItem: (SoundMedia new mediaName: 'pop' localized; sound: ScratchSpriteMorph popSound). ^ self]].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/10/2015 16:56'!startup | startupFileNames fileName arg presentationMode | HostSystemMenus startUp. HostSystemMenus menuBarControler reviseHostMenus. ScriptableScratchMorph randomInit. ScratchTranslator detectRenderPlugin. IPhoneScratchProxy isActive ifFalse: [ ScratchTranslator importLanguagesList. ]. self processSettingsFile. self readDefaultNotes. self updateProjectName. shuffledCostumeNames _ nil. author _ ''. loginName _ ''. loginPassword _ ''. justSaved _ true. presentationMode _ false. startupFileNames _ InputSensor startupFileNames asOrderedCollection. 2 to: 10 do: [:i | arg _ Smalltalk getSystemAttribute: i. (arg notNil and: [arg size > 0]) ifTrue: [ startupFileNames addLast: (ScratchPlugin primShortToLongPath: arg)]]. startupFileNames do: [:n | (n asLowercase = 'presentation') ifTrue: [presentationMode _ true]. (n asLowercase = 'fullscreen') ifTrue: [TakeOverScreen _ true]]. TakeOverScreen ifTrue: [ Smalltalk fullScreenMode: true. World restoreDisplay]. self enterQuarterModeIfSmallScreen. fileName _ startupFileNames detect: [:fn | (fn asLowercase endsWith: '.sb') or: [fn asLowercase endsWith: '.scratch']] ifNone: [nil]. fileName ifNotNil: [ presentationMode ifTrue: [Display fillColor: Color black]. self openScratchProjectNamed: fileName. presentationMode ifTrue: [self enterPresentationMode; shoutGo]. ^ self]. viewerPane currentCategory: 'motion'. self setDefaultSprite. self newScratchProject. fileName _ startupFileNames detect: [:fn | fn asLowercase endsWith: '.sprite'] ifNone: [^ self]. "open a .sprite file" workPane submorphs do: [:m | (m isKindOf: ScratchSpriteMorph) ifTrue: [m deleteSprite]]. self importSpriteOrProject: fileName.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'MU 4/1/2021 21:19'!updateHistoryProjectName: projName op: operation "The given user is about to save or upload a project with the given name. Update the project history. operation is a string specifying the operation." | timestamp tab history platform osVersion | projectInfo removeKey: 'organization' ifAbsent: []. "obsolete" projectInfo at: 'scratch-version' put: Version. timestamp _ (Date today printFormat: #(3 2 1 $- 1 1)), ' ', Time now print24. tab _ String tab. history _ projectInfo at: 'history' ifAbsent: ['']. history _ history, timestamp, tab. history _ history, operation, tab, (self nameFromFileName: projName), tab, loginName, tab, author. history _ history, String cr. projectInfo at: 'history' put: history. "record other data" projectInfo at: 'scratch-version' put: Version. projectInfo at: 'language' put: ScratchTranslator currentLanguage. platform _ Smalltalk platformName. platform ifNil: [platform _ 'unknown']. 'linux' = platform ifTrue: [ Display extent = (1200@900) ifTrue: [platform _ 'XO']]. projectInfo at: 'platform' put: platform. osVersion _ Smalltalk osVersion. osVersion ifNil: [osVersion _ 'unknown']. projectInfo at: 'os-version' put: osVersion. (workPane scratchServer notNil and: [workPane scratchServer isHosting]) ifTrue: [projectInfo at: 'isHosting' put: true] ifFalse: [projectInfo removeKey: 'isHosting' ifAbsent: []]. (IPhoneScratchProxy isActive and: [IPhoneScratchProxy microbitAccessorIsRunning]) ifTrue: [projectInfo at: 'isSensingMicrobit' put: true] ifFalse: [projectInfo removeKey: 'isSensingMicrobit' ifAbsent: []]. (IPhoneScratchProxy isActive and: [IPhoneScratchProxy sensorAccessorIsRunning]) ifTrue: [projectInfo at: 'isSensingLocal' put: true] ifFalse: [projectInfo removeKey: 'isSensingLocal' ifAbsent: []]. (self allBlocksString includesSubString: 'motor') ifTrue: [projectInfo at: 'hasMotorBlocks' put: true] ifFalse: [projectInfo removeKey: 'hasMotorBlocks' ifAbsent: []]. workPane penTrailsForm ifNil: [projectInfo removeKey: 'penTrails' ifAbsent: []] ifNotNil: [projectInfo at: 'penTrails' put: workPane penTrailsForm].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/19/2014 22:49'!updatePanes [ | p | menuPanel delete. self createMenuPanel. toolbarPanel delete. self createToolbar. viewModeButtonsPanel delete. self createViewModeButtonsPanel. stageButtonsPanel delete. self createStageButtonsPanel. titlePane addMorph: stageButtonsPanel. scriptsPane tabPane delete. scriptsPane createTabPane. readoutPane delete. self createReadoutPane. workPane sensorBoard owner ifNil: [p _ nil] ifNotNil: [p _ workPane sensorBoard position]. workPane sensorBoard addReadouts. p ifNotNil:[ self showSensorBoard. workPane sensorBoard position: p]. libraryPane clearLibrary. self scratchWatchers do: [:w | w languageChanged]. self listWatchers do: [:w | w fixLayoutForNewLanguage]. World startSteppingSubmorphsOf: self. self fixLayout. scriptsPane fixLayout. self updateViewModeButtons.] showIndicator! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-override' stamp: 'MU 12/11/2020 15:29'!writeScratchProject "Write this Scratch project to the file named projectFile in the project directory. Called by saveScratchProject." [ | oldScriptsTarget oldTab oldViewerCategory oldPosition saveError out | self stopAll. self world ifNotNil: [self world activeHand newKeyboardFocus: nil]. "terminates active editor" "share duplicate sounds and images" self canonicalizeSoundsBits: nil saveOriginal: false. self canonicalizeImagesQuality: nil saveOriginal: false. oldScriptsTarget _ scriptsPane target. oldTab _ scriptsPane tabPane currentTab. oldViewerCategory _ viewerPane currentCategory. scriptsPane target: nil. workPane updateSpritesList. oldPosition _ workPane position. workPane delete; position: 0@0. self updatePenPositions. ScriptableScratchMorph buildBlockSpecDictionary. workPane allMorphsDo: [:m | (m isKindOf: ScriptableScratchMorph) ifTrue: [ m blocksBin allMorphsDo: [:b | (b isKindOf: BlockMorph) ifTrue: [b stop]]. m convertStacksToTuples]]. saveError _ nil. [ out _ FileStream newFileNamed: (projectDirectory unusedNameStartingWith: 'tmp'). out ifNil: [saveError _ 'Folder may be locked or read-only'] ifNotNil: [ out binary. out nextPutAll: 'ScratchV02' asByteArray. self storeProjectInfoOn: out. ObjStream new storeObj: workPane on: out. out close]. ] ifError: [:err :rcvr | out ifNotNil: [ [ out close. projectDirectory deleteFileNamed: out localName. ] ifError: []]. "clean up, ignoring any errors" saveError _ err]. workPane allMorphsDo: [:m | (m isKindOf: ScriptableScratchMorph) ifTrue: [ m convertTuplesToStacks]]. self addMorph: (workPane position: oldPosition). oldScriptsTarget ifNil: [oldScriptsTarget _ workPane]. oldScriptsTarget viewBlocksAndScripts. scriptsPane tabPane currentTab: oldTab. viewerPane currentCategory: oldViewerCategory. self updatePenPositions. ] showIndicator. saveError ifNil: [ justSaved _ true. self updateProjectName. projectDirectory deleteFileNamed: projectName. [projectDirectory rename: out localName toBe: projectName] ifError: [^ self inform: 'Save failed' withDetails: 'Is the folder read-only?' localized]. projectDirectory setMacFileNamed: projectName type: 'STsb' creator: 'MITS'] ifNotNil: [ | errorProjectName | errorProjectName := projectName. projectName _ ''. self inform: 'Save failed' withDetails: errorProjectName].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-enable/disable' stamp: 'mu 7/9/2014 22:25'!disableInteractions menuPanel allMorphsSatisfying: [:each | (each isKindOf: ToggleButton) or: [each isKindOf: ScratchMenuTitleMorph]] do: [:each | each lock]. toolbarPanel allToggleButtonsDo: [:each | each lock]. viewModeButtonsPanel allToggleButtonsDo: [:each | each lock].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-enable/disable' stamp: 'mu 7/9/2014 22:25'!enableInteractions menuPanel allMorphsSatisfying: [:each | (each isKindOf: ToggleButton) or: [each isKindOf: ScratchMenuTitleMorph]] do: [:each | each isLocked: false]. toolbarPanel allToggleButtonsDo: [:each | each isLocked: false]. viewModeButtonsPanel allToggleButtonsDo: [:each | each isLocked: false].! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-menu-actions-override' stamp: 'MU 11/11/2022 23:58'!enableRemoteSensors "Start running the Scratch server, allowing Scratch and other applications to interact with this Scratch remotely." | scratchServer | (scratchServer := workPane scratchServer) ifNil: [ scratchServer := ScratchServer new userName: 'Scratch'. scratchServer stage: workPane. workPane scratchServer: scratchServer]. scratchServer isHosting ifTrue: [^self]. IPhoneScratchProxy isActive ifTrue: [ SoiNotificationCenter postNofification: 'MeshEnabledProjectLoaded'. ]. scratchServer startHosting. DialogBoxMorph inform: 'Remote sensor connections enabled' localized.! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 10/28/2022 18:18'!exitMesh self isMeshRunning ifFalse: [^self]. self exitScratchSession. SoiMeshStats clearAllConnectionResults! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 11/4/2022 15:35'!isMeshHosting ^ (workPane scratchServer notNil and: [workPane scratchServer isHosting])! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 11/4/2022 16:49'!isMeshHostingBroken ^ (workPane scratchServer notNil and: [workPane scratchServer isHostingBroken])! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 10/28/2022 18:17'!isMeshJoined: ipAddressString ipAddressString size = 0 ifTrue: [^ false]. self isMeshRunning ifFalse: [^ false]. ^ SoiMeshStats connectionResultAt: ipAddressString! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 10/28/2022 17:46'!isMeshRunning ^ (workPane scratchServer notNil and: [workPane scratchServer sessionInProgress])! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 10/28/2022 18:17'!joinMesh: ipAddressString | server ok | server := ScratchServer new. server stage: workPane. workPane scratchServer: server. ipAddressString size = 0 ifTrue: [^ false]. ok := workPane scratchServer joinSessionAt: ipAddressString. SoiMeshStats connectionResultAt: ipAddressString put: ok. ^ ok! !!ScratchFrameMorph methodsFor: '*ScratchOnIPad-actions-mesh' stamp: 'MU 10/28/2022 17:46'!startMesh | server | self isMeshRunning ifTrue: [^self]. workPane scratchServer ifNil: [ server := ScratchServer new. server stage: workPane. workPane scratchServer: server]. workPane scratchServer startHosting! !!ScratchFrameMorph class methodsFor: '*ScratchOnIPad-skin' stamp: 'mu 7/4/2014 02:19'!fixLogo "ScratchFrameMorph fixLogo" ScratchFrameMorph mergeReadSkinMatches: 'scratchLogo*' from: (FileDirectory default directoryNamed: 'ScratchSkin'). self allInstances do: [:each | each reloadLogo; fixLayout]! !!ScratchFrameMorph class methodsFor: '*ScratchOnIPad-skin' stamp: 'mu 5/29/2015 16:13'!fixSkins ScratchSkin at: #languageButtonOver put: (ScratchSkin at: #languageButton). ScratchSkin at: #saveButtonOver put: (ScratchSkin at: #saveButton). ScratchSkin at: #mailButtonOver put: (ScratchSkin at: #mailButton). ScratchSkin at: #airDropButtonOver put: (ScratchSkin at: #airDropButton). ScratchSkin at: #meshButtonOver put: (ScratchSkin at: #meshButton). ScratchSkin at: #copyButtonOver put: (ScratchSkin at: #copyButtonPressed). ScratchSkin at: #deleteButtonOver put: (ScratchSkin at: #deleteButtonPressed). ScratchSkin at: #zoomOutButtonOver put: (ScratchSkin at: #zoomOutButtonPressed). ScratchSkin at: #zoomInButtonOver put: (ScratchSkin at: #zoomInButtonPressed). ScratchSkin at: #quarterViewModeOn put: (ScratchSkin at: #quarterViewModeOver). ScratchSkin at: #normalViewModeOn put: (ScratchSkin at: #normalViewModeOver). ScratchSkin at: #presentationViewModeOn put: (ScratchSkin at: #presentationViewModeOver). ScratchSkin at: #spriteResize put: (ScratchSkin at: #spriteResizeOver). ScratchSkin at: #spriteRotate put: (ScratchSkin at: #spriteRotateOver). ScratchSkin at: #rotStyleSmoothOver put: (ScratchSkin at: #rotStyleSmoothOn). ScratchSkin at: #rotStyleFlipOver put: (ScratchSkin at: #rotStyleFlipOn). ScratchSkin at: #rotStyleNoneOver put: (ScratchSkin at: #rotStyleNoneOn). ^ScratchSkin! !!ScratchFrameMorph class methodsFor: '*ScratchOnIPad-skin' stamp: 'mu 6/13/2014 15:26'!mergeReadSkinFrom: aDirectory " self mergeReadSkinFrom: (FileDirectory default directoryNamed: 'ScratchSkin'). self fixSkins " | dict img i | dict _ Dictionary new. aDirectory fileNames do: [:fn | Cursor read showWhile: [ img _ [Form fromFileNamed: (aDirectory fullNameFor: fn)] ifError: [nil]]. img ifNotNil: [ i _ fn findLast: [:c | c = $.]. i = 0 ifFalse: [fn _ fn copyFrom: 1 to: i - 1]. dict at: fn asSymbol put: img]]. dict keysAndValuesDo: [:k :v | ScratchSkin at: k put: v]. ^ScratchSkin! !!ScratchFrameMorph class methodsFor: '*ScratchOnIPad-skin' stamp: 'MU 4/27/2021 23:12'!mergeReadSkinMatches: nameMatcher from: aDirectory " ScratchFrameMorph mergeReadSkinMatches: 'uploadToMicrobit*' from: (FileDirectory default directoryNamed: 'ScratchSkin'). ScratchFrameMorph mergeReadSkinMatches: 'deleteCircle*' from: (FileDirectory default directoryNamed: 'ScratchSkin'). ScratchFrameMorph mergeReadSkinMatches: 'sprite*' from: (FileDirectory default directoryNamed: 'ScratchSkin'). ScratchFrameMorph mergeReadSkinMatches: 'watcher*' from: (FileDirectory default directoryNamed: 'ScratchSkin'). ScratchFrameMorph fixSkins " | dict img i | dict _ Dictionary new. (aDirectory fileNames select: [:each | nameMatcher match: each]) do: [:fn | Cursor read showWhile: [ img _ [Form fromFileNamed: (aDirectory fullNameFor: fn)] ifError: [nil]]. img ifNotNil: [ i _ fn findLast: [:c | c = $.]. i = 0 ifFalse: [fn _ fn copyFrom: 1 to: i - 1]. dict at: fn asSymbol put: img]]. dict keysAndValuesDo: [:k :v | ScratchSkin at: k put: v]. ^ScratchSkin! !!ScratchLibraryMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/10/2014 20:05'!makeNewSpriteButtons: aScratchFrameMorph "Return a morph containing a set of new sprite buttons." | panel buttonSpecs buttons button butonExtent x buttonPadding | panel _ Morph new color: Color transparent. buttonSpecs _ #( " icon name selector tooltip" (newSpritePaint paintSpriteMorph 'Paint new sprite') (newSpriteLibrary addSpriteMorph 'Choose new sprite from file') (newSpriteSurprise surpriseSpriteMorph 'Get surprise sprite') ). buttons _ buttonSpecs collect: [:spec | button _ ToggleButton new onForm: (ScratchFrameMorph skinAt: ((spec at: 1), 'Pressed')) offForm: (ScratchFrameMorph skinAt: (spec at: 1)). button target: aScratchFrameMorph; actionSelector: (spec at: 2); isMomentary: true; setProperty: #balloonText toValue: (spec at: 3) localized. IPhoneScratchProxy isActive ifTrue:[button actWhen: #buttonDown]. button]. butonExtent _ ScratchFrameMorph isXO ifTrue: [37@27] ifFalse: [37@27]. buttonPadding := IPhoneScratchProxy isActive ifTrue: [10] ifFalse: [5]. x _ 0. buttons do: [:b | b extent: butonExtent. panel addMorph: (b position: x@1). x _ x + buttonPadding + b width]. panel extent: x@(butonExtent y + 1). ^ panel! !!ScratchListMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/15/2017 23:36'!exportList | fName f | fName _ titleMorph contents. fName size <= 1 ifTrue: [fName _ 'newList']. fName _ ScratchFileChooserDialog chooseNewFileDefault: fName title: 'File Name?' type: #list. fName = #cancelled ifTrue: [^ self]. fName size > 0 ifFalse: [^ self]. (fName asLowercase endsWith: '.txt') ifFalse: [fName _ fName, '.txt']. f _ StandardFileStream newScratchFileNamed: fName. f ifNil: [^ self]. cellMorphs do: [:m | f nextPutAll: m firstSubmorph contents; crlf]. f close. IPhoneScratchProxy exportToCloudIfNeeded: fName! !!ScratchMedia methodsFor: '*ScratchOnIPad-naming' stamp: 'mu 7/4/2014 00:01'!mediaNameLocalized self mediaName: self mediaName localized! !!ImageMedia methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/16/2017 16:53'!exportFilename: fileName for: stageOrSprite "Export my image to a file with the given name. Save sprite costumes as GIF's, dropping color resolution if necessary." | myForm f fName | myForm _ self compositeForm. "save as GIF if image has under 256 colors" ((myForm depth <= 8) or: [myForm couldBeColorReduced]) ifTrue: [ f _ myForm colorReduced8Bit. (fileName asLowercase endsWith: '.gif') ifTrue: [fName _ fileName] ifFalse: [fName _ fileName, '.gif']. GIFReadWriter putForm: f onFileNamed: fName. IPhoneScratchProxy exportToCloudIfNeeded: fName. ^ self]. "otherwise, save as BMP to retain color resolution" (fileName asLowercase endsWith: '.bmp') ifTrue: [fName _ fileName] ifFalse: [fName _ fileName, '.bmp']. (stageOrSprite isKindOf: ScratchSpriteMorph) ifTrue: [ f _ Form extent: myForm extent depth: 32. f fillColor: Color white. "BMP cannot handle transparency; use white as BG color" myForm displayOn: f at: form offset negated rule: Form paint] ifFalse: [ f _ myForm asFormOfDepth: 32]. f writeBMPFileNamed: fName. IPhoneScratchProxy exportToCloudIfNeeded: fName.! !!ScratchNotePlayer methodsFor: '*ScratchOnIPad-playing' stamp: 'mu 1/16/2018 00:36'!noteOff: aNumber "Turn of the currently sounding note, if any." aNumber ifNotNil: [ | key | key _ aNumber rounded abs within: 0 and: 127. SoiMIDISynth noteOff: key velocity: 127 channel: channel - 1. ]. snd ifNotNil: [ snd stopGracefully. snd _ nil].! !!ScratchNotesDialog methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/29/2014 11:50'!useMorphTitle ^true! !!ScratchPrompterMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/27/2014 23:56'!accept "Accept button was pressed." LastAnswer _ typeinMorph contents. done _ true. self delete. sprite ifNotNil: [sprite sayNothing]. World doOneCycle. "erase myself from the screen" IPhonePresentationSpaceKeyState initMaxUnclaimedKeystrokeSize! !!ScratchPrompterMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/6/2014 23:29'!initialize "Set the forms for all my UI elements, create a row to hold my buttons, and a column to hold my shortcut buttons." super initialize. self initFromForm: (ScratchFrameMorph skinAt: #promptBubbleFrame). done _ false. typeinMorph _ StringFieldMorph new client: self; borderWidth: 2; color: (Color gray: 55); font: (ScratchFrameMorph getFont: #StringDialogTypeIn). okButton _ ToggleButton onForm: (ScratchFrameMorph skinAt: #promptCheckButtonPressed) offForm: (ScratchFrameMorph skinAt: #promptCheckButton). okButton target: self; actionSelector: #accept; actWhen: #buttonDown; toggleMode: false; setBalloonText: 'Close and continue' localized. ScratchTranslator isRTL ifTrue: [self addMorph: okButton. self addMorph: typeinMorph] ifFalse: [self addMorph: typeinMorph. self addMorph: okButton]. self extent: 450@47.! !!ScratchScriptEditorMorph methodsFor: 'stepping' stamp: 'mu 8/6/2017 14:11'!updateCostumeSelection "Update the currently selected costume if the costumes tab is selected." | currentCostume target | currentCategory = 'Costumes' ifFalse: [^ self]. target := self target ifNil: [^self]. currentCostume _ target costume. pageViewerMorph contents submorphsDo: [:m | ((m isKindOf: MediaItemMorph) and: [m media isImage]) ifTrue: [ m highlight: (m media = currentCostume)]].! !!ScratchScriptEditorMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/8/2017 16:04'!saveScriptsToImage "Take a snapshot of all scripts for a sprite and save as a GIF file" | fName saveForm | saveForm _ pageViewerMorph contents screenshot. saveForm ifNil: [^DialogBoxMorph inform: 'No scripts.' localized]. fName _ ScratchFileChooserDialog chooseNewFileDefault: '' title: 'Save Scripts Snapshot' type: #scriptsSnapshot. fName = #cancelled ifTrue: [^ self]. fName size = 0 ifTrue: [^ self]. (fName asLowercase endsWith: '.gif') ifFalse: [fName _ fName, '.gif']. saveForm writeGIFFileNamed: fName. IPhoneScratchProxy exportToCloudIfNeeded: fName! !!ScratchScriptEditorMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 9/11/2015 11:57'!step | tar | currentCategory = 'Costumes' ifTrue: [self updateCostumeSelection]. (penReadout isNil or: [penReadout owner ~= self]) ifTrue: [^ self]. tar := self target. tar ifNil: [^self]. tar penDown ifTrue: [penReadout color: self target penColor] ifFalse: [penReadout color: Color transparent].! !!ScratchScriptsMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/2/2014 21:04'!screenshot "answer a Form of myself apt for exporting" | saveForm leftX topY rightX bottomY | self submorphs isEmpty ifTrue: [^nil]. screenshooting _ true. self changed. saveForm _ self imageForm. "clip" leftX _ submorphs anyOne left. topY _ submorphs anyOne top. rightX _ submorphs anyOne right. bottomY _ submorphs anyOne bottom. (self allMorphs select: [:m | m ~= self]) do: [:m | leftX _ leftX min: m left. topY _ topY min: m top. rightX _ rightX max: m right. bottomY _ bottomY max: m bottom]. saveForm _ saveForm copy: (((leftX @ topY) - self position) rect: ((rightX @ bottomY) - self position)). screenshooting _ false. self changed. ^ saveForm! !!ScratchScriptsMorph methodsFor: '*ScratchOnIPad-events' stamp: 'mu 4/28/2018 14:28'!mouseMove: evt self scrollFrameDo: [:scrollFrame | scrollFrame mouseMove: evt]! !!ScratchScriptsMorph methodsFor: '*ScratchOnIPad-events' stamp: 'mu 4/28/2018 14:28'!mouseUp: evt self scrollFrameDo: [:scrollFrame | scrollFrame mouseUp: evt]! !!ScratchServer methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/17/2017 00:34'!doBroadcast: cmd from: requestSocket "Handle a broadcast command: broadcast <event-name>" | evtName | cmd size = 2 ifFalse: [^ self]. ((evtName _ cmd at: 2) isKindOf: String) ifFalse: [^ self]. evtName _ (UTF8 withAll: evtName). incomingBroadcasts add: evtName. broadcastCache add: evtName.! !!ScratchServer methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/17/2017 00:09'!doSensorUpdate: cmd from: requestSocket "Handle a sensor update command: sensor-update [<sensor-name> <sensor-value>]" | i sName sValue | i _ 2. [i < cmd size] whileTrue: [ sName _ cmd at: i. sValue _ cmd at: i + 1. (sName isKindOf: String) ifTrue: [sensors at: (UTF8 withAll: sName) put: sValue]. i _ i + 2].! !!ScratchServer methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/29/2015 14:44'!joinSessionAt: ipAddressString "Add an outgoing connection to the given address. Fail if a connection cannot be made in bounded amount of time. Answer true if the connection was added successfully." | addr sock ok | addr _ NetNameResolver addressForName: ipAddressString timeout: 5. addr ifNil: [^false]. sock _ MessageSocket new. ok _ sock connectTo: addr port: ScratchServer portNumber waitSecs: 5. ok ifFalse: [sock destroy. ^ false]. sock sendMessage: 'peer-name ', userName. peerSockets add: sock. ^ true! !!ScratchServer methodsFor: '*ScratchOnIPad-testing' stamp: 'MU 11/4/2022 16:47'!isHostingBroken ^ self isHosting and: [serverSocket isUnconnectedOrInvalid]! !!ScratchSoundRecorderDialogMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/2/2014 21:28'!updateTime | dur | dur := duration rounded. timerMorph contents: (self convertToMmss: dur). (currentMode == #record and: [dur > self maxRecodingSeconds]) ifTrue: [ self stop. DialogBoxMorph inform: 'Exceeded recording time limit'. ]! !!ScratchTabPaneMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/4/2014 01:10'!createTab: tabID withLabel: aString onForm: aForm1 offForm: aForm2 | button | button _ ResizableToggleButton2 new target: self; actionSelector: #currentTab:; toggleMode: false; toggleButtonMode: true; arguments: (Array with: tabID). IPhoneScratchProxy isActive ifTrue: [button actWhen: #buttonDown]. button offForm: aForm2 onForm: aForm1. self tab: button label: aString. button position: (lastTabAdded ifNil: [-0@0] ifNotNil: [(lastTabAdded right - 16)@(self bottom - button height)]). lastTabAdded _ button. self addMorph: button. (button height > self height) ifTrue: [ self height: button height. "if we just changed the height, then we must make sure all the previous tabs are aligned to the bottom" self submorphs do: [:m | (m isKindOf: ResizableToggleButton2) ifTrue: [ m height: self height; bottom: self bottom. m label top: m label top]]].! !!ScratchToolTipMorph methodsFor: '*ScratchOnIPad-events' stamp: 'mu 9/9/2014 14:45'!handlesMouseDown: evt ^ true! !!ScratchToolTipMorph methodsFor: '*ScratchOnIPad-events' stamp: 'mu 9/9/2014 14:46'!mouseDown: evt self delete! !!ScratchToolTipMorph methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 9/1/2014 12:24'!isToolTipMorph ^true! !!ScratchToolTipMorph class methodsFor: '*ScratchOnIPad-utilities-override' stamp: 'mu 9/1/2014 12:28'!clearToolTips "Delete all tooltip morphs from the world." self toolTips do: [:each | each delete]! !!ScratchToolTipMorph class methodsFor: '*ScratchOnIPad-utilities-override' stamp: 'mu 9/1/2014 12:28'!toolTips "Delete all tooltip morphs from the world." World ifNil: [^ #()]. ^World submorphs select: [:m | m isToolTipMorph].! !!ScratchTranslator class methodsFor: '*ScratchOnIPad-po' stamp: 'mu 6/2/2014 01:34'!setDefaultRenderFont TranslationDict isEmpty ifTrue: [^ self]. Smalltalk isiPhone ifTrue: [^self]. Smalltalk isWindows ifTrue: [ ((TranslationDict includesKey: 'Win-Font') and: [(TranslationDict at: 'Win-Font') size > 0]) ifTrue: [RenderFont _ TranslationDict at: 'Win-Font']]. Smalltalk isMacOSX ifTrue: [ ((TranslationDict includesKey: 'Mac-Font') and: [(TranslationDict at: 'Mac-Font') size > 0]) ifTrue: [RenderFont _ TranslationDict at: 'Mac-Font']]. (Smalltalk isWindows | Smalltalk isMacOSX) ifFalse: [ ((TranslationDict includesKey: 'Linux-Font') and: [(TranslationDict at: 'Linux-Font') size > 0]) ifTrue: [RenderFont _ TranslationDict at: 'Linux-Font']].! !!ScratchTranslator class methodsFor: '*ScratchOnIPad-po' stamp: 'mu 6/2/2014 15:41'!setDefaultRenderScale | s | TranslationDict isEmpty ifTrue: [^ self]. Smalltalk isiPhone ifTrue: [^RenderScale := SoiSettings default initialFontScale]. s _ TranslationDict at: 'Font-Scale' ifAbsent: ['']. s size > 0 ifTrue: [ RenderScale _ s asString asNumberNoError. RenderScale = 0 ifTrue: [RenderScale _ 1]. "non-number string" RenderScale _ RenderScale within: 0.5 and: 2.5].! !!ScratchTranslator class methodsFor: '*ScracthOnIPad-override' stamp: 'mu 9/11/2015 14:15'!guessLanguage "Try to guess a language setting based on the local." "ScratchTranslator guessLanguage" | lang country tokens longLocale shortLocale partMatch | (lang := self primLanguage) ifNil: [^ 'en']. country := self primCountry. country isEmptyOrNil ifTrue: [^ lang]. partMatch := false. lang := lang asLowercase. tokens := lang findTokens: '-'. tokens size >=2 ifTrue: [ (tokens at: 2) size = 2 ifTrue: [lang := lang upTo: $-] ifFalse: [partMatch := true] ]. country := country asLowercase. "first try lang + country, then try just lang:" longLocale := lang, '_', country. shortLocale := lang. ISODict keys do: [:code | | lowerCode | lowerCode := code asLowercase. lowerCode = longLocale ifTrue: [^ code]. partMatch ifTrue: [(lowerCode beginsWith: shortLocale) ifTrue: [^code]] ifFalse: [lowerCode = shortLocale ifTrue: [^ code].] ]. ^ 'en' "if no match, use English"! !!ScratchTranslator class methodsFor: '*ScracthOnIPad-override' stamp: 'mu 4/9/2015 17:44'!objectiveCPrimCountry | localeClass currentCountry what string | localeClass _ ObjectiveCBridge classObjectForName: 'SUYUtils'. currentCountry _ localeClass currentCountry. ^currentCountry asString! !!ScratchTranslator class methodsFor: '*ScracthOnIPad-override' stamp: 'mu 9/11/2015 13:35'!objectiveCPrimLanguage | localeClass preferredLanguages | localeClass _ ObjectiveCBridge classObjectForName: 'SUYUtils'. preferredLanguages _ localeClass currentLanguage. ^preferredLanguages asString! !!ScratchTranslator class methodsFor: '*ScracthOnIPad-override' stamp: 'mu 6/2/2014 15:15'!setLanguage: aString "Set the current language. If the language is not supported, use English (i.e. an empty translation dictionary)." | dict | "default to English" Language _ 'en'. TranslationDict _ Dictionary new. HeaderString _ ''. ScratchTranslator detectRenderPlugin. "aString = 'en' ifTrue: [^ self]." dict _ self importTranslation: aString, '.po'. dict ifNotNil: [ Language _ aString. TranslationDict _ dict. HeaderString _ dict at: '' ifAbsent: ['']. dict removeKey: '' ifAbsent: []. self setRenderingHints. RenderWithSqueak ifTrue: [self convertToMacRoman]. self isRTL ifTrue: [self fixAmbigousRTLPunctuation]. self addSensorTranslations].! !!ScratchTranslator class methodsFor: '*ScracthOnIPad-override' stamp: 'mu 6/2/2014 01:35'!setRenderingHints "Set optional rendering hints from fields in the translation file header. If a given hint is not explicitly set by the header, set it to its default value." | s | "default values:" IsRTL _ false. IsRTLMath _ false. RenderAntiAliasing _ Smalltalk isMacOSX or: [Smalltalk isiPhone]. RenderFont _ nil. RenderHintString _ nil. RenderScale _ Smalltalk isiPhone ifTrue: [1.3] ifFalse: [1]. RenderSuppressBold _ false. RenderCenterOffsetCache _ IdentityDictionary new. RenderVerticalTrimCache _ IdentityDictionary new. RenderWithSqueak _ true. TranslationDict isEmpty ifTrue: [^ self]. (TranslationDict includesKey: 'Language-Direction') ifTrue: [ IsRTLMath _ (TranslationDict at: 'Language-Direction') asString asUppercase = 'RTL-MATH'. IsRTLMath ifTrue: [IsRTL _ true] ifFalse: [IsRTL _ (TranslationDict at: 'Language-Direction') asString asUppercase = 'RTL']]. self setDefaultRenderFont. self setDefaultRenderScale. s _ TranslationDict at: 'Suppress-Bold' ifAbsent: ['']. s size > 0 ifTrue: [s asString asLowercase = 'true' ifTrue: [RenderSuppressBold _ true]]. "even though we are not actively using the hint string, keep this code in case we need it in the future:" s _ TranslationDict at: 'Layout-Hint' ifAbsent: ['']. s size > 0 ifTrue: [RenderHintString _ s]. RenderWithSqueak _ self useSqueakRendering.! !!ScratchTranslator class methodsFor: '*ScracthOnIPad-override' stamp: 'mu 5/10/2015 16:14'!translationDir "Returns the directory which contains the translation files and creates it if it doesn't exist." | dir bundleClassOop mainBundleOop resourcePathOop | IPhoneScratchProxy isActive ifFalse: [^(FileDirectory default directoryNamed: 'Resources') directoryNamed: 'locale']. bundleClassOop := ObjectiveCObject findClassName: 'NSBundle'. mainBundleOop := bundleClassOop mainBundle. resourcePathOop := mainBundleOop resourcePath. dir _ FileDirectory on: resourcePathOop asString. (dir directoryNames includes: 'locale') ifFalse: [[dir createDirectory: 'locale'] ifError: [^ dir]]. dir _ dir directoryNamed: 'locale'. ^ dir! !!ScratchTranslator class methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 5/6/2014 01:12'!renderScale: number RenderScale := number! !!ScratchViewerMorph methodsFor: '*ScratchOnIPad-initialize-override' stamp: 'mu 7/10/2014 21:12'!rebuildCategorySelectors | catList maxExtent buttons label offForm onForm overForm b pad leftColumnX rightColumnX x y | catList _ #( motion control looks sensing sound operators pen variables). "First, delete the old category buttons" submorphs do: [:m | (m isKindOf: ResizableToggleButton2) ifTrue: [m delete]]. "Create new buttons, keeping track of the maximum extent." maxExtent _ 75@0. buttons _ catList collect: [:cat | label _ (ScratchTranslator translationFor: cat asString) capitalized. offForm _ (ScratchFrameMorph skinAt: cat). onForm _ (ScratchFrameMorph skinAt: (cat, 'Pressed')). overForm _ (ScratchFrameMorph skinAt: (cat, 'Over')). ScratchTranslator isRTL ifTrue:[ b _ ResizableToggleButton2 new offForm: (offForm flipBy: #horizontal centerAt: offForm center) onForm: (onForm flipBy: #horizontal centerAt: onForm center) overForm: (overForm flipBy: #horizontal centerAt: overForm center)] ifFalse:[ b _ ResizableToggleButton2 new offForm: offForm onForm: onForm overForm: overForm]. b label: label font: (ScratchFrameMorph getFont: #Category); setLabelColor: Color white; target: self; actionSelector: #currentCategory:; arguments: (Array with: cat); toggleButtonMode: true; toggleMode: false. ScratchTranslator isRTL ifTrue:[b rightJustifyInset: 10] ifFalse:[b leftJustifyInset: 10]. maxExtent _ maxExtent max: (b extent + (3 @ -6)). IPhoneScratchProxy isActive ifTrue: [b actWhen: #buttonDown]. b]. "calculate catButtonsExtent" pad _ 15. "padding on left, right, and betwen the button columns" catButtonsExtent _ ((2 * maxExtent x) + (3 * pad)) @ (((catList size // 2) * (maxExtent y + 6)) + 25). "place the buttons" leftColumnX _ self left + 12 + pad. rightColumnX _ leftColumnX + maxExtent x + pad. x _ leftColumnX. y _ self top + 17. 1 to: buttons size do: [:i | b _ buttons at: i. b extent: maxExtent. self addMorph: (b position: x@y). i even ifTrue: [x _ leftColumnX. y _ y + b height + 6] ifFalse: [x _ rightColumnX]]. self width: catButtonsExtent x. pageViewer position: self position + (0@catButtonsExtent y). topSectionHeight _ catButtonsExtent y - 4.! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 6/6/2014 00:28'!importImageNamed: fName | fList ext isFirst el newName | fList _ OrderedCollection new. ext _ FileDirectory extensionFor: fName asLowercase. ext = 'gif' ifTrue: [[fList _ (GIFReadWriter new on: (FileStream readOnlyFileNamed: fName)) nextImageSet] ifError: [^ self]] ifFalse: [[fList addLast: (Form fromFileNamed: fName)] ifError: [^ self]]. isFirst _ true. fList do: [:f | el _ ImageMedia new form: (ScratchFrameMorph scaledFormForPaintEditor: f). newName _ self mediaNameFromFileName: fName default: 'costume'. el mediaName: (self unusedMediaNameFromBaseName: (UTF8 withAll: newName)). media addLast: el. isFirst ifTrue: [isFirst _ false. self lookLike: el mediaName.]]. self updateMediaCategory.! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/1/2014 18:52'!takePhotoOnIPad | delegate mode nsString prox | delegate := IPhoneScratchProxy delegate. mode := (self class name = 'ScratchStageMorph') ifTrue: ['stage'] ifFalse: ['normal']. nsString := mode asNSStringUTF8. delegate openCamera: nsString. nsString release. (prox := IPhoneScratchProxy current) ifNotNil: [ prox workingMorph: self. ]! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-override' stamp: 'MU 4/4/2020 23:56'!createBlock: block atPosition: pos onPage: page "Creates a block on the given page. If the block is one that can become a watcher, then a toggle button is created as well." | x y changingX toggleButton yOffset frame | x _ pos x. y _ pos y. changingX _ x. block canBecomeWatcher ifTrue: [ toggleButton _ self createToggleButtonFor: block. yOffset _ (block fullBounds height - toggleButton fullBounds height) // 2. page addMorphBack: (toggleButton position: x@(y+yOffset)). changingX _ x + toggleButton fullBounds width + 2]. block fixBlockLayout; position: changingX@y. page addMorphBack: block. block canBecomeWatcher ifTrue: [ frame _ self ownerThatIsA: ScratchFrameMorph. page updateWatcherButtonsForFrame: frame]. ^ y + block height + 3! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/19/2014 22:30'!editDrawingOldCostumeName: oldCostumeName deleteOnCancel: aBoolean "Edit my original form with the paint editor." | sFrame paintEditor | costume isMovie ifTrue: [^ self beep]. (sFrame _ self ownerThatIsA: ScratchFrameMorph) ifNotNil: [ sFrame paintingInProgress ifTrue: [^ self beep]. sFrame stopAll. sFrame paintingInProgress: true]. [paintEditor _ PaintFrame new. paintEditor withStartingObject: self; scratchFrame: sFrame; oldCostumeName: oldCostumeName deleteOnCancel: aBoolean. oldCostumeName ifNotNil: [ "When an oldCostumeName is supplied, it means I'm making a new drawing. Clear the initial rotation center." paintEditor clearRotationCenter]. ] showIndicator. (paintEditor isKindOf: DialogBoxMorph) ifTrue: [paintEditor getUserResponse] ifFalse: [ World addMorphFront: paintEditor. World startSteppingSubmorphsOf: paintEditor]! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/10/2017 17:39'!exportObject | fName dir f objToExport exportingToCloud | fName _ ScratchFileChooserDialog chooseNewFileDefault: objName title: 'Export Sprite' type: #sprite. fName = #cancelled ifTrue: [^ self]. fName size = 0 ifTrue: [^ self]. (fName endsWith: '.sprite') ifFalse: [fName _ fName, '.sprite']. exportingToCloud := SoiUtils belongsToTemporary: fName. exportingToCloud ifFalse: [ fName _ FileDirectory localNameFor: fName. "ignore path, if any; save in default directory" ]. dir _ ScratchFileChooserDialog getLastFolderForType: #sprite forSave: true. (dir fileExists: fName) ifTrue: [ (DialogBoxMorph ask: 'The file name already exists. Overwrite existing file?') ifFalse: [^ self]. dir deleteFileNamed: fName]. f _ nil. [ f _ (dir newFileNamed: fName) binary. objToExport _ self copyForExport. objToExport objName: fName. ObjStream new storeObj: objToExport on: f showProgress: true. f close. exportingToCloud ifTrue: [IPhoneScratchProxy exportToCloud: fName]. dir setMacFileNamed: fName type: 'STsb' creator: 'MITS'. ] ifError: [ f ifNotNil: [f close]. self inform: 'Could not write file' withDetails: 'Export failed' localized].! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 9/21/2018 11:15'!importMedia: fileName "Import a new image from a file and add it to my media." | extension elList baseName fList isFirst | extension _ FileDirectory extensionFor: fileName asLowercase. elList _ OrderedCollection new. (#(aif aiff wav mp3) includes: extension) ifTrue: [ | smedia | baseName _ self mediaNameFromFileName: fileName default: 'sound'. smedia := [SoundMedia new loadFile: fileName] ifError: []. smedia ifNil: [^self]. elList addLast: smedia]. (#(jpg jpeg gif bmp png) includes: extension) ifTrue: [ baseName _ self mediaNameFromFileName: fileName default: self defaultImageMedia mediaName. fList _ OrderedCollection new. extension = 'gif' ifTrue: [[fList _ (GIFReadWriter new on: (FileStream oldFileNamed: fileName)) nextImageSet] ifError: [^ self]] ifFalse: [[fList addLast: (Form fromFileNamed: fileName)] ifError: [^ self]]. fList do: [:f | elList addLast: (ImageMedia new form: (ScratchFrameMorph scaledFormForPaintEditor: f))]]. elList isEmpty ifTrue: [^ self]. "unknown file type; ignore" isFirst _ true. elList do: [:el | el mediaName: (self unusedMediaNameFromBaseName: (UTF8 withAll: baseName)). media addLast: el. isFirst ifTrue: [ isFirst _ false. el isSound ifFalse: [self lookLike: el mediaName]]]. self updateMediaCategory.! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/17/2014 21:30'!mediaNameFromFileName: fileName default: defaultName "Answer a name for the given media item. If the existing name is '$$squeak$$' then the media was copied via windows drag-and-drop; use the given default name instead." | result utf8result utf32result | result _ (FileDirectory baseNameFor: (FileDirectory localNameFor: fileName)). (result beginsWith: '$$squeak$$') ifTrue: [result _ defaultName]. result isAsciiString ifTrue: [result size > 16 ifTrue: [result _ result copyFrom: 1 to: 16]. ^result]. utf8result := UTF8 withAll: result. utf32result := utf8result asUTF32. (utf32result size > 8) ifTrue: [utf32result := utf32result copyFrom: 1 to: 8. ^utf32result asUTF8]. ^utf8result! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-override' stamp: 'MU 4/20/2021 21:44'!primSetVar: varName to: newValue "Set the value of the given variable of this object to the given value." | vName stage | vName _ varName asString. "convert Symbol to String if needed" (vars includesKey: vName) ifFalse: [ stage _ self ownerThatIsA: ScratchStageMorph. (stage notNil and: [stage ~= self]) ifTrue: [ stage setVar: varName to: newValue]. ^ false]. vars at: vName put: newValue. ^true! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-override' stamp: 'MU 4/20/2021 21:45'!setVar: varName to: newValue "Set the value of the given variable of this object to the given value." (self primSetVar: varName to: newValue) ifFalse: [^self]. self microbitSensorIfMatch: varName to: newValue! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/10/2014 23:50'!takePhoto "Take a photo." IPhoneScratchProxy isActive ifTrue: [^self takePhotoOnIPad]. ScratchCameraDialog new client: self; openInWorld; openCamera.! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-sensors-override' stamp: 'MU 5/8/2021 10:40'!hookupSensorNames | sensorNames stage virtualSensors | sensorNames := OrderedCollection new. (IPhoneScratchProxy isActive and: [IPhoneScratchProxy sensorAccessorIsRunning]) ifTrue: [ sensorNames _ sensorNames, #('accX' 'accY' 'accZ' 'gyroX' 'gyroY' 'gyroZ' 'yaw' 'pitch' 'roll' 'northHeading' 'brightness'). ]. (IPhoneScratchProxy isActive and: [IPhoneScratchProxy microbitAccessorIsRunning]) ifTrue: [ sensorNames _ sensorNames, #('mb:accX' 'mb:accY' 'mb:accZ' 'mb:magX' 'mb:magY' 'mb:magZ' 'mb:northHeading' 'mb:temperature' 'mb:buttonA' 'mb:buttonB' 'mb:uart' 'mb:pin0' 'mb:pin1' 'mb:pin2'). Sensor shiftPressed ifTrue: [sensorNames _ sensorNames, #('mb:pin3' 'mb:pin4' 'mb:pin5' 'mb:pin6' 'mb:pin7' 'mb:pin8' 'mb:pin9' 'mb:pin10' 'mb:pin11' 'mb:pin12' 'mb:pin13' 'mb:pin14' 'mb:pin15' 'mb:pin16' 'mb:pin17' 'mb:pin18' 'mb:pin19' 'mb:pin20')] ]. (stage := self ownerThatIsA: ScratchStageMorph) ifNotNil: [ stage scratchServer ifNotNil: [ virtualSensors _ stage scratchServer sensorNames. virtualSensors size > 0 ifTrue: [ sensorNames := sensorNames, {'-'}, stage scratchServer sensorNames]]]. sensorNames size > 0 ifTrue: [sensorNames add: '-']. sensorNames := sensorNames, #( 'slider' 'light' 'sound' 'resistance' ). sensorNames := sensorNames, #('-' 'tilt' 'distance'). "WeDo sensors" ^ sensorNames. ! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-sensors-override' stamp: 'MU 4/20/2021 22:51'!sensor: sensorName "Answer the value of the given sensor, or zero if the sensorboard is not available." | stage v sb | (IPhoneScratchProxy isActive and: [IPhoneScratchProxy sensorAccessorIsRunning]) ifTrue: [ self localSensorValueAt: sensorName ifPresent: [:val | ^ val]. ]. (IPhoneScratchProxy isActive and: [IPhoneScratchProxy microbitAccessorIsRunning]) ifTrue: [ self microbitSensorValueAt: sensorName ifPresent: [:val | ^ self microbitSensorProcessedValueAt: sensorName from: val]. ]. (stage _ self ownerThatIsA: ScratchStageMorph) ifNil: [^ 0]. stage scratchServer ifNotNil: [ v _ stage scratchServer sensorValueFor: sensorName. v ifNotNil: [^ v]]. 'tilt' = sensorName ifTrue: [^ WeDoPlugin tilt]. 'distance' = sensorName ifTrue: [^ WeDoPlugin distance]. sb _ stage sensorBoard. sb tryToOpenPort ifFalse: [^ 0]. "could not open" ^ sb sensor: (self indexForSensorName: sensorName)! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-sensors' stamp: 'mu 6/8/2015 22:29'!localSensorValueAt: sensorName ifPresent: oneArgBlock ^IPhoneScratchProxy localSensorValueAt: sensorName ifPresent: oneArgBlock! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/7/2021 21:02'!microbitEventSend: newValue at: eventLabel by: microbitAccessor | newIntValue typeValue rawTypeValue | newIntValue := [newValue asNumber] ifError: [^self]. rawTypeValue := vars at: ('mb:event', eventLabel, 'type') ifAbsent: [vars at: ('mb:event', eventLabel, 'Type') ifAbsent: []]. typeValue := [rawTypeValue asNumber] ifError: [^self]. microbitAccessor triggerEventWithType: (typeValue min: 65535 max: 0) value: (newIntValue min: 65535 max: 0)! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/2/2021 17:09'!microbitLedMessage: newValue by: microbitAccessor | scrollRate msg | scrollRate := vars at: 'mb:scrollRate' ifAbsent: [vars at: 'mb:scrollrate' ifAbsent: ['400']]. msg := newValue asString asNSStringUTF8. microbitAccessor ledTextWithMessage: msg scrollRate: ([scrollRate asNumber min: 32768 max: 0] ifError: [400]). msg release ! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/6/2021 22:11'!microbitPin: pinLabel to: newValue by: microbitAccessor | pinIndex newIntValue | pinIndex := [pinLabel asNumber] ifError: [^self]. newIntValue := [newValue asNumber] ifError: [^self]. microbitAccessor pinToValue: (newIntValue min: 1023 max: 0) at: (pinIndex min: 20 max: 0)! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/6/2021 14:59'!microbitPin: pinLabel toAnalog: newValue by: microbitAccessor | pinIndex newIntValue | pinIndex := [(pinLabel copyReplaceAll: 'analog' with: '') asNumber] ifError: [^self]. newIntValue := [newValue asNumber] ifError: [^self]. microbitAccessor pinToAnalog: (newIntValue min: 255 max: 0) at: (pinIndex min: 20 max: 0)! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/6/2021 15:17'!microbitPin: pinLabel toAnalogPeriod: newValue by: microbitAccessor | trimmedLabel pinIndex pinVarName pinRawValue newIntValue | trimmedLabel := pinLabel copyReplaceAll: 'period' with: ''. pinIndex := [trimmedLabel asNumber] ifError: [^self]. pinVarName := 'mb:pin', trimmedLabel. pinRawValue := [(vars at: pinVarName ifAbsent: ['0']) asNumber] ifError: [^self]. newIntValue := [newValue asNumber] ifError: [^self]. microbitAccessor pinToAnalogPeriod: (newIntValue min: 4294967295 max: 0) value: (pinRawValue min: 1023 max: 0) at: (pinIndex min: 20 max: 0)! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/6/2021 14:58'!microbitPin: pinLabel toRead: newValue by: microbitAccessor | pinIndex newIntValue | pinIndex := [(pinLabel copyReplaceAll: 'read' with: '') asNumber] ifError: [^self]. newIntValue := [newValue asNumber] ifError: [^self]. microbitAccessor pinToRead: (newIntValue min: 255 max: 0) at: (pinIndex min: 20 max: 0)! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/6/2021 15:08'!microbitPinSend: newValue label: pinLabel by: microbitAccessor (pinLabel size between: 1 and: 2) ifTrue: [ ^ self microbitPin: pinLabel to: newValue by: microbitAccessor]. (pinLabel endsWith: 'read') ifTrue: [ ^ self microbitPin: pinLabel toRead: newValue by: microbitAccessor]. (pinLabel endsWith: 'analog') ifTrue: [ ^ self microbitPin: pinLabel toAnalog: newValue by: microbitAccessor]. (pinLabel endsWith: 'period') ifTrue: [ ^ self microbitPin: pinLabel toAnalogPeriod: newValue by: microbitAccessor].! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/7/2021 21:02'!microbitSensorIfMatch: rawVarName to: newValue | varName microbitAccessor varLabel | (IPhoneScratchProxy isActive and: [IPhoneScratchProxy microbitAccessorIsRunning]) ifFalse: [^self]. varName := rawVarName asLowercase. (varName beginsWith: 'mb:') ifFalse: [^self]. varLabel := varName copyTailIfBegins: 'mb:'. microbitAccessor := IPhoneScratchProxy microbitAccessor. (varLabel = 'uart') ifTrue: [^ self microbitUartSend: newValue by: microbitAccessor]. (varLabel = 'ledtext') ifTrue: [^ self microbitLedMessage: newValue by: microbitAccessor]. (varLabel beginsWith: 'pin') ifTrue: [ | pinLabel | pinLabel := varLabel copyTailIfBegins: 'pin'. ^ self microbitPinSend: newValue label: pinLabel by: microbitAccessor ]. (varLabel beginsWith: 'event') ifTrue: [ | eventLabel | eventLabel := varLabel copyTailIfBegins: 'event'. ^ self microbitEventSend: newValue at: eventLabel by: microbitAccessor ] ! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 4/20/2021 22:58'!microbitSensorProcessedValueAt: sensorName from: rawValue | value | value := rawValue. sensorName = 'mb:uart' ifTrue: [ | tokens | value := value withoutTrailingBlanks. tokens := value findTokens: ':'. tokens size = 2 ifTrue: [self microbitUartSetVar: tokens first to: tokens last]. ]. ^value! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 4/20/2021 22:58'!microbitSensorValueAt: sensorName ifPresent: oneArgBlock ^ IPhoneScratchProxy microbitSensorValueAt: sensorName ifPresent: oneArgBlock! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 5/5/2021 15:25'!microbitUartSend: newValue by: microbitAccessor | separator msg | separator := vars at: 'mb:uartSeparator' ifAbsent: [vars at: 'mb:uartseparator' ifAbsent: [Character lf asString]]. msg := (newValue asString, separator asString) asNSStringUTF8. microbitAccessor uartSendWithMessage: msg. msg release! !!ScriptableScratchMorph methodsFor: '*ScratchOnIPad-microbit' stamp: 'MU 4/20/2021 22:46'!microbitUartSetVar: varName to: newValue | val | self ensureVariableExists: varName. val := [newValue asNumber] ifError: [newValue]. self primSetVar: varName to: val.! !!ScratchSpriteMorph methodsFor: '*ScratchOnIPad-look ops-override' stamp: 'mu 8/26/2014 13:41'!bubble: obj thinkFlag: thinkFlag promptFlag: promptFlag "Make a talk bubble with the given string." | s talkBubble | self sayNothing. obj isNumber ifTrue: [ obj isInteger ifTrue: [s _ obj printString] ifFalse: [s _ (obj asFloat "roundTo: 0.01") printString]] ifFalse: [(obj isKindOf: Boolean) ifTrue: [s _ obj asString localized] ifFalse: [s _ obj asString]]. (s skipDelimiters: ' ' startingAt: 1) > s size ifTrue: [^ self]. s size < 5 ifTrue: [s _ s, ' ']. talkBubble _ ScratchTalkBubbleMorph new message: s. thinkFlag ifTrue: [talkBubble beThoughtBubble: true]. promptFlag ifTrue: [talkBubble bePrompt: true]. talkBubble lock; position: self position. self setProperty: #talkBubble toValue: talkBubble. self addMorphFront: talkBubble. self positionTalkBubble. World displayWorldSafely. ^ talkBubble! !!ScratchSpriteMorph methodsFor: '*ScratchOnIPad-drawing-override' stamp: 'mu 8/28/2014 00:36'!drawOn: aCanvas "Draw myself if my visibility is > 0. If my visibility is 1, draw using the normal 'paint' mode. Otherwise, draw using 'alpha' resulting in a partially transparent rendering." | f alpha | f _ self filteredForm. f ifNil: [^self]. visibility < 100 ifTrue: [ visibility > 0 ifTrue: [ alpha _ ((255.0 * visibility) / 100.0) truncated. aCanvas paintImage: f at: bounds origin sourceRect: f boundingBox alpha: alpha]. ^ self]. aCanvas paintImage: f at: bounds origin.! !!ScratchStageMorph methodsFor: '*ScratchOnIPad-constants' stamp: 'mu 7/21/2014 14:51'!quarterModeDrawRect ^bounds origin extent: (SoiUtils quarterModeDrawExtent)! !!ScratchStageMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/21/2014 15:11'!drawQuarterSizeOn: aCanvas "Draw myself and my submorphs to an offscreen canvas, then scale down to quarter size and draw that on the given canvas." | fullR r srcR c | aCanvas fillRectangle: self quarterModeDrawRect color: SoiUtils quarterModeBackgroundColor. cachedForm ifNil: [cachedForm _ Form extent: self extent depth: 32]. fullR := bounds origin extent: bounds extent // 2. r _ aCanvas clipRect intersect: (fullR). srcR _ ((r origin - bounds origin) * 2.0) truncated extent: (r extent * 2.0) rounded. c _ (FormCanvas on: cachedForm) copyOrigin: self position negated clipRect: srcR. super fullDrawOn: c. ScratchPlugin halfSize: cachedForm into: Display srcPoint: srcR origin dstRect: r. aCanvas frameRectangle: fullR width: 1 color: Color gray."xxx cachedForm unhibernate. LowResPlugin primHalf2Average: cachedForm bits w: cachedForm width h: cachedForm height into: Display bits w: Display width h: Display height srcX: srcR left srcY: srcR top dstX: r left dstY: r top dstW: r width dstH: r height. (WarpBlt toForm: Display) sourceForm: cachedForm; combinationRule: Form over; clipRect: aCanvas clipRect; cellSize: 2; copyQuad: srcR corners toRect: r.xxx" "the following scales down entire stage:"" LowResPlugin scale: cachedForm into: aCanvas form at: aCanvas origin + self position."! !!ScratchStageMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/8/2017 16:41'!exportFileName: fileName | form fName | form _ self stageShotForm. form depth <= 8 ifTrue: [ (fileName asLowercase endsWith: '.gif') ifTrue: [fName _ fileName] ifFalse: [fName _ fileName, '.gif']. GIFReadWriter putForm: form colorReduced8Bit onFileNamed: fName. IPhoneScratchProxy exportToCloudIfNeeded: fName. ^ self]. (fileName asLowercase endsWith: '.bmp') ifTrue: [fName _ fileName] ifFalse: [fName _ fileName, '.bmp']. (form asFormOfDepth: 32) writeBMPFileNamed: fName. IPhoneScratchProxy exportToCloudIfNeeded: fName! !!ScratchStageMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 1/17/2018 00:19'!midiAllNotesOff | channels | "If the MIDI port is open, send an 'all notes off' command on every channel." "midiPort ifNil: [^ self]. midiPort ensureOpenIfFail: [self closeMIDI]." channels := Set with: 10. channels addAll: (notePlayerDict values collect: [:pl | pl channel]). channels do: [:cha | "player noteOff." SoiMIDISynth allSoundOff: cha - 1. ]. channels nslog: '###midiAllNotesOff###'. ! !!ScrollFrameMorph2 methodsFor: '*ScratchOnIPad-override-geometry' stamp: 'mu 4/27/2018 15:53'!extent: aPoint "After setting my size, position and size my scrollbars and grow box. Also update my contents and scrollbar ranges." | mobileHBarOffset inner w h | mobileHBarOffset := 6. super extent: (aPoint truncated max: self minWidth@self minHeight). scrollBarStartInset ifNil: [ scrollBarStartInset _ scrollBarEndInset _ 0]. "needed during initialization" inner _ self innerBounds. w _ inner width - scrollBarStartInset. vScrollbar owner = self ifTrue: [w _ w - vbarInset] ifFalse: [w _ w - scrollBarEndInset]. hScrollbar position: (inner left + scrollBarStartInset)@(inner bottom - hbarInset - mobileHBarOffset). hScrollbar width: w. h _ inner height - scrollBarStartInset. hScrollbar owner = self ifTrue: [h _ h - hbarInset] ifFalse: [h _ h - scrollBarEndInset]. ScratchTranslator isRTL ifTrue: [vScrollbar position: (inner left + 9)@(inner top + scrollBarStartInset)] ifFalse: [vScrollbar position: (inner right - vbarInset)@(inner top + scrollBarStartInset)]. vScrollbar height: h. self updateContentsExtent. self updateScrollbars.! !!ScrollFrameMorph2 methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 4/28/2018 15:00'!handlesMouseEvents ^handlesMouseEvents ifNil: [handlesMouseEvents := true]! !!ScrollFrameMorph2 methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 4/28/2018 15:01'!handlesMouseEvents: aBoolean handlesMouseEvents := aBoolean! !!ScrollFrameMorph2 methodsFor: '*ScratchOnIPad-events' stamp: 'mu 4/28/2018 15:01'!handlesMouseDown: evt ^self handlesMouseEvents! !!ScrollFrameMorph2 methodsFor: '*ScratchOnIPad-events' stamp: 'mu 4/27/2018 23:28'!mouseMove: evt | curPoint diff | curPoint := evt cursorPoint. prevCursorPoint ifNil: [^ prevCursorPoint := curPoint ]. diff := curPoint - prevCursorPoint. (diff = (0@0)) ifTrue: [^self]. self vScrollPixels: (self vScrollPixels - diff y). self hScrollPixels: (self hScrollPixels - diff x). prevCursorPoint := evt cursorPoint.! !!ScrollFrameMorph2 methodsFor: '*ScratchOnIPad-events' stamp: 'mu 4/27/2018 23:25'!mouseUp: evt prevCursorPoint := nil! !!ScrollingStringMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 9/19/2014 11:26'!breakLine: lineIndex "Break the given line by moving some of it down to the following line. Answer true if the line was broken, false otherwise. (This may cause the next line to become too long, thus propaging the need to word-wrap.) Try the following strategies, in order: a. break at an embedded if that leaves the line short enough b. break at the last space character before a word that hits the edge c. break a word that hits the edge if there is no space before that word" | line breakIndex i lineUpToBreak lineAfterBreak | line _ lines at: lineIndex. breakIndex _ nil. (self fits: line) ifTrue: [^ false]. "line already fits" (i _ line indexOf: CR) ~= 0 ifTrue: [ (self fits: (line copyFrom: 1 to: i - 1)) ifTrue: [breakIndex _ i]]. breakIndex ifNil: [ i _ line indexOfSeparatorStartingAt: 1. [i <= line size] whileTrue: [ (self fits: (line copyFrom: 1 to: i - 1)) ifTrue: [ breakIndex _ i. i _ line indexOfSeparatorStartingAt: i + 1] ifFalse: [i _ line size + 1]]]. breakIndex ifNil: [ i _ line size. [i > 1 and: [(self fits: (line copyFrom: 1 to: i)) not]] whileTrue: [i _ i - 1]. breakIndex _ i]. lineUpToBreak _ line copyFrom: 1 to: breakIndex. lineAfterBreak _ line copyFrom: breakIndex + 1 to: line size. lineIndex = lines size ifTrue: [lines _ lines copyWith: self emptyLine]. "make sure there is a next line" lineIndex > lines size ifTrue: [^false]. lines at: lineIndex put: lineUpToBreak. lines at: lineIndex + 1 put: lineAfterBreak, (lines at: lineIndex + 1). ^ true! !!ScrollingStringMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/22/2023 12:20'!drawCursor: charIndex line: lineIndex on: aCanvas "Draw a cursor at the given character index on the given line." | line pair x p | line _ lines at: lineIndex ifAbsent: [^self]. line size = 0 ifTrue: [pair _ #(0 0)] ifFalse: [pair _ (renderer xRangesFor: line) at: (charIndex within: 1 and: line size) ifAbsent: [#(0 0)]]. ScratchTranslator isRTL ifTrue: [x _ charIndex > line size ifTrue: [pair min] ifFalse: [pair max]] ifFalse: [x _ charIndex > line size ifTrue: [pair max] ifFalse: [pair min]]. p _ self offsetForLine: lineIndex. aCanvas fillRectangle: (p + (x@0) extent: 2@lineHeight) color: selectionColor.! !!ScrollingStringMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/22/2023 12:14'!indexForPoint: aPoint "Answer the character index for the given point in screen coordinates." "Note: This could be speeded up by doing a binary search for the character index, but it seems fast enough." | y lineNum x lineStart line xRanges pair | lines size = 0 ifTrue: [^ 1]. y _ aPoint y - (self top + self textInset y + 2). lineNum _ ((y // lineHeight) + firstVisibleLine) max: 1. lineNum > lines size ifTrue: [^ (self startOfLine: lineNum) + 1]. x _ (aPoint x - self left - (self offsetForLine: lineNum) x) min: self width. x < 0 ifTrue: [ "start of a line" lineNum = 1 ifTrue: [^ 1] ifFalse: [^ self startOfLine: lineNum]]. "search for character index" lineStart _ self startOfLine: lineNum. line _ lines at: lineNum. xRanges _ renderer xRangesFor: line. 1 to: line size do: [:i | pair _ xRanges at: i ifAbsent: [#(0 0)]. (x between: pair first and: pair second) ifTrue: [^ lineStart + i]]. "end of line" lineNum = lines size ifTrue: [^ lineStart + line size + 1] ifFalse: [^ lineStart + line size].! !!ScrollingStringMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/18/2014 23:18'!keyboardFocusChange: aBoolean hasFocus = aBoolean ifFalse: [ self changed]. hasFocus := aBoolean. IPhoneScratchProxy isActive ifTrue: [self ipadTextFieldFocused: aBoolean]! !!SequenceableCollection methodsFor: '*ScratchOnIPad-enumeration' stamp: 'mu 6/13/2014 15:53'!do: elementBlock separatedBy: separatorBlock 1 to: self size do: [:index | index = 1 ifFalse: [separatorBlock value]. elementBlock value: (self at: index)]! !!SequenceableCollection methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 5/21/2014 01:20'!lastOrNil self isEmpty ifTrue: [^nil]. ^ self last! !!SimpleButtonMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 9/11/2015 11:52'!showBalloon: msg | w worldBounds tooltip | w _ self world. w ifNil: [^self]. tooltip _ ScratchToolTipMorph string: msg for: self. w addMorphFront: tooltip "(w activeHand position + tooltip offset)". self drawToolTipAbove ifTrue: [tooltip position: self topLeft - (0@tooltip height)] ifFalse: [tooltip position: self bottomLeft + (0@8)]. worldBounds _ w bounds. (worldBounds containsRect: tooltip bounds) ifFalse: [ tooltip bounds: (tooltip bounds translatedToBeWithin: worldBounds). (tooltip bounds intersects: w activeHand bounds) ifTrue: [tooltip left: w activeHand bounds right]. (worldBounds containsRect: tooltip bounds) ifFalse: [ tooltip bounds: (tooltip bounds translatedToBeWithin: worldBounds). (tooltip bounds intersects: w activeHand bounds) ifTrue: [tooltip right: w activeHand bounds left - 8]]].! !!ResizableToggleButton2 methodsFor: '*ScratchOnIPad-events-override' stamp: 'mu 7/4/2014 01:21'!mouseDown: evt evt hand toolType: nil. wasOn _ isOn. evt hand newKeyboardFocus: nil. evt rightButtonPressed ifTrue: [ Sensor waitNoButton. ^ self rightButtonMenu]. toggleButtonMode ifTrue: [ toggleMode ifTrue: [ isOn ifTrue: [isOn _ false. self over] ifFalse: [self on]] ifFalse: [ isOn ifTrue: [^ self] ifFalse: [self on]]] ifFalse: [self on]. actWhen = #buttonDown ifTrue: [ self doButtonAction. toggleButtonMode ifFalse: [ self off ]].! !!ResizableToggleButton2 methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 4/10/2017 11:54'!setFlatIcon: aForm self icon: aForm. self extent: (iconMorph extent + 10).! !!SliderRangeDialog methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/29/2014 12:21'!useMorphTitle ^true! !!SoiActivityIndicator class methodsFor: 'actions' stamp: 'mu 7/1/2014 18:51'!showWhile: aBlock | delegate | IPhoneScratchProxy isActive ifFalse: [^aBlock value]. delegate := IPhoneScratchProxy delegate. [delegate showWaitIndicator. aBlock value] ensure: [delegate hideWaitIndicator].! !!SoiJobQueue methodsFor: 'initialization' stamp: 'mu 7/2/2014 15:10'!initialize sharedQueue := SharedQueue new. self prepareWatcherProcess! !!SoiJobQueue methodsFor: 'accessing' stamp: 'mu 7/2/2014 15:07'!isRunning ^watcherProcess ~~ nil ! !!SoiJobQueue methodsFor: 'accessing' stamp: 'mu 7/2/2014 15:00'!priority ^ priority ifNil: [priority := Processor userSchedulingPriority]! !!SoiJobQueue methodsFor: 'accessing' stamp: 'mu 7/2/2014 15:11'!priority: anInteger priority = anInteger ifFalse: [self stopWatcherProcess]. priority := anInteger! !!SoiJobQueue methodsFor: 'accessing' stamp: 'mu 7/2/2014 15:01'!watcherProcess ^watcherProcess ifNil: [self prepareWatcherProcess]! !!SoiJobQueue methodsFor: 'private' stamp: 'mu 7/2/2014 15:04'!perform sharedQueue next value! !!SoiJobQueue methodsFor: 'private' stamp: 'mu 7/2/2014 15:03'!prepareWatcherProcess self stopWatcherProcess. watcherProcess := [ [watcherProcess notNil] whileTrue: [ self perform. ] ] newProcess. watcherProcess priority: self priority. watcherProcess resume! !!SoiJobQueue methodsFor: 'private' stamp: 'mu 7/2/2014 15:26'!stopWatcherProcess watcherProcess == nil ifFalse: [watcherProcess terminate]. watcherProcess := nil! !!SoiJobQueue methodsFor: 'actions' stamp: 'mu 7/2/2014 15:10'!defer: aBlock sharedQueue nextPut: aBlock! !!SoiJobQueue methodsFor: 'actions' stamp: 'mu 7/2/2014 15:27'!start self prepareWatcherProcess! !!SoiJobQueue methodsFor: 'actions' stamp: 'mu 7/2/2014 15:26'!stop self stopWatcherProcess! !!SoiJobQueue class methodsFor: 'instance creation' stamp: 'mu 7/2/2014 15:34'!priority: anInteger | inst | inst := self basicNew. inst priority: anInteger. inst initialize. ^inst! !!SoiMIDISynth class methodsFor: 'actions' stamp: 'mu 9/21/2018 14:38'!allSoundOff: channel IPhoneScratchProxy isActive ifFalse: [^self]. IPhoneScratchProxy isFirstLaunch ifTrue: [^self]. ObjectiveCBridge performSelectorOnMainThread: [ self delegate allSoundOff: channel asInteger ]! !!SoiMIDISynth class methodsFor: 'actions' stamp: 'mu 5/12/2017 10:37'!noteOff: note velocity: velocity channel: channel IPhoneScratchProxy isActive ifFalse: [^self]. ObjectiveCBridge performSelectorOnMainThread: [ self delegate noteOff: note asInteger velocity: velocity asInteger channel: channel asInteger ]! !!SoiMIDISynth class methodsFor: 'actions' stamp: 'mu 5/12/2017 10:38'!noteOn: note velocity: velocity channel: channel IPhoneScratchProxy isActive ifFalse: [^self]. ObjectiveCBridge performSelectorOnMainThread: [ self delegate noteOn: note asInteger velocity: velocity asInteger channel: channel asInteger ]! !!SoiMIDISynth class methodsFor: 'actions' stamp: 'mu 5/12/2017 10:38'!programChange: progNum channel: channel IPhoneScratchProxy isActive ifFalse: [^self]. ObjectiveCBridge performSelectorOnMainThread: [ self delegate programChange: progNum asInteger channel: channel asInteger ]! !!SoiMIDISynth class methodsFor: 'accessing' stamp: 'mu 3/19/2017 15:51'!delegate ^delegate ifNil: [delegate := (ObjectiveCObject findClassName: 'SUYMIDISynth') soleInstance]! !!SoiMIDISynth class methodsFor: 'class initialization' stamp: 'MU 5/16/2023 21:33'!initialize delegate := nil! !!SoiMeshStats class methodsFor: 'actions' stamp: 'MU 10/28/2022 18:11'!clearAllConnectionResults self initialize! !!SoiMeshStats class methodsFor: 'actions' stamp: 'MU 10/28/2022 18:08'!clearConnectionResultAt: ipAddressString self connectionResults removeKey: ipAddressString ifAbsent: []! !!SoiMeshStats class methodsFor: 'actions' stamp: 'MU 10/28/2022 18:09'!connectionResultAt: ipAddressString ^ self connectionResults at: ipAddressString ifAbsent: [false]! !!SoiMeshStats class methodsFor: 'actions' stamp: 'MU 10/28/2022 18:10'!connectionResultAt: ipAddressString put: aBoolean self connectionResults at: ipAddressString put: aBoolean! !!SoiMeshStats class methodsFor: 'class initialization' stamp: 'MU 10/28/2022 18:04'!initialize connectionResults := nil! !!SoiMeshStats class methodsFor: 'accessing' stamp: 'MU 10/28/2022 18:05'!connectionResults ^ connectionResults ifNil: [connectionResults := Dictionary new]! !!SoiNotificationCenter class methodsFor: 'actions' stamp: 'mu 7/9/2014 15:45'!postNofification: notificationName ^ self postNofification: notificationName with: nil! !!SoiNotificationCenter class methodsFor: 'actions' stamp: 'mu 7/9/2014 15:44'!postNofification: notificationName with: argObject | notificationLabel dfc | notificationLabel := notificationName asNSStringMacRoman. dfc := (ObjectiveCBridge classObjectForName: #NSNotificationCenter) defaultCenter. dfc postNotificationName: notificationLabel object: argObject asObjc. notificationLabel release.! !!SoiSettings methodsFor: 'settings access' stamp: 'mu 6/6/2014 21:18'!defaultFontScale ^2.0! !!SoiSettings methodsFor: 'settings access' stamp: 'mu 6/6/2014 21:19'!fontScale ^(self settingsDict at: 'FontScale' ifAbsentPut: [self defaultFontScale asString]) asFloat! !!SoiSettings methodsFor: 'settings access' stamp: 'mu 6/21/2014 00:19'!fontScaleArray ^#(1.3 1.4 1.5 1.6 1.7 1.8 1.9 2.0 2.1 2.2)! !!SoiSettings methodsFor: 'settings access' stamp: 'mu 6/21/2014 00:23'!fontScaleAt: idx ^ self fontScaleArray at: idx ifAbsent:[self defaultFontScale]! !!SoiSettings methodsFor: 'settings access' stamp: 'mu 6/21/2014 00:23'!fontScaleIndex ^ self fontScaleArray indexOf: self fontScale ifAbsent: [8]! !!SoiSettings methodsFor: 'settings access' stamp: 'mu 6/2/2014 16:18'!initialFontScale ^1.3! !!SoiSettings methodsFor: 'settings access' stamp: 'mu 7/1/2014 22:42'!language ^self settingsDict at: 'Language' ifAbsentPut: [ScratchTranslator guessLanguage]! !!SoiSettings methodsFor: 'reading' stamp: 'mu 6/2/2014 15:35'!createDefaultSettingsFile | settingsFileName lines strm f | IPhoneScratchProxy isActive ifFalse: [^Dictionary new]. settingsFileName := self class settingsPath, FileDirectory slash, 'Scratch.ini'. strm := FileStream newFileNamed: settingsFileName. lines := { 'FontScale=1.8'. }. lines do: [:line | strm nextPutAll: line, String crlf ]. strm close. f := FileStream readOnlyFileNamedOrNil: settingsFileName. f ifNil: [^Dictionary new]. ^self readSettingsFromLines: f contentsOfEntireFile lines! !!SoiSettings methodsFor: 'reading' stamp: 'mu 6/2/2014 15:33'!readSettingsFile "Read my settings file and answer a Dictionary of settings." "ScratchFrameMorph new readSettingsFile" | settingsFileName f | settingsFileName := (self class settingsPath, FileDirectory slash, 'Scratch.ini'). f _ FileStream readOnlyFileNamedOrNil: settingsFileName. f ifNil: [ ^ self createDefaultSettingsFile]. ^self readSettingsFromLines: f contentsOfEntireFile lines! !!SoiSettings methodsFor: 'reading' stamp: 'mu 6/2/2014 16:06'!readSettingsFromLines: lines | dict s tokens key | dict _ Dictionary new. lines do: [:line | s _ line collect: [:c | (c asciiValue < 32) ifTrue: [Character space] ifFalse: [c]]. tokens _ s findTokens: '='. key _ tokens first withBlanksTrimmed. tokens size = 2 ifTrue: [dict at: key put: tokens second withBlanksTrimmed] ifFalse: [dict at: key put: '1']]. dict keysAndValuesDo: [:k :v | self settingsDict at: k put: v ]. ^ self! !!SoiSettings methodsFor: 'accessing' stamp: 'mu 6/2/2014 15:45'!at: key ^ self settingsDict at: key asString capitalized ifAbsent:[]! !!SoiSettings methodsFor: 'accessing' stamp: 'mu 6/2/2014 15:56'!at: key ifAbsent: block ^ self settingsDict at: key ifAbsent: block! !!SoiSettings methodsFor: 'accessing' stamp: 'mu 6/2/2014 15:56'!at: key ifPresent: block ^ self settingsDict at: key ifPresent: block! !!SoiSettings methodsFor: 'accessing' stamp: 'mu 6/2/2014 15:58'!at: key ifPresent: aBlock ifAbsent: absentBlock ^ self settingsDict at: key ifPresent: aBlock ifAbsent: absentBlock! !!SoiSettings methodsFor: 'accessing' stamp: 'mu 6/2/2014 15:44'!at: key put: value ^ self settingsDict at: key asString capitalized put: value! !!SoiSettings methodsFor: 'accessing' stamp: 'mu 6/2/2014 15:27'!settingsDict ^settingsDict ifNil: [settingsDict := Dictionary new]! !!SoiSettings class methodsFor: 'instance creation' stamp: 'mu 6/2/2014 15:19'!default ^ default ifNil: [default := self new]! !!SoiSettings class methodsFor: 'saving' stamp: 'mu 6/2/2014 15:51'!applySetting: key to: value | keyString fName f sz settings all | self default at: key put: value. keyString := key asString, '='. fName _ FileDirectory default fullNameFor: (self settingsPath, FileDirectory slash, 'Scratch.ini'). f _ FileStream concreteStream new open: fName forWrite: true. f ifNil: [^ self]. sz _ f size. settings _ (f next: sz) lines. settings _ settings reject: [:s | s beginsWith: keyString]. settings _ settings reject: [:s | all _ s asByteArray asSet. (all size = 1) and: [all asArray first = 0]]. settings _ settings copyWith: (keyString, value asString). f position: 0. settings do: [:s | f nextPutAll: s, String crlf]. [f position < sz] whileTrue: [f nextPut: 0 asCharacter]. f close.! !!SoiSettings class methodsFor: 'accessing' stamp: 'mu 6/30/2014 23:13'!basicHelpDir | classOop helpDirOop dirNameOop dirName | classOop := ObjectiveCObject findClassName: 'SUYUtils'. helpDirOop := 'Help' asNSStringMacRoman. dirNameOop := classOop bundleResourceDirectoryWith: helpDirOop. helpDirOop release. dirName := dirNameOop asString. ^ FileDirectory on: dirName! !!SoiSettings class methodsFor: 'accessing' stamp: 'mu 6/2/2014 15:31'!basicSettingsDir | classOop dirNameOop dirName | classOop := ObjectiveCObject findClassName: 'SUYUtils'. dirNameOop := classOop applicationSupportDirectory. dirName := dirNameOop asString. ^ FileDirectory on: dirName! !!SoiSettings class methodsFor: 'accessing' stamp: 'mu 6/6/2014 00:05'!basicTempDir | classOop dirNameOop dirName | classOop := ObjectiveCObject findClassName: 'SUYUtils'. dirNameOop := classOop tempDirectory. dirName := dirNameOop asString. ^ FileDirectory on: dirName! !!SoiSettings class methodsFor: 'accessing' stamp: 'mu 7/2/2014 23:57'!helpDir | dir | IPhoneScratchProxy isActive ifFalse: [^FileDirectory default]. ObjectiveCBridge wrapWithAutoReleasePool: [dir := self basicHelpDir]. ^dir! !!SoiSettings class methodsFor: 'accessing' stamp: 'mu 9/10/2014 10:44'!helpPathOfCurrentLanguage | langStr helpDir pathReturner helpPah | langStr := self default language. helpDir := self helpDir. pathReturner := [:lang | | path | path := (helpDir fullNameFor: lang) pathName. (helpDir directoryExists: path) ifTrue: [path] ifFalse: []]. (helpPah := pathReturner value: langStr) ifNotNil: [^helpPah]. (helpPah := pathReturner value: (langStr findTokens: '_') first) ifNotNil: [^helpPah]. ^helpDir fullNameFor: 'en'! !!SoiSettings class methodsFor: 'accessing' stamp: 'mu 6/2/2014 15:31'!settingsDir | dir | ObjectiveCBridge wrapWithAutoReleasePool: [ dir := self basicSettingsDir]. ^dir! !!SoiSettings class methodsFor: 'accessing' stamp: 'mu 6/6/2014 00:08'!settingsPath IPhoneScratchProxy isActive ifFalse: [^FileDirectory default pathName]. ^ self settingsDir pathName. ! !!SoiSettings class methodsFor: 'accessing' stamp: 'mu 6/6/2014 00:06'!tempDir | dir | ObjectiveCBridge wrapWithAutoReleasePool: [ dir := self basicTempDir]. ^dir! !!SoiSettings class methodsFor: 'accessing' stamp: 'mu 6/6/2014 00:08'!tempPath IPhoneScratchProxy isActive ifFalse: [^FileDirectory default pathName]. ^ self tempDir pathName. ! !!SoiSettings class methodsFor: 'class initialization' stamp: 'mu 6/2/2014 15:19'!initialize default := nil! !!SoiTouchCursor class methodsFor: 'accessing' stamp: 'mu 9/29/2017 17:28'!delegate ^delegate ifNil: [delegate := (IPhoneScratchProxy delegate)]! !!SoiTouchCursor class methodsFor: 'actions' stamp: 'mu 9/29/2017 17:28'!hide self delegate hideCursor! !!SoiTouchCursor class methodsFor: 'actions' stamp: 'mu 9/29/2017 17:28'!show: cursorType | code | code := 0. cursorType = #eyeDropper ifTrue: [code := 1]. self delegate showCursor: code! !!SoiUtils class methodsFor: 'actions' stamp: 'mu 4/10/2017 17:42'!belongsToTemporary: filePath filePath nslog: 'temp-path: ', SoiSettings tempPath. ^filePath beginsWith: SoiSettings tempPath! !!SoiUtils class methodsFor: 'actions' stamp: 'mu 7/3/2014 23:28'!prepareRelease "SoiUtils prepareRelease" SoiSettings initialize. self initialize. self loadDefaultSprite.! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 7/2/2014 23:28'!aboutContents aboutContents ifNil: [self loadAbout]. ^aboutContents! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 9/10/2014 10:52'!aboutMediaContents IPhoneScratchProxy isActive ifFalse: [^'']. aboutMediaContents ifNil: [self loadAboutMedia]. ^aboutMediaContents! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 9/10/2014 10:52'!aboutMediaTitle IPhoneScratchProxy isActive ifFalse: [^'']. aboutMediaTitle ifNil: [self loadAboutMedia]. ^aboutMediaTitle! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 7/14/2014 14:33'!aboutSamplesContents IPhoneScratchProxy isActive ifFalse: [^'']. aboutSamplesContents ifNil: [self loadAboutSamples]. ^aboutSamplesContents! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 7/14/2014 14:34'!aboutSamplesTitle IPhoneScratchProxy isActive ifFalse: [^'']. aboutSamplesTitle ifNil: [self loadAboutSamples]. ^aboutSamplesTitle! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 7/2/2014 23:35'!aboutTitle IPhoneScratchProxy isActive ifFalse: [^'']. aboutTitle ifNil: [self loadAbout]. ^aboutTitle! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 7/3/2014 23:27'!defaultSprite ^DefaultSprite! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 6/9/2015 00:36'!localPrimaryIpV4Address | classOop addressesString tokens | IPhoneScratchProxy isActive ifFalse: [^'']. classOop := ObjectiveCObject findClassName: 'SUYNetUtils'. addressesString := classOop localIpV4AddressesString asString. tokens := (addressesString findTokens: ','). ^ tokens size > 0 ifTrue: [tokens first] ifFalse: [nil]! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 7/21/2014 14:51'!quarterModeBackgroundColor ^quarterModeBackgroundColor ifNil: [quarterModeBackgroundColor := Color r: 0.584 g: 0.603 b: 0.623]! !!SoiUtils class methodsFor: 'accessing' stamp: 'mu 7/21/2014 15:19'!quarterModeDrawExtent ^quarterModeDrawExtent ifNil: [quarterModeDrawExtent := 260@180] "x: 20px padding"! !!SoiUtils class methodsFor: 'class initialization' stamp: 'mu 9/10/2014 10:53'!initialize aboutTitle := aboutContents := aboutSamplesTitle := aboutSamplesContents := aboutMediaTitle := aboutMediaContents := quarterModeBackgroundColor := quarterModeDrawExtent := nil! !!SoiUtils class methodsFor: 'class initialization' stamp: 'mu 7/13/2014 00:12'!loadDefaultSprite | skinDir fname1 fname2 | skinDir := FileDirectory default directoryNamed: 'ScratchSkin'. fname1 := 'costume1.png'. (skinDir fileExists: fname1) ifFalse: [^self]. fname2 := 'costume2.png'. (skinDir fileExists: fname2) ifFalse: [^self]. DefaultSprite := ScratchSpriteMorph new importMedia: (skinDir fullNameFor: fname1); importMedia: (skinDir fullNameFor: fname2); addMediaItem: (SoundMedia new mediaName: 'pop' localized; sound: ScratchSpriteMorph popSound). DefaultSprite lookLike: 1.! !!SoiUtils class methodsFor: 'private' stamp: 'mu 7/14/2014 14:56'!loadAbout | arr | "SoiUtils loadAbout" arr := self loadAbout: 'about.txt'. aboutTitle := arr first. aboutContents := arr second! !!SoiUtils class methodsFor: 'private' stamp: 'mu 7/14/2014 14:55'!loadAbout: localFileName | strm title conts | strm := SoiSettings helpDir readOnlyFileNamed: localFileName. title := strm upTo: $\. strm skip: 2. conts := strm upToEnd. strm close. ^{title. conts}! !!SoiUtils class methodsFor: 'private' stamp: 'mu 9/10/2014 11:08'!loadAboutMedia | arr | "SoiUtils loadAboutMedia" arr := self loadAbout: 'aboutMedia.txt'. aboutMediaTitle := arr first. aboutMediaContents := arr second! !!SoiUtils class methodsFor: 'private' stamp: 'mu 7/14/2014 14:56'!loadAboutSamples | arr | "SoiUtils loadAboutSamples" arr := self loadAbout: 'aboutSamples.txt'. aboutSamplesTitle := arr first. aboutSamplesContents := arr second! !!SoiUtils class methodsFor: 'reboot support' stamp: 'mu 8/1/2014 12:09'!deleteLastProjectStatus FileDirectory default deleteFileNamed: (SoiSettings settingsPath, FileDirectory slash, 'LastProjectStatus.data') ifAbsent: [].! !!SoiUtils class methodsFor: 'reboot support' stamp: 'mu 8/1/2014 17:16'!readLastProjectStatus | strm conts statusArray | strm := FileStream readOnlyFileNamedOrNil: (SoiSettings settingsPath, FileDirectory slash, 'LastProjectStatus.data'). strm ifNil: [^ nil]. conts := strm contentsOfEntireFile withBlanksTrimmed. strm := ReadStream on: conts. statusArray := Array new: 4. statusArray at: 1 put: ((strm upToAll: String crlf) withBlanksTrimmed). statusArray at: 2 put: ((strm upToAll: String crlf) asNumber). statusArray at: 3 put: ((strm upToAll: String crlf) = 'true'). statusArray at: 4 put: ((strm upToAll: String crlf) = 'true'). ^statusArray! !!SoiUtils class methodsFor: 'reboot support' stamp: 'mu 8/1/2014 16:59'!writeLastProjectStatus: statusArray | fName strm path viewMode isInPresen isRunning |statusArray nslog: '!!!! writeLastProjectStatus:'. fName := FileDirectory default fullNameFor: (SoiSettings settingsPath, FileDirectory slash, 'LastProjectStatus.data'). strm := FileStream concreteStream new open: fName forWrite: true. strm ifNil: [^ false]. path := statusArray first. strm nextPutAll: path. strm crlf. viewMode := statusArray second. strm nextPutAll: viewMode asString. strm crlf. isInPresen := statusArray third. strm nextPutAll: isInPresen asString. strm crlf. isRunning := statusArray fourth. strm nextPutAll: isRunning asString. strm crlf. strm close. ^true! !!SoundMedia methodsFor: '*ScratchOnIPad-override' stamp: 'mu 4/10/2017 17:41'!exportFilename: fileName for: stageOrSprite "Export my sound to a file with the given name." | fName f | fName _ fileName. (fName asLowercase endsWith: '.wav') ifFalse: [fName _ fName, '.wav']. f _ StandardFileStream newScratchFileNamed: fName. f ifNil: [^ self]. "could not create or open file for writing" f binary. originalSound storeWAVSamplesOn: f. f close. IPhoneScratchProxy exportToCloudIfNeeded: fName! !!SoundMedia methodsFor: '*ScratchOnIPad-override' stamp: 'mu 9/14/2018 23:15'!loadFile: fName "Read my samples from a sound file." | snd errorString sndName mergedBuf | "(FileDirectory default fileExists: fName) ifFalse: [^ self inform: 'File not found' withDetails: fName]." errorString _ nil. sndName _ FileDirectory localNameFor: fName. Utilities informUserDuring: [:bar | bar value: 'Reading' translated, ': ', sndName, '...'. [snd _ SampledSound fromFileNamed: fName] ifError: [:err :rcvr | snd _ nil. errorString _ err]. snd ifNotNil: [ snd isStereo ifTrue: [ "merge stereo to mono" bar value: 'Converting ', sndName, 'to mono...'. mergedBuf _ snd sounds first samples. mergedBuf mixIn: snd sounds second samples. snd _ SampledSound samples: mergedBuf samplingRate: snd sounds first originalSamplingRate]. snd originalSamplingRate > 22050 ifTrue: [ "downsample to save space" bar value: 'Downsampling ', sndName, '...'. snd _ SampledSound samples: (snd samples downSampledLowPassFiltering: false) samplingRate: snd originalSamplingRate / 2]]]. errorString ifNotNil: [self inform: 'Cannot load File' translated withDetails: errorString translated. ^nil]. self sound: snd.! !!StandardFileStream class methodsFor: '*ScrachOnIPad-file creation' stamp: 'MU 12/11/2020 14:49'!readOnlyFileNamed: fileName "Open an existing file with the given name for reading." "Changed to open a more usefull popup menu. It now also includes the most likely choices. jaf" | selection dir files choices fullName newName | fullName _ self fullName: fileName. (self isAFileNamed: fullName) ifTrue: [^ self new open: fullName forWrite: false]. "File does not exist..." dir _ FileDirectory forFileName: fullName. files _ dir fileNames. choices _ (FileDirectory localNameFor: fullName) correctAgainst: files. selection _ (PopUpMenu labelArray: choices lines: (Array with: 5) ) startUpWithCaption: 'Could not read' translated, ': ', (FileDirectory localNameFor: fullName). newName _ (dir pathName , FileDirectory slash , (choices at: selection)). ^ self readOnlyFileNamed: (self fullName: newName)! !!String methodsFor: '*ScratchOnIPad' stamp: 'mu 6/2/2014 16:12'!asFloat ^ Float readFrom: self! !!String methodsFor: '*ScratchOnIPad' stamp: 'mu 4/30/2015 17:35'!copyTailIfBegins: aString (self beginsWith: aString) ifFalse: [^self]. aString size > self size ifTrue: [^self]. ^self copyFrom: aString size+1 to: self size! !!String methodsFor: '*ScratchOnIPad' stamp: 'mu 8/14/2014 02:52'!isAsciiString 1 to: self size do: [:pos | (self at: pos) asInteger >= 128 ifTrue: [^ false]. ]. ^ true.! !!String methodsFor: '*ScratchOnIPad' stamp: 'mu 5/21/2014 01:14'!pathName ^self! !!String methodsFor: '*ScratchOnIPad' stamp: 'mu 4/30/2015 17:38'!pathNameTrimmed ^self pathName copyTailIfBegins: '/private'.! !!String methodsFor: '*ScratchOnIPad' stamp: 'mu 8/14/2014 02:53'!translated self isAsciiString ifFalse: [^self]. ^ self localized! !!String methodsFor: 'iphone' stamp: 'mu 4/9/2014 22:59'!nslog | out | out := thisContext sender selector printString, '> ', self. Smalltalk isiPhone ifFalse: [^Transcript show: out]. ^ out iPhoneConsole! !!String methodsFor: 'iphone' stamp: 'mu 4/9/2014 23:44'!nslog: mark | out | out := thisContext sender selector printString, '> ', mark asString,': ', self. Smalltalk isiPhone ifFalse: [^Transcript show: out]. ^ out iPhoneConsole! !!StringDialog methodsFor: '*ScratchOnIPad-testing' stamp: 'mu 7/29/2014 12:21'!useMorphTitle ^true! !!StringDialog methodsFor: '*ScratchOnIPad-geometry' stamp: 'mu 7/29/2014 12:46'!ipadCenterYOffset ^ (super ipadCenterYOffset * 2) - 30! !!NewVariableDialog methodsFor: '*ScratchOnIPad-override' stamp: 'mu 8/4/2014 15:06'!initialize | label1 label2 | super initialize. spriteSpecificFlag _ false. radioButtons _ AlignmentMorph newRow color: Color transparent; hResizing: #shrinkWrap; vResizing: #shrinkWrap. allSpritesRadioButton _ ToggleButton onForm: (ScratchFrameMorph skinAt: #radioButtonOn) offForm: (ScratchFrameMorph skinAt: #radioButton). allSpritesRadioButton on; target: self; actWhen: #buttonDown; actionSelector: #toggleSpriteSpecific. label1 _ StringMorph new contents: ('For all sprites' localized); font: (ScratchFrameMorph getFont: #NewVariableDialogBox). radioButtons addMorphBack: allSpritesRadioButton. radioButtons addMorphBack: (Morph new extent: (5@5); color: Color transparent). radioButtons addMorphBack: label1. radioButtons addMorphBack: (Morph new extent: (15@5); color: Color transparent). thisSpriteRadioButton _ allSpritesRadioButton fullCopy off. label2 _ StringMorph new contents: ('For this sprite only' localized); font: (ScratchFrameMorph getFont: #NewVariableDialogBox). radioButtons addMorphBack: thisSpriteRadioButton. radioButtons addMorphBack: (Morph new extent: (5@5); color: Color transparent). radioButtons addMorphBack: label2. ScratchTranslator isRTL ifTrue: [radioButtons submorphs reversed do: [:m | m delete. radioButtons addMorphBack: m]]. mainColumn submorphsDo: [: m | ((m = messageLineMorphs) not) ifTrue: [m delete]]. mainColumn addMorphBack: (Morph new extent: (5@6); color: Color transparent); addMorphBack: typeinMorph; addMorphBack: (Morph new extent: (5@7); color: Color transparent); addMorphBack: radioButtons; addMorphBack: (Morph new extent: (5@7); color: Color transparent); addMorphBack: buttonRow; addMorphBack: bottomSpacer.! !!StringFieldMorph methodsFor: '*ScratchOnIPad-override' stamp: 'MU 4/5/2020 10:54'!forExpressionArg frame _ nil. borderColor _ Color transparent. borderWidth _ 0. insetX _ 2. heightPadding _ 6. self font: (ScratchFrameMorph getFont: #Arg).! !!StringFieldMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/18/2014 16:20'!keyboardFocusChange: amGettingFocus "Set my color to show whether I have focus." (amGettingFocus and: [isKeyboardFocus not]) ifTrue: [ lastContents _ stringMorph contents]. (isKeyboardFocus and: [amGettingFocus not]) ifTrue: [ lastContents _ nil. isNumeric ifTrue: [ self contents: stringMorph contents asNumberNoError printStringNoExponent]. acceptWhenFocusLost ifTrue: [self acceptEdits]]. isKeyboardFocus _ amGettingFocus. isKeyboardFocus ifTrue: [selectionStart _ 0. selectionEnd _ stringMorph contents size]. self changed. IPhoneScratchProxy isActive ifTrue: [self ipadTextFieldFocused: amGettingFocus]! !!StringFieldMorph methodsFor: '*ScratchOnIPad-override' stamp: 'MU 4/5/2020 10:42'!stringChanged "My string has changed. Resize myself if necessary and report the change." doResizing ifTrue: [ stringMorph fitContents. self width: (stringMorph right - self left) + borderWidth + 6]. (owner respondsTo: #fixArgLayout) ifTrue: [owner fixArgLayout]. self changed.! !!StringMorph methodsFor: '*ScratchOnIPad-utils' stamp: 'mu 5/11/2015 17:41'!truncatedString: objName limitWidth: limitWidth | utf8str n ellipses s w | utf8str := UTF8 withAll: objName. n _ utf8str asUTF32. ellipses _ ScratchTranslator ellipsesSuffix asUTF32. 1 to: n size do: [:i | s _ n copyFrom: 1 to: i. w _ self stringWidth: (s asUTF32, ellipses). w > limitWidth ifTrue: [ ^ ((n copyFrom: 1 to: i - 1) asUTF32, ellipses) asUTF8]]. ^utf8str! !!ScratchMenuTitleMorph methodsFor: '*ScratchOnIPad-events' stamp: 'mu 7/8/2014 01:12'!ipadMouseDown: evt target isNil | selector isNil ifTrue: [^ self]. self color: self highlightColor.! !!ScratchMenuTitleMorph methodsFor: '*ScratchOnIPad-events' stamp: 'mu 7/8/2014 01:11'!ipadMouseUp: evt target isNil | selector isNil ifTrue: [^ self]. self color: self normalColor. target perform: selector with: self. ! !!ScratchMenuTitleMorph methodsFor: '*ScratchOnIPad-events' stamp: 'mu 7/8/2014 01:08'!mouseUp: evt IPhoneScratchProxy isActive ifTrue: [^self ipadMouseUp: evt]. super mouseUp: evt! !!ScratchMenuTitleMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/8/2014 00:44'!handlesMouseOver: evt IPhoneScratchProxy isActive ifTrue: [^false]. ^ true! !!ScratchMenuTitleMorph methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/8/2014 01:04'!mouseDown: evt IPhoneScratchProxy isActive ifTrue: [^self ipadMouseDown: evt]. target isNil | selector isNil ifTrue: [^ self]. Cursor normal show. MenuBarIsActive _ true. target perform: selector with: self. "invoke my menu"! !!SystemDictionary methodsFor: '*ScratchOnIPad-accessing-override' stamp: 'mu 7/22/2014 20:43'!lowSpaceThreshold "Return the low space threshold. When the amount of free memory (after garbage collection) falls below this limit, the system is in serious danger of completely exhausting memory and crashing. This limit should be made high enough to allow the user open a debugger to diagnose a problem or to save the image." "Smalltalk installLowSpaceWatcher" ^ 250000! !!SystemDictionary methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 5/22/2023 12:06'!bailIfIPhoneGrabFile: aFilename | ff string stringOops | self isiPhone ifFalse: [^self]. IPhoneScratchProxy isOnDevelopment ifTrue: [^self]. ff _ FileStream readOnlyFileNamed: aFilename. string := ff contentsOfEntireFile. stringOops := string asNSStringMacRoman. IPhoneScratchProxy delegate bailWeAreBroken: stringOops. stringOops release. ff close.! !!ToggleButton methodsFor: '*ScratchOnIPad-override' stamp: 'mu 5/11/2015 17:15'!containsPoint: aPoint | f | (self bounds containsPoint: aPoint) ifFalse: [^ false]. f _ isOn ifTrue: [onForm] ifFalse: [offForm]. f ifNil: [^ true]. self ignoreTransparentArea ifTrue: [^true]. ^ (f isTransparentAt: aPoint - bounds origin) not! !!ToggleButton methodsFor: '*ScratchOnIPad-override' stamp: 'mu 6/16/2015 10:20'!handlesMouseDown: evt ^ true! !!ToggleButton methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/8/2014 21:50'!handlesMouseOver: evt IPhoneScratchProxy isActive ifTrue: [^false]. ^ true! !!ToggleButton methodsFor: '*ScratchOnIPad-override' stamp: 'mu 9/29/2017 23:57'!initialize super initialize. self cornerStyle: #square. isMomentary _ false. toggleMode _ true. isDisabled _ false. isOn _ isOver _ false. wasOn _ false. alphaOn _ false.! !!ToggleButton methodsFor: '*ScratchOnIPad-override' stamp: 'mu 7/8/2014 22:17'!mouseDown: evt "If I am currently turned on, turn myself off and vice versa. If toggleMode is false, then do nothing if I am already on. If isMomentary, then turn myself off immediately. If I am to act when I'm pressed, then send my target my action selector." evt hand toolType: nil. isDisabled ifTrue: [^ self]. wasOn _ isOn. actWhen == #buttonDown ifTrue: [ self on. self doButtonAction. isMomentary ifTrue: [[(Delay forMilliseconds: 500) wait. self off] fork] ].! !!ToggleButton methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 6/5/2015 14:38'!ignoreTransparentArea ^ignoreTransparentArea ifNil: [ignoreTransparentArea := self bounds area < 480]! !!ToggleButton methodsFor: '*ScratchOnIPad-accessing' stamp: 'mu 6/5/2015 14:39'!ignoreTransparentArea: aBoolean ignoreTransparentArea := aBoolean! !!ToggleButton methodsFor: '*ScratchOnIPad-actions' stamp: 'mu 7/8/2014 22:00'!setDisabled: aBoolean self isDisabled: aBoolean. isOver := false. "isOn := false." self changed.! !!UndefinedObject methodsFor: 'iPhone' stamp: 'mu 4/9/2014 23:00'!nslog | out | out := thisContext sender selector printString, '> nil'. Smalltalk isiPhone ifFalse: [^Transcript show: out]. ^out iPhoneConsole! !!UndefinedObject methodsFor: 'iPhone' stamp: 'mu 4/9/2014 23:44'!nslog: mark | out | out := thisContext sender selector printString, '> ', mark asString, ': nil'. Smalltalk isiPhone ifFalse: [^Transcript show: out]. ^out iPhoneConsole! !!VolumeEnvelope methodsFor: '*ScratchOnIPad-patches' stamp: 'mu 2/11/2015 23:26'!computeSlopeAtMSecs: mSecs "Private!! Find the next inflection point of this envelope and compute its target volume and the number of milliseconds until the inflection point is reached." | t i | ((loopEndMSecs ~~ nil) and: [mSecs >= loopEndMSecs]) ifTrue: [ "decay phase" t _ (points at: loopEndIndex) x + (mSecs - loopEndMSecs). i _ self indexOfPointAfterMSecs: t startingAt: loopEndIndex. i == nil ifTrue: [ "past end" targetVol _ points last y * decayScale. mSecsForChange _ 0. nextRecomputeTime _ mSecs + 1000000. ^ self]. targetVol _ (points at: i) y * decayScale. mSecsForChange _ (((points at: i) x - t) min: (endMSecs - mSecs)) max: 4. nextRecomputeTime _ mSecs + mSecsForChange. ^ self]. mSecs < loopStartMSecs ifTrue: [ "attack phase" i _ self indexOfPointAfterMSecs: mSecs startingAt: 1. targetVol _ (points at: i) y. mSecsForChange _ ((points at: i) x - mSecs) max: 4. nextRecomputeTime _ mSecs + mSecsForChange. ((loopEndMSecs ~~ nil) and: [nextRecomputeTime > loopEndMSecs]) ifTrue: [nextRecomputeTime _ loopEndMSecs]. ^ self]. "sustain and loop phase" noChangesDuringLoop ifTrue: [ targetVol _ (points at: loopEndIndex) y. mSecsForChange _ 10. loopEndMSecs == nil ifTrue: [nextRecomputeTime _ mSecs + 10] "unknown end time" ifFalse: [nextRecomputeTime _ loopEndMSecs]. ^ self]. loopMSecs = 0 ifTrue: [^ (points at: loopEndIndex) y]. "looping on a single point" t _ loopStartMSecs + ((mSecs - loopStartMSecs) \\ loopMSecs). i _ self indexOfPointAfterMSecs: t startingAt: loopStartIndex. targetVol _ (points at: i) y. mSecsForChange _ ((points at: i) x - t) max: 4. loopEndMSecs == nil ifTrue:[nextRecomputeTime _ (mSecs + mSecsForChange)] ifFalse:[nextRecomputeTime _ (mSecs + mSecsForChange) min: loopEndMSecs].! !!ToggleButton reorganize!('initialization' onForm:offForm: onForm:offForm:overForm: onForm:offForm:overForm:disabledForm: setDefaultLabel)('*ScratchOnIPad-override' containsPoint: handlesMouseDown: handlesMouseOver: initialize mouseDown:)('*ScratchOnIPad-accessing' ignoreTransparentArea ignoreTransparentArea:)('*ScratchOnIPad-actions' setDisabled:)('accessing' alphaOn: clearIsOver color isDisabled isDisabled: isMomentary: isOn label label:font: off on setLabelColor: shortcutLabel:font: toggleMode:)('geometry' extent:)('drawing' areasRemainingToFill: drawOn:)('event handling' mouseEnter: mouseLeave: mouseMove: mouseUp:)('menu' addCustomMenuItems:hand:)('object i/o' fieldsVersion initFieldsFrom:version: storeFieldsOn:)('*ScratchOnIPad-testing')!!SystemDictionary reorganize!('dictionary access' associationAtOrAbove:ifAbsent: at:put: atOrAbove:ifAbsent: atOrBelow:ifAbsent: includesKeyOrAbove: scopeFor:from:envtAndPathIfFound:)('browsing' browseAllCallsOn: browseAllImplementorsOf: browseAllImplementorsOfList:title: browseAllMethodsInCategory: browseAllObjectReferencesTo:except:ifNone: browseAllSelect: browseAllSelect:name:autoSelect: browseAllUnSentMessages browseAllUnimplementedCalls browseMessageList:name: browseMessageList:name:autoSelect: browseMethodsWhoseNamesContain: browseMethodsWithSourceString: browseMethodsWithString: browseObsoleteReferences showMenuOf:withFirstItem:ifChosenDo:)('retrieving' allBehaviorsDo: allCallsOn: allClassesDo: allClassesImplementing: allImplementedMessages allImplementorsOf: allMethodsInCategory: allMethodsWithSourceString:matchCase: allMethodsWithString: allObjectsDo: allPrimitiveMessages allSelect: allSelectNoDoits: allSentMessages allUnSentMessages allUnSentMessagesIn: allUnimplementedCalls pointersTo: pointersTo:except: pointersToItem:of: unimplemented)('class names' classNamed: classNames flushClassNameCache removeClassFromSystem: removeClassFromSystemUnlogged: removeClassNamed: renameClass:as: renameClassNamed:as:)('shrinking' abandonSources abandonTempNames discardMIDI discardMVC discardMorphic discardOddsAndEnds discardSoundSynthesis discardSpeech lastRemoval majorShrink printSpaceAnalysis printSpaceAnalysis:on: printSpaceDifferenceFrom:to: removeAllUnSentMessages unusedClasses zapMVCprojects)('*ScratchOnIPad-accessing-override' lowSpaceThreshold)('memory space' bytesLeft createStackOverflow garbageCollect garbageCollectMost installLowSpaceWatcher lowSpaceWatcher okayToProceedEvenIfSpaceIsLow primBytesLeft primLowSpaceSemaphore: primSignalAtBytesLeft: setGCBiasToGrow: setGCBiasToGrowGCLimit: signalLowSpace useUpMemory useUpMemoryWithArrays useUpMemoryWithContexts useUpMemoryWithTinyObjects)('special objects' clearExternalObjects compactClassesArray externalObjects hasSpecialSelector:ifTrueSetByte: recreateSpecialObjectsArray registerExternalObject: specialNargsAt: specialObjectsArray specialSelectorAt: specialSelectorSize unregisterExternalObject:)('image, changes name' changesName imageName imageName: sourcesName vmPath)('sources, change log' aboutThisSystem assureStartupStampLogged changes closeSourceFiles currentChangeSetString externalizeSources forceChangesToDisk internalizeChangeLog internalizeSources isBigEndian lastUpdateString logChange: newChanges: noChanges openSourceFiles systemInformationString timeStamp: version)('snapshot and quit' isMorphic lastQuitLogPosition processShutDownList processStartUpList quitPrimitive readDocumentFile saveAs setGCParameters snapshot:andQuit: snapshotPrimitive unbindExternalPrimitives)('housekeeping' cleanOutUndeclared condenseChanges condenseSources forgetDoIts makeInternalRelease obsoleteBehaviors obsoleteClasses reclaimDependents recompileAllFrom: removeAllLineFeeds removeEmptyMessageCategories sanityCheckSourceFiles testDecompiler testFormatter testFormatter2 verifyChanges)('miscellaneous' clipboardText clipboardText: exitToDebugger extraVMMemory: fullScreenMode: getSystemAttribute: getVMParameters handleUserInterrupt hasMorphic isMacOSX isUnix isWindows isiPhone listBuiltinModule: listBuiltinModules listLoadedModule: listLoadedModules logError:inContext:to: osVersion platformName spaceForInstancesOf: spaceTally unloadPlugin: verifyMorphicAvailability vmParameterAt: vmParameterAt:put:)('accessing' organization)('printing' printElementsOn:)('iphone' vmVersion)('*ScratchOnIPad-actions' bailIfIPhoneGrabFile:)!!SoundMedia reorganize!('initialize' initialize)('accessing' balance balance: currentSeconds currentSeconds: infoString isSound mediaSizeInKilobytes mediaType savedSound sound sound: volume volume:)('*ScratchOnIPad-override' exportFilename:for: loadFile:)('scratch ops' isPlaying pausePlaying playFrom: playFrom:to: playFromStart rewindSound startPlaying thumbnailFormExtent: totalSeconds)('compressing' compressBitsPerSample:saveOriginal: compressedBitsPerSample compressedData compressedSampleRate decompress isBuiltInSound reduceSamplingRate revertToUncompressed shareSoundWith:)('copying' updateReferencesUsing:)('object i/o' fieldsVersion initFieldsFrom:version: storeFieldsOn:)!SoiUtils initialize!SoiUtils class instanceVariableNames: 'aboutTitle aboutContents aboutSamplesTitle aboutSamplesContents aboutMediaTitle aboutMediaContents quarterModeBackgroundColor quarterModeDrawExtent '!SoiSettings initialize!SoiMeshStats initialize!SoiMIDISynth initialize!!SoiJobQueue class reorganize!('instance creation' priority:)!!ResizableToggleButton2 reorganize!('initialization' forceUnicodeRendering: initialize label:font: offForm:onForm: offForm:onForm:overForm: setDefaultLabel setLabelColor:)('accessing' action color icon: isOn label off on over padding: toggleButtonMode: toggleMode:)('*ScratchOnIPad-events-override' mouseDown:)('event handling' copyRecordingIn: handlesMouseOver: keyStroke: keyboardFocusChange: mouseEnter: mouseLeave: mouseMove: mouseUp: rightButtonMenu)('geometry' extent:)('layout' centerLabelOffset: leftJustifyInset: rightJustifyInset:)('private' helpScreenName labelColorOn:labelColorOff:labelColorOver: normal: over: presentHelpScreen pressed: setCurrent: updateLayout updateSize)('*ScratchOnIPad-actions' setFlatIcon:)!ScrollFrameMorph subclass: #ScrollFrameMorph2 instanceVariableNames: 'scrollBarStartInset scrollBarEndInset handlesMouseEvents prevCursorPoint ' classVariableNames: '' poolDictionaries: '' category: 'Scratch-UI-Support'!!ScratchSpriteMorph reorganize!('initialization' initialize)('accessing' defaultImageMedia draggable draggable: heading heading: isClone: isPaintable isRotatable isSprite position: referencePosition referencePosition: rotatedForm rotationCenter rotationDegrees rotationDegrees: rotationStyle rotationStyle: scale scalePoint scalePoint: xpos xpos: ypos ypos:)('pen ops' changePenHueBy: changePenShadeBy: changePenSizeBy: clearPenTrails penColor penColor: penDown penDown: penPosition penSize penSize: putPenDown putPenUp setPenColorFromCostumedNamed:x:y: setPenHueTo: setPenShadeTo: stampCostume)('motion ops' bounceOffEdge changeXposBy: changeYposBy: color:sees: directionMenu distanceTo: forward: glideSecs:toX:y:elapsed:from: gotoSpriteOrMouse: gotoX:y: gotoX:y:duration:elapsed:from: isClone isOnEdge pointToX:y: pointTowards: touching: touchingColor: turn: turnAwayFromEdge turnLeft: turnRight:)('*ScratchOnIPad-look ops-override' bubble:thinkFlag:promptFlag:)('looks ops' changeSizeBy: changeStretchBy: goBackByLayers: hide layer: lookLike: multiplySizeBy: recordScene: say: say:duration:elapsed:from: sayNothing scenes setScene: setSizeTo: setStretchTo: show think: think:duration:elapsed:from:)('movie ops' stopPlaying)('sensing ops' attributeNames getAttribute: hideQuestion showQuestion:)('clone ops' cloneAndSend:)('*ScratchOnIPad-drawing-override' drawOn:)('drawing' drawSubmorphsOn: drawTalkBubbleOn:)('geometry' containsPoint:)('event handling' justDroppedInto:event:)('right button menu' grabFromScreen rightButtonMenu)('object i/o' fieldsVersion initFieldsFrom:version: storeFieldsOn:)('private' copyForExport generateRotatedForm grabFormFromScreen keepOnScreen layoutChanged positionTalkBubble rotateByFlipping rotationDegrees:scalePoint:)('handle ops' resizeHandle rotateHandle)!!ScratchTranslator class reorganize!('class initialization' initialize)('startup' shutDown startUp)('language translation' addMIDITranslation: addSensorTranslations addUITranslation: checkAllTranslations checkTranslationDict colonSuffix currentLanguage doNotTranslate ellipsesSuffix extractQuotedStringFrom: formattingHeaderFields formattingSectionForPOT importLanguagesList insertISOCode:forLanguage: isRTLMath isoCodeForName: isoDict labelPartsFor: languageNames midiTranslationSet parameterSpecs: resetMIDITranslationSet resetUITranslationSet translationDict translationFor: uiTranslationSet uiTranslationSetAsSortedArray varSpecTranslationFor:varName:)('Unicode rendering' canRenderUnicode centerOffsetForButtonWithFont: centerOffsetForLabelWithFont: convertToMacRoman detectRenderPlugin fixAmbigousRTLPunctuation formFor:font:fgColor:bgColor: formFor:font:fgColor:bgColor:suppressAntiAliasing: isRTL: renderHintString renderWithSqueak setFont:antialias: showHintString stringExtent:font: useSqueakRendering verticalTrimForFont: xRangesFor:font:)('Unicode copy/paste' unicodeClipboard unicodeClipboardPut:)('locale' primCountry primLanguage)('rendering menu' fontMenu fontScaleMenu renderAntiAliasing renderScale renderingMenu toggleAntiAliasing toggleSuppressBold updateScratchUI)('import/export' export:value:to: exportPootleTranslations exportStringsToTranslateFrom:toFile: extractLanguageFromFileNamed: importOLPCTranslations importPootleTranslations importTranslation: isRTL lineOf:containingIndex: parseCommandSpec: parseTranslationLines: templateFilename updateTranslationFiles verifyTranslationFiles verifyTranslationFilesArgOrder withoutComment:)('*ScratchOnIPad-po' setDefaultRenderFont setDefaultRenderScale)('*ScracthOnIPad-override' guessLanguage objectiveCPrimCountry objectiveCPrimLanguage setLanguage: setRenderingHints translationDir)('*ScratchOnIPad-accessing' renderScale:)!!ScratchTabPaneMorph reorganize!('initialization' initialize)('*ScratchOnIPad-override' createTab:withLabel:onForm:offForm:)('accessing' currentTab currentTab: targetPane targetPane:)('drawing' drawSubmorphsOn:)('private' lightUpCurrentTab setLabelForTab:to: tab:label:)!!ScratchPrompterMorph reorganize!('*ScratchOnIPad-override' accept initialize)('initialize')('accessing' question: sprite:)('geometry' extent: fixLayout)('other' dispatchKeyStroke: enterKeyPressed grabKeyboardFocus isDone stopAsk)!!ImageMedia reorganize!('initialization' initialize)('accessing' compositeForm form form: hasTextLayer infoString isImage jpegBytes mediaSizeInKilobytes mediaType rotationCenter rotationCenter: savedForm textBox textBox: thumbnailFormExtent:)('copying' copy)('*ScratchOnIPad-override' exportFilename:for:)('other' jpegCompressIfPossibleQuality: jpegCompressIfPossibleQuality:saveOriginal: revertToUncompressed shareFormWith:)('object i/o' fieldsVersion initFieldsFrom:version: storeFieldsOn:)!!ScratchFrameMorph reorganize!('intialization' createBasicPanes createLogo createMenuPanel createReadoutPane createStageButtonsPanel createToolbar createViewModeButtonsPanel initialize makeXYReadout)('accessing' author author: libraryPane loginName loginName: loginPassword loginPassword: paintingInProgress paintingInProgress: projectAuthor projectComment projectCommentOrTemplate projectInfo projectName projectName: projectNameRaw scratchObjects scriptsPane viewMode viewerPane workPane)('iphone' buildWebSiteIntefaceOn:bundle: iphoneBuildUIWebViewFileURLOn:bundle: iphoneBuildUIWebViewOn:bundle: iphoneLaunchHelpFile: iphoneLaunchHelpHtmlInner: isRunning launchHelpHtml: setupTheLanguageOnThisDevice)('*ScratchOnIPad-initialization' reloadLogo)('*ScratchOnIPad-updating' updateFontScale:)('*ScratchOnIPad-menu' aboutApp aboutMedia aboutSamples askStepSpeed ipadHelpMenu: launchMicrobitConnectTutorialPage openAbout:contents: openSetFontScaleMenu)('*ScratchOnIPad-menu-override' addSensorsMenuTo: helpMenu: iphoneEditMenu: iphoneFileMenu: iphoneLaunchHelpFileInner: saveImageForEndUser setSingleStepping writeSummaryFile:)('menu/button actions' aboutScratch addSpriteMorph allProjectMedia canonicalizeImagesQuality:saveOriginal: canonicalizeSoundsBits:saveOriginal: compressImages compressSounds developersMenu editMenu: editNotes exitScratchSession exportSprite fileMenu: fillScreenOff fillScreenOn getLoginName hideMotorBlocks iphoneHelpMenu: launchAllHelpScreens launchHelpFile: launchHelpPage launchVideoTutorialPage launchWebSiteLogin newScratchProject paintSpriteMorph pressGreenFlagButton quitScratch renderingMenu resaveAllProjects shoutGo showMotorBlocks showSensorBoard startHostingScratchSession stopAll toggleErrorCatcher toggleSingleStepping uniqueSummaryFileName writeMultipleSummaries writeSummaryFile writeSummaryTotalsOn:)('geometry' extent: hidePalette:)('drawing' areasRemainingToFill: drawOn: fullDrawOn:)('event handling' handlesMouseDown: mouseDown: wantsKeyboardFocusFor:)('stepping' checkForWeDo processDroppedFiles processKeyboardEvents processWhenConditions step stepTime updateToolButtons)('dropping/grabbing' wantsDroppedMorph:event:)('view mode' closeDialogBoxes projectComment: updatePenPositions updateViewModeButtons)('other' addAndView: closeMediaEditorsAndDialogs delete mouseX mouseY newSound openMIDI presentHelpScreen: projectDirectory projectModified updateMediaCategoryFor: view:tab:category:)('startup' readDefaultNotes)('file read/write' clearStage extractInfoFrom: fixByteReversedSounds importScratchProject nameFromFileName: openScratchDroppedProjectNamed: saveScratchProject storeProjectInfoOn: updateLastHistoryEntryIfNeeded writeScratchProjectOld)('uploading' compressMediaForUpload printTupleElement:on: printTupleList:on: removeLastHistoryEntry revertToUncompressedMedia scriptsStringForUpload writeScratchProjectOn:)('watchers' deleteWatchersForSprite: deleteWatchersForVar:ofSprite: deletingWatcher initializeWatcherPositions listWatchers scratchWatchers showWatcher: unusedPositionForWatcher watcherForBlock: watcherShowingFor:selectorAndArg:)('tools (no longer used)' copyTool cutTool normalTool undoTool zoomInTool zoomOutTool)('*ScratchOnIPad-defaults' shortcutButtonsSpec)('*ScratchOnIPad-accessing' recorderRelatedWatchers)('*ScratchOnIPad-callback' watcherWasAdded:reporter: watcherWasDeleted:)('*ScratchOnIPad-settings' readFontScaleSetting: readLangSetting:)('*ScratchOnIPad-actions-override' addServerCommandsTo: importSpriteOrProject: installNewProject: joinScratchSession openScratchProject openScratchProjectNamed: saveScratchProjectNoDialog showNetworkAddress surpriseSpriteMorph)('*ScratchOnIPad-actions' airDropProject airDropProject: connectToMicrobit disconnectFromMicrobit exportToCloud exportToCloud: forceCloseMediaEditorsAndDialogs importFromCloud importMedia: ipadMailProject: ipadOpenWebViewFileURLOn: mailProject midiAllNotesOff openAutoSavedProjectNamed: openMeshMenu prepareBeforeRestart prepareRelease setFontScaleIndex: shareMicrobitHexProjectNamed: shareProject shareProjectDoing:onOverwriteConfirming: showMicrobitPopup silentWriteScratchProject startSensing stopSensing)('*ScratchOnIPad-mode' getLastViewModeIndex getViewModeIndex getViewModeIndexOf: setViewModeIndex: setViewModeIndex:presenting:running:)('*ScratchOnIPad-private' basicAddSpriteMorph fileNameFrom: ipadSetDefaultSprite)('*ScratchOnIPad-override' addShortcutButtonsTo: allBlocksString enterNormalMode enterPresentationMode enterQuarterMode exitPresentationMode extractProjectFrom: fixLayout fixProjectTitleMorphLayout languageMenu: nextSurpriseCostumeName processSettingsFile readSettingsFile recordLanguage: setDefaultSprite startup updateHistoryProjectName:op: updatePanes writeScratchProject)('private' enterQuarterModeIfSmallScreen projectIsEmpty rebuildUIForNewLanguage setLanguage: updateProjectName)('*ScratchOnIPad-enable/disable' disableInteractions enableInteractions)('*ScratchOnIPad-menu-actions-override' enableRemoteSensors)('*ScratchOnIPad-actions-mesh' exitMesh isMeshHosting isMeshHostingBroken isMeshJoined: isMeshRunning joinMesh: startMesh)!!ScratchFilePicker class reorganize!('*ScratchOnIPad-instance creation' forSave:)!ImageFrameMorph subclass: #ScratchFilePicker instanceVariableNames: 'directoryBarMorph contentsPaneMorph feedbackMorph scratchInfoClient currentDir extensions fetchInProgress showThumbnails thumbnailFetchProcess scratchServers scratchProjectFetcher lastUpMSecs wasSelected isDoubleClick sound finalSelection freezeFocus topBarMorph directoryBarArrowMorph initialParentDirectory presetParentDirectory forSave loadedSampledSound ' classVariableNames: '' poolDictionaries: '' category: 'Scratch-UI-Dialogs'!!ScratchFileChooserDialog class reorganize!('class initialization' clearFolderCache initialize)('instance creation' chooseExistingFileType:extensions:title: chooseFolder: chooseImageFileType:title: chooseNewFileDefault:title:type: deleteDuplicates openScratchFileFor:)('accessing' homeDir setHomeDir: setLastFolderTo:forType: userScratchProjectsDir)('utilities' confirmFileOverwriteIfExisting: replaceAsteriskWithUserName: waitForCompletionOrCancelOfFetch:)('*ScratchOnIPad' basicBundleDir basicBundleMediaSubFolder: bundleDir bundleMediaDir bundleMediaSubFolder: homeIndoxDir iphoneMediaSubFolderForType:forSave: lastFolderIsHomeInboxFolder lastFolderIsReadonlyFolder sampleProjectsDir userMediaDir userMediaSubFolder:)('*ScratchOnIPad-override' chooseSpriteCostumeFor: getDefaultFolderForType: getDefaultFolderForType:forSave: getLastFolderForType: getLastFolderForType:forSave: lastFolderIsSampleProjectsFolder saveScratchFileFor:)!!ScratchFileChooserDialog reorganize!('initialization' getUserResponse initialize)('*ScratchOnIPad-accessing-override' type:)('accessing' choosingFolder: defaultName: extensions: listExtent: redirectSavesToSampleFolder scratchFrame: setDirectory: showThumbnails: type)('interaction' yes)('iphone' iphoneSampleProjects)('*ScratchOnIPad-events' onClose onOpen)('*ScratchOnIPad-testing' forSave isSticky)('*ScratchOnIPad-shortcuts-override' myHome scratchBackgrounds scratchCostumes scratchSounds userProjects)('*ScratchOnIPad-override' addShortcutButtons createFileChooserLayout: createScratchFileChooserFor:saving: delete getUserResponseForFolder getUserResponseForNewFile iphoneSampleProjectsInner labelForHomeFolder)('shortcuts' myComp myDesktop sampleProjects)('other' scratchInfo:)('*ScratchOnIPad-private' addMoreActionButtons cloudUpload redirectSaveDirectoryIfNeeded)('*ScratchOnIPad-shortcuts' inboxProjects)!IfElseBlockMorph removeSelector: #containsPoint:!HandMorph initialize!!IPhoneScratchProxy class reorganize!('*ScratchOnIPad-testing' isActive isActive: isFirstLaunch)('accessing' delegate)('accessing class hierarchy' squeakProxy)('*ScratchOnIPad-event handling' onVmSpaceIsLow)('*ScratchOnIPad-exporting' exportToCloud: exportToCloudIfNeeded:)('*ScratchOnIPad-actions' cleanUp)('*ScratchOnIPad-opening' prepareHelpers prepareScratchFrameMorphBeforeOpen)('*ScratchOnIPad-override' startUp)('*ScratchOnIPad-registration' registerPublicMethods)('startup' alterMemorySettings)('terminationlogic' shouldWeExitPresentationMode shouldWeStopScratchProject)('*ScratchOnIPad-accessing' current isActiveProduction isInPresentation isInPresentation: isOnDevelopment isOnMac osVersion)('*ScratchOnIPad-sensors' localSensorValueAt:ifPresent: sensorAccessor sensorAccessorIsRunning)('*ScratchOnIPad-microbit' microbitAccessor microbitAccessorIsRunning microbitSensorValueAt:ifPresent:)!IPhoneScratchProxy removeSelector: #basicOpenProject:shouldRun:!IPhoneScratchProxy removeSelector: #launchWebSite!IPhoneScratchProxy removeSelector: #launchWebSiteFromPresentationMode!ObjectiveCSqueakProxy subclass: #IPhoneScratchProxy instanceVariableNames: 'projectPicked projectData scratchMorphic projectPickedRun startMutex workingMorph photoPickerQueue isInPresentation sensorAccessor microbitAccessor meshHandlingQueue projectOpenCount ' classVariableNames: 'ExitPresentationMode MouseClickProcessHandler SqueakProxy StopScratchProject ' poolDictionaries: '' category: 'Scratch-Proxy'!!IPhoneScratchProxy reorganize!('accessing' scratchMorphic scratchMorphic:)('*ScratchOnIPad-events' onProjectOpened onVmSpaceIsLow scratchDialogClosed: scratchDialogOpened:)('*ScratchOnIPad-override' openProjectForPresentation:runProject:)('processing' chooseThisProject:runProject: exitToDebugMode postLockProcessing shoutGo showStartLog stopAll)('initialize-release' initialize)('*ScratchOnIPad-actions' becomeActive becomeActiveAfter: becomeBackground cleanUp clearWorkingMorph commandKeyStateChanged: exitPresentationMode flushInputString: getDevelopmentModeIndex getFontScaleIndex getViewModeIndex pickPhoto: restartVm restoreDisplay restoreMeshIfNeeded scriptsAreRunning setFontScaleIndex: setViewModeIndex: shiftKeyStateChanged:)('*ScratchOnIPad-accessing' isInPresentation isInPresentation: meshHandlingQueue microbitAccessor photoPickerQueue projectOpenCount sensorAccessor viewMode workingMorph workingMorph:)('*ScratchOnIPad-private' basicOpenProject: basicRestartVm basicSetViewModeIndex: incrementProjectOpenCount)('*ScratchOnIPad-project-loading' autoSavedProjectName deleteAutoSavedProject:in: loadWhenAutoSavedProjectFound)('*ScratchOnIPad-actions-mesh' meshIsRunning meshJoin: meshJoined: meshRun:)!IPhonePresentationSpaceKeyState initialize!!IPhonePresentationSpaceKeyState class reorganize!('testing' isCommandPressed isShiftPressed)('accessing' commandPressed commandPressed: maxUnclaimedKeystrokeSize maxUnclaimedKeystrokeSize: shiftPressed shiftPressed:)('class initialization' initMaxUnclaimedKeystrokeSize initialize)!IPhoneMenu removeSelector: #localize!Object subclass: #IPhoneMenu instanceVariableNames: 'menuItemsActions menuDialog target iPhoneSemaphore ' classVariableNames: '' poolDictionaries: '' category: 'iPhoneScratchSupport'!