1
0
Fork 0

isup: Attempt to make the code more readable

We want to handle fixed, mandatory and then optional|optionals,
make the code more readabl.
This commit is contained in:
Holger Hans Peter Freyther 2012-02-02 20:06:15 +01:00
parent f4a72bab38
commit fc5778fa3c
1 changed files with 31 additions and 22 deletions

View File

@ -117,16 +117,33 @@ Object subclass: MSGStructure [
^ lst
]
filterdDo: aBlock filter: aFilter [
<category: 'private'>
^ self fields do: [:each |
each first = aFilter ifTrue: [
aBlock value: each first value: each second]].
]
fixed [
<category: 'private'>
^ self filter: #fixed
]
fixedDo: aBlock [
<category: 'private'>
^ self filterdDo: aBlock filter: #fixed.
]
variable [
<category: 'private'>
^ self filter: #variable
]
variableDo: aBlock [
<category: 'private'>
^ self filterdDo: aBlock filter: #variable.
]
optional [
<category: 'private'>
^ self filter: #optional
@ -270,38 +287,30 @@ Object subclass: MSGStructure [
]
encodeCollection: aCollection [
| stream msg type_state aState |
| stream msg aState |
<category: 'encoding'>
msg := WriteStream on: (ByteArray new: 3).
stream := aCollection readStream.
type_state := #initial.
aState := self createState.
"Try to match the fields of the structure with the fields of
the collection. We keep some local state to check if we are
passed the fixed and variable fields."
"Write the fixed portion"
self fixedDo: [:type :clazz |
self writeFixed: msg with: clazz from: stream next state: aState.
].
self writeFixedEnd: msg state: aState.
"Write the variable portion"
self variableDo: [:type :clazz |
self writeVariable: msg with: clazz from: stream next state: aState.
].
self writeVariableEnd: msg state: aState.
self fieldsDo: [:type :clazz |
type = #fixed
ifTrue: [
self writeFixed: msg with: clazz from: stream next state: aState.
] ifFalse: [
type_state = #initial ifTrue: [
type_state := #fixedDone.
self writeFixedEnd: msg state: aState.
].
].
type = #variable
ifTrue: [
self writeVariable: msg with: clazz from: stream next state: aState.
] ifFalse: [
type_state = #fixedDone ifTrue: [
type_state := #variableDone.
self writeVariableEnd: msg state: aState.
].
].
"Check if we are compatible"
(clazz isCompatible: stream peek) ifTrue: [
type = #optional ifTrue: [