1
0
Fork 0

fakebts: Respond to the ipa MGCP endpoint commands and send indication

Respond to the CRCX, MDCX and generate a DLCX Ind at the end of the call.
This commit is contained in:
Holger Hans Peter Freyther 2012-12-23 20:14:06 +01:00
parent 6db40339de
commit d54d1648d8
3 changed files with 124 additions and 2 deletions

View File

@ -172,6 +172,47 @@ RSLReleaseRequest extend [
]
]
RSLIPACreateConnection extend [
trxDispatchOn: aTrx with: lchan [
| ack |
<category: '*-BTS-Core'>
lchan ipaConnId: aTrx mainBts newConnectionIdentifier asRSLAttributeData.
ack := RSLIPACreateConnectionAck new
channelNumber: lchan channelNumber;
connectionIdentifier: lchan ipaConnId;
localPort: #(23 42) asRSLAttributeData;
localIP: #(0 0 0 0) asRSLAttributeData;
yourself.
aTrx mainBts sendRSL: ack toMessage on: aTrx.
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"A sapi has been released."
self trxChannelDispatch: aTrx.
]
]
RSLIPAModifyConnection extend [
trxDispatchOn: aTrx with: lchan [
| ack |
<category: '*-BTS-Core'>
ack := RSLIPAModifyConnectionAck new
channelNumber: lchan channelNumber;
connectionIdentifier: lchan ipaConnId;
yourself.
aTrx mainBts sendRSL: ack toMessage on: aTrx.
]
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
"A sapi has been released."
self trxChannelDispatch: aTrx.
]
]
RSLPagingCommand extend [
trxDispatchOn: aTrx [
<category: '*-BTS-Core'>
@ -181,7 +222,7 @@ RSLPagingCommand extend [
Object subclass: BTS [
| site_mgr oml rsl oml_queue oml_init connected oml_up ras ras_mutex
bts_id on_paging |
bts_id on_paging last_conn_id |
<category: 'BTS-Core'>
<comment: 'A fake BTS to test the state machine and inject
RSL messages to test a network without RF.'>
@ -195,6 +236,7 @@ Object subclass: BTS [
self stop.
rsl := nil.
last_conn_id := 0.
oml := BTSOmlConnection new
onData: [:each | self handleOml: each];
onStop: [self omlStopped];
@ -406,4 +448,11 @@ Object subclass: BTS [
onPaging: aCallback [
on_paging := aCallback
]
newConnectionIdentifier [
last_conn_id := last_conn_id + 1.
^ ByteArray
with: ((last_conn_id bitShift: -8) bitAnd: 16rFF)
with: (last_conn_id bitAnd: 16rFF)
]
]

View File

@ -664,7 +664,7 @@ OMLChannelCombination extend [
]
Object subclass: LogicalChannel [
| number free sapis ts onDataCb onReleaseReqCB |
| number free sapis ts onDataCb onReleaseReqCB conn_id |
<category: 'BTS-OML'>
<comment: 'I am a logical that is on the ChannelOML.'>
@ -781,6 +781,18 @@ Object subclass: LogicalChannel [
| ack |
<category: 'release'>
conn_id ifNotNil: [
| ind |
ind := RSLIPADeleteConnectionInd new
defaultValues;
channelNumber: self channelNumber;
connectionIdentifier: conn_id;
yourself.
conn_id := nil.
ts forwardRsl: ind toMessage.
].
free := true.
ack := RSLRFChannelReleaseAck new
channelNumber: self channelNumber;
@ -831,6 +843,16 @@ Object subclass: LogicalChannel [
yourself.
ts forwardRsl: rsl toMessage.
]
ipaConnId [
<category: 'ipa-audio'>
^ conn_id
]
ipaConnId: anId [
<category: 'ipa-audio'>
conn_id := anId
]
]
OMLManagerBase subclass: ChannelOML [

View File

@ -1259,6 +1259,10 @@ RSLIPAVendorManagement subclass: RSLIPACreateConnection [
<comment: 'I represent a Create Connection (CRCX) message'>
<rslMessageType: #messageCRCX>
<rslMessageDefinition: #createConnectionMessage>
channelNumber [
^ channel_number
]
]
RSLIPAVendorManagement subclass: RSLIPACreateConnectionAck [
@ -1267,6 +1271,24 @@ RSLIPAVendorManagement subclass: RSLIPACreateConnectionAck [
<comment: 'I represent a Create Connection (CRCX) ACK message'>
<rslMessageType: #messageCRCXAck>
<rslMessageDefinition: #createConnectionAckMessage>
channelNumber: aNumber [
<category: 'creation'>
channel_number := aNumber
]
connectionIdentifier: anId [
<category: 'creation'>
conn_id := anId
]
localPort: aPort [
local_port := aPort
]
localIP: anAddr [
local_ip := anAddr
]
]
RSLIPAVendorManagement subclass: RSLIPAModifyConnection [
@ -1275,6 +1297,10 @@ RSLIPAVendorManagement subclass: RSLIPAModifyConnection [
<comment: 'I represent a Modify Connection (MDCX) message'>
<rslMessageType: #messageMDCX>
<rslMessageDefinition: #modifyConnectionMessage>
channelNumber [
^ channel_number
]
]
RSLIPAVendorManagement subclass: RSLIPAModifyConnectionAck [
@ -1283,6 +1309,16 @@ RSLIPAVendorManagement subclass: RSLIPAModifyConnectionAck [
<comment: 'I represent a Modify Connection (MDCX) ACK message'>
<rslMessageType: #messageMDCXAck>
<rslMessageDefinition: #modifyConnectionAckMessage>
channelNumber: aNumber [
<category: 'creation'>
channel_number := aNumber
]
connectionIdentifier: anId [
<category: 'creation'>
conn_id := anId
]
]
RSLIPAVendorManagement subclass: RSLIPADeleteConnectionInd [
@ -1291,4 +1327,19 @@ RSLIPAVendorManagement subclass: RSLIPADeleteConnectionInd [
<comment: 'I represent a Delete Connection (DLCX) Indication message'>
<rslMessageType: #messageDLCXInd>
<rslMessageDefinition: #deleteConnectionIndMessage>
defaultValues [
stats := (ByteArray new: 28) asRSLAttributeData.
cause := (ByteArray new: 1) asRSLAttributeData.
]
channelNumber: aNumber [
<category: 'creation'>
channel_number := aNumber
]
connectionIdentifier: anId [
<category: 'creation'>
conn_id := anId
]
]