[Goodie] Anaglyph Viewing Morph

Rick ret at deltanet.com
Wed Apr 26 20:49:09 UTC 2000


Hello All,

Here is my first Goodie for Squeak...   An Anaglyph Viewing Morph...

Yep, get out those goofy Red-n-Blue 3D glasses...
Because now you can read a JPS format Stereo 3D image file and display various Anaglyph style images.  Also read left and right eye JPG files to display various Anaglyphs.

You can find many JPS format Stereo 3D image file on the net...

Have fun!!!

-Rick-

"We keep moving forward, opening new doors and doing new things, because we're curious."
- Walt Disney -


-------------- next part --------------
'From Squeak2.8alpha of 12 January 2000 [latest update: #2040] on 26 April 2000 at 1:38:18 pm'!
ImageMorph subclass: #AnaglyphViewMorph
	instanceVariableNames: 'jpsImage leftEyeImage rightEyeImage anaglyphImage showing alignmentUpDown alignmentLeftRight isSwapped myScale mySepiaColor '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Demo'!
!AnaglyphViewMorph commentStamp: '<historical>' prior: 0!
Hello...

I am an Anaglyph Viewing Morph.  I was written by Rick Thomas.

Yep, get out those goofy Red-n-Blue 3D glasses...
Because I can read a JPS format Stereo 3D image file and display various Anaglyph style images.
I can also read left and right eye JPG files to display various Anaglyphs.
You can find many JPS format Stereo 3D image file on the net...

My Read File commands include:
	A JPS File
	A Left Eye View File
	A Right Eye View File

My Show me commands include:
	As a Red-On-Left Anaglyph
	As a Blue-On-Left Anaglyph
	As Pure Red-On-Left Anaglyph
	As Pure Blue-On-Left Anaglyph
	As a JPS
	As a Left Eye View
	As a Right Eye View
	Swap Left & Right Eye Views

My various Color me commands include:
	As Color
	As GrayScale
	As SepiaTone
	As Blu-o-Tone
	As Pick-Yo-Tone

My up, down, left and right arrow keys will fine-tune the alignment and separation (3D effect).

How to use me...

1)  Read a JPS file (or Read a Left Eye View File, then Read a Right Eye View File).
2)  Show as a Red-On-Left Anaglyph (or pick another style).
3)  Put on a pair of those goofy red and blue glasses (make sure the red filter on over the left eye).
4)  Use up, down, left and right arrow keys to fine-tune the alignment and separation (3D effect).
5)  Try viewing as GrayScale or as Blu-o-Tone.

Happy Viewing...

PS - I hope someone will take a few of my routines to add a "poor mans 3D VR" viewing system for Balloon3D and for Wonderlands!!!!!!

PPSS - Here is the design...  Create two cameras, position them side by side, 2 and 1/2 inches apart (left/right), point them at the same point in a scene, render each camera for a left eye and right eye view, pipe into anaglyph routine, display.!


!AnaglyphViewMorph methodsFor: 'file In/Out' stamp: 'ret 4/26/2000 12:01'!
readJPSFromFile

	| fileName |

	fileName _ FillInTheBlank
		request: 'Enter the JPS image file name'
		initialAnswer: 'fileName.jps'.
	fileName isEmpty ifTrue: [^ self].

	jpsImage _ ImageReadWriter formFromFileNamed: fileName.
	isSwapped _ false.
	showing _ 'InputJPS'.
	self makeBothEyesFromJPS! !

!AnaglyphViewMorph methodsFor: 'file In/Out' stamp: 'ret 4/25/2000 16:46'!
readLeftEyeImageFile
	| fileName |
	fileName _ FillInTheBlank
		request: 'Enter the Left Eye Image file name'
		initialAnswer: 'fileName.jpg'.
	fileName isEmpty ifTrue: [^ self].

	leftEyeImage _ ImageReadWriter formFromFileNamed: fileName.
	isSwapped _ false.
	self resetUpDownLeftRight.
	showing _ 'LeftEyeView'.
	self updateImageBuffers! !

