smalltalk
/
osmo-st-all
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-all/osmo-st-network/isup/generator/create_structs.st

332 lines
9.9 KiB
Smalltalk

Object subclass: StructItem [
| data |
StructItem class >> initWith: aData [
^ self new
data: aData; yourself
]
StructItem class >> makeCamelCase: aString [
| res capital |
res := OrderedCollection new: aString size.
capital := true.
1 to: aString size do: [:pos | | item |
item := aString at: pos.
item = $' ifFalse: [
item = $
ifTrue: [capital := true]
ifFalse: [
capital
ifTrue: [res add: item asUppercase]
ifFalse: [res add: item].
capital := false.
].
].
].
^ res asString
]
data: aData [
data := aData reverse substrings: ' '
]
isFixedLength [ ^ (self length indexOf: $-) = 0 ]
minLength [ ^ (self length substrings: '-') at: 1 ]
maxLength [ ^ (self length substrings: '-') at: 2 ]
isOptional [ ^ self type = 'O' ]
isVariable [ ^ self type = 'V' ]
isFixed [ ^ self type = 'F' ]
appearsMultiple [ ^ ((self text indexOf: '(Note 3)' matchCase: false startingAt: 1) isNil not) or: [
((self text indexOf: '(Note 1)' matchCase: false startingAt: 1) isNil not)] ]
name [
| shorten |
"TODO: Run more things.... shorten.. replace Backward -> Backw and such"
shorten := self shortenText.
^ ('ISUP' , (self class makeCamelCase: shorten)) ]
className [
| replaced makeUp |
makeUp := false.
replaced := OrderedCollection new.
self name do: [:each |
((each = $/) or: [each = $-]) ifFalse: [
makeUp ifTrue: [replaced add: each asUppercase]
ifFalse:[replaced add: each].
makeUp := false]
ifTrue: [makeUp := true].
].
^ replaced asString
]
param [
^ self className copyFrom: 5
]
length [ ^ (data at: 1) reverse]
type [ ^ data at: 2 ]
ref [ ^ (data at: 3) reverse ]
text [ ^ (String join: (data copyFrom: 4) separatedBy: ' ') reverse ]
shortenText [
| text paren |
text := self text.
(paren := text indexOf: $() > 0 ifTrue: [
text := (text copyFrom: 1 to: paren - 1) trimSeparators.
].
^ text
]
commentName [
| text replaced |
text := self shortenText.
replaced := OrderedCollection new.
text do: [:each |
replaced add: each.
each = $' ifTrue: [replaced add: $' ].
].
^ replaced asString
]
]
Object subclass: StructCreator [
| fields structs struct structName |
StructCreator class >> initWith: aFilename [
^ self new
file: (FileStream open: aFilename);
yourself
]
StructCreator class >> new [
^ super new
initialize
]
initialize [
fields := Dictionary new.
structs := OrderedCollection new.
]
file: aFile [
| out aStream |
struct := OrderedCollection new.
structName := (aFile copyFrom: 1 to: (aFile indexOf: $.) - 1) asUppercase.
aStream := FileStream open: aFile.
aStream linesDo: [:line | | def handle |
handle := (line indexOf: $#) = 0 and: [line size > 0].
handle ifTrue: [
self parse: line.
].
].
struct add: ' yourself.'.
struct add: ' ]'.
struct add: ']'.
out := String join: struct separatedBy: Character nl asString.
structs add: out.
]
parse: aLine [
| def |
def := StructItem initWith: aLine.
[
def isFixedLength
ifTrue: [self handleFixedLength: def]
ifFalse: [self handleVariableLength: def].
self addStruct: def.
] on: Exception do: [:e | e printNl. aLine printNl. e inspect].
]
addType: aType struct: aStruct [
fields at: aType ifPresent: [:other |
other = aStruct ifFalse: [
('Conflicting types of %1' % {aType}) printNl.
other printNl.
aStruct printNl.
].
].
fields at: aType put: aStruct.
]
handleFixedLength: aDef [
"Some fields have conflicting types... E.g. Range and Status
appears sometimes only as range... without the status."
| 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].
len isNil ifTrue: [
aDef isFixed printNl.
aDef isVariable printNl.
aDef isOptional printNl.
aDef minLength printNl.
].
tag_only := ''.
len <= 0 ifTrue: [
len := 0.
tag_only := '
%1 class >> lengthLength [ <category: ''field''> ^ 0 ]
' % {aDef className}.
].
aDef className = 'ISUPMessageType'
ifTrue: [^self].
type :=
'MSGFixedField subclass: %1 [
<category: ''OsmoNetwork-ISUP''>
<comment: ''I am an auto generated ISUP fixed field.''>
%1 class >> parameterName [ <category: ''field''> ^ ''%2'' ]
%1 class >> parameterValue [ <category: ''field''> ^ ISUPConstants par%3 ]
%1 class >> octalLength [ <category: ''field''> ^ %4 ]
%1 class >> spec [ <category: ''field''> ^ ''%5'' ]%6
]' % {aDef className. aDef commentName. aDef param. len. aDef ref. tag_only.}.
self addType: aDef ref struct: type.
]
handleVariableLength: aDef [
| type minLen maxLen off |
aDef isVariable ifTrue: [off := 1].
aDef isOptional ifTrue: [off := 2].
minLen := (Number readFrom: aDef minLength readStream) - off.
maxLen := aDef maxLength.
maxLen = '?' ifTrue: [maxLen := nil.]
ifFalse: [maxLen := (Number readFrom: maxLen readStream) - off].
type :=
'MSGVariableField subclass: %1 [
<category: ''OsmoNetwork-ISUP''>
<comment: ''I am an auto generated ISUP variable.''>
%1 class >> parameterName [ <category: ''field''> ^ ''%2'' ]
%1 class >> parameterValue [ <category: ''field''> ^ ISUPConstants par%3 ]
%1 class >> octalLength [ <category: ''field''> ^ %4 ]
%1 class >> maxLength [ <category: ''field''> ^ %5 ]
%1 class >> spec [ <category: ''field''> ^ ''%6'' ]
]' % {aDef className. aDef commentName. aDef param. minLen. maxLen. aDef ref}.
self addType: aDef ref struct: type.
]
addStruct: def [
"Create boiler plate code"
struct isEmpty ifTrue: [
struct add: '
ISUPMessage subclass: ISUP%1 [
<category: ''OsmoNetwork-ISUP''>
<comment: ''I am auto-generated ISUP message.''>
ISUP%1 class >> tlvDescription [
<category: ''field''>
^ (self initWith: ISUPConstants msg%1)' % {structName. }.
^ true
].
def isFixed ifTrue: [
struct add: ' addFixed: %1;' % {def className}.
].
def isVariable ifTrue: [
struct add: ' addVariable: %1;' % {def className}.
].
def isOptional ifTrue: [
def appearsMultiple
ifTrue: [struct add: ' addOptionals: %1;' % {def className}]
ifFalse: [struct add: ' addOptional: %1;' % {def className}]
].
]
structsDo: aBlock [
structs do: aBlock.
]
typesDo: aBlock [
fields do: aBlock.
]
]
Object subclass: SubclassCreator [
| structs |
<comment: 'I will create subclasses for identical structs but with a different
message type.'>
file: aName [
| className baseName |
className := (aName copyFrom: 6 to: (aName indexOf: $.) - 1) asUppercase.
baseName := ((FileStream open: aName) lines next copyFrom: 9) asUppercase.
self structs add: '
ISUP%1 subclass: ISUP%2 [
<category: ''OsmoNetwork-ISUP''>
<comment: ''I am an auto generated ISUP message.''>
ISUP%2 class >> tlvDescription [
<category: ''field''>
^ (super tlvDescription)
type: ISUPConstants msg%2; yourself
]
]' % {baseName. className}.
]
structsDo: aBlock [
self structs do: aBlock.
]
structs [
^ structs ifNil: [structs := OrderedCollection new]
]
]
Eval [
| struct outp subs |
same := #('same_bla.txt' 'same_ccr.txt' 'same_cgba.txt' 'same_cgua.txt'
'same_cgu.txt' 'same_far.txt' 'same_gra.txt' 'same_lpa.txt'
'same_olm.txt' 'same_rsc.txt' 'same_sus.txt' 'same_uba.txt'
'same_ubl.txt' 'same_ucic.txt' 'same_upa.txt').
files := #('acm.txt' 'amn.txt' 'apt.txt' 'blo.txt' 'cfn.txt' 'cgb.txt' 'con.txt'
'cot.txt' 'cpg.txt' 'cqr.txt' 'faa.txt' 'fac.txt' 'fot.txt' 'frj.txt'
'gra.txt' 'grs.txt' 'iam.txt' 'idr.txt' 'ids.txt' 'inf.txt' 'inr.txt'
'lpr.txt' 'nrm.txt' 'pri.txt' 'rel.txt' 'res.txt' 'rlc.txt'
'sam.txt' 'san.txt' 'seg.txt' 'upt.txt' 'usr.txt').
struct := StructCreator new.
files do: [:each | struct file: each. ].
outp := FileStream open: 'isup_generated.st' mode: 'w'.
outp nextPutAll: '"Types for ISUP"'.
outp nextPut: Character nl.
struct typesDo: [:each | outp nextPutAll: each. outp nextPut: Character nl. outp nextPut: Character nl.].
outp nextPutAll: '"MSGs for ISUP"'.
struct structsDo: [:struct | outp nextPutAll: struct. outp nextPut: Character nl. outp nextPut: Character nl].
subs := SubclassCreator new.
same do: [:each | subs file: each. ].
subs structsDo: [:struct | outp nextPutAll: struct. outp nextPut: Character nl; nextPut: Character nl.]
]