smalltalk
/
osmo-st-gsm
Archived
1
0
Fork 0

BSSMAP: Parse the Clear Command message.

This commit is contained in:
Holger Hans Peter Freyther 2010-11-24 15:33:19 +01:00
parent 92c95cab97
commit 50001c769b
2 changed files with 62 additions and 0 deletions

View File

@ -210,3 +210,38 @@ GSM0808IE subclass: GSMLayer3Info [
aMsg putByteArray: dat.
]
]
GSM0808IE subclass: GSMCauseIE [
| cause |
<category: 'osmo-message'>
<comment: 'Generate a CauseIE'>
"TODO: Only simple ones are supported right now"
GSMCauseIE class >> elementId [ <category: 'spec'> ^ 4 ]
GSMCauseIE class >> initWith: aCause [
^ self new
cause: aCause;
yourself
]
GSMCauseIE class >> parseFrom: aByteArray [
| size |
size := aByteArray at: 2.
size = 1
ifFalse: [
^ Error signal: 'Extended error codes are not supported.'.
].
^ GSMCauseIE initWith: (aByteArray at: 3)
]
cause [ ^ cause ]
cause: aCause [ cause := aCause ]
writeOn: aMsg [
aMsg putByte: self class elementId.
aMsg putByte: 1.
aMsg putByte: cause.
]
]

View File

@ -54,6 +54,18 @@ TestCase subclass: GSM0808Test [
self assert: buf asByteArray = res
]
testCuaseIE [
| buf ie res |
res := #(4 1 32) asByteArray.
ie := GSMCauseIE initWith: 32.
buf := ie toMessage asByteArray.
self assert: buf = res.
ie := GSMCauseIE parseFrom: res.
self assert: ie cause = 32.
]
testIEDecoding [
| inp res |
inp := #(16r57 16r05 16r08 16r00 16r72 16rF4 16r80 16r20 16r12
@ -248,4 +260,19 @@ TestCase subclass: TestMessages [
self assert: msg toMessage asByteArray = inp.
]
testMsgparserDt1Clear [
| inp msg bssap bssmap |
inp := #(6 154 2 0 0 1 6 0 4 32 4 1 32) asByteArray.
msg := MSGParser parse: inp.
self assert: (msg isKindOf: Osmo.SCCPConnectionData).
bssap := msg data.
self assert: (bssap isKindOf: BSSAPManagement).
bssmap := bssap data.
self assert: (bssmap isKindOf: IEMessage).
self assert: msg toMessage asByteArray = inp.
]
]