presence feddsch

Niko Schwarz niko.schwarz at gmx.net
Mon Feb 17 18:11:04 UTC 2003


-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

So, jetzt klappt alles ganz gut.
Ich bau jetzt das gui, fühl dich eingeladen, an allem rumzuschreiben, was dir 
nicht gefällt.

slt,

niko
- -- 
WHERE CAN THE MATTER BE

	Oh, dear, where can the matter be
	When it's converted to energy?
	There is a slight loss of parity.
	Johnny's so long at the fair.
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.2.1 (GNU/Linux)

iD8DBQE+USW43P3nmXTVnC8RApiXAJ9DI4LQXqc7nM/CNctaoFrhw57mwgCeJvVm
imfufrPjZbkykileTVbZ00g=
=ttJ7
-----END PGP SIGNATURE-----
-------------- next part --------------
'From Squeak3.4gamma of ''7 January 2003'' [latest update: #5168] on 17 February 2003 at 7:08:50 pm'!
Error subclass: #AuthenticationException
	instanceVariableNames: 'query '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Jabber'!
Object subclass: #JabberConnection
	instanceVariableNames: 'socket readProc usrName domainString channels semaphore '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Jabber'!

!JabberConnection commentStamp: 'NES 2/17/2003 18:20' prior: 0!
A connection to a jabber server.

For examples see the JabberTests.

Structure:
semaphore		Semaphore -- notifies the authenticateName:password:resource: message that an answer arrived


This is the very heart of the jabber protocol implementation.!

TestCase subclass: #JabberTests
	instanceVariableNames: 'c '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Jabber'!
XMLElement subclass: #JabberElement
	instanceVariableNames: 'connection '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Jabber'!

!JabberElement commentStamp: 'NES 2/17/2003 16:35' prior: 0!
This is an abstract superclass for a few special elements from the jabber protocol specification.
Many elements in jabber share some attributes, such as id, and some behaviour.

connection -- A connection used when sending this element to a server
!

JabberElement subclass: #JabberMessage
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Jabber'!

!JabberMessage commentStamp: 'NES 2/17/2003 16:36' prior: 0!
The xml element named message, as defined in jabber protocol.

See testSimpleMessage and testAdvancedMessage for examples.!

JabberElement subclass: #JabberPresence
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Jabber'!

!JabberPresence commentStamp: 'NES 2/17/2003 16:37' prior: 0!
The xml element named presence, as defined in jabber protocol.

See testPresence in JabberTests for examples.!

JabberElement class
	instanceVariableNames: 'lastId '!
JabberMessage class
	instanceVariableNames: 'lastId '!

!AuthenticationException methodsFor: 'accessing' stamp: 'NES 2/10/2003 01:00'!
query
	"Answer the value of query"

	^ query! !

!AuthenticationException methodsFor: 'accessing' stamp: 'NES 2/10/2003 01:00'!
query: anObject
	"Set the value of query"

	query _ anObject! !


!AuthenticationException class methodsFor: 'as yet unclassified' stamp: 'NES 2/10/2003 01:18'!
signalWithQuery: aQuery
^ (self new query: aQuery) signal: 'Jabber authentication failed'
! !


!Collection methodsFor: 'converting' stamp: 'NES 2/9/2003 14:57'!
asDictionary
	"Answer a dictionary whose entries are the elements of the receiver."
	^ Dictionary withAll: self! !


!JabberConnection methodsFor: 'testing' stamp: 'NES 2/10/2003 15:25'!
isAuthenticated
^ usrName notNil! !

!JabberConnection methodsFor: 'testing' stamp: 'NES 2/9/2003 14:07'!
isConnected
	^ socket notNil
		and: [socket isConnected] and: [readProc notNil]! !

!JabberConnection methodsFor: 'testing' stamp: 'NES 2/8/2003 19:00'!
isUnconnected
	^ self isConnected not! !

