[squeak-dev] The Trunk: Morphic-fbs.661.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jul 2 21:21:15 UTC 2013


Frank Shearar uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-fbs.661.mcz

==================== Summary ====================

Name: Morphic-fbs.661
Author: fbs
Time: 2 July 2013, 10:19:47.213 pm
UUID: 8fa711eb-1495-b14c-aa55-5b7e25d6f96a
Ancestors: Morphic-fbs.660

This nearly severs the Multilingual -> Morphic dependency.

=============== Diff against Morphic-fbs.660 ===============

Item was changed:
  SystemOrganization addCategory: #'Morphic-Balloon'!
  SystemOrganization addCategory: #'Morphic-Basic'!
  SystemOrganization addCategory: #'Morphic-Basic-NewCurve'!
  SystemOrganization addCategory: #'Morphic-Borders'!
  SystemOrganization addCategory: #'Morphic-Collections-Arrayed'!
  SystemOrganization addCategory: #'Morphic-Demo'!
  SystemOrganization addCategory: #'Morphic-Events'!
  SystemOrganization addCategory: #'Morphic-Explorer'!
  SystemOrganization addCategory: #'Morphic-Kernel'!
  SystemOrganization addCategory: #'Morphic-Layouts'!
  SystemOrganization addCategory: #'Morphic-Menus'!
  SystemOrganization addCategory: #'Morphic-Menus-DockingBar'!
  SystemOrganization addCategory: #'Morphic-Models'!
  SystemOrganization addCategory: #'Morphic-Pluggable Widgets'!
  SystemOrganization addCategory: #'Morphic-Support'!
+ SystemOrganization addCategory: #'Morphic-Multilingual'!
  SystemOrganization addCategory: #'Morphic-Text Support'!
+ SystemOrganization addCategory: #'Morphic-ToolBuilder'!
  SystemOrganization addCategory: #'Morphic-TrueType'!
  SystemOrganization addCategory: #'Morphic-Widgets'!
  SystemOrganization addCategory: #'Morphic-Windows'!
  SystemOrganization addCategory: #'Morphic-Worlds'!
- SystemOrganization addCategory: #'Morphic-ToolBuilder'!

Item was added:
+ ----- Method: LinedTTCFont>>computeForm: (in category '*Morphic-Multilingual') -----
+ computeForm: char
+ 
+ 	| ttGlyph scale |
+ 
+ 	char = Character tab ifTrue: [^ super computeForm: char].
+ 
+ 	"char = $U ifTrue: [self doOnlyOnce: [self halt]]."
+ 	scale := self pixelSize asFloat / (ttcDescription ascender - ttcDescription descender).
+ 	ttGlyph := ttcDescription at: char.
+ 	^ ttGlyph asFormWithScale: scale ascender: ttcDescription ascender descender: ttcDescription descender fgColor: foregroundColor bgColor: Color transparent depth: self depth replaceColor: false lineGlyph: lineGlyph lingGlyphWidth: contourWidth emphasis: emphasis!

