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/MessageStructure.st

365 lines
9.7 KiB
Smalltalk

"
(C) 2011 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 extend [
subclassResponsibility [
thisContext backtrace printNl.
SystemExceptions.SubclassResponsibility signal
]
]
"
The next attempt to generalize the message pattern. We will just describe
messages that have a type, mandantory and optional parameters. The parameters
will be simple ids. There should be code to generate nice parsing routines
"
Object subclass: MSGStructure [
| type fields |
<comment: 'Attempt to have a DSL for messages'>
MSGStructure class >> initWith: aType [
^ self new
instVarNamed: #type put: aType; yourself
]
MSGStructure class >> findStructure: aType [
self allSubclassesDo: [:each | | struct |
struct := each structure.
struct type = aType ifTrue: [
^ struct
]
].
^ self error: 'Can not find structure for type: %1' % {aType.}
]
MSGStructure class >> decodeByteStream: aStream type: aType [
| structure |
"This is a generic decoding method that works by finding the
message structure and then following the structure and will
return an OrderedCollection with tuples."
structure := self findStructure: aType.
^ structure decodeByteStream: aStream.
]
MSGStructure class >> encodeCollection: aCollection type: aType [
| structure |
"This is a generic encoding method that will put the collection
onto a MessageBuffer class."
structure := self findStructure: aType.
^ structure encodeCollection: aCollection.
]
type: aType [
<category: 'private'>
type := aType.
]
type [
<category: 'The type of this message'>
^ type
]
addFixed: aType [
self fields add: {#fixed. aType}
]
addOptional: aType [
self fields add: {#optional. aType}
]
addOptionals: aType [
"Optional Parameters that may appear more than once."
self fields add: {#optionals. aType}
]
addVariable: aType [
self fields add: {#variable. aType}
]
fields [
<category: 'private'>
^ fields ifNil: [fields := OrderedCollection new]
]
fieldsDo: aBlock [
^ self fields do: [:each | aBlock value: each first value: each second]
]
filter: aFilter [
| lst |
lst := OrderedCollection new.
self fields inject: lst into: [:list :each |
each first = aFilter ifTrue: [
list add: each second.
].
list].
^ lst
]
fixed [
<category: 'private'>
^ self filter: #fixed
]
variable [
<category: 'private'>
^ self filter: #variable
]
optional [
<category: 'private'>
^ self filter: #optional
]
optionals [
<category: 'private'>
^ self filter: #optionals
]
parseFixed: aStream with: aClass into: decoded [
<category: 'decoding'>
decoded add: (aClass readFixedFrom: aStream).
^ true
]
parseField: aStream with: aClass into: decoded [
| len |
<category: 'private'>
"Is this an empty tag"
aClass lengthLength = 0 ifTrue: [
decoded add: (aClass readVariableFrom: aStream length: 0).
^ true
].
len := (aStream next: aClass lengthLength) byteAt: 1.
decoded add: (aClass readVariableFrom: aStream length: len).
^ true
]
parseVariable: aStream with: aClass into: decoded [
<category: 'decoding'>
^ self parseField: aStream with: aClass into: decoded.
]
parseOptional: aStream with: aClass into: decoded [
| tag len |
<category: 'decoding'>
tag := aStream peek.
tag = aClass parameterValue ifFalse: [^ false].
aStream skip: 1.
self parseField: aStream with: aClass into: decoded.
^ true
]
parseOptionals: aStream with: aClass into: decoded [
<category: 'decoding'>
[
self parseOptional: aStream with: aClass into: decoded.
] whileTrue: [].
]
prepareOptional: aStream [
"Nothing to be done here. Subclasses can manipulate the stream"
]
decodeByteStream: aStream [
| decoded first_optional |
<category: 'decoding'>
decoded := OrderedCollection new.
first_optional := true.
self fieldsDo: [:type :clazz |
type = #fixed ifTrue: [
self parseFixed: aStream with: clazz into: decoded.
].
type = #variable ifTrue: [
self parseVariable: aStream with: clazz into: decoded.
].
type = #optional ifTrue: [
first_optional ifTrue: [first_optional := false. self prepareOptional: aStream].
self parseOptional: aStream with: clazz into: decoded.
].
type = #optionals ifTrue: [
first_optional ifTrue: [first_optional := false. self prepareOptional: aStream].
self parseOptionals: aStream with: clazz into: decoded.
].
].
"TODO: complain about unfetched bytes?"
^ decoded
]
writeFixed: msg with: clazz from: field [
<category: 'encoding'>
(field isKindOf: clazz) ifFalse: [
^ self error: 'Mandantory information must be %1 but was %2.' % {clazz. field.}.
].
msg nextPutAll: field data.
]
writeVariable: msg with: clazz from: field [
<category: 'encoding'>
(field isKindOf: clazz) ifFalse: [
^ self error: 'Variable information must be %1 but was %2.' % {clazz. field.}
].
"TODO: Respect the lengthLength here"
msg nextPut: field data size.
msg nextPutAll: field data.
]
prepareWrite: aStream [
]
encodeCollection: aCollection [
| stream msg fixed_done |
<category: 'encoding'>
msg := WriteStream on: (ByteArray new: 3).
stream := aCollection readStream.
fixed_done := false.
self fieldsDo: [:type :clazz |
type = #fixed ifTrue: [
self writeFixed: msg with: clazz from: stream next.]
ifFalse: [
fixed_done ifFalse: [
fixed_done := true.
self prepareWrite: msg.
].
].
type = #variable ifTrue: [
self writeVariable: msg with: clazz from: stream next.
].
"
type = #optional ifTrue: [
].
type = #optionals ifTrue: [
].
"
].
^ msg contents
]
]
Object subclass: MSGField [
| data |
<category: 'osmo-networking'>
<comment: 'The description of an Information Element'>
MSGField class >> readVariableFrom: aStream length: aLength [
"I verify that I am allowed to read that much and then will read it"
aLength < self octalLength ifTrue: [
^ self error: 'The data is too short. %1 < %2' % {aLength. self octalLength}.
].
self maxLength ifNotNil: [
aLength > self maxLength ifTrue: [
^ self error: 'The data is too long %1 > %2.' % {aLength. self maxLength}.
]
].
^ self new
data: (aStream next: aLength);
yourself
]
MSGField class >> parameterName [
<category: 'accessing'>
^ self subclassResponsibility
]
MSGField class >> parameterValue [
<category: 'accessing'>
^ self subclassResponsibility
]
MSGField class >> lengthLength [
"The length of the length field. The default is to assume a length of
one octet and in the units of octets"
<category: 'accessing'>
^ 1
]
MSGField class >> octalLength [
<category: 'accessing'>
^ self subclassResponsibility
]
MSGField class >> isVarible [
"If this field is variable in length"
^ self subclassResponsibility
]
MSGField class >> isFixed [
"If this field is of a fixed length"
^ self subclassResponsibility
]
MSGField class >> maxLength [
<category: 'accessing'>
^ nil
]
data: aData [
<category: 'accessing'>
data := aData.
]
data [
<category: 'accessing'>
^ data
]
]
MSGField subclass: MSGFixedField [
MSGFixedField class >> isVarible [ ^ false ]
MSGFixedField class >> isFixed [ ^ true ]
MSGFixedField class >> readFixedFrom: aStream [
^ self new
data: (aStream next: self octalLength);
yourself
]
MSGFixedField class >> readVariableFrom: aStream length: aLength [
aLength = self octalLength ifFalse: [
^ self error: 'The size needs to be exact'.
].
^ super readVariableFrom: aStream length: aLength
]
]
MSGField subclass: MSGVariableField [
MSGVariableField class >> isVarible [ ^ true ]
MSGVariableField class >> isFixed [ ^ false ]
]