!JabberConnection methodsFor: 'accessing' stamp: 'NES 2/9/2003 13:41'!
domainString
 ^ domainString! !

!JabberConnection methodsFor: 'accessing' stamp: 'NES 2/9/2003 13:41'!
domainString: aString
domainString _ aString! !

!JabberConnection methodsFor: 'accessing' stamp: 'NES 2/9/2003 15:25'!
send: aString
 "XXX blocks"
socket sendData: aString! !

!JabberConnection methodsFor: 'connection open/close' stamp: 'NES 2/10/2003 22:18'!
connectTo: aString port: anInteger 
	| address |
	self disconnect.
	domainString _ aString.
	Socket
		initializeNetworkIfFail: [^ self error: 'Jabber: Network init failed'].
	address _ NetNameResolver addressForName: aString timeout: 10.
	address
		ifNil: [^ self error: 'Jabber: cannot find server'].
	socket _ Socket new.
	socket connectTo: address port: anInteger;
		 waitForConnectionUntil: Time millisecondClockValue + 4000.
	socket isConnected
		ifFalse: [^ self error: 'Jabber: not connected'].
	self openConnection.
	self initializeThreading!
]style[(11 7 7 9 4 8 4 4 14 12 3 7 3 6 31 4 8 29 4 7 3 15 17 7 10 2 3 7 13 4 8 28 4 6 3 6 7 6 12 7 7 9 29 4 32 6 27 4 8 23 4 4 18 4 20)f1b,f1cblue;b,f1b,f1cblue;b,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1c202202126,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cblue;i,f1,f1c202202126,f1,f1cblue;i,f1,f1cmagenta;,f1,f1c202202126,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1c202202126,f1,f1cmagenta;,f1,f1cmagenta;,f1! !

!JabberConnection methodsFor: 'connection open/close' stamp: 'NES 2/10/2003 22:14'!
disconnect
	"verify that the connection is unconnected"
	readProc
		ifNotNil: [readProc terminate.
			readProc _ nil].
	socket
		ifNotNil: [socket closeAndDestroy.
			socket _ nil].
	usrName _ nil! !

!JabberConnection methodsFor: 'threading' stamp: 'NES 2/10/2003 22:04'!
initializeThreading
	| ws |
	readProc _ [[(Delay forMilliseconds: 100) wait.
			ws _ WriteStream
						on: (String new: 4000).
			[socket dataAvailable]
				whileTrue: [ws nextPutAll: socket getData asString].
			ws size > 0
				ifTrue: [self processIncoming: ws contents]] repeat]
				forkAt: Processor userInterruptPriority - 10! !

!JabberConnection methodsFor: 'initialization' stamp: 'NES 2/10/2003 22:04'!
initialize
	"preconfigure the iq channel so that checking for the last logon never  
	fails. initialize the inst variables."
	channels _ {#iq -> {(XMLDOMParser parseDocumentFrom: '<iq type="result" id="authenticate"/>' readStream) elements first} asOrderedCollection} asDictionary.! !

!JabberConnection methodsFor: 'private' stamp: 'NES 2/10/2003 22:10'!
update: aspect 
 "Notify all waiters on the /current/ semaphore. note that semaphore will store the signal when there was nobody listening and send it when you wait on it later"
	semaphore signal! !

!JabberConnection methodsFor: 'private' stamp: 'NES 2/9/2003 15:25'!
verifyProtocol: aDictionary 
	"This method takes the attributes of the stream:stream element from the  
	jabber server and verifies that namespace is just right"
	self assert: (aDictionary at: 'xmlns')
			= 'jabber:client';
		 assert: (aDictionary at: 'xmlns:stream')
			= 'http://etherx.jabber.org/streams'!
]style[(16 11 3 131 2 4 10 11 5 7 7 15 14 11 5 14 7 34)f1b,f1cblue;b,f1,f1c152050000,f1,f1cmagenta;,f1,f1cblue;i,f1,f1c202202126,f1,f1c202202126,f1,f1cblue;i,f1,f1c202202126,f1,f1c202202126! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/10/2003 22:11'!
authenticateName: name password: pwd resource: rsc 
 "authenticate the user and wait for the result. throw exception if not authenticated"
	| el |
	self send: '<iq type="set" id="authenticate">
<query xmlns="jabber:iq:auth">
<username>' , name asXml , '</username>
<password>' , pwd asXml , '</password>
<resource>' , rsc asXml , '</resource>
</query>
</iq>'.
	semaphore _ Semaphore new.
	semaphore waitTimeoutSeconds: 2.
	el _ (channels at: #iq) last.
	(el attributes at: #type)
			= #error
		ifTrue: [AuthenticationException
				signalWithQuery: (el firstTagNamed: #query)].
	usrName _ name! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/10/2003 22:03'!
channel: aSymbol add: anElement 
	channels
		at: aSymbol
		ifAbsent: [channels at: aSymbol put: OrderedCollection new].
	(channels at: aSymbol)
		add: anElement.
	self changed: anElement.! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 17:48'!
iqChannel
	^ channels at: #iq! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 17:27'!
messageChannel 
	^ channels at: #message! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/10/2003 15:31'!
newMessageTo: jidString
^ JabberMessage forConnection: self from: (self userJid) to: jidString! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 17:54'!
newMessageTo: jidString body: body 
	^ (self newMessageTo: jidString) body: body! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 18:42'!
newPresence
	^ JabberPresence
		forConnection: self
! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/9/2003 13:38'!
openConnection
"XXX blocks"
	socket sendData: '<stream:stream
	to="' , domainString , '"
	xmlns="jabber:client"
	xmlns:stream="http://etherx.jabber.org/streams">'! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 18:15'!
presenceChannel
	^ channels at: #presence ifAbsent: [nil]!
]style[(15 4 8 5 25)f1b,f1,f1cmagenta;,f1,f1c202202126! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 19:02'!
processAfterTransform: anXmlElement 
"FIXME - messy!!"
	| el |
	el _ anXmlElement.
	el name caseOf: {
		[#stream:stream] -> [self verifyProtocol: el attributes].
		[#iq] -> [self channel: #iq add: el].
		[#message] -> [self
			channel: #message
			add: (el asJabberElementForConn: self)].
		[#presence] -> [self
			channel: #presence
			add: (el asJabberElementForConn: self)].
		[#stream:error] -> [self channel: #stream:error add: el]}
		 otherwise: [self error: el name asString , ' is unknown!!']! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 19:03'!
processIncoming: aString 
	"Check if the stream is closing  and then  process the data further in processAfterTransform.
	If it is closing, disconnect after processing."
	| doc xmlString closing |
	Transcript show: 'incoming: ' , aString;
		 cr.
	closing _ aString endsWith: '</stream:stream>'.
	closing
		ifTrue: [xmlString _ aString first: aString size - '</stream:stream>' size]
		ifFalse: [xmlString _ aString].
	doc _ XMLDOMParser parseDocumentFrom: xmlString readStream.
	doc elements
		do: [:each | self processAfterTransform: each].
	closing
		ifTrue: [self disconnect]! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/8/2003 19:07'!
socket
	^ socket! !

!JabberConnection methodsFor: 'as yet unclassified' stamp: 'NES 2/10/2003 15:39'!
userJid
	^ usrName , '@' , domainString!
]style[(7 4 7 3 3 3 12)f1b,f1,f1cmagenta;,f1,f1c202202126,f1,f1cmagenta;! !


!JabberConnection class methodsFor: 'instance creation' stamp: 'NES 2/8/2003 18:52'!
connect
	^ self connectTo: 'amessage.de' port: 5222! !

!JabberConnection class methodsFor: 'instance creation' stamp: 'NES 2/10/2003 00:19'!
connectTo: aString port: anInteger 
	^ self new initialize connectTo: aString port: anInteger! !


!JabberTests methodsFor: 'Private' stamp: 'NES 2/10/2003 15:38'!
logOn
c
				authenticateName: 'nes'
				password: 'nes'
				resource: 'nes'! !

!JabberTests methodsFor: 'Running' stamp: 'NES 2/16/2003 17:46'!
setUp
	c _ JabberConnection connect.
	! !

!JabberTests methodsFor: 'Running' stamp: 'NES 2/16/2003 17:46'!
tearDown
	c disconnect.
	! !

!JabberTests methodsFor: 'Testing' stamp: 'NES 2/17/2003 18:06'!
testAdvancedMsg
	"test normal accessing to messages"
	| msg recMsg |
	self logOn.
	msg _ c newMessageTo: 'nes at amessage.de/nes'.
	self assert: msg id notNil.
	msg type: #normal;
		 body: 'Message Testing';
		 subject: 'test';
		 thread: 'testing thread'.
	msg send.
	(Delay forMilliseconds: 1000) wait.
	recMsg _ c messageChannel last.
	"alright, test validity"
	self assert: recMsg notNil.
	self assert: recMsg type = #normal;
		 assert: recMsg body = 'Message Testing';
		 assert: recMsg subject = 'test';
		 assert: recMsg thread = 'testing thread'.
	"it's ok to set values twice, and to reuse messages:"
	recMsg body: 'Replaced it'.
	self assert: recMsg body = 'Replaced it'.
     "Deletion like this:"
     recMsg body: nil.
     self assert: (recMsg body = nil).
	"Lo and behold, replying messages is as simple as:"
	recMsg reply send.
	"there's a shortcut for message creation:"
	self assert: (c newMessageTo: 'nes at amessage.de/nes' body: 'Message Testing') body = 'Message Testing'!
]style[(15 2 35 3 11 4 4 9 3 3 1 15 21 3 4 9 3 13 3 7 7 11 17 14 6 13 16 3 3 9 5 18 4 9 6 3 1 23 24 2 4 9 6 10 4 9 6 8 7 13 6 8 17 13 6 11 6 13 6 10 16 3 53 2 6 7 13 3 4 9 6 8 13 92 51 2 6 14 42 2 4 10 1 15 21 7 17 26)f1b,f1,f1c152050000,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cmagenta;,f1,f1c202202126,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cblue;i,f1,f1c202202126,f1,f1c202202126,f1,f1c202202126,f1,f1c202202126,f1,f1cblue;i,f1,f1cmagenta;,f1,f1c202202126,f1,f1cblue;i,f1,f1cmagenta;,f1,f1c152050000,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cblue;i,f1,f1c202202126,f1,f1cblue;i,f1,f1c202202126,f1,f1cblue;i,f1,f1c202202126,f1,f1cblue;i,f1,f1c202202126,f1,f1c152050000,f1,f1cblue;i,f1,f1c202202126,f1,f1cmagenta;,f1,f1cblue;i,f1,f1c202202126,f1,f1c152050000,f1,f1cblue;i,f1,f1c152050000,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1c202202126,f1,f1c202202126,f1! !

!JabberTests methodsFor: 'Testing' stamp: 'NES 2/17/2003 19:04'!
testAdvancedPresence
	"test complete presence thingy without errors"
	| p |
	self logOn.
	p _ c newPresence.
	p to: 'nes at amessage.de/nes';
		 from: 'nes at amessage.de/nes';
		 type: #subscribed;
		 show: #away;
		 status: 'Bin wieder daaaa!!!!!!';
		 priority: 3.
	p send.
	(Delay forMilliseconds: 1500) wait.
	self assert: c presenceChannel last = p!
]style[(20 2 46 3 2 4 4 9 1 3 1 15 1 5 21 11 21 11 11 11 5 13 21 15 1 3 1 9 5 18 4 9 4 9 1 24 1)f1b,f1,f1c152050000,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cblue;i,f1,f1c202202126,f1,f1c202202126,f1,f1c202202126,f1,f1c202202126,f1,f1c202202126,f1,f1c202202126,f1,f1cblue;i,f1,f1cmagenta;,f1,f1c202202126,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1cblue;i! !

!JabberTests methodsFor: 'Testing' stamp: 'NES 2/16/2003 17:47'!
testAuth
	self
		shouldnt: [c
				authenticateName: 'nes'
				password: 'nes'
				resource: 'nes']
		raise: AuthenticationException.
	(Delay forMilliseconds: 1000) wait.
	self assert: (c iqChannel last attributes at: #type)
			= #result.
	self assert: c isAuthenticated! !

!JabberTests methodsFor: 'Testing' stamp: 'NES 2/10/2003 15:27'!
testAuthFail
	self
		should: [c
				authenticateName: 'nes'
				password: 'asdf'
				resource: 'nes']
		raise: AuthenticationException
! !

!JabberTests methodsFor: 'Testing' stamp: 'NES 2/8/2003 19:52'!
testConnection
	
	self assert: c isConnected.
	c disconnect.
	self assert: c isUnconnected! !

!JabberTests methodsFor: 'Testing' stamp: 'NES 2/17/2003 18:16'!
testPresence
	"test presence setting and receiving"
	"Never forget authenticating!!"
	| p |
	self logOn.
	c newPresence send.
	(c newPresence to: 'nes at amessage.de/nes') type: #subscribe;
		 send.
	(Delay forMilliseconds: 400) wait.
	(c newPresence to: 'nes at amessage.de/nes') type: #subscribed;
		 send.
	p _ c newPresence.
	p to: 'nes at amessage.de/nes';
		 show: #chat;
		 send.
(     Delay forMilliseconds: 1000) wait.
	self assert: c presenceChannel last name = #presence! !

!JabberTests methodsFor: 'Testing' stamp: 'NES 2/17/2003 15:40'!
testSimpleMsg
	| msg |
	self logOn.
	msg _ c newMessageTo: 'nes at amessage.de/nes'.
	msg send.
	(Delay forMilliseconds: 1000) wait.
	self
		shouldnt: [c messageChannel last]
		raise: Error!
]style[(13 3 4 4 4 9 3 3 1 15 21 3 3 9 5 18 4 9 4 14 1 31 5)f1b,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cmagenta;,f1,f1c202202126,f1,f1cblue;i,f1,f1cmagenta;,f1,f1c202202126,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1cmagenta;! !


!SequenceableCollection methodsFor: 'accessing' stamp: 'NES 2/9/2003 14:36'!
at: anIndex putAll: aCollection 
     "insert the collection at the given index, overwriting the existing values"
	self
		replaceFrom: anIndex
		to: anIndex + aCollection size - 1
		with: aCollection
		startingAt: 1! !


!String methodsFor: 'converting' stamp: 'NES 2/9/2003 14:37'!
asXml
  	"Do the basic character conversion for XML"
	| top each outIndex buffer input |
	self isEmpty
		ifTrue: [^ self].
	top _ self size.
	input _ ByteArray new: top.
     buffer _ ByteArray new: top * 6.
	input
		replaceFrom: 1
		to: top
		with: self
		startingAt: 1.
	outIndex _ 1.
	1
		to: top
		do: [:index | (each _ input at: index) > 62
				ifTrue: ["$>"
					buffer at: outIndex put: each.
					outIndex _ outIndex + 1]
				ifFalse: [each < 34
						ifTrue: ["$"
							""
							buffer at: outIndex put: each.
							outIndex _ outIndex + 1]
						ifFalse: [each < 40
								ifTrue: [each == 34
										ifTrue: ["$"
											""
											buffer at: outIndex putAll: '&quot;'.
											outIndex _ outIndex + 6]
										ifFalse: [each == 38
												ifTrue: ["$&"
													buffer at: outIndex putAll: '&amp;'.
													outIndex _ outIndex + 5]
												ifFalse: [each == 39
														ifTrue: ["$'"
															buffer at: outIndex putAll: '&apos;'.
															outIndex _ outIndex + 6]
														ifFalse: [buffer at: outIndex put: each.
															outIndex _ outIndex + 1]]]]
								ifFalse: [each > 59
										ifTrue: [each == 60
												ifTrue: ["$<"
													buffer at: outIndex putAll: '&lt;'.
													outIndex _ outIndex + 4]
												ifFalse: [each == 62
														ifTrue: ["$>"
															buffer at: outIndex putAll: '&gt;'.
															outIndex _ outIndex + 4]
														ifFalse: [buffer at: outIndex put: each.
															outIndex _ outIndex + 1]]]
										ifFalse: [buffer at: outIndex put: each.
											outIndex _ outIndex + 1]]]]].
	^ (String new: outIndex - 1)
		replaceFrom: 1
		to: outIndex - 1
		with: buffer
		startingAt: 1! !


!XMLNodeWithElements methodsFor: 'accessing' stamp: 'NES 2/17/2003 16:11'!
addElement: element 
 "Add the element, answer the element"
	^ self elements add: element! !

!XMLNodeWithElements methodsFor: 'accessing' stamp: 'NES 2/17/2003 16:59'!
elementAt: entityName ifAbsent: aBlock 
	elements
		ifNil: [^ aBlock value].
	^ self elements
		detect: [:each | each name = entityName]
		ifNone: [^ aBlock value]!
]style[(11 10 11 6 3 8 13 6 12 4 21 6 2 4 8 10 15 6 7)f1b,f1cblue;b,f1b,f1cblue;b,f1,f1cmagenta;,f1,f1cblue;i,f1,f1cmagenta;,f1,f1cred;,f1,f1cblue;i,f1,f1cblue;i,f1,f1cblue;i,f1! !

!XMLNodeWithElements methodsFor: 'accessing' stamp: 'NES 2/10/2003 15:54'!
elements: anOrderedCollection
elements _ anOrderedCollection! !


!XMLElement methodsFor: 'accessing' stamp: 'NES 2/10/2003 16:41'!
addContent: contentString 
    |stringNode|
    stringNode _ (contentString class = XMLStringNode) ifTrue: [contentString] ifFalse: [XMLStringNode string: contentString].
	self contents add: stringNode! !

!XMLElement methodsFor: 'accessing' stamp: 'NES 2/17/2003 18:03'!
asJabberElementForConn: aJabberConnection
	^ self name caseOf: {
		[#presence] -> [JabberPresence forConnection: aJabberConnection from: self].
		[#message] -> [JabberMessage forConnection: aJabberConnection from: self]}
		 otherwise: [self error: 'unconvertable!!']! !

!XMLElement methodsFor: 'accessing' stamp: 'NES 2/17/2003 17:23'!
contentString: contentString 
	| |
	contents _ OrderedCollection new.
     self addContent: contentString! !

!XMLElement methodsFor: 'accessing' stamp: 'NES 2/10/2003 16:29'!
ensureNoTagNamed: aSymbol 
	self elements
		remove: (self firstTagNamed: aSymbol)
		ifAbsent: []!
]style[(18 7 8 8 12 4 16 7 16)f1b,f1cblue;b,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1cblue;i,f1! !

!XMLElement methodsFor: 'comparing' stamp: 'NES 2/17/2003 18:44'!
= anObject 
	^ anObject class = self class
		and: [self asString = anObject asString]!
]style[(2 8 5 8 9 4 49)f1b,f1cblue;b,f1,f1cblue;i,f1,f1cmagenta;,f1! !


!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:45'!
attrValue: attrName
 ^ attributes at: attrName! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 18:37'!
connection
	"Answer the value of connection"
	^ connection! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 18:37'!
connection: anObject 
	"Set the value of connection"
	connection _ anObject! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:44'!
fetchElementContent: elName 
	"Fetch the content string of the first element called elName, nil if no such element"
	| t |
	t _ self firstTagNamed: elName.
	^ t
		ifNotNil: [t contentString]! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:45'!
from
^ self attrValue: #from! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:45'!
from: aString 
self	setAttribute: #from to: aString! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 18:35'!
id
	^ attributes at: #id! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 18:35'!
send
	connection send: self asString! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:42'!
setAttribute: attrName to: attrValue
 attributes at: attrName put: attrValue! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 17:38'!
setElement: elementName to: contentString 
	"Adds an element named elementName with no attributes and content  
	contentString. If there is an element, modify it. If contentString is nil,  
	remove the element."
	contentString
		ifNil: [elements
				remove: (self
						elementAt: elementName
						ifAbsent: ["nothing to be done"
							^ self])
			] ifNotNil: [
	(self
		elementAt: elementName
		ifAbsent: [(self
				addElement: (XMLElement named: elementName))
				addContent: contentString.
			^ self])
		contentString: contentString]! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:46'!
to
^ self attrValue: #to! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:46'!
to: aString 
self setAttribute: #to to: aString! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:47'!
type
	^ self attrValue: #type! !

!JabberElement methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:47'!
type: aString
 self setAttribute: #type to: aString! !


!JabberMessage methodsFor: 'accessing' stamp: 'NES 2/17/2003 16:48'!
body
	^ self fetchElementContent: #body! !

!JabberMessage methodsFor: 'accessing' stamp: 'NES 2/17/2003 16:48'!
body: aString 
	self setElement: #body to: aString! !

!JabberMessage methodsFor: 'accessing' stamp: 'NES 2/17/2003 16:48'!
subject
^ self fetchElementContent: #subject! !

!JabberMessage methodsFor: 'accessing' stamp: 'NES 2/17/2003 16:48'!
subject: aString 
self 	setElement: #subject to: aString! !

!JabberMessage methodsFor: 'accessing' stamp: 'NES 2/17/2003 16:49'!
thread
^	self fetchElementContent: #thread! !

!JabberMessage methodsFor: 'accessing' stamp: 'NES 2/17/2003 16:49'!
thread: aString 
	self setElement: #thread to: aString! !

!JabberMessage methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 17:55'!
reply
 "return a new message, replying this one"
	^ (connection newMessageTo: self from) thread: self thread;
		 yourself! !


!JabberPresence methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:51'!
priority
	"Return the priority as integer"
^( (self fetchElementContent: #priority )	ifNil: [^nil]) asInteger! !

!JabberPresence methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:50'!
priority: aStringOrInteger 
	self setElement: #priority to: aStringOrInteger asString! !

!JabberPresence methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:52'!
show
self fetchElementContent: #show! !

!JabberPresence methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:52'!
show: aString 
self setElement: #show to: aString! !

!JabberPresence methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:52'!
status
self fetchElementContent: #status! !

!JabberPresence methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 16:52'!
status: aString 
self setElement: #status to: aString! !

!JabberPresence methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 15:50'!
type
" see type: "
^ super type! !

!JabberPresence methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 15:51'!
type: aString 
	"Should be one of the following:  
	- unavailable - Signals that the entity is no longer available for  
	communication. 
	- subscribe - The sender wishes to subscribe to the  
	recipient's presence.  
	- subscribed - The sender has allowed the recipient to receive their  
	presence. 
	- unsubscribe - A notification that an entity is unsubscribing  
	from another entity's presence.  
	- unsubscribed - The subscription request has been denied or a  
	previously-granted subscription has been cancelled.  
	- probe - A request for an entity's current presence.  
	- error - An error has occurred regarding processing or delivery of a  
	previously-sent presence chunk."
	^ super type: aString! !


!XMLElement class methodsFor: 'instance creation' stamp: 'NES 2/10/2003 16:35'!
named: aString 
	^ self named: aString attributes: Dictionary new! !


!JabberElement class methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 15:25'!
forConnection: aJabberConnection 
	^ (self
		named: self tag
		attributes: (Dictionary with: #id -> self nextId))
		connection: aJabberConnection!
]style[(15 17 6 4 10 4 20 10 7 3 4 4 24 17)f1b,f1cblue;b,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1cmagenta;,f1,f1c202202126,f1,f1cmagenta;,f1,f1cblue;i! !

!JabberElement class methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 18:02'!
forConnection: aJabberConnection from: anXMLElement 
	self assert: anXMLElement name = self tag.
	^ (self named: self tag attributes: anXMLElement attributes)
		elements: anXMLElement elements ; connection: aJabberConnection ; yourself! !

!JabberElement class methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 18:34'!
forConnection: aJabberConnection from: fromString to: toString 
	^ ((self forConnection: aJabberConnection)
		from: fromString)
		to: toString! !

!JabberElement class methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 18:34'!
initialize
	lastId _ 0! !

!JabberElement class methodsFor: 'as yet unclassified' stamp: 'NES 2/16/2003 18:35'!
nextId
	"return a unique messageId as string"
	^ (lastId _ lastId + 1) asString! !

!JabberElement class methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 15:30'!
tag
 "the xml element this class feels responsible for"
	self subclassResponsibility! !


!JabberMessage class methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 15:27'!
tag ^ #message! !


!JabberPresence class methodsFor: 'as yet unclassified' stamp: 'NES 2/17/2003 15:30'!
tag ^ #presence! !

JabberMessage class removeSelector: #forConnection:!
JabberMessage class removeSelector: #forConnection:from:to:!
JabberMessage class removeSelector: #from:!
JabberMessage class removeSelector: #initialize!
JabberMessage class removeSelector: #nextId!
JabberElement class removeSelector: #from:!
JabberElement initialize!
JabberPresence removeSelector: #id!
JabberMessage removeSelector: #connection!
JabberMessage removeSelector: #connection:!
JabberMessage removeSelector: #from!
JabberMessage removeSelector: #from:!
JabberMessage removeSelector: #id!
JabberMessage removeSelector: #send!
JabberMessage removeSelector: #to!
JabberMessage removeSelector: #to:!
JabberMessage removeSelector: #type!
JabberMessage removeSelector: #type:!
JabberElement removeSelector: #forConnection:!
JabberElement removeSelector: #forConnection:from:to:!
JabberElement removeSelector: #subject!
JabberElement removeSelector: #subject:!
XMLElement removeSelector: #asJabberElement!
XMLElement removeSelector: #asJabberMessage!
XMLNode removeSelector: #asString!
JabberTests removeSelector: #testRegistration!
JabberTests removeSelector: #testSimplePresence!
JabberTests removeSelector: #update:!
JabberConnection class removeSelector: #on:!
JabberConnection removeSelector: #checkIfClosing:!
JabberConnection removeSelector: #checkIfClosingAndRepair:!
JabberConnection removeSelector: #initializeThreads!
JabberConnection removeSelector: #isUnConnected!
JabberConnection removeSelector: #processIq:!
JabberConnection removeSelector: #semaphore!
JabberConnection removeSelector: #socket:!

!JabberConnection reorganize!
('testing' isAuthenticated isConnected isUnconnected)
('accessing' domainString domainString: send:)
('connection open/close' connectTo:port: disconnect)
('threading' initializeThreading)
('initialization' initialize)
('private' update: verifyProtocol:)
('as yet unclassified' authenticateName:password:resource: channel:add: iqChannel messageChannel newMessageTo: newMessageTo:body: newPresence openConnection presenceChannel processAfterTransform: processIncoming: socket userJid)
!



More information about the Squeak-dev mailing list