The Inbox: DesktopBackgroundLoader-sbw.20.mcz

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

The Inbox: DesktopBackgroundLoader-sbw.20.mcz

commits-2
A new version of DesktopBackgroundLoader was added to project The Inbox:
http://source.squeak.org/inbox/DesktopBackgroundLoader-sbw.20.mcz

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

Name: DesktopBackgroundLoader-sbw.20
Author: sbw
Time: 23 April 2010, 8:15:17.965 pm
UUID: bd0f5baa-9676-4e16-9e04-893e65f26d25
Ancestors: DesktopBackgroundLoader-sbw.19

Published for general distribution.  See Extras menu from Dock for access.

==================== Snapshot ====================

SystemOrganization addCategory: #DesktopBackgroundLoader!

----- Method: TheWorldMainDockingBar>>extrasMenuOn: (in category '*DesktopBackgroundLoader') -----
extrasMenuOn: aDockingBar

        aDockingBar addItem: [ :it|
                it contents: 'Extras' translated;
                        addSubMenu: [:menu|
                                menu addItem:[:item|
                                        item
                                                contents: 'Recover Changes' translated;
                                                help: 'Recover changes after a crash' translated;
                                                icon: MenuIcons smallHelpIcon;
                                                target: ChangeList;
                                                selector: #browseRecentLog].
                                menu addLine.
                                menu addItem:[:item|
                                        item
                                                contents: 'Window Colors' translated;
                                                help: 'Changes the window color scheme' translated;
                                                addSubMenu:[:submenu| self windowColorsOn: submenu]].
                                menu addItem:[:item|
                                        item
                                                contents: 'Set Author Initials' translated;
                                                help: 'Sets the author initials' translated;
                                                target: Utilities;
                                                selector: #setAuthorInitials].
                                menu addItem:[:item|
                                        item
                                                contents: 'Restore Display (r)' translated;
                                                help: 'Redraws the entire display' translated;
                                                target: World;
                                                selector: #restoreMorphicDisplay].
                                menu addItem:[:item|
                                        item
                                                contents: 'Rebuild Menus' translated;
                                                help: 'Rebuilds the menu bar' translated;
                                                target: TheWorldMainDockingBar;
                                                selector: #updateInstances].
                                menu addLine.
                                menu addItem:[:item|
                                        item
                                                contents: 'Start Profiler' translated;
                                                help: 'Starts the profiler' translated;
                                                target: self;
                                                selector: #startMessageTally].
                                menu addItem:[:item|
                                        item
                                                contents: 'Collect Garbage' translated;
                                                help: 'Run the garbage collector and report space usage' translated;
                                                target: Utilities;
                                                selector: #garbageCollectAndReport].
                                menu addItem:[:item|
                                        item
                                                contents: 'Purge Undo Records' translated;
                                                help: 'Save space by removing all the undo information remembered in all projects' translated;
                                                target: CommandHistory;
                                                selector: #resetAllHistory].
                                menu addItem:[:item|
                                        item
                                                contents: 'VM statistics' translated;
                                                help: 'Virtual Machine information' translated;
                                                target: self;
                                                selector: #vmStatistics].
                                menu addLine.
                                menu addItem:[:item|
                                        item
                                                contents: 'Graphical Imports' translated;
                                                help: 'View the global repository called ImageImports; you can easily import external graphics into ImageImports via the FileList' translated;
                                                target: (Imports default);
                                                selector: #viewImages].
                                menu addItem:[:item|
                                        item
                                                contents: 'Standard Graphics Library' translated;
                                                help: 'Lets you view and change the system''s standard library of graphics' translated;
                                                target: ScriptingSystem;
                                                selector: #inspectFormDictionary].
                                menu addItem:[:item|
                                        item
                                                contents: 'Annotation Setup' translated;
                                                help: 'Click here to get a little window that will allow you to specify which types of annotations, in which order, you wish to see in the annotation panes of browsers and other tools' translated;
                                                target: Preferences;
                                                selector: #editAnnotations].
                                menu addItem:[:item|
                                        item
                                                contents: 'Desktop Background Loader' translated;
                                                help: 'Let''s you select a graphic image and place it as your desktop background.' translated;
                                                target: StandardToolSet;
                                                selector: #openDesktopBackgroundLoader].
                        ] ]!

Model subclass: #DesktopBackgroundLoader
        instanceVariableNames: 'directory directoryCache list listIndex fileName volList volListIndex'
        classVariableNames: 'DefaultImagesLocation RecentDirs'
        poolDictionaries: ''
        category: 'DesktopBackgroundLoader'!

----- Method: DesktopBackgroundLoader classSide>>defaultImagesLocation (in category 'accessing') -----
defaultImagesLocation
        DefaultImagesLocation isNil ifTrue: [self initializeDefaultImagesLocation].
        ^DefaultImagesLocation!

----- Method: DesktopBackgroundLoader classSide>>defaultImagesLocation: (in category 'accessing') -----
defaultImagesLocation: aFileDirectory
        DefaultImagesLocation := aFileDirectory!

----- Method: DesktopBackgroundLoader classSide>>initialize (in category 'class initialization') -----
initialize
        TheWorldMainDockingBar updateInstances.
        RecentDirs := OrderedCollection new.
!

----- Method: DesktopBackgroundLoader classSide>>initializeDefaultImagesLocation (in category 'initialize-release') -----
initializeDefaultImagesLocation
        self defaultImagesLocation: FileDirectory default!

----- Method: DesktopBackgroundLoader classSide>>myWorkspace (in category 'workspace') -----
myWorkspace
"
DesktopBackgroundLoader defaultImagesLocation: (FileDirectory on: '/Users/steve/Pictures/Wallpaper')
"!

----- Method: DesktopBackgroundLoader classSide>>open (in category 'instance creation') -----
open
        "Open a view of an instance of me on the default directory."
        ^ToolBuilder open: self!

----- Method: DesktopBackgroundLoader classSide>>validExtensions (in category 'constants') -----
validExtensions
        ^ImageReadWriter allTypicalFileExtensions!

----- Method: DesktopBackgroundLoader>>addPath: (in category 'tree') -----
addPath: aString
        "Add the given string to the list of recently visited directories."

        | full |
        aString ifNil: [^self].
        full := String streamContents:
                [ :strm | 2 to: volList size do:
                        [ :i | strm nextPutAll: (volList at: i) withBlanksTrimmed.
                        strm nextPut: FileDirectory pathNameDelimiter]].
        full := full, aString.
"Remove and super-directories of aString from the collection."
        RecentDirs removeAllSuchThat: [ :aDir | ((aDir, '*') match: full)].

"If a sub-directory is in the list, do nothing."
        (RecentDirs detect: [ :aDir | ((full, '*') match: aDir)] ifNone: [nil])
                ifNotNil: [^self].

        [RecentDirs size >= 10]
                whileTrue: [RecentDirs removeFirst].
        RecentDirs addLast: full!

----- Method: DesktopBackgroundLoader>>attachForm:asMorphToWorld: (in category 'image') -----
attachForm: aForm asMorphToWorld: world
        | sketch previous |
        sketch := SketchMorph withForm: aForm.
        sketch
                setToAdhereToEdge: #center;
                name: self worldImageName;
                lock.
        previous := world submorphNamed: self worldImageName.
        previous isNil ifFalse: [previous delete].
        sketch
                openInWorld;
                goBehind!

----- Method: DesktopBackgroundLoader>>buildButtonPaneWith: (in category 'toolbuilder') -----
buildButtonPaneWith: builder
        | panel |
        panel := builder pluggablePanelSpec new.
        panel
                children: OrderedCollection new;
                layout: #horizontal.
        self optionalButtons do: [:spec |
                | btnSpec |
                btnSpec := builder pluggableActionButtonSpec new.
                btnSpec
                        model: self;
                        label: spec first;
                        action: spec second;
                        help: spec third translated.
                panel children add: btnSpec
                ].
        ^panel!

----- Method: DesktopBackgroundLoader>>buildFileInfoPaneWith: (in category 'toolbuilder') -----
buildFileInfoPaneWith: builder
        | textSpec |
        textSpec := builder pluggableTextSpec new.
        textSpec
                model: self;
                getText: #fileInfoContents;
                menu: nil.
        ^textSpec!

----- Method: DesktopBackgroundLoader>>buildListPaneWith: (in category 'toolbuilder') -----
buildListPaneWith: builder
        | listSpec |
        listSpec := builder pluggableListSpec new.
        listSpec
                model: self;
                list: #fileList;
                getIndex: #fileListIndex;
                setIndex: #fileListIndex:;
                menu: #fileListMenu:;
                keyPress: nil.
        ^listSpec!

----- Method: DesktopBackgroundLoader>>buildTreePaneWith: (in category 'toolbuilder') -----
buildTreePaneWith: builder
        | treeSpec |
        treeSpec := builder pluggableTreeSpec new.
        treeSpec
                model: self;
                roots: #rootDirectoryList;
                hasChildren: #hasMoreDirectories:;
                getChildren: #subDirectoriesOf:;
                getSelectedPath: #selectedPath;
                setSelected: #setDirectoryTo:;
                label: #directoryNameOf:;
                menu: #volumeMenu:;
                autoDeselect: false.
        ^treeSpec!

----- Method: DesktopBackgroundLoader>>buildViewerPaneWith: (in category 'toolbuilder') -----
buildViewerPaneWith: builder
        | panel |
        panel := builder pluggablePanelSpec new.
        panel
                model: self;
                name: 'imageViewer';
                children: #childrenForViewer.
        ^panel
!

----- Method: DesktopBackgroundLoader>>buildWith: (in category 'toolbuilder') -----
buildWith: builder
        | windowSpec window |
        windowSpec := builder pluggableWindowSpec new.
        windowSpec model: self.
        windowSpec label: 'Desktop Background Loader'.
        windowSpec children: OrderedCollection new.
        (self widgetSpecsWith: builder) do: [:array |
                | widgetSpec |
                widgetSpec := array last value.
                widgetSpec frame: (LayoutFrame fractions: array first offsets: array second).
                windowSpec children add: widgetSpec].
        window := builder build: windowSpec.
        self changed: #selectedPath.
        ^window!

----- Method: DesktopBackgroundLoader>>centerScreen (in category 'buttons') -----
centerScreen
        self fileName isNil ifFalse: [
                | world |
                world := Project current currentWorld.
                self attachForm: self currentForm asMorphToWorld: world.
                ]!

----- Method: DesktopBackgroundLoader>>childrenForViewer (in category 'image') -----
childrenForViewer
        ^OrderedCollection with: self scaledImageMorph!

----- Method: DesktopBackgroundLoader>>clearBackground (in category 'buttons') -----
clearBackground
        | world previous |
        world := Project current currentWorld.
        previous := world submorphNamed: self worldImageName.
        previous isNil
                ifTrue: [self inform: 'No background image found.' translated]
                ifFalse: [previous delete].
!

----- Method: DesktopBackgroundLoader>>currentForm (in category 'image') -----
currentForm
        ^self fileName isNil
                ifTrue: [self emptyForm]
                ifFalse: [Form fromFileNamed: (self directory fullNameFor: self fileName)]!

----- Method: DesktopBackgroundLoader>>directory (in category 'accessing') -----
directory

        ^directory!

----- Method: DesktopBackgroundLoader>>directory: (in category 'accessing') -----
directory: dir

        directory := dir.
        volList := ((Array with: '[]'), self directory pathParts)
                withIndexCollect: [:each :index | (String new: index - 1 withAll: $ ), each].
        volListIndex := volList size.
        self changed: #volumeList.
        self updateFileList!

----- Method: DesktopBackgroundLoader>>directoryNameOf: (in category 'tree') -----
directoryNameOf: aDirectory
        "Attempt to find the name of ServerDirectories when used."
        ^(aDirectory isRemoteDirectory and:[aDirectory isKindOf: ServerDirectory])
                ifTrue:[ServerDirectory servers keyAtIdentityValue: aDirectory]
                ifFalse:[aDirectory localName]!

----- Method: DesktopBackgroundLoader>>directoryNamesFor: (in category 'toolbuilder') -----
directoryNamesFor: item
        ^item directoryNames!

----- Method: DesktopBackgroundLoader>>emptyForm (in category 'image') -----
emptyForm
        | form |
        form := Form extent: 800@800 depth: Display depth.
        form fillWhite.
        ^form!

----- Method: DesktopBackgroundLoader>>fileInfoContents (in category 'file info') -----
fileInfoContents
        ^self fileName isNil
                ifTrue: ['No file selected' translated]
                ifFalse: [
                        | entry sizeStr form stream |
                        entry := self directory directoryEntryFor: self fileName.
                        sizeStr := entry fileSize asStringWithCommas.
                        form := self currentForm.
                        stream := WriteStream on: String new.
                        stream
                                nextPutAll: 'File Size: ';
                                nextPutAll: sizeStr;
                                nextPutAll: ' Image Size: ';
                                nextPutAll: form extent asString.
                        ^stream contents]!

----- Method: DesktopBackgroundLoader>>fileList (in category 'list') -----
fileList
        ^list!

----- Method: DesktopBackgroundLoader>>fileListIndex (in category 'list') -----
fileListIndex
        ^listIndex!

----- Method: DesktopBackgroundLoader>>fileListIndex: (in category 'list') -----
fileListIndex: anInteger
        | item name |
        listIndex := anInteger.
        listIndex = 0
                ifTrue: [fileName := nil]
                ifFalse:
                        [
                        item := self fileNameFromFormattedItem: (list at: anInteger).
                        (item endsWith: self folderString)
                                ifTrue:
                                        [
                                        name := item copyFrom: 1 to: item size - self folderString size.
                                        listIndex := 0.
                                        self addPath: name.
                                        name first = $^
                                                ifTrue: [self directory: (ServerDirectory serverNamed: name allButFirst)]
                                                ifFalse: [volListIndex = 1 ifTrue: [name := name, directory slash].
                                                        self directory: (directory directoryNamed: name)]]
                                ifFalse: [fileName := item]].
        self changed: #fileListIndex.
        self changed: #fileInfoContents.
        self changed: #childrenForViewer!

----- Method: DesktopBackgroundLoader>>fileListMenu: (in category 'list') -----
fileListMenu: aMenu
        ^aMenu.!

----- Method: DesktopBackgroundLoader>>fileName (in category 'accessing') -----
fileName

        ^ fileName!

----- Method: DesktopBackgroundLoader>>fileNameFormattedFrom:sizePad: (in category 'list') -----
fileNameFormattedFrom: entry sizePad: sizePad
        "entry is a 5-element array of the form:
                (name creationTime modificationTime dirFlag fileSize)"
        | nameStr |
        nameStr := entry isDirectory
                ifTrue: [entry name , self folderString]
                ifFalse: [entry name].
        ^nameStr!

----- Method: DesktopBackgroundLoader>>fileNameFromFormattedItem: (in category 'list') -----
fileNameFromFormattedItem: item
        | offset |
        offset := item lastIndexOf: $] ifAbsent: [0].
        ^(offset = 0
                ifTrue: [item]
                ifFalse: [item copyFrom: offset + 1 to: item size]) withBlanksTrimmed!

----- Method: DesktopBackgroundLoader>>fillScreen (in category 'buttons') -----
fillScreen
        self fileName isNil ifFalse: [
                | world scaledForm |
                world := Project current currentWorld.
                scaledForm := self scaledForm: self currentForm toSizeUsingMaximum: world extent.
                self attachForm: scaledForm asMorphToWorld: world]!

----- Method: DesktopBackgroundLoader>>folderString (in category 'accessing') -----
folderString
        ^ ' [...]'!

----- Method: DesktopBackgroundLoader>>fullName (in category 'accessing') -----
fullName
        "Answer the full name for the currently selected file; answer nil if no file is selected."

        ^ fileName ifNotNil: [directory
                ifNil:
                        [FileDirectory default fullNameFor: fileName]
                ifNotNil:
                        [directory fullNameFor: fileName]]
!

----- Method: DesktopBackgroundLoader>>hasMoreDirectories: (in category 'tree') -----
hasMoreDirectories: aDirectory
        (aDirectory isKindOf: FileDirectory) ifFalse:[^true]. "server directory; don't ask"
        ^directoryCache at: aDirectory ifAbsentPut:[
                [aDirectory directoryNames notEmpty] on: Error do:[:ex| true].
        ].!

----- Method: DesktopBackgroundLoader>>imageViewerMorph (in category 'image') -----
imageViewerMorph
        ^self myDependents detect: [:ea | ea knownName = 'imageViewer'] ifNone: []!

----- Method: DesktopBackgroundLoader>>initialize (in category 'initialize-release') -----
initialize
        super initialize.
        directoryCache := WeakIdentityKeyDictionary new.
        self directory: self class defaultImagesLocation!

----- Method: DesktopBackgroundLoader>>optionalButtons (in category 'buttons') -----
optionalButtons
        | list |
        list := OrderedCollection new.
        list
                add: {'Fill'. #fillScreen. 'The currently selected image will be scaled to fill background.  Narrowest dimension is kept intact.'};
                add: {'Stretch'. #stretchScreen. 'Stretches, or shrinks, the selected image to fully fit the current background dimensions.'};
                add: {'Center'. #centerScreen. 'Places the selected image centered in the background.'};
                add: {'Tile'. #tileScreen. 'Repeats the selected image in the background.'};
                add: {'Clear'. #clearBackground. 'Will remove the background morph last installed with this tool.'};
                yourself.
        ^list!

----- Method: DesktopBackgroundLoader>>recentDirs (in category 'accessing') -----
recentDirs
        "Put up a menu and let the user select from the list of recently visited directories."

        | dirName |
        RecentDirs isEmpty ifTrue: [^self].
        dirName := UIManager default chooseFrom: RecentDirs values: RecentDirs.
        dirName == nil ifTrue: [^self].
        self directory: (FileDirectory on: dirName)!

----- Method: DesktopBackgroundLoader>>rootDirectoryList (in category 'tree') -----
rootDirectoryList
        | dir dirList servers |
        dir := FileDirectory on: ''.
        dirList := dir directoryNames collect: [:each | dir directoryNamed: each].
        dirList isEmpty ifTrue: [dirList := Array with: FileDirectory default].
        servers := ServerDirectory serverNames collect: [ :n | ServerDirectory serverNamed: n].
        servers := servers select:[:each| each respondsTo: #localName].
        ^dirList, servers!

----- Method: DesktopBackgroundLoader>>scaledForm:toSizeUsingMaximum: (in category 'image') -----
scaledForm: aForm toSizeUsingMaximum: newExtent
        | scale |
        newExtent = aForm extent ifTrue: [^aForm].
        scale := newExtent x / aForm width max: newExtent y / aForm height.
        ^aForm
                magnify: aForm boundingBox
                by: scale
                smoothing: 2!

----- Method: DesktopBackgroundLoader>>scaledImageMorph (in category 'image') -----
scaledImageMorph
        | fullForm scaledForm imageMorph holder |
        holder := self imageViewerMorph.
        fullForm := self currentForm.
        scaledForm := self fileName isNil
                ifTrue: [fullForm]
                ifFalse: [fullForm scaledToSize: holder extent].
        imageMorph := ImageMorph new image: scaledForm.
        imageMorph position: holder position.
        ^imageMorph!

----- Method: DesktopBackgroundLoader>>selectedPath (in category 'tree') -----
selectedPath
        | top here result |
        top := FileDirectory root.
        here := self directory.
        result := (Array streamContents:[:s| | next |
                s nextPut: here.
                [next := here containingDirectory.
                top pathName = next pathName] whileFalse:[
                        s nextPut: next.
                        here := next.
                ]]) reversed.
        ^result!

----- Method: DesktopBackgroundLoader>>setDirectoryTo: (in category 'tree') -----
setDirectoryTo: dir
        dir ifNil:[^self].
        self directory: dir.
        self changed: #fileList.
!

----- Method: DesktopBackgroundLoader>>stretchScreen (in category 'buttons') -----
stretchScreen
        self fileName isNil ifFalse: [
                | world scaledForm |
                world := Project current currentWorld.
                scaledForm := self currentForm scaledToSize: world extent.
                self attachForm: scaledForm asMorphToWorld: world]!

----- Method: DesktopBackgroundLoader>>subDirectoriesOf: (in category 'toolbuilder') -----
subDirectoriesOf: aDirectory
        ^aDirectory directoryNames collect:[:each| aDirectory directoryNamed: each].!

----- Method: DesktopBackgroundLoader>>tileScreen (in category 'buttons') -----
tileScreen
        self fileName isNil ifFalse: [
                | world repeatingForm destForm top left |
                world := Project current currentWorld.
                destForm := Form extent: world extent depth: Display depth.
                repeatingForm := self currentForm.
                top := 0.
                left := 0.
                left to: (destForm extent x - 1) by: repeatingForm extent x do: [:xOffset |
                        top to: (destForm extent y - 1) by: repeatingForm extent y do: [:yOffset |
                                repeatingForm displayOn: destForm at: xOffset@yOffset
                                ]
                        ].
                self attachForm: destForm asMorphToWorld: world.
                ]
       
!

----- Method: DesktopBackgroundLoader>>updateFileList (in category 'list') -----
updateFileList
        | entries patterns newList sizePad |
        entries := self directory entries reject:[:e| e isDirectory].
        patterns := self class validExtensions collect: [:ea | '*.', ea].
        newList := entries select: [:entry |
                patterns anySatisfy: [:each |
                        each match: entry name]].
        sizePad := (newList inject: 0 into: [:mx :entry | mx max: entry fileSize])
                                        asStringWithCommas size.
        list := newList collect: [:ea | self fileNameFormattedFrom: ea sizePad: sizePad].
        volList size = 1 ifTrue:
                [
                list := list  ,
                        (ServerDirectory serverNames collect: [:n | '^' , n , self folderString])].
        listIndex := 0.
        volListIndex := volList size.
        fileName := nil.
        self changed: #volumeListIndex.
        self changed: #fileList.
        self changed: #fileListIndex.
        self changed: #fileInfoContents.
!

----- Method: DesktopBackgroundLoader>>volumeList (in category 'accessing') -----
volumeList
        "Answer the current list of volumes."

        ^ volList
!

----- Method: DesktopBackgroundLoader>>volumeListIndex (in category 'accessing') -----
volumeListIndex
        "Answer the index of the currently selected volume."

        ^ volListIndex
!

----- Method: DesktopBackgroundLoader>>volumeListIndex: (in category 'accessing') -----
volumeListIndex: index
        | path |
        volListIndex := index.
        index = 1
                ifTrue: [self directory: (FileDirectory on: '')]
                ifFalse: [
                        | delim |
                        delim := directory pathNameDelimiter.
                        path := String streamContents: [:strm |
                                2 to: index do: [:i |
                                        strm nextPutAll: (volList at: i) withBlanksTrimmed.
                                        i < index ifTrue: [strm nextPut: delim]]].
                                self directory: (directory on: path)].
        self addPath: path.
        self changed: #fileList.
!

----- Method: DesktopBackgroundLoader>>volumeMenu: (in category 'accessing') -----
volumeMenu: aMenu
        aMenu addList: {
                        {'recent...' translated. #recentDirs}.
                        #-.
                        {'add server...' translated. #askServerInfo}.
                        {'remove server...' translated. #removeServer}.
                        #-.
                        {'delete directory...' translated. #deleteDirectory}.
                        #-}.
        aMenu
                addServices: (self itemsForDirectory: self directory)
                for: self
                extraLines: #().
        ^aMenu.!

----- Method: DesktopBackgroundLoader>>widgetSpecsWith: (in category 'toolbuilder') -----
widgetSpecsWith: builder
        | btnPaneHeight listPaneHeight infoPaneHeight |
        btnPaneHeight := 24.
        listPaneHeight := 100.
        infoPaneHeight := 30.
        ^OrderedCollection new
                add: {
                        (0@0 corner: 0.25@1).
                        (0@0 corner: 0@0).
                        [self buildTreePaneWith: builder]};
                add: {
                        (0.25@0 corner: 1@0).
                        (2@0 corner: 0@btnPaneHeight).
                        [self buildButtonPaneWith: builder]};
                add: {
                        (0.25@0 corner: 1@0).
                        (2@(btnPaneHeight + 2) corner: 0@(btnPaneHeight + 2 + listPaneHeight)).
                        [self buildListPaneWith: builder]};
                add: {
                        (0.25@0 corner: 1@0).
                        (2@(btnPaneHeight + 2 + listPaneHeight + 2) corner: 0@(btnPaneHeight + 2 + listPaneHeight + 2 + infoPaneHeight)).
                        [self buildFileInfoPaneWith: builder]};
                add: {
                        (0.25@0 corner: 1@1).
                        (2@(btnPaneHeight + 2 + listPaneHeight + 2 + infoPaneHeight + 2) corner: 0@0).
                        [self buildViewerPaneWith: builder]};
                yourself!

----- Method: DesktopBackgroundLoader>>worldImageName (in category 'image') -----
worldImageName
        ^'worldBackgroundImage'!

----- Method: StandardToolSet class>>openDesktopBackgroundLoader (in category '*DesktopBackgroundLoader') -----
openDesktopBackgroundLoader
        DesktopBackgroundLoader open!


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: DesktopBackgroundLoader-sbw.20.mcz

Bert Freudenberg
On 24.04.2010, at 01:15, [hidden email] wrote:

>
> A new version of DesktopBackgroundLoader was added to project The Inbox:
> http://source.squeak.org/inbox/DesktopBackgroundLoader-sbw.20.mcz
>
> ==================== Summary ====================
>
> Name: DesktopBackgroundLoader-sbw.20
> Author: sbw
> Time: 23 April 2010, 8:15:17.965 pm
> UUID: bd0f5baa-9676-4e16-9e04-893e65f26d25
> Ancestors: DesktopBackgroundLoader-sbw.19
>
> Published for general distribution.  See Extras menu from Dock for access.

I find that duplication of FileList functionality somewhat questionable. If this became a specialized FileList for choosing images, along with its previews etc., that would be great. But all this effort just to choose a background?

In any case, to consider this for inclusion in trunk, it should not be a separate package. Packages that modify other packages are a Bad Thing. This one removes a method from the Morphic package (interestingly, the Morphic package is not marked dirty, that's a bug).

My suggestion would be to make the extras menu (or rather, the whole menu bar) extensible, then this package would not have to touch that existing method. Then this could just be a loadable package.

- Bert -



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: DesktopBackgroundLoader-sbw.20.mcz

Hannes Hirzel
On 4/24/10, Bert Freudenberg <[hidden email]> wrote:

> On 24.04.2010, at 01:15, [hidden email] wrote:
>>
>> A new version of DesktopBackgroundLoader was added to project The Inbox:
>> http://source.squeak.org/inbox/DesktopBackgroundLoader-sbw.20.mcz
>>
>> ==================== Summary ====================
>>
>> Name: DesktopBackgroundLoader-sbw.20
>> Author: sbw
>> Time: 23 April 2010, 8:15:17.965 pm
>> UUID: bd0f5baa-9676-4e16-9e04-893e65f26d25
>> Ancestors: DesktopBackgroundLoader-sbw.19
>>
>> Published for general distribution.  See Extras menu from Dock for access.

> I find that duplication of FileList functionality somewhat questionable. If
> this became a specialized FileList for choosing images, along with its
> previews etc., that would be great. But all this effort just to choose a
> background?

I am happy having the functionality in 4.1 with this package. For me
this is a need.

But I agree that a subclass of FileList for choosing images is better.

So for including it into the image it should be that. For having as an
addon-package it may remain as is and people can download it from
Stephen's web site.

> In any case, to consider this for inclusion in trunk, it should not be a
> separate package. Packages that modify other packages are a Bad Thing. This
> one removes a method from the Morphic package (interestingly, the Morphic
> package is not marked dirty, that's a bug).
Yes

> My suggestion would be to make the extras menu (or rather, the whole menu
> bar) extensible, then this package would not have to touch that existing
> method. Then this could just be a loadable package.
>
> - Bert -
>

Having an extensible extras menu is a thing Stephen prefers. Who is
going to do this?

--Hannes

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: DesktopBackgroundLoader-sbw.20.mcz

Steve Wessels-2

On Apr 24, 2010, at 5:43 PM, Hannes Hirzel wrote:

> On 4/24/10, Bert Freudenberg <[hidden email]> wrote:
>> On 24.04.2010, at 01:15, [hidden email] wrote:
>>>
>>> A new version of DesktopBackgroundLoader was added to project The  
>>> Inbox:
>>> http://source.squeak.org/inbox/DesktopBackgroundLoader-sbw.20.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: DesktopBackgroundLoader-sbw.20
>>> Author: sbw
>>> Time: 23 April 2010, 8:15:17.965 pm
>>> UUID: bd0f5baa-9676-4e16-9e04-893e65f26d25
>>> Ancestors: DesktopBackgroundLoader-sbw.19
>>>
>>> Published for general distribution.  See Extras menu from Dock for  
>>> access.
>
>> I find that duplication of FileList functionality somewhat  
>> questionable. If
>> this became a specialized FileList for choosing images, along with  
>> its
>> previews etc., that would be great. But all this effort just to  
>> choose a
>> background?
>
> I am happy having the functionality in 4.1 with this package. For me
> this is a need.
>
> But I agree that a subclass of FileList for choosing images is better.

I have published an updated version of the code to my Squeak goodies  
site this evening and will be updating
Squeak Source again soon to match.  This new code moves the tool back  
under FileList (where I first started
writing it) based upon feedback presented here.  And that's a smart  
move because it reduces code.  However, the
reasons I published a version as a subclass off of Model was a  
deliberate choice because I saw a few places in FileList
that need refactoring to make this sort of tools extension simpler.  
And rather than spend time mucking around inside
FileList, which I did not see as my charter for creating this tool, I  
saw that as a diversion which can be undertaken and utilized
at a later time.

This tool was created over an evening and part of the next day, so the  
effort is insignificant.  And I wanted to try out the newer tool  
builder approach that I see newer Squeak tools using.  This tool was  
rewritten as a response to someone who wrote to me requesting that I  
bring the old utility up to date with Squeak 4.1 and I was happy to  
oblige.

>
> So for including it into the image it should be that. For having as an
> addon-package it may remain as is and people can download it from
> Stephen's web site.
>
>> In any case, to consider this for inclusion in trunk, it should not  
>> be a
>> separate package. Packages that modify other packages are a Bad  
>> Thing. This
>> one removes a method from the Morphic package (interestingly, the  
>> Morphic
>> package is not marked dirty, that's a bug).
> Yes

I agree that modifying another package is a Bad Thing.  However I  
remain confused about this notion that this code
removes a method from the Morphic package.  Not that I can tell.  I  
may need a tip on where this is.

The only place where this utility collides with existing code is in  
the mechanism of adding to the dock/extras menu.  The
current design is locked in an prohibits this sort of change without  
cross impacts - which really is a bad thing.  What I find  
disappointing is
that we still have menu code like this in the image that does not  
support a registry.  This is not a new concept.  I'm pretty sure I have
published an enhancement for Squeak as far back as the 2.x days that  
provided a registry for the projects, world and appearance menus,  
precisely
because of nonsense collisions like this every time I wanted to  
publish an enhancement to Squeak's user interface.  And it has to be  
true
that whenever we produce enhancements that support individual styles  
(like a background loader or project thumbnail artifacts or whatever)
the user has to have the option of NOT including this capability.  
Hence a registry for these menus and now the dock.


>
>> My suggestion would be to make the extras menu (or rather, the  
>> whole menu
>> bar) extensible, then this package would not have to touch that  
>> existing
>> method. Then this could just be a loadable package.

That's the correct answer.

>>
>> - Bert -
>>
>
> Having an extensible extras menu is a thing Stephen prefers. Who is
> going to do this?

I could take another crack at this capability but I'm not really  
certain how the Squeak Community handles this kind of thing anymore.  
I've pretty much stayed away from the main mailing list the past few  
years so I'm coming into this sort of thing unawares of how code is  
added to the base anymore.

>
> --Hannes
>


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: DesktopBackgroundLoader-sbw.20.mcz

Hannes Hirzel
First of all,

Thank you Steve that you reacted so quickly to my with to have a
background chooser in 4.1
Please see some more comments below

Hannes

On 4/25/10, Steve Wessels <[hidden email]> wrote:

>
> On Apr 24, 2010, at 5:43 PM, Hannes Hirzel wrote:
>
>> On 4/24/10, Bert Freudenberg <[hidden email]> wrote:
>>> On 24.04.2010, at 01:15, [hidden email] wrote:
>>>>
>>>> A new version of DesktopBackgroundLoader was added to project The
>>>> Inbox:
>>>> http://source.squeak.org/inbox/DesktopBackgroundLoader-sbw.20.mcz
>>>>
>>>> ==================== Summary ====================
>>>>
>>>> Name: DesktopBackgroundLoader-sbw.20
>>>> Author: sbw
>>>> Time: 23 April 2010, 8:15:17.965 pm
>>>> UUID: bd0f5baa-9676-4e16-9e04-893e65f26d25
>>>> Ancestors: DesktopBackgroundLoader-sbw.19
>>>>
>>>> Published for general distribution.  See Extras menu from Dock for
>>>> access.
>>
>>> I find that duplication of FileList functionality somewhat
>>> questionable. If
>>> this became a specialized FileList for choosing images, along with
>>> its
>>> previews etc., that would be great. But all this effort just to
>>> choose a
>>> background?
>>
>> I am happy having the functionality in 4.1 with this package. For me
>> this is a need.
>>
>> But I agree that a subclass of FileList for choosing images is better


> I have published an updated version of the code to my Squeak goodies
> site this evening and will be updating
> Squeak Source again soon to match.  This new code moves the tool back
> under FileList (where I first started
> writing it) based upon feedback presented here.  And that's a smart
> move because it reduces code.  However, the
> reasons I published a version as a subclass off of Model was a
> deliberate choice because I saw a few places in FileList
> that need refactoring to make this sort of tools extension simpler.

I understand.

Stephen you background chooser is a nice  application of ToolBuilder
(the one which directly subclasses 'Model').

FileList subclasses StringHolder which subclasses Model. And it uses
ToolBuilder as well. And you say it should be reworked, to make is
easier to extend.


> And rather than spend time mucking around inside
> FileList, which I did not see as my charter for creating this tool, I
> saw that as a diversion which can be undertaken and utilized
> at a later time.

I understand.

> This tool was created over an evening and part of the next day, so the
> effort is insignificant.

I like your version of the Background chooser as another fine easy to
read example of using the ToolBuilder.

 And I wanted to try out the newer tool
> builder approach that I see newer Squeak tools using.  This tool was
> rewritten as a response to someone who wrote to me requesting that I
> bring the old utility up to date with Squeak 4.1 and I was happy to
> oblige.

That was me and I am happy with the result.

>>
>> So for including it into the image it should be that. For having as an
>> addon-package it may remain as is and people can download it from
>> Stephen's web site.

I prefer having it in the image, but if that is not possible for
whatever reason then downloading it as an addon is fine as well.

>>> In any case, to consider this for inclusion in trunk, it should not
>>> be a
>>> separate package. Packages that modify other packages are a Bad
>>> Thing. This
>>> one removes a method from the Morphic package (interestingly, the
>>> Morphic
>>> package is not marked dirty, that's a bug).
>> Yes
>
> I agree that modifying another package is a Bad Thing.  However I
> remain confused about this notion that this code
> removes a method from the Morphic package.  Not that I can tell.  I
> may need a tip on where this is.
>
> The only place where this utility collides with existing code is in
> the mechanism of adding to the dock/extras menu.  The
> current design is locked in an prohibits this sort of change without
> cross impacts - which really is a bad thing.  What I find
> disappointing is
> that we still have menu code like this in the image that does not
> support a registry.  This is not a new concept.  I'm pretty sure I have
> published an enhancement for Squeak as far back as the 2.x days that
> provided a registry for the projects, world and appearance menus,
> precisely
> because of nonsense collisions like this every time I wanted to
> publish an enhancement to Squeak's user interface.  And it has to be
> true
> that whenever we produce enhancements that support individual styles
> (like a background loader or project thumbnail artifacts or whatever)
> the user has to have the option of NOT including this capability.
> Hence a registry for these menus and now the dock.
>
>
>>
>>> My suggestion would be to make the extras menu (or rather, the
>>> whole menu
>>> bar) extensible, then this package would not have to touch that
>>> existing
>>> method. Then this could just be a loadable package.
>
> That's the correct answer.
>
>>>
>>> - Bert -
>>>
>>
>> Having an extensible extras menu is a thing Stephen prefers. Who is
>> going to do this?
>
> I could take another crack at this capability but I'm not really
> certain how the Squeak Community handles this kind of thing anymore.
> I've pretty much stayed away from the main mailing list the past few
> years so I'm coming into this sort of thing unawares of how code is
> added to the base anymore.
>
>>
>> --Hannes
>>
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: DesktopBackgroundLoader-sbw.20.mcz

Bert Freudenberg
In reply to this post by Steve Wessels-2
On 25.04.2010, at 06:47, Steve Wessels wrote

> I agree that modifying another package is a Bad Thing.  However I remain confused about this notion that this code
> removes a method from the Morphic package.  Not that I can tell.  I may need a tip on where this is.

It removes TheWorldMainDockingBar>>extrasMenuOn: from the Morphic package. It adds it to the DesktopBackgroundLoader package. Unloading your package breaks Morphic.

> The only place where this utility collides with existing code is in the mechanism of adding to the dock/extras menu.  The
> current design is locked in an prohibits this sort of change without cross impacts - which really is a bad thing.  What I find disappointing is that we still have menu code like this in the image that does not support a registry.  This is not a new concept.


True. The docking bar is new, and not as refined yet as the old world menu, which had a lot more functionality and allowed customization. But the bar is more discoverable and people generally appear to like it.

Now that the simple thing is in place, it's time to refactor so add-on packages can add menu entries without having to modify existing packages. Your's is the first to want to do so, there was no need before (even though it was foreseeable).

That refactoring would be a nice contribution, hint hint ;^)

- Bert -



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: DesktopBackgroundLoader-sbw.20.mcz

Steve Wessels-2
I'll take a crack at a general package that adds registry behavior to  
the dock menus, and probably while I'm at it, since I've done this  
sort if thing before, see what can be done about the other menus that  
provide points where we would all benefit with flexibility.

The world menu currently supports a registry for Open.

Once the work is done I can publish 2 packages:
   1.  Desktop background loader that uses menu registry to install  
(and no longer collides with existing code)
   2.  A menu registries enhancement so we cross this bridge more  
smoothly in the future.

My question remains unanswered however, about how do I make this  
happen?  Just put it all in Squeak Source?  What really belongs in the  
inbox then?

- Steve

On Apr 25, 2010, at 6:52 AM, Bert Freudenberg <[hidden email]>  
wrote:

> On 25.04.2010, at 06:47, Steve Wessels wrote
>
>> I agree that modifying another package is a Bad Thing.  However I  
>> remain confused about this notion that this code
>> removes a method from the Morphic package.  Not that I can tell.  I  
>> may need a tip on where this is.
>
> It removes TheWorldMainDockingBar>>extrasMenuOn: from the Morphic  
> package. It adds it to the DesktopBackgroundLoader package.  
> Unloading your package breaks Morphic.
>
>> The only place where this utility collides with existing code is in  
>> the mechanism of adding to the dock/extras menu.  The
>> current design is locked in an prohibits this sort of change  
>> without cross impacts - which really is a bad thing.  What I find  
>> disappointing is that we still have menu code like this in the  
>> image that does not support a registry.  This is not a new concept.
>
>
> True. The docking bar is new, and not as refined yet as the old  
> world menu, which had a lot more functionality and allowed  
> customization. But the bar is more discoverable and people generally  
> appear to like it.
>
> Now that the simple thing is in place, it's time to refactor so add-
> on packages can add menu entries without having to modify existing  
> packages. Your's is the first to want to do so, there was no need  
> before (even though it was foreseeable).
>
> That refactoring would be a nice contribution, hint hint ;^)
>
> - Bert -
>
>
>

Reply | Threaded
Open this post in threaded view
|

World Menu Registry enhancement

Steve Wessels-2
In reply to this post by Hannes Hirzel
I have published this morning to Squeak Source a package that provides  
broader menu registry capability to the World Menu.  The package is  
WorldMenuRegistry-sbw.1.mcz.  With this package installed into Squeak  
4.1, a developer can easily extend, and later on remove if required,  
menus entries for the following World menus using a registry system:
        open - Already existed and works with this package without changing  
existing entries
        appearance
        changes
        project
        help

There is also a unit test which exercises each of these menus and can  
be perused for examples of menu registry use.

The next step is to enhance the new menu/world dock to add registry  
support.  When all of that is working, I'll publish an update to the  
Desktop Background Screens package that will use the new menu  
registries dynamically.

Cheers,
  - Steve


Reply | Threaded
Open this post in threaded view
|

Contributing to inbox (was: The Inbox: DesktopBackgroundLoader-sbw.20.mcz)

David T. Lewis
In reply to this post by Steve Wessels-2
On Sat, Apr 24, 2010 at 11:47:53PM -0500, Steve Wessels wrote:
>
> I could take another crack at this capability but I'm not really  
> certain how the Squeak Community handles this kind of thing anymore.  
> I've pretty much stayed away from the main mailing list the past few  
> years so I'm coming into this sort of thing unawares of how code is  
> added to the base anymore.

Hi Steve,

It's really good to see you back!

The development model is described here:
  http://squeakboard.wordpress.com/2009/07/02/a-new-community-development-model/ 

The trunk and inbox repositories are at http://source.squeak.org/.
Make an account for yourself ("Register Member") and you're good
to go.

If you work with a development image that is up to date with the trunk,
then you can save your contributions to the inbox repository. Assuming
that you are using a Squeak 4.1 image, then the key things to do are:

- Point the Monticello update stream back at the trunk:
     Tools -> Preferences -> Monticello -> Update URL -> trunk

- Bring your image up to date with trunk (do this frequently):
     world -> help... -> Update code from server

That's about it. Anyone keeping up with trunk development can browse
your inbox entries with a Monticello browser, and load them to try
them out. Folks with trunk access can move them into trunk.

Of course if you are working on a package that is big enough to
maintain separately, you will still want to do that on SqueakSource.

Dave


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: DesktopBackgroundLoader-sbw.20.mcz

Balázs Kósi
In reply to this post by Bert Freudenberg
Hi,

> Now that the simple thing is in place, it's time to refactor so add-on packages can add menu entries without having to modify existing packages. Your's is the first to want to do so, there was no need before (even though it was foreseeable).

My first stab at the problem is in The Inbox: Morphic-kb.248
I wrote some explanation about how it works in the commit message [1].
It uses pragmas to fill the docking bar. I tried to keep it simple.
What do you think?

Balázs

[1] I copy the commit message here:

First stab at refactoring TheWorldMainDockingBar to allow external
packages to insert new menus, or menu items. We use two pragmas to
fill the docking bar.

A method in TheWorldMainDockingBar marked with pragma:
<createDockingBarMenuWithPriority: NN> will get a chance to build on
the DockingBarMorph, which it gets as its sole argument.

A method in TheWorldMainDockingBar marked with pragma:
<fillDockingBarMenu: #MENUNAME priority: NN> will get a chance to
build on a menu, which it gets as its sole argument, when someone
calls TheWorldMainDockingBar >> fillMenu: menu with: #MENUNAME

Priority controls the order in which these methods are called.

Currently there are three menus filled with this technique: #tools,
#extras, #help

So if you want to add a new menu item to the #extras menu from your
package, you'll need to create an extension method on
TheWorldMainDockingBar containing the pragma <fillDockingBarMenu:
#extras priority: 50>, and evaluate [TheWorldMainDockingBar
updateInstances]

You can find examples in TheWorldMainDockingBar.

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: DesktopBackgroundLoader-sbw.20.mcz

Steve Wessels-2
I just saw your work and like it.  Thank you.  I just published an  
update of my background loader to the inbox using this scheme.  That  
removes it's impact on other system code and now it installs clean.


On Apr 25, 2010, at 10:16 AM, Balázs Kósi wrote:

> Hi,
>
>> Now that the simple thing is in place, it's time to refactor so add-
>> on packages can add menu entries without having to modify existing  
>> packages. Your's is the first to want to do so, there was no need  
>> before (even though it was foreseeable).
>
> My first stab at the problem is in The Inbox: Morphic-kb.248
> I wrote some explanation about how it works in the commit message [1].
> It uses pragmas to fill the docking bar. I tried to keep it simple.
> What do you think?
>
> Balázs
>
> [1] I copy the commit message here:
>
> First stab at refactoring TheWorldMainDockingBar to allow external
> packages to insert new menus, or menu items. We use two pragmas to
> fill the docking bar.
>
> A method in TheWorldMainDockingBar marked with pragma:
> <createDockingBarMenuWithPriority: NN> will get a chance to build on
> the DockingBarMorph, which it gets as its sole argument.
>
> A method in TheWorldMainDockingBar marked with pragma:
> <fillDockingBarMenu: #MENUNAME priority: NN> will get a chance to
> build on a menu, which it gets as its sole argument, when someone
> calls TheWorldMainDockingBar >> fillMenu: menu with: #MENUNAME
>
> Priority controls the order in which these methods are called.
>
> Currently there are three menus filled with this technique: #tools,
> #extras, #help
>
> So if you want to add a new menu item to the #extras menu from your
> package, you'll need to create an extension method on
> TheWorldMainDockingBar containing the pragma <fillDockingBarMenu:
> #extras priority: 50>, and evaluate [TheWorldMainDockingBar
> updateInstances]
>
> You can find examples in TheWorldMainDockingBar.
>