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/IPAOMLMsg.st

173 lines
4.5 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/>.
"
FOMMessage subclass: IPAFOMMessage [
| man |
<category: 'BTS-OML'>
<comment: 'I represent the IPA Manufacturer messages.'>
IPAFOMMessage class >> msgType [
<category: 'parsing'>
^ 16r10
]
IPAFOMMessage class >> fieldBaseClass [
<category: 'parsing'>
^ IPAOMLDataField
]
IPAFOMMessage class >> readFrom: aStream [
| placement seq len man dataStream type |
<category: 'parsing'>
"Sanity checking"
(placement := aStream next) = self placementOnly
ifFalse: [^self error: 'Can not deal with fragmented OML'].
(seq := aStream next) = 0
ifFalse: [^self error: 'Can not deal with sequence numbers'].
"Prepare a new buffer"
len := aStream next.
man := aStream next: aStream next.
dataStream := (aStream next: len) readStream.
type := dataStream next.
IPAOMLDataField allSubclassesDo: [:each |
(each canHandle: type) ifTrue: [
^self new
manId: man;
omDataField: (each readFrom: dataStream);
yourself]].
^ self error: 'Can not parse O&M Data field type:', type asString.
]
manId: anId [
<category: 'creation'>
man := anId
]
manId [
<category: 'accessing'>
^ man
]
writeOn: aMsg [
| msg |
<category: 'serialize'>
msg := om_field toMessage asByteArray.
aMsg
putByte: self class msgType;
putByte: self class placementOnly;
putByte: 0;
putByte: msg size;
putByte: man size;
putByteArray: man;
putByteArray: msg.
]
createAck [
<category: 'acking'>
"Try to create an ACK"
^ self class new
manId: self manId;
omDataField: om_field createAck;
yourself
]
]
OMLDataField subclass: IPAOMLDataField [
<category: 'BTS-OML'>
<comment: 'I represent IPA messages. I am just a baseclass '>
IPAOMLDataField class >> canHandle: aType [
<category: 'parsing'>
"Exclude myself from possible parsers"
^ self = IPAOMLDataField
ifTrue: [false]
ifFalse: [super canHandle: aType].
]
]
IPAOMLDataField subclass: IPAOMLRSLConnect [
| streamid port |
<category: 'BTS-OML'>
<comment: 'A request to make a RSL connection'>
IPAOMLRSLConnect class >> attributeType [
<category: 'parsing'>
^ 16rE0
]
IPAOMLRSLConnect class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (TLVDescription newOMLDescription
tag: 16r85; beTV; valueSize: 1;
instVarName: #streamid; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription newOMLDescription
tag: 16r81; beTV; valueSize: 2;
instVarName: #port; parseClass: OMLAttributeData;
yourself);
yourself.
]
streamId [
<category: 'accessing'>
^ streamid
]
streamId: anId [
<category: 'creation'>
streamid := anId
]
port [
<category: 'accessing'>
^ port
]
port: aPort [
<category: 'creation'>
port := aPort
]
createAck [
<category: 'acking'>
^ IPAOMLRSLConnectAck new
objectClass: self objectClass;
objectInstance: self objectInstance;
streamId: self streamId;
port: self port;
yourself.
]
]
IPAOMLRSLConnect subclass: IPAOMLRSLConnectAck [
<category: 'BTS-OML'>
<comment: 'A request to make a RSL connection'>
IPAOMLRSLConnectAck class >> attributeType [
<category: 'parsing'>
^ 16rE1
]
]