1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-openbsc-test/fakebts/BTSConnection.st

292 lines
6.8 KiB
Smalltalk

"
(C) 2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
PackageLoader
fileInPackage: #Sockets;
fileInPackage: #OsmoCore;
fileInPackage: #OsmoNetwork.
Osmo.IPAProtoHandler subclass: BTSIPAProtoHandler [
| on_id_get id |
<category: 'BTS-Core'>
<comment: 'ID Get'>
<import: Osmo>
onIdGet: aBlock [
<category: 'connection'>
on_id_get := aBlock
]
btsId: anId [
<category: 'creation'>
"Set the BTS ID"
id := anId
]
handleIdGet: aMsg [
| name in_msg out_msg unit_id |
name := 'BTS Test'.
"null terminate the string"
unit_id := (WriteStream on: (ByteArray new: 6))
nextPutAll: id asByteArray;
nextPut: 16r0;
contents.
in_msg := IPAMsgRequest parse: aMsg asByteArray readStream.
out_msg := IPAMsgResponse new
type: IPAConstants msgIdResp;
data: (Array
with: (16r8->unit_id));
yourself.
muxer nextPut: out_msg toMessage asByteArray with: IPAConstants protocolIPA.
"Inform about the request"
on_id_get value.
]
]
Object subclass: BTSConnectionBase [
| socket txQueue mux demux rxDispatch rxProc txProc stopped
onData onStop onConnect connected address btsId streamId |
<category: 'BTS-Core'>
<comment: 'I am the base class for the OML and RSL connection
to the BSC'>
<import: Osmo>
BTSConnectionBase class >> new [
<category: 'creation'>
^ super new
initialize;
yourself.
]
initialize [
<category: 'creation'>
stopped := false.
]
btsId: anId [
<category: 'creation'>
btsId := anId
]
btsId [
<category: 'query'>
^ btsId ifNil: ['1801/0/0']
]
streamId: anId [
<category: 'creation'>
streamId := anId
]
streamId [
<category: 'query'>
^ streamId ifNil: [self class ipaPrototype]
]
connect: anAddress [
<category: 'connect'>
^ self connect: anAddress port: self class defaultPort
]
address [
<category: 'accessing'>
^ address
]
txQueueIsEmpty [
<category: 'accessing'>
^ txQueue isEmpty.
]
connect: anAddress port: aPort[
| proto_handler |
<category: 'connect'>
address := anAddress.
socket := Sockets.StreamSocket remote: anAddress port: aPort.
txQueue := SharedQueue new.
demux := IPADemuxer initOn: socket.
mux := IPAMuxer initOn: txQueue.
rxDispatch := IPADispatcher new.
proto_handler := BTSIPAProtoHandler new
token: '1801';
registerOn: rxDispatch;
muxer: mux;
onIdGet: [self gotIdRequest];
btsId: self btsId;
yourself.
self streamConnected.
stopped := false.
connected := false.
"Now start the input/output process"
rxProc := [
Processor activeProcess name: self class name, ' RX'.
[stopped] whileFalse: [self processOne].
] fork.
txProc := [
Processor activeProcess name: self class name, ' TX'.
[stopped] whileFalse: [self sendOne].
] fork.
]
processOne [
<category: 'receive'>
| msg |
[
msg := demux next.
] on: SystemExceptions.EndOfStream do: [:e |
Transcript
nextPutAll: 'Socket is at an end.'; nl.
self stop.
^ false.
] on: SystemExceptions.FileError do: [:e |
Transcript
nextPutAll: 'FileError on read'; nl.
self stop.
^ false.
].
OsmoDispatcher
dispatchBlock: [rxDispatch dispatch: msg first with: msg second].
]
sendOne [
| msg |
<category: 'send'>
msg := txQueue next.
"Pill of death?"
msg isNil ifTrue: [^false].
socket nextPutAllFlush: msg.
]
send: aMsg [
<category: 'send'>
mux nextPut: aMsg with: self streamId
]
onData: aBlock [
<category: 'input'>
onData := aBlock.
]
onStop: aBlock [
<category: 'input'>
onStop := aBlock.
]
onConnect: aBlock [
<category: 'input'>
onConnect := aBlock.
]
stop [
<category: 'control'>
"Already stopped?"
stopped ifTrue: [^false].
stopped := true.
"Close things down."
socket close.
socket := nil.
txQueue nextPut: nil.
"Inform about the end of stream."
onStop isNil ifFalse: [
OsmoDispatcher
dispatchBlock: [onStop value]].
]
gotIdRequest [
<category: 'connection'>
connected ifTrue: [^true].
connected := true.
onConnect isNil ifFalse: [
OsmoDispatcher
dispatchBlock: [onConnect value]].
]
]
BTSConnectionBase subclass: BTSOmlConnection [
<category: 'BTS-Core'>
<comment: 'I am the OML connection'>
BTSOmlConnection class >> defaultPort [
<category: 'port'>
^ 3002
]
BTSOmlConnection class >> ipaPrototype [
<category: 'internal'>
^ IPAConstants protocolOML
]
streamConnected [
<category: 'initialize'>
rxDispatch
addHandler: self streamId
on: [:msg | self handleOml: msg].
]
handleOml: aMsg [
<category: 'input'>
onData value: aMsg
]
]
BTSConnectionBase subclass: BTSRslConnection [
<category: 'BTS-Core'>
<comment: 'I am the RSL connection'>
BTSRslConnection class >> defaultPort [
<category: 'port'>
^ 3003
]
BTSRslConnection class >> ipaPrototype [
<category: 'internal'>
^ IPAConstants protocolRSL
]
streamConnected [
<category: 'initialize'>
rxDispatch
addHandler: self streamId
on: [:msg | self handleRsl: msg].
]
handleRsl: aMsg [
<category: 'input'>
onData value: aMsg
]
]