!AnaglyphViewMorph methodsFor: 'file In/Out' stamp: 'ret 4/25/2000 16:47'!
readRightEyeImageFile

	| fileName |

	fileName _ FillInTheBlank
		request: 'Enter the Right Eye Image file name'
		initialAnswer: 'fileName.jpg'.
	fileName isEmpty ifTrue: [^ self].

	rightEyeImage _ ImageReadWriter formFromFileNamed: fileName.
	isSwapped _ false.
	self resetUpDownLeftRight.
	showing _ 'RightEyeView'.
	self updateImageBuffers! !


!AnaglyphViewMorph methodsFor: 'menu commands' stamp: 'ret 4/26/2000 11:17'!
addCustomMenuItems: aCustomMenu hand: aHandMorph
	"Add my custom menu options..."

	| readSubMenu showSubMenu |

	aCustomMenu addLine.
	readSubMenu _ MenuMorph new defaultTarget: self.
	readSubMenu add: 'A JPS File' action: #readJPSFromFile.
	readSubMenu add: 'A Left Eye View File' action: #readLeftEyeImageFile.
	readSubMenu add: 'A Right Eye View File' action: #readRightEyeImageFile.
	aCustomMenu add: 'Read File...' subMenu: readSubMenu.

	aCustomMenu addLine.
	showSubMenu _ MenuMorph new defaultTarget: self.
	showSubMenu add: 'As a Red-On-Left Anaglyph' action: #displayRedOnLeftAnaglyph.
	showSubMenu add: 'As a Blue-On-Left Anaglyph' action: #displayBlueOnLeftAnaglyph.
	showSubMenu add: 'As Pure Red-On-Left Anaglyph' action: #displayRedOnLeftPureAnaglyph.
	showSubMenu add: 'As Pure Blue-On-Left Anaglyph' action: #displayBlueOnLeftPureAnaglyph.
	showSubMenu add: 'As a JPS' action: #displayInputJPS.
	showSubMenu add: 'As a Left Eye View' action: #displayLeftEyeView.
	showSubMenu add: 'As a Right Eye View' action: #displayRightEyeView.
	showSubMenu add: 'Swap Left & Right Eye Views' action: #swapLeftAndRightEyeBufs.
	aCustomMenu add: 'Show me...' subMenu: showSubMenu.

	aCustomMenu addLine.
	readSubMenu _ MenuMorph new defaultTarget: self.
	readSubMenu add: 'As Color' action: #makeColorImage.
	readSubMenu add: 'As GrayScale' action: #displayGrayScaleImage.
	readSubMenu add: 'As SepiaTone' action: #displaySepiaToneImage.
	readSubMenu add: 'As Blu-o-Tone' action: #displayBluoToneImage.
	readSubMenu add: 'As Pick-Yo-Tone' action: #displayPickToneImage.
	aCustomMenu add: 'Color me...' subMenu: readSubMenu.
! !

!AnaglyphViewMorph methodsFor: 'menu commands' stamp: 'ret 4/26/2000 11:54'!
swapLeftAndRightEyeBufs
	"I swap the left and right image buffers."

	rightEyeImage become: leftEyeImage.

	"toggle the swap flag..."
	isSwapped
		ifTrue: [isSwapped _ false]
		ifFalse: [isSwapped _ true].
	self updateImageBuffers! !


!AnaglyphViewMorph methodsFor: 'other' stamp: 'ret 4/25/2000 16:46'!
resetUpDownLeftRight

	self alignmentUpDown: 0.
	self alignmentLeftRight: 0.! !

!AnaglyphViewMorph methodsFor: 'other' stamp: 'ret 4/26/2000 11:12'!
rgbADD
	"Answer the integer denoting BitBlt's rgbADD combination rule."

	^20! !

