[Vm-dev] VM Maker: VMMaker.oscog-eem.342.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Sep 2 23:17:04 UTC 2013


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.342.mcz

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

Name: VMMaker.oscog-eem.342
Author: eem
Time: 2 September 2013, 4:14:17.875 pm
UUID: a317db9c-c8be-424e-800c-8525d0bfe8fa
Ancestors: VMMaker.oscog-eem.341

Add oldSpace freeList support (still no allocInOldSpace).
Rename slotSize to numSlots to avoid confusion with misnamed slotSizeOf: (should be elementCountOf:).

=============== Diff against VMMaker.oscog-eem.341 ===============

Item was changed:
  ----- Method: CMM32LSBSimulator>>headerForSlots:format:classIndex: (in category 'header format') -----
  headerForSlots: numSlots format: formatField classIndex: classIndex
  	"The header format in LSB is
  	 MSB:	| 2 bits				|
  			| 22: identityHash	|
  			| 8: slotSize			|
  			| 3 bits				|
  			| 5: format			|
  			| 2 bits				|
  			| 22: classIndex		| : LSB"
+ 	self assert: (numSlots between: 0 and: self numSlotsMask).
- 	self assert: (numSlots between: 0 and: self slotSizeMask).
  	self assert: (formatField between: 0 and: 31).
  	self assert: (classIndex between: 0 and: 16r3fffff).
  	^super headerForSlots: numSlots format: formatField classIndex: classIndex!

Item was added:
+ ----- Method: CogMemoryManager>>addToFreeList: (in category 'garbage collection') -----
+ addToFreeList: freeChunk
+ 	| chunkBytes childBytes parent child index |
+ 	chunkBytes := self bytesInObject: freeChunk.
+ 	index := chunkBytes / self wordSize.
+ 	index < NumFreeLists ifTrue:
+ 		[self storePointerUnchecked: 0 ofObject: freeChunk withValue: (freeLists at: index).
+ 		 freeLists at: index put: freeChunk.
+ 		 ^self].
+ 	self
+ 		storePointerUnchecked: self freeChunkNextIndex ofObject: freeChunk withValue: 0;
+ 		storePointerUnchecked: self freeChunkParentIndex ofObject: freeChunk withValue: 0;
+ 		storePointerUnchecked: self freeChunkSmallerIndex ofObject: freeChunk withValue: 0;
+ 		storePointerUnchecked: self freeChunkLargerIndex ofObject: freeChunk withValue: 0.
+ 	"Large chunk list organized as a tree, each node of which is a list of chunks of the same size.
+ 	 Beneath the node are smaller and larger blocks."
+ 	parent := 0.
+ 	child := freeLists at: 0.
+ 	[child ~= 0] whileTrue:
+ 		[childBytes := self bytesInObject: child.
+ 		 childBytes = chunkBytes ifTrue: "size match; add to list at node."
+ 			[self storePointerUnchecked: self freeChunkNextIndex
+ 					ofObject: freeChunk
+ 						withValue: (self fetchPointer: self freeChunkNextIndex ofObject: child);
+ 				storePointerUnchecked: self freeChunkNextIndex
+ 					ofObject: child
+ 						withValue: freeChunk.
+ 			 ^self].
+ 		 "walk down the tree"
+ 		 parent := child.
+ 		 child := self fetchPointer: (childBytes > chunkBytes
+ 										ifTrue: [self freeChunkSmallerIndex]
+ 										ifFalse: [self freeChunkLargerIndex])
+ 					ofObject: child].
+ 	parent = 0 ifTrue:
+ 		[self assert: (freeLists at: 0) = 0.
+ 		 freeLists at: 0 put: freeChunk.
+ 		 ^self].
+ 	"insert in tree"
+ 	self storePointerUnchecked: self freeChunkParentIndex
+ 			ofObject: freeChunk
+ 				withValue: parent.
+ 	 self storePointerUnchecked: (childBytes > chunkBytes
+ 									ifTrue: [self freeChunkSmallerIndex]
+ 									ifFalse: [self freeChunkLargerIndex])
+ 			ofObject: parent
+ 				withValue: freeChunk!

