[Cuis-dev] Patch for VectorEnginePlugin code generation on oscog

David T. Lewis lewis at mail.msen.com
Tue Jul 27 15:15:36 PDT 2021


Hi Juan,

Attached is a patch to VectorEnginePlugin that allows the C code to be
generated from VMMaker.oscog for opensmalltalk-vm.

Background: The C generated code for VectorEnginePlugin from Cuis or Squeak
VMMaker compiles and runs without issue in opensmalltalk VM. However, if
the C code is generated from VMMaker.oscog, the plugin will fail at runtime
with an unresolved symbol.

Cause: The slang inliner in VMMaker.oscog is failing to inline newTrajectoryFragment,
which is therefore referenced as C function newTrajectoryFragment() in various
places in the plugin code. The method itself is generated as a primitive with
different name, so primNewTrajectoryFragment() is generated instead. This
results in undefined symbol references at runtime.

The fix: Extract the (trivial) body of the primitive into a separate method.
This allows the inliner to work on VMMaker.oscog.

Note, there is another issue with the type inferencer in oscog code generation
that I am looking at, but that is a separate issue.

Dave

-------------- next part --------------
'From Cuis 5.0 [latest update: #4701] on 27 July 2021 at 4:46:43 pm'!

!VectorEnginePlugin methodsFor: 'accessing' stamp: 'dtl 7/27/2021 16:40:35'!
initializeTrajectoryFragment

	prevYTruncated _ 16r7FFFFFFF.! !


!VectorEnginePlugin methodsFor: 'accessing' stamp: 'dtl 7/27/2021 16:41:01'!
newTrajectoryFragment
	self
		primitive: 'primNewTrajectoryFragment'
		parameters: #().

	^ self initializeTrajectoryFragment.! !

!VectorEnginePlugin methodsFor: 'text and multi paths' stamp: 'dtl 7/27/2021 16:41:33'!
displayString: aString from: startIndex to: stopIndex atx: destX y: destY scalex: sx y: sy contourData: contourData contourDataIndexes: contourDataIndexes useST80Glyphs: aBoolean edgeCounts: otherWordArray alphaMask: anotherWordArray

	| answer nextGlyphX nextGlyphY ttMoveToX ttMoveToY ttEndX ttEndY ttControlX ttControlY advanceWidth numContours contourStartX contourStartY numBeziers startX startY endX endY controlX controlY dx dy iso8859s15 i xMinEnd xMaxEnd yMinEnd yMaxEnd length t0 x0 y0 t oneLessT increment f1 f2 f3 x y correction |
	self
		primitive: 'primDisplayString'
		parameters: #(String SmallInteger SmallInteger Float Float Float Float Float32Array IntegerArray Boolean WordArray WordArray).

	self var: #answer type: 'double'.
	self var: #nextGlyphX type: 'float'.
	self var: #nextGlyphY type: 'float'.
	self var: #ttMoveToX type: 'float'.
	self var: #ttMoveToY type: 'float'.
	self var: #ttEndX type: 'float'.
	self var: #ttEndY type: 'float'.
	self var: #ttControlX type: 'float'.
	self var: #ttControlY type: 'float'.
	self var: #advanceWidth type: 'float'.
	self var: #contourStartX type: 'float'.
	self var: #contourStartY type: 'float'.
	self var: #startX type: 'float'.
	self var: #startY type: 'float'.
	self var: #endX type: 'float'.
	self var: #endY type: 'float'.
	self var: #controlX type: 'float'.
	self var: #controlY type: 'float'.
	self var: #dx type: 'float'.
	self var: #dy type: 'float'.
	self var: #iso8859s15 type: 'uint8_t'.

	self var: #length type: 'float'.
	self var: #correction type: 'float'.
	self var: #t0 type: 'float'.
	self var: #x0 type: 'float'.
	self var: #y0 type: 'float'.
	self var: #t type: 'float'.
	self var: #oneLessT type: 'float'.
	self var: #increment type: 'float'.
	self var: #f1 type: 'float'.
	self var: #f2 type: 'float'.
	self var: #f3 type: 'float'.
	self var: #x type: 'float'.
	self var: #y type: 'float'.
	self var: #xMinEnd type: 'float'.
	self var: #xMaxEnd type: 'float'.
	self var: #yMinEnd type: 'float'.
	self var: #yMaxEnd type: 'float'.

	edgeCounts _ otherWordArray.
	alphaMask _ anotherWordArray.
	txA11 _ txA11 * sx.
	txA12 _ txA12 * sy.
	txA21 _ txA21 * sx.
	txA22 _ txA22 * sy.

	nextGlyphX _ destX / sx.
	nextGlyphY _ destY / sy.
	startIndex-1 to: stopIndex-1 do: [ :charIndex |
		self cCode:
				'iso8859s15 = aString[charIndex];'
			inSmalltalk: [
				iso8859s15 _ (aString at: charIndex+1) iso8859s15Code. ].
		aBoolean ifTrue: [
			iso8859s15 = 95 ifTrue: [ iso8859s15 _ 28 ].												"If underscore, use left arrow"
			iso8859s15 = 94 ifTrue: [ iso8859s15 _ 30 ].												"If caret, use up arrow"
			].
		i _ contourDataIndexes at: iso8859s15.
		i _ i - 1.
		advanceWidth _ contourData at: i. i _ i + 5.
		numContours _ (contourData at: i) asInteger. i _ i + 1.
		1 to: numContours do: [ :idx |
			numBeziers _ (contourData at: i) asInteger. i _ i + 1.
			ttMoveToX _ (contourData at: i) + nextGlyphX. i _ i + 1.
			ttMoveToY _ (contourData at: i) + nextGlyphY. i _ i + 1.
			startX _ (ttMoveToX * txA11) + (ttMoveToY * txA12) + txA13.
			startY _ (ttMoveToX * txA21) + (ttMoveToY * txA22) + txA23.
			contourStartX _ startX.
			contourStartY _ startY.
			self initializeTrajectoryFragment.
			1 to: numBeziers do: [ :idx2 |
				ttEndX _ contourData at: i. i _ i + 1.
				ttEndY _ contourData at: i. i _ i + 1.
				ttControlX _ contourData at: i. i _ i + 1.
				ttControlY _ contourData at: i. i _ i + 1.
				endX _ (ttEndX * txA11) + (ttEndY * txA12) + startX.
				endY _ (ttEndX * txA21) + (ttEndY * txA22) + startY.
				controlX _ (ttControlX * txA11) + (ttControlY * txA12) + startX.
				controlY _ (ttControlX * txA21) + (ttControlY * txA22) + startY.
				"This computed span of the Bezier curve is a bit pessimistic (larger than strict bounds), but safe."
				xMinEnd _ startX min: endX.
				xMaxEnd _ startX max: endX.
				yMinEnd _ startY min: endY.
				yMaxEnd _ startY max: endY.
				spanLeft _ spanLeft min: (xMinEnd min: (xMinEnd+controlX) / 2.0).
				spanRight _ spanRight max: (xMaxEnd max: (xMaxEnd+controlX) / 2.0).
				spanTop _ spanTop min: (yMinEnd min: (yMinEnd+controlY) / 2.0).
				spanBottom _ spanBottom max: (yMaxEnd max: (yMaxEnd+controlY) / 2.0).
				"Compute Quadratic Bezier Curve,"
				"Case t = 0.0"
				x _ startX.
				y _ startY.
				self updateAlphasForX: x y: y.
				self updateEdgeCountAtX: x y: y.
				"Will be corrected for each hop. This, being close to pointFrom, is a good initial guess for first correction."
				self cCode: 'dx = fabs(endX-startX); dy = fabs(endY-startY);'
				inSmalltalk: [ dx _ (endX-startX) abs. dy _ (endY-startY) abs ].
				increment _ 0.5 / (dx max: dy) min: 0.5.
				t _ 0.0.
				[
					t0 _ t. x0 _ x. y0 _ y.
					"Compute next point"
					t _ t0 + increment. oneLessT _ 1.0 - t.
					f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
					x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
					y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
					"Now adjust the increment to aim at the required hop length, and recompute next point."
					dx _ x-x0. dy _ y-y0.
					self cCode: '
						length = sqrt(dx*dx + dy*dy);'
						inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
					correction _ hop / length.
					[
						increment _ increment / length * hop.
						t _ t0 + increment. oneLessT _ 1.0 - t.
						f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
						x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
						y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
						dx _ x-x0. dy _ y-y0.
						self cCode: '
							length = sqrt(dx*dx + dy*dy);'
							inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
						correction _ hop / length.
						correction < 1.0]  whileTrue.		   "Keep adjusting if hop would be too big"
					t < 1.0 ]
				whileTrue: [
					self updateAlphasForX: x y: y.
					self updateEdgeCountAtX: x y: y ].
				"Note: For TrueType font definitions, we assume that all contour fragments start exactly where the previous ends.
				This means that the end point is only added for the last fragment of the contour, and not for each one of them."
				startX _ endX.
				startY _ endY.	
			].
			self updateAlphasForX: endX y: endY.
			self updateEdgeCountAtX: endX y: endY.
			"Similar effect to ensureClosePath in #finishPath:,
			but assume the TrueType definition is essentially right, and there might only be a rounding error.
			So, don't draw a line, but just (possibly) correct edgeCounts. The possibility of rounding error is most likely zero.
			Anyway, this is cheap."
			self updateEdgeCountAtX: contourStartX y: contourStartY.
		].
		nextGlyphX _ nextGlyphX + advanceWidth.
	].
	txA11 _ txA11 / sx.
	txA12 _ txA12 / sy.
	txA21 _ txA21 / sx.
	txA22 _ txA22 / sy.
	answer _ nextGlyphX * sx.
	^answer asOop: Float! !