!AnaglyphViewMorph methodsFor: 'other' stamp: 'ret 4/26/2000 11:12'!
rgbSUB
	"Answer the integer denoting BitBlt's rgbSUB combination rule."

	^21! !


!AnaglyphViewMorph methodsFor: 'accessing' stamp: 'ret 4/26/2000 11:08'!
alignmentLeftRight: anInteger

	alignmentLeftRight _ anInteger.! !

!AnaglyphViewMorph methodsFor: 'accessing' stamp: 'ret 4/25/2000 11:55'!
alignmentUpDown

	^ alignmentUpDown
! !

!AnaglyphViewMorph methodsFor: 'accessing' stamp: 'ret 4/26/2000 11:08'!
alignmentUpDown: anInteger

	alignmentUpDown _ anInteger.! !

!AnaglyphViewMorph methodsFor: 'accessing' stamp: 'ret 4/25/2000 11:54'!
leftEyeImage

	^ leftEyeImage
! !

!AnaglyphViewMorph methodsFor: 'accessing' stamp: 'ret 4/25/2000 11:54'!
leftEyeImage: anImage

	leftEyeImage _ anImage.! !

!AnaglyphViewMorph methodsFor: 'accessing' stamp: 'ret 4/25/2000 15:53'!
magnifyIt

	myScale < 2.00
	ifTrue: [myScale _ myScale + 0.25].
	self updateImageBuffers.
! !

!AnaglyphViewMorph methodsFor: 'accessing' stamp: 'ret 4/25/2000 11:55'!
rightEyeImage

	^ rightEyeImage
! !

!AnaglyphViewMorph methodsFor: 'accessing' stamp: 'ret 4/25/2000 11:54'!
rightEyeImage: anImage

	rightEyeImage _ anImage.! !

!AnaglyphViewMorph methodsFor: 'accessing' stamp: 'ret 4/26/2000 11:07'!
showing: aString

	showing _ aString.! !


!AnaglyphViewMorph methodsFor: 'event handling' stamp: 'ret 4/26/2000 11:12'!
handlesMouseOver: evt

	^ true
! !

!AnaglyphViewMorph methodsFor: 'event handling' stamp: 'ret 4/26/2000 11:12'!
keyStroke: evt 

	| charValue |

	charValue _ evt keyCharacter asciiValue.
	charValue = 28 ifTrue: [^ self moveLeft].
	charValue = 29 ifTrue: [^ self moveRight].
	charValue = 30 ifTrue: [^ self moveUp].
	charValue = 31 ifTrue: [^ self moveDown]
! !

!AnaglyphViewMorph methodsFor: 'event handling' stamp: 'ret 4/26/2000 11:13'!
mouseEnter: evt

        evt hand newKeyboardFocus: self
! !


!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 17:00'!
displayBlueOnLeftAnaglyph

	self updateImageBuffersWith: 'BlueOnLeftAnaglyph'.! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 17:00'!
displayBlueOnLeftPureAnaglyph

	self updateImageBuffersWith: 'BlueOnLeftPureAnaglyph'.! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/26/2000 11:18'!
displayBluoToneImage
	"I make the images a blue tinted Tone..."

	| myBlue |

	myBlue _ (Color r: 0.23 g: 0.23 b: 0.54).
	myBlue _ myBlue twiceLighter.

	self leftEyeImage: (self makeSepiaTone: self leftEyeImage aTone: myBlue steps: 128).
	self rightEyeImage: (self makeSepiaTone: self rightEyeImage aTone: myBlue steps: 128).
	self updateImageBuffers.! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 16:17'!
displayGrayScaleImage
	"I return GrayScale image..."

	self leftEyeImage: (self leftEyeImage asGrayScale).
	self leftEyeImage: (self leftEyeImage asFormOfDepth: 32).

	self rightEyeImage: (self rightEyeImage asGrayScale).
	self rightEyeImage: (self rightEyeImage asFormOfDepth: 32).

	self updateImageBuffers.! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 16:59'!
