[Pkg] The Trunk: ST80-nice.67.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Nov 16 14:08:47 UTC 2009


Nicolas Cellier uploaded a new version of ST80 to project The Trunk:
http://source.squeak.org/trunk/ST80-nice.67.mcz

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

Name: ST80-nice.67
Author: nice
Time: 16 November 2009, 3:08:41 am
UUID: a955b212-61f0-0e40-9194-e5fff8e6e747
Ancestors: ST80-ar.66

Let paragraph handle more cases of cr/lf/crlf delimiters

=============== Diff against ST80-ar.66 ===============

Item was changed:
  ----- Method: ParagraphEditor>>encompassLine: (in category 'new selection') -----
  encompassLine: anInterval
  	"Return an interval that encompasses the entire line"
  	| string left right |
  	string := paragraph text string.
+ 	left := (string lastIndexOfAnyOf: CharacterSet crlf startingAt: anInterval first - 1 ifAbsent:[0]) + 1.
+ 	right := (string indexOfAnyOf: CharacterSet crlf startingAt: anInterval last + 1 ifAbsent: [string size + 1]) - 1.
- 	left := (string lastIndexOf: Character cr startingAt: anInterval first - 1 ifAbsent:[0]) + 1.
- 	right := (string indexOf: Character cr startingAt: anInterval last + 1 ifAbsent: [string size + 1]) - 1.
  	^left to: right!

Item was changed:
  ----- Method: ParagraphEditor>>cursorEnd: (in category 'nonediting/nontyping keys') -----
  cursorEnd: characterStream 
  
  	"Private - Move cursor end of current line."
  	| string |
  	self closeTypeIn: characterStream.
  	string := paragraph text string.
  	self
  		moveCursor:
  			[:position | Preferences wordStyleCursorMovement
  				ifTrue:[| targetLine |
  					targetLine := paragraph lines at:(paragraph lineIndexOfCharacterIndex: position).
  					targetLine = paragraph lines last
  						ifTrue:[targetLine last + 1]
  						ifFalse:[targetLine last]]
  				ifFalse:[
  					string
+ 						indexOfAnyOf: CharacterSet crlf
- 						indexOf: Character cr
  						startingAt: position
  						ifAbsent:[string size + 1]]]
  		forward: true
  		specialBlock:[:dummy | string size + 1].
  	^true!

Item was changed:
  ----- Method: ParagraphEditor>>cursorHome: (in category 'nonediting/nontyping keys') -----
  cursorHome: characterStream 
  
  	"Private - Move cursor from position in current line to beginning of
  	current line. If control key is pressed put cursor at beginning of text"
  
  	| string |
  
  	string := paragraph text string.
  	self
  		moveCursor: [ :position | Preferences wordStyleCursorMovement
  				ifTrue:[
  					(paragraph lines at:(paragraph lineIndexOfCharacterIndex: position)) first]
  				ifFalse:[
  					(string
+ 						lastIndexOfAnyOf: CharacterSet crlf
- 						lastIndexOf: Character cr
  						startingAt: position - 1
  						ifAbsent:[0]) + 1]]
  		forward: false
  		specialBlock: [:dummy | 1].
  	^true!

Item was changed:
  ----- Method: ParagraphEditor>>selectedSymbol (in category 'menu messages') -----
  selectedSymbol
  	"Return the currently selected symbol, or nil if none.  Spaces, tabs and returns are ignored"
  
  	| aString |
  	self hasCaret ifTrue: [^ nil].
  	aString := self selection string.
  	aString isOctetString ifTrue: [aString := aString asOctetString].
  	aString := aString copyWithoutAll:
+ 		{Character space.  Character cr.  Character lf. Character tab}.
- 		{Character space.  Character cr.  Character tab}.
  	aString size == 0 ifTrue: [^ nil].
  	Symbol hasInterned: aString  ifTrue: [:sym | ^ sym].
  
  	^ nil!

Item was changed:
  ----- Method: Paragraph>>updateCompositionHeight (in category 'private') -----
  updateCompositionHeight
  	"Mainly used to insure that intersections with compositionRectangle work." 
  
  	compositionRectangle := compositionRectangle withHeight:
  		(self bottomAtLineIndex: lastLine) - compositionRectangle top.
+ 	(text size ~= 0 and: [(text at: text size) = CR of: [(text at: text size) = Character lf]])
- 	(text size ~= 0 and: [(text at: text size) = CR])
  		ifTrue: [compositionRectangle := compositionRectangle withHeight:
  					compositionRectangle height + (lines at: lastLine) lineHeight]!

Item was changed:
  ----- Method: ParagraphEditor>>inOutdent:delta: (in category 'editing keys') -----
  inOutdent: characterStream delta: delta
  	"Add/remove a tab at the front of every line occupied by the selection. Flushes typeahead.  Derived from work by Larry Tesler back in December 1985.  Now triggered by Cmd-L and Cmd-R.  2/29/96 sw"
  
+ 	| realStart realStop lines startLine stopLine start stop adjustStart indentation size numLines inStream newString outStream |
- 	| cr realStart realStop lines startLine stopLine start stop adjustStart indentation size numLines inStream newString outStream |
  	
  	sensor keyboard.  "Flush typeahead"
