[squeak-dev] The Trunk: EToys-topa.307.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Oct 4 12:49:52 UTC 2017


Tobias Pape uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-topa.307.mcz

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

Name: EToys-topa.307
Author: topa
Time: 4 October 2017, 2:50:50.655952 pm
UUID: c75ac142-2eb0-4153-b7f2-d1acd65e66b4
Ancestors: EToys-tpr.306

Fix and Improve WebCamMorph (try it!)

FYI: Windows-DLL is at https://github.com/OpenSmalltalk/opensmalltalk-vm/raw/Cog/platforms/win32/plugins/CameraPlugin/CameraPlugin.dll

Aside: make Tetris appear in objects -> games

=============== Diff against EToys-tpr.306 ===============

Item was added:
+ ----- Method: Player>>getShowFPS (in category '*Etoys-Squeakland-MorphicExtras-WebCam') -----
+ getShowFPS
+ 	^ self getValueFromCostume: #getShowFPS!

Item was added:
+ ----- Method: Player>>getWebCamOrientation (in category '*Etoys-Squeakland-MorphicExtras-WebCam') -----
+ getWebCamOrientation
+ 	^ self getValueFromCostume: #getWebCamOrientation!

Item was added:
+ ----- Method: Player>>setShowFPS: (in category '*Etoys-Squeakland-MorphicExtras-WebCam') -----
+ setShowFPS: aBoolean
+ 	self setCostumeSlot: #setShowFPS: toValue: aBoolean!

Item was added:
+ ----- Method: Player>>setWebCamOrientation: (in category '*Etoys-Squeakland-MorphicExtras-WebCam') -----
+ setWebCamOrientation: aSymbol
+ 	costume renderedMorph setWebCamOrientation: aSymbol!

Item was changed:
  ----- Method: Tetris class>>descriptionForPartsBin (in category 'parts bin') -----
  descriptionForPartsBin
  	^ self partName:	'Tetris' translatedNoop
+ 		categories:		{'Games' translatedNoop}
- 		categories:		#()
  		documentation:	'Tetris, yes Tetris' translatedNoop!

Item was changed:
  RectangleMorph subclass: #WebCamMorph
