1
0
Fork 0

tlv: Move the TLV from the FakeBTS code to here to be used and improved

This commit is contained in:
Holger Hans Peter Freyther 2012-08-23 16:23:32 +02:00
parent 52a0026d32
commit e7f79e2621
3 changed files with 315 additions and 0 deletions

268
TLV.st Normal file
View File

@ -0,0 +1,268 @@
"
(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: 'OsmoNetwork-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: 'OsmoNetwork-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.
].
]
]
]

44
TLVTests.st Normal file
View File

@ -0,0 +1,44 @@
"
(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/>.
"
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
]
]

View File

@ -19,6 +19,7 @@
<filein>M2UA.st</filein>
<filein>LogAreas.st</filein>
<filein>SocketBase.st</filein>
<filein>TLV.st</filein>
<test>
<sunit>Osmo.SCCPTests</sunit>
@ -28,8 +29,10 @@
<sunit>Osmo.M2UATests</sunit>
<sunit>Osmo.ISUPGeneratedTest</sunit>
<sunit>Osmo.OsmoUDPSocketTest</sunit>
<sunit>Osmo.TLVDescriptionTest</sunit>
<filein>Tests.st</filein>
<filein>ISUPTests.st</filein>
<filein>IPATests.st</filein>
<filein>TLVTests.st</filein>
</test>
</package>