Item was removed:
- ----- Method: CogMemoryManager>>baseSlotSizeOf: (in category 'object access') -----
- baseSlotSizeOf: oop
- 	<returnTypeC: #usqInt>
- 	| halfHeader slotSize |
- 	self flag: #endianness.
- 	halfHeader := self longAt: oop + 4.
- 	slotSize := halfHeader >> self slotSizeHalfShift bitAnd: self slotSizeMask.
- 	^slotSize = self slotSizeMask
- 		ifTrue: [self longAt: oop - self baseHeaderSize] "overflow slots; (2^32)-1 slots are plenty"
- 		ifFalse: [slotSize]!

Item was added:
+ ----- Method: CogMemoryManager>>freeChunkLargerIndex (in category 'garbage collection') -----
+ freeChunkLargerIndex
+ 	^3!

Item was added:
+ ----- Method: CogMemoryManager>>freeChunkNextIndex (in category 'garbage collection') -----
+ freeChunkNextIndex
+ 	^0!

Item was added:
+ ----- Method: CogMemoryManager>>freeChunkParentIndex (in category 'garbage collection') -----
+ freeChunkParentIndex
+ 	^1!

Item was added:
+ ----- Method: CogMemoryManager>>freeChunkSmallerIndex (in category 'garbage collection') -----
+ freeChunkSmallerIndex
+ 	^2!

Item was changed:
  ----- Method: CogMemoryManager>>headerForSlots:format:classIndex: (in category 'header format') -----
  headerForSlots: numSlots format: formatField classIndex: classIndex 
  	"The header format in LSB is
  	 MSB:	| 8: slotSize			| (on a byte boundary)
  			| 2 bits				|
  			| 22: identityHash	| (on a word boundary)
  			| 3 bits				|
  			| 5: format			| (on a byte boundary)
  			| 2 bits				|
  			| 22: classIndex		| (on a word boundary) : LSB
  	 The remaining bits (7) need to be used for
  		isGrey
  		isMarked
  		isRemembered
  		isPinned
  		isImmutable
  	 leaving 2 unused bits."
+ 	^ (numSlots << self numSlotsFullShift)
- 	^ (numSlots << self slotSizeFullShift)
  	+ (formatField << self formatShift)
  	+ classIndex!

Item was added:
+ ----- Method: CogMemoryManager>>initFreeChunkWithBytes:at: (in category 'garbage collection') -----
+ initFreeChunkWithBytes: numBytes at: address
+ 	| numSlots |
+ 	self assert: numBytes \\ self allocationUnit = 0.
+ 	numSlots := numBytes >> self shiftForWord
+ 				- (numBytes >= (self numSlotsMask << self shiftForWord)
+ 					ifTrue: [self baseHeaderSize + self baseHeaderSize / self wordSize]
+ 					ifFalse: [self baseHeaderSize / self wordSize]).
+ 	^self initFreeChunkWithSlots: numSlots at: address!

Item was changed:
  ----- Method: CogMemoryManager>>initialize (in category 'initialization') -----
  initialize
+ 	freeLists := CArrayAccessor on: (Array new: NumFreeLists withAll: 0)!
- 	freeLists := Array new: NumFreeLists. "gets an extra element in C"!

Item was changed:
  ----- Method: CogMemoryManager>>initializeOldSpaceFirstFree: (in category 'garbage collection') -----
  initializeOldSpaceFirstFree: startOfFreeOldSpace
  	<var: 'startOfFreeOldSpace' type: #usqLong>
  	| freeOldStart freeChunk |
  	<var: 'freeOldStart' type: #usqLong>
+ 	0 to: NumFreeLists - 1 do:
+ 		[:i| freeLists at: i put: 0].
- 	1 to: NumFreeLists do:
- 		[:i| freeLists at: i put: nil].
  	freeOldStart := startOfFreeOldSpace.
  	[endOfMemory - freeOldStart >= (2 raisedTo: 32)] whileTrue:
  		[freeChunk := self initFreeChunkWithSlots: (2 raisedTo: 32) / self wordSize at: freeOldStart.
  		self addToFreeList: freeChunk.
  		freeOldStart := self addressAfter: freeChunk].
