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

452 lines
13 KiB
Smalltalk

"
(C) 2011-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/>.
"
"
The next attempt to generalize the message pattern. We will just describe
messages that have a type, mandatory and optional parameters. The parameters
will be simple ids. There should be code to generate nice parsing routines
"
Object subclass: TLVDescriptionContainer [
| type fields |
<category: 'OsmoNetwork-MSG'>
<comment: 'Attempt to have a DSL for messages'>
TLVDescriptionContainer class >> initWith: aType [
<category: 'creation'>
^ self new
instVarNamed: #type put: aType; yourself
]
TLVDescriptionContainer class >> findTLVDescription: aType [
<category: 'creation'>
self allSubclassesDo: [:each | | struct |
struct := each tlvDescription.
struct type = aType ifTrue: [
^ struct
]
].
^ self error: ('Can not find TLV Description for type: <1p>' expandMacrosWith: aType).
]
TLVDescriptionContainer class >> decodeByteStream: aStream type: aType [
| description |
<category: 'parsing'>
"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."
description := self findTLVDescription: aType.
^ description decodeByteStream: aStream.
]
TLVDescriptionContainer class >> encodeCollection: aCollection type: aType [
| description |
<category: 'encoding'>
"This is a generic encoding method that will put the collection
onto a MessageBuffer class."
description := self findTLVDescription: aType.
^ description encodeCollection: aCollection.
]
type: aType [
<category: 'private'>
type := aType.
]
type [
<category: 'accessing'>
^ type
]
addFixed: aType [
<category: 'fields'>
self fields add: {#fixed. aType}
]
addOptional: aType [
<category: 'fields'>
self fields add: {#optional. aType}
]
addOptionals: aType [
<category: 'fields'>
"Optional Parameters that may appear more than once."
self fields add: {#optionals. aType}
]
addVariable: aType [
<category: 'fields'>
self fields add: {#variable. aType}
]
fields [
<category: 'fields'>
^ fields ifNil: [fields := OrderedCollection new]
]
fieldsDo: aBlock [
<category: 'fields'>
^ self fields do: [:each | aBlock value: each first value: each second]
]
filter: aFilter [
| lst |
<category: 'fields'>
lst := OrderedCollection new.
self fields inject: lst into: [:list :each |
each first = aFilter ifTrue: [
list add: each second.
].
list].
^ lst
]
filterdDo: aBlock filter: aFilter [
<category: 'private'>
^ self fields do: [:each |
each first = aFilter ifTrue: [
aBlock value: each first value: each second]].
]
fixed [
<category: 'private'>
^ self filter: #fixed
]
fixedDo: aBlock [
<category: 'private'>
^ self filterdDo: aBlock filter: #fixed.
]
variable [
<category: 'private'>
^ self filter: #variable
]
variableDo: aBlock [
<category: 'private'>
^ self filterdDo: aBlock 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 [
<category: 'decoding'>
"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 state: aState [
<category: 'encoding'>
(clazz isCompatible: field) ifFalse: [
^ self error:
('Mandatory information must be <1p> but was <2p>.'
expandMacrosWith: clazz with: field).
].
msg nextPutAll: field data.
]
writeVariable: msg with: clazz from: field state: aState [
<category: 'encoding'>
(clazz isCompatible: field) ifFalse: [
^ self error:
('Variable information must be <1p> but was <2p>.'
expandMacrosWith: clazz with: field).
].
"TODO: Respect the lengthLength here"
field class lengthLength > 0 ifTrue: [
msg nextPut: field data size.
msg nextPutAll: field data.
]
]
writeOptional: msg with: clazz from: field state: aState [
<category: 'encoding'>
(clazz isCompatible: field) ifFalse: [
^ self error:
('Optional information must be <1p> but was <2p>.'
expandMacrosWith: clazz with: field).
].
"TODO: Respect the lengthLength here"
msg nextPut: field class parameterValue.
field class lengthLength > 0 ifTrue: [
msg nextPut: field data size.
msg nextPutAll: field data.
]
]
createState [
<category: 'encoding'>
"Subclasses can create their own state to allow jumping in the
stream or leave markers"
^ nil
]
writeFixedEnd: aStream state: aState [
<category: 'encoding'>
"Subclasses can use me to do something at the end of fixed messages."
]
writeVariableEnd: aStream state: aState [
<category: 'encoding'>
]
encodeCollection: aCollection [
| stream msg aState |
<category: 'encoding'>
msg := WriteStream on: (ByteArray new: 3).
stream := aCollection readStream.
aState := self createState.
"Try to match the fields of the TLV description with the fields of
the collection. We keep some local state to check if we are
passed the fixed and variable fields."
"Write the fixed portion"
self fixedDo: [:type :clazz |
self writeFixed: msg with: clazz from: stream next state: aState.
].
self writeFixedEnd: msg state: aState.
"Write the variable portion"
self variableDo: [:type :clazz |
self writeVariable: msg with: clazz from: stream next state: aState.
].
self writeVariableEnd: msg state: aState.
self fieldsDo: [:type :clazz |
"Check if we are compatible"
(clazz isCompatible: stream peek) ifTrue: [
type = #optional ifTrue: [
self writeOptional: msg with: clazz from: stream next state: aState.
].
type = #optionals ifTrue: [
self notYetImplemented
]
].
].
^ msg contents
]
]
Object subclass: MSGField [
| data |
<category: 'OsmoNetwork-MSG'>
<comment: 'The description of an Information Element'>
MSGField class >> isCompatible: aField [
<category: 'parsing'>
^ aField isKindOf: self.
]
MSGField class >> readVariableFrom: aStream length: aLength [
<category: 'parsing'>
"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. <1p> < <2p>'
expandMacrosWith: aLength with: self octalLength).
].
self maxLength ifNotNil: [
aLength > self maxLength ifTrue: [
^ self error:
('The data is too long <1p> > <2p>.'
expandMacrosWith: aLength with: 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 [
<category: 'kind'>
"If this field is variable in length"
^ self subclassResponsibility
]
MSGField class >> isFixed [
<category: 'kind'>
"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 [
<category: 'OsmoNetwork-MSG'>
<comment: 'I represent a fixed length field.'>
MSGFixedField class >> isVarible [ <category: 'kind'> ^ false ]
MSGFixedField class >> isFixed [ <category: 'kind'> ^ true ]
MSGFixedField class >> readFixedFrom: aStream [
<category: 'parsing'>
^ self new
data: (aStream next: self octalLength);
yourself
]
MSGFixedField class >> readVariableFrom: aStream length: aLength [
<category: 'parsing'>
aLength = self octalLength ifFalse: [
^ self error: 'The size needs to be exact'.
].
^ super readVariableFrom: aStream length: aLength
]
]
MSGField subclass: MSGVariableField [
<category: 'OsmoNetwork-MSG'>
<comment: 'I represent a variable sized field.'>
MSGVariableField class >> isVarible [ <category: 'kind'> ^ true ]
MSGVariableField class >> isFixed [ <category: 'kind'> ^ false ]
]