aboutsummaryrefslogtreecommitdiffstats
path: root/isup
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2011-03-23 15:32:28 +0100
committerHolger Hans Peter Freyther <zecke@selfish.org>2011-03-23 15:40:28 +0100
commit1d0b0c1bb41e70359cb21f746a92cb825d28307f (patch)
treeddce46fe384425af1ca3f082cd7d639be5bd7be7 /isup
parent611237a5769e125cd9f6a1abd4149f431eb7fee2 (diff)
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.
Diffstat (limited to 'isup')
-rw-r--r--isup/create_structs.st21
1 files changed, 15 insertions, 6 deletions
diff --git a/isup/create_structs.st b/isup/create_structs.st
index 17dbf0f..7f7df09 100644
--- a/isup/create_structs.st
+++ b/isup/create_structs.st
@@ -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
].