1
0
Fork 0

SCCP: Implement the parsing of the option data.

Parse the PNC data completly in the CR message.
This commit is contained in:
Holger Hans Peter Freyther 2010-11-20 21:46:05 +01:00
parent e45b92dceb
commit dce3c01f9e
1 changed files with 41 additions and 27 deletions

68
SCCP.st
View File

@ -43,7 +43,32 @@ Object subclass: SCCPHelper [
Object subclass: SCCPPNC [
| dict |
SCCPPNC class >> parseFrom: aMsg [
SCCPPNC class >> parseFrom: aPnc [
| dict pnc |
pnc := aPnc.
dict := Dictionary new.
[pnc isEmpty not] whileTrue: [
| type |
type := pnc at: 1.
type = SCCPHelper pncEoO
ifTrue: [
pnc := ByteArray new.
]
ifFalse: [
| size data |
size := pnc at: 2.
data := pnc copyFrom: 3 to: 3 + size - 1.
pnc := pnc copyFrom: 3 + size.
dict at: type put: data.
].
].
^ (self new)
dict: dict;
yourself.
]
at: aKey put: aValue [
@ -59,6 +84,11 @@ Object subclass: SCCPPNC [
^ dict ifNil: [dict := Dictionary new.]
]
dict: aDict [
<category: 'private'>
dict := aDict.
]
writeOn: aMsg [
self dict keysAndValuesDo: [:key :val |
| dat |
@ -173,6 +203,13 @@ SCCPMessage subclass: SCCPConnectionRequest [
^ SCCPHelper msgCr
]
SCCPConnectionRequest class >> initWith: src dest: dest pnc: pnc [
<category: 'construction'>
^ self new
src: src dest: dest pnc: pnc;
yourself
]
SCCPConnectionRequest class >> initWith: src dest: dest data: data [
<category: 'construction'>
| pnc |
@ -185,8 +222,7 @@ SCCPMessage subclass: SCCPConnectionRequest [
]
SCCPConnectionRequest class >> parseFrom: aMsg [
| src addr proto variable optional pnc data |
data := nil.
| src addr proto variable optional pnc |
src := SCCPAddrReference fromByteArray: (aMsg copyFrom: 2 to: 4).
proto := (aMsg at: 5) asInteger.
variable := (aMsg at: 6) asInteger.
@ -201,31 +237,9 @@ SCCPMessage subclass: SCCPConnectionRequest [
addr := SCCPAddress parseFrom: (aMsg copyFrom: (6 + variable)).
"parse the optional data"
pnc := aMsg copyFrom: (7 + optional).
[pnc isEmpty not] whileTrue: [
| type |
"TODO: Refactor...."
type := pnc at: 1.
type = SCCPHelper pncData
ifTrue: [
| size |
size := pnc at: 2.
data := pnc copyFrom: 3 to: 3 + size - 1.
pnc := pnc copyFrom: 3 + size.
]
ifFalse: [
type = SCCPHelper pncEoO
ifTrue: [
pnc := ByteArray new.
]
ifFalse: [
Exception signal: 'PNC Type is not handled', type asString.
].
].
].
pnc := SCCPPNC parseFrom: (aMsg copyFrom: (7 + optional)).
^ SCCPConnectionRequest initWith: src dest: addr data: data.
^ SCCPConnectionRequest initWith: src dest: addr pnc: pnc.
]
src [