+ 	instanceVariableNames: 'camNum camIsOn frameExtent displayForm resolution useFrameSize captureDelayMs showFPS framesSinceLastDisplay lastDisplayTime fps orientation'
- 	instanceVariableNames: 'camNum camIsOn frameExtent displayForm resolution useFrameSize captureDelayMs'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Etoys-Squeakland-MorphicExtras-WebCam'!
  
  !WebCamMorph commentStamp: '<historical>' prior: 0!
  INTRODUCTION
  =========
  
  WebCamMorph together with CameraPlugin (originally from MIT Scratch) provides an easy and cross platform way to use webcam input in Squeak and Etoys. The first version has been created specifically with Etoys in mind. To view a live feed simply drag a "WebCam" tile from the "WebCam" category in the objects tool. Open up a viewer on the morph and display the "camera settings" category to explore the following basic settings:
  
  	"camera is on": turn the camera on/off.
  
  	"camera number": usually the default of "1" is ok but if you have more than one camera connected then adjust between 1 and 9 for other instances of WebCamMorph.
  
  	"max fps": leave as is for now. It is unusual for webcams to capture at higher than 30fps. See later for further explanation of how fps is controlled.
  
  	"actual fps": read-only. Indicates the actual fps being achieved which can depend significantly on lighting conditions and capture resolution...
  
  	"resolution": webcams can have a range of resolutions but for simplicity three are supported: "low" (160x120), "medium" (320x240) and "high" (640x480). Adjust in good lighting to see if "actual fps" increases. 
  
  	"use frame size": the resolution used for capturing can differ from the resolution used for display. If this setting is true then WebCamMorph is resized to match the camera resolution. If false then you are free to resize it however you want (via the "resize" halo button, use shift to preserve aspect ratio)
  
  
  Beyond viewing a live feed WebCamMorph has been designed to support different uses including simple effects, time-lapse photography, stop-motion animation, character recognition, motion detection and more complex processing of every frame for feature detection. The following information is to help you understand how and why WebCamMorph operates so you can adjust it for your particular needs.
  
  
  "FRAMES PER SECOND", LIGHTING & CAMERA RESOLUTION
  ==================================
  
  The maximum possible frame rate depends on many factors, some of which are outside of our control. Frame rates differ between cameras and usually depend significantly on chosen resolution and lighting conditions. To ensure a balance between capturing every available frame and keeping everything else responsive, WebCamMorph dynamically adjusts the delay between capturing one frame and the next (does not apply when in "manual capture" mode, see later). 
  
  WebCams often include automatic compensation for lighting conditions. In low lighting it takes significantly more time for the camera to get a picture than it does in good lighting conditions. For example 30fps may be possible with good lighting compared to 7fps in low lighting. So for best capture rates ensure you have good lighting!! 
  
  Cameras have a "native" resolution at which frame rates are usually better than for other resolutions. Note though that the native resolution might be *higher*
  than the *minimum* resolution available. It pays to experiment with different resolutions to find which one results in the highest frame rate. Use good lighting conditions when experimenting with resolutions.
  
  
  "MANUAL CAPTURE" MODE
  ===============
  
  In simply usage WebCamMorph automatically captures a frame and displays it. To support Etoys scripting a "manual capture" mode is provided where you or your script determines when to capture, when to apply effects (or not) and when to update the display. In between these steps you can do anything you want. Note that frames rates will be lower than that in automatic capture mode and that "skip frames" (described next) will need adjusting at very low capture rates.
  
  Tip: In manual mode the camera can be turned off. It will be turned on automatically when required and return to it's previous state after a frame has been captured. For capture periods of five seconds or more turning the camera off may save power, which can especially useful when running off batteries. For smaller periods leaving the camera on will avoid some delays and could help speed up webcam related scripts.
  
  
  "SKIP FRAMES"
  ========
  
  Webcams and their drivers are typically designed for streaming live video and use internal buffering to help speed things up. At low capture rates the picture can appear to lag real-time because what you see is the next available buffer not the *latest* buffer. So for example if you capture a frame every ten seconds and there are three buffers being used then what you actually see may be thirty seconds old. We have little/no control over the number of buffers used and the actual number can vary between cameras and under different circumstances for the same camera. "skip frames" is provided to compensate for buffering so increase it when doing "manual" capturing until you see what you expect to see. Typically a setting of 8 is enough but I have had to use 20 with one particular camera in low lighting.
  
  
  "SNAPSHOTS"
  ========
  
  Where as "capturing" is the process of getting an image from the Camera into Squeak/Etoys, a "snapshot" preserves whatever is currently displayed (which may be the captured image after effects have been applied). To store snapshots you need to designate a "holder" which at the moment can be either a "holder" morph or a "movie" morph. Create one of these before proceeding. To assign a holder open up a viewer for WebCamMorph, display the "snapshot" category and click in the box at the right of the entry called "snapshot holder". The cursor will now resemble a cross-hair and can be clicked on the target holder/movie morph. To take a single snapshot at any time click (!!) on the left of "take snapshot". In auto-capture mode WebCamMorph can also be set to take multiple consecutive snapshots . First, before turning the camera on, set a sensible limit using "snapshot limit" (to avoid using all the computers memory) then set "auto snapshot" to true. When the camera is next turned on then s
 napshots are taken for every frame until "snapshot limit" becomes zero. "snapshot limit" is automatically decremented but not reset to avoid problems (although you are free to reset it manually or via a script).
  
  
  "EFFECTS" - WIP
  =========
  
  Similar to snapshots, a holder can be designated as the "effects holder". This holder is intended to be populated with "fx" morphs (coming soon) which will operate on captured frames prior to displaying. Stay tuned ;-)
  
  
  CLEARING SNAPSHOT & EFFECTS HOLDERS
  =========================
  
  Keeping a link to snapshot or effects holders can tie up resources even after the target holders have been deleted and are no longer visible. To ensure this does not happen designate the WebCamMorph itself as the holder (for method see "snapshots" section above).
  
  
  COMING SOON!!
  =========
  
  - Built-in basic effects such as brightness, contrast and hue.
  - Image "fx" morphs for effects such as those found in MIT Scratch and many other types of effects/ image processing.
  - More snapshot options, eg, store to file
  - Demo projects
  
  !

Item was changed:
  ----- Method: WebCamMorph class>>additionsToViewerCategories (in category 'scripting') -----
  additionsToViewerCategories
  	"Answer a list of (<categoryName> <list of category specs>) pairs that characterize the phrases this kind of morph wishes to add to various Viewer categories."
  	^ #(
  
  	(#'camera' (
+ 		(slot resolution '160x120, 320x240, 640x480 or 1280x960' 
- 		(slot resolution '160x120, 320x240 or 640x480' 
  			WebCamResolution readWrite Player getWebCamResolution Player setWebCamResolution:)
+ 		(slot orientation 'Natural (mirrored) or navtive (as from the camera' 
+ 			WebCamOrientation readWrite Player getWebCamOrientation Player setWebCamOrientation:)
  		(slot cameraIsOn 'Whether the camera is on/off' Boolean readWrite Player getWebCamIsOn Player setWebCamIsOn:)
  		(slot useFrameSize 'Resize the player to match the camera''s frame size' 
  			Boolean readWrite Player getUseFrameSize Player setUseFrameSize:)
  		(slot lastFrame 'A player with the last frame' Player readOnly	Player getLastFrame unused unused)
+ 		(slot showFPS 'Whether to show the samera''s frames per second' Boolean readWrite Player getShowFPS Player setShowFPS:)
  		))
  )
  !

