[squeak-dev] The Inbox: Network-EG.246.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jul 20 18:16:51 UTC 2021


A new version of Network was added to project The Inbox:
http://source.squeak.org/inbox/Network-EG.246.mcz

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

Name: Network-EG.246
Author: EG
Time: 20 July 2021, 2:16:51.031725 pm
UUID: 286844ab-38ff-4f7d-97a4-37d69eda41e5
Ancestors: Network-ct.245

Adding methods and helpers for:
1. Converting from an IPv6 string to an IPv6 ByteArray;
2. Converting from an IPv6 ByteArray to a valid IPv6 string.
  
Note that the complexity here is mostly taken up in dealing with the IPv6 "feature" of compressing the longest consecutive series of 0 values to the string '::'.
  
I have also updated the plain #addressFromString: and #stringFromAddress: methods to first try and see if they are dealing with what appears to be and IPv6 string/bytes and to call the IPv6 specialized versions of the method if so.

=============== Diff against Network-ct.245 ===============

Item was added:
+ ----- Method: NetNameResolver class>>addressFromIPv6String: (in category 'address string utils') -----
+ addressFromIPv6String: aString
+ 	"Return a ByteArray corresponding to an IPv6 address in text format"
+ 	| stream headStream headBytes tailStream tailBytes hextets |
+ 	headStream := WriteStream on: ByteArray new.
+ 	tailStream := WriteStream on: ByteArray new.
+ 	
+ 	"Obtain a collection of the string hextets from the
+ 	original IPv6 string. Any instance of a double colon (::)
+ 	will be present in the list as an empty string."
+ 	hextets := self splitIPv6HextetsOn: aString.
+ 	Transcript show: hextets; cr.
+ 	stream := hextets readStream.
+ 	(stream upTo: '') do: [ :hextet |
+ 		headStream nextPutAll: (ByteArray readHexFrom: hextet) ].
+ 	(stream upToEnd) do: [ :hextet |
+ 		tailStream nextPutAll: (ByteArray readHexFrom: hextet) ].
+ 	headBytes := headStream contents.
+ 	tailBytes := tailStream contents.
+ 	
+ 	"If the total number of bytes is less than 16, that means
+ 	we have a compressed range of 0-value hextets specified
+ 	using the double colon (::). We add these at the end of
+ 	the headBytes collection"
+ 	(16 - (headBytes size + tailBytes size)) timesRepeat: [
+ 		headBytes := headBytes,#[0] ].
+ 	
+ 	^ headBytes,tailBytes!

Item was changed:
  ----- Method: NetNameResolver class>>addressFromString: (in category 'address string utils') -----
  addressFromString: addressString
  	"Return the internet address represented by the given string. The string should contain four positive decimal integers delimited by periods, commas, or spaces, where each integer represents one address byte. Return nil if the string is not a host address in an acceptable format."
  	"NetNameResolver addressFromString: '1.2.3.4'"
  	"NetNameResolver addressFromString: '1,2,3,4'"
  	"NetNameResolver addressFromString: '1 2 3 4'"
  
  	| newAddr s byte delimiter |
+ 	"If the address string contains a colon, then we
+ 	consider it an IPv6 address"
+ 	(addressString includes: $:) ifTrue: [ ^ self addressFromIPv6String: addressString ].
+ 	
+ 	"Otherwise parse as a normal IPv4 string"
  	newAddr := ByteArray new: 4.
  	s := ReadStream on: addressString.
  	s skipSeparators.
  	1 to: 4 do: [:i |
  		byte := self readDecimalByteFrom: s.
  		byte = nil ifTrue: [^ nil].
  		newAddr at: i put: byte.
  		i < 4 ifTrue: [
  			delimiter := s next.
  			((delimiter = $.) or: [(delimiter = $,) or: [delimiter = $ ]])
  				ifFalse: [^ nil]]].
  	^ newAddr
  !

Item was added:
+ ----- Method: NetNameResolver class>>findLongestIPv6ZerosIn: (in category 'private') -----
+ findLongestIPv6ZerosIn: aCollection
+ 	"Given a collection of Integers, find the longest (or leftmost)
+ 	range of contiguous consecutive zero values (if any).
+ 	Respond with a size 2 array corresponding to the start
+ 	and end index, or nil if there are no zero ranges at all"
+ 	| active start end cursor ranges largest firstLargest |
+ 	active := false. "Whether or not the beginning of some range has been found"
+ 	start := 0.
+ 	end := 0.
+ 	ranges := OrderedCollection new.
+ 	cursor := 1.
+ 	[ cursor < aCollection size ] whileTrue: [
+ 		| current next isConsecutive |
+ 		current := aCollection at: cursor.
+ 		next := aCollection at: cursor + 1.
+ 		isConsecutive := (current = 0) and: [ next = 0].
+ 		
+ 		isConsecutive
+ 			ifTrue: [ 
+ 				active
+ 					ifFalse: [
+ 						"If the current values are consecutive zeros,
+ 						and we are not active, set active to true and update
+ 						the start and end values." 
+ 						start := cursor.
+ 						end := cursor + 1.
+ 						active := true ]
+ 					ifTrue: [ 
+ 						"If the current values are consecutive zeros,
+ 						and we _are_ active, this means we need to just
+ 						update the end"
+ 						end := cursor + 1 ] ].
+ 
+ 			
+ 		"If we are active, but the values are _not_ consecutive,
+ 		it means we've reached the end of a range"
+ 		((active and: [ isConsecutive not ]) or: [ (active and: [ (cursor + 1) = aCollection size ])])
+ 			ifTrue: [
+ 				active := false.
+ 				ranges add: { start. end }.
+ 				start := 0.
+ 				end := 0 ].
+ 		
+ 		"Increment the cursor"
+ 		cursor := cursor + 1.
+ 	].
+ 
+ 	"If there are no zero ranges, return nil."
+ 	ranges ifEmpty: [ ^ nil ].
+ 	
+ 	"Otherwise, return the longest range.
+ 	If there are multiple ranges with the same size,
+ 	return the first (leftmost) encountered."
+ 	largest := 0.
+ 	firstLargest := 1. "index of the first instance of the largest value, in case there are multiple with same size"
+ 	(ranges collect: [ :range |
+ 		(range last - range first )]) doWithIndex: [ :rangeSize :index |
+ 			rangeSize > largest ifTrue: [ 
+ 				largest := rangeSize.
+ 				firstLargest := index ] ].
+ 	
+ 	^ ranges at: firstLargest!

Item was added:
+ ----- Method: NetNameResolver class>>putIPv6HexIntegers:on: (in category 'private') -----
+ putIPv6HexIntegers: aCollection on: aWriteStream
+ 	"Given a collection of Integers, convert them to
+ 	hex strings and join them with the ':' separator
+ 	on the given write stream"
+ 	aCollection 
+ 		do: [ :integer |
+ 			aWriteStream nextPutAll: (integer printStringBase: 16) asLowercase ]
+ 		separatedBy: [ aWriteStream nextPut: $: ]
+ 	
+ 	!

Item was added:
+ ----- Method: NetNameResolver class>>splitIPv6HextetsOn: (in category 'private') -----
+ splitIPv6HextetsOn: aString
+ 	"Respond with a collection of hextet strings extracted
+ 	from a single string in IPv6 format. These are separated
+ 	by the $: character.
+ 	We avoid using #splitOn: or #splitBy: since they
+ 	are not consistent across Smalltalks"
+ 	| stream result |
+ 	result := OrderedCollection new.
+ 	stream := aString readStream.
+ 	[ stream atEnd ] whileFalse: [ 
+ 		"Pad any valid hextets so that they are each length 4, 
+ 		ie they have the leading zeros. This is so that ByteArray class >> #readFromHex:
+ 		will work properly -- it does not correctly parse hextets without the leading zeros."
+ 		| next |
+ 		next := stream upTo: $:.
+ 		(next = '')
+ 			ifTrue: [ result add: next ]
+ 			ifFalse: [
+ 				(4 - next size) timesRepeat: [
+ 					next := '0',next ].
+ 				result add: next ] ].
+ 	
+ 	^ result!

Item was changed:
  ----- Method: NetNameResolver class>>stringFromAddress: (in category 'address string utils') -----
  stringFromAddress: addr
  	"Return a string representing the given host address as four decimal bytes delimited with decimal points."
  	"NetNameResolver stringFromAddress: NetNameResolver localHostAddress"
  
  	| s |	
  	(addr isKindOf: SocketAddress) ifTrue: [^addr printString copyUpTo: $( ].
+ 	"If the incoming addr is a size 16 ByteArray, we assume it is
+ 	representing an IPv6 address."
+ 	(addr size = 16) ifTrue: [ ^ self stringFromIPv6Address: addr ].
+ 	
+ 	"Otherwise write out in IPv4 format"
  	s := WriteStream on: ''.
  	1 to: 3 do: [ :i | (addr at: i) printOn: s. s nextPut: $.].
  	(addr at: 4) printOn: s.
  	^ s contents
  !

Item was added:
+ ----- Method: NetNameResolver class>>stringFromIPv6Address: (in category 'address string utils') -----
+ stringFromIPv6Address: aByteArray
+ 	"Respond with a correctly formatted IPv6 string
+ 	parsed from the incoming ByteArray.
+ 	Note the 'compressed-zero' rule for IPv6 address strings:
+ 	the longest contiguous range of two or more consecutive
+ 	0 values can be compressed to '::'.
+ 	If there are two ranges of the same size, use the leftmost"
+ 	| readStream integerCollection indices writeStream |
+ 	
+ 	"If the ByteArray as an Integer is zero (ie, it's all zeros),
+ 	then just return the double colon"
+ 	aByteArray asInteger = 0 ifTrue: [ ^ '::' ].
+ 	
+ 	readStream := aByteArray readStream.
+ 	integerCollection := OrderedCollection new.
+ 	[ readStream atEnd ] whileFalse: [
+ 		integerCollection add: (readStream next: 2) asInteger ].
+ 	
+ 	"Find the start and end indices of the longest
+ 	contiguous set of zeroes, if any"
+ 	writeStream := WriteStream on: String new.
+ 	indices := self findLongestIPv6ZerosIn: integerCollection.
+ 	indices ifNil: [
+ 		self putIPv6HexIntegers: integerCollection on: writeStream.
+ 		^ writeStream contents ].
+ 	
+ 	"If the start index of the zeros is 1, then there are contiguous
+ 	zeros at the beginning of the string"
+ 	(indices first = 1) ifTrue: [
+ 		writeStream nextPutAll: '::'.
+ 		self 
+ 			putIPv6HexIntegers:  (integerCollection copyFrom: (indices second + 1) to: integerCollection size)
+ 			on: writeStream.
+ 		^ writeStream contents ].
+ 	
+ 	"If the end index of the zeros is the same as the size
+ 	of the collection of integers, then there are contiguous
+ 	zeros at the end of the string."
+ 	(indices second = integerCollection size)
+ 		ifTrue: [
+ 			self
+ 				putIPv6HexIntegers: (integerCollection copyFrom: 1 to: (indices first - 1))
+ 				on: writeStream.
+ 			writeStream nextPutAll: '::'.
+ 			^ writeStream contents ].
+ 		
+ 	"Otherwise, there is a range of zeros somewhere in the middle
+ 	of the string that should get compressed. Write normal strings for
+ 	each side out of the range of the indices, then join them by the
+ 	compression string (::)"
+ 	self
+ 		putIPv6HexIntegers: (integerCollection copyFrom: 1 to: (indices first - 1))
+ 		on: writeStream.
+ 	writeStream nextPutAll: '::'.
+ 	self
+ 		putIPv6HexIntegers: (integerCollection copyFrom: (indices second + 1) to: integerCollection size)
+ 		on: writeStream.
+ 	^ writeStream contents
+ 	
+ 	
+ 	!



More information about the Squeak-dev mailing list