displayInputJPS

	self updateImageBuffersWith: 'InputJPS'.
! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 16:58'!
displayLeftEyeView

	self updateImageBuffersWith: 'LeftEyeView'.! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/26/2000 11:19'!
displayPickToneImage
	"I make the images Your color pick tinted Tone..."

	mySepiaColor _ Color fromUser.

	self leftEyeImage: (self makeSepiaTone: self leftEyeImage aTone: mySepiaColor steps: 128).
	self rightEyeImage: (self makeSepiaTone: self rightEyeImage aTone: mySepiaColor steps: 128).
	self updateImageBuffers.! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 16:57'!
displayRedOnLeftAnaglyph

	self updateImageBuffersWith: 'RedOnLeftAnaglyph'.
! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 16:57'!
displayRedOnLeftPureAnaglyph

	self updateImageBuffersWith: 'RedOnLeftPureAnaglyph'.
! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 16:56'!
displayRightEyeView

	self updateImageBuffersWith: 'RightEyeView'.! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/26/2000 11:20'!
displaySepiaToneImage
	"I make the images a brown tinted tone..."

	| myMix myMagenta myYellow |

	myMagenta _ (Color r: 0.65 g: 0.36 b:0.51).
	myYellow _ (Color r: 1.0 g: 0.92 b: 0.0).
	myMix _ myMagenta mixed: 0.55 with: myYellow.

	self leftEyeImage: (self makeSepiaTone: self leftEyeImage aTone: myMix steps: 128).
	self rightEyeImage: (self makeSepiaTone: self rightEyeImage aTone: myMix steps: 128).
	self updateImageBuffers.! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 16:07'!
updateImageBuffers
	"I call whoever is showing to refresh any changes..."

	showing = 'RedOnLeftAnaglyph'
		ifTrue: 
			[self makeRedEyeLeftAnaglyph.
			self image: anaglyphImage.
			^ self updateScaleAndShow].
	showing = 'BlueOnLeftAnaglyph'
		ifTrue: 
			[self makeBlueEyeLeftAnaglyph.
			self image: anaglyphImage.
			^ self updateScaleAndShow].
	showing = 'RedOnLeftPureAnaglyph'
		ifTrue: 
			[self makeRedOnLeftPureAnaglyph.
			self image: anaglyphImage.
			^ self updateScaleAndShow].
	showing = 'BlueOnLeftPureAnaglyph'
		ifTrue: 
			[self makeBlueOnLeftPureAnaglyph.
			self image: anaglyphImage.
			^ self updateScaleAndShow].
	showing = 'InputJPS'
		ifTrue: 
			[self image: jpsImage.
			^ self updateScaleAndShow].
	showing = 'LeftEyeView'
		ifTrue: 
			[self image: leftEyeImage.
			^ self updateScaleAndShow].
	showing = 'RightEyeView'
		ifTrue: 
			[self image: rightEyeImage.
			^ self updateScaleAndShow]! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/25/2000 16:07'!
updateImageBuffersWith: whosShowing 
	"I call whoever is showing to refresh any changes..."
	self showing: whosShowing.

	whosShowing = 'RedOnLeftAnaglyph'
		ifTrue: 
			[self makeRedEyeLeftAnaglyph.
			self image: anaglyphImage.
			^ self updateScaleAndShow].
	whosShowing = 'BlueOnLeftAnaglyph'
		ifTrue: 
			[self makeBlueEyeLeftAnaglyph.
			self image: anaglyphImage.
			^ self updateScaleAndShow].
	whosShowing = 'RedOnLeftPureAnaglyph'
		ifTrue: 
			[self makeRedOnLeftPureAnaglyph.
			self image: anaglyphImage.
			^ self updateScaleAndShow].
	whosShowing = 'BlueOnLeftPureAnaglyph'
		ifTrue: 
			[self makeBlueOnLeftPureAnaglyph.
			self image: anaglyphImage.
			^ self updateScaleAndShow].
	whosShowing = 'InputJPS'
		ifTrue: 
			[self image: jpsImage.
			^ self updateScaleAndShow].
	whosShowing = 'LeftEyeView'
		ifTrue: 
			[self image: leftEyeImage.
			^ self updateScaleAndShow].
	whosShowing = 'RightEyeView'
		ifTrue: 
			[self image: rightEyeImage.
			^ self updateScaleAndShow]! !

