Grafoscopio/src/Grafoscopio/GrafoscopioLine.class.st

328 lines
8.3 KiB
Smalltalk

Class {
#name : #GrafoscopioLine,
#superclass : #Object,
#instVars : [
'from',
'to',
'bounds',
'text',
'styler',
'fontCode',
'lastUsedConfiguration'
],
#category : #'Grafoscopio-Rub'
}
{ #category : #'as yet unclassified' }
GrafoscopioLine >> approximateWidth [
| runs |
text ifNil: [ ^ 1 ].
runs := text runs.
^ ((self first to: self last)
collect: [ :r |
(styler
fontAt: ((runs at: r) detect: [ :a | a isKindOf: TextFontChange ]) fontNumber)
widthOf: $A ]) max * self size * 1.2
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> baseline [
| runs |
text ifNil:[^0] .
runs := text runs.
^ ((self first to: self last)
collect: [ :r |
(styler
fontAt: ((runs at: r) detect: [ :a | a isKindOf: TextFontChange ]) fontNumber)
ascent ]) max
]
{ #category : #accessing }
GrafoscopioLine >> bottom [
^ bounds bottom
]
{ #category : #accessing }
GrafoscopioLine >> bottomRight [
^ bounds bottomRight
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> bounds: aRectangle [
bounds := aRectangle
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> configurationFor: aText with: style at: lastIndex [
| attributes |
attributes := aText attributesAt: lastIndex forStyle: style.
(lastUsedConfiguration isNotNil and: [lastUsedConfiguration attributes = attributes ]) ifFalse: [
lastUsedConfiguration := GrafoscopioLineConfiguration new.
lastUsedConfiguration loadDefaultsFromStyle: style and: attributes.
].
^ lastUsedConfiguration .
]
{ #category : #accessing }
GrafoscopioLine >> display: aText textStyle: style on: bitBlt at: lastPos startDrawingAt: destX withBaseline: baselineY from: startIndex upTo: lastIndex [
| configuration kern font emphasisCode |
configuration := self
configurationFor: aText
with: style
at: lastIndex.
kern := configuration kern.
font := configuration font.
emphasisCode := configuration emphasisCode.
lastIndex >= startIndex
ifTrue: [ [ bitBlt
displayString: (aText extractStringFrom: startIndex to: lastIndex)
from: 1
to: lastIndex - startIndex + 1
at: lastPos
kern: kern
baselineY: baselineY
font: font ]
on: Error
do: [ :e | self halt ] ].
(emphasisCode allMask: 4)
ifTrue: [ font
displayUnderlineOn: bitBlt
from: lastPos x @ baselineY
to: destX @ baselineY ].
(emphasisCode allMask: 16)
ifTrue: [ font
displayStrikeoutOn: bitBlt
from: lastPos x @ baselineY
to: destX @ baselineY ]
]
{ #category : #accessing }
GrafoscopioLine >> first [
^ from
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> fontCodeFor: aGrafoscopioPillarASText [
fontCode
ifNil: [ (aGrafoscopioPillarASText runs at: self first)
do: [ :d | d emphasizeScanner: self ] ].
^ fontCode
]
{ #category : #'instance creation' }
GrafoscopioLine >> from: anInteger to: anInteger2 [
from := anInteger.
to := anInteger2.
bounds := 0@0 corner: 0@0
]
{ #category : #'instance creation' }
GrafoscopioLine >> from: anInteger to: anInteger2 text: aText styler: aStyler [
aText ifNil: [ self halt ].
self from: anInteger to: anInteger2.
text := aText.
styler := aStyler
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> height [
| runs |
text ifNil:[^0] .
runs := text runs.
^ ((self first to: self last)
collect: [ :r |
(styler
fontAt: ((runs at: r) detect: [ :a | a isKindOf: TextFontChange ]) fontNumber)
height ]) max
]
{ #category : #accessing }
GrafoscopioLine >> heightForWidth: aWidth [
| onelineWidth onlineHeight|
onelineWidth := self width.
onlineHeight := self height.
aWidth > onelineWidth ifTrue: [ ^ onlineHeight ].
^((onelineWidth /aWidth )roundUpTo: 1)* onlineHeight
]
{ #category : #accessing }
GrafoscopioLine >> last [
^ to
]
{ #category : #accessing }
GrafoscopioLine >> left [
^ 1
]
{ #category : #accessing }
GrafoscopioLine >> leftMargin [
^ self left
]
{ #category : #accessing }
GrafoscopioLine >> leftMarginForAlignment: anInteger [
^ self left
]
{ #category : #accessing }
GrafoscopioLine >> lineHeight [
^ self height
]
{ #category : #accessing }
GrafoscopioLine >> right [
^ self width
]
{ #category : #accessing }
GrafoscopioLine >> rightMargin [
^ self right
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> scanAndDrawCharactersFrom: startIndex to: stopIndex in: aText rightX: rightX stopConditions: stopConditions kern: kernDelta firstDestX: d style: textStyle on: bitBlt at: lastPos withBaseline: baselineY [
| bundle lastIndex stopCondition destX |
[ bundle := self
scanCharactersFrom: startIndex
to: stopIndex
in: aText
rightX: rightX
stopConditions: stopConditions
kern: kernDelta
firstDestX: d.
lastIndex := bundle first.
stopCondition := bundle second.
destX := bundle fourth.
self
display: aText
textStyle: textStyle
on: bitBlt
at: lastPos
startDrawingAt: destX
withBaseline: baselineY
from: startIndex
upTo:
(stopCondition == #endOfRun
ifTrue: [ lastIndex ]
ifFalse: [ lastIndex - 1 ]).
^ bundle ]
on: SubscriptOutOfBounds
do: [ :e | self halt ]
]
{ #category : #scanning }
GrafoscopioLine >> scanCharactersFrom: startIndex to: stopIndex in: aText rightX: rightX stopConditions: stops kern: kernDelta firstDestX:d [
| ascii encoding f nextDestX maxAscii startEncoding floatDestX widthAndKernedWidth nextChar atEndOfRun font lastIndex pendingKernX destX source |
source := text string.
startIndex > stopIndex
ifTrue: [ lastIndex := stopIndex.
^ {lastIndex . stops endOfRun . 0 . d } ].
lastIndex := startIndex.
startEncoding := (source at: startIndex) leadingChar.
" font := self fontFor: text at: startIndex."
destX := d .
font ifNil: [font := TextStyle defaultFont fontArray at: 1].
font isFontSet ifTrue: [
f := [font fontArray at: startEncoding + 1]
on: Exception do: [:ex | nil].
f ifNil: [ f := font fontArray at: 1].
maxAscii := f maxAscii.
] ifFalse: [
maxAscii := font maxAscii.
].
floatDestX := destX.
widthAndKernedWidth := Array new: 2.
atEndOfRun := false.
[lastIndex <= stopIndex] whileTrue: [
encoding := (source at: lastIndex) leadingChar.
encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stops endOfRun].
ascii := (source at: lastIndex) charCode.
ascii > maxAscii ifTrue: [ascii := maxAscii].
(encoding = 0 and: [ascii < stops size and: [(stops at: ascii + 1) ~~ nil]]) ifTrue: [
^ {lastIndex .(stops at: ascii + 1) . pendingKernX . destX }].
nextChar := (lastIndex + 1 <= stopIndex)
ifTrue:[source at: lastIndex + 1]
ifFalse:[
atEndOfRun := true.
"if there is a next char in sourceString, then get the kern
and store it in pendingKernX"
lastIndex + 1 <= source size
ifTrue:[source at: lastIndex + 1]
ifFalse:[ nil]].
font
widthAndKernedWidthOfLeft: (source at: lastIndex)
right: nextChar
into: widthAndKernedWidth.
nextDestX := floatDestX + (widthAndKernedWidth at: 1).
nextDestX > rightX ifTrue: [^ {lastIndex . stops crossedX . pendingKernX . destX }].
floatDestX := floatDestX + kernDelta + (widthAndKernedWidth at: 2).
atEndOfRun
ifTrue:[
pendingKernX := (widthAndKernedWidth at: 2) - (widthAndKernedWidth at: 1).
floatDestX := floatDestX - pendingKernX].
destX := floatDestX .
lastIndex := lastIndex + 1.
].
lastIndex := stopIndex.
^ {lastIndex . stops endOfRun . pendingKernX . destX }
]
{ #category : #initialization }
GrafoscopioLine >> setFont: anInteger [
fontCode := anInteger
]
{ #category : #accessing }
GrafoscopioLine >> size [
^ (self last - self first ) + 1
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> string [
^ text extractStringFrom: from to: to
]
{ #category : #accessing }
GrafoscopioLine >> top [
^ bounds top
]
{ #category : #accessing }
GrafoscopioLine >> topLeft [
^ bounds topLeft
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> width [
| string runs font |
text ifNil: [ ^1 ].
string := self string.
runs := text runs.
^ (1 to: self size)
inject: 0
into: [ :acc :idx |
font := styler
fontAt:
((runs at: idx) detect: [ :a | a isKindOf: TextFontChange ])
fontNumber.
acc + (font widthOf: (string at: idx)) ]
]
{ #category : #accessing }
GrafoscopioLine >> withThePrevious: anAmountOfCharacters [
^ anAmountOfCharacters = 0
ifTrue: [ self ]
ifFalse: [ self class new
from: from - anAmountOfCharacters - 1
to: to
text: text
styler: styler;
yourself ]
]