Item was added:
+ ----- Method: MultiCompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide: (in category '*Morphic-Text Support-scanning') -----
+ composeFrom: startIndex inRectangle: lineRectangle
+ 	firstLine: firstLine leftSide: leftSide rightSide: rightSide
+ 	"Answer an instance of TextLineInterval that represents the next line in the paragraph."
+ 	| runLength stopCondition |
+ 	"Set up margins"
+ 	leftMargin := lineRectangle left.
+ 	leftSide ifTrue: [leftMargin := leftMargin +
+ 						(firstLine ifTrue: [textStyle firstIndent]
+ 								ifFalse: [textStyle restIndent])].
+ 	destX := spaceX := leftMargin.
+ 	firstDestX := destX.
+ 	rightMargin := lineRectangle right.
+ 	rightSide ifTrue: [rightMargin := rightMargin - textStyle rightIndent].
+ 	lastIndex := startIndex.	"scanning sets last index"
+ 	destY := lineRectangle top.
+ 	lineHeight := baseline := 0.  "Will be increased by setFont"
+ 	self setStopConditions.	"also sets font"
+ 	runLength := text runLengthFor: startIndex.
+ 	runStopIndex := (lastIndex := startIndex) + (runLength - 1).
+ 	line := (TextLine start: lastIndex stop: 0 internalSpaces: 0 paddingWidth: 0)
+ 				rectangle: lineRectangle.
+ 	presentationLine := (TextLine start: lastIndex stop: 0 internalSpaces: 0 paddingWidth: 0)
+ 				rectangle: lineRectangle.
+ 	numOfComposition := 0.
+ 	spaceCount := 0.
+ 	self handleIndentation.
+ 	leftMargin := destX.
+ 	line leftMargin: leftMargin.
+ 	presentationLine leftMargin: leftMargin.
+ 
+ 	presentation := TextStream on: (Text fromString: (WideString new: text size)).
+ 
+ 	[stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
+ 		in: text string rightX: rightMargin stopConditions: stopConditions
+ 		kern: kern.
+ 	"See setStopConditions for stopping conditions for composing."
+ 	(self perform: stopCondition)
+ 		ifTrue: [presentationLine lineHeight: lineHeight + textStyle leading
+ 					baseline: baseline + textStyle leading.
+ 				^ line lineHeight: lineHeight + textStyle leading
+ 					baseline: baseline + textStyle leading]] repeat!

Item was added:
+ ----- Method: MultiCompositionScanner>>setFont (in category '*Morphic-Multilingual') -----
+ setFont
+ 	super setFont.
+ 	breakAtSpace := false.
+ 	wantsColumnBreaks == true ifTrue: [
+ 		stopConditions := stopConditions copy.
+ 		stopConditions at: TextComposer characterForColumnBreak asciiValue + 1 put: #columnBreak.
+ 	].
+ !

Item was added:
+ NewParagraph subclass: #MultiNewParagraph
+ 	instanceVariableNames: 'presentationText presentationLines'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'TextConstants'
+ 	category: 'Morphic-Multilingual'!

Item was added:
+ ----- Method: MultiNewParagraph>>displayOn:using:at: (in category 'fonts-display') -----
+ displayOn: aCanvas using: displayScanner at: somePosition
+ 	"Send all visible lines to the displayScanner for display"
+ 
+ 	| visibleRectangle offset leftInRun line |
+ 	visibleRectangle := aCanvas clipRect.
+ 	offset := somePosition - positionWhenComposed.
+ 	leftInRun := 0.
+ 	(self lineIndexForPoint: visibleRectangle topLeft)
+ 		to: (self lineIndexForPoint: visibleRectangle bottomRight)
+ 		do: [:i | line := lines at: i.
+ 			self displaySelectionInLine: line on: aCanvas.
+ 			line first <= line last ifTrue:
+ 				[leftInRun := displayScanner displayLine: line
+ 								offset: offset leftInRun: leftInRun]].
+ !

Item was added:
+ ----- Method: MultiNewParagraph>>displayOnTest:using:at: (in category 'fonts-display') -----
+ displayOnTest: aCanvas using: displayScanner at: somePosition
+ 	"Send all visible lines to the displayScanner for display"
+ 
+ 	| visibleRectangle offset leftInRun line |
+ 	(presentationText isNil or: [presentationLines isNil]) ifTrue: [
+ 		^ self displayOn: aCanvas using: displayScanner at: somePosition.
+ 	].
+ 	visibleRectangle := aCanvas clipRect.
+ 	offset := somePosition - positionWhenComposed.
+ 	leftInRun := 0.
+ 	(self lineIndexForPoint: visibleRectangle topLeft)
+ 		to: (self lineIndexForPoint: visibleRectangle bottomRight)
+ 		do: [:i | line := presentationLines at: i.
+ 			self displaySelectionInLine: line on: aCanvas.
+ 			line first <= line last ifTrue:
+ 				[leftInRun := displayScanner displayLine: line
+ 								offset: offset leftInRun: leftInRun]].
+ !