Item was changed:
  ----- Method: WebCamMorph class>>resolutionFor: (in category 'scripting') -----
  resolutionFor: aSymbol
+ 	(#(low medium high hd) includes: aSymbol) ifFalse: [^ 320 at 240].
- 	(#(#low #medium #high) includes: aSymbol) ifFalse: [^ 320 at 240].
  
+ 	^ {160 @ 120. 320 @ 240. 640 @ 480. 1280 @ 960} 
- 	^ {160 at 120. 320 at 240. 640 at 480} 
  			at: (WebCamResolution resolutions indexOf: aSymbol)
  !

Item was changed:
  ----- Method: WebCamMorph>>addCustomMenuItems:hand: (in category 'menu') -----
  addCustomMenuItems: aMenu hand: aHandMorph 
+ 
- 	| item |
  	super addCustomMenuItems: aMenu hand: aHandMorph.
- 	item := (camIsOn == true)
- 				ifTrue:	['turn camera off' translated]
- 				ifFalse: ['turn camera on' translated].
  	aMenu
+ 		addUpdating: #cameraToggleString action: #toggleCameraOnOff;
+ 		addLine;
+ 		add: 'resolution...' translated subMenu: ([:menu |
+ 			WebCamResolution resolutions do: [:res |
+ 				menu
+ 					add: (resolution == res ifTrue: ['<on>'] ifFalse: ['<off>']), res translated
+ 					selector: #setWebCamResolution:
+ 					argument: res].
+ 			menu] value: (aMenu class new defaultTarget: aMenu defaultTarget));
+ 		add: 'orientation...' translated subMenu: ([:menu |
+ 			WebCamOrientation orientations do: [:ori |
+ 				menu
+ 					add: (orientation == ori ifTrue: ['<on>'] ifFalse: ['<off>']), ori translated
+ 					selector: #setWebCamOrientation:
+ 					argument: ori].
+ 			menu] value: (aMenu class new defaultTarget: aMenu defaultTarget));
+ 		addUpdating: #frameSizeToggleString action: #toggleUseFrameSize;
+ 		addUpdating: #showFPSToggleString action: #toggleShowFPS;
+ 		yourself
+ !
- 		add: item translated
- 		target: self
- 		action: #toggleCameraOnOff.
- 	
- 	
- 
- 	
- 	!

Item was added:
+ ----- Method: WebCamMorph>>cameraToggleString (in category 'menu') -----
+ cameraToggleString
+ 
+ 	^ camIsOn
+ 		ifTrue: ['<on>', 'turn camera off' translated]
+ 		ifFalse: ['<off>', 'turn camera on' translated].
+ 	
+ 
+ 	
+ !

Item was added:
+ ----- Method: WebCamMorph>>decreaseCaptureDelay (in category 'accessing') -----
+ decreaseCaptureDelay
+ 
+ 	captureDelayMs := (captureDelayMs - 1) min: 200.!

Item was changed:
  ----- Method: WebCamMorph>>delete (in category 'submorphs-add/remove') -----
  delete
+ 	self class instanceCount > 1
+ 		ifFalse: [self off]
+ 		ifTrue: [
+ 			self stopStepping.
+ 			camIsOn := false].
- 	(self class instanceCount > 1) 
- 	ifFalse:[self off]
- 	ifTrue:[self stopStepping. camIsOn := false].
  	super delete.!

Item was added:
+ ----- Method: WebCamMorph>>drawCameraImageOn: (in category 'drawing') -----
+ drawCameraImageOn: aCanvas
+ 	| scale offset |
+ 	offset :=  0 @ 0.
+ 	scale := 1 @ 1.
+ 	bounds extent = displayForm extent
+ 		ifFalse: [scale := bounds extent  / displayForm extent].
+ 	orientation == #natural
+ 		ifTrue: [
+ 			scale := scale x negated @ scale y.
+ 			offset := bounds width @ 0].
+ 	1 @ 1 = scale
+ 		ifTrue: [aCanvas drawImage: displayForm at: bounds origin + offset]
+ 		ifFalse: [aCanvas
+ 			warpImage: displayForm
+ 			transform: (MatrixTransform2x3 withScale: scale)
+ 			at: bounds origin + offset].
+ !

Item was added:
+ ----- Method: WebCamMorph>>drawFPSOn: (in category 'drawing') -----
+ drawFPSOn: aCanvas
+ 	showFPS ifFalse: [^self].
+ 	aCanvas
+ 		drawString: 'FPS: ', fps asString
+ 		at: bounds bottomLeft + (5 @ -20)
+ 		font: Preferences windowTitleFont
+ 		color: Color white!

Item was changed:
  ----- Method: WebCamMorph>>drawOn: (in category 'drawing') -----
  drawOn: aCanvas 
+ 
  	useFrameSize ifTrue: [self extent: frameExtent].
+ 	self drawCameraImageOn: aCanvas.
+ 	self drawFPSOn: aCanvas.
+ 	self drawOverlayTextOn: aCanvas.
- 	aCanvas
- 		drawImage: (
- 			(self extent = displayForm extent) 
- 				ifTrue: [displayForm] 
- 				ifFalse: [displayForm scaledToSize: self extent]
- 		) at: bounds origin.
  !

Item was added:
+ ----- Method: WebCamMorph>>drawOverlayTextOn: (in category 'drawing') -----
+ drawOverlayTextOn: aCanvas
+ 	camIsOn ifTrue: [^self].
+ 	aCanvas
+ 		drawString: 'Camera is off' translated
+ 		at: bounds origin + (5 @ 2)
+ 		font: Preferences windowTitleFont
+ 		color: Color white.!

Item was added:
+ ----- Method: WebCamMorph>>frameSizeToggleString (in category 'menu') -----
+ frameSizeToggleString
+ 
+ 	^ (useFrameSize ifTrue: ['<on>'] ifFalse: ['<off>']), 'use frame size' translated
+ 
+ 	
+ !

Item was added:
+ ----- Method: WebCamMorph>>getShowFPS (in category 'e-toy - settings') -----
+ getShowFPS
+ 	^ showFPS
+ !

Item was added:
+ ----- Method: WebCamMorph>>increaseCaptureDelay (in category 'accessing') -----
+ increaseCaptureDelay
+ 
+ 	captureDelayMs := (captureDelayMs + 1) max: 10.!

Item was changed:
  ----- Method: WebCamMorph>>initialize (in category 'initialization') -----
  initialize
  	super initialize.
  	camNum := 1.
  	camIsOn := false.
+ 	showFPS := false.
+ 	captureDelayMs := 16. "stepTime"	
+ 	fps := 60. "guess."
+ 	lastDisplayTime := 0.
+ 	framesSinceLastDisplay := 0.
- 	captureDelayMs := 0. "stepTime"	
  	useFrameSize := false.
+ 	resolution := #medium.
+ 	orientation := #natural.
- 	resolution := #'medium'.
  	frameExtent := self class resolutionFor: resolution.
+ 	self initializeDisplayForm.
- 	displayForm := Form extent: frameExtent depth:32.
  	self extent: frameExtent.
  	self on.
  
  	!

Item was added:
+ ----- Method: WebCamMorph>>initializeDisplayForm (in category 'initialization') -----
+ initializeDisplayForm
+ 	| cameraExtent formExtent |
+ 
+ 	cameraExtent := CameraInterface frameExtent: camNum.
+ 	cameraExtent isZero 
+ 		ifTrue: [formExtent := frameExtent]
+ 		ifFalse: [ | camRatio frameRatio |
+ 			formExtent := cameraExtent.
+ 			camRatio := cameraExtent x / cameraExtent y.
+ 			frameRatio := frameExtent x / frameExtent y.
+ 			camRatio ~= frameRatio ifTrue: [frameExtent := frameExtent x @ (frameExtent x * camRatio reciprocal)]].
+ 	displayForm := Form extent: formExtent depth: 32.
+ 	self extent: frameExtent.
+ !

Item was added:
+ ----- Method: WebCamMorph>>knownName (in category 'testing') -----
+ knownName
+ 
+ 	^ CameraInterface cameraName: camNum	!

Item was changed:
  ----- Method: WebCamMorph>>nextFrame (in category 'stepping and presenter') -----
  nextFrame
  	
+ 	| frameCount |
+ 	frameCount := CameraInterface getFrameForCamera: camNum into: displayForm bits.
+ 	frameCount = 0 ifTrue: [self increaseCaptureDelay].
+ 	frameCount > 2 ifTrue: [self decreaseCaptureDelay].
+ 	framesSinceLastDisplay := framesSinceLastDisplay + frameCount!
- 	CameraInterface getFrameForCamera: camNum into: displayForm bits.
- 	!

Item was changed:
  ----- Method: WebCamMorph>>on (in category 'accessing') -----
  on
  	
  	(CameraInterface cameraIsOpen: camNum)
  		ifTrue: [ ^camIsOn := true.].
+ 	(CameraInterface openCamera: camNum width: frameExtent x height: frameExtent y)
- 	(CameraInterface
- 		openCamera: camNum
- 		width: frameExtent x
- 		height: frameExtent y)
  		ifNil: [^false].
+ 	CameraInterface waitForCameraStart: camNum.
+ 	self initializeDisplayForm.
+ 	self extent: frameExtent.
- 	(Delay forSeconds: 2) wait.
- 	displayForm := Form extent: frameExtent depth:32.
  	camIsOn := true.
  	self startStepping.
  	!

Item was added:
+ ----- Method: WebCamMorph>>setShowFPS: (in category 'e-toy - settings') -----
+ setShowFPS: aBoolean
+ 	showFPS := aBoolean
+ !

Item was added:
+ ----- Method: WebCamMorph>>setWebCamOrientation: (in category 'e-toy - settings') -----
+ setWebCamOrientation: aSymbol
+ 
+ 	((WebCamOrientation orientations) includes: aSymbol) ifFalse: [^ self].
+ 	orientation := aSymbol.
+ 			
+ 
+ !

Item was added:
+ ----- Method: WebCamMorph>>showFPSToggleString (in category 'menu') -----
+ showFPSToggleString
+ 
+ 	^ (showFPS ifTrue: ['<on>'] ifFalse: ['<off>']), 'show fps' translated
+ 
+ 	
+ !

Item was added:
+ ----- Method: WebCamMorph>>toggleShowFPS (in category 'menu') -----
+ toggleShowFPS
+ 
+ 	showFPS := showFPS not.
+ !

Item was added:
+ ----- Method: WebCamMorph>>toggleUseFrameSize (in category 'menu') -----
+ toggleUseFrameSize
+ 
+ 	useFrameSize := useFrameSize not.
+ !

Item was changed:
  ----- Method: WebCamMorph>>updateDisplay (in category 'stepping and presenter') -----
  updateDisplay
+ 	camIsOn ifTrue:[self nextFrame].
+ 	self updateFPS.
+ 	self changed.!
- 	camIsOn
- 		ifFalse: [displayForm getCanvas
- 				drawString: 'Camera is off' translated
- 				at: 5 @ 2
- 				font: Preferences windowTitleFont
- 				color: Color white.
- 			]
- 		ifTrue:[self nextFrame].
-      self changed.!

Item was added:
+ ----- Method: WebCamMorph>>updateFPS (in category 'stepping and presenter') -----
+ updateFPS
+ 
+ 	| now mSecs |
+ 	now := Time millisecondClockValue.
+ 	mSecs := now - lastDisplayTime.
+ 	(mSecs > 500 or: [mSecs < 0 "clock wrap-around"])
+ 		ifTrue: [
+ 			fps := (framesSinceLastDisplay * 1000) // mSecs.
+ 			lastDisplayTime := now.
+ 			framesSinceLastDisplay := 0].!

Item was added:
+ SymbolListType subclass: #WebCamOrientation
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Squeakland-MorphicExtras-WebCam'!

Item was added:
+ ----- Method: WebCamOrientation class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	Vocabulary initialize.!

Item was added:
+ ----- Method: WebCamOrientation class>>orientations (in category 'as yet unclassified') -----
+ orientations
+ 	^ #( native natural )!

Item was added:
+ ----- Method: WebCamOrientation>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	super initialize.
+ 	self vocabularyName: #WebCamOrientation.
+ 	
+ 	self symbols: self class orientations.!

Item was added:
+ ----- Method: WebCamOrientation>>representsAType (in category 'as yet unclassified') -----
+ representsAType
+ 	^true!

Item was changed:
  ----- Method: WebCamResolution class>>initialize (in category 'as yet unclassified') -----
  initialize
+ 	Vocabulary initialize.!
- 	Vocabulary initialize!

Item was changed:
  ----- Method: WebCamResolution class>>resolutions (in category 'as yet unclassified') -----
  resolutions
+ 	^ #(#'low' #'medium' #'high' #'hd')
- 	^ #(#'low' #'medium' #'high')
  !



More information about the Squeak-dev mailing list