1
0
Fork 0

isup: Various changes and fixes to the MessageStructure

* Use parameterName instead of name to avoid funny effects.
* Handle tag only classes as fixed field with a zero lengthLength
* Make the structure classes return an instance of itself. This
  is a bit weird and will need more thinking.
This commit is contained in:
Holger Hans Peter Freyther 2011-03-23 15:32:28 +01:00
parent 611237a576
commit 1d0b0c1bb4
3 changed files with 160 additions and 142 deletions

View File

@ -103,7 +103,7 @@ Object subclass: MSGField [
<category: 'osmo-networking'>
<comment: 'The description of an Information Element'>
MSGField class >> name [
MSGField class >> parameterName [
<category: 'accessing'>
^ self subclassResponsibility
]
@ -113,6 +113,13 @@ Object subclass: MSGField [
^ self subclassResponsibility
]
MSGField class >> lengthLength [
"The length of the length field. The default is to assume a length of
one octet and in the units of octets"
<category: 'accessing'>
^ 1
]
MSGField class >> octalLength [
<category: 'accessing'>
^ self subclassResponsibility

View File

@ -167,7 +167,7 @@ Object subclass: StructCreator [
handleFixedLength: aDef [
"Some fields have conflicting types... E.g. Range and Status
appears sometimes only as range... without the status."
| len type |
| len type tag_only |
aDef isFixed ifTrue: [len := aDef minLength].
aDef isVariable ifTrue: [len := (Number readFrom: aDef minLength readStream) - 1].
aDef isOptional ifTrue: [len := (Number readFrom: aDef minLength readStream) - 2].
@ -179,13 +179,22 @@ Object subclass: StructCreator [
aDef minLength printNl.
].
tag_only := ''.
len <= 0 ifTrue: [
len := 0.
tag_only := '
%1 class >> lengthLength [ ^ 0 ]
' % {aDef className}.
].
type :=
'MSGFixedField subclass: %1 [
%1 class >> name [ ^ ''%2'' ]
%1 class >> parameterName [ ^ ''%2'' ]
%1 class >> parameterValue [ ^ ISUPConstants par%3 ]
%1 class >> octalLength [ ^ %4 ]
%1 class >> spec [ ^ ''%5'' ]
]' % {aDef className. aDef commentName. aDef param. len. aDef ref.}.
%1 class >> spec [ ^ ''%5'' ]%6
]' % {aDef className. aDef commentName. aDef param. len. aDef ref. tag_only.}.
self addType: aDef ref struct: type.
]
@ -204,7 +213,7 @@ Object subclass: StructCreator [
type :=
'MSGVariableField subclass: %1 [
%1 class >> name [ ^ ''%2'' ]
%1 class >> parameterName [ ^ ''%2'' ]
%1 class >> parameterValue [ ^ ISUPConstants par%3 ]
%1 class >> octalLength [ ^ %4 ]
%1 class >> maxLength [ ^ %5 ]
@ -220,7 +229,7 @@ Object subclass: StructCreator [
struct add: '
ISUPMessage subclass: ISUP%1 [
ISUP%1 class >> structure [
^ (MSGStructure initWith: ISUPConstants msg%1)' % {structName. }.
^ (self initWith: ISUPConstants msg%1)' % {structName. }.
^ true
].

File diff suppressed because it is too large Load Diff