1
0
Fork 0

msgstruct: Move to class based message fields

Remove the need to create an instance of this class. So we either
need to make this totally instance based and hold the dictionary
in the ISUPMessage or we can keep it class based. I am not sure what
is best right now.
This commit is contained in:
Holger Hans Peter Freyther 2011-03-20 11:45:45 +01:00
parent ad58823edf
commit 611237a576
4 changed files with 397 additions and 630 deletions

View File

@ -21,22 +21,31 @@ TestCase subclass: ISUPGeneratedTest [
instantiate all generated class and walk the hierachy to see if
there are any DNUs'>
playWith: aField [
aField name.
aField parameterValue.
aField octalLength.
self assert: aField isVarible ~= aField isFixed.
aField isVarible ifTrue: [aField maxLength].
]
testGeneration [
ISUPMessage allSubclassesDo: [:class |
| struct |
struct := class structure.
struct fixed do: [:each |
each create].
self playWith: each].
struct variable do: [:each |
each create].
self playWith: each].
struct optional do: [:each |
each create].
self playWith: each].
struct optionals do: [:each |
each create].
self playWith: each].
"same thing once more"
struct fieldsDo: [:type :class |
class create].
self playWith: class].
].
]

View File

@ -101,79 +101,45 @@ Object subclass: MSGStructure [
Object subclass: MSGField [
<category: 'osmo-networking'>
<comment: 'The description of a Information Element'>
| par name length maxLength |
<comment: 'The description of an Information Element'>
name [
MSGField class >> name [
<category: 'accessing'>
^ name
^ self subclassResponsibility
]
parameterValue [
MSGField class >> parameterValue [
<category: 'accessing'>
^ par
^ self subclassResponsibility
]
octalLength [
MSGField class >> octalLength [
<category: 'accessing'>
^ length
^ self subclassResponsibility
]
maxLength [
<category: 'accessing'>
^ maxLength
]
isVarible [
MSGField class >> isVarible [
"If this field is variable in length"
^ self subclassResponsibility
]
isFixed [
MSGField class >> isFixed [
"If this field is of a fixed length"
^ self subclassResponsibility
]
]
MSGField subclass: MSGFixedField [
MSGFixedField class [
initWith: aName parameter: aParm octalLength: aLen [
^ self new
instVarNamed: #name put: aName;
instVarNamed: #par put: aParm;
instVarNamed: #length put: aLen;
yourself
]
]
isVarible [ ^ false ]
isFixed [ ^ true ]
MSGFixedField class >> isVarible [ ^ false ]
MSGFixedField class >> isFixed [ ^ true ]
]
MSGField subclass: MSGVariableField [
MSGVariableField class [
initWith: aName parameter: aParm
minOctalLength: aLen [
^ self new
instVarNamed: #name put: aName;
instVarNamed: #par put: aParm;
instVarNamed: #length put: aLen;
yourself
]
initWith: aName parameter: aParm
minOctalLength: aMin maxOctalLength: aMax [
^ self new
instVarNamed: #name put: aName;
instVarNamed: #par put: aParm;
instVarNamed: #length put: aMin;
instVarNamed: #maxLength put: aMax;
yourself
]
MSGVariableField class >> maxLength [
<category: 'accessing'>
^ nil
]
isVarible [ ^ true ]
isFixed [ ^ false ]
MSGVariableField class >> isVarible [ ^ true ]
MSGVariableField class >> isFixed [ ^ false ]
]

View File

@ -181,11 +181,9 @@ Object subclass: StructCreator [
type :=
'MSGFixedField subclass: %1 [
%1 class >> create [
^ self initWith: ''%2''
parameter: ISUPConstants par%3
octalLength: %4; yourself
]
%1 class >> name [ ^ ''%2'' ]
%1 class >> parameterValue [ ^ ISUPConstants par%3 ]
%1 class >> octalLength [ ^ %4 ]
%1 class >> spec [ ^ ''%5'' ]
]' % {aDef className. aDef commentName. aDef param. len. aDef ref.}.
@ -206,12 +204,10 @@ Object subclass: StructCreator [
type :=
'MSGVariableField subclass: %1 [
%1 class >> create [
^ self initWith: ''%2''
parameter: ISUPConstants par%3
minOctalLength: %4
maxOctalLength: %5
]
%1 class >> name [ ^ ''%2'' ]
%1 class >> parameterValue [ ^ ISUPConstants par%3 ]
%1 class >> octalLength [ ^ %4 ]
%1 class >> maxLength [ ^ %5 ]
%1 class >> spec [ ^ ''%6'' ]
]' % {aDef className. aDef commentName. aDef param. minLen. maxLen. aDef ref}.

File diff suppressed because it is too large Load Diff