[Pkg] The Trunk: Kernel-ar.337.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Dec 22 12:55:56 UTC 2009


Andreas Raab uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-ar.337.mcz

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

Name: Kernel-ar.337
Author: ar
Time: 22 December 2009, 1:54:20 am
UUID: 357ce99e-9fe1-f548-9540-060ed21b7479
Ancestors: Kernel-ar.336

CompiledMethodTrailer: Cleanup.

=============== Diff against Kernel-ar.336 ===============

Item was changed:
  Object subclass: #CompiledMethodTrailer
  	instanceVariableNames: 'data encodedData kind size method'
+ 	classVariableNames: ''
- 	classVariableNames: 'TrailerClass'
  	poolDictionaries: ''
  	category: 'Kernel-Methods'!
  
  !CompiledMethodTrailer commentStamp: 'Igor.Stasenko 12/13/2009 12:53' prior: 0!
  I am responsible for encoding and decoding various kinds of compiled method trailer data.
  I should not expose any binary data outside of myself, so all tools which working with compiled methods
  should ask me to encode the meta-data, they want to be added to the compiled method trailer, as well as retrieve it.
  
  To add a new kind of trailer, you should give it a proper name and define it in the #trailerKinds method at my class side.
  Then you need to implement a corresponding #encode<your name> and #decode<your name> methods at instance side. Then add any public accessor methods, which will use a newly introduced trailer kind for communicating with outer layer(s).
  
  An encodeXXX methods should store result (byte array) into encodedData instance variable.
  
  A decodeXXX methods should read the data from compiled method instance, held by 'method' ivar,
  and always set 'size' ivar (denoting a total length of trailer in compiled method) and optionally 'data' ivar which should keep a decoded data, ready to be used by outer layer(s) using accessor method(s) you providing.
  
  The kind of compiled method trailer is determined by the last byte of compiled method.
  
  The byte format used is following: 
  	"2rkkkkkkdd"
  
  where 'k' bits stands for 'kind' , allowing totally 64 different kinds of method trailer
  and 'd' bits is data.
  
  Following is the list of currently defined trailer kinds:
  
  NoTrailer , k = 000000, dd unused
  method has no trailer, and total trailer size bytes is always 1
  
  ClearedTrailer, k = 000001, 
  method has cleared trailer (it was set to something else, but then cleared) 
  dd+1  determines the number of bytes for size field, and size is a total length of trailer bytes
  So a total length of trailer is: 1 + (dd + 1) + size
  
  TempsNamesQCompress, k = 000010
  the trailer contains a list of method temp names,  compressed using qCompress: method. 
  dd+1  determines the number of bytes for size field, and size is a number of bytes of compressed buffer.
  So a total length of trailer is:  1 + (dd + 1) + size
  
  TempsNamesZip, k = 000011
  the trailer contains a list of method temp names,  compressed using GZIP compression method. 
  dd+1  determines the number of bytes for size field, and size is a number of bytes of compressed buffer
  So a total length of trailer is: 1 + (dd + 1) + size
  
  SourceBySelector, k = 000100
  the trailer indicates , that method source is determined by a class + selector where it is installed to. 
  Trailer size = 1.
  
  SourceByStringIdentifier, k = 000101
  the trailer indicates , that method source is determined by a class + some ByteString identifier. 
  dd+1  determines the number of bytes for size of ByteString identifier, and size is number of bytes of string.
  A total length of trailer is:  1 + (dd + 1) + size
  
  EmbeddedSourceQCompress, k = 000110
  the trailer contains an utf-8 encoded method source code, compressed using qCompress method
  dd+1  determines the number of bytes for size field, and size is a number of bytes of compressed source code
  A total length of trailer is:  1 + (dd + 1) + size
  
  EmbeddedSourceZip, k = 000111
  the trailer contains an utf-8 encoded method source code, comressed using GZIP 
  dd+1  determines the number of bytes for size field, and size is a number of bytes of compressed buffer
  A total length of trailer is:  1 + (dd + 1) + size
  
  VarLengthSourcePointer, k = 001000
  the trailer is variable-length encoded source pointer. 
  dd bits is unused.
  
  ExtendedKind, k = 001001
  the next byte of trailer (one that prepends the last byte of compiled method)
  denotes an extended kind of trailer, allowing to use additional 256 kinds of encoding method's trailer in future. 
  
  SourcePointer, k = 111111 
  the trailer is encoded source pointer. Total trailer size is 4-bytes 
  (this kind of encoding is backwards compatible with most of existing compiled methods)
  
  !

Item was removed:
- CompiledMethodTrailer subclass: #OldMethodTrailer
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Kernel-Methods'!