- 	cr := Character cr.
  
  	"Operate on entire lines, but remember the real selection for re-highlighting later"
  	realStart := self startIndex.
  	realStop := self stopIndex - 1.
  
  	"Special case a caret on a line of its own, including weird case at end of paragraph"
  	(realStart > realStop and:
+ 				[realStart < 2 or: [(paragraph string at: realStart - 1) == Character cr or: [(paragraph string at: realStart - 1) == Character lf]]])
- 				[realStart < 2 or: [(paragraph string at: realStart - 1) == cr]])
  		ifTrue:
  			[delta < 0
  				ifTrue:
  					[view flash]
  				ifFalse:
  					[self replaceSelectionWith: Character tab asSymbol asText.
  					self selectAt: realStart + 1].
  			^ true].
  
  	lines := paragraph lines.
  	startLine := paragraph lineIndexOfCharacterIndex: realStart.
  	stopLine := paragraph lineIndexOfCharacterIndex: (realStart max: realStop).
  	start := (lines at: startLine) first.
  	stop := (lines at: stopLine) last.
  	
  	"Pin the start of highlighting unless the selection starts a line"
  	adjustStart := realStart > start.
  
  	"Find the indentation of the least-indented non-blank line; never outdent more"
  	indentation := (startLine to: stopLine) inject: 1000 into:
  		[:m :l |
  		m := m min: (paragraph indentationOfLineIndex: l ifBlank: [:tabs | 1000])].			
  
  	size :=  stop + 1 - start.
  	numLines := stopLine + 1 - startLine.
  	inStream := ReadStream on: paragraph string from: start to: stop.
  
  	newString := WideString new: size + ((numLines * delta) max: 0).
  	outStream := ReadWriteStream on: newString.
  
  	"This subroutine does the actual work"
  	self indent: delta fromStream: inStream toStream: outStream.
  
  	"Adjust the range that will be highlighted later"
  	adjustStart ifTrue: [realStart := (realStart + delta) max: start].
  	realStop := realStop + outStream position - size.
  
  	"Prepare for another iteration"
  	indentation := indentation + delta.
  	size := outStream position.
  	inStream := outStream setFrom: 1 to: size.
  
  	outStream == nil
  		ifTrue: 	"tried to outdent but some line(s) were already left flush"
  			[view flash]
  		ifFalse:
  			[self selectInvisiblyFrom: start to: stop.
  			size = newString size ifFalse: [newString := outStream contents].
  			self replaceSelectionWith: newString asText].
  	self selectFrom: realStart to: realStop. 	"highlight only the original range"
  	^ true!

Item was changed:
  ----- Method: Paragraph>>stringAtLineNumber: (in category 'accessing') -----
  stringAtLineNumber: aNumber
  	(aNumber > lastLine or: [aNumber < 1]) ifTrue: [^ nil].
+ 	^ (text string copyFrom: (lines at: aNumber) first to: (lines at: aNumber) last) copyWithoutAll: CharacterSet crlf!
- 	^ (text string copyFrom: (lines at: aNumber) first to: (lines at: aNumber) last) copyWithout: Character cr!

Item was changed:
  ----- Method: ParagraphEditor>>lines (in category 'private') -----
  lines
  	"Other than my member paragraph i compute lines based on logical
  	line breaks, not optical (which may change due to line wrapping of the editor)"
  	| lines string index lineIndex stringSize |
  	string := paragraph text string.
  	"Empty strings have no lines at all. Think of something."
  	string isEmpty ifTrue:[^{#(1 0 0)}].
  	stringSize := string size.
  	lines := OrderedCollection new: (string size // 15).
  	index := 0.
  	lineIndex := 0.
  	string linesDo:[:line |
  		lines addLast: (Array
  			with: (index := index + 1)
  			with: (lineIndex := lineIndex + 1)
  			with: (index := index + line size min: stringSize))].
  	"Special workaround for last line empty."
+ 	(string last == Character cr or: [string last == Character lf])
- 	string last == Character cr
  	"lines last last < stringSize" ifTrue:[lines addLast:{stringSize +1. lineIndex+1. stringSize}].
  	^lines!

Item was changed:
  ----- Method: Paragraph>>indentationOfLineIndex:ifBlank: (in category 'accessing') -----
  indentationOfLineIndex: lineIndex ifBlank: aBlock
  	"Answer the number of leading tabs in the line at lineIndex.  If there are
  	 no visible characters, pass the number of tabs to aBlock and return its value.
  	 If the line is word-wrap overflow, back up a line and recur."
  
+ 	| arrayIndex first last reader leadingTabs lastSeparator lf tab ch |
+ 	lf := Character lf.
- 	| arrayIndex first last reader leadingTabs lastSeparator cr tab ch |
- 	cr := Character cr.
  	tab := Character tab.
  	arrayIndex := lineIndex.
  	[first := (lines at: arrayIndex) first.
+ 	 first > 1 and: [(text string at: first - 1) ~~ CR and: [(text string at: first - 1) ~~ lf]]] whileTrue: "word wrap"
- 	 first > 1 and: [(text string at: first - 1) ~~ cr]] whileTrue: "word wrap"
  		[arrayIndex := arrayIndex - 1].
  	last := (lines at: lastLine) last.
  	reader := ReadStream on: text string from: first to: last.
  	leadingTabs := 0.
  	[reader atEnd not and: [(ch := reader next) == tab]]
  		whileTrue: [leadingTabs := leadingTabs + 1].
  	lastSeparator := first - 1 + leadingTabs.
+ 	[reader atEnd not and: [ch isSeparator and: [ch ~~ CR and: [ch ~~ lf]]]]
- 	[reader atEnd not and: [ch isSeparator and: [ch ~~ cr]]]
  		whileTrue: [lastSeparator := lastSeparator + 1. ch := reader next].
+ 	(lastSeparator = last or: [ch == CR or: [ch == lf]])
- 	lastSeparator = last | (ch == cr)
  		ifTrue: [^aBlock value: leadingTabs].
  	^leadingTabs!



More information about the Packages mailing list