1
0
Fork 0

msg: Work on a very generic parsing routine and test it on ISUP

The parsing routine should be able to be used for GSM 04.08,
08.08, ISUP and other parts. It should allow to have variable
sized length and tag fields etc. Right now it is not yet doing
all of what it should do.

E.g. the order of optional entries can be different, the code
assume an order right now.
This commit is contained in:
Holger Hans Peter Freyther 2011-03-23 17:56:47 +01:00
parent 1d0b0c1bb4
commit 6b40cc6866
2 changed files with 170 additions and 5 deletions

22
ISUP.st
View File

@ -181,5 +181,27 @@ Object subclass: ISUPConstants [
MSGStructure subclass: ISUPMessage [
<comment: 'I am the base class for the ISUP messages'>
parseVariable: aStream with: aClass into: decoded [
| pos ptr res |
pos := aStream position.
ptr := aStream next.
aStream skip: ptr - 1.
res := super parseVariable: aStream with: aClass into: decoded.
aStream position: pos + 1.
^ res
]
prepareOptional: aStream [
"We are done with the variable section and now get the pointer
to the optional part and will move the stream there."
| pos ptr |
pos := aStream position.
ptr := aStream next.
aStream skip: ptr - 1.
]
]

View File

@ -31,6 +31,27 @@ Object subclass: MSGStructure [
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.
]
type: aType [
<category: 'private'>
type := aType.
@ -97,12 +118,110 @@ Object subclass: MSGStructure [
<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.
].
].
aStream atEnd ifFalse: [
decoded inspect.
^ self error: 'Stream should be at the end. Unconsumed bytes.'.
].
^ decoded
]
]
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
@ -134,19 +253,43 @@ Object subclass: MSGField [
"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 >> maxLength [
<category: 'accessing'>
^ nil
]
MSGVariableField class >> isVarible [ ^ true ]
MSGVariableField class >> isFixed [ ^ false ]
]