Item was removed:
- ----- Method: OldMethodTrailer class>>testOldStuffIsFine (in category 'as yet unclassified') -----
- testOldStuffIsFine
- "OldMethodTrailer testOldStuffIsFine"
- 	| meth |
- 	CompiledMethod allInstancesDo: [:m |
- 		| trailer |	
- 		trailer := self new method: m.
- 		self assert: (m endPC = trailer endPC).
- 	].
- 	meth := CompiledMethod toReturnSelf copyWithTempNames: #( a b c d e).
- 	self assert: (self new method: meth) tempNames = meth tempNamesString.
- 	self assert: (CompiledMethod toReturnSelfTrailerBytes: (self new tempNames: 'a b c d e ')) tempNamesString
- 	 = meth tempNamesString.
- 	!

Item was removed:
- ----- Method: CompiledMethodTrailer class>>new (in category 'as yet unclassified') -----
- new
- 	^ self trailerClass basicNew initialize!

Item was removed:
- ----- Method: CompiledMethodTrailer class>>trailerClass (in category 'as yet unclassified') -----
- trailerClass
- 	^TrailerClass ifNil:[OldMethodTrailer]!

Item was removed:
- ----- Method: CompiledMethodTrailer class>>usingNewFormat (in category 'as yet unclassified') -----
- usingNewFormat
- 	^ self trailerClass == CompiledMethodTrailer!

Item was removed:
- ----- Method: CompiledMethodTrailer class>>convertTrailers (in category 'as yet unclassified') -----
- convertTrailers
- 	| toConvert converted |
- 	"Protect against doing this in already converted image."
- 	self usingNewFormat ifTrue:[^self].
- 
- 	toConvert := OrderedCollection new.
- 	CompiledMethod allInstancesDo: [:m |
- 		"we need to convert only methods which has no sourcePointer "
- 		m sourcePointer = 0 ifTrue: [
- 			toConvert add: m.
- 			].
- 		].
- 
- 	toConvert := toConvert asArray.
- 	converted := toConvert collect: [:m |
- 		m copyWithTrailerBytes: self basicNew initialize. "clear the trailers"
- 	].
- 
- 	toConvert elementsExchangeIdentityWith: converted asArray.
- 
- 	"replace the #trailerClass method in CompiledMethodTrailer class"
- 	TrailerClass := CompiledMethodTrailer.	
- !

