[comp.lang.smalltalk] Rotating bit-maps 45 degrees goodie

pieter@prls.UUCP (Pieter van der Meulen) (03/30/90)

Anybody tried to rotate bit-maps by 45 degrees?
If you are interested and see a use for it, here is a simple
implementation. If you find a better/faster way of doing
it, please post it.

-------------------------- cut here ------------------------
'These methods allow you to rotate Forms by 45 degrees.
The other angles (135, 225, 315) can easily be implemented.
The lazy way would be to rotate the first by 90, 180 or 270.
See Form>>rotate45 for more information on its use.

Try:	Cursor blank showWhile:
			[(Cursor thumbsUp rotate45 shiftBy: 1@0)
				follow: [Sensor cursorPoint]
				while: [Sensor noButtonPressed]]

I guess it usefull if you want your PC to hitch-hike,
have fun, Pieter.'!

!Form methodsFor: 'private'!

rotate45Square
	"Rotate a square bitmap by 45 degrees.
	A bitmap of 2 by 2 pixels is mapped a bitmap of 3 by 3:

		12		x1x
		34	->	3x2
				x4x	
	x indicates a -white- pixel.

	See Form>>rotate45 for more information.
	Written by Pieter S. van der Meulen."

	| newForm w2 w2Point destForm newBitBlt destBitBlt | 
	(width > 2 or: [height > 2])
		ifFalse:
			[^Form
				extent: 3@3
				fromArray: (Array
					with: (((bits at: 1) bitAnd: 32768) bitShift: -1)
					with: ((((bits at: 1) bitAnd: 16384) bitShift: -1)
						bitOr: ((bits at: 2) bitAnd: 32768))
					with: ((bits at: 2) bitAnd: 16384))
				offset: 0@0].
	newForm _ Form extent: (width * 2 - 1) asPoint.
	w2 _ width / 2.
	w2Point _ w2 asPoint.
	destForm _ self class extent: w2Point.
	destBitBlt _ (BitBlt 
		destForm: destForm
		sourceForm: self
		halftoneForm: nil
		combinationRule: Form over
		destOrigin: 0@0
		sourceOrigin: 0@0
		extent: w2Point
		clipRect: (0@0 extent: w2Point)).
	destBitBlt copyBits.
	newBitBlt _ BitBlt 
		destForm: newForm
		sourceForm: destForm rotate45Square
		halftoneForm: nil
		combinationRule: Form under
		destOrigin: w2@0
		sourceOrigin: 0@0
		extent: self extent
		clipRect: newForm boundingBox.
	newBitBlt copyBits.

	destBitBlt sourceOrigin: 0@w2; copyBits.
	newBitBlt
		sourceForm: destForm rotate45Square;
		destOrigin: 0@w2; copyBits.

	destBitBlt sourceOrigin: w2@0; copyBits.
	newBitBlt
		sourceForm: destForm rotate45Square;
		destOrigin: width@w2; copyBits.

	destBitBlt sourceOrigin: w2Point; copyBits.
	newBitBlt
		sourceForm: destForm rotate45Square;
		destOrigin: w2@width; copyBits.
	^newForm! !

!Form methodsFor: 'image manipulation'!

rotate45
	"Rotate a Form by 45 degrees. Be patient, it is a compute-intensive method.
	Forms are first converted to a rectangular form and then rotated, so a
	100X1 form may be just as slow to rotate as a 100X100 form.
	This method enlarges your original by about 1.4 (2 sqrt), but does not -loose-
	any bits. You may use the <shiftBy: 1@0> method on the result to make it solid.

	The original size is almost obtained (but quality is not) if you magnify by (2/3) :
		(((Form fromUser rotate45 shiftBy: 1@1)
				magnifyBy: 2@2) shrinkBy: 3@3) display.

	The best result however is obtained if you only shift the result, try:
		(Form fromUser rotate45 shiftBy: 1@0) display.
	Written by Pieter S. van der Meulen."

	| rotSize rotForm | 
	rotSize _ width max: height.
	rotSize _ 2 raisedTo: ((rotSize-1) asFloat floorLog: 2)+1.
	rotForm _ self class extent: rotSize asPoint.
	(BitBlt 
		destForm: rotForm
		sourceForm: self
		halftoneForm: nil
		combinationRule: 3
		destOrigin: 0@0
		sourceOrigin: 0@0
		extent: rotSize asPoint
		clipRect: (0@0 extent: width@height)) copyBits.
	^rotForm rotate45Square!

shiftBy: aPoint 
	"The new form will be aPoint larger than myself. Lines will be aPoint bigger."

	| saveOffset shiftedForm box x y |
	saveOffset _ self offset.
	self offset: 0 @ 0.
	shiftedForm _ Form new extent: (self extent + aPoint).
	box _ shiftedForm boundingBox.
	x _ aPoint x.
	[x >= 0]
		whileTrue:
			[y _ aPoint y.
			[y >= 0]
				whileTrue:
					[shiftedForm
						copyBits: box
						from: self
						at: (x @ y)
						clippingBox: box
						rule: Form under
						mask: nil.
						y _ y - 1].
			x _ x - 1].
	self offset: saveOffset.
	shiftedForm offset: offset + (aPoint // 2).
	^shiftedForm!

shiftShrinkBy: aPoint 
	"Return aForm first shifted and then shrunk by aPoint 
	factor. "

	aPoint x > 1 | (aPoint y > 1) ifFalse: [^self].
	^(self shiftBy: aPoint - (1 @ 1)) shrinkBy: aPoint! !
-------------------------- cut here ------------------------
-- 
---------------------------------------------
P.S. van der Meulen, MS 02        prls!pieter
PRLS, Signetics div. of NAPC      -----------
811 E.Arques Avenue, Sunnyvale, CA 94088-3409