!AnaglyphViewMorph methodsFor: 'displaying' stamp: 'ret 4/26/2000 11:52'!
updateScaleAndShow

	myScale = 1.0 ifFalse: [self image: (image
				magnify: image boundingBox
				by: myScale @ myScale
				smoothing: 1)]! !


!AnaglyphViewMorph methodsFor: 'initialization' stamp: 'ret 4/25/2000 14:28'!
initialize

	super initialize.
	myScale _ 1.00.
	isSwapped _ false.
	showing _ nil.

	self image: DefaultForm.! !


!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/26/2000 11:24'!
makeBlueEyeLeftAnaglyph

	| aBlitter |

	anaglyphImage _ leftEyeImage deepCopy.

	"Remove the red channel from the left eye image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: leftEyeImage
				fillColor: Color red
				combinationRule: self rgbSUB
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: leftEyeImage extent
				clipRect: leftEyeImage boundingBox.
	aBlitter copyBits.

	"Now add the red channel from the right side image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: rightEyeImage
				fillColor: Color red
				combinationRule: self rgbADD
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: rightEyeImage extent
				clipRect: rightEyeImage boundingBox.
	aBlitter copyBits.! !

!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/25/2000 16:09'!
makeBlueOnLeftPureAnaglyph

	| aBlitter |

	anaglyphImage _ leftEyeImage deepCopy.

	"Remove the red channel from the left eye image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: leftEyeImage
				fillColor: Color red
				combinationRule: self rgbSUB
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: leftEyeImage extent
				clipRect: leftEyeImage boundingBox.
	aBlitter copyBits.

	"Remove the green channel from the left eye image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: anaglyphImage
				fillColor: Color green
				combinationRule: self rgbSUB
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: anaglyphImage extent
				clipRect: anaglyphImage boundingBox.
	aBlitter copyBits.

	"Now add the red channel from the right side image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: rightEyeImage
				fillColor: Color red
				combinationRule: self rgbADD
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: rightEyeImage extent
				clipRect: rightEyeImage boundingBox.
	aBlitter copyBits.! !

