File tree Expand file tree Collapse file tree 5 files changed +12
-13
lines changed Expand file tree Collapse file tree 5 files changed +12
-13
lines changed Original file line number Diff line number Diff line change @@ -80,7 +80,7 @@ EmbeddedFreeTypeFontInstaller >> addFromFileContents: bytes baseName: originalF
80
80
[ " we use the primNewFaceFromFile:index: method because we want to do this as fast as possible and we don't need the face registered because it will be explicitly destroyed later"
81
81
face newFaceFromExternalMemory: externalMem index: i.
82
82
face loadFields]
83
- on: FT2Error
83
+ on: FT2Error , PrimitiveFailed
84
84
do: [:e |
85
85
self failedToOpen: face index: i.
86
86
^ self ].
Original file line number Diff line number Diff line change @@ -321,7 +321,7 @@ FreeTypeFont >> getLinearWidthOf: aCharacter [
321
321
face validate.
322
322
face setPixelWidth: em height: em.
323
323
[face loadCharacter: charCode flags: (LoadNoBitmap bitOr: (LoadIgnoreTransform bitOr: " FreeTypeSettings current hintingFlags" 2 " no hinting" ))]
324
- on: FT2Error do: [:e |
324
+ on: FT2Error , PrimitiveFailed do: [:e |
325
325
face loadGlyph: 0 flags: (LoadNoBitmap bitOr: (LoadIgnoreTransform bitOr: FreeTypeSettings current hintingFlags " no hinting" )) ].
326
326
glyph := face glyph.
327
327
la := glyph linearHorizontalAdvance.
@@ -363,7 +363,7 @@ FreeTypeFont >> getWidthOf: aCharacter [
363
363
hintingFlags := FreeTypeSettings current hintingFlags.
364
364
flags := LoadNoBitmap bitOr: ( LoadIgnoreTransform bitOr: hintingFlags).
365
365
[face loadCharacter: charCode flags: flags.
366
- ] on: FT2Error do: [:e | " character not in map?" ^ 0 ].
366
+ ] on: FT2Error , PrimitiveFailed do: [:e | " character not in map?" ^ 0 ].
367
367
glyph := face glyph.
368
368
" When not hinting FreeType sets the advance to the truncated linearAdvance.
369
369
The characters appear squashed together. Rounding is probably better, so we
Original file line number Diff line number Diff line change @@ -380,12 +380,10 @@ FreeTypeFontProvider >> platformImageRelativeDirectories [
380
380
381
381
{ #category : #' file paths' }
382
382
FreeTypeFontProvider >> platformVMRelativeDirectories [
383
-
384
- | directory |
385
- directory := Smalltalk vm path asFileReference / ' Fonts' .
386
- directory exists
387
- ifTrue: [ ^ { directory } ].
388
- ^ #()
383
+ | directory |
384
+ directory := Smalltalk vm directory asFileReference / ' Fonts' .
385
+ directory exists ifTrue: [ ^ {directory} ].
386
+ ^ #()
389
387
]
390
388
391
389
{ #category : #' loading and updating' }
@@ -503,7 +501,7 @@ FreeTypeFontProvider >> updateFromFile: aFile [
503
501
[" we use the primNewFaceFromFile:index: method because we want to do this as fast as possible and we don't need the face registered because it will be explicitly destroyed later"
504
502
face newFaceFromFile: path index: i.
505
503
face loadFields]
506
- on: FT2Error
504
+ on: FT2Error , PrimitiveFailed
507
505
do: [:e | ^ self failedToOpen: face from: path index: i ].
508
506
(face height notNil and :[face hasFamilyName and :[face hasStyleName and :[face isValid]]])
509
507
ifFalse: [ ^ self failedToOpen: face from: path index: i ]
Original file line number Diff line number Diff line change @@ -177,12 +177,13 @@ FreeTypeGlyphRenderer >> renderGlyph: aCharacter depth: depth subpixelPosition:
177
177
hintingFlags := FreeTypeSettings current hintingFlags.
178
178
flags := LoadNoBitmap bitOr: ( LoadIgnoreTransform bitOr: hintingFlags).
179
179
face loadCharacter: charCode flags: flags]
180
- on: FT2Error do: [:e |
180
+ on: FT2Error , PrimitiveFailed do: [:e |
181
181
^ (GlyphForm extent: 0 @0 depth: depth)
182
182
advance: 0 @0 ;
183
183
linearAdvance: 0 @0 ;
184
184
offset: 0 @0 ;
185
- yourself ].
185
+ yourself ].
186
+
186
187
glyph := face glyph.
187
188
slant := aFreeTypeFont simulatedItalicSlant.
188
189
extraWidth := (glyph height * slant) abs ceiling.
Original file line number Diff line number Diff line change @@ -128,7 +128,7 @@ FreeTypeSubPixelAntiAliasedGlyphRenderer >> renderStretchedGlyph: aCharacter dep
128
128
hintingFlags := FreeTypeSettings current hintingFlags.
129
129
flags := LoadNoBitmap bitOr: ( LoadIgnoreTransform bitOr: hintingFlags).
130
130
face loadCharacter: charCode flags: flags.
131
- ] on: FT2Error do: [:e |
131
+ ] on: FT2Error , PrimitiveFailed do: [:e |
132
132
^ (GlyphForm extent: 0 @0 depth: depth)
133
133
advance: 0 @0 ;
134
134
linearAdvance: 0 @0 ;
You can’t perform that action at this time.
0 commit comments