1
0
Fork 0

isup: Generate properly formatted ISUP messages.

The structure of the code is not as clean as it could and should
be, the abstraction between the generic MessageStructure and ISUPMessage
is not good enough. Some ISUP corner cases are not handled well.
This commit is contained in:
Holger Hans Peter Freyther 2012-02-02 19:16:45 +01:00
parent adc964df90
commit f4a72bab38
4 changed files with 200 additions and 7 deletions

56
ISUP.st
View File

@ -1,5 +1,5 @@
"
(C) 2011 by Holger Hans Peter Freyther
(C) 2011-2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -184,7 +184,31 @@ MSGStructure subclass: ISUPMessage [
<comment: 'I am the base class for the ISUP messages'>
<category: 'OsmoNetwork-ISUP'>
ISUPMessage class >> decodeByteStream: aStream [
<category: 'parsing'>
| col cic type |
cic := (aStream next: 2) shortAt: 1.
type := (aStream next: 1) at: 1.
col := self decodeByteStream: aStream type: type.
^ OrderedCollection with: cic with: type with: col.
]
ISUPMessage class >> encodeCollection: aCollection [
<category: 'encoding'>
| msg type |
msg := Osmo.MessageBuffer new.
type := aCollection at: 2.
msg put16: (aCollection at: 1).
msg putByte: type.
msg putByteArray: (self encodeCollection: (aCollection at: 3) type: type).
^ msg
]
parseVariable: aStream with: aClass into: decoded [
<category: 'parsing'>
| pos ptr res |
pos := aStream position.
ptr := aStream next.
@ -199,11 +223,41 @@ MSGStructure subclass: ISUPMessage [
prepareOptional: aStream [
"We are done with the variable section and now get the pointer
to the optional part and will move the stream there."
<category: 'parsing'>
| pos ptr |
pos := aStream position.
ptr := aStream next.
aStream skip: ptr - 1.
]
writeVariableEnd: aStream state: aState [
<category: 'encoding'>
"Write the optional pointer. TODO: In case of no optional this
should be 0"
aStream nextPut: (aState at: 'data') size + 1.
aStream nextPutAll: (aState at: 'data') contents.
]
writeVariable: msg with: clazz from: field state: aState [
| var_len |
"We will write a pointer and then store the data in the state"
<category: 'encoding'>
"Write the pointer of where the data will be"
var_len := self variable size.
msg nextPut: (aState at: 'data') size + var_len + 1.
"Store the data for later"
super writeVariable: (aState at: 'data') with: clazz from: field state: nil.
]
createState [
"Our parsing state. We need to queue the variable fields until all
of them have been written."
<category: 'encoding'>
^ Dictionary from: {'data' -> (WriteStream on: (ByteArray new: 3))}.
]
]

View File

@ -1,5 +1,5 @@
"
(C) 2011 by Holger Hans Peter Freyther
(C) 2011-2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -49,6 +49,19 @@ TestCase subclass: ISUPGeneratedTest [
].
]
testDecode [
| decode struct data |
decode := #(16r15 16r00 16r01 16r00 16r00 16r00 16r0A 16r00
16r02 16r0B 16r09 16r04 16r10 16r00 16r19 16r79
16r64 16r64 16r64 16r78 16r0A 16r09 16r02 16r13
16r00 16r79 16r51 16r20 16r01 16r79 16r42 16r00) asByteArray.
struct := ISUPMessage decodeByteStream: decode readStream.
data := ISUPMessage encodeCollection: struct.
self assert: data asByteArray = decode.
]
testClassCount [
self assert: ISUPMessage allSubclasses size = 46.
]

View File

@ -48,6 +48,14 @@ Collection subclass: MessageBuffer [
chunks add: aByteArray.
]
put16: aInt [
| data low high |
low := (aInt bitAnd: 16rFF).
high := (aInt bitShift: -8) bitAnd: 16rFF.
data := ByteArray with: low with: high.
chunks add: data.
]
putLen16: aInt [
| data low high |
low := (aInt bitShift: -8) bitAnd: 16rFF.

View File

@ -1,5 +1,5 @@
"
(C) 2011 by Holger Hans Peter Freyther
(C) 2011-2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
@ -16,6 +16,13 @@
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
@ -54,6 +61,15 @@ Object subclass: MSGStructure [
^ 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.
@ -194,12 +210,110 @@ Object subclass: MSGStructure [
].
].
aStream atEnd ifFalse: [
decoded inspect.
^ self error: 'Stream should be at the end. Unconsumed bytes.'.
"TODO: complain about unfetched bytes?"
^ decoded
]
writeFixed: msg with: clazz from: field state: aState [
<category: 'encoding'>
(clazz isCompatible: field) ifFalse: [
^ self error: 'Mandantory information must be %1 but was %2.' % {clazz. field.}.
].
^ decoded
msg nextPutAll: field data.
]
writeVariable: msg with: clazz from: field state: aState [
<category: 'encoding'>
(clazz isCompatible: field) ifFalse: [
^ self error: 'Variable information must be %1 but was %2.' % {clazz. 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 %1 but was %2.' % {clazz. 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 type_state aState |
<category: 'encoding'>
msg := WriteStream on: (ByteArray new: 3).
stream := aCollection readStream.
type_state := #initial.
aState := self createState.
"Try to match the fields of the structure with the fields of
the collection. We keep some local state to check if we are
passed the fixed and variable fields."
self fieldsDo: [:type :clazz |
type = #fixed
ifTrue: [
self writeFixed: msg with: clazz from: stream next state: aState.
] ifFalse: [
type_state = #initial ifTrue: [
type_state := #fixedDone.
self writeFixedEnd: msg state: aState.
].
].
type = #variable
ifTrue: [
self writeVariable: msg with: clazz from: stream next state: aState.
] ifFalse: [
type_state = #fixedDone ifTrue: [
type_state := #variableDone.
self writeVariableEnd: msg state: aState.
].
].
"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
]
]
@ -209,6 +323,10 @@ Object subclass: MSGField [
<category: 'OsmoNetwork-MSG'>
<comment: 'The description of an Information Element'>
MSGField class >> isCompatible: aField [
^ aField isKindOf: self.
]
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: [