1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-network/ipa/IPAProtoHandler.st

109 lines
2.9 KiB
Smalltalk

"
(C) 2010-2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: IPAProtoHandler [
| token muxer |
<comment: 'I can be registered on an IPADispatcher and will
handle the IPA protocol. You can subclass me to change the
behavior.'>
<category: 'OsmoNetwork-IPA'>
IPAProtoHandler class [
| handlers |
initialize [
<category: 'creation'>
^ self initializeHandlers
]
]
IPAProtoHandler class >> initializeHandlers [
<category: 'private'>
(handlers := Dictionary new)
at: IPAConstants msgPing put: #handlePing:;
at: IPAConstants msgPong put: #handlePong:;
at: IPAConstants msgIdGet put: #handleIdGet:;
at: IPAConstants msgIdAck put: #handleIdAck:.
]
IPAProtoHandler class >> handlers [
^ handlers ifNil: [self initialize. handlers].
]
registerOn: aDispatcher [
<category: 'initialize'>
aDispatcher addHandler: IPAConstants protocolIPA on: self with: #handleMsg:.
]
muxer: aMuxer [
<category: 'initialize'>
muxer := aMuxer.
]
token: aToken [
<category: 'authentication'>
token := aToken.
]
handleMsg: aMsg [
| selector |
<category: 'dispatch'>
selector := self class handlers at: (aMsg first asInteger) ifAbsent: [
self logError: 'IPA message not understood ', aMsg first asInteger asString
area: #ipa.
^ false
].
self perform: selector with: aMsg.
]
handlePing: aMsg [
<category: 'private'>
muxer nextPut: (ByteArray with: IPAConstants msgPong) with: IPAConstants protocolIPA.
]
handlePong: aMsg [
<category: 'private'>
self logDebug: 'PONG' area: #ipa.
]
handleIdGet: aMsg [
| msg |
<category: 'authentication'>
msg := MessageBuffer new.
msg putByte: IPAConstants msgIdResp.
msg putLen16: token size + 1.
msg putByte: IPAConstants idtagUnitName.
msg putByteArray: token asByteArray.
muxer nextPut: msg asByteArray with: IPAConstants protocolIPA.
]
handleIdAck: aMsg [
<category: 'private'>
self logDebug: 'ID ACK' area: #ipa.
]
]
Eval [
IPAProtoHandler initialize.
]