Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
How to set the pane background of a Workspace to a picture
Last updated at 6:02 pm UTC on 2 October 2020
The content of this page is outdated.

ToDo: Add more recent information how to set the background image of a workspace.

2006

We need some images to use as backgrounds for a Workspace. I chose to use some backgrounds taken from ethemes.org . They are distributed under a GPL license. Of course, you are welcome to use any backgrounds that you choose, I just wouldn't expect them to look exactly the same.

Here's a link to the background that I used in the example shot:

Schematic-Diagram-5.jpg

Here's a link to a slightly darker version:

Schematic-Diagram-6.jpg

And here's the same thing in a different color scheme:

Schematic-Diagram-3.jpg

Save these images to the directory that your image is stored in. The easiest way to save the images for me was to open the web page and save the picture from the popup menu as the above names. For reference, I'll refer to the images as Schematic-Diagram-5.jpg, Schematic-Diagram-6.jpg, and Schematic-Diagram-3.jpg.

So we're ready to get started. First set your background to be Schematic-Diagram-5.jpg. You can do this by opening a file list, selecting the file 'Schematic-Diagram-5.jpg'. Bring up the file menu. Select 'open image as background'. This will set your desktop background to be the image Schematic-Diagram-5.jpg.

Now, let's set the background of a WorkspacePane:

mary _ Form fromFileNamed: 'Schematic-Diagram-3.jpg'

WorkspacePane defaultBackground: mary


Now open up a new WorkspacePane:

WorkspacePane openInWindow

A WorkspacePane in a window should appear. Now open in the menu in the windows title bar. Select 'use default background'. This will set the background of the WorkspacePane to be 'Schematic-Diagram-3.jpg'.

Now go to the window and type in some text. Hmm, probably a little difficult to see. We can set the color of the text by selecting 'set edit text color' in the menu located in the windows title bar. This brings up a Color Picker where we can select what color we would like the text in the WorkspacePane to be. Select a color in the Color Picker. Notice by holding down the mouse and running it over the Color Picker, the color of the text in the WorkspacePane changes.

So let's talk a little bit about how all of this works. Here's what we're trying to accomplish: We want to set the background of the pane to be a bitmap. We do this by setting the fill style of the PluggableTextMorph to be a BitmapFillStyle. Here's the code:

setBackground: theForm
	" Assign the background to the PluggableTextMorph"
	| fill tm |
	(tm _ self findA: PluggableTextMorph)
		ifNotNil: 
			[theForm
				ifNil: 
					[tm removeProperty: #fillStyle.
					tm color: Color transparent.
					^ self].
			fill _ BitmapFillStyle fromForm: theForm.
			fill origin: 1@1.
			tm fillStyle: fill]

Two tricky bits. First we need to get hold of the PluggableTextMorph. We can send the message #findA: to a Morph to find a submorph of a certain type. Because we only have one PluggableTextMorph in a WorkspacePane, we just findA: PluggableTextMorph to get the text Morph from the WorkspacePane.

Once we have that, we set the fillStyle. We create a BitmapFillStyle based on the bitmap stored in the parameter theForm, and set that to be the fillStyle of the PluggableTextMorph. Then we get to the hard part, which is setting the origin. The origin of a BitmapFillStyle indicates the location in the bitmap where the upper left hand corner of the Morph will be place at. In our example, the bitmap is tiled, that is, replicated and appears in a repeated fashion.

In our example, notice what happens when you move the Fancy Workspace window. When you move the window to a different, the geometric pattern lines up with the desktop pattern. If the geometries are the same in the patterns that we are using, we line them up by specifying the origin of the BitmapFillStyle to be 1@1. The location 0@0 has a special meaning, which is that a BitmapFillStyle always starts at the origin of the pattern. In order to 'let it slide', we set that origin to 1@1. Note that this is different than the default behaviour of BitmapFillStyle, which tries to maintain the same pattern at the same offset. We juggle this offset in #privateMoveBy:, but a better place to do this might be in the #drawOn: method. You should try rewriting the #drawOn: method to accomplish this by making sure that the fillStyle is at the correct position when you draw the PluggableTextMorph.

Another tricky bit is the Color Picker. When we make the appropriate menu selection, we send #setEditTextColor to the WorkspacePane. This opens a ColorPickerMorph. When a color is selected in the ColorPickerMorph, it sends the message #setEditTextColor: back to the WorkspacePane, which in turn sets the color of the text in the PluggableTextMorph. All this is accomplished by the same target/selector technique we first talked about in the LaunchButtonMorph.

Another visual trick you'll see on the themes on Linux desktops is something on the order of:

mary _ Form fromFileNamed: 'Schematic-Diagram-6.jpg'

WorkspacePane defaultBackground: mary


You can open up another workspace and set the default background to see that effect.

This trick gives the illusion that you are typing on a 'darkened' version of the desktop. Of course, the bitmap Schematic-Diagram-6.jpg is just a darkened version of the desktop bitmap, so that you appear to be typing on a darkened version of the desktop. Remember that we line up the two geometric patterns by adjusting the origin of the bitmap so that the illusion is convincing.

[
Ted Wright wrote me a note saying:
"While playing around with your example code I noticed that it's easy to get a real (no illusion) transparent 'Fancy Workspace' to type on with:

((WorkspacePane openInWindow color: (Color transparent)) findA: WorkspacePane)
color: (Color fromArray: #(1.0 1.0 0.0 0.2))

"
Check it out.
]

You should use these effects sparingly, because they are usually much more difficult to read than text on a solid color background. For example, this technique may be nice to use in a status window where you only need to look at what's going on occasionally. Most of the time you don't want a status window sticking out like a sore thumb. After all, a patterned pane does tend to fade into the background.

All in all, this WorkspacePane project covers a lot of ground. While the implementation is fairly straightforward, we changed how a Workspace 'looks'. We added a small amount of functionality by adding some buttons at the top of the pane. We learned a little about menus, and where we tie them into a SystemWindow and a pane. We also covered different fillStyles of Morphs, so that now we can make a Morph look like virtually anything we like, either algorithmically or gluing on the veneer of a bitmap. We did all this in only a couple of pages of code. Pretty cool if you ask me.

On to Check Check Roger Roger


Jim Benson
jb@speed.net

[fixed typo, and the image links direct to a freshmeat.net search. -Lyndon Tremblay]