1
0
Fork 0

rsl: Add the paging command to the rsl code and use GSM48 for parsing

This commit is contained in:
Holger Hans Peter Freyther 2012-12-23 10:21:24 +01:00
parent 314d1339a8
commit e01a38431f
2 changed files with 70 additions and 0 deletions

View File

@ -16,6 +16,8 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
PackageLoader fileInPackage: #OsmoGSM.
Iterable extend [
asRSLAttributeData [
<category: '*-BTS-OML-Msg'>
@ -538,6 +540,28 @@ Object subclass: RSLMessageDefinitions [
yourself
]
pagingCommandMessage [
<category: 'channel-management'>
^ self commonChannelManagementBase
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrPagingGroup;
instVarName: #paging_group; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrMSIdentifty;
instVarName: #ms_identity; parseClass: RSLAttributeData;
beTLV; minSize: 1 maxSize: 9; yourself);
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrChannelNeeded;
instVarName: #channel_needed; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
add: (Osmo.TLVDescription new
tag: RSLInformationElement attreMLPPPriority;
instVarName: #emlpp;
beOptional; beTV; valueSize: 2; yourself);
yourself.
]
immediateAssignCommandMessage [
<category: 'channel-management'>
^ self commonChannelManagementBase
@ -797,6 +821,37 @@ RSLCommonChannelManagement subclass: RSLBCCHInformation [
<rslMessageDefinition: #bcchInformationMessage>
]
RSLCommonChannelManagement subclass: RSLPagingCommand [
| paging_group ms_identity channel_needed emlpp |
<category: 'BTS-RSL'>
<comment: 'I represent a GSM 08.58 GSM 8.5.5'>
<rslMessageType: #messageTrxPagingCommand>
<rslMessageDefinition: #pagingCommandMessage>
pagingGroup [
<category: 'accessing'>
^ paging_group
]
msIdenity [
<category: 'accessing'>
^ OsmoGSM.GSM48MIdentity
parseFrom: ms_identity data readStream
length: ms_identity data size.
]
channelNeeded [
<category: 'accessing'>
^ channel_needed
]
emlppPriority [
<category: 'accessing'>
^ emlpp
]
]
RSLCommonChannelManagement subclass: RSLImmediateAssignment [
| full_info |
<category: 'BTS-RSL'>

View File

@ -445,6 +445,11 @@ RoundTripTestCase subclass: RSLRoundTripTest [
43 43 43 43 43 43)
]
pagingCommandData [
^ #(16r0C 16r15 16r01 16r90 16r0E 16r02 16r0C 16r05 16rF4 16r53
16rD3 16rD3 16r03 16r28 16r02)
]
establishIndicationData [
^ #(16r02 16r06 16r01 16r20 16r02 16r00 16r0B 16r00 16r0F 16r05 16r08
16r00 16r02 16rF8 16r01 16r74 16r05 16r30 16r05 16rF4 16rB5 16r0A
@ -524,6 +529,16 @@ RoundTripTestCase subclass: RSLRoundTripTest [
testReleaseRequestData [
self roundtripTestFor: #releaseRequestData class: RSLReleaseRequest.
]
testPagingCommand [
| msg mi |
self roundtripTestFor: #pagingCommandData class: RSLPagingCommand.
msg := RSLMessageBase parse: self pagingCommandData readStream.
mi := msg msIdenity.
self assert: mi type = OsmoGSM.GSM48IdentityType typeTMSI.
self assert: mi tmsi asByteArray = #(83 211 211 3 ) asByteArray.
]
]
TestCase subclass: RSLIETest [