[Pkg] The Trunk: Kernel-nice.563.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Mar 30 19:21:50 UTC 2011


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

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

Name: Kernel-nice.563
Author: nice
Time: 30 March 2011, 9:20:36.797 pm
UUID: 8550c4d6-b22a-409a-91d7-68a3c9ad6a7b
Ancestors: Kernel-nice.562

As previously discussed in squeak-dev, implement two utilities: #newCompiler #newParser
(self newCompiler) is a replacement for (self compilerClass new), except it arranges to have the compiler initialized with proper Parser.

Advantage 1:
This way, you can define only parserClass rather than a pair compilerClass/parserClass for experimenting alternate syntax.
Also, this may later simplify Compiler initialization of parser inst. var.

Advantage 2:
If any special initialization is required for YourOwnCompiler/parser instance, then just refine #newCompiler/Parser rather than hacking each and every #compilerClass/parserClass sender.

Disadvantage 1:
Encouraging experimentations of alternate Parser might show the limits of some tools (MC RB etc...).
Bet we wouldn't put such experimentations in trunk, would we ?

Disadvantage 2:
none foreseen, but you tell me.

=============== Diff against Kernel-nice.562 ===============

Item was changed:
  ----- Method: Behavior>>compile:classified:notifying:trailer:ifFail: (in category 'compiling') -----
  compile: code classified: category notifying: requestor trailer: bytes ifFail: failBlock
  	"Compile code without logging the source in the changes file"
  
  	| methodNode |
+ 	methodNode  := self newCompiler
- 	methodNode  := self compilerClass new
  				compile: code
  				in: self
  				classified: category 
  				notifying: requestor
  				ifFail: failBlock.
  	^ CompiledMethodWithNode generateMethodFromNode: methodNode trailer: bytes.!

Item was changed:
  ----- Method: Behavior>>compressedSourceCodeAt: (in category 'accessing method dictionary') -----
  compressedSourceCodeAt: selector
  	"(Paragraph compressedSourceCodeAt: #displayLines:affectedRectangle:) size 721 1921
  	Paragraph selectors inject: 0 into: [:tot :sel | tot + (Paragraph compressedSourceCodeAt: sel) size] 13606 31450"
  	| rawText parse |
  	rawText := (self sourceCodeAt: selector) asString.
+ 	parse := self newCompiler parse: rawText in: self notifying: nil.
- 	parse := self compilerClass new parse: rawText in: self notifying: nil.
  	^ rawText compressWithTable:
  		((selector keywords ,
  		parse tempNames ,
  		self instVarNames ,
  		#(self super ifTrue: ifFalse:) ,
  		((0 to: 7) collect:
  			[:i | String streamContents:
  				[:s | s cr. i timesRepeat: [s tab]]]) ,
  		(self compiledMethodAt: selector) literalStrings)
  			asSortedCollection: [:a :b | a size > b size])!

