[GOODIE] FishEyeMorph

ohshima at is.titech.ac.jp ohshima at is.titech.ac.jp
Wed Dec 15 17:35:08 UTC 1999


----Next_Part(Thu_Dec_16_02:34:57_1999)--
Content-Type: Text/Plain; charset=us-ascii
Content-Transfer-Encoding: 7bit


  Hi,

  Uh, I'm still wasting my time, (and probably yours also if
you're reading), but I happend to write a demo of displaying
"fish eye view".

  The attached is the code of FishEyeMorph, which is a
subclass of MagnifierMorph.  You can test it by choosing
"new morph..." - > "Demo" -> "FishEyeMorph" from the menu.

  Have fun.

  -- Yoshiki

P.S.
  I think I've got a bit experience about what WarpBlt is
and what it is not.  The version I attached here is one of
the simplest "distorted view" argorithm, which transforms
the square patches on the original Form into rectangles on
the result.  In this case, WarpBlt works just fine.

  However, there are many other classes of the distorted
views, including "polar fish eye", "polyfocal (close to the
'science' screen saver of Windows)", etc.  Even I could
include "Perspective Wall" among them.

  In order to implement those views, it must be able to
transform square Forms (or rectangle, more generally) onto
arbitrary quadrilaterals.  The limitation of WarpBlt is it
cannot perform such a kind of transformation. (At least my
mathematics ability doesn't let me to do so).

  I think such graphics primitive is very handy and more
general than WarpBlt.

  By the way, if I want to implement the approximation of
those transformation by using WarpBlt, does anyone have idea
how I can figure out the sourceQuad?

  Here is an example: there is a Form whose bounding box is
(0 at 0 corner: 10 at 10), and I'd like to transform it onto a
quad specified as "{0 at 0. 2 at 12. 7 at 8. 16 at -6}".  It's ok the
edges are distorted (inward) by WarpBlt but I want the
original corners to be transformed onto the corners of the
resulting quad.

#  I think we can implement the Perspective Wall by simply
# building the wall in Wonderland.  But this is another
# story...

----Next_Part(Thu_Dec_16_02:34:57_1999)--
Content-Type: Text/Plain; charset=us-ascii
Content-Transfer-Encoding: quoted-printable


'From Squeak2.7alpha of 20 November 1999 [latest update: #1698] on 15 De=
cember 1999 at 10:26:28 pm'!=0DMagnifierMorph subclass: #FishEyeMorph=0D=
	instanceVariableNames: 'arrayX arrayY grid form clipRects toRects d '=0D=
	classVariableNames: ''=0D	poolDictionaries: ''=0D	category: 'Morphic-De=
mo'!=0D=0D!FishEyeMorph methodsFor: 'private' stamp: 'yo 12/15/1999 20:5=
1'!=0DmagnifiedForm=0D	| warp step tx ty srcRect exclusion fromForm |=0D=
=0D	step _ self extent x // grid.=0D	lastPos _ self sourcePoint.=0D	"sel=
f halt."=0D	srcRect _ (lastPos - (self extent // 2 )) extent: self exten=
t.=0D	((srcRect intersects: self bounds) and: [ RecursionLock =3D=3D nil=
 ])=0D		ifTrue: [RecursionLock _ self.=0D				self isRound=0D					ifTrue:=
 [exclusion _ owner]=0D					ifFalse: [exclusion _ self].=0D				fromForm =
_ self world patchAt: srcRect without: exclusion andNothingAbove: false.=
=0D				RecursionLock _ nil]=0D		ifFalse: ["cheaper method if the source =
is not occluded"=0D				fromForm _ Display copy: srcRect].=0D=0D	0 to: gr=
id - 1 do: [:j |=0D		0 to: grid - 1 do: [:i |=0D			"(i =3D 10 and: [j =3D=
 10]) ifTrue: [self halt]."=0D			"rect _ (((arrayX at: (j+1)) at: (i+1))=
@((arrayY at: (j+1)) at: (i+1)))=0D						corner: ((arrayX at: (j+2)) at:=
 (i+2))@((arrayY at: (j+2)) at: (j+2))."=0D			warp _  (WarpBlt toForm: f=
orm)=0D				clipRect: ((clipRects at: j+1) at: i+1);=0D				sourceForm: fr=
omForm;=0D				colorMap: nil;=0D				cellSize: 2;=0D				combinationRule: F=
orm over.=0D				tx _ (i+1)*step.=0D				ty _ (j+1)*step.=0D			warp=0D				=
copyQuad: {=0D					(tx)@(ty).=0D					(tx)@(ty+step).=0D					(tx+step)@(t=
y+step).=0D					(tx+step)@(ty)=0D				} =0D				toRect: ((toRects at: j+1)=
 at: i+1).=0D		].=0D	].=0D	^form=0D! !=0D=0D=0D!FishEyeMorph methodsFor:=
 'initialization' stamp: 'yo 12/15/1999 21:12'!=0Dcalculate=0D	| step re=