+ 	freeChunk := self initFreeChunkWithBytes: endOfMemory - freeOldStart at: freeOldStart.
+ 	self addToFreeList: freeChunk.
+ 	self assert: (self addressAfter: freeChunk) = endOfMemory!
- 	freeChunk := self initFreeChunkWithSlots: endOfMemory - freeOldStart / self wordSize at: freeOldStart.
- 	self addToFreeList: freeChunk!

Item was changed:
  ----- Method: CogMemoryManager>>lastPointerOf: (in category 'object enumeration') -----
+ lastPointerOf: obj 
- lastPointerOf: oop 
  	"Answer the byte offset of the last pointer field of the given object.
  	 Works with CompiledMethods, as well as ordinary objects."
  	<api>
  	<inline: true>
  	<asmLabel: false>
  	| fmt header contextSize numLiterals |
  	<var: 'header' type: #usqLong>
+ 	header := self baseHeader: obj.
- 	header := self baseHeader: oop.
  	fmt := self formatOfHeader: header.
  	fmt <= self lastPointerFormat ifTrue:
  		[(fmt = self indexablePointersFormat
  		  and: [self isContextHeader: header]) ifTrue:
  			["contexts end at the stack pointer"
+ 			contextSize := coInterpreter fetchStackPointerOf: obj.
- 			contextSize := coInterpreter fetchStackPointerOf: oop.
  			^CtxtTempFrameStart + contextSize * BytesPerOop].
+ 		^(self numSlotsOf: obj) * BytesPerOop  "all pointers"].
- 		^(self baseSlotSizeOf: oop) * BytesPerOop  "all pointers"].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
+ 	numLiterals := coInterpreter literalCountOf: obj.
- 	numLiterals := coInterpreter literalCountOf: oop.
  	^numLiterals + LiteralStart * BytesPerOop!

Item was changed:
  ----- Method: CogMemoryManager>>nilFieldsOf: (in category 'primitive support') -----
  nilFieldsOf: obj 
+ 	0 to: (self numSlotsOf: obj) - 1 do:
- 	0 to: (self baseSlotSizeOf: obj) - 1 do:
  		[:i|
  		self storePointerUnchecked: i ofObject: obj withValue: nilObj]!

Item was added:
+ ----- Method: CogMemoryManager>>numSlotsFullShift (in category 'header format') -----
+ numSlotsFullShift
+ 	^56!

Item was added:
+ ----- Method: CogMemoryManager>>numSlotsHalfShift (in category 'header format') -----
+ numSlotsHalfShift
+ 	^24!

Item was added:
+ ----- Method: CogMemoryManager>>numSlotsMask (in category 'header format') -----
+ numSlotsMask
+ 	"8-bit slot count
+ 		max 64-bit small obj size 254 * 8 =  2032 bytes
+ 		max 32-bit small obj size 254 * 4 =   1016 bytes"
+ 	^255!

Item was added:
+ ----- Method: CogMemoryManager>>numSlotsOf: (in category 'object access') -----
+ numSlotsOf: objOop
+ 	<returnTypeC: #usqInt>
+ 	| halfHeader numSlots |
+ 	self flag: #endianness.
+ 	halfHeader := self longAt: objOop + 4.
+ 	numSlots := halfHeader >> self numSlotsHalfShift bitAnd: self numSlotsMask.
+ 	^numSlots = self numSlotsMask
+ 		ifTrue: [self longAt: objOop - self baseHeaderSize] "overflow slots; (2^32)-1 slots are plenty"
+ 		ifFalse: [numSlots]!

Item was removed:
- ----- Method: CogMemoryManager>>slotSizeFullShift (in category 'header format') -----
- slotSizeFullShift
- 	^56!

Item was removed:
- ----- Method: CogMemoryManager>>slotSizeHalfShift (in category 'header format') -----
- slotSizeHalfShift
- 	^24!

Item was removed:
- ----- Method: CogMemoryManager>>slotSizeMask (in category 'header format') -----
- slotSizeMask
- 	"8-bit slot size:
- 		max 64-bit small obj size 254 * 8 =  2032 bytes
- 		max 32-bit small obj size 254 * 4 =   1016 bytes"
- 	^255!