Item was changed:
  ----- Method: Behavior>>firstPrecodeCommentFor: (in category 'accessing method dictionary') -----
  firstPrecodeCommentFor:  selector
  	"If there is a comment in the source code at the given selector that preceeds the body of the method, return it here, else return nil"
  
  	| parser source tree |
  	"Behavior firstPrecodeCommentFor: #firstPrecodeCommentFor:"
  	(#(Comment Definition Hierarchy) includes: selector)
  		ifTrue:
  			["Not really a selector"
  			^ nil].
  	source := self sourceCodeAt: selector asSymbol ifAbsent: [^ nil].
+ 	parser := self newParser.
- 	parser := self parserClass new.
  	tree := 
  		parser
  			parse: (ReadStream on: source)
  			class: self
  			noPattern: false
  			context: nil
  			notifying: nil
  			ifFail: [^ nil].
  	^ (tree comment ifNil: [^ nil]) first!

Item was changed:
  ----- Method: Behavior>>formalParametersAt: (in category 'accessing method dictionary') -----
  formalParametersAt: aSelector
  	"Return the names of the arguments used in this method."
  
  	| source |
  	source := self sourceCodeAt: aSelector ifAbsent: [^ #()].	"for now"
+ 	^self newParser parseParameterNames: source!
- 	^(self parserClass new) parseParameterNames: source!

Item was changed:
  ----- Method: Behavior>>methodHeaderFor: (in category 'accessing method dictionary') -----
  methodHeaderFor: selector 
  	"Answer the string corresponding to the method header for the given selector"
  
  	| sourceString parser |
  	sourceString := self ultimateSourceCodeAt: selector ifAbsent: [self standardMethodHeaderFor: selector].
+ 	(parser := self newParser) parseSelector: sourceString.
- 	(parser := self parserClass new) parseSelector: sourceString.
  	^ sourceString asString copyFrom: 1 to: (parser endOfLastToken min: sourceString size)
  
  	"Behavior methodHeaderFor: #methodHeaderFor: "
  !

Item was added:
+ ----- Method: Behavior>>newCompiler (in category 'compiling') -----
+ newCompiler
+ 	"Answer a Compiler suitable for compiling this Behavior"
+ 	^self compilerClass new parser: self newParser!

Item was added:
+ ----- Method: Behavior>>newParser (in category 'compiling') -----
+ newParser
+ 	"Answer a Parser suitable for parsing source code in this Behavior"
+ 	^self parserClass new!

Item was changed:
  ----- Method: Behavior>>recompile:from: (in category 'compiling') -----
  recompile: selector from: oldClass
  	"Compile the method associated with selector in the receiver's method dictionary."
  	"ar 7/10/1999: Use oldClass compiledMethodAt: not self compiledMethodAt:"
  	| method trailer methodNode |
  	method := oldClass compiledMethodAt: selector.
  	trailer := method trailer.
+ 	methodNode := self newCompiler
- 	methodNode := self compilerClass new
  				compile: (oldClass sourceCodeAt: selector)
  				in: self
  				notifying: nil
  				ifFail: [^ self].   "Assume OK after proceed from SyntaxError"
  	selector == methodNode selector ifFalse: [self error: 'selector changed!!'].
  	self basicAddSelector: selector withMethod: (methodNode generate: trailer).
  !

Item was changed:
  ----- Method: Behavior>>recompileNonResidentMethod:atSelector:from: (in category 'compiling') -----
  recompileNonResidentMethod: method atSelector: selector from: oldClass
  	"Recompile the method supplied in the context of this class."
  
  	| trailer methodNode |
  	trailer := method trailer.
+ 	methodNode := self newCompiler
- 	methodNode := self compilerClass new
  			compile: (method getSourceFor: selector in: oldClass)
  			in: self
  			notifying: nil
  			ifFail: ["We're in deep doo-doo if this fails (syntax error).
  				Presumably the user will correct something and proceed,
  				thus installing the result in this methodDict.  We must
  				retrieve that new method, and restore the original (or remove)
  				and then return the method we retrieved."
  				^ self error: 'see comment'].
  	selector == methodNode selector ifFalse: [self error: 'selector changed!!'].
  	^ methodNode generate: trailer
  !

Item was changed:
  ----- Method: Behavior>>sourceMatchesBytecodeAt: (in category 'testing') -----
  sourceMatchesBytecodeAt: selector
  	"Answers true if the source code at the selector compiles to the bytecode at the selector, and false otherwise. Implemented to detect an error where Monticello did not recompile sources when the class shape changed"
  	"This code was copied from #recompile:from:, with few changes. Several methods would benefit from a method which turned a selector and class into a CompiledMethod, without  installing it into the methodDictionary"
  
  	| method trailer methodNode |
  	method := self compiledMethodAt: selector.
  	trailer := method trailer.
+ 	methodNode := self newCompiler
- 	methodNode := self compilerClass new
  				compile: (self sourceCodeAt: selector)
  				in: self
  				notifying: nil
  				ifFail: [^ false].   "Assume OK after proceed from SyntaxError"
  	selector == methodNode selector ifFalse: [self error: 'selector changed!!'].
  	^ (methodNode generate: trailer) = method!

Item was changed:
  ----- Method: ClassCategoryReader>>scanFromNoCompile: (in category 'fileIn/Out') -----
  scanFromNoCompile: aStream 
  	"Just move the source code for the methods from aStream."
  	| methodText selector |
  
  	[methodText := aStream nextChunkText.
  	 methodText size > 0]
  		whileTrue:
  		[(SourceFiles at: 2) ifNotNil: [
+ 			selector := class newParser parseSelector: methodText.
- 			selector := class parserClass new parseSelector: methodText.
  			(class compiledMethodAt: selector) putSource: methodText 
  				fromParseNode: nil class: class category: category
  				withStamp: changeStamp inFile: 2 priorMethod: nil]]!

Item was changed:
  ----- Method: ClassDescription>>replaceSilently:to: (in category 'instance variables') -----
  replaceSilently: old to: new
  	"text-replace any part of a method.  Used for class and pool variables.  Don't touch the header.  Not guaranteed to work if name appears in odd circumstances"
  	| oldName newName |
  	oldName := old asString.
  	newName := new asString.
  	self withAllSubclasses do:
  		[:cls |
  		| sels |
  		sels := cls selectors copyWithoutAll: #(DoIt DoItIn:).
  		sels do:
  			[:sel |
  			| oldCode newCode parser header body |
  			oldCode := cls sourceCodeAt: sel.
  			"Don't make changes in the method header"
+ 			(parser := cls newParser) parseSelector: oldCode.
- 			(parser := cls parserClass new) parseSelector: oldCode.
  			header := oldCode copyFrom: 1 to: (parser endOfLastToken min: oldCode size).
  			body := header size > oldCode size
  					ifTrue: ['']
  					ifFalse: [oldCode copyFrom: header size+1 to: oldCode size].
  			newCode := header , (body copyReplaceTokens: oldName with: newName).
  			newCode ~= oldCode ifTrue:
  				[cls compile: newCode
  					classified: (cls organization categoryOfElement: sel)
  					notifying: nil]].
  		cls isMeta ifFalse:
  			[| oldCode newCode |
  			oldCode := cls comment.
  			newCode := oldCode copyReplaceTokens: oldName with: newName.
  			newCode ~= oldCode ifTrue:
  				[cls comment: newCode]]]!

Item was changed:
  ----- Method: CompiledMethod>>methodNode (in category 'decompiling') -----
  methodNode
  	"Return the parse tree that represents self. If parsing fails, decompile the method."
  	| aClass source |
  	aClass := self methodClass.
  	source := self
  				getSourceFor: (self selector ifNil: [self defaultSelector])
  				in: aClass.
+ 	^[(aClass newParser
- 	^[(aClass parserClass new
  		encoderClass: (self isBlueBookCompiled
  						ifTrue: [EncoderForV3]
  						ifFalse: [EncoderForV3PlusClosures]);
  		parse: source class: aClass)
  			sourceText: source;
  			yourself]
  		on: SyntaxErrorNotification
  		do: [:ex | ex return: self decompile].!

Item was changed:
  ----- Method: CompiledMethod>>methodNodeFormattedAndDecorated: (in category 'decompiling') -----
  methodNodeFormattedAndDecorated: decorate
  	"Answer a method node made from pretty-printed (and colorized, if decorate is true) 
  	 source text."
  
  	| class source node  |
  	
  	source := self getSourceFromFile.
  	class := self methodClass ifNil: [self sourceClass].
  	source ifNil: [^self decompile].
  	source := class prettyPrinterClass 
  				format: source
  				in: class
  				notifying: nil
  				decorated: decorate.
+ 	node := class newParser parse: source class: class.
- 	node := class parserClass new parse: source class: class.
  	node sourceText: source.
  	^node!

Item was changed:
  ----- Method: CompiledMethod>>replace:with:in: (in category 'private') -----
  replace: oldSelector with: newSelector in: aText
  	| oldKeywords newKeywords args newSelectorWithArgs startOfSource lastSelectorToken |
  	oldKeywords := oldSelector keywords.
  	newKeywords := (newSelector ifNil: [self defaultSelector]) keywords.
  	self assert: oldKeywords size = newKeywords size.
+ 	args := (self methodClass newParser
- 	args := (self methodClass parserClass new
  		parseArgsAndTemps: aText string notifying: nil) copyFrom: 1 to: self numArgs.
  	newSelectorWithArgs := String streamContents: [:stream |
  		newKeywords withIndexDo: [:keyword :index |
  			stream nextPutAll: keyword.
  			stream space.
  			args size >= index ifTrue: [
  				stream nextPutAll: (args at: index); space]]].
  	lastSelectorToken := args isEmpty
  		ifFalse: [args last]
  		ifTrue: [oldKeywords last].
  	startOfSource := (aText string
  		indexOfSubCollection: lastSelectorToken startingAt: 1) + lastSelectorToken size.
  	^newSelectorWithArgs withBlanksTrimmed asText , (aText copyFrom: startOfSource to: aText size)!

Item was changed:
  ----- Method: CompiledMethod>>sourceSelector (in category 'source code management') -----
  sourceSelector
  	"Answer my selector extracted from my source.  If no source answer nil"
  
  	| sourceString |
  	sourceString := self getSourceFromFile ifNil: [^ nil].
+ 	^self methodClass newParser parseSelector: sourceString!
- 	^self methodClass parserClass new parseSelector: sourceString!



More information about the Packages mailing list