[squeak-dev] The Trunk: Graphics-mt.479.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Feb 11 09:17:21 UTC 2022


Marcel Taeumel uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-mt.479.mcz

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

Name: Graphics-mt.479
Author: mt
Time: 11 February 2022, 10:17:15.672479 am
UUID: dac43fc9-8dd5-8242-adcb-2ff421c27e9b
Ancestors: Graphics-mt.478

Fixes tabs in text fields. Adds a new preference #numSpacesPerTab and use a field's current text style's default font to compute the correct tab spacing.

Note that Squeak's default has always been 6 spaces per tab, based on Text class >> #initTextConstants (4px for default space and 24px for default tab). So, we keep that default for now.

=============== Diff against Graphics-mt.478 ===============

Item was changed:
  ----- Method: StrikeFont>>newFromStrike: (in category 'file in/out') -----
  newFromStrike: fileName
  	"Build an instance from the strike font file name. The '.strike' extension
  	is optional."
  
  	| strike startName raster16 |
  	name := fileName copyUpTo: $..	"assumes extension (if any) is '.strike'"
  	strike := FileStream readOnlyFileNamed: name, '.strike.'.
  	strike binary.
  
  	"strip off direcory name if any"
  	startName := name size.
  	[startName > 0 and: [((name at: startName) ~= $>) & ((name at: startName) ~= $])]]
  		whileTrue: [startName := startName - 1].
  	name := name copyFrom: startName+1 to: name size.
  
  	type			:=		strike nextWord.		"type is ignored now -- simplest
  												assumed.  Kept here to make
  												writing and consistency more
  												straightforward."
  	minAscii		:=		strike nextWord.
  	maxAscii		:=		strike nextWord.
  	maxWidth		:=		strike nextWord.
  	strikeLength	:=		strike nextWord.
  	ascent			:=		strike nextWord.
  	descent			:=		strike nextWord.
  	"xOffset			:="		strike nextWord. 	
  	raster16			:=		strike nextWord.	
  	superscript		:=		ascent - descent // 3.	
  	subscript		:=		descent - ascent // 3.	
  	emphasis		:=		0.
  	glyphs			:=	Form extent: (raster16 * 16) @ (self height)  
  							offset: 0 at 0.
  		glyphs bits fromByteStream: strike.
  
  	xTable := (Array new: maxAscii + 3) atAllPut: 0.
  	(minAscii + 1 to: maxAscii + 3) do:
  		[:index | xTable at: index put: strike nextWord].
  
  	"Set up space character"
  	((xTable at: (Space asciiValue + 2))  = 0 or:
  			[(xTable at: (Space asciiValue + 2)) = (xTable at: (Space asciiValue + 1))])
  		ifTrue:	[(Space asciiValue + 2) to: xTable size do:
+ 					[:index | xTable at: index put: ((xTable at: index) + 4 "DefaultSpace")]].
- 					[:index | xTable at: index put: ((xTable at: index) + DefaultSpace)]].
  	strike close.
  	characterToGlyphMap := nil.!

Item was changed:
  ----- Method: StrikeFont>>readFromStrike2Stream: (in category 'file in/out') -----
  readFromStrike2Stream: file 
  	"Build an instance from the supplied binary stream on data in strike2 format"
  	type := file nextInt32.  type = 2 ifFalse: [file close. self error: 'not strike2 format'].
  	minAscii := file nextInt32.
  	maxAscii := file nextInt32.
  	maxWidth := file nextInt32.
  	ascent := file nextInt32.
  	descent := file nextInt32.
  	pointSize := file nextInt32.
  	superscript := ascent - descent // 3.	
  	subscript := descent - ascent // 3.	
  	emphasis := file nextInt32.
  	xTable := (Array new: maxAscii + 3) atAllPut: 0.
  	(minAscii + 1 to: maxAscii + 3) do:
  		[:index | xTable at: index put: file nextInt32].
  	glyphs := Form new readFrom: file.
  
  	"Set up space character"
  	((xTable at: (Space asciiValue + 2))  = 0 or:
  			[(xTable at: (Space asciiValue + 2)) = (xTable at: (Space asciiValue + 1))])
  		ifTrue:	[(Space asciiValue + 2) to: xTable size do:
+ 					[:index | xTable at: index put: ((xTable at: index) + 4 "DefaultSpace")]].
- 					[:index | xTable at: index put: ((xTable at: index) + DefaultSpace)]].
  	characterToGlyphMap := nil.!

Item was changed:
  Object subclass: #TextStyle
  	instanceVariableNames: 'fontArray fontFamilySize lineGrid baseline alignment firstIndent restIndent rightIndent tabsArray marginTabsArray leading leadingSlice defaultFontIndex'
+ 	classVariableNames: 'NumSpacesPerTab'
- 	classVariableNames: ''
  	poolDictionaries: 'TextConstants'
  	category: 'Graphics-Text'!
  
  !TextStyle commentStamp: '<historical>' prior: 0!
  A textStyle comprises the formatting information for composing and displaying a unit (usually a paragraph) of text.  Typically one makes a copy of a master textStyle (such as TextStyle default), and then that copy may get altered in the process of editing.  Bad things can happen if you do not copy first.
  
  Each of my instances consists of...
  	fontArray		An array of StrikeFonts
  	fontFamilySize	unused
  	lineGrid			An integer; default line spacing for paragraphs
  	baseline			An integer; default baseline (dist from line top to bottom of an 'a')
  	alignment		An integer; text alignment, see TextStyle alignment:
  	firstIndent		An integer; indent of first line in pixels
  	restIndent		An integer; indent of remaining lines in pixels
  	rightIndent		An integer; indent of right margin rel to section
  	tabsArray		An array of integers giving tab offsets in pixels
  	marginTabsArray	An array of margin tabs
  	leading			An integer giving default vertical line separation
  
  For a concrete example, look at TextStyle default copy inspect!