!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/26/2000 13:16'!
makeBothEyesFromJPS
	"Make both the Left and Right Eyes from a JPS..."

	self resetUpDownLeftRight.

	"Remember that a JPS image is formatted as rightEyeImage is on the left 
	hand side.  So we calculate the right side jpsImage rectangle"
	leftEyeImage _ jpsImage copy: (jpsImage width // 2 @ 0 extent: jpsImage width // 2 @ jpsImage height).

	"Now calculate the left side jpsImage rectangle"
	rightEyeImage _ jpsImage copy: (0 @ 0 extent: jpsImage width // 2 @ jpsImage height).

	self updateImageBuffers! !

!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/26/2000 12:00'!
makeColorImage

	self makeBothEyesFromJPS! !

!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/25/2000 17:45'!
makeRedEyeLeftAnaglyph

	| aBlitter |

	anaglyphImage _ rightEyeImage deepCopy.

	"Remove the red channel from the right eye image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: rightEyeImage
				fillColor: Color red
				combinationRule: self rgbSUB
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: rightEyeImage extent
				clipRect: rightEyeImage boundingBox.
	aBlitter copyBits.

	"Now add the red channel from the left eye image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: leftEyeImage
				fillColor: Color red
				combinationRule: self rgbADD
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: leftEyeImage extent
				clipRect: leftEyeImage boundingBox.
	aBlitter copyBits.! !

!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/25/2000 16:03'!
makeRedOnLeftPureAnaglyph

	| aBlitter |

	anaglyphImage _ rightEyeImage deepCopy.

	"Remove the red channel from the right eye image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: rightEyeImage
				fillColor: Color red
				combinationRule: self rgbSUB
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: rightEyeImage extent
				clipRect: rightEyeImage boundingBox.
	aBlitter copyBits.

	"Remove the green channel from the right eye image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: anaglyphImage
				fillColor: Color green
				combinationRule: self rgbSUB
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: anaglyphImage extent
				clipRect: anaglyphImage boundingBox.
	aBlitter copyBits.

	"Now add the red channel from the left eye image."
	aBlitter _ BitBlt
				destForm: anaglyphImage
				sourceForm: leftEyeImage
				fillColor: Color red
				combinationRule: self rgbADD
				destOrigin: 0 @ 0
				sourceOrigin: 0 @ 0
				extent: leftEyeImage extent
				clipRect: leftEyeImage boundingBox.
	aBlitter copyBits.! !

!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/26/2000 11:31'!
makeSepiaTone: anImage aTone: aColor steps: aNumber
	"I return a SepiaTone image..."

	| myImage myBlackToTone myToneToWhite mySepiaToneMap |

	"Make my Black to Tone (in steps) and then to White array..."
	myBlackToTone _ Color black mix: aColor shades: aNumber.
	myToneToWhite _ aColor mix: Color white shades: (256 - aNumber).

	mySepiaToneMap _ Array new: 256.
	mySepiaToneMap replaceFrom: 1 to: aNumber with: myBlackToTone startingAt: 1.
	mySepiaToneMap replaceFrom: (aNumber + 1) to: 256 with: myToneToWhite startingAt: 1.

"	Color showColors: mySepiaToneMap. <<<=== Used to debug and see the color swatch"

	"Hack anImage down to grayscale. It returns a 8 bit color form..."
	myImage _ anImage asGrayScale.

	"Swap in my new color map..."
	myImage colors: mySepiaToneMap.

	"Make myImage 32 bits deep again..."
	myImage _ myImage asFormOfDepth: 32.
	^ myImage! !

!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/25/2000 15:22'!
reSize: anImage to: aNumber
	"I resize an image to fit within the constraints of width @ height..."

	anImage height > anImage width
	ifTrue:[^self reSize: anImage toHeight: aNumber]
	ifFalse:[^self reSize: anImage toWidth: aNumber].! !

!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/25/2000 14:49'!
reSize: anImage toHeight: aNumber
	"I resize an image to fit within the constraints of width @ height..."

	| scaleY scaleX myHeight |

	myHeight _ aNumber.

	scaleY _ myHeight / anImage height. "Keep the height invariant..."
	scaleX _ anImage width * scaleY <= self width
				ifTrue: [scaleY] "the usual case; same scale factor, to preserve aspect ratio"
				ifFalse: [myHeight / anImage width].

	^(anImage magnify: anImage boundingBox by: scaleX @ scaleY smoothing: 2).! !

!AnaglyphViewMorph methodsFor: 'making' stamp: 'ret 4/25/2000 15:18'!
reSize: anImage toWidth: aNumber
	"I resize an image to fit within the constraints of width @ height..."

	| scaleY scaleX myWidth |

	myWidth _ aNumber.

	scaleX _ myWidth / anImage width. "Keep the width invariant..."
	scaleY _ anImage height * scaleX <= self height
				ifTrue: [scaleX] "the usual case; same scale factor, to preserve aspect ratio"
				ifFalse: [myWidth / anImage height].

	^(anImage magnify: anImage boundingBox by: scaleX @ scaleY smoothing: 2).! !


!AnaglyphViewMorph methodsFor: 'moving' stamp: 'ret 4/26/2000 11:37'!
moveDown
	"move the left eye image up and the right eye image down for   
	seperation and alignment."

	| aBlitter |

	alignmentUpDown _ alignmentUpDown - 1.
	aBlitter _ alignmentUpDown odd
				ifTrue: [BitBlt
						destForm: leftEyeImage
						sourceForm: leftEyeImage
						fillColor: nil
						combinationRule: Form paint
						destOrigin: 0 @ -1
						sourceOrigin: 0 @ 0
						extent: leftEyeImage extent
						clipRect: leftEyeImage boundingBox]
				ifFalse: [BitBlt
						destForm: rightEyeImage
						sourceForm: rightEyeImage
						fillColor: nil
						combinationRule: Form paint
						destOrigin: 0 @ 1
						sourceOrigin: 0 @ 0
						extent: rightEyeImage extent
						clipRect: rightEyeImage boundingBox].
	aBlitter copyBits.
	self updateImageBuffers! !

!AnaglyphViewMorph methodsFor: 'moving' stamp: 'ret 4/26/2000 11:37'!
moveLeft
	"move the images left/right for seperation and alignment."

	| aBlitter |

	alignmentLeftRight _ alignmentLeftRight - 1.
	aBlitter _ alignmentLeftRight even
				ifTrue: [BitBlt
						destForm: leftEyeImage
						sourceForm: leftEyeImage
						fillColor: nil
						combinationRule: Form paint
						destOrigin: 1 @ 0
						sourceOrigin: 0 @ 0
						extent: leftEyeImage extent
						clipRect: leftEyeImage boundingBox]
				ifFalse: [BitBlt
						destForm: rightEyeImage
						sourceForm: rightEyeImage
						fillColor: nil
						combinationRule: Form paint
						destOrigin: -1 @ 0
						sourceOrigin: 0 @ 0
						extent: rightEyeImage extent
						clipRect: rightEyeImage boundingBox].
	aBlitter copyBits.
	self updateImageBuffers! !

!AnaglyphViewMorph methodsFor: 'moving' stamp: 'ret 4/26/2000 11:37'!
moveRight
	"move the images left/right for seperation and alignment."

	| aBlitter |

	alignmentLeftRight _ alignmentLeftRight + 1.
	aBlitter _ alignmentLeftRight odd
				ifTrue: [BitBlt
						destForm: leftEyeImage
						sourceForm: leftEyeImage
						fillColor: nil
						combinationRule: Form paint
						destOrigin: -1 @ 0
						sourceOrigin: 0 @ 0
						extent: leftEyeImage extent
						clipRect: leftEyeImage boundingBox]
				ifFalse: [BitBlt
						destForm: rightEyeImage
						sourceForm: rightEyeImage
						fillColor: nil
						combinationRule: Form paint
						destOrigin: 1 @ 0
						sourceOrigin: 0 @ 0
						extent: rightEyeImage extent
						clipRect: rightEyeImage boundingBox].
	aBlitter copyBits.
	self updateImageBuffers! !

!AnaglyphViewMorph methodsFor: 'moving' stamp: 'ret 4/26/2000 11:37'!
moveUp
	"move the left eye image up and the right eye image down for    
	seperation and alignment."

	| aBlitter |

	alignmentUpDown _ alignmentUpDown + 1.
	aBlitter _ alignmentUpDown even
				ifTrue: [BitBlt
						destForm: leftEyeImage
						sourceForm: leftEyeImage
						fillColor: nil
						combinationRule: Form paint
						destOrigin: 0 @ 1
						sourceOrigin: 0 @ 0
						extent: leftEyeImage extent
						clipRect: leftEyeImage boundingBox]
				ifFalse: [BitBlt
						destForm: rightEyeImage
						sourceForm: rightEyeImage
						fillColor: nil
						combinationRule: Form paint
						destOrigin: 0 @ -1
						sourceOrigin: 0 @ 0
						extent: rightEyeImage extent
						clipRect: rightEyeImage boundingBox].
	aBlitter copyBits.
	self updateImageBuffers! !




More information about the Squeak-dev mailing list