[squeak-dev] The Trunk: Morphic-nice.327.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Feb 8 11:40:35 UTC 2010


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

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

Name: Morphic-nice.327
Author: nice
Time: 8 February 2010, 12:39:27.985 pm
UUID: 878e6022-f56c-744e-bcc0-160a96afc924
Ancestors: Morphic-cmm.326

make TextEditor a bit more LF friendly
clean up dead code in inOutdent:delta:

Note: currently, shift+cmd+L will outdent even if line with min outdent is zero. This was the old behaviour, but we can change it by uncommenting the "^false"

=============== Diff against Morphic-cmm.326 ===============

Item was changed:
  ----- Method: TextEditor>>explainChar: (in category 'explain') -----
  explainChar: string
  	"Does string start with a special character?"
  
  	| char |
  	char := string at: 1.
  	char = $. ifTrue: [^'"Period marks the end of a Smalltalk statement.  A period in the middle of a number means a decimal point.  (The number is an instance of class Float)."'].
  	char = $' ifTrue: [^'"The characters between two single quotes are made into an instance of class String"'].
  	char = $" ifTrue: [^'"Double quotes enclose a comment.  Smalltalk ignores everything between double quotes."'].
  	char = $# ifTrue: [^'"The characters following a hash mark are made into an instance of class Symbol.  If parenthesis follow a hash mark, an instance of class Array is made.  It contains literal constants."'].
  	(char = $( or: [char = $)]) ifTrue: [^'"Expressions enclosed in parenthesis are evaluated first"'].
  	(char = $[ or: [char = $]]) ifTrue: [^'"The code inside square brackets is an unevaluated block of code.  It becomes an instance of BlockContext and is usually passed as an argument."'].
  	(char = ${ or: [char = $}]) ifTrue: [^ '"A sequence of expressions separated by periods, when enclosed in curly braces, are evaluated to yield the elements of a new Array"'].
  	(char = $< or: [char = $>]) ifTrue: [^'"<primitive: xx> means that this method is usually preformed directly by the virtual machine.  If this method is primitive, its Smalltalk code is executed only when the primitive fails."'].
  	char = $^ ifTrue: [^'"Uparrow means return from this method.  The value returned is the expression following the ^"'].
  	char = $| ifTrue: [^'"Vertical bars enclose the names of the temporary variables used in this method.  In a block, the vertical bar separates the argument names from the rest of the code."'].
  	char = $_ ifTrue: [^'"Left arrow means assignment.  The value of the expression after the left arrow is stored into the variable before it."'].
  	char = $; ifTrue: [^'"Semicolon means cascading.  The message after the semicolon is sent to the same object which received the message before the semicolon."'].
  	char = $: ifTrue: [^'"A colon at the end of a keyword means that an argument is expected to follow.  Methods which take more than one argument have selectors with more than one keyword.  (One keyword, ending with a colon, appears before each argument).', '\\' withCRs, 'A colon before a variable name just inside a block means that the block takes an agrument.  (When the block is evaluated, the argument will be assigned to the variable whose name appears after the colon)."'].
  	char = $$ ifTrue: [^'"The single character following a dollar sign is made into an instance of class Character"'].
  	char = $- ifTrue: [^'"A minus sign in front of a number means a negative number."'].
  	char = $e ifTrue: [^'"An e in the middle of a number means that the exponent follows."'].
  	char = $r ifTrue: [^'"An r in the middle of a bunch of digits is an instance of Integer expressed in a certain radix.  The digits before the r denote the base and the digits after it express a number in that base."'].
  	char = Character space ifTrue: [^'"the space Character"'].
  	char = Character tab ifTrue: [^'"the tab Character"'].
  	char = Character cr ifTrue: [^'"the carriage return Character"'].
+ 	char = Character lf ifTrue: [^'"the line feed Character"'].
  	^nil!

Item was changed:
  ----- Method: TextEditor>>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 lastLine
  						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: TextEditor>>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: TextEditor>>tabCount (in category 'typing/selecting keys') -----
  tabCount
  	^ self class autoIndent
  		ifTrue:
  			[ | tabCount s i char |
  			s := paragraph string.
  			i := self stopIndex.
  			tabCount := 0.
+ 			[(i := i-1) > 0 and: [(char := s at: i) ~= Character cr and: [char ~= Character lf]]]
- 			[(i := i-1) > 0 and: [(char := s at: i) ~= Character cr]]
  				whileTrue:  "Count tabs and brackets (but not a leading bracket)"
  				[(char = Character tab and: [i < s size and: [(s at: i+1) ~= $[ ]]) ifTrue: [tabCount := tabCount + 1].
  				char = $[ ifTrue: [tabCount := tabCount + 1].
  				char = $] ifTrue: [tabCount := tabCount - 1]].
  			tabCount ]
  		ifFalse: [ 0 ]!

Item was changed:
  ----- Method: TextEditor>>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 copyWithoutAll: CharacterSet separators.
- 	aString := self selection string copyWithoutAll:
- 		{Character space.  Character cr.  Character tab}.
  	aString size = 0 ifTrue: [^ nil].
  	Symbol hasInterned: aString  ifTrue: [:sym | ^ sym].
  
  	^ nil!

Item was changed:
  ----- Method: TextEditor>>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: TextEditor>>changeLfToCr: (in category 'editing keys') -----
  changeLfToCr: characterStream 
  	"Replace all LFs by CRs.
  	Triggered by Cmd-U -- useful when getting code from FTP sites
  	jmv- Modified to als change crlf by cr"
  	
  	| fixed |
  	sensor keyboard.		"flush the triggering cmd-key character"
  	
+ 	fixed := self selection string withSqueakLineEndings. 
- 	fixed := self selection string.
- 	fixed := fixed copyReplaceAll: String crlf with: String cr.
- 	fixed := fixed copyReplaceAll: String lf with: String cr. 
  	self replaceSelectionWith: (Text fromString: fixed).
  	^ true!

Item was changed:
  ----- Method: TextEditor>>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:
  					[morph 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 min: (paragraph indentationOfLineIndex: l ifBlank: [:tabs | 1000])].
+ 	indentation + delta <= 0 ifTrue: ["^false"].
- 		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 := String new: size + ((numLines * delta) max: 0).
+ 	outStream := WriteStream on: newString.
- 	outStream := ReadWriteStream on: newString.
  
  	"This subroutine does the actual work"
  	self indent: delta fromStream: inStream toStream: outStream.
+ 	newString := outStream contents.
  
  	"Adjust the range that will be highlighted later"
  	adjustStart ifTrue: [realStart := (realStart + delta) max: start].
+ 	realStop := realStop + newString size - size.
- 	realStop := realStop + outStream position - size.
  
+ 	"Replace selection"
+ 	self selectInvisiblyFrom: start to: stop.
+ 	self replaceSelectionWith: newString asText.
- 	"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"
- 			[morph 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!




More information about the Squeak-dev mailing list