Item was added:
+ ----- Method: TextStyle class>>numSpacesPerTab (in category 'preferences') -----
+ numSpacesPerTab
+ 	<preference: 'Tab width (i.e., number of spaces)'
+ 		categoryList: #(tools visuals)
+ 		description: 'Amount of spaces to be used when calculating the width of a tab character for a specific font face and point size.'
+ 		type: #Number>
+ 	^ NumSpacesPerTab ifNil: [6]!

Item was added:
+ ----- Method: TextStyle class>>numSpacesPerTab: (in category 'preferences') -----
+ numSpacesPerTab: anInteger
+ 
+ 	anInteger = NumSpacesPerTab ifTrue: [^ self].
+ 	NumSpacesPerTab := anInteger ifNotNil: [anInteger truncated max: 1].
+ 	TextStyle allInstancesDo: [:ea | ea initializeTabsArray].
+ 
+ 	"Avoid dependency to Morphic project..."
+ 	(self environment classNamed: #TextMorph)
+ 		ifNotNil: [:tmClass | tmClass allSubInstancesDo: [:tm |
+ 			tm releaseParagraph; changed]].!

Item was changed:
  ----- Method: TextStyle>>defaultFontIndex: (in category 'default font') -----
  defaultFontIndex: anIndex
  
  	defaultFontIndex := anIndex.
  	
  	leading := self defaultFont lineGap.
  	leadingSlice := self defaultFont lineGapSlice.
  	lineGrid := self defaultFont height + leading.
+ 	baseline := self defaultFont ascent + leadingSlice.
+ 	
+ 	self initializeTabsArray.!
- 	baseline := self defaultFont ascent + leadingSlice.!

Item was added:
+ ----- Method: TextStyle>>initializeTabsArray (in category 'initialize-release') -----
+ initializeTabsArray
+ 
+ 	| fontToUse numSpacesPerTab tabWidth maxWidth |
+ 	self flag: #discuss. "mt: Add cache per font and pointSize? Maybe it is not worth it..."
+ 	
+ 	numSpacesPerTab := self class numSpacesPerTab.
+ 	fontToUse := self defaultFont.
+ 	maxWidth := Display width max: 3840.	
+ 	tabWidth := (fontToUse widthOf: Character space) * numSpacesPerTab.
+ 	
+ 	"Note that using Interval via #to:by: and #asArray would be about 4x slower."
+ 	tabsArray := Array new: maxWidth // tabWidth.
+ 	1 to: tabsArray size do: [:i | tabsArray at: i put: tabWidth * i].
+ 	
+ 	marginTabsArray := Array new: (maxWidth // tabWidth) // 2.
+ 	1 to: marginTabsArray size do: [:i | | offset |
+ 		marginTabsArray at: i put: (Array with: (offset := tabWidth * i) with: offset)].!

Item was changed:
  ----- Method: TextStyle>>newFontArray: (in category 'private') -----
  newFontArray: anArray
  	"Currently there is no supporting protocol for changing these arrays. If an editor wishes to implement margin setting, then a copy of the default should be stored with these instance variables.  
  	, Make size depend on first font."
  
  	fontArray := anArray.
  	self defaultFontIndex: 1.
  	alignment := 0.
  	firstIndent := 0.
  	restIndent := 0.
  	rightIndent := 0.
- 	tabsArray := DefaultTabsArray.
- 	marginTabsArray := DefaultMarginTabsArray
  "
  TextStyle allInstancesDo: [:ts | ts newFontArray: TextStyle default fontArray].
  "!

Item was changed:
  ----- Method: TextStyle>>tabWidth (in category 'tabs and margins') -----
  tabWidth
  	"Answer the width of a tab."
  
+ 	^ tabsArray at: 1 ifAbsent: [24]!
- 	^DefaultTab!

Item was changed:
+ (PackageInfo named: 'Graphics') postscript: '"Compute the correct tab widths per style using its current default font."
+ TextStyle allInstancesDo: [:ea | ea initializeTabsArray].'!
- (PackageInfo named: 'Graphics') postscript: '"Unpack unnecessary StrikeFontSet in Accuny."
- (TextStyle named: ''Accuny'') ifNotNil: [:style |
- 	style fontArray withIndexDo: [:fontSet :index |
- 		((fontSet isKindOf: StrikeFontSet) and: [fontSet fontArray size = 1])
- 			ifTrue: [style fontArray at: index put: fontSet fontArray first]]].
- 	
- "Fix font names for Atlanta."
- (TextStyle named: ''Atlanta'') fontArray do: [:font |
- 	font name last isDigit ifFalse: [font name: font name, font pointSize]].
- 
- "Fix PPI to be around 96 in all pre-rendered fonts."
- (TextStyle knownTextStylesWithoutDefault
- 	collect: [:ea | TextStyle named: ea]
- 	thenSelect: [:style | style defaultFont isTTCFont not])
- 		do: [:style | style fontArray do: [:font |
- 			font pointSize: ((72 * font height / 96) roundTo: 0.5).
- 			font derivativeFonts do: [:derivate |
- 				derivate pointSize: font pointSize]]].'!



More information about the Squeak-dev mailing list