Skip to content

Commit

Permalink
refactoring FreeTypeFontProvider>>#updateFromFile:
Browse files Browse the repository at this point in the history
  • Loading branch information
Hely committed May 6, 2024
1 parent 55cbcc0 commit c146abb
Show file tree
Hide file tree
Showing 4 changed files with 105 additions and 105 deletions.
63 changes: 63 additions & 0 deletions src/EmbeddedFreeType/AbstractFreeTypeFontFile.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,63 @@
"
Abstract superclass for a FreeType font installer/updator
"
Class {
#name : 'AbstractFreeTypeFontFile',
#superclass : 'Object',
#instVars : [
'fileInfoProvider',
'face',
'numFaces',
'index'
],
#category : 'EmbeddedFreeType-Installation',
#package : 'EmbeddedFreeType',
#tag : 'Installation'
}

{ #category : 'testing' }
AbstractFreeTypeFontFile class >> isAbstract [

^ self == AbstractFreeTypeFontFile
]

{ #category : 'accessing' }
AbstractFreeTypeFontFile >> cachedNumFacesFromData: bytes [

| cachedInfo cachedNumFaces |
[
(cachedInfo := self fileInfoProvider
validEmbeddedCachedInfoFor: bytes
index: index) isNotNil ] whileTrue: [
index = 0 ifTrue: [ cachedNumFaces := cachedInfo numFaces ].
self fileInfoProvider addFirstFileInfo: cachedInfo index: index.
index := index + 1 ].
^ cachedNumFaces
]

{ #category : 'accessing' }
AbstractFreeTypeFontFile >> fileInfoProvider [

^ fileInfoProvider
]

{ #category : 'accessing' }
AbstractFreeTypeFontFile >> fileInfoProvider: anObject [

fileInfoProvider := anObject
]

{ #category : 'accessing' }
AbstractFreeTypeFontFile >> isAlreadyCached: cachedNumFaces [

^ cachedNumFaces isNotNil and: [ index >= cachedNumFaces ]
]

{ #category : 'accessing' }
AbstractFreeTypeFontFile >> isValidFace [

^ face isNotNil and: [
face height isNotNil and: [
face hasFamilyName and: [
face hasStyleName and: [ face isValid ] ] ] ]
]
49 changes: 1 addition & 48 deletions src/EmbeddedFreeType/FreeTypeFontFileInstaller.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,7 @@ Install Free Types Fonts from a file.
"
Class {
#name : 'FreeTypeFontFileInstaller',
#superclass : 'Object',
#instVars : [
'fileInfoProvider',
'face',
'numFaces',
'index'
],
#superclass : 'AbstractFreeTypeFontFile',
#category : 'EmbeddedFreeType-Installation',
#package : 'EmbeddedFreeType',
#tag : 'Installation'
Expand Down Expand Up @@ -53,20 +47,6 @@ FreeTypeFontFileInstaller >> addFromFileContents: bytes baseName: originalFileBa
index < numFaces ] whileTrue: [ ]
]

{ #category : 'accessing' }
FreeTypeFontFileInstaller >> cachedNumFacesFromData: bytes [

| cachedInfo cachedNumFaces |
[
(cachedInfo := self fileInfoProvider
validEmbeddedCachedInfoFor: bytes
index: index) isNotNil ] whileTrue: [
index = 0 ifTrue: [ cachedNumFaces := cachedInfo numFaces ].
self fileInfoProvider addFirstFileInfo: cachedInfo index: index.
index := index + 1 ].
^ cachedNumFaces
]

{ #category : 'error handling' }
FreeTypeFontFileInstaller >> failedToOpen: face index: index [
"Transcript cr; show: 'Failed : ', path asString, '[', i asString,']'."
Expand All @@ -91,33 +71,6 @@ FreeTypeFontFileInstaller >> fileInfoFromBytes: bytes filename: originalFileBase
yourself
]

{ #category : 'accessing' }
FreeTypeFontFileInstaller >> fileInfoProvider [

^ fileInfoProvider
]

{ #category : 'accessing' }
FreeTypeFontFileInstaller >> fileInfoProvider: anObject [

fileInfoProvider := anObject
]

{ #category : 'accessing' }
FreeTypeFontFileInstaller >> isAlreadyCached: cachedNumFaces [

^ cachedNumFaces isNotNil and: [ index >= cachedNumFaces ]
]

{ #category : 'accessing' }
FreeTypeFontFileInstaller >> isValidFace [

^ face isNotNil and: [
face height isNotNil and: [
face hasFamilyName and: [
face hasStyleName and: [ face isValid ] ] ] ]
]

{ #category : 'accessing' }
FreeTypeFontFileInstaller >> newFaceFromData: externalMem [

Expand Down
53 changes: 39 additions & 14 deletions src/EmbeddedFreeType/FreeTypeFontFileUpdator.class.st
Original file line number Diff line number Diff line change
@@ -1,11 +1,29 @@
"
update Free Types Fonts from a file.
"
Class {
#name : 'FreeTypeFontFileUpdator',
#superclass : 'FreeTypeFontFileInstaller',
#superclass : 'AbstractFreeTypeFontFile',
#category : 'EmbeddedFreeType-Installation',
#package : 'EmbeddedFreeType',
#tag : 'Installation'
}

{ #category : 'instance creation' }
FreeTypeFontFileUpdator class >> withFileInfoProvider: anFreeTypeFontProvider [

^ self new fileInfoProvider: anFreeTypeFontProvider
]

{ #category : 'loading and updating' }
FreeTypeFontFileUpdator >> addAndCacheFileInfoFromPath: path file: aFile [

| info |
info := self fileInfoFromPath: path file: aFile.
self fileInfoProvider addFileInfo: info index: index.
self fileInfoProvider cacheFileInfo: info index: index
]

{ #category : 'error handling' }
FreeTypeFontFileUpdator >> failedToOpen: face from: path index: i [
"Transcript cr; show: 'Failed : ', path asString, '[', i asString,']'."
Expand Down Expand Up @@ -33,31 +51,38 @@ FreeTypeFontFileUpdator >> fileInfoFromPath: path file: aFile [
yourself
]

{ #category : 'instance creation' }
FreeTypeFontFileUpdator >> newFaceFromPath: path [

| newFace |
newFace := FreeTypeFace basicNew
filename: path;
index: index.
^ [
newFace newFaceFromFile: path index: index.
newFace loadFields.
newFace ]
on: FT2Error , PrimitiveFailed
do: [ :e | nil ]
]

{ #category : 'loading and updating' }
FreeTypeFontFileUpdator >> updateFromFile: aFile [

| info cachedNumFaces path |
| cachedNumFaces path |
index := 0.
cachedNumFaces := self cachedNumFacesFromData: aFile.

(self isAlreadyCached: cachedNumFaces) ifTrue: [ ^ self ].

path := aFile fullName utf8Encoded asString.
[
[face := FreeTypeFace basicNew filename: path; index: index.
face newFaceFromFile: path index: index.
face loadFields]
on: FT2Error, PrimitiveFailed
do: [:e | ^self failedToOpen: face from: path index: index ].
(self isValidFace )
face := self newFaceFromPath: path.
self isValidFace
ifFalse: [ ^ self failedToOpen: face from: path index: index ]
ifTrue: [
numFaces ifNil: [ numFaces := face numFaces ].
info := self fileInfoFromPath: path file: aFile.
self fileInfoProvider addFileInfo: info index: index.
self fileInfoProvider cacheFileInfo: info index: index
"Transcript show: 'from file : ', info asString." ].
self addAndCacheFileInfoFromPath: path file: aFile ].
index := index + 1.
index < numFaces "note, we use < rather than <= , because i is zero based" ]
whileTrue: [ ]
index < numFaces ] whileTrue: [ ]
]
45 changes: 2 additions & 43 deletions src/FreeType/FreeTypeFontProvider.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -421,49 +421,8 @@ FreeTypeFontProvider >> updateFromDirectory: aDirectory done: aSet [

{ #category : 'loading and updating' }
FreeTypeFontProvider >> updateFromFile: aFile [
| i face numFaces cachedInfo info cachedNumFaces path |

i:= 0.
[(cachedInfo := self validCachedInfoFor: aFile index: i) isNotNil]
whileTrue:[
i = 0 ifTrue: [ cachedNumFaces := cachedInfo numFaces ].
self addFileInfo: cachedInfo index: i.
i := i + 1.].

(cachedNumFaces isNotNil and:[ i >= cachedNumFaces ]) ifTrue:[ ^ self ].

path := aFile fullName utf8Encoded asString.
[face := FreeTypeFace basicNew filename: path; index: i.
["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"
face newFaceFromFile: path index: i.
face loadFields]
on: FT2Error, PrimitiveFailed
do: [:e | ^self failedToOpen: face from: path index: i ].
(face height isNotNil and:[face hasFamilyName and:[face hasStyleName and:[face isValid]]])
ifFalse: [ ^self failedToOpen:face from: path index: i ]
ifTrue: [
numFaces ifNil: [numFaces := face numFaces].
info :=FreeTypeFileInfo new
absoluteOrRelativePath: aFile path isAbsolute;
absolutePath: path; "used for quick lookup on same platform"
locationType: #default;
index: i;
fileSize: aFile size;
modificationTime: aFile modificationTime;
familyName: face familyName;
styleName: face styleName;
postscriptName: face postscriptName;
bold: face isBold;
italic: face isItalic;
fixedWidth: face isFixedWidth;
numFaces: numFaces;
extractAttributesFromNames;
yourself.
self addFileInfo: info index: i.
self cacheFileInfo: info index: i.
"Transcript show: 'from file : ', info asString."].
i := i + 1.
i < numFaces "note, we use < rather than <= , because i is zero based"] whileTrue:[]

(FreeTypeFontFileUpdator withFileInfoProvider: self) updateFromFile: aFile
]

{ #category : 'loading and updating' }
Expand Down

0 comments on commit c146abb

Please sign in to comment.