Item was added:
+ ----- Method: MultiNewParagraph>>multiComposeLinesFrom:to:delta:into:priorLines:atY: (in category 'composition') -----
+ multiComposeLinesFrom: start to: stop delta: delta into: lineColl priorLines: priorLines
+ 	atY: startingY
+ 	"While the section from start to stop has changed, composition may ripple all the way to the end of the text.  However in a rectangular container, if we ever find a line beginning with the same character as before (ie corresponding to delta in the old lines), then we can just copy the old lines from there to the end of the container, with adjusted indices and y-values"
+ 
+ 	| newResult composer presentationInfo |
+ 
+ 	composer := MultiTextComposer new.
+ 	presentationLines := nil.
+ 	presentationText := nil.
+ 	newResult := composer
+ 		multiComposeLinesFrom: start 
+ 		to: stop 
+ 		delta: delta 
+ 		into: lineColl 
+ 		priorLines: priorLines
+ 		atY: startingY
+ 		textStyle: textStyle 
+ 		text: text 
+ 		container: container
+ 		wantsColumnBreaks: wantsColumnBreaks == true.
+ 	lines := newResult first asArray.
+ 	maxRightX := newResult second.
+ 	presentationInfo := composer getPresentationInfo.
+ 	presentationLines := presentationInfo first asArray.
+ 	presentationText := presentationInfo second.
+ 	"maxRightX printString displayAt: 0 at 0."
+ 	^maxRightX
+ !

Item was added:
+ ----- Method: MultiNewParagraph>>presentationLines (in category 'accessing') -----
+ presentationLines
+ 
+ 	^ presentationLines.
+ !

Item was added:
+ ----- Method: MultiNewParagraph>>presentationText (in category 'accessing') -----
+ presentationText
+ 
+ 	^ presentationText.
+ !

Item was added:
+ TextComposer subclass: #MultiTextComposer
+ 	instanceVariableNames: 'presentation presentationLines'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'TextConstants'
+ 	category: 'Morphic-Multilingual'!

