Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Video input
Last updated at 12:32 am UTC on 7 September 2007
Question: Rob Hensley July 07, 2004 I am working on a project that combines real actors (captured with a video camera) and virtual entities (in this case, Morphic balls similar in design to the AtomMorph demo) that will interact in real-time on screen. My problem is finding code samples or demos of how to take the input from the video camera and use the image to create a Morph object on screen. [I'm using a Mac for this project...]

Answer: Göran Krampe This is EXACTLY what Martin McClure did with the Flying Karamazov brothers! http://www.google.com/search?q=Karamazov+brothers+Squeak&sourceid=firefox&start=0&start=0&ie=utf-8&oe=utf-8Here you can see it in action:http://www.fkb.com/luni_media.html

Answer:Ned KonzDiego Gomez Deckhas been working on an interface from Video4Linux to Squeak. Look at:Video4SqueakAlso:Squeak and WebcamsVideo and Image Processing (aka VideoFlow)http://www.is.titech.ac.jp/~ohshima/squeak/DShowVideo/

Answer:Vanessa Freudenberg [For a Mac...]You would have to write a plugin similar to Diego's V4LPlugin that uses Quicktime to read from the camera. To my knowledge, there is no such plugin, yet. It might be a good idea to use the same primitives to minimize platform-dependencies on the image side.

Question: Rob Hensley July 16, 2004 2:31 I started this project using a Mac, and then switched to a PC running Windows I am using the DVideoShowDecoderPlugin. I have tested it, and it works. My next step is separating the live actor's shadow part of the video image from the white background: I need to convert the Form from color to black and white. Once I have the shadow only, I can make a Morph out of it and instruct the virtual balls to react to it. Does anyone have any tips on the easiest way to convert the color image to B/W?
Ultimately, what I want to do is a) convert the color image to B/W, b) set a threshold of what is "white" and what is "black" (that is, everything over a certain value – let's say 123 – will be considered white, and everything below will be considered black), and c) construct a Morph object out of the "black" part of the image. This Morph object will interact w/ the virtual balls (which are already done).

Answer:Vanessa Freudenberg Use BitBlt with a colorMap (see BitBlt's class comment).

Question: Rob Hensley So, I want to take my Form object and make a BitBlt out of it, and then do what w/ the BitBlt object's colorMap? The comments seem to indicate that I can convert my Form object into a MaskedForm object, and then pass a list of colors (in my case, black and white) that the colorMap should be in terms of. Is that what you were advising me to do?
bAnswer:Vanessa Freudenberg Like this?
| orgForm bwForm threshold thresholdMap rect morph |
"Make a dark shape on light ground"
Display getCanvas
	fillRectangle: (0@0 extent: 400@300) color: Color yellow;
	fillOval: (100@100 extent: 30@50) color: Color blue.
orgForm := Form fromUser.
"a) convert the color image to B/W"
bwForm := orgForm asGrayScale.
"b) set a threshold of what is 'white' and what is 'black'" =threshold := 123. thresholdMap := (0 to: 255) collect: [:brightness |
	brightness  threshold
		ifTrue: [Color black]
		ifFalse: [Color white]].
bwForm colors: thresholdMap.
"c) construct a Morph object out of the 'black' part of the image." =bwForm := bwForm asFormOfDepth: 16. 
"bug?" rect := bwForm =rectangleEnclosingPixelsNotOfColor: Color white.
morph := Morph =new. morph bounds: rect; color: (Color red alpha: 0.5).
"display"
ImageMorph new
	image: bwForm;
	addMorph: morph;
	openInWorld.
"done"

Answer: Jack Johnson I can't help you with the implementation details, but I can tell you that in order to generate B&W, most people will average the RGB to get an 8-bit grayscale value. The overhead of this for a live video feed can be noticeable, and you'll find that for most video systems if you just take the values for green and compose a B&W image from it, the contrast will be more what you would want or expect from B&W video.

As for true B&W, the easy thing to do once you have grayscale is to pick some frames and test kicking all values below x to black, and above to white. Depending on the contrast in the back & foreground, this can be trivial or a real pain in the rear. Otherwise you're probably looking at fudging some sort of edge detection or some other process to generate a nice, clean shadow (if that's what you're after).

Typical blue- and green-screen tricks work well if you have some level of wardrobe control or are willing to invest a little more time in the image filtering.

Comment:Vanessa Freudenberg Yep, this can be very efficiently done in a single BitBlt call (mapping green component directly into black or white). See ColorMap>mapPixel:, which is what the bitblt primitive does for each pixel when you set an instance of ColorMap as the bitblt's colorMap.

Comment: Dean_Swan@Mitel.COM Form asGrayScale actually does extract the green component from 32 bit forms, or converts a lower depth Form to a 32 bit form and then extracts the green component. It is NOT however, a single BitBlt call. It does a copyBits for each column, and some fancy form/bitmap substituion to treat the 32 bit form as if it were an 8 bit form four times as wide. How would you accomplish this with only a "single BitBlt call"?
=== snip ====
| orgForm bwForm |
"Make a dark shape on light ground"
Display getCanvas
	fillRectangle: (0@0 extent: 400@300) color: Color yellow;
	fillOval: (100@100 extent: 30@50) color: Color blue.
orgForm := Form fromUser asFormOfDepth: 16.
"setup colormap to extract green component and map to 0 or 1" =colorMap := ColorMap shifts: #(0 0 -5 0)
	masks: #(0 0 2r000001111100000 0)
	colors: ((1 to: 32) collect: [:i | i  16 ifTrue: [1] 
                                                 ifFalse: [0]]). 
"16 = threshold of 0.5"
"This should also be allocated only once "
bwForm := Form extent: orgForm extent depth: 1.
"Do this every frame"
(BitBlt toForm: bwForm)
	copyForm: orgForm to: 0@0 rule: Form over colorMap: =colorMap. "Done" bwForm display ==== snap ====

For 32 bpp, you of course need to tweak the shifts, masks, and colors:
ColorMap shifts: #(0 0 -8 0)
	masks: #(0 0 16r00FF00 0)
	colors: ((1 to: 256) collect: [:i | i  128 ifTrue: [1]
                       ifFalse:[0]]).  "128 = threshold of 0.5"
I guess the 16 bpp version will be faster, but you should use whatever the plugin delivers fastest. You should avoid the conversion to another depth unless it is really necessary. Also, all constant calculations should be moved out of the inner loop (the one that fetches images from the camera and processes them).

Also, if your destination bitmap is not of depth 1, the colors in the ColorMap of course need other PixelValues:
String streamContents: [:s | #(1 8 16 32) do: [:d |
	s print: d; nextPutAll: ': '.
	{Color black. Color white} do: [:c |
		s nextPutAll: (c pixelValueForDepth: d) hex; space].
	s cr]]

1: 16r1 16r0
8: 16r1 16rFF
16: 16r1 16r7FFF
32: 16rFF000001 16rFFFFFFFF


Question: OK, I'm almost there! The version I'm working with now (includingyou're wonderful suggestions!) displays exactly ONE frame of the B/W image (Woo Hoo!) but then blows up. This is the code:
 initializeProcess
    | colorMap bwFrame |
    frame _ Form extent: self decoderSize depth: Display depth.
    process _ [[true] whileTrue: [
 	self decoderRequestCapture.
 	frameSemaphore wait.
 	self decoderCopyLastCapturedFrameInto: frame.
 	colorMap _ ColorMap shifts: #(0 0 -5 0)
 		masks: #(0 0 2r000001111100000 0)
 		colors: ((1 to: 32) collect: [:i |
 		i  16 ifTrue: [1] ifFalse: [0]]).
 	bwFrame _ Form extent: frame extent depth:1.
 	(BitBlt toForm: bwFrame)
 		copyForm: frame to: 0@0 rule: Form over colorMap: colorMap.
Here's the problem: the class I am extending wants to display frame (which MUST be of depth 16 or greater), not bwFrame (which is of depth 1), so I need to get bwFrame's revised colorMap back to depth 16 before I make frame equal to bwFrame. This is why it is blowing up. Any ideas?"
Answer: Vanessa FreudenbergWell, in this case, why do you allocate a new form at all? Just overwrite the values in the one you got! Also, for speed, do not build the colorMap inside the loop, but before:
initializeProcess
    | colorMap threshold |
    frame := Form extent: self decoderSize depth: 16.	"must be 16, or you need a different colorMap"
    threshold := 0.5. "tweak here"
    colorMap := ColorMap shifts: #(0 0 -5 0)
       masks: #(0 0 2r000001111100000 0)
       colors: ((1 to: 32) collect: [:i | i  (threshold 32)
          ifTrue: [Color black pixelValueForDepth: 16]
          ifFalse: [Color white pixelValueForDepth: 16]]).
    process := [[
	self decoderRequestCapture.
	frameSemaphore wait.
	self decoderCopyLastCapturedFrameInto: frame.
	(BitBlt toForm: frame)
		copyForm: frame to: 0@0 rule: Form over colorMap: colorMap.
	] repeat] forkAt: self decoderProcessPriority.
This code is untested, of course, but I doubt you can get much more efficient than that ;)

Question: OK, that makes a lot of sense; Thanks again!


Answer: Yoshiki Ohshima [Regarding the error:] "Error: DirectShow: True" This error simply indicates that you were trying to initialize the subsystem when it is already initialized. One thing you can do is call the class side #shutdown method once and it shouldn't raise this error.

In regards to the multi-threaded code, you should use the WorldState class #addDeferredUIMessage: to avoid the race condition.