ct |=0D	step _ self extent x // grid.=0D=0D	arrayX _ (1 to: grid + 1) co=
llect: [:i | FloatArray new: grid + 1].=0D	arrayY _ (1 to: grid + 1) col=
lect: [:i |  FloatArray new: grid + 1].=0D=0D	0 to: grid do: [:j |=0D		0=
 to: grid do: [:i |=0D			(arrayX at: (j + 1)) at: (i + 1) put: i*step.=0D=
			(arrayY at: (j + 1)) at: (i + 1) put: j*step.=0D		].=0D	].=0D=0D	0 to=
: grid do: [:j |=0D		self transformRow: (arrayX at: (j+1)).=0D		self tra=
nsformColumn: (arrayY at: (j+1)).=0D	].=0D=0D	0 to: grid do: [:j |=0D		a=
rrayX at: (j+1) put: ((1 to: grid+1) collect: [:i | ((arrayX at: (j+1)) =
at: i) asInteger]).=0D		arrayY at: (j+1) put: ((1 to: grid+1) collect: [=
:i | ((arrayY at: (j+1)) at: i) asInteger]).=0D	].=0D=0D=0D	clipRects _ =
(1 to: grid + 1) collect: [:i | Array new: grid + 1].=0D	toRects _ (1 to=
: grid + 1) collect: [:i |  Array new: grid + 1].=0D=0D	0 to: grid - 1 d=
o: [:j |=0D		0 to: grid - 1 do: [:i |=0D			rect _ (((arrayX at: (j+1)) a=
t: (i+1))@((arrayY at: (j+1)) at: (i+1)))=0D						corner: ((arrayX at: (=
j+2)) at: (i+2))@((arrayY at: (j+2)) at: (j+2)).=0D			(clipRects at: j+1=
) at: i+1 put: rect.=0D			rect width >=3D step ifTrue: [rect _ rect expa=
ndBy: (1 at 0)].=0D			rect height >=3D step ifTrue: [rect _ rect expandBy: =
(0 at 1)].=0D			(toRects at: j+1) at: i+1 put: rect.=0D		].=0D	].=0D! !=0D=0D=
!FishEyeMorph methodsFor: 'initialization' stamp: 'yo 12/14/1999 18:00'!=
=0Dg: aFloatArray max: max=0D	| dNormX array focus |=0D=0D	focus _ self =
extent x // 2.=0D	dNormX _ aFloatArray - focus.=0D	=0D	array _ dNormX / =
max.=0D	array *=3D d.=0D	array +=3D 1.0.=0D	array _ 1.0 / array.=0D	dNor=
mX *=3D (d+1.0).=0D	array *=3D dNormX.=0D	^array +=3D focus.=0D! !=0D=0D=
!FishEyeMorph methodsFor: 'initialization' stamp: 'yo 12/15/1999 21:56'!=
=0Dinitialize=0D	super initialize.=0D	d _ 1.3.=0D	"size _ 200 at 200."=0D	g=
rid _ 16.=0D	form _ Form extent: self extent depth: Display depth.=0D=0D=
	self calculate.=0D! !=0D=0D!FishEyeMorph methodsFor: 'initialization' s=
tamp: 'yo 12/14/1999 18:00'!=0DtransformColumn: aFloatArray=0D	| focus s=
ubArray dMaxY |=0D=0D	focus _ (self extent y) // 2.=0D=0D	(aFloatArray a=
t: 1) <=3D focus ifTrue: [=0D		dMaxY _ 0.0 - focus.=0D	] ifFalse: [=0D		=
dMaxY _ focus asFloat.    " =3D (size - focus)".=0D	].=0D		=0D	subArray =
_ self g: (aFloatArray copyFrom: 1 to: grid + 1) max: dMaxY.=0D=0D	aFloa=
tArray replaceFrom: 1 to: grid + 1 with: subArray startingAt: 1.=0D=0D! =
!=0D=0D!FishEyeMorph methodsFor: 'initialization' stamp: 'yo 12/14/1999 =
18:00'!=0DtransformRow: aFloatArray=0D	| focus grid2 subArray dMaxX |=0D=
=0D	focus _ (self extent x) // 2.=0D	grid2 _ grid // 2.=0D=0D	dMaxX _ 0.=
0 - focus.=0D	subArray _ self g: (aFloatArray copyFrom: 1 to: grid2) max=
: dMaxX.=0D=0D	aFloatArray replaceFrom: 1 to: grid2 with: subArray start=
ingAt: 1.=0D=0D=0D	dMaxX _ focus asFloat.    " =3D (size - focus)".=0D	s=
ubArray _ self g: (aFloatArray copyFrom: grid2 + 1 to: grid + 1) max: dM=
axX.=0D=0D	aFloatArray replaceFrom: grid2 + 1 to: grid + 1 with: subArra=
y startingAt: 1.=0D! !=0D=

----Next_Part(Thu_Dec_16_02:34:57_1999)----





More information about the Squeak-dev mailing list