Item was added:
+ ----- Method: MultiTextComposer>>composeEachRectangleIn: (in category 'as yet unclassified') -----
+ composeEachRectangleIn: rectangles
+ 
+ 	| myLine lastChar |
+ 
+ 	1 to: rectangles size do: [:i | 
+ 		currCharIndex <= theText size ifFalse: [^false].
+ 		myLine := scanner 
+ 			composeFrom: currCharIndex 
+ 			inRectangle: (rectangles at: i)				
+ 			firstLine: isFirstLine 
+ 			leftSide: i=1 
+ 			rightSide: i=rectangles size.
+ 		lines addLast: myLine.
+ 		presentationLines addLast: scanner getPresentationLine.
+ 		presentation ifNil: [presentation := scanner getPresentation]
+ 			ifNotNil: [presentation := presentation, scanner getPresentation].
+ 		actualHeight := actualHeight max: myLine lineHeight.  "includes font changes"
+ 		currCharIndex := myLine last + 1.
+ 		lastChar := theText at: myLine last.
+ 		(CharacterSet crlf includes: lastChar) ifTrue: [^#cr].
+ 		wantsColumnBreaks ifTrue: [
+ 			lastChar = TextComposer characterForColumnBreak ifTrue: [^#columnBreak].
+ 		].
+ 	].
+ 	^false!

Item was added:
+ ----- Method: MultiTextComposer>>getPresentationInfo (in category 'as yet unclassified') -----
+ getPresentationInfo
+ 
+ 	^ Array with: presentationLines with: presentation.
+ !

Item was added:
+ ----- Method: MultiTextComposer>>multiComposeLinesFrom:to:delta:into:priorLines:atY:textStyle:text:container:wantsColumnBreaks: (in category 'as yet unclassified') -----
+ multiComposeLinesFrom: argStart to: argStop delta: argDelta into: argLinesCollection priorLines: argPriorLines atY: argStartY textStyle: argTextStyle text: argText container: argContainer wantsColumnBreaks: argWantsColumnBreaks
+ 
+ 	wantsColumnBreaks := argWantsColumnBreaks.
+ 	lines := argLinesCollection.
+ 	presentationLines := argLinesCollection copy.
+ 	theTextStyle := argTextStyle.
+ 	theText := argText.
+ 	theContainer := argContainer.
+ 	deltaCharIndex := argDelta.
+ 	currCharIndex := startCharIndex := argStart.
+ 	stopCharIndex := argStop.
+ 	prevLines := argPriorLines.
+ 	currentY := argStartY.
+ 	defaultLineHeight := theTextStyle lineGrid.
+ 	maxRightX := theContainer left.
+ 	possibleSlide := stopCharIndex < theText size and: [theContainer isMemberOf: Rectangle].
+ 	nowSliding := false.
+ 	prevIndex := 1.
+ 	scanner := MultiCompositionScanner new text: theText textStyle: theTextStyle.
+ 	scanner wantsColumnBreaks: wantsColumnBreaks.
+ 	isFirstLine := true.
+ 	self composeAllLines.
+ 	isFirstLine ifTrue: ["No space in container or empty text"
+ 		self 
+ 			addNullLineWithIndex: startCharIndex
+ 			andRectangle: (theContainer topLeft extent: 0 at defaultLineHeight)
+ 	] ifFalse: [
+ 		self fixupLastLineIfCR
+ 	].
+ 	^{lines asArray. maxRightX}
+ 
+ !

Item was added:
+ ----- Method: TTCFont>>computeForm: (in category '*Morphic-Multilingual') -----
+ computeForm: char
+ 	"Compute the glyph form for the given character"
+ 	^ttcDescription renderGlyph: char height: self height fgColor: foregroundColor bgColor: Color transparent depth: self depth!

Item was added:
+ ----- Method: TTGlyph>>asFormWithScale:ascender:descender:fgColor:bgColor:depth:replaceColor:lineGlyph:lingGlyphWidth:emphasis: (in category '*Morphic-Multilingual') -----
+ asFormWithScale: scale ascender: ascender descender: descender fgColor: fgColor bgColor: bgColor depth: depth replaceColor: replaceColorFlag lineGlyph: lineGlyph lingGlyphWidth: lWidth emphasis: code
+ 
+ 	| form canvas newScale |
+ 	form := Form extent: (advanceWidth @ (ascender - descender) * scale) rounded depth: depth.
+ 	form fillColor: bgColor.
+ 	canvas := BalloonCanvas on: form.
+ 	canvas aaLevel: 4.
+ 	canvas transformBy: (MatrixTransform2x3 withScale: scale asPoint * (1 @ -1)).
+ 	canvas transformBy: (MatrixTransform2x3 withOffset: 0 @ ascender negated).
+ 	canvas
+ 		drawGeneralBezierShape: self contours
+ 		color: fgColor 
+ 		borderWidth: 0 
+ 		borderColor: fgColor.
+ 	((code bitAnd: 4) ~= 0 or: [(code bitAnd: 16) ~= 0]) ifTrue: [
+ 		newScale := (form width + 1) asFloat / lineGlyph calculateWidth asFloat.
+ 		canvas transformBy: (MatrixTransform2x3 withScale: (newScale / scale)@1.0).
+ 
+ 		(code bitAnd: 4) ~= 0 ifTrue: [
+ 			canvas
+ 				drawGeneralBezierShape: lineGlyph contours
+ 				color: fgColor 
+ 				borderWidth: 0 
+ 				borderColor: fgColor.
+ 		].
+ 
+ 		(code bitAnd: 16) ~= 0 ifTrue: [
+ 			canvas transformBy: (MatrixTransform2x3 withOffset: 0@(ascender // 2)).
+ 			canvas
+ 				drawGeneralBezierShape: lineGlyph contours
+ 				color: fgColor 
+ 				borderWidth: 0 
+ 				borderColor: fgColor.
+ 		].
+ 	].
+ 
+ 	replaceColorFlag ifTrue: [
+ 		form replaceColor: bgColor withColor: Color transparent.
+ 	].
+ 	^ form!



More information about the Squeak-dev mailing list