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

bssmap: Add code to ease creating a ChannelType IE

This commit is contained in:
Holger Hans Peter Freyther 2011-06-25 09:13:03 +02:00
parent f8e669904d
commit 1266abafa0
2 changed files with 58 additions and 7 deletions

View File

@ -461,25 +461,55 @@ GSM0808IE subclass: GSM0808ChosenEncrIE [
GSM0808IE subclass: GSM0808ChannelTypeIE [
| type preferred codecs |
<comment: 'I implement 3.2.2.11 of GSM08.08'>
GSM0808ChannelTypeIE class >> speechSpeech [ ^ 1 ]
GSM0808ChannelTypeIE class >> speechData [ ^ 2 ]
GSM0808ChannelTypeIE class >> speechSignalling [ ^ 3 ]
"TODO: provide defs for the 3.2.2.11 ChannelType rate"
GSM0808ChannelTypeIE class [
chanSpeechFullBm [ <category: 'ChannelType-Speech'> ^ 2r1000 ]
chanSpeechHalfLm [ <category: 'ChannelType-Speech'> ^ 2r1001 ]
chanSpeechFullPref [ <category: 'ChannelType-Speech'> ^ 2r1010 ]
chanSpeechHalfPref [ <category: 'ChannelType-Speech'> ^ 2r1011 ]
chanSpeechFullPrefNoChange [ <category: 'ChannelType-Speech'> ^ 2r11010 ]
chanSpeechHalfPrefNoChange [ <category: 'ChannelType-Speech'> ^ 2r11011 ]
chanSpeechAny [ <category: 'ChannelType-Speech'> ^ 2r1111 ]
chanSpeechAnyNoChange [ <category: 'ChannelType-Speec'> ^ 2r11111 ]
speechFullRateVersion1 [ <category: 'Speech-Version'> ^ 2r000001 ]
speechFullRateVersion2 [ <category: 'Speech-Version'> ^ 2r010001 ]
speechFullRateVersion3 [ <category: 'Speech-Version'> ^ 2r100001 ]
speechHalfRateVersion1 [ <category: 'Speech-Version'> ^ 2r000101 ]
speechHalfRateVersion2 [ <category: 'Speech-Version'> ^ 2r010101 ]
speechHalfRateVersion3 [ <category: 'Speech-Version'> ^ 2r100101 ]
buildPermittedSpeechList: aList [
| out |
out := aList asByteArray copy.
1 to: out size - 1 do: [:pos |
out at: pos put: ((out at: pos) bitOr: 16r80)
].
^ out
]
]
GSM0808ChannelTypeIE class >> elementId [ ^ 11 ]
GSM0808ChannelTypeIE class >> initWith: aType audio: anAudioType codecs: codecs [
GSM0808ChannelTypeIE class >> initWith: aType audio: anAudioType [
^ self new
type: aType;
preferred: anAudioType;
audioCodecs: codecs;
yourself
]
GSM0808ChannelTypeIE class >> parseFrom: aByteArray [
^ self initWith: (aByteArray at: 3)
audio: (aByteArray at: 4)
codecs: (aByteArray copyFrom: 5)
^ (self initWith: (aByteArray at: 3)
audio: (aByteArray at: 4))
audioCodecs: (aByteArray copyFrom: 5);
yourself
]
type [ ^ type ]
@ -490,10 +520,15 @@ GSM0808IE subclass: GSM0808ChannelTypeIE [
preferred [ ^ preferred ]
preferred: aPreferred [ preferred := aPreferred ]
audioCodecs: aList [
<category: 'audio-codes'>
self audioCodecsData: (self class buildPermittedSpeechList: aList).
]
"TODO: This should decode/encode the codecs"
audioCodecs [ ^ codecs ]
audioCodecs: aCodecs [ codecs := aCodecs. ]
audioCodecsData [ ^ codecs ]
audioCodecsData: aCodecs [ codecs := aCodecs. ]
writeOnDirect: aMsg [
aMsg putByte: 2 + codecs size.

View File

@ -104,6 +104,22 @@ TestCase subclass: GSM0808Test [
res := (GSM0808CICIE initWithMultiplex: 1 timeslot: 20) toMessage asByteArray.
self assert: res = #(1 0 52) asByteArray.
]
testChanIE [
| res |
res := (GSM0808ChannelTypeIE buildPermittedSpeechList:
{GSM0808ChannelTypeIE speechFullRateVersion3.
GSM0808ChannelTypeIE speechHalfRateVersion3}).
self assert: res = #(161 37) asByteArray.
res := ((GSM0808ChannelTypeIE
initWith: (GSM0808ChannelTypeIE speechSpeech)
audio: (GSM0808ChannelTypeIE chanSpeechHalfPrefNoChange))
audioCodecs: {GSM0808ChannelTypeIE speechFullRateVersion3.
GSM0808ChannelTypeIE speechHalfRateVersion3};
yourself).
self assert: res toMessage asByteArray = #(11 4 1 27 161 37) asByteArray.
]
]
TestCase subclass: BSSAPTest [