!VectorEnginePlugin methodsFor: 'text and multi paths' stamp: 'dtl 7/27/2021 16:41:42'!
displayUtf32: aWordArray from: startIndex to: stopIndex atx: destX y: destY scalex: sx y: sy contourData: contourData contourDataIndexes: contourDataIndexes useST80Glyphs: aBoolean edgeCounts: otherWordArray alphaMask: anotherWordArray

	| answer nextGlyphX nextGlyphY ttMoveToX ttMoveToY ttEndX ttEndY ttControlX ttControlY advanceWidth numContours contourStartX contourStartY numBeziers startX startY endX endY controlX controlY dx dy utf32 utf8Byte i xMinEnd xMaxEnd yMinEnd yMaxEnd length t0 x0 y0 t oneLessT increment f1 f2 f3 x y correction |
	self
		primitive: 'primDisplayUtf32'
		parameters: #(WordArray SmallInteger SmallInteger Float Float Float Float Float32Array IntegerArray Boolean WordArray WordArray).

	self var: #answer type: 'double'.
	self var: #nextGlyphX type: 'float'.
	self var: #nextGlyphY type: 'float'.
	self var: #ttMoveToX type: 'float'.
	self var: #ttMoveToY type: 'float'.
	self var: #ttEndX type: 'float'.
	self var: #ttEndY type: 'float'.
	self var: #ttControlX type: 'float'.
	self var: #ttControlY type: 'float'.
	self var: #advanceWidth type: 'float'.
	self var: #contourStartX type: 'float'.
	self var: #contourStartY type: 'float'.
	self var: #startX type: 'float'.
	self var: #startY type: 'float'.
	self var: #endX type: 'float'.
	self var: #endY type: 'float'.
	self var: #controlX type: 'float'.
	self var: #controlY type: 'float'.
	self var: #dx type: 'float'.
	self var: #dy type: 'float'.

	self var: #length type: 'float'.
	self var: #correction type: 'float'.
	self var: #t0 type: 'float'.
	self var: #x0 type: 'float'.
	self var: #y0 type: 'float'.
	self var: #t type: 'float'.
	self var: #oneLessT type: 'float'.
	self var: #increment type: 'float'.
	self var: #f1 type: 'float'.
	self var: #f2 type: 'float'.
	self var: #f3 type: 'float'.
	self var: #x type: 'float'.
	self var: #y type: 'float'.
	self var: #xMinEnd type: 'float'.
	self var: #xMaxEnd type: 'float'.
	self var: #yMinEnd type: 'float'.
	self var: #yMaxEnd type: 'float'.

	edgeCounts _ otherWordArray.
	alphaMask _ anotherWordArray.
	txA11 _ txA11 * sx.
	txA12 _ txA12 * sy.
	txA21 _ txA21 * sx.
	txA22 _ txA22 * sy.

	nextGlyphX _ destX / sx.
	nextGlyphY _ destY / sy.
	startIndex-1 to: stopIndex-1 do: [ :utf32Index |
		utf32 _ aWordArray at: utf32Index.
		aBoolean ifTrue: [
			utf32 = 95 ifTrue: [ utf32 _ 8592 ].												"If underscore, use left arrow"
			utf32 = 94 ifTrue: [ utf32 _ 8593 ].												"If caret, use up arrow"
			].
		utf32 <= 16r7F
			ifTrue: [
				utf8Byte _ utf32.
				i _ contourDataIndexes at: utf8Byte ]
			ifFalse: [ utf32 <= 16r7FF
			ifTrue: [
				utf8Byte _ (utf32 bitShift: -6) bitOr: 2r11000000.
				i _ contourDataIndexes at: utf8Byte.
				utf8Byte _ (utf32 bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i ]
			ifFalse: [ utf32 <= 16rFFFF
			ifTrue: [
				utf8Byte _ (utf32 bitShift: -12) bitOr: 2r11100000.
				i _ contourDataIndexes at: utf8Byte.
				utf8Byte _ ((utf32 bitShift: -6) bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i.
				utf8Byte _ (utf32 bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i ]
			ifFalse: [
				utf8Byte _ (utf32 bitShift: -18) bitOr: 2r11110000.
				i _ contourDataIndexes at: utf8Byte.
				utf8Byte _ ((utf32 bitShift: -12) bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i.
				utf8Byte _ ((utf32 bitShift: -6) bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i.
				utf8Byte _ (utf32 bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i ]]].
		i _ i - 1.
		advanceWidth _ contourData at: i. i _ i + 5.
		numContours _ (contourData at: i) asInteger. i _ i + 1.
		1 to: numContours do: [ :idx |
			numBeziers _ (contourData at: i) asInteger. i _ i + 1.
			ttMoveToX _ (contourData at: i) + nextGlyphX. i _ i + 1.
			ttMoveToY _ (contourData at: i) + nextGlyphY. i _ i + 1.
			startX _ (ttMoveToX * txA11) + (ttMoveToY * txA12) + txA13.
			startY _ (ttMoveToX * txA21) + (ttMoveToY * txA22) + txA23.
			contourStartX _ startX.
			contourStartY _ startY.
			self initializeTrajectoryFragment.
			1 to: numBeziers do: [ :idx2 |
				ttEndX _ contourData at: i. i _ i + 1.
				ttEndY _ contourData at: i. i _ i + 1.
				ttControlX _ contourData at: i. i _ i + 1.
				ttControlY _ contourData at: i. i _ i + 1.
				endX _ (ttEndX * txA11) + (ttEndY * txA12) + startX.
				endY _ (ttEndX * txA21) + (ttEndY * txA22) + startY.
				controlX _ (ttControlX * txA11) + (ttControlY * txA12) + startX.
				controlY _ (ttControlX * txA21) + (ttControlY * txA22) + startY.
				"This computed span of the Bezier curve is a bit pessimistic (larger than strict bounds), but safe."
				xMinEnd _ startX min: endX.
				xMaxEnd _ startX max: endX.
				yMinEnd _ startY min: endY.
				yMaxEnd _ startY max: endY.
				spanLeft _ spanLeft min: (xMinEnd min: (xMinEnd+controlX) / 2.0).
				spanRight _ spanRight max: (xMaxEnd max: (xMaxEnd+controlX) / 2.0).
				spanTop _ spanTop min: (yMinEnd min: (yMinEnd+controlY) / 2.0).
				spanBottom _ spanBottom max: (yMaxEnd max: (yMaxEnd+controlY) / 2.0).
				"Compute Quadratic Bezier Curve,"
				"Case t = 0.0"
				x _ startX.
				y _ startY.
				self updateAlphasForX: x y: y.
				self updateEdgeCountAtX: x y: y.
				"Will be corrected for each hop. This, being close to pointFrom, is a good initial guess for first correction."
				self cCode: 'dx = fabs(endX-startX); dy = fabs(endY-startY);'
				inSmalltalk: [ dx _ (endX-startX) abs. dy _ (endY-startY) abs ].
				increment _ 0.5 / (dx max: dy) min: 0.5.
				t _ 0.0.
				[
					t0 _ t. x0 _ x. y0 _ y.
					"Compute next point. Only C version to avoid hitting a limit in Smalltalk compiler."
					self cCode: '
						t = t0 + increment; oneLessT = 1.0 - t;
						f1 = oneLessT * oneLessT; f2 = 2.0 * oneLessT * t; f3 = t * t;
						x = (f1 * startX) + (f2 * controlX) + (f3 * endX);
						y = (f1 * startY) + (f2 * controlY) + (f3 * endY);
						dx = x-x0; dy = y-y0;
						length = sqrt(dx*dx + dy*dy);'
						inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
					correction _ hop / length.
					"Now adjust the increment to aim at the required hop length, and recompute next point."
					[
						increment _ increment / length * hop.
						t _ t0 + increment. oneLessT _ 1.0 - t.
						f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
						x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
						y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
						dx _ x-x0. dy _ y-y0.
						self cCode: '
							length = sqrt(dx*dx + dy*dy);'
							inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
						correction _ hop / length.
						correction < 1.0]  whileTrue.		   "Keep adjusting if hop would be too big"
					t < 1.0 ]
				whileTrue: [
					self updateAlphasForX: x y: y.
					self updateEdgeCountAtX: x y: y. ].
				"Note: For TrueType font definitions, we assume that all contour fragments start exactly where the previous ends.
				This means that the end point is only added for the last fragment of the contour, and not for each one of them."
				startX _ endX.
				startY _ endY.	
			].
			self updateAlphasForX: endX y: endY.
			self updateEdgeCountAtX: endX y: endY.
			"Similar effect to ensureClosePath in #finishPath:,
			but assume the TrueType definition is essentially right, and there might only be a rounding error.
			So, don't draw a line, but just (possibly) correct edgeCounts. The possibility of rounding error is most likely zero.
			Anyway, this is cheap."
			self updateEdgeCountAtX: contourStartX y: contourStartY.
		].
		nextGlyphX _ nextGlyphX + advanceWidth.
	].
	txA11 _ txA11 / sx.
	txA12 _ txA12 / sy.
	txA21 _ txA21 / sx.
	txA22 _ txA22 / sy.
	answer _ nextGlyphX * sx.
	^answer asOop: Float! !

!VectorEnginePlugin methodsFor: 'text and multi paths' stamp: 'dtl 7/27/2021 16:41:51'!
displayUtf8: aByteArray fromByte: byteStartIndex toByte: byteStopIndex atx: destX y: destY scalex: sx y: sy contourData: contourData contourDataIndexes: contourDataIndexes useST80Glyphs: aBoolean edgeCounts: otherWordArray alphaMask: anotherWordArray

	| answer nextGlyphX nextGlyphY ttMoveToX ttMoveToY ttEndX ttEndY ttControlX ttControlY advanceWidth numContours contourStartX contourStartY numBeziers startX startY endX endY controlX controlY dx dy baseIndex byte i xMinEnd xMaxEnd yMinEnd yMaxEnd length t0 x0 y0 t oneLessT increment f1 f2 f3 x y correction |
	self
		primitive: 'primDisplayUtf8'
		parameters: #(ByteArray SmallInteger SmallInteger Float Float Float Float Float32Array IntegerArray Boolean WordArray WordArray).

	self var: #answer type: 'double'.
	self var: #nextGlyphX type: 'float'.
	self var: #nextGlyphY type: 'float'.
	self var: #ttMoveToX type: 'float'.
	self var: #ttMoveToY type: 'float'.
	self var: #ttEndX type: 'float'.
	self var: #ttEndY type: 'float'.
	self var: #ttControlX type: 'float'.
	self var: #ttControlY type: 'float'.
	self var: #advanceWidth type: 'float'.
	self var: #contourStartX type: 'float'.
	self var: #contourStartY type: 'float'.
	self var: #startX type: 'float'.
	self var: #startY type: 'float'.
	self var: #endX type: 'float'.
	self var: #endY type: 'float'.
	self var: #controlX type: 'float'.
	self var: #controlY type: 'float'.
	self var: #dx type: 'float'.
	self var: #dy type: 'float'.
	self var: #byte type: 'uint8_t'.

	self var: #length type: 'float'.
	self var: #correction type: 'float'.
	self var: #t0 type: 'float'.
	self var: #x0 type: 'float'.
	self var: #y0 type: 'float'.
	self var: #t type: 'float'.
	self var: #oneLessT type: 'float'.
	self var: #increment type: 'float'.
	self var: #f1 type: 'float'.
	self var: #f2 type: 'float'.
	self var: #f3 type: 'float'.
	self var: #x type: 'float'.
	self var: #y type: 'float'.
	self var: #xMinEnd type: 'float'.
	self var: #xMaxEnd type: 'float'.
	self var: #yMinEnd type: 'float'.
	self var: #yMaxEnd type: 'float'.

	edgeCounts _ otherWordArray.
	alphaMask _ anotherWordArray.
	txA11 _ txA11 * sx.
	txA12 _ txA12 * sy.
	txA21 _ txA21 * sx.
	txA22 _ txA22 * sy.

	nextGlyphX _ destX / sx.
	nextGlyphY _ destY / sy.
	baseIndex _ 0.
	byteStartIndex-1 to: byteStopIndex-1 do: [ :byteIndex |
		byte _ aByteArray at: byteIndex.
		i _ contourDataIndexes at: baseIndex + byte.
		aBoolean ifTrue: [
			byte = 95 ifTrue: [
				i _ contourDataIndexes at: 226.
				i _ contourDataIndexes at: 134 - i.
				i _ contourDataIndexes at: 144 - i ].
			byte = 94 ifTrue: [ 
				i _ contourDataIndexes at: 226.
				i _ contourDataIndexes at: 134 - i.
				i _ contourDataIndexes at: 145 - i ]].
		i < 0
			ifTrue: [ baseIndex _ 0 - i ]
			ifFalse: [
				i _ i - 1.
				advanceWidth _ contourData at: i. i _ i + 5.
				numContours _ (contourData at: i) asInteger. i _ i + 1.
				1 to: numContours do: [ :idx |
					numBeziers _ (contourData at: i) asInteger. i _ i + 1.
					ttMoveToX _ (contourData at: i) + nextGlyphX. i _ i + 1.
					ttMoveToY _ (contourData at: i) + nextGlyphY. i _ i + 1.
					startX _ (ttMoveToX * txA11) + (ttMoveToY * txA12) + txA13.
					startY _ (ttMoveToX * txA21) + (ttMoveToY * txA22) + txA23.
					contourStartX _ startX.
					contourStartY _ startY.
					self initializeTrajectoryFragment.
					1 to: numBeziers do: [ :idx2 |
						ttEndX _ contourData at: i. i _ i + 1.
						ttEndY _ contourData at: i. i _ i + 1.
						ttControlX _ contourData at: i. i _ i + 1.
						ttControlY _ contourData at: i. i _ i + 1.
						endX _ (ttEndX * txA11) + (ttEndY * txA12) + startX.
						endY _ (ttEndX * txA21) + (ttEndY * txA22) + startY.
						controlX _ (ttControlX * txA11) + (ttControlY * txA12) + startX.
						controlY _ (ttControlX * txA21) + (ttControlY * txA22) + startY.
						"This computed span of the Bezier curve is a bit pessimistic (larger than strict bounds), but safe."
						xMinEnd _ startX min: endX.
						xMaxEnd _ startX max: endX.
						yMinEnd _ startY min: endY.
						yMaxEnd _ startY max: endY.
						spanLeft _ spanLeft min: (xMinEnd min: (xMinEnd+controlX) / 2.0).
						spanRight _ spanRight max: (xMaxEnd max: (xMaxEnd+controlX) / 2.0).
						spanTop _ spanTop min: (yMinEnd min: (yMinEnd+controlY) / 2.0).
						spanBottom _ spanBottom max: (yMaxEnd max: (yMaxEnd+controlY) / 2.0).
						"Case t = 0.0"
						x _ startX.
						y _ startY.
						self updateAlphasForX: x y: y.
						self updateEdgeCountAtX: x y: y.
						"Will be corrected for each hop. This, being close to pointFrom, is a good initial guess for first correction."
						self cCode: 'dx = fabs(endX-startX); dy = fabs(endY-startY);'
						inSmalltalk: [ dx _ (endX-startX) abs. dy _ (endY-startY) abs ].
						increment _ 0.5 / (dx max: dy) min: 0.5.
						"Compute Quadratic Bezier Curve,"
						t _ 0.0.
						[
							t0 _ t. x0 _ x. y0 _ y.
							"Compute next point"
							t _ t0 + increment. oneLessT _ 1.0 - t.
							f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
							x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
							y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
							"Now adjust the increment to aim at the required hop length, and recompute next point."
							dx _ x-x0. dy _ y-y0.
							self cCode: '
								length = sqrt(dx*dx + dy*dy);'
								inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
							correction _ hop / length.
							[
								increment _ increment / length * hop.
								t _ t0 + increment. oneLessT _ 1.0 - t.
								f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
								x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
								y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
								dx _ x-x0. dy _ y-y0.
								self cCode: '
									length = sqrt(dx*dx + dy*dy);'
									inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
								correction _ hop / length.
								correction < 1.0]  whileTrue.		   "Keep adjusting if hop would be too big"
							t < 1.0 ]
						whileTrue: [
							self updateAlphasForX: x y: y.
							self updateEdgeCountAtX: x y: y ].
						"Note: For TrueType font definitions, we assume that all contour fragments start exactly where the previous ends.
						This means that the end point is only added for the last fragment of the contour, and not for each one of them."
						startX _ endX.
						startY _ endY.	
					].
					self updateAlphasForX: endX y: endY.
					self updateEdgeCountAtX: endX y: endY.
					"Similar effect to ensureClosePath in #finishPath:,
					but assume the TrueType definition is essentially right, and there might only be a rounding error.
					So, don't draw a line, but just (possibly) correct edgeCounts. The possibility of rounding error is most likely zero.
					Anyway, this is cheap."
					self updateEdgeCountAtX: contourStartX y: contourStartY.
				].
				nextGlyphX _ nextGlyphX + advanceWidth.
				baseIndex _ 0.
			]
	].
	txA11 _ txA11 / sx.
	txA12 _ txA12 / sy.
	txA21 _ txA21 / sx.
	txA22 _ txA22 / sy.
	answer _ nextGlyphX * sx.
	^answer asOop: Float! !

!VectorEnginePlugin methodsFor: 'text and multi paths' stamp: 'dtl 7/27/2021 16:41:59'!
pathSequence: aFloat32Array size: size edgeCounts: otherWordArray alphaMask: anotherWordArray contour: otherFloat32Array

	| i commandType startX startY endX endY control1X control1Y control2X control2Y |
	self
		primitive: 'primPathSequence'
		parameters: #(Float32Array SmallInteger WordArray WordArray Float32Array).

	self var: #startX type: 'float'.
	self var: #startY type: 'float'.
	self var: #endX type: 'float'.
	self var: #endY type: 'float'.
	self var: #control1X type: 'float'.
	self var: #control1Y type: 'float'.
	self var: #control2X type: 'float'.
	self var: #control2Y type: 'float'.

	edgeCounts _ otherWordArray.
	alphaMask _ anotherWordArray.
	contour _ otherFloat32Array.
	i _ 0.
	[ i < size ] whileTrue: [
		commandType _ (aFloat32Array at: i) asInteger. i _ i + 1.
		commandType caseOf: {
			[0] -> [
				i+1 < size ifFalse: [ ^self "failure" ].
				startX _ aFloat32Array at: i. i _ i + 1.
				startY _ aFloat32Array at: i. i _ i + 1.
				self initializeTrajectoryFragment.
				].
			[1] -> [
				i+1 < size ifFalse: [ ^self "failure" ].
				endX _ aFloat32Array at: i. i _ i + 1.
				endY _ aFloat32Array at: i. i _ i + 1.
				self pvt_lineFromX: startX y: startY toX: endX y: endY.
				startX _ endX.
				startY _ endY.
				].
			[2] -> [
				i+3 < size ifFalse: [ ^self "failure" ].
				endX _ aFloat32Array at: i. i _ i + 1.
				endY _ aFloat32Array at: i. i _ i + 1.
				control1X _ aFloat32Array at: i. i _ i + 1.
				control1Y _ aFloat32Array at: i. i _ i + 1.
				self pvt_quadraticBezierFromX: startX y: startY
					toX: endX y: endY
					controlX: control1X y: control1Y.
				startX _ endX.
				startY _ endY.
				].
			[3] -> [
				i+5 < size ifFalse: [ ^self "failure" ].
				endX _ aFloat32Array at: i. i _ i + 1.
				endY _ aFloat32Array at: i. i _ i + 1.
				control1X _ aFloat32Array at: i. i _ i + 1.
				control1Y _ aFloat32Array at: i. i _ i + 1.
				control2X _ aFloat32Array at: i. i _ i + 1.
				control2Y _ aFloat32Array at: i. i _ i + 1.
				self pvt_cubicBezierFromX: startX y: startY
					toX: endX y: endY
					control1X: control1X y: control1Y
					control2X: control2X y: control2Y.
				startX _ endX.
				startY _ endY.
				]}
		otherwise: [ ^self "failure"]].! !

!VectorEnginePlugin methodsFor: 'whole pixel - text and multi paths' stamp: 'dtl 7/27/2021 16:41:37'!
displayStringWP: aString from: startIndex to: stopIndex atx: destX y: destY scalex: sx y: sy contourData: contourData contourDataIndexes: contourDataIndexes useST80Glyphs: aBoolean edgeCounts: otherByteArray alphaMask: anotherByteArray

	| answer nextGlyphX nextGlyphY ttMoveToX ttMoveToY ttEndX ttEndY ttControlX ttControlY advanceWidth numContours contourStartX contourStartY numBeziers startX startY endX endY controlX controlY dx dy iso8859s15 i xMinEnd xMaxEnd yMinEnd yMaxEnd length t0 x0 y0 t oneLessT increment f1 f2 f3 x y correction |
	self
		primitive: 'primDisplayStringWP'
		parameters: #(String SmallInteger SmallInteger Float Float Float Float Float32Array IntegerArray Boolean ByteArray ByteArray).

	self var: #answer type: 'double'.
	self var: #nextGlyphX type: 'float'.
	self var: #nextGlyphY type: 'float'.
	self var: #ttMoveToX type: 'float'.
	self var: #ttMoveToY type: 'float'.
	self var: #ttEndX type: 'float'.
	self var: #ttEndY type: 'float'.
	self var: #ttControlX type: 'float'.
	self var: #ttControlY type: 'float'.
	self var: #advanceWidth type: 'float'.
	self var: #contourStartX type: 'float'.
	self var: #contourStartY type: 'float'.
	self var: #startX type: 'float'.
	self var: #startY type: 'float'.
	self var: #endX type: 'float'.
	self var: #endY type: 'float'.
	self var: #controlX type: 'float'.
	self var: #controlY type: 'float'.
	self var: #dx type: 'float'.
	self var: #dy type: 'float'.
	self var: #iso8859s15 type: 'uint8_t'.

	self var: #length type: 'float'.
	self var: #correction type: 'float'.
	self var: #t0 type: 'float'.
	self var: #x0 type: 'float'.
	self var: #y0 type: 'float'.
	self var: #t type: 'float'.
	self var: #oneLessT type: 'float'.
	self var: #increment type: 'float'.
	self var: #f1 type: 'float'.
	self var: #f2 type: 'float'.
	self var: #f3 type: 'float'.
	self var: #x type: 'float'.
	self var: #y type: 'float'.
	self var: #xMinEnd type: 'float'.
	self var: #xMaxEnd type: 'float'.
	self var: #yMinEnd type: 'float'.
	self var: #yMaxEnd type: 'float'.

	edgeCountsWP _ otherByteArray.
	alphaMaskWP _ anotherByteArray.
	txA11 _ txA11 * sx.
	txA12 _ txA12 * sy.
	txA21 _ txA21 * sx.
	txA22 _ txA22 * sy.

	nextGlyphX _ destX / sx.
	nextGlyphY _ destY / sy.
	startIndex-1 to: stopIndex-1 do: [ :charIndex |
		self cCode:
				'iso8859s15 = aString[charIndex];'
			inSmalltalk: [
				iso8859s15 _ (aString at: charIndex+1) iso8859s15Code. ].
		aBoolean ifTrue: [
			iso8859s15 = 95 ifTrue: [ iso8859s15 _ 28 ].												"If underscore, use left arrow"
			iso8859s15 = 94 ifTrue: [ iso8859s15 _ 30 ].												"If caret, use up arrow"
			].
		i _ contourDataIndexes at: iso8859s15.
		i _ i - 1.
		advanceWidth _ contourData at: i. i _ i + 5.
		numContours _ (contourData at: i) asInteger. i _ i + 1.
		1 to: numContours do: [ :idx |
			numBeziers _ (contourData at: i) asInteger. i _ i + 1.
			ttMoveToX _ (contourData at: i) + nextGlyphX. i _ i + 1.
			ttMoveToY _ (contourData at: i) + nextGlyphY. i _ i + 1.
			startX _ (ttMoveToX * txA11) + (ttMoveToY * txA12) + txA13.
			startY _ (ttMoveToX * txA21) + (ttMoveToY * txA22) + txA23.
			contourStartX _ startX.
			contourStartY _ startY.
			self initializeTrajectoryFragment.
			1 to: numBeziers do: [ :idx2 |
				ttEndX _ contourData at: i. i _ i + 1.
				ttEndY _ contourData at: i. i _ i + 1.
				ttControlX _ contourData at: i. i _ i + 1.
				ttControlY _ contourData at: i. i _ i + 1.
				endX _ (ttEndX * txA11) + (ttEndY * txA12) + startX.
				endY _ (ttEndX * txA21) + (ttEndY * txA22) + startY.
				controlX _ (ttControlX * txA11) + (ttControlY * txA12) + startX.
				controlY _ (ttControlX * txA21) + (ttControlY * txA22) + startY.
				"This computed span of the Bezier curve is a bit pessimistic (larger than strict bounds), but safe."
				xMinEnd _ startX min: endX.
				xMaxEnd _ startX max: endX.
				yMinEnd _ startY min: endY.
				yMaxEnd _ startY max: endY.
				spanLeft _ spanLeft min: (xMinEnd min: (xMinEnd+controlX) / 2.0).
				spanRight _ spanRight max: (xMaxEnd max: (xMaxEnd+controlX) / 2.0).
				spanTop _ spanTop min: (yMinEnd min: (yMinEnd+controlY) / 2.0).
				spanBottom _ spanBottom max: (yMaxEnd max: (yMaxEnd+controlY) / 2.0).
				"Compute Quadratic Bezier Curve,"
				"Case t = 0.0"
				x _ startX.
				y _ startY.
				self updateAlphasWPZeroStrokeForX: x y: y.
				self updateEdgeCountWPAtX: x y: y.
				"Will be corrected for each hop. This, being close to pointFrom, is a good initial guess for first correction."
				self cCode: 'dx = fabs(endX-startX); dy = fabs(endY-startY);'
				inSmalltalk: [ dx _ (endX-startX) abs. dy _ (endY-startY) abs ].
				increment _ 0.5 / (dx max: dy) min: 0.5.
				t _ 0.0.
				[
					t0 _ t. x0 _ x. y0 _ y.
					"Compute next point"
					t _ t0 + increment. oneLessT _ 1.0 - t.
					f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
					x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
					y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
					"Now adjust the increment to aim at the required hop length, and recompute next point."
					dx _ x-x0. dy _ y-y0.
					self cCode: '
						length = sqrt(dx*dx + dy*dy);'
						inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
					correction _ hop / length.
					[
						increment _ increment / length * hop.
						t _ t0 + increment. oneLessT _ 1.0 - t.
						f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
						x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
						y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
						dx _ x-x0. dy _ y-y0.
						self cCode: '
							length = sqrt(dx*dx + dy*dy);'
							inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
						correction _ hop / length.
						correction < 1.0]  whileTrue.		   "Keep adjusting if hop would be too big"
					t < 1.0 ]
				whileTrue: [
					self updateAlphasWPZeroStrokeForX: x y: y.
					self updateEdgeCountWPAtX: x y: y ].
				"Note: For TrueType font definitions, we assume that all contour fragments start exactly where the previous ends.
				This means that the end point is only added for the last fragment of the contour, and not for each one of them."
				startX _ endX.
				startY _ endY.	
			].
			self updateAlphasWPZeroStrokeForX: endX y: endY.
			self updateEdgeCountWPAtX: endX y: endY.
			"Similar effect to ensureClosePath in #finishPath:,
			but assume the TrueType definition is essentially right, and there might only be a rounding error.
			So, don't draw a line, but just (possibly) correct edgeCountsWP. The possibility of rounding error is most likely zero.
			Anyway, this is cheap."
			self updateEdgeCountWPAtX: contourStartX y: contourStartY.
		].
		nextGlyphX _ nextGlyphX + advanceWidth.
	].
	txA11 _ txA11 / sx.
	txA12 _ txA12 / sy.
	txA21 _ txA21 / sx.
	txA22 _ txA22 / sy.
	answer _ nextGlyphX * sx.
	^answer asOop: Float! !

!VectorEnginePlugin methodsFor: 'whole pixel - text and multi paths' stamp: 'dtl 7/27/2021 16:41:46'!
displayUtf32WP: aWordArray from: startIndex to: stopIndex atx: destX y: destY scalex: sx y: sy contourData: contourData contourDataIndexes: contourDataIndexes useST80Glyphs: aBoolean edgeCounts: otherByteArray alphaMask: anotherByteArray

	| answer nextGlyphX nextGlyphY ttMoveToX ttMoveToY ttEndX ttEndY ttControlX ttControlY advanceWidth numContours contourStartX contourStartY numBeziers startX startY endX endY controlX controlY dx dy utf32 utf8Byte i xMinEnd xMaxEnd yMinEnd yMaxEnd length t0 x0 y0 t oneLessT increment f1 f2 f3 x y correction |
	self
		primitive: 'primDisplayUtf32WP'
		parameters: #(WordArray SmallInteger SmallInteger Float Float Float Float Float32Array IntegerArray Boolean ByteArray ByteArray).

	self var: #answer type: 'double'.
	self var: #nextGlyphX type: 'float'.
	self var: #nextGlyphY type: 'float'.
	self var: #ttMoveToX type: 'float'.
	self var: #ttMoveToY type: 'float'.
	self var: #ttEndX type: 'float'.
	self var: #ttEndY type: 'float'.
	self var: #ttControlX type: 'float'.
	self var: #ttControlY type: 'float'.
	self var: #advanceWidth type: 'float'.
	self var: #contourStartX type: 'float'.
	self var: #contourStartY type: 'float'.
	self var: #startX type: 'float'.
	self var: #startY type: 'float'.
	self var: #endX type: 'float'.
	self var: #endY type: 'float'.
	self var: #controlX type: 'float'.
	self var: #controlY type: 'float'.
	self var: #dx type: 'float'.
	self var: #dy type: 'float'.

	self var: #length type: 'float'.
	self var: #correction type: 'float'.
	self var: #t0 type: 'float'.
	self var: #x0 type: 'float'.
	self var: #y0 type: 'float'.
	self var: #t type: 'float'.
	self var: #oneLessT type: 'float'.
	self var: #increment type: 'float'.
	self var: #f1 type: 'float'.
	self var: #f2 type: 'float'.
	self var: #f3 type: 'float'.
	self var: #x type: 'float'.
	self var: #y type: 'float'.
	self var: #xMinEnd type: 'float'.
	self var: #xMaxEnd type: 'float'.
	self var: #yMinEnd type: 'float'.
	self var: #yMaxEnd type: 'float'.

	edgeCountsWP _ otherByteArray.
	alphaMaskWP _ anotherByteArray.
	txA11 _ txA11 * sx.
	txA12 _ txA12 * sy.
	txA21 _ txA21 * sx.
	txA22 _ txA22 * sy.

	nextGlyphX _ destX / sx.
	nextGlyphY _ destY / sy.
	startIndex-1 to: stopIndex-1 do: [ :utf32Index |
		utf32 _ aWordArray at: utf32Index.
		aBoolean ifTrue: [
			utf32 = 95 ifTrue: [ utf32 _ 8592 ].												"If underscore, use left arrow"
			utf32 = 94 ifTrue: [ utf32 _ 8593 ].												"If caret, use up arrow"
			].
		utf32 <= 16r7F
			ifTrue: [
				utf8Byte _ utf32.
				i _ contourDataIndexes at: utf8Byte ]
			ifFalse: [ utf32 <= 16r7FF
			ifTrue: [
				utf8Byte _ (utf32 bitShift: -6) bitOr: 2r11000000.
				i _ contourDataIndexes at: utf8Byte.
				utf8Byte _ (utf32 bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i ]
			ifFalse: [ utf32 <= 16rFFFF
			ifTrue: [
				utf8Byte _ (utf32 bitShift: -12) bitOr: 2r11100000.
				i _ contourDataIndexes at: utf8Byte.
				utf8Byte _ ((utf32 bitShift: -6) bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i.
				utf8Byte _ (utf32 bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i ]
			ifFalse: [
				utf8Byte _ (utf32 bitShift: -18) bitOr: 2r11110000.
				i _ contourDataIndexes at: utf8Byte.
				utf8Byte _ ((utf32 bitShift: -12) bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i.
				utf8Byte _ ((utf32 bitShift: -6) bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i.
				utf8Byte _ (utf32 bitAnd: 2r00111111) bitOr: 2r10000000.
				i _ contourDataIndexes at: utf8Byte - i ]]].
		i _ i - 1.
		advanceWidth _ contourData at: i. i _ i + 5.
		numContours _ (contourData at: i) asInteger. i _ i + 1.
		1 to: numContours do: [ :idx |
			numBeziers _ (contourData at: i) asInteger. i _ i + 1.
			ttMoveToX _ (contourData at: i) + nextGlyphX. i _ i + 1.
			ttMoveToY _ (contourData at: i) + nextGlyphY. i _ i + 1.
			startX _ (ttMoveToX * txA11) + (ttMoveToY * txA12) + txA13.
			startY _ (ttMoveToX * txA21) + (ttMoveToY * txA22) + txA23.
			contourStartX _ startX.
			contourStartY _ startY.
			self initializeTrajectoryFragment.
			1 to: numBeziers do: [ :idx2 |
				ttEndX _ contourData at: i. i _ i + 1.
				ttEndY _ contourData at: i. i _ i + 1.
				ttControlX _ contourData at: i. i _ i + 1.
				ttControlY _ contourData at: i. i _ i + 1.
				endX _ (ttEndX * txA11) + (ttEndY * txA12) + startX.
				endY _ (ttEndX * txA21) + (ttEndY * txA22) + startY.
				controlX _ (ttControlX * txA11) + (ttControlY * txA12) + startX.
				controlY _ (ttControlX * txA21) + (ttControlY * txA22) + startY.
				"This computed span of the Bezier curve is a bit pessimistic (larger than strict bounds), but safe."
				xMinEnd _ startX min: endX.
				xMaxEnd _ startX max: endX.
				yMinEnd _ startY min: endY.
				yMaxEnd _ startY max: endY.
				spanLeft _ spanLeft min: (xMinEnd min: (xMinEnd+controlX) / 2.0).
				spanRight _ spanRight max: (xMaxEnd max: (xMaxEnd+controlX) / 2.0).
				spanTop _ spanTop min: (yMinEnd min: (yMinEnd+controlY) / 2.0).
				spanBottom _ spanBottom max: (yMaxEnd max: (yMaxEnd+controlY) / 2.0).
				"Compute Quadratic Bezier Curve,"
				"Case t = 0.0"
				x _ startX.
				y _ startY.
				self updateAlphasWPZeroStrokeForX: x y: y.
				self updateEdgeCountWPAtX: x y: y.
				"Will be corrected for each hop. This, being close to pointFrom, is a good initial guess for first correction."
				self cCode: 'dx = fabs(endX-startX); dy = fabs(endY-startY);'
				inSmalltalk: [ dx _ (endX-startX) abs. dy _ (endY-startY) abs ].
				increment _ 0.5 / (dx max: dy) min: 0.5.
				t _ 0.0.
				[
					t0 _ t. x0 _ x. y0 _ y.
					"Compute next point. Only C version to avoid hitting a limit in Smalltalk compiler."
					self cCode: '
						t = t0 + increment; oneLessT = 1.0 - t;
						f1 = oneLessT * oneLessT; f2 = 2.0 * oneLessT * t; f3 = t * t;
						x = (f1 * startX) + (f2 * controlX) + (f3 * endX);
						y = (f1 * startY) + (f2 * controlY) + (f3 * endY);
						dx = x-x0; dy = y-y0;
						length = sqrt(dx*dx + dy*dy);'
						inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
					correction _ hop / length.
					"Now adjust the increment to aim at the required hop length, and recompute next point."
					[
						increment _ increment / length * hop.
						t _ t0 + increment. oneLessT _ 1.0 - t.
						f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
						x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
						y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
						dx _ x-x0. dy _ y-y0.
						self cCode: '
							length = sqrt(dx*dx + dy*dy);'
							inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
						correction _ hop / length.
						correction < 1.0]  whileTrue.		   "Keep adjusting if hop would be too big"
					t < 1.0 ]
				whileTrue: [
					self updateAlphasWPZeroStrokeForX: x y: y.
					self updateEdgeCountWPAtX: x y: y. ].
				"Note: For TrueType font definitions, we assume that all contour fragments start exactly where the previous ends.
				This means that the end point is only added for the last fragment of the contour, and not for each one of them."
				startX _ endX.
				startY _ endY.	
			].
			self updateAlphasWPZeroStrokeForX: endX y: endY.
			self updateEdgeCountWPAtX: endX y: endY.
			"Similar effect to ensureClosePath in #finishPath:,
			but assume the TrueType definition is essentially right, and there might only be a rounding error.
			So, don't draw a line, but just (possibly) correct edgeCountsWP. The possibility of rounding error is most likely zero.
			Anyway, this is cheap."
			self updateEdgeCountWPAtX: contourStartX y: contourStartY.
		].
		nextGlyphX _ nextGlyphX + advanceWidth.
	].
	txA11 _ txA11 / sx.
	txA12 _ txA12 / sy.
	txA21 _ txA21 / sx.
	txA22 _ txA22 / sy.
	answer _ nextGlyphX * sx.
	^answer asOop: Float! !

!VectorEnginePlugin methodsFor: 'whole pixel - text and multi paths' stamp: 'dtl 7/27/2021 16:41:54'!
displayUtf8WP: aByteArray fromByte: byteStartIndex toByte: byteStopIndex atx: destX y: destY scalex: sx y: sy contourData: contourData contourDataIndexes: contourDataIndexes useST80Glyphs: aBoolean edgeCounts: otherByteArray alphaMask: anotherByteArray

	| answer nextGlyphX nextGlyphY ttMoveToX ttMoveToY ttEndX ttEndY ttControlX ttControlY advanceWidth numContours contourStartX contourStartY numBeziers startX startY endX endY controlX controlY dx dy baseIndex byte i xMinEnd xMaxEnd yMinEnd yMaxEnd length t0 x0 y0 t oneLessT increment f1 f2 f3 x y correction |
	self
		primitive: 'primDisplayUtf8WP'
		parameters: #(ByteArray SmallInteger SmallInteger Float Float Float Float Float32Array IntegerArray Boolean ByteArray ByteArray).

	self var: #answer type: 'double'.
	self var: #nextGlyphX type: 'float'.
	self var: #nextGlyphY type: 'float'.
	self var: #ttMoveToX type: 'float'.
	self var: #ttMoveToY type: 'float'.
	self var: #ttEndX type: 'float'.
	self var: #ttEndY type: 'float'.
	self var: #ttControlX type: 'float'.
	self var: #ttControlY type: 'float'.
	self var: #advanceWidth type: 'float'.
	self var: #contourStartX type: 'float'.
	self var: #contourStartY type: 'float'.
	self var: #startX type: 'float'.
	self var: #startY type: 'float'.
	self var: #endX type: 'float'.
	self var: #endY type: 'float'.
	self var: #controlX type: 'float'.
	self var: #controlY type: 'float'.
	self var: #dx type: 'float'.
	self var: #dy type: 'float'.
	self var: #byte type: 'uint8_t'.

	self var: #length type: 'float'.
	self var: #correction type: 'float'.
	self var: #t0 type: 'float'.
	self var: #x0 type: 'float'.
	self var: #y0 type: 'float'.
	self var: #t type: 'float'.
	self var: #oneLessT type: 'float'.
	self var: #increment type: 'float'.
	self var: #f1 type: 'float'.
	self var: #f2 type: 'float'.
	self var: #f3 type: 'float'.
	self var: #x type: 'float'.
	self var: #y type: 'float'.
	self var: #xMinEnd type: 'float'.
	self var: #xMaxEnd type: 'float'.
	self var: #yMinEnd type: 'float'.
	self var: #yMaxEnd type: 'float'.

	edgeCountsWP _ otherByteArray.
	alphaMaskWP _ anotherByteArray.
	txA11 _ txA11 * sx.
	txA12 _ txA12 * sy.
	txA21 _ txA21 * sx.
	txA22 _ txA22 * sy.

	nextGlyphX _ destX / sx.
	nextGlyphY _ destY / sy.
	baseIndex _ 0.
	byteStartIndex-1 to: byteStopIndex-1 do: [ :byteIndex |
		byte _ aByteArray at: byteIndex.
		i _ contourDataIndexes at: baseIndex + byte.
		aBoolean ifTrue: [
			byte = 95 ifTrue: [
				i _ contourDataIndexes at: 226.
				i _ contourDataIndexes at: 134 - i.
				i _ contourDataIndexes at: 144 - i ].
			byte = 94 ifTrue: [ 
				i _ contourDataIndexes at: 226.
				i _ contourDataIndexes at: 134 - i.
				i _ contourDataIndexes at: 145 - i ]].
		i < 0
			ifTrue: [ baseIndex _ 0 - i ]
			ifFalse: [
				i _ i - 1.
				advanceWidth _ contourData at: i. i _ i + 5.
				numContours _ (contourData at: i) asInteger. i _ i + 1.
				1 to: numContours do: [ :idx |
					numBeziers _ (contourData at: i) asInteger. i _ i + 1.
					ttMoveToX _ (contourData at: i) + nextGlyphX. i _ i + 1.
					ttMoveToY _ (contourData at: i) + nextGlyphY. i _ i + 1.
					startX _ (ttMoveToX * txA11) + (ttMoveToY * txA12) + txA13.
					startY _ (ttMoveToX * txA21) + (ttMoveToY * txA22) + txA23.
					contourStartX _ startX.
					contourStartY _ startY.
					self initializeTrajectoryFragment.
					1 to: numBeziers do: [ :idx2 |
						ttEndX _ contourData at: i. i _ i + 1.
						ttEndY _ contourData at: i. i _ i + 1.
						ttControlX _ contourData at: i. i _ i + 1.
						ttControlY _ contourData at: i. i _ i + 1.
						endX _ (ttEndX * txA11) + (ttEndY * txA12) + startX.
						endY _ (ttEndX * txA21) + (ttEndY * txA22) + startY.
						controlX _ (ttControlX * txA11) + (ttControlY * txA12) + startX.
						controlY _ (ttControlX * txA21) + (ttControlY * txA22) + startY.
						"This computed span of the Bezier curve is a bit pessimistic (larger than strict bounds), but safe."
						xMinEnd _ startX min: endX.
						xMaxEnd _ startX max: endX.
						yMinEnd _ startY min: endY.
						yMaxEnd _ startY max: endY.
						spanLeft _ spanLeft min: (xMinEnd min: (xMinEnd+controlX) / 2.0).
						spanRight _ spanRight max: (xMaxEnd max: (xMaxEnd+controlX) / 2.0).
						spanTop _ spanTop min: (yMinEnd min: (yMinEnd+controlY) / 2.0).
						spanBottom _ spanBottom max: (yMaxEnd max: (yMaxEnd+controlY) / 2.0).
						"Case t = 0.0"
						x _ startX.
						y _ startY.
						self updateAlphasWPZeroStrokeForX: x y: y.
						self updateEdgeCountWPAtX: x y: y.
						"Will be corrected for each hop. This, being close to pointFrom, is a good initial guess for first correction."
						self cCode: 'dx = fabs(endX-startX); dy = fabs(endY-startY);'
						inSmalltalk: [ dx _ (endX-startX) abs. dy _ (endY-startY) abs ].
						increment _ 0.5 / (dx max: dy) min: 0.5.
						"Compute Quadratic Bezier Curve,"
						t _ 0.0.
						[
							t0 _ t. x0 _ x. y0 _ y.
							"Compute next point"
							t _ t0 + increment. oneLessT _ 1.0 - t.
							f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
							x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
							y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
							"Now adjust the increment to aim at the required hop length, and recompute next point."
							dx _ x-x0. dy _ y-y0.
							self cCode: '
								length = sqrt(dx*dx + dy*dy);'
								inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
							correction _ hop / length.
							[
								increment _ increment / length * hop.
								t _ t0 + increment. oneLessT _ 1.0 - t.
								f1 _ oneLessT * oneLessT. f2 _ 2.0 * oneLessT * t. f3 _ t * t.
								x _ (f1 * startX) + (f2 * controlX) + (f3 * endX).
								y _ (f1 * startY) + (f2 * controlY) + (f3 * endY).
								dx _ x-x0. dy _ y-y0.
								self cCode: '
									length = sqrt(dx*dx + dy*dy);'
									inSmalltalk: [ length _ ((dx*dx) + (dy*dy)) sqrt ].
								correction _ hop / length.
								correction < 1.0]  whileTrue.		   "Keep adjusting if hop would be too big"
							t < 1.0 ]
						whileTrue: [
							self updateAlphasWPZeroStrokeForX: x y: y.
							self updateEdgeCountWPAtX: x y: y ].
						"Note: For TrueType font definitions, we assume that all contour fragments start exactly where the previous ends.
						This means that the end point is only added for the last fragment of the contour, and not for each one of them."
						startX _ endX.
						startY _ endY.	
					].
					self updateAlphasWPZeroStrokeForX: endX y: endY.
					self updateEdgeCountWPAtX: endX y: endY.
					"Similar effect to ensureClosePath in #finishPath:,
					but assume the TrueType definition is essentially right, and there might only be a rounding error.
					So, don't draw a line, but just (possibly) correct edgeCountsWP. The possibility of rounding error is most likely zero.
					Anyway, this is cheap."
					self updateEdgeCountWPAtX: contourStartX y: contourStartY.
				].
				nextGlyphX _ nextGlyphX + advanceWidth.
				baseIndex _ 0.
			]
	].
	txA11 _ txA11 / sx.
	txA12 _ txA12 / sy.
	txA21 _ txA21 / sx.
	txA22 _ txA22 / sy.
	answer _ nextGlyphX * sx.
	^answer asOop: Float! !

!VectorEnginePlugin methodsFor: 'whole pixel - text and multi paths' stamp: 'dtl 7/27/2021 16:42:07'!
pathSequenceWP: aFloat32Array size: size edgeCounts: otherByteArray alphaMask: anotherByteArray contour: otherFloat32Array

	| i commandType startX startY endX endY control1X control1Y control2X control2Y |
	self
		primitive: 'primPathSequenceWP'
		parameters: #(Float32Array SmallInteger ByteArray ByteArray Float32Array).

	self var: #startX type: 'float'.
	self var: #startY type: 'float'.
	self var: #endX type: 'float'.
	self var: #endY type: 'float'.
	self var: #control1X type: 'float'.
	self var: #control1Y type: 'float'.
	self var: #control2X type: 'float'.
	self var: #control2Y type: 'float'.

	edgeCountsWP _ otherByteArray.
	alphaMaskWP _ anotherByteArray.
	contour _ otherFloat32Array.
	i _ 0.
	[ i < size ] whileTrue: [
		commandType _ (aFloat32Array at: i) asInteger. i _ i + 1.
		commandType caseOf: {
			[0] -> [
				i+1 < size ifFalse: [ ^self "failure" ].
				startX _ aFloat32Array at: i. i _ i + 1.
				startY _ aFloat32Array at: i. i _ i + 1.
				self initializeTrajectoryFragment.
				].
			[1] -> [
				i+1 < size ifFalse: [ ^self "failure" ].
				endX _ aFloat32Array at: i. i _ i + 1.
				endY _ aFloat32Array at: i. i _ i + 1.
				self pvt_lineWPFromX: startX y: startY toX: endX y: endY.
				startX _ endX.
				startY _ endY.
				].
			[2] -> [
				i+3 < size ifFalse: [ ^self "failure" ].
				endX _ aFloat32Array at: i. i _ i + 1.
				endY _ aFloat32Array at: i. i _ i + 1.
				control1X _ aFloat32Array at: i. i _ i + 1.
				control1Y _ aFloat32Array at: i. i _ i + 1.
				self pvt_quadraticBezierWPFromX: startX y: startY
					toX: endX y: endY
					controlX: control1X y: control1Y.
				startX _ endX.
				startY _ endY.
				].
			[3] -> [
				i+5 < size ifFalse: [ ^self "failure" ].
				endX _ aFloat32Array at: i. i _ i + 1.
				endY _ aFloat32Array at: i. i _ i + 1.
				control1X _ aFloat32Array at: i. i _ i + 1.
				control1Y _ aFloat32Array at: i. i _ i + 1.
				control2X _ aFloat32Array at: i. i _ i + 1.
				control2Y _ aFloat32Array at: i. i _ i + 1.
				self pvt_cubicBezierWPFromX: startX y: startY
					toX: endX y: endY
					control1X: control1X y: control1Y
					control2X: control2X y: control2Y.
				startX _ endX.
				startY _ endY.
				]}
		otherwise: [ ^self "failure"]].! !



More information about the Cuis-dev mailing list