Item was changed:
  ----- Method: CogMemoryManager32Bits>>addressAfter: (in category 'object enumeration') -----
  addressAfter: objOop
  	"Answer the address immediately following an object."
+ 	| numSlots slotBytes |
+ 	numSlots := self numSlotsOf: objOop.
+ 	slotBytes := numSlots = 0
- 	| rawSlotSize slotBytes |
- 	rawSlotSize := self baseSlotSizeOf: objOop.
- 	slotBytes := rawSlotSize = 0
  					ifTrue: [self allocationUnit]
+ 					ifFalse: [numSlots + (numSlots bitAnd: 1) << self shiftForWord].
- 					ifFalse: [rawSlotSize + (rawSlotSize bitAnd: 1) << self shiftForWord].
  	^objOop + self baseHeaderSize + slotBytes!

Item was changed:
  ----- Method: CogMemoryManager32Bits>>allocateSlots:format:classIndex: (in category 'allocation') -----
  allocateSlots: numSlots format: formatField classIndex: classIndex
  	| numBytes newObj |
+ 	"Object headers are 8 bytes in length if the slot size fits in the num slots field (max implies overflow),
- 	"Object headers are 8 bytes in length if the slot size fits in the slot size field (max implies overflow),
  	 16 bytes otherwise (slot size in preceeding word).
  	 Objects always have at least one slot, for the forwarding pointer,
  	 and are multiples of 8 bytes in length."
+ 	numSlots >= self numSlotsMask
- 	numSlots >= self slotSizeMask
  		ifTrue:
  			[newObj := freeStart + self baseHeaderSize.
  			 numBytes := self baseHeaderSize + self baseHeaderSize "double header"
  						+ (numSlots + (numSlots bitAnd: 1) * self bytesPerSlot)] "roundTo allocationUnit"
  		ifFalse:
  			[newObj := freeStart.
  			 numBytes := self baseHeaderSize "single header"
  						+ (numSlots <= 1
  							ifTrue: [self allocationUnit] "at least one slot for the forwarding pointer"
  							ifFalse: [numSlots + (numSlots bitAnd: 1) * self bytesPerSlot])]. "roundTo allocationUnit"
  	self assert: numBytes \\ self allocationUnit = 0.
  	freeStart + numBytes > scavengeThreshold ifTrue:
  		[freeStart + numBytes > newSpaceLimit ifTrue:
  			[^self allocateSlotsInOldSpace: numSlots format: formatField classIndex: classIndex].
  		 self scheduleScavenge].
+ 	numSlots >= self numSlotsMask
- 	numSlots >= self slotSizeMask
  		ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  			[self flag: #endianness.
  			 self longAt: freeStart put: numSlots.
+ 			 self longAt: freeStart + 4 put: self numSlotsMask << self numSlotsHalfShift.
+ 			 self longLongAt: newObj put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)]
- 			 self longAt: freeStart + 4 put: self slotSizeMask << self slotSizeHalfShift.
- 			 self longLongAt: newObj put: (self headerForSlots: self slotSizeMask format: formatField classIndex: classIndex)]
  		ifFalse:
  			[self longLongAt: newObj put: (self headerForSlots: numSlots format: formatField classIndex: classIndex)].
  	self assert: numBytes \\ self allocationUnit = 0.
  	self assert: newObj \\ self allocationUnit = 0.
  	freeStart := freeStart + numBytes.
  	^newObj!

Item was added:
+ ----- Method: CogMemoryManager32Bits>>bytesInObject: (in category 'object enumeration') -----
+ bytesInObject: objOop
+ 	"Answer the total number of bytes in an object including header and possible overflow size header."
+ 	| halfHeader headerNumSlots numSlots |
+ 	self flag: #endianness.
+ 	halfHeader := self longAt: objOop + 4.
+ 	headerNumSlots := halfHeader >> self numSlotsHalfShift bitAnd: self numSlotsMask.
+ 	numSlots := headerNumSlots = self numSlotsMask
+ 					ifTrue: [self longAt: objOop - self baseHeaderSize]
+ 					ifFalse: [numSlots = 0 ifTrue: [1] ifFalse: [numSlots]].
+ 	^numSlots + (numSlots bitAnd: 1) << self shiftForWord
+ 	+ (headerNumSlots = self numSlotsMask
+ 		ifTrue: [self baseHeaderSize + self baseHeaderSize]
+ 		ifFalse: [self baseHeaderSize])!

