[squeak-dev] XML status in 4.3

Hernán Morales Durand hernan.morales at gmail.com
Tue Sep 25 06:50:38 UTC 2012


You may be interested if you work with XML in Squeak. The instructions 
in http://www.squeaksource.com/XMLSupport.html for Squeak 4.3 only 
produces endless debuggers. It seems there are unsynchronized YAXO XML 
versions: In the Squeak trunk repo and XML-Parser in SqS 
(http://www.squeaksource.com/XMLSupport). The last common ancestor is:

Name: XML-Parser-Alexandre_Bergel.19
UUID: a8fe6c4d-fa69-4921-8ef5-f939749ee78b
Ancestors: XML-Parser-Alexandre_Bergel.18

Minor change in XMLElement>>contentString.

I've managed to merge the contents from XMLSupport, but have to manually 
file in two missing dependencies:

-OrderPreservingDictionary
-BitmapCharacterSet

which I've attached here. If you have comments or better approaches I'd 
be glad to see it.
Cheers,

Hernán
-------------- next part --------------
'From Pharo1.4 of 18 April 2012 [Latest update: #14459] on 25 September 2012 at 1:33:21 am'!
Collection subclass: #BitmapCharacterSet
	instanceVariableNames: 'byteCharacters wideCharacters'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-BitmapCharacterSet'!
!BitmapCharacterSet commentStamp: '<historical>' prior: 0!
This class implements a set of Character objects that uses a bitmap internally for multibyte characters to quickly tell if they belongs to it or not, rather than using a Dictionary like WideCharacterSet does. Byte characters are tested using a 256-element ByteArray.!


!BitmapCharacterSet methodsFor: 'accessing' stamp: 'JAAyer 1/20/2011 01:05'!
capacity
	^ byteCharacters size +
		(wideCharacters
			ifNil: [0]
			ifNotNil: [(wideCharacters size) * 8 - 256]).! !


!BitmapCharacterSet methodsFor: 'adding' stamp: 'JAAyer 1/20/2011 01:05'!
add: aCharacter
	| asciiValue |

	(asciiValue := aCharacter asciiValue) > 255
		ifTrue: [| byteIndex |
			byteIndex := (asciiValue / 8) asInteger + 1.
			(wideCharacters isNil or: [byteIndex > wideCharacters size])
				ifTrue: [self growWideCharacterBitmapTo: (byteIndex * 1.5) asInteger].
			wideCharacters
				at: byteIndex
				put:
					((wideCharacters at: byteIndex)
						bitOr: (16r80 bitShift: (asciiValue \\ 8) negated))]
		ifFalse: [byteCharacters at: asciiValue + 1 put: 1].
	^ aCharacter.! !


!BitmapCharacterSet methodsFor: 'comparing' stamp: 'JAAyer 1/20/2011 01:06'!
= anObject
	^ self == anObject
		or: [self class == anObject class
			and: [byteCharacters = anObject byteCharacters
				and: [wideCharacters = anObject wideCharacters]]].! !


!BitmapCharacterSet methodsFor: 'copying' stamp: 'JAAyer 1/20/2011 01:05'!
postCopy
	byteCharacters := byteCharacters copy.
	wideCharacters
		ifNotNil: [wideCharacters := wideCharacters copy].! !


!BitmapCharacterSet methodsFor: 'enumerating' stamp: 'JAAyer 1/20/2011 01:05'!
do: aBlock
	byteCharacters doWithIndex: [:each :i |
		each = 1
			ifTrue: [aBlock value: (Character value: i - 1)]].

	wideCharacters ifNil: [^ self].
	wideCharacters doWithIndex: [:each :byteIndex |
		0 to: 7 do: [:shiftIndex |
			(each bitAnd: (16r80 bitShift: shiftIndex negated)) > 0
				ifTrue: [aBlock value: (Character value: (byteIndex - 1) * 8 + shiftIndex)]]]! !


!BitmapCharacterSet methodsFor: 'initialization' stamp: 'JAAyer 1/20/2011 01:05'!
initialize: aCapacity
	byteCharacters := ByteArray new: 256.
	aCapacity > 256
		ifTrue: [self growWideCharacterBitmapTo: ((aCapacity - 1) / 8) asInteger + 1].! !


!BitmapCharacterSet methodsFor: 'removing' stamp: 'JAAyer 1/20/2011 01:05'!
remove: aCharacter ifAbsent: aBlock
	| asciiValue |

	(asciiValue := aCharacter asciiValue) > 255
		ifTrue: [| byteIndex byte bitmask |
			byteIndex := (asciiValue / 8) asInteger + 1.
			(wideCharacters isNil or: [byteIndex > wideCharacters size])
				ifTrue: [^ aBlock value].
			bitmask := 16r80 bitShift: (asciiValue \\ 8) negated.
			((byte := wideCharacters at: byteIndex) bitAnd: bitmask) > 0
				ifFalse: [^ aBlock value].
			wideCharacters at: byteIndex put: (byte bitAnd: bitmask bitInvert)]
		ifFalse: [
			(byteCharacters at: asciiValue + 1) = 1
				ifFalse: [^ aBlock value].
			byteCharacters at: asciiValue + 1 put: 0].
	^ aCharacter.! !


!BitmapCharacterSet methodsFor: 'testing' stamp: 'JAAyer 1/20/2011 01:09'!
hash
	| hash |

	hash := byteCharacters hash.
	wideCharacters
		ifNotNil: [hash := hash bitXor: wideCharacters hash].
	^ hash.! !

!BitmapCharacterSet methodsFor: 'testing' stamp: 'JAAyer 1/20/2011 01:05'!
includes: aCharacter
	| asciiValue |

	^ (asciiValue := aCharacter asciiValue) > 255
		ifTrue: [ | byteIndex |
			byteIndex := (asciiValue / 8) asInteger + 1.
			(wideCharacters isNil or: [byteIndex > wideCharacters size])
				ifTrue: [^ false].
			^ ((wideCharacters at: byteIndex)
				bitAnd: (16r80 bitShift: (asciiValue \\ 8) negated)) > 0]
		ifFalse: [(byteCharacters at: asciiValue + 1) = 1]! !


!BitmapCharacterSet methodsFor: 'private' stamp: 'JAAyer 1/20/2011 01:05'!
byteCharacters
	^ byteCharacters! !

!BitmapCharacterSet methodsFor: 'private' stamp: 'JAAyer 1/20/2011 01:05'!
growWideCharacterBitmapTo: aSize
	wideCharacters
		ifNil: [
			wideCharacters := ByteArray new: aSize.
			^ self].

	wideCharacters :=
		(ByteArray new: aSize)
			replaceFrom: 1
			to: wideCharacters size
			with: wideCharacters
			startingAt: 1.! !

!BitmapCharacterSet methodsFor: 'private' stamp: 'JAAyer 1/20/2011 01:05'!
wideCharacters
	^ wideCharacters! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

BitmapCharacterSet class
	instanceVariableNames: ''!

!BitmapCharacterSet class methodsFor: 'instance creation' stamp: 'JAAyer 1/19/2011 23:03'!
new
	^ self new: 256! !

!BitmapCharacterSet class methodsFor: 'instance creation' stamp: 'JAAyer 1/19/2011 23:04'!
new: aCapacity
	^ self basicNew initialize: aCapacity! !

!BitmapCharacterSet class methodsFor: 'instance creation' stamp: 'JAAyer 1/20/2011 00:52'!
newFrom: aCollection
	^ self new
		addAll: aCollection;
		yourself	! !
-------------- next part --------------
'From Pharo1.4 of 18 April 2012 [Latest update: #14459] on 25 September 2012 at 1:43:25 am'!
Collection subclass: #OrderPreservingDictionary
	instanceVariableNames: 'dictionary orderedKeys defaultValue'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-OrderPreservingDictionary'!
!OrderPreservingDictionary commentStamp: '<historical>' prior: 0!
This class is a Dictionary that preserves the order of its aassociations. That means messages that return collections of keys, values or associations and messages that enumerate those collections all operate based on the order that the underlying associations were added to the receiver. Association order is not, however, considered when comparing dictionaries for equality. As a result, instances can be compared safely with regular Dictionaries, and if they contain the same associations, regardless of the order, they wil be considered equal. Instances also return a configurable default value, which is nil by default, when an absent key or value is requested from it rather than raising an exception. Other than those differences, this class can generally be used the same way Dictionary can.

(This class is not a subclass of HashedCollection due to a belief that relying on the public API of Dictionary is probably a safer long-term bet than relying on the public and private API of a relatively recent addition to Squeak and Pharo.)!


!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 1/16/2011 13:57'!
associationAt: aKey
	^ self associationAt: aKey ifAbsent: [nil]! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:11'!
associationAt: aKey ifAbsent: aBlock
	^ dictionary associationAt: aKey ifAbsent: aBlock! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 19:05'!
associations
	| associations i |

	associations := Array new: self size.
	i := 1.
	self associationsDo: [:each |
		associations at: i put: each.
		i := i + 1].
	^ associations.! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 12/4/2010 20:39'!
at: aKey
	^ self at: aKey ifAbsent: [defaultValue]! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:14'!
at: aKey ifAbsent: aBlock
	^ dictionary at: aKey ifAbsent: aBlock! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:17'!
at: aKey ifAbsentPut: aBlock
	^ self at: aKey ifAbsent: [self at: aKey put: aBlock value]! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 19:21'!
at: aKey ifPresent: aBlock
	^ dictionary at: aKey ifPresent: aBlock! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:29'!
at: aKey put: aBlock
	self addOrderedKeyIfAbsent: aKey.
	^ dictionary at: aKey put: aBlock.! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:31'!
capacity
	^ dictionary capacity! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 12/4/2010 20:39'!
defaultValue
	^ defaultValue! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 12/4/2010 20:39'!
defaultValue: aDefaultValue
	defaultValue := aDefaultValue! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 12/4/2010 20:40'!
keyAtIdentityValue: aValue
	^ self keyAtIdentityValue: aValue ifAbsent: [defaultValue]! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:30'!
keyAtIdentityValue: aValue ifAbsent: aBlock
	^ dictionary keyAtIdentityValue: aValue ifAbsent: aBlock! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 12/4/2010 20:40'!
keyAtValue: aValue
	^ self keyAtValue: aValue ifAbsent: [defaultValue]! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:19'!
keyAtValue: aValue ifAbsent: aBlock
	^ dictionary keyAtValue: aValue ifAbsent: aBlock! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 19:12'!
keyForIdentity: anObject
	^ dictionary keyForIdentity: anObject! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 7/12/2010 05:11'!
keys
	^ Array newFrom: orderedKeys! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:31'!
keysSortedSafely
	^ dictionary keysSortedSafely! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:27'!
size
	^ dictionary size! !

!OrderPreservingDictionary methodsFor: 'accessing' stamp: 'JAAyer 8/4/2010 17:25'!
values
	^ self associations collect: [:each | each value]! !


!OrderPreservingDictionary methodsFor: 'adding' stamp: 'JAAyer 8/4/2010 17:20'!
add: anAssociation
	self addOrderedKeyIfAbsent: anAssociation key.
	^ dictionary add: anAssociation.! !

!OrderPreservingDictionary methodsFor: 'adding' stamp: 'JAAyer 1/15/2011 23:27'!
addAll: aKeyedCollection
	"This method can accept any collection of associations, not just Dictionaries, because is uses
	#associationsDo rather than #keysAndValuesDo:, and #associationsDo: has a default implementation in
	Collection that just sends #do:. Since this is an order-preserving dictionary, you should be able to add
	multiple associations at once from a SequenceableCollection and have their order be preserved."

	aKeyedCollection associationsDo: [:each | self add: each].
	^ aKeyedCollection.! !


!OrderPreservingDictionary methodsFor: 'comparing' stamp: 'JAAyer 12/4/2010 21:18'!
= anObject
	^ self == anObject
		or: [anObject isDictionary and: [dictionary = anObject]]! !


!OrderPreservingDictionary methodsFor: 'copying' stamp: 'JAAyer 12/5/2010 11:25'!
copyEmpty
	^ self species defaultValue: defaultValue! !

!OrderPreservingDictionary methodsFor: 'copying' stamp: 'JAAyer 8/4/2010 19:17'!
postCopy
	orderedKeys := orderedKeys copy.
	dictionary := dictionary copy.! !


!OrderPreservingDictionary methodsFor: 'enumerating' stamp: 'JAAyer 8/4/2010 18:04'!
associationsDo: aBlock
	self keysDo: [:each | aBlock value: (self associationAt: each)]! !

!OrderPreservingDictionary methodsFor: 'enumerating' stamp: 'JAAyer 8/4/2010 18:05'!
associationsSelect: aBlock
	^ self species newFrom: (self associations select: aBlock)! !

!OrderPreservingDictionary methodsFor: 'enumerating' stamp: 'JAAyer 8/4/2010 19:28'!
collect: aBlock
	^ self species newFrom:
		(self associations collect: [:each |
			each key -> (aBlock value: each value)])! !

!OrderPreservingDictionary methodsFor: 'enumerating' stamp: 'JAAyer 8/4/2010 17:44'!
do: aBlock
	self valuesDo: aBlock! !

!OrderPreservingDictionary methodsFor: 'enumerating' stamp: 'JAAyer 3/6/2010 23:03'!
keysAndValuesDo: aBlock
	self keysDo: [:each | aBlock value: each value: (self at: each)]! !

!OrderPreservingDictionary methodsFor: 'enumerating' stamp: 'JAAyer 3/6/2010 23:15'!
keysDo: aBlock
	orderedKeys do: aBlock! !

!OrderPreservingDictionary methodsFor: 'enumerating' stamp: 'JAAyer 8/4/2010 19:39'!
select: aBlock
	^ self species newFrom:
		(self associations select: [:each | aBlock value: each value])! !

!OrderPreservingDictionary methodsFor: 'enumerating' stamp: 'JAAyer 8/4/2010 18:03'!
valuesDo: aBlock
	self keysDo: [:each | aBlock value: (self at: each)]! !


!OrderPreservingDictionary methodsFor: 'initialization' stamp: 'JAAyer 12/4/2010 20:34'!
initialize: aCapacity withDefaultValue: aDefaultValue
	dictionary := Dictionary new: aCapacity.
	orderedKeys := OrderedCollection new: aCapacity.
	defaultValue := aDefaultValue.! !


!OrderPreservingDictionary methodsFor: 'inspecting' stamp: 'JAAyer 8/4/2010 17:11'!
inspectorClass
	^ DictionaryInspector! !


!OrderPreservingDictionary methodsFor: 'printing' stamp: 'JAAyer 3/7/2010 21:39'!
printElementsOn: aStream
	self ifEmpty: [^ self].

	aStream nextPut: $(.
	self associations doWithIndex: [:associaiton :i |
		aStream
			print: associaiton key;
			nextPutAll: '->';
			print: associaiton value.
		(i < self size)
			ifTrue: [aStream space]].
	aStream nextPut: $).! !

!OrderPreservingDictionary methodsFor: 'printing' stamp: 'JAAyer 3/12/2010 08:17'!
printNameOn: aStream
	aStream
		nextPutAll: 'an';
		space;
		nextPutAll: self class name! !


!OrderPreservingDictionary methodsFor: 'removing' stamp: 'JAAyer 8/4/2010 20:39'!
keysAndValuesRemove: aTwoArgumentBlock
	| removedAssociations |

	removedAssociations := OrderedCollection new.
	self associationsDo: [:each |
		(aTwoArgumentBlock value: each key value: each value)
			ifTrue: [removedAssociations add: each]].
	removedAssociations do: [:each | self removeKey: each key].! !

!OrderPreservingDictionary methodsFor: 'removing' stamp: 'JAAyer 8/4/2010 18:11'!
remove: anObject ifAbsent: aBlock
	self shouldNotImplement! !

!OrderPreservingDictionary methodsFor: 'removing' stamp: 'JAAyer 8/4/2010 18:11'!
removeAll
	orderedKeys removeAll.
	dictionary removeAll.! !

!OrderPreservingDictionary methodsFor: 'removing' stamp: 'JAAyer 12/4/2010 20:40'!
removeKey: aKey
	^ self removeKey: aKey ifAbsent: [defaultValue]! !

!OrderPreservingDictionary methodsFor: 'removing' stamp: 'JAAyer 8/4/2010 18:12'!
removeKey: aKey ifAbsent: aBlock
	self removeOrderedKeyIfPresent: aKey.
	^ dictionary removeKey: aKey ifAbsent: aBlock.! !


!OrderPreservingDictionary methodsFor: 'testing' stamp: 'JAAyer 8/4/2010 17:37'!
hash
	^ dictionary hash! !

!OrderPreservingDictionary methodsFor: 'testing' stamp: 'JAAyer 8/4/2010 17:40'!
includes: anObject
	^ dictionary includes: anObject! !

!OrderPreservingDictionary methodsFor: 'testing' stamp: 'JAAyer 8/4/2010 17:41'!
includesAssociation: anAssociation
	^ dictionary includesAssociation: anAssociation! !

!OrderPreservingDictionary methodsFor: 'testing' stamp: 'JAAyer 8/4/2010 17:41'!
includesIdentity: anObject
	^ dictionary includesIdentity: anObject! !

!OrderPreservingDictionary methodsFor: 'testing' stamp: 'JAAyer 8/4/2010 17:40'!
includesKey: aKey
	^ dictionary includesKey: aKey! !

!OrderPreservingDictionary methodsFor: 'testing' stamp: 'JAAyer 8/4/2010 17:09'!
isDictionary
	^ true! !

!OrderPreservingDictionary methodsFor: 'testing' stamp: 'JAAyer 8/4/2010 17:27'!
occurrencesOf: anObject
	^ self values
		inject: 0
		into: [:total :each |
			each = anObject
				ifTrue: [total + 1]
				ifFalse: [total]]! !


!OrderPreservingDictionary methodsFor: 'private' stamp: 'JAAyer 8/4/2010 19:04'!
addOrderedKeyIfAbsent: aString
	(dictionary includesKey: aString)
		ifFalse: [orderedKeys addLast: aString]! !

!OrderPreservingDictionary methodsFor: 'private' stamp: 'JAAyer 10/15/2010 14:07'!
dictionary
	^ dictionary! !

!OrderPreservingDictionary methodsFor: 'private' stamp: 'JAAyer 8/4/2010 18:12'!
removeOrderedKeyIfPresent: aKey
	(self includesKey: aKey)
		ifTrue: [orderedKeys remove: aKey]! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

OrderPreservingDictionary class
	instanceVariableNames: ''!

!OrderPreservingDictionary class methodsFor: 'instance creation' stamp: 'JAAyer 12/5/2010 11:21'!
defaultValue: aDefaultValue
	^ self new defaultValue: aDefaultValue! !

!OrderPreservingDictionary class methodsFor: 'instance creation' stamp: 'JAAyer 12/4/2010 20:36'!
new
	^ self new: 10! !

!OrderPreservingDictionary class methodsFor: 'instance creation' stamp: 'JAAyer 12/4/2010 20:37'!
new: aCapacity
	^ self new: aCapacity withDefaultValue: nil! !

!OrderPreservingDictionary class methodsFor: 'instance creation' stamp: 'JAAyer 12/4/2010 20:36'!
new: aCapacity withDefaultValue: aDefaultValue
	^ self basicNew initialize: aCapacity withDefaultValue: aDefaultValue! !

!OrderPreservingDictionary class methodsFor: 'instance creation' stamp: 'JAAyer 12/4/2010 20:41'!
newFrom: aDictionaryOrArray
	| newDictionary |

	newDictionary := self new: aDictionaryOrArray size.
	aDictionaryOrArray associationsDo: [:each | newDictionary add: each].
	(aDictionaryOrArray respondsTo: #defaultValue)
		ifTrue: [newDictionary defaultValue: aDictionaryOrArray defaultValue].
	^ newDictionary.! !


More information about the Squeak-dev mailing list