Item was removed:
- ----- Method: OldMethodTrailer>>tempNames (in category 'as yet unclassified') -----
- tempNames
- 
- 	"Answer the string, containing the temps names or nil "
- 	^ (kind == #OldTempsNames) 
- 		ifTrue: [ data ] ifFalse: [ nil ]!

Item was removed:
- ----- Method: OldMethodTrailer>>encodeNoTrailer (in category 'as yet unclassified') -----
- encodeNoTrailer
- 
- 	encodedData := #(0 0 0 0)!

Item was removed:
- ----- Method: OldMethodTrailer>>tempNames: (in category 'as yet unclassified') -----
- tempNames: aString
- 	"Embed the temp names string into compiled method trailer"
- 
- 	self clear.
- 	kind := #OldTempsNames.
- 	data := aString.
- 	
- 	self encode.
- !

Item was removed:
- ----- Method: OldMethodTrailer>>decodeOldEmptyTrailer (in category 'as yet unclassified') -----
- decodeOldEmptyTrailer
- 
- 	"1 to 4 zero bytes"
- 	size := 0.
- 	[ (method at: (method size - size)) = 0 and: [size <4]] whileTrue: [ size := size + 1].
- !

Item was removed:
- ----- Method: OldMethodTrailer>>decodeOldTempsNames (in category 'as yet unclassified') -----
- decodeOldTempsNames
- 
- 	| sz flagByte |
- 	flagByte := method at: (sz := method size).
- 	(flagByte = 0 or: [flagByte > 251]) ifTrue: [^self error: 'not yet implemented'].
- 	(flagByte = 251
- 	 and: [(1 to: 3) allSatisfy: [:i | (method at: method size - i) = 0]]) ifTrue:
- 		[^self error: 'not yet implemented'].
- 	
- 	size := flagByte <= 127
- 			ifTrue: [flagByte + 1]
- 			ifFalse: [ (flagByte - 128 * 128) + (method at: sz - 1) + 2].
- 				
- 	data := self qDecompressFrom: (flagByte <= 127
- 								ifTrue:
- 									[ReadStream on: method from: sz - flagByte to: sz - 1]
- 								ifFalse:
- 									[ReadStream on: method from: sz - (flagByte - 128 * 128 + (method at: sz - 1)) - 1 to: sz - 2])	
- !

Item was removed:
- ----- Method: OldMethodTrailer>>encodeOldEmptyTrailer (in category 'as yet unclassified') -----
- encodeOldEmptyTrailer
- 
- 	encodedData := #(0 0 0 0).
- 	!

Item was removed:
- ----- Method: OldMethodTrailer>>encodeOldTempsNames (in category 'as yet unclassified') -----
- encodeOldTempsNames
- 
- 	
- 	"A very simple text compression routine designed for method temp names.
- 	 Most common 11 chars get values 1-11 packed in one 4-bit nibble;
- 	 the next most common get values 12-15 (2 bits) * 16 plus next nibble;
- 	 unusual ones get three nibbles, the first being the escape nibble 0.
- 	 CompiledMethod>>endPC determines the maximum length of encoded
- 	 output, which means 1 to (251 - 128) * 128 + 127, or 15871 bytes"
- 	data isEmpty ifTrue: [ data := ' '].
- 	encodedData := ByteArray streamContents:
- 		[:strm | | ix oddNibble sz |
- 		oddNibble := nil.
- 		data do:
- 			[:char |
- 			ix := 'ear tonsilcmbdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ012345[]()'
- 					indexOf: char ifAbsent: 0.
- 			(ix = 0
- 				ifTrue:
- 					[char asInteger > 255 ifTrue: [^nil]. "Could use UTF8 here; too lazy right now"
- 					{ 0. char asInteger // 16. char asInteger \\ 16 }]
- 				ifFalse:
- 					[ix <= 11
- 						ifTrue: [{ ix }]
- 						ifFalse: [{ ix//16+12. ix\\16 }]])
- 					do: [:nibble |
- 						oddNibble
- 							ifNotNil: [strm nextPut: oddNibble*16 + nibble. oddNibble := nil]
- 							ifNil: [oddNibble := nibble]]].
- 		oddNibble ifNotNil: "4 = 'ear tonsil' indexOf: Character space"
- 			[strm nextPut: oddNibble * 16 + 4].
- 		(sz := strm position) > ((251 - 128) * 128 + 127) ifTrue:
- 			[^nil].
- 		sz <= 127
- 			ifTrue: [strm nextPut: sz]
- 			ifFalse:
- 				[strm nextPut: sz \\ 128; nextPut: sz // 128 + 128]]!

Item was removed:
- ----- Method: CompiledMethodTrailer class>>initialize (in category 'as yet unclassified') -----
- initialize
- 	"CompiledMethodTrailer initialize"
- 	^self convertTrailers
- !

Item was removed:
- ----- Method: OldMethodTrailer>>qDecompressFrom: (in category 'as yet unclassified') -----
- qDecompressFrom: input "<ReadStream on: ByteArray> ^<String>"
- 	"Decompress strings compressed by qCompress:.
- 	Most common 11 chars get values 0-10 packed in one 4-bit nibble;
- 	next most common 52 get values 12-15 (2 bits) * 16 plus next nibble;
- 	escaped chars get three nibbles"
- 	^ String streamContents:
- 		[:strm | | nextNibble nibble peek charTable char |
- 		charTable :=  "Character encoding table must match qCompress:"
- 		'ear tonsilcmbdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ012345[]()'.
- 		peek := true.
- 		nextNibble := [peek
- 						ifTrue: [peek := false. input peek ifNil: [0] ifNotNil: [:b| b // 16]]
- 						ifFalse: [peek := true. input next ifNil: [0] ifNotNil: [:b| b \\ 16]]].
- 		[input atEnd] whileFalse:
- 			[(nibble := nextNibble value) = 0
- 				ifTrue: [input atEnd ifFalse:
- 						[strm nextPut: (Character value: nextNibble value * 16 + nextNibble value)]]
- 				ifFalse:
- 					[nibble <= 11
- 						ifTrue:
- 							[strm nextPut: (charTable at: nibble)]
- 						ifFalse:
- 							[strm nextPut: (charTable at: nibble-12 * 16 + nextNibble value)]]]]!

Item was removed:
- ----- Method: OldMethodTrailer>>method: (in category 'as yet unclassified') -----
- method: aMethod
- 	"old method trailer format has only 3 kinds:
- 	 0 [ 0 0 0 ] - no trailer
- 	 source pointer
- 	 temps names
- 	"
- 	| flagByte |
- 	data := size := nil.
- 	method := aMethod.
- 	flagByte := method at: (method size).
- 
- 	kind := (flagByte = 0) ifTrue: [ #OldEmptyTrailer ] 
- 		ifFalse: [
- 			(flagByte < 252) ifTrue: [ #OldTempsNames ]
- 			ifFalse: [ #SourcePointer ]].
- 		
- 	"decode the trailer bytes"
- 	self perform: ('decode' , kind) asSymbol.
- 	
- 	"after decoding the trailer, size must be set"
- 	self assert: (size notNil).
- 
- !



More information about the Packages mailing list