Item was changed:
  ----- Method: CogMemoryManager32Bits>>initFreeChunkWithSlots:at: (in category 'garbage collection') -----
  initFreeChunkWithSlots: numSlots at: address 
  	self flag: #endianness.
  	self longAt: address put: numSlots;
+ 		longAt: address + 4 put: self numSlotsMask << self numSlotsHalfShift;
- 		longAt: address + 4 put: self slotSizeMask << self slotSizeHalfShift;
  		longAt: address + 8 put: 0; "0's classIndex; 0 = classIndex of free chunks"
+ 		longAt: address + 12 put: self numSlotsMask << self numSlotsHalfShift.
- 		longAt: address + 12 put: self slotSizeMask << self slotSizeHalfShift.
  	^address + 8!

Item was changed:
  ----- Method: CogMemoryManager32Bits>>objectAfter: (in category 'object enumeration') -----
  objectAfter: objOop
  	"Object parsing.
  	1. all objects have at least a word following the header, for a forwarding pointer.
+ 	2. objects with an overflow size have a preceeing word with a saturated numSlots.  If the word
+ 	   following an object doesn't have a saturated numSlots field it must be a single-header object.
+ 	   If the word following does have a saturated numSlots it must be the overflow size word."
- 	2. objects with an overflow size have a preceeing word with a saturated slotSize.  If the word following
- 	    an object doesn't have a saturated size field it must be a single-header object.  If the word following
- 	   does have a saturated slotSize it must be the overflow size word."
  	| followingWordAddress followingWord |
  	followingWordAddress := self addressAfter: objOop.
  	followingWordAddress >= freeStart ifTrue:
  		[^freeStart].
  	self flag: #endianness.
  	followingWord := self longAt: followingWordAddress + 4.
+ 	^followingWord >> self numSlotsHalfShift = self numSlotsMask
- 	^followingWord >> self slotSizeHalfShift = self slotSizeMask
  		ifTrue: [followingWordAddress + self baseHeaderSize]
  		ifFalse: [followingWordAddress]!

Item was changed:
  ----- Method: CogMemoryManager64Bits>>addressAfter: (in category 'object enumeration') -----
  addressAfter: objOop
  	"Answer the address immediately following an object."
+ 	| numSlots slotBytes |
+ 	numSlots := self numSlotsOf: objOop.
+ 	slotBytes := numSlots = 0
- 	| rawSlotSize slotBytes |
- 	rawSlotSize := self baseSlotSizeOf: objOop.
- 	slotBytes := rawSlotSize = 0
  					ifTrue: [self allocationUnit]
+ 					ifFalse: [numSlots << self shiftForWord].
- 					ifFalse: [rawSlotSize << self shiftForWord].
  	^objOop + self baseHeaderSize + slotBytes!

Item was changed:
  ----- Method: CogMemoryManager64Bits>>allocateSlots:format:classIndex: (in category 'allocation') -----
  allocateSlots: numSlots format: formatField classIndex: classIndex
  	| numBytes newObj |
+ 	"Object headers are 8 bytes in length if the slot size fits in the num slots field (max implies overflow),
+ 	 16 bytes otherwise (num slots in preceeding word).
- 	"Object headers are 8 bytes in length if the slot size fits in the slot size field (max implies overflow),
- 	 16 bytes otherwise (slot size in preceeding word).
  	 Objects always have at least one slot, for the forwarding pointer,
  	 and are multiples of 8 bytes in length."
+ 	numSlots >= self numSlotsMask
- 	numSlots >= self slotSizeMask
  		ifTrue:
  			[numSlots > 16rffffffff ifTrue:
  				[^nil].
  			 newObj := freeStart + self baseHeaderSize.
  			 numBytes := (self baseHeaderSize + self baseHeaderSize) "double header"
  						+ (numSlots * self bytesPerSlot)]
  		ifFalse:
  			[newObj := freeStart.
  			 numBytes := self baseHeaderSize "single header"
  						+ (numSlots < 1
  							ifTrue: [self allocationUnit] "at least one slot for the forwarding pointer"
  							ifFalse: [numSlots * self bytesPerSlot])].
  	
  	freeStart + numBytes > scavengeThreshold ifTrue:
  		[freeStart + numBytes > newSpaceLimit ifTrue:
  			[^self allocateSlotsInOldSpace: numSlots format: formatField classIndex: classIndex].
  		 self scheduleScavenge].
