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

streams: Switch BSSAP to use streams.

This commit is contained in:
Holger Hans Peter Freyther 2012-03-25 21:50:02 +02:00
parent 7b43f3eed2
commit 8bdb0be6dc
3 changed files with 15 additions and 15 deletions

View File

@ -1,5 +1,5 @@
" "
(C) 2010 by Holger Hans Peter Freyther (C) 2010-2012 by Holger Hans Peter Freyther
All Rights Reserved All Rights Reserved
This program is free software: you can redistribute it and/or modify This program is free software: you can redistribute it and/or modify
@ -49,14 +49,14 @@ Object subclass: BSSAPHelper [
Object subclass: BSSAPMessage [ Object subclass: BSSAPMessage [
<category: 'OsmoGSM'> <category: 'OsmoGSM'>
BSSAPMessage class >> decode: bssap [ BSSAPMessage class >> decode: aStream [
| type | | type |
type := bssap at: 1. type := aStream next.
BSSAPMessage allSubclassesDo: [:each | BSSAPMessage allSubclassesDo: [:each |
each msgType = type each msgType = type
ifTrue: [ ifTrue: [
^ each parseFrom: bssap. ^ each parseFrom: aStream.
] ]
]. ].
@ -76,10 +76,10 @@ BSSAPMessage subclass: BSSAPManagement [
yourself. yourself.
] ]
BSSAPMessage class >> parseFrom: aByteArray [ BSSAPMessage class >> parseFrom: aStream [
| size data | | size data |
size := aByteArray at: 2. size := aStream next.
data := aByteArray copyFrom: 3 to: 2 + size. data := aStream next: size.
^ BSSAPManagement initWith: data. ^ BSSAPManagement initWith: data.
] ]
@ -115,11 +115,11 @@ BSSAPMessage subclass: BSSAPDTAP [
yourself yourself
] ]
BSSAPDTAP class >> parseFrom: aByteArray [ BSSAPDTAP class >> parseFrom: aStream [
| li size dat | | li size dat |
li := aByteArray at: 2. li := aStream next.
size := aByteArray at: 3. size := aStream next.
dat := aByteArray copyFrom: 4 to: 4 + size - 1. dat := aStream next: size.
^ BSSAPDTAP initWith: dat linkIdentifier: li. ^ BSSAPDTAP initWith: dat linkIdentifier: li.
] ]

View File

@ -334,15 +334,15 @@ Object subclass: MSGParser [
sccp := Osmo.SCCPMessage decode: aByteArray. sccp := Osmo.SCCPMessage decode: aByteArray.
(sccp respondsTo: #data) (sccp respondsTo: #data)
ifTrue: [ ifTrue: [
sccp data: (self decodeBSSAP: sccp data). sccp data: (self decodeBSSAP: sccp data readStream).
]. ].
^ sccp ^ sccp
] ]
MSGParser class >> decodeBSSAP: aData [ MSGParser class >> decodeBSSAP: aStream [
| bssap | | bssap |
bssap := BSSAPMessage decode: aData. bssap := BSSAPMessage decode: aStream.
bssap class msgType = BSSAPDTAP msgType bssap class msgType = BSSAPDTAP msgType
ifTrue: [ ifTrue: [
bssap data: (GSM48MSG decode: bssap data) bssap data: (GSM48MSG decode: bssap data)

View File

@ -144,7 +144,7 @@ TestCase subclass: BSSAPTest [
testParseManagement [ testParseManagement [
| man | | man |
man := BSSAPMessage decode: #(0 3 1 2 3) asByteArray. man := BSSAPMessage decode: #(0 3 1 2 3) asByteArray readStream.
self assert: (man isKindOf: BSSAPManagement). self assert: (man isKindOf: BSSAPManagement).
self assert: man data = #(1 2 3) asByteArray. self assert: man data = #(1 2 3) asByteArray.
] ]