1
0
Fork 0

tlv: Move the TLV from here into the OsmoNetwork package

Update the references to the TLV code as it is now inside the
OsmoNetwork package
This commit is contained in:
Holger Hans Peter Freyther 2012-08-24 15:47:56 +02:00
parent 038cc7833b
commit dd58be49d6
6 changed files with 74 additions and 362 deletions

View File

@ -1,6 +1,5 @@
Eval [
FileStream
fileIn: 'TLV.st';
fileIn: 'OMLMsg.st';
fileIn: 'IPAOMLMsg.st';
fileIn: 'OML.st';

View File

@ -272,7 +272,7 @@ Object subclass: OMLAttribute [
asTLVDescription [
<category: 'parsing'>
^ TLVDescription new
^ Osmo.TLVDescription new
parseClass: self;
tag: self attributeType;
yourself
@ -968,7 +968,7 @@ OMLMessageBase subclass: FOMMessage [
]
]
TLVParserBase subclass: OMLDataField [
Osmo.TLVParserBase subclass: OMLDataField [
| object_class object_instance |
OMLDataField class >> canHandle: aType [
@ -1091,7 +1091,7 @@ OMLDataField subclass: OMLSWActivateRequest [
OMLSWActivateRequest class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrHWConfiguration;
instVarName: #hw_config;
parseClass: OMLAttributeData;
@ -1240,82 +1240,82 @@ OMLDataField subclass: OMLSetBTSAttributes [
OMLSetBTSAttributes class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrInterferenceLevelBoundaries;
beOptional; beTV; valueSize: 6;
instVarName: #inter_bounds; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrIntave;
beOptional; beTV; valueSize: 1;
instVarName: #intave; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrConnectionFailureCriterion;
beOptional;
instVarName: #con_fail; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrT200;
beOptional; beTV; valueSize: 7;
instVarName: #t200; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrMaxTimingAdvance;
beOptional; beTV; valueSize: 1;
instVarName: #max_timing; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrOverloadPeriod;
beOptional;
instVarName: #overload_period; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrCCCHLoadThreshold;
beOptional; beTV; valueSize: 1;
instVarName: #ccch_threshold; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrCCCHLoadIndicationPeriod;
beOptional; beTV; valueSize: 1;
instVarName: #ccch_ind; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrRACHBusyThreshold;
beOptional; beTV; valueSize: 1;
instVarName: #rach_busy; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrRACHLoadAveragingSlots;
beOptional; beTV; valueSize: 2;
instVarName: #rach_load; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrBTSAirTimer;
beOptional; beTV; valueSize: 1;
instVarName: #bts_air; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrNy1;
beOptional; beTV; valueSize: 1;
instVarName: #ny1; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrBCCHArfcn;
beOptional; beTV; valueSize: 2;
instVarName: #bcch_arfcn; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrBSIC;
beOptional; beTV; valueSize: 1;
instVarName: #bsic; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrStartingTime;
beOptional; beTV; valueSize: 2;
instVarName: #time; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: 16r99; beOptional; instVarName: #ipa_cgi;
parseClass: OMLAttributeData; yourself);
yourself
@ -1407,12 +1407,12 @@ OMLDataField subclass: OMLSetRadioCarrierAttributes [
OMLSetRadioCarrierAttributes class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrMaxPowerReduction;
beOptional; beTV; valueSize: 1;
instVarName: #max_power; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrARFCNList;
beOptional;
instVarName: #arfcn_list; parseClass: OMLAttributeData;
@ -1478,25 +1478,25 @@ OMLDataField subclass: OMLSetChannelAttributes [
add: (OMLChannelCombination asTLVDescription
beOptional;
instVarName: #chan_comb; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrHSN; beOptional; beTV; valueSize: 1;
parseClass: OMLAttributeData;
instVarName: #hsn; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrMAIO; beOptional; beTV; valueSize: 1;
parseClass: OMLAttributeData;
instVarName: #maio; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrARFCNList;
beOptional;
instVarName: #arfcn_list; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrStartingTime;
beOptional; beTV; valueSize: 2;
instVarName: #time; parseClass: OMLAttributeData;
yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: OMLAttribute attrTSC;
beOptional; beTV; valueSize: 1;
instVarName: #tsc; parseClass: OMLAttributeData;

View File

@ -24,7 +24,7 @@ Iterable extend [
]
]
TLVParserBase subclass: RSLMessageBase [
Osmo.TLVParserBase subclass: RSLMessageBase [
<category: 'BTS-RSL'>
<comment: 'I am the base of all RSL messages. I follow GSM 08.58'>
@ -247,7 +247,7 @@ Object subclass: RSLMessageDefinitions [
RSLMessageDefinitions class [
channelNumberIE [
<category: 'common-ie'>
^ TLVDescription new
^ Osmo.TLVDescription new
tag: RSLInformationElement attrChannelNumber;
instVarName: #channel_number; parseClass: RSLChannelNumber;
beTV; valueSize: 1; yourself.
@ -257,7 +257,7 @@ Object subclass: RSLMessageDefinitions [
<category: 'radio-link'>
^ OrderedCollection new
add: self channelNumberIE;
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrLinkIdentifier;
instVarName: #link_id; parseClass: RSLAttributeData;
beTV; valueSize: 2; yourself);
@ -267,7 +267,7 @@ Object subclass: RSLMessageDefinitions [
dataRequestMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrL3Information;
instVarName: #l3_info; parseClass: RSLAttributeData;
beTLV; yourself);
@ -282,7 +282,7 @@ Object subclass: RSLMessageDefinitions [
errorIndicationMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrRLMCause;
instVarName: #rlm_cause; parseClass: RSLAttributeData;
beTLV; minSize: 0 maxSize: 2; yourself);
@ -317,7 +317,7 @@ Object subclass: RSLMessageDefinitions [
unitDataRequestMessage [
<category: 'radio-link'>
^ self radioLinkMessageBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrL3Information;
instVarName: #l3_info; parseClass: RSLAttributeData;
minSize: 1 maxSize: 23;
@ -340,71 +340,71 @@ Object subclass: RSLMessageDefinitions [
channelActivationMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrActivationType;
instVarName: #activation_type; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrChannelMode;
instVarName: #channel_mode; parseClass: RSLAttributeData;
beTLV; minSize: 6 maxSize: 7; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrChannelIdentification;
instVarName: #channel_ident; parseClass: RSLAttributeData;
beOptional; beTLV; valueSize: 6; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrEncryptionInformation;
instVarName: #encr_info; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrHandoverReference;
instVarName: #handover_ref; parseClass: RSLAttributeData;
beConditional; beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrBSPower;
instVarName: #bs_power; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrMSPower;
instVarName: #ms_power; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrTimingAdvance;
instVarName: #timing_advance; parseClass: RSLAttributeData;
beConditional; beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrBSPowerParameters;
instVarName: #bs_powerparams; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 0; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrMSPowerParameters;
instVarName: #ms_powerparams; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 0; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrPhysicalContext;
instVarName: #physical_context; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 0; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrSacchInformation;
instVarName: #sacch_information; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrUIC;
instVarName: #uic; parseClass: RSLAttributeData;
beOptional; beTLV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrMainChannelReference;
instVarName: #main_chan_ref; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrMultiRateConfiguration;
instVarName: #mr_conf; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 2; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrMultiRateControl;
instVarName: #mr_control; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 2; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrSupportedCodecTypes;
instVarName: #supported_codecs; parseClass: RSLAttributeData;
beOptional; beTLV; minSize: 3; yourself);
@ -414,7 +414,7 @@ Object subclass: RSLMessageDefinitions [
channelActivationAckMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrFrameNumber;
instVarName: #frame_number; parseClass: RSLAttributeData;
beTV; valueSize: 2; yourself);
@ -424,7 +424,7 @@ Object subclass: RSLMessageDefinitions [
channelActivationNackMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrCause;
instVarName: #cause; parseClass: RSLAttributeData;
beTLV; minSize: 1; yourself);
@ -444,15 +444,15 @@ Object subclass: RSLMessageDefinitions [
encryptionCommandMessage [
<category: 'dedicated-channel'>
^ self dedicatedChannelMessageBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrEncryptionInformation;
instVarName: #encr_info; parseClass: RSLAttributeData;
beTLV; minSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrLinkIdentifier;
instVarName: #link_identifier; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrL3Information;
instVarName: #l3_info; parseClass: RSLAttributeData;
beTLV; minSize: 4 maxSize: 4; yourself);
@ -466,36 +466,46 @@ Object subclass: RSLMessageDefinitions [
yourself
]
bcchInformation [
bcchInformationMessage [
<category: 'channel-management'>
^ self commonChannelManagementBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrSystemInfoType;
instVarName: #si_type; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrFullBcchInformation;
instVarName: #full_bcch; parseClass: RSLAttributeData;
beOptional; beTLV; valueSize: 23; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrStartingTime;
instVarName: #start_time; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);
yourself
]
immediateAssignCommandMessage [
<category: 'channel-management'>
^ self commonChannelManagementBase
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrFullImmediateAssignInfo;
instVarName: #full_info; parseClass: RSLAttributeData;
beOptional; beTLV; valueSize: 23; yourself);
yourself
]
channelRequiredMessage [
<category: 'channel-management'>
^ self commonChannelManagementBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrRequestReference;
instVarName: #request_reference; parseClass: RSLAttributeData;
beTV; valueSize: 3; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrAccessDelay;
instVarName: #access_delay; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrPhysicalContext;
instVarName: #physical_context; parseClass: RSLAttributeData;
beTLV; minSize: 0; beOptional; yourself);
@ -510,15 +520,15 @@ Object subclass: RSLMessageDefinitions [
sacchFillingMessage [
<category: 'trx-management'>
^ self trxManagementMessageBase
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrSystemInfoType;
instVarName: #si_type; parseClass: RSLAttributeData;
beTV; valueSize: 1; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrL3Information;
instVarName: #l3_info; parseClass: RSLAttributeData;
beOptional; beTLV; beLen16; valueSize: 20; yourself);
add: (TLVDescription new
add: (Osmo.TLVDescription new
tag: RSLInformationElement attrStartingTime;
instVarName: #start_time; parseClass: RSLAttributeData;
beOptional; beTV; valueSize: 1; yourself);

View File

@ -1,268 +0,0 @@
"
(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/>.
"
Object subclass: TLVDescription [
| tag kind parse_class type inst_var min_size max_size len_size |
<category: 'BTS-TLV'>
<comment: 'I am another attempt to express optional and mandatory fields.'>
TLVDescription class [
"Kind"
optional [
<category: 'presence'>
^ #optional
]
mandatory [
<category: 'presence'>
^ #mandatory
]
conditional [
<category: 'presence'>
^ #conditional
]
"Type"
tagLengthValue [
<category: 'type'>
^ #tlv
]
tagValue [
<category: 'type'>
^ #tv
]
valueOnly [
<category: 'type'>
^ #valueOnly
]
tagOnly [
<category: 'type'>
^ #tagOnly
]
new [
<category: 'creation'>
^ super basicNew
initialize;
yourself
]
]
initialize [
<category: 'creation'>
kind := self class mandatory.
type := self class tagLengthValue.
len_size := 1.
]
tag: aTag [
<category: 'creation'>
tag := aTag
]
tag [
<category: 'access'>
"The tag value for this tag inside the bytestream"
^ tag
]
minSize: aMin maxSize: aMax [
<category: 'size'>
"This only makes sense for *LV elements"
min_size := aMin.
max_size := aMax.
]
minSize: aMin [
min_size := aMin.
max_size := nil.
]
valueSize: aSize [
<category: 'size'>
^ self minSize: aSize maxSize: aSize.
]
valueSize [
^ max_size
]
isOptional [
<category: 'access'>
^ kind = self class optional
]
isMandatory [
<category: 'access'>
^ kind = self class mandatory
]
isConditional [
<category: 'access'>
^ kind = self class conditional
]
isFixedSize [
<category: 'access'>
^ type = self class tagValue or: [type = self class valueOnly].
]
hasLength [
<category: 'access'>
^ type = self class tagLengthValue
]
isLen16 [
<category: 'access'>
^ self hasLength and: [len_size = 2]
]
isLen8 [
<category: 'access'>
^ self hasLength and: [len_size = 1]
]
presenceKind: aKind [
<category: 'creation'>
"Is this required, optional, variable?"
kind := aKind
]
beOptional [
<category: 'creation'>
self presenceKind: self class optional.
]
beConditional [
<category: 'creation'>
self presenceKind: self class conditional.
]
beTV [
<category: 'creation'>
self typeKind: self class tagValue
]
beTLV [
<category: 'creation'>
self typeKind: self class tagLengthValue
]
beLen16 [
<category: 'creation'>
len_size := 2.
]
typeKind: aType [
<category: 'creation'>
type := aType
]
typeKind [
<category: 'accessing'>
^ type
]
parseClass: aClass [
<category: 'creation'>
"The class to be used to parse this"
parse_class := aClass
]
parseClass [
<category: 'creation'>
^ parse_class
]
instVarName: aName [
<category: 'creation'>
inst_var := aName
]
instVarName [
<category: 'accessing'>
^ inst_var
]
]
Object subclass: TLVParserBase [
<category: 'BTS-TLV'>
<comment: 'I am the base class for TLV like parsers. I provide common
routines for parsing.'>
parseMandatory: attr tag: aTag stream: aStream [
<category: 'parsing'>
aTag = attr tag
ifFalse: [^self error: 'Mandatory %1 element is missing' % {attr instVarName}.].
aStream skip: 1.
self doParse: attr stream: aStream.
]
parseConditional: attr tag: aTag stream: aStream [
<category: 'parsing'>
^ self parseOptional: attr tag: aTag stream: aStream
]
parseOptional: attr tag: aTag stream: aStream [
<category: 'parsing'>
aTag = attr tag
ifFalse: [^false].
aStream skip: 1.
self doParse: attr stream: aStream.
]
doParse: attr stream: aStream [
<category: 'parsing'>
attr parseClass isNil
ifTrue: [^self error: 'No parse class available'].
self instVarNamed: attr instVarName
put: (attr parseClass readFrom: aStream with: attr).
^ true
]
writeOn: aMsg [
<category: 'serialize'>
"Write the header"
self writeHeaderOn: aMsg.
"Write each element"
self class tlvDescription do: [:attr |
| val |
val := self instVarNamed: attr instVarName.
"Check if it may be nil"
(val isNil and: [attr isMandatory])
ifTrue: [^self error: 'Mandatory parameter is nil.'].
"Now write it"
val isNil ifFalse: [
aMsg
putByte: attr tag.
val writeOn: aMsg with: attr.
].
]
]
]

View File

@ -301,33 +301,6 @@ RoundTripTestCase subclass: OMLMsgTest [
]
]
TestCase subclass: TLVDescriptionTest [
<category: 'BTS-OML-Tests'>
<comment: 'I try to test the TLV Description'>
testTLVCreation [
| tlv |
"Test default"
tlv := TLVDescription new.
self
assert: tlv isMandatory;
deny: tlv isOptional.
"Test update"
tlv presenceKind: tlv class optional.
self
assert: tlv isOptional;
deny: tlv isMandatory.
tlv instVarName: #bla.
self assert: tlv instVarName = #bla.
tlv tag: 16r23.
self assert: tlv tag = 16r23
]
]
TestCase subclass: RSLSmokeTest [
<category: 'BTS-RSL-Test'>
<comment: 'I am a simple smoke test for some of the RSL message support

View File

@ -3,7 +3,6 @@
<namespace>FakeBTS</namespace>
<prereq>OsmoNetwork</prereq>
<filein>TLV.st</filein>
<filein>OMLMsg.st</filein>
<filein>IPAOMLMsg.st</filein>
<filein>OML.st</filein>
@ -20,7 +19,6 @@
<sunit>FakeBTS.BasebandTransceiverOMLTest</sunit>
<sunit>FakeBTS.RadioChannelOMLTest</sunit>
<sunit>FakeBTS.OMLMsgTest</sunit>
<sunit>FakeBTS.TLVDescriptionTest</sunit>
<sunit>FakeBTS.RSLSmokeTest</sunit>
<sunit>FakeBTS.RSLRoundTripTest</sunit>
<sunit>FakeBTS.RSLIETest</sunit>