Skip to content

Commit

Permalink
Initial commit of the extended OSWindow generic renderer API with sup…
Browse files Browse the repository at this point in the history
…port for text rendering.
  • Loading branch information
ronsaldo committed Jun 24, 2020
1 parent e9015f1 commit 9874e04
Show file tree
Hide file tree
Showing 17 changed files with 824 additions and 12 deletions.
37 changes: 37 additions & 0 deletions src/Fonts-Abstract/AbstractFont.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -92,6 +92,18 @@ AbstractFont >> basicDescentOf: aCharacter [

]

{ #category : #'glyph lookup' }
AbstractFont >> characterFormAt: aCharacter [
^ nil
]

{ #category : #'glyph lookup' }
AbstractFont >> characterRenderingOptimizedFormAt: aCharacter [
"This method returns a version of the character form which is optimized for rendering
through an accelerated alpha blending equation in the style of the OpenGL glBlendFuncSeparate."
^ (self characterFormAt: aCharacter) ifNotNil: [:form | form invertedAndAlphaMultiplied]
]

{ #category : #accessing }
AbstractFont >> characterToGlyphMap [
"Return the character to glyph mapping table. If the table is not provided the character scanner will query the font directly for the width of each individual character."
Expand Down Expand Up @@ -137,6 +149,11 @@ AbstractFont >> familyName [
^self subclassResponsibility
]

{ #category : #testing }
AbstractFont >> hasSubPixelAntiAliasing [
^ false
]

{ #category : #accessing }
AbstractFont >> height [
"Answer the height of the receiver, total of maximum extents of
Expand Down Expand Up @@ -196,6 +213,16 @@ AbstractFont >> releaseCachedState [

]

{ #category : #metrics }
AbstractFont >> strikeoutThickness [
^ 0
]

{ #category : #metrics }
AbstractFont >> strikeoutTop [
^ 0
]

{ #category : #accessing }
AbstractFont >> textStyle [
^ TextStyle actualTextStyles detect:
Expand All @@ -208,6 +235,16 @@ AbstractFont >> textStyleName [
^self familyName
]

{ #category : #metrics }
AbstractFont >> underlineThickness [
^ 0
]

{ #category : #metrics }
AbstractFont >> underlineTop [
^ 0
]

{ #category : #'development support' }
AbstractFont >> validate [
"Concrete classes should override this to provide validation"
Expand Down
30 changes: 30 additions & 0 deletions src/Fonts-Infrastructure/LogicalFont.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -377,6 +377,11 @@ LogicalFont >> characterFormAt: aCharacter [
^self realFont characterFormAt: aCharacter
]

{ #category : #'glyph lookup' }
LogicalFont >> characterRenderingOptimizedFormAt: aCharacter [
^ self realFont characterRenderingOptimizedFormAt: aCharacter
]

{ #category : #'forwarded to realFont' }
LogicalFont >> characterToGlyphMap [
"Provided only for accelerating text scanning thru primitive 103 - see super."
Expand Down Expand Up @@ -605,6 +610,11 @@ LogicalFont >> hasGlyphsForAll: asciiString [
^self realFont hasGlyphsForAll: asciiString
]

{ #category : #testing }
LogicalFont >> hasSubPixelAntiAliasing [
^ self realFont hasSubPixelAntiAliasing
]

{ #category : #'forwarded to realFont' }
LogicalFont >> height [
^self realFont height
Expand Down Expand Up @@ -790,6 +800,26 @@ LogicalFont >> stretchValue: anObject [
stretchValue := anObject
]

{ #category : #metrics }
LogicalFont >> strikeoutThickness [
^ self realFont strikeoutThickness
]

{ #category : #metrics }
LogicalFont >> strikeoutTop [
^ self realFont strikeoutTop
]

{ #category : #metrics }
LogicalFont >> underlineThickness [
^ self realFont underlineThickness
]

{ #category : #metrics }
LogicalFont >> underlineTop [
^ self realFont underlineTop
]

{ #category : #accessing }
LogicalFont >> weightValue [
"Answer the value of weightValue"
Expand Down
36 changes: 36 additions & 0 deletions src/FreeType/FreeTypeFont.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,17 @@ FreeTypeFont >> characterFormAt: aCharacter [
subpixelPosition: 0]
]

{ #category : #'glyph lookup' }
FreeTypeFont >> characterRenderingOptimizedFormAt: aCharacter [
FreeTypeSettings current useSubPixelAntiAliasing ifFalse: [ ^ super characterRenderingOptimizedFormAt: aCharacter ].

^ (self
glyphOf: aCharacter
destDepth: 32
colorValue: (Color white pixelValueForDepth: 32)
subpixelPosition: 0) withAlphaExtractedFromSubpixelRendering
]

{ #category : #accessing }
FreeTypeFont >> clearCachedMetrics [
widthAndKernedWidthCache := cachedHeight := cachedAscent := cachedDescent := subPixelPositioned := nil
Expand Down Expand Up @@ -469,6 +480,11 @@ FreeTypeFont >> hasGlyphsForAll: asciiString [
^true
]

{ #category : #testing }
FreeTypeFont >> hasSubPixelAntiAliasing [
^ FreeTypeSettings current useSubPixelAntiAliasing
]

{ #category : #comparing }
FreeTypeFont >> hash [
^pointSize hash
Expand Down Expand Up @@ -786,6 +802,16 @@ FreeTypeFont >> simulatedItalicSlant [
^0
]

{ #category : #metrics }
FreeTypeFont >> strikeoutThickness [
^ self underlineThickness
]

{ #category : #metrics }
FreeTypeFont >> strikeoutTop [
^ (((self face ascender / 4) * self pixelSize / self face unitsPerEm) negated - (self strikeoutThickness/2)) rounded.
]

{ #category : #'glyph lookup' }
FreeTypeFont >> subGlyphOf: aCharacter colorValue: aColorValue mono: monoBoolean subpixelPosition: sub [

Expand Down Expand Up @@ -816,6 +842,16 @@ FreeTypeFont >> subPixelPositioned [
subPixelPositioned := settings hinting not or:[settings lightHinting]]
]

{ #category : #metrics }
FreeTypeFont >> underlineThickness [
^ self face underlineThickness * self pixelSize / self face unitsPerEm.
]

{ #category : #metrics }
FreeTypeFont >> underlineTop [
^ ((self face underlinePosition * self pixelSize / self face unitsPerEm) negated - (self underlineThickness/2)) rounded + 1 "needs the +1 , possibly because glyph origins are moved down by 1 so that their baselines line up with strike fonts"
]

{ #category : #validation }
FreeTypeFont >> validate [
self face validate
Expand Down
33 changes: 33 additions & 0 deletions src/FreeType/GlyphForm.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,17 @@ GlyphForm >> asFormOfDepth: d [
^newForm
]

{ #category : #converting }
GlyphForm >> invertedAndAlphaMultiplied [
| result |
result := super invertedAndAlphaMultiplied.
^ (self class extent: result extent depth: result depth bits: result bits)
offset: offset;
advance: advance;
linearAdvance: linearAdvance;
yourself
]

{ #category : #accessing }
GlyphForm >> linearAdvance [
^linearAdvance
Expand All @@ -48,3 +59,25 @@ GlyphForm >> linearAdvance [
GlyphForm >> linearAdvance: aNumber [
^linearAdvance := aNumber
]

{ #category : #converting }
GlyphForm >> withAlphaExtractedFromSubpixelRendering [
| result |
"Take the maximum of r,g,b as the alpha. Then multiply by a."
result := self collectColors: [:c |
| r g b a|
r := c red.
g := c green.
b := c blue.
a := c alpha.
a := ((r max: g) max: b) * a.

Color r: r g: g b: b alpha: a
].

^ (self class extent: result extent depth: result depth bits: result bits)
offset: offset;
advance: advance;
linearAdvance: linearAdvance;
yourself
]
32 changes: 32 additions & 0 deletions src/Graphics-Display Objects/Form.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -277,6 +277,15 @@ Form >> allocateForm: extentPoint [
^Form extent: extentPoint depth: self nativeDepth
]

{ #category : #converting }
Form >> alphaMultiplied [
^ (self asFormOfDepth: 32) collectColors: [ :c |
| a |
a := c alpha.
Color r: c red * a g: c green * a b: c blue * a alpha: a
]
]

{ #category : #converting }
Form >> as8BitColorForm [
"Simple conversion of zero pixels to transparent. Force it to 8 bits."
Expand Down Expand Up @@ -1432,6 +1441,15 @@ Form >> innerPixelRectFor: pv orNot: not [
(xTally findLast: [:t | t>0])@(yTally findLast: [:t | t>0])
]

{ #category : #converting }
Form >> invertedAndAlphaMultiplied [
^ (self asFormOfDepth: 32) collectColors: [ :c |
| a |
a := c alpha.
Color r: (1.0 - c red) * a g: (1.0 - c green) * a b: (1.0 - c blue) * a alpha: a
]
]

{ #category : #testing }
Form >> isAllWhite [
"Answer whether all bits in the receiver are white"
Expand Down Expand Up @@ -2560,6 +2578,20 @@ Form >> wipeImage: otherImage at: topLeft delta: delta clippingBox: clipBox [
ifFalse: [nil]]
]

{ #category : #converting }
Form >> withAlphaExtractedFromSubpixelRendering [
^ (self asFormOfDepth: 32) collectColors: [ :c |
| r g b a|
r := c red.
g := c green.
b := c blue.
a := c alpha.
a := ((r max: g) max: b) * a.

Color r: r g: g b: b alpha: a
]
]

{ #category : #'file in/out' }
Form >> writeAttributesOn: file [
self unhibernate.
Expand Down
6 changes: 6 additions & 0 deletions src/OSWindow-SDL2/AbstractFont.extension.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
Extension { #name : #AbstractFont }

{ #category : #'*OSWindow-SDL2' }
AbstractFont >> createCachedFontForSDL2GenericRenderer: renderer [
^ renderer createTextureAtlasFontCacheFor: self
]
6 changes: 6 additions & 0 deletions src/OSWindow-SDL2/LogicalFont.extension.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
Extension { #name : #LogicalFont }

{ #category : #'*OSWindow-SDL2' }
LogicalFont >> createCachedFontForSDL2GenericRenderer: renderer [
^ renderer getOrCreateCachedFontFor: self realFont
]
1 change: 0 additions & 1 deletion src/OSWindow-SDL2/OSSDL2AthensRenderer.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,6 @@ OSSDL2AthensRenderer >> initializeWindowHandle: aBackendWindow [
renderer := backendWindow sdl2Window createDefaultRenderer.
self resetResources.


]

{ #category : #drawing }
Expand Down
Loading

0 comments on commit 9874e04

Please sign in to comment.