diff --git a/src/Deprecated90/AbstractFont.extension.st b/src/Deprecated90/AbstractFont.extension.st new file mode 100644 index 00000000000..7e1d02fee00 --- /dev/null +++ b/src/Deprecated90/AbstractFont.extension.st @@ -0,0 +1,9 @@ +Extension { #name : #AbstractFont } + +{ #category : #'*Deprecated90' } +AbstractFont >> scanMultibyteJapaneseCharactersFrom: startIndex to: stopIndex in: aWideString with: aCharacterScanner rightX: rightX [ + "scan a multibyte Japanese character string" + self deprecated: 'Deprecated similar to JapaneseEnvironment in Pharo 9'. + ^aCharacterScanner scanJapaneseCharactersFrom: startIndex to: stopIndex in: aWideString rightX: rightX + +] diff --git a/src/Deprecated90/CharacterScanner.extension.st b/src/Deprecated90/CharacterScanner.extension.st new file mode 100644 index 00000000000..31a01edb828 --- /dev/null +++ b/src/Deprecated90/CharacterScanner.extension.st @@ -0,0 +1,37 @@ +Extension { #name : #CharacterScanner } + +{ #category : #'*Deprecated90' } +CharacterScanner >> isBreakableAt: index in: sourceString in: encodingClass [ +"check with the encoding whether the character at index is a breakable character. +Only the JISX0208 & JapaneseEnvironments ever return true, so only the scanJapaneseCharacters... method calls this" + self deprecated: 'Deprecated similar to JapaneseEnvironment in Pharo 9'. + ^ encodingClass isBreakableAt: index in: sourceString. + +] + +{ #category : #'*Deprecated90' } +CharacterScanner >> scanJapaneseCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX [ +"this is a scanning method for +multibyte Japanese characters in a WideString - hence the isBreakable:in:in: +a font that does not do character-pair kerning " + + | ascii encoding nextDestX char charset | + self deprecated: 'Deprecated similar to JapaneseEnvironment in Pharo 9'. + lastIndex := startIndex. + lastIndex > stopIndex ifTrue: [^self handleEndOfRunAt: stopIndex]. + charset := EncodedCharSet charsetAt: 0. + [lastIndex <= stopIndex] whileTrue: [ + char := sourceString at: lastIndex. + ascii := char charCode. + (encoding = 0 and: [ascii < 256 and:[(stopConditions at: ascii + 1) ~~ nil]]) + ifTrue: [^ stopConditions at: ascii + 1]. + (self isBreakableAt: lastIndex in: sourceString in: charset) + ifTrue: [ self registerBreakableIndex]. + nextDestX := destX + (font widthOf: char). + nextDestX > rightX + ifTrue: [^#crossedX]. + destX := nextDestX + kern. + lastIndex := lastIndex + 1. + ]. + ^self handleEndOfRunAt: stopIndex +] diff --git a/src/Fonts-Abstract/AbstractFont.class.st b/src/Fonts-Abstract/AbstractFont.class.st index fa9e0f91ca5..63d71789900 100644 --- a/src/Fonts-Abstract/AbstractFont.class.st +++ b/src/Fonts-Abstract/AbstractFont.class.st @@ -220,13 +220,6 @@ AbstractFont >> releaseCachedState [ ] -{ #category : #'as yet unclassified' } -AbstractFont >> scanMultibyteJapaneseCharactersFrom: startIndex to: stopIndex in: aWideString with: aCharacterScanner rightX: rightX [ - "scan a multibyte Japanese character string" - ^aCharacterScanner scanJapaneseCharactersFrom: startIndex to: stopIndex in: aWideString rightX: rightX - -] - { #category : #metrics } AbstractFont >> strikeoutThickness [ ^ 0 diff --git a/src/Text-Scanning/CharacterScanner.class.st b/src/Text-Scanning/CharacterScanner.class.st index 21698b08411..6c20ccdc96a 100644 --- a/src/Text-Scanning/CharacterScanner.class.st +++ b/src/Text-Scanning/CharacterScanner.class.st @@ -266,14 +266,6 @@ CharacterScanner >> initialize [ destX := destY := leftMargin := 0. ] -{ #category : #'as yet unclassified' } -CharacterScanner >> isBreakableAt: index in: sourceString in: encodingClass [ -"check with the encoding whether the character at index is a breakable character. -Only the JISX0208 & JapaneseEnvironments ever return true, so only the scanJapaneseCharacters... method calls this" - ^ encodingClass isBreakableAt: index in: sourceString. - -] - { #category : #private } CharacterScanner >> leadingTab [ "return true if only tabs lie to the left" @@ -336,32 +328,6 @@ CharacterScanner >> scanCharactersFrom: startIndex to: stopIndex in: sourceStrin ^sourceString scanCharactersFrom: startIndex to: stopIndex with: self rightX: rightX font: font ] -{ #category : #'as yet unclassified' } -CharacterScanner >> scanJapaneseCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX [ -"this is a scanning method for -multibyte Japanese characters in a WideString - hence the isBreakable:in:in: -a font that does not do character-pair kerning " - - | ascii encoding nextDestX char charset | - lastIndex := startIndex. - lastIndex > stopIndex ifTrue: [^self handleEndOfRunAt: stopIndex]. - charset := EncodedCharSet charsetAt: 0. - [lastIndex <= stopIndex] whileTrue: [ - char := sourceString at: lastIndex. - ascii := char charCode. - (encoding = 0 and: [ascii < 256 and:[(stopConditions at: ascii + 1) ~~ nil]]) - ifTrue: [^ stopConditions at: ascii + 1]. - (self isBreakableAt: lastIndex in: sourceString in: charset) - ifTrue: [ self registerBreakableIndex]. - nextDestX := destX + (font widthOf: char). - nextDestX > rightX - ifTrue: [^#crossedX]. - destX := nextDestX + kern. - lastIndex := lastIndex + 1. - ]. - ^self handleEndOfRunAt: stopIndex -] - { #category : #scanning } CharacterScanner >> scanKernableByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX [ "this is a scanning method for