+ 	numSlots >= self numSlotsMask
- 	numSlots >= self slotSizeMask
  		ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  			[self flag: #endianness.
  			 self longAt: freeStart put: numSlots.
+ 			 self longAt: freeStart + 4 put: self numSlotsMask << self numSlotsHalfShift.
+ 			 self longLongAt: newObj put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)]
- 			 self longAt: freeStart + 4 put: self slotSizeMask << self slotSizeHalfShift.
- 			 self longLongAt: newObj put: (self headerForSlots: self slotSizeMask format: formatField classIndex: classIndex)]
  		ifFalse:
  			[self longLongAt: newObj put: (self headerForSlots: numSlots format: formatField classIndex: classIndex)].
  		freeStart := freeStart + numBytes.
  	^newObj!

Item was added:
+ ----- Method: CogMemoryManager64Bits>>bytesInObject: (in category 'object enumeration') -----
+ bytesInObject: objOop
+ 	"Answer the total number of bytes in an object including header and possible overflow size header."
+ 	| halfHeader headerNumSlots numSlots |
+ 	self flag: #endianness.
+ 	halfHeader := self longAt: objOop + 4.
+ 	headerNumSlots := halfHeader >> self numSlotsHalfShift bitAnd: self numSlotsMask.
+ 	numSlots := headerNumSlots = self numSlotsMask
+ 					ifTrue: [self longAt: objOop - self baseHeaderSize]
+ 					ifFalse: [numSlots = 0 ifTrue: [1] ifFalse: [numSlots]].
+ 	^numSlots << self shiftForWord
+ 	+ (headerNumSlots = self numSlotsMask
+ 		ifTrue: [self baseHeaderSize + self baseHeaderSize]
+ 		ifFalse: [self baseHeaderSize])!

Item was changed:
  ----- Method: CogMemoryManager64Bits>>initFreeChunkWithSlots:at: (in category 'garbage collection') -----
  initFreeChunkWithSlots: numSlots at: address 
  	self flag: #endianness.
+ 	self longAt: address put: self numSlotsMask << self numSlotsFullShift + numSlots;
+ 		longAt: address + 8 put: self numSlotsMask << self numSlotsFullShift. "0's classIndex; 0 = classIndex of free chunks"
- 	self longAt: address put: self slotSizeMask << self slotSizeFullShift + numSlots;
- 		longAt: address + 8 put: self slotSizeMask << self slotSizeFullShift. "0's classIndex; 0 = classIndex of free chunks"
  	^address + 8!

Item was changed:
  ----- Method: CogMemoryManager64Bits>>objectAfter: (in category 'object enumeration') -----
  objectAfter: objOop
  	"Object parsing.
  	1. all objects have at least a word following the header, for a forwarding pointer.
+ 	2. objects with an overflow size have a preceeing word with a saturated numSlots.  If the word
+ 	   following an object doesn't have a saturated numSlots field it must be a single-header object.
+ 	   If the word following does have a saturated numSlots it must be the overflow size word."
- 	2. objects with an overflow size have a preceeing word with a saturated slotSize.  If the word following
- 	    an object doesn't have a saturated size field it must be a single-header object.  If the word following
- 	   does have a saturated slotSize it must be the overflow size word."
  	| followingWordAddress followingWord |
  	followingWordAddress := self addressAfter: objOop.
  	followingWordAddress >= freeStart ifTrue:
  		[^freeStart].
  	self flag: #endianness.
  	followingWord := self longAt: followingWordAddress + 4.
+ 	^followingWord >> self numSlotsHalfShift = self numSlotsMask
- 	^followingWord >> self slotSizeHalfShift = self slotSizeMask
  		ifTrue: [followingWordAddress + self baseHeaderSize]
  		ifFalse: [followingWordAddress]!



More information about the Vm-dev mailing list