Grafoscopio/src/Grafoscopio/GrafoscopioDisplayScanner.c...

424 lines
13 KiB
Smalltalk

Class {
#name : #GrafoscopioDisplayScanner,
#superclass : #Object,
#instVars : [
'destX',
'lastIndex',
'stopConditions',
'text',
'textStyle',
'alignment',
'leftMargin',
'rightMargin',
'font',
'line',
'runStopIndex',
'spaceCount',
'spaceWidth',
'emphasisCode',
'kern',
'pendingKernX',
'bitBlt',
'lineY',
'runX',
'foregroundColor',
'fillBlt',
'morphicOffset',
'ignoreColorChanges',
'destY'
],
#classVars : [
'DefaultStopConditions',
'PaddedSpaceCondition'
],
#category : #'Grafoscopio-Rub'
}
{ #category : #queries }
GrafoscopioDisplayScanner class >> defaultFont [
^ TextStyle defaultFont
]
{ #category : #'class initialization' }
GrafoscopioDisplayScanner class >> initialize [
"
RubCharacterScanner initialize
"
| a |
a := RubTextStopConditions new.
a at: 1 + 1 put: #embeddedObject.
a at: Character tab asciiValue + 1 put: #tab.
a at: Character cr asciiValue + 1 put: #cr.
a at: Character lf asciiValue + 1 put: #cr.
DefaultStopConditions := a .
PaddedSpaceCondition := a copy.
PaddedSpaceCondition at: Character space asciiValue + 1 put: #paddedSpace.
]
{ #category : #private }
GrafoscopioDisplayScanner >> addEmphasis: code [
"Set the bold-ital-under-strike emphasis."
emphasisCode := emphasisCode bitOr: code
]
{ #category : #private }
GrafoscopioDisplayScanner >> addKern: kernDelta [
"Set the current kern amount."
kern := kern + kernDelta
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> cr [
"When a carriage return is encountered, simply increment the pointer
into the paragraph."
pendingKernX := 0.
(lastIndex < text size and: [(text at: lastIndex) = Character cr and: [(text at: lastIndex+1) = Character lf]])
ifTrue: [lastIndex := lastIndex + 2]
ifFalse: [lastIndex := lastIndex + 1].
^false
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> crossedX [
"This condition will sometimes be reached 'legally' during display, when,
for instance the space that caused the line to wrap actually extends over
the right boundary. This character is allowed to display, even though it
is technically outside or straddling the clipping ectangle since it is in
the normal case not visible and is in any case appropriately clipped by
the scanner."
^ true
]
{ #category : #displaying }
GrafoscopioDisplayScanner >> displayEmbeddedForm: aForm [
aForm
displayOn: bitBlt destForm
at: destX @ (lineY + line baseline - aForm height)
clippingBox: bitBlt clipRect
rule: Form blend
fillColor: Color white
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> displayLine: textLine offset: offset [
"The call on the primitive (scanCharactersFrom:to:in:rightX:) will be interrupted according to an array of stop conditions passed to the scanner at which time the code to handle the stop condition is run and the call on the primitive continued until a stop condition returns true (which means the line has terminated). leftInRun is the # of characters left to scan in the current run; when 0, it is time to call setStopConditions."
| stopCondition baselineY lastPos bundle |
offset traceCr.
line := textLine.
morphicOffset := offset.
lineY := textLine top + offset y.
rightMargin := (textLine rightMargin + offset x).
lastIndex := textLine first.
self setStopConditions.
leftMargin := (textLine leftMarginForAlignment: alignment) + offset x.
destX := runX := leftMargin.
self fillTextBackgroundAt: lineY .
lastIndex := textLine first.
baselineY := lineY + textLine baseline.
destY := baselineY - font ascent.
runStopIndex := textLine last.
spaceCount := 0.
[
lastPos := destX@destY.
destY = 388 ifTrue: [ self haltOnce ].
lastPos traceCr.
bundle := textLine scanAndDrawCharactersFrom: lastIndex to: runStopIndex
in: text rightX: rightMargin stopConditions: stopConditions
kern: kern firstDestX:destX style: textStyle on: bitBlt at: lastPos withBaseline: baselineY.
lastIndex := bundle first.
stopCondition := bundle second.
pendingKernX := bundle third.
destX := bundle fourth.
"textLine display: text textStyle: textStyle on: bitBlt at: lastPos startDrawingAt: destX withBaseline: baselineY from: startIndex upTo: (stopCondition == #endOfRun ifTrue:[lastIndex] ifFalse:[lastIndex-1]) ."
" textLine display: text with: font with: kern on: bitBlt at: lastPos destX: destX baseline: baselineY startIndex: startIndex lastIndex:(stopCondition == #endOfRun ifTrue:[lastIndex] ifFalse:[lastIndex-1]) emphasisCode: emphasisCode."
self perform: stopCondition.
] whileFalse.
^ {stopCondition . runStopIndex - lastIndex} "Number of characters remaining in the current run"
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> embeddedObject [
| savedIndex |
savedIndex := lastIndex.
text
attributesAt: lastIndex
do: [ :attr |
attr anchoredMorph
ifNotNil: [
"Following may look strange but logic gets reversed.
If the morph fits on this line we're not done (return false for true)
and if the morph won't fit we're done (return true for false)"
(self placeEmbeddedObject: attr anchoredMorph)
ifFalse: [ ^ true ] ] ].
lastIndex := savedIndex + 1. "for multiple(!) embedded morphs"
^ false
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> endOfRun [
"The end of a run in the display case either means that there is actually
a change in the style (run code) to be associated with the string or the
end of this line has been reached."
| runLength |
lastIndex >=( line last - 1) ifTrue: [^true].
runX := destX.
runLength := text runLengthFor: (lastIndex := lastIndex + 1).
runStopIndex := lastIndex + (runLength - 1) min: line last.
self setStopConditions.
^ false
]
{ #category : #displaying }
GrafoscopioDisplayScanner >> fillTextBackgroundAt: aPosition [
fillBlt == nil ifFalse:
["Not right"
fillBlt destX: line left destY: aPosition
width: line width left height: line lineHeight; copyBits].
]
{ #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> initialize [
super initialize.
destX := destY := leftMargin := 0
]
{ #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> isBreakableAt: index in: sourceString in: encodingClass [
^ encodingClass isBreakableAt: index in: sourceString.
]
{ #category : #'text constants' }
GrafoscopioDisplayScanner >> justified [
^ 3
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> leadingTab [
"return true if only tabs lie to the left"
line first to: lastIndex do:
[:i | (text at: i) == Character tab ifFalse: [^ false]].
^ true
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> nextTabXFrom: anX [
"Tab stops are distances from the left margin. Set the distance into the
argument, anX, normalized for the paragraph's left margin."
| normalizedX tabX mx |
mx := 9999.
normalizedX := anX - leftMargin.
tabX := self tabWidth.
[ tabX <= normalizedX and: [ tabX < mx ] ] whileTrue: [ tabX := tabX + self tabWidth ].
^ tabX < mx
ifTrue: [ leftMargin + tabX min: rightMargin ]
ifFalse: [ rightMargin ]
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> paddedSpace [
"Each space is a stop condition when the alignment is right justified.
Padding must be added to the base width of the space according to
which space in the line this space is and according to the amount of
space that remained at the end of the line when it was composed."
spaceCount := spaceCount + 1.
destX := destX + spaceWidth + (line justifiedPadFor: spaceCount font: font).
lastIndex := lastIndex + 1.
pendingKernX := 0.
^ false
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> placeEmbeddedObject: anchoredMorph [
anchoredMorph relativeTextAnchorPosition ifNotNil:[
anchoredMorph position:
anchoredMorph relativeTextAnchorPosition +
(anchoredMorph owner bounds origin x @ 0)
- (0@morphicOffset y) + (0@lineY).
^true
].
(self superPlaceEmbeddedObject: anchoredMorph) ifFalse: [^ false].
anchoredMorph isMorph ifTrue: [
anchoredMorph position: ((destX - anchoredMorph width)@lineY) - morphicOffset
] ifFalse: [
destY := lineY.
runX := destX.
anchoredMorph
displayOn: bitBlt destForm
at: destX - anchoredMorph width @ destY
clippingBox: bitBlt clipRect
rule: Form blend
fillColor: Color white
].
^ true
]
{ #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> registerBreakableIndex [
"Record left x and character index of the line-wrappable point.
The default implementation here does nothing."
^ false.
]
{ #category : #private }
GrafoscopioDisplayScanner >> setActualFont: aFont [
"Set the basal font to an isolated font reference."
font := aFont
]
{ #category : #private }
GrafoscopioDisplayScanner >> setAlignment: style [
alignment := style.
]
{ #category : #private }
GrafoscopioDisplayScanner >> setConditionArray: aSymbol [
aSymbol == #paddedSpace ifTrue: [^stopConditions := PaddedSpaceCondition "copy"].
aSymbol == nil ifTrue: [^stopConditions := DefaultStopConditions "copy"].
self error: 'undefined stopcondition for space character'.
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> setFont [
| priorFont baselineY |
foregroundColor := Smalltalk ui theme textColor.
text ifNil:[ ^ self setActualFont: textStyle defaultFont ].
"Set the font and other emphasis."
priorFont := font.
text == nil
ifFalse: [
emphasisCode := 0.
kern := 0.
alignment := textStyle alignment.
font := nil.
(text attributesAt: lastIndex forStyle: textStyle) do: [ :att | att emphasizeScanner: self ] ].
font == nil
ifTrue: [ self setActualFont: textStyle defaultFont ].
font := font emphasized: emphasisCode.
priorFont
ifNotNil: [
font = priorFont
ifTrue: [
"font is the same, perhaps the color has changed?
We still want kerning between chars of the same
font, but of different color. So add any pending kern to destX"
destX := destX + (pendingKernX ifNil: [ 0 ]) ].
destX := destX + priorFont descentKern ].
pendingKernX := 0. "clear any pending kern so there is no danger of it being added twice"
destX := destX - font descentKern. "NOTE: next statement should be removed when clipping works"
leftMargin ifNotNil: [ destX := destX max: leftMargin ].
kern := kern - font baseKern. "Install various parameters from the font."
spaceWidth := font widthOf: Character space. " map := font characterToGlyphMap."
stopConditions := DefaultStopConditions.
font installOn: bitBlt foregroundColor: foregroundColor backgroundColor: Color transparent.
text ifNotNil:[
destY := lineY + line baseline - font ascent].
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> setFont: aNumber [
self setActualFont: (textStyle fontAt: aNumber)
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> setPort: aBitBlt [
"Install the BitBlt to use"
bitBlt := aBitBlt.
bitBlt sourceX: 0; width: 0. "Init BitBlt so that the first call to a primitive will not fail"
bitBlt sourceForm: nil. "Make sure font installation won't be confused"
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> setStopConditions [
"Set the font and the stop conditions for the current run."
self setFont.
self setConditionArray: (alignment = self justified ifTrue: [#paddedSpace]).
"
alignment = self justified ifTrue: [
stopConditions == DefaultStopConditions
ifTrue:[stopConditions := stopConditions copy].
stopConditions at: Character space asciiValue + 1 put: #paddedSpace]
"
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> superPlaceEmbeddedObject: anchoredMorph [
"Place the anchoredMorph or return false if it cannot be placed.
In any event, advance destX by its width."
| w |
"Workaround: The following should really use #textAnchorType"
anchoredMorph relativeTextAnchorPosition ifNotNil:[^true].
destX := destX + (w := anchoredMorph width).
(destX > rightMargin and: [(leftMargin + w) <= rightMargin])
ifTrue: ["Won't fit, but would on next line"
^ false].
lastIndex := lastIndex + 1.
^ true
]
{ #category : #private }
GrafoscopioDisplayScanner >> text: t textStyle: ts foreground: foreColor background: backColor fillBlt: blt ignoreColorChanges: shadowMode [
text := t.
textStyle := ts.
foregroundColor := foreColor.
backColor isTransparent
ifFalse: [ fillBlt := blt.
fillBlt fillColor: backColor ].
ignoreColorChanges := shadowMode
]
{ #category : #private }
GrafoscopioDisplayScanner >> textColor: textColor [
ignoreColorChanges ifTrue: [^ self].
foregroundColor := textColor
]
{ #category : #'as yet unclassified' }
GrafoscopioDisplayScanner >> textStyle [
^ textStyle
]
{ #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> widthOf: char inFont: aFont [
(char isMemberOf: CombinedChar) ifTrue: [
^ aFont widthOf: char base.
] ifFalse: [
^ aFont widthOf: char.
].
]