1: ================================================================================
  2: 
  3: Smalltalk defineClass: #SynapseNeuron
  4:     superclass: #{Core.Object}
  5:     indexedType: #none
  6:     private: false
  7:     instanceVariableNames: 'neuronType connectorDictionary inputPortDictionary actionBlock '
  8:     classInstanceVariableNames: ''
  9:     imports: ''
 10:     category: ''
 11: 
 12: ================================================================================
 13: 
 14: SynapseNeuron method for 'operation'
 15: 
 16: action
 17: 
 18:     self actionBlock value: self necessityDictionary
 19:     "self necessityDictionary
 20:         ifNotNil: [:aCollection | self actionBlock value: aCollection]"
 21: 
 22: ------------------------------------------------------------
 23: 
 24: SynapseNeuron method for 'accessing'
 25: 
 26: actionBlock
 27: 
 28:     actionBlock
 29:         ifNil: [actionBlock := [:aCollection | self error: 'actionBlock is nil.']].
 30:     ^actionBlock
 31: 
 32: ------------------------------------------------------------
 33: 
 34: SynapseNeuron method for 'accessing'
 35: 
 36: actionBlock: aBlock
 37: 
 38:     actionBlock := aBlock
 39: 
 40: ------------------------------------------------------------
 41: 
 42: SynapseNeuron method for 'operation'
 43: 
 44: connect: fromPort toNeuron: aNeuron port: toPort
 45: 
 46:     | aConnector |
 47:     aConnector := self connectorDictionary at: fromPort
 48:                 ifAbsent: [self error: 'Undefined output port ''' , fromPort printString , '''.'].
 49:     aConnector registerNeuron: aNeuron port: toPort
 50: 
 51: ------------------------------------------------------------
 52: 
 53: SynapseNeuron method for 'accessing'
 54: 
 55: connectorDictionary
 56: 
 57:     connectorDictionary ifNil: [connectorDictionary := Dictionary new].
 58:     ^connectorDictionary
 59: 
 60: ------------------------------------------------------------
 61: 
 62: SynapseNeuron method for 'defaults'
 63: 
 64: defaultConnectorClass
 65: 
 66:     ^KSU.SynapseNeuralConnector
 67: 
 68: ------------------------------------------------------------
 69: 
 70: SynapseNeuron method for 'defaults'
 71: 
 72: defaultShellInterpreterClass
 73: 
 74:     ^KSU.ShellInterpreter
 75: 
 76: ------------------------------------------------------------
 77: 
 78: SynapseNeuron method for 'initialize-release'
 79: 
 80: file: arguments
 81: 
 82:     self
 83:         neuronType: #File;
 84:         registerInputPort: self class defaultInputPort;
 85:         registerOutputPort: self class defaultOutputPort;
 86:         actionBlock: 
 87:                 [:necessityDictionaryOrNil |
 88:                 | aFilename fileModeString fileMode |
 89:                 aFilename := Filename named: arguments first.
 90:                 arguments size < 2 ifTrue: [self error: 'Please specify the file mode.'].
 91:                 fileModeString := arguments at: 2.
 92:                 fileMode := self fileModeFrom: fileModeString.
 93:                 fileMode = #read
 94:                     ifTrue: 
 95:                         [| aString |
 96:                         aString := (aFilename withEncoding: self class defaultEncoding) readStream contents.
 97:                         self output: aString port: self class defaultOutputPort].
 98:                 ((fileMode = #write or: [fileMode = #append]) and: [necessityDictionaryOrNil isNil not])
 99:                     ifTrue: 
100:                         [| necessityDictionary aValue aString fileWithEncoding aStream |
101:                         necessityDictionary := necessityDictionaryOrNil.
102:                         aValue := necessityDictionary at: self class defaultInputPort.
103:                         aString := aValue isString ifTrue: [aValue] ifFalse: [aValue printString].
104:                         fileWithEncoding := aFilename withEncoding: self class defaultEncoding.
105:                         aStream := fileMode = #write
106:                                     ifTrue: [fileWithEncoding writeStream]
107:                                     ifFalse: [fileWithEncoding appendStream].
108:                         aStream
109:                             nextPutAll: aString;
110:                             close].
111:                 fileMode = #other ifTrue: [self error: 'Bad argument. file mode ''' , fileModeString , '''.']]
112: 
113: ------------------------------------------------------------
114: 
115: SynapseNeuron method for 'defaults'
116: 
117: fileModeFrom: fileModeString
118: 
119:     | aDictionary |
120:     aDictionary := (Dictionary new)
121:                 add: 'read' -> #read;
122:                 add: 'r' -> #read;
123:                 add: 'write' -> #write;
124:                 add: 'w' -> #write;
125:                 add: 'append' -> #append;
126:                 add: 'a' -> #append;
127:                 yourself.
128:     ^aDictionary at: fileModeString asLowercase ifAbsent: [#other]
129: 
130: ------------------------------------------------------------
131: 
132: SynapseNeuron method for 'initialize-release'
133: 
134: files: arguments
135: 
136:     self
137:         neuronType: #Files;
138:         actionBlock: [:necessityDictionaryOrNil | ]
139: 
140: ------------------------------------------------------------
141: 
142: SynapseNeuron method for 'initialize-release'
143: 
144: initialize
145: 
146:     neuronType := nil.
147:     connectorDictionary := nil.
148:     inputPortDictionary := nil.
149:     actionBlock := nil
150: 
151: ------------------------------------------------------------
152: 
153: SynapseNeuron method for 'operation'
154: 
155: input: aValue port: portSymbol
156: 
157:     | aQueue |
158:     aQueue := self inputPortDictionary at: portSymbol
159:                 ifAbsent: 
160:                     [self error: 'Undefined input port ''' , portSymbol printString , '''.'].
161:     aQueue add: aValue.
162:     self action
163: 
164: ------------------------------------------------------------
165: 
166: SynapseNeuron method for 'accessing'
167: 
168: inputPortDictionary
169: 
170:     inputPortDictionary ifNil: [inputPortDictionary := Dictionary new].
171:     ^inputPortDictionary
172: 
173: ------------------------------------------------------------
174: 
175: SynapseNeuron method for 'accessing'
176: 
177: inputPortSymbols
178: 
179:     | aCollection |
180:     aCollection := OrderedCollection new.
181:     self inputPortDictionary keysAndValuesDo: [:aSymbol :aQueue | aCollection add: aSymbol].
182:     ^aCollection
183: 
184: ------------------------------------------------------------
185: 
186: SynapseNeuron method for 'private - metrics'
187: 
188: inputSymbolsOf: pathToMetrics
189: 
190:     | aStream resultString inputSymbolStrings inputSymbols |
191:     aStream := (String new writeStream)
192:                 nextPutAll: 'cd "';
193:                 nextPutAll: (self class escapeDoubleQuote: pathToMetrics asString);
194:                 nextPutAll: '";';
195:                 nextPutAll: 'make inputs;';
196:                 yourself.
197:     resultString := self defaultShellInterpreterClass shellScript: aStream contents.
198:     inputSymbolStrings := self class separateBySpaces: resultString.
199:     inputSymbols := inputSymbolStrings collect: [:each | each asSymbol].
200:     ^inputSymbols
201: 
202: ------------------------------------------------------------
203: 
204: SynapseNeuron method for 'operation'
205: 
206: inputWithoutAction: aValue port: portSymbol
207: 
208:     | aQueue |
209:     aQueue := self inputPortDictionary at: portSymbol
210:                 ifAbsent: 
211:                     [self error: 'Undefined input port ''' , portSymbol printString , '''.'].
212:     aQueue add: aValue
213: 
214: ------------------------------------------------------------
215: 
216: SynapseNeuron method for 'testing'
217: 
218: isHeadNeuron
219: 
220:     ^#(#File #Files #Value #Values) includes: self neuronType
221: 
222: ------------------------------------------------------------
223: 
224: SynapseNeuron method for 'initialize-release'
225: 
226: metrics: arguments
227: 
228:     | pathToMetrics inputSymbols outputSymbols |
229:     pathToMetrics := Filename named: arguments first.
230:     pathToMetrics exists
231:         ifFalse: [self error: 'File ''' , pathToMetrics asString , ''' is not found.'].
232:     inputSymbols := self inputSymbolsOf: pathToMetrics.
233:     outputSymbols := self outputSymbolsOf: pathToMetrics.
234:     inputSymbols do: [:aSymbol | self registerInputPort: aSymbol].
235:     outputSymbols do: [:aSymbol | self registerOutputPort: aSymbol].
236:     self
237:         neuronType: #Metrics;
238:         actionBlock: 
239:                 [:necessityDictionaryOrNil |
240:                 necessityDictionaryOrNil
241:                     ifNotNil: 
242:                         [:necessityDictionary |
243:                         | aStream shellScript resultString outputDictionary |
244:                         aStream := (String new writeStream)
245:                                     nextPutAll: 'cd "';
246:                                     nextPutAll: (self class escapeDoubleQuote: pathToMetrics asString);
247:                                     nextPutAll: '";';
248:                                     nextPutAll: 'make ';
249:                                     yourself.
250:                         self inputPortSymbols do: 
251:                                 [:aSymbol |
252:                                 | valueString |
253:                                 valueString := necessityDictionary at: aSymbol
254:                                             ifAbsent: 
255:                                                 [| errorString |
256:                                                 errorString := (String new writeStream)
257:                                                             nextPutAll: 'Not found ''';
258:                                                             nextPutAll: aSymbol asString;
259:                                                             nextPutAll: ''' value in necessityDictionary.';
260:                                                             contents.
261:                                                 self error: errorString].
262:                                 aStream
263:                                     nextPutAll: aSymbol asString;
264:                                     nextPutAll: '="';
265:                                     nextPutAll: (self class encodeBase64: valueString);
266:                                     nextPutAll: '" '].
267:                         shellScript := aStream contents.
268:                         resultString := self defaultShellInterpreterClass shellScript: shellScript.
269:                         outputDictionary := self class parseJSONObjectAsDictionary: resultString.
270:                         self outputPortSymbols do: 
271:                                 [:aSymbol |
272:                                 | base64String valueString |
273:                                 base64String := outputDictionary at: aSymbol
274:                                             ifAbsent: 
275:                                                 [| errorString |
276:                                                 errorString := (String new writeStream)
277:                                                             nextPutAll: 'Not found ''';
278:                                                             nextPutAll: aSymbol asString;
279:                                                             nextPutAll: ''' value in metrics results.';
280:                                                             contents.
281:                                                 self error: errorString].
282:                                 valueString := self class decodeBase64: base64String.
283:                                 self output: valueString port: aSymbol]]]
284: 
285: ------------------------------------------------------------
286: 
287: SynapseNeuron method for 'accessing'
288: 
289: necessityDictionary
290: 
291:     | hasAllNecessities aDictionary |
292:     hasAllNecessities := true.
293:     self inputPortDictionary
294:         keysAndValuesDo: [:portSymbol :aQueue | aQueue size = 0 ifTrue: [hasAllNecessities := false]].
295:     hasAllNecessities ifFalse: [^nil].
296:     aDictionary := Dictionary new.
297:     self inputPortDictionary keysAndValuesDo: 
298:             [:portSymbol :aQueue |
299:             | aValue |
300:             aValue := aQueue removeFirst.
301:             aDictionary add: portSymbol -> aValue].
302:     ^aDictionary
303: 
304: ------------------------------------------------------------
305: 
306: SynapseNeuron method for 'accessing'
307: 
308: neuronType
309: 
310:     ^neuronType
311: 
312: ------------------------------------------------------------
313: 
314: SynapseNeuron method for 'accessing'
315: 
316: neuronType: typeSymbol
317: 
318:     neuronType := typeSymbol
319: 
320: ------------------------------------------------------------
321: 
322: SynapseNeuron method for 'operation'
323: 
324: output: aValue port: portSymbol
325: 
326:     | aConnector |
327:     aConnector := self connectorDictionary at: portSymbol
328:                 ifAbsent: [self error: 'Undefined output port ''' , portSymbol printString , '''.'].
329:     aConnector value: aValue
330: 
331: ------------------------------------------------------------
332: 
333: SynapseNeuron method for 'accessing'
334: 
335: outputPortSymbols
336: 
337:     | aCollection |
338:     aCollection := OrderedCollection new.
339:     self connectorDictionary keysAndValuesDo: [:aSymbol :aConnector | aCollection add: aSymbol].
340:     ^aCollection
341: 
342: ------------------------------------------------------------
343: 
344: SynapseNeuron method for 'private - metrics'
345: 
346: outputSymbolsOf: pathToMetrics
347: 
348:     | aStream resultString outputSymbolStrings outputSymbols |
349:     aStream := (String new writeStream)
350:                 nextPutAll: 'cd "';
351:                 nextPutAll: (self class escapeDoubleQuote: pathToMetrics asString);
352:                 nextPutAll: '";';
353:                 nextPutAll: 'make outputs;';
354:                 yourself.
355:     resultString := self defaultShellInterpreterClass shellScript: aStream contents.
356:     outputSymbolStrings := self class separateBySpaces: resultString.
357:     outputSymbols := outputSymbolStrings collect: [:each | each asSymbol].
358:     ^outputSymbols
359: 
360: ------------------------------------------------------------
361: 
362: SynapseNeuron method for 'printing'
363: 
364: printOn: aStream
365: 
366:     aStream
367:         nextPutAll: self class name;
368:         nextPutAll: '(';
369:         nextPutAll: self neuronType printString;
370:         nextPutAll: ')';
371:         yourself
372: 
373: ------------------------------------------------------------
374: 
375: SynapseNeuron method for 'operation'
376: 
377: registerInputPort: portSymbol
378: 
379:     | anAssociation |
380:     anAssociation := portSymbol -> OrderedCollection new.
381:     self inputPortDictionary add: anAssociation
382: 
383: ------------------------------------------------------------
384: 
385: SynapseNeuron method for 'operation'
386: 
387: registerOutputPort: portSymbol
388: 
389:     | anAssociation |
390:     anAssociation := portSymbol -> self defaultConnectorClass new.
391:     self connectorDictionary add: anAssociation
392: 
393: ------------------------------------------------------------
394: 
395: SynapseNeuron method for 'initialize-release'
396: 
397: transcript: arguments
398: 
399:     self
400:         neuronType: #Transcript;
401:         registerInputPort: self class defaultInputPort;
402:         actionBlock: 
403:                 [:necessityDictionaryOrNil |
404:                 necessityDictionaryOrNil
405:                     ifNotNil: 
406:                         [:necessityDictionary |
407:                         | aValue aString |
408:                         aValue := necessityDictionary at: self class defaultInputPort.
409:                         aString := aValue isString ifTrue: [aValue] ifFalse: [aValue printString].
410:                         Transcript
411:                             cr;
412:                             show: aString]]
413: 
414: ------------------------------------------------------------
415: 
416: SynapseNeuron method for 'initialize-release'
417: 
418: value: arguments
419: 
420:     self
421:         neuronType: #Value;
422:         registerOutputPort: self class defaultOutputPort;
423:         actionBlock: 
424:                 [:necessityDictionaryOrNil |
425:                 | aValue aString |
426:                 aValue := arguments first.
427:                 aString := aValue isString ifTrue: [aValue] ifFalse: [aValue printString].
428:                 self output: aString port: self class defaultOutputPort]
429: 
430: ------------------------------------------------------------
431: 
432: SynapseNeuron method for 'initialize-release'
433: 
434: values: arguments
435: 
436:     self
437:         neuronType: #Values;
438:         actionBlock: [:necessityDictionaryOrNil | ]
439: 
440: ================================================================================
441: 
442: Smalltalk.SynapseNeuron class
443:     instanceVariableNames: ''
444: 
445: ================================================================================
446: 
447: SynapseNeuron class method for 'utilities'
448: 
449: argumentsOf: constructorNode
450: 
451:     | arguments |
452:     arguments := OrderedCollection new.
453:     constructorNode allNodesDo: 
454:             [:aNode |
455:             (aNode isInnerNode and: [aNode symbol = self defaultArgumentNodeSymbol])
456:                 ifTrue: 
457:                     [| tokenString |
458:                     tokenString := aNode subNode token tokenString.
459:                     arguments add: (self parseString: tokenString)]].
460:     ^arguments
461: 
462: ------------------------------------------------------------
463: 
464: SynapseNeuron class method for 'utilities'
465: 
466: decodeBase64: aString
467: 
468:     | encodedString |
469:     encodedString := (aString withEncoding: #Base64) readStream contents.
470:     ^(encodedString withEncoding: self defaultEncoding) readStream contents
471: 
472: ------------------------------------------------------------
473: 
474: SynapseNeuron class method for 'defaults'
475: 
476: defaultArgumentNodeSymbol
477: 
478:     ^#Argument
479: 
480: ------------------------------------------------------------
481: 
482: SynapseNeuron class method for 'defaults'
483: 
484: defaultEncoding
485: 
486:     ^#UTF_8
487: 
488: ------------------------------------------------------------
489: 
490: SynapseNeuron class method for 'defaults'
491: 
492: defaultInputPort
493: 
494:     ^#input
495: 
496: ------------------------------------------------------------
497: 
498: SynapseNeuron class method for 'defaults'
499: 
500: defaultOutputPort
501: 
502:     ^#output
503: 
504: ------------------------------------------------------------
505: 
506: SynapseNeuron class method for 'utilities'
507: 
508: encodeBase64: aString
509: 
510:     | encodedString |
511:     encodedString := (aString withEncoding: #UTF_8) readStream contents asBase64String.
512:     ^encodedString reject: [:aCharacter | aCharacter isSeparator]
513: 
514: ------------------------------------------------------------
515: 
516: SynapseNeuron class method for 'utilities'
517: 
518: escapeDoubleQuote: aString
519: 
520:     | aStream |
521:     aStream := String new writeStream.
522:     aString do: 
523:             [:aCharacter |
524:             aCharacter = $" ifTrue: [aStream nextPut: $\].
525:             aStream nextPut: aCharacter].
526:     ^aStream contents
527: 
528: ------------------------------------------------------------
529: 
530: SynapseNeuron class method for 'utilities'
531: 
532: escapeForMakeMacro: aString
533:     "Maybe, this message is not used."
534: 
535:     | replacingDictionary aStream |
536:     replacingDictionary := (Dictionary new)
537:                 add: $\ -> '\\\\\\\\';
538:                 add: $" -> '\\\"';
539:                 add: $% -> '%%';
540:                 add: Character cr -> '\\\\r';
541:                 add: Character lf -> '\\\\n';
542:                 add: Character tab -> '\\\\t';
543:                 add: Character newPage -> '\\\\f';
544:                 add: Character backspace -> '\\\\b';
545:                 yourself.
546:     aStream := String new writeStream.
547:     aString do: 
548:             [:aCharacter |
549:             (replacingDictionary at: aCharacter ifAbsent: [nil])
550:                 ifNil: [aStream nextPut: aCharacter]
551:                 ifNotNil: [:replacingString | aStream nextPutAll: replacingString]].
552:     ^aStream contents
553: 
554: ------------------------------------------------------------
555: 
556: SynapseNeuron class method for 'examples'
557: 
558: example1
559:     "KSU.SynapseNeuron example1."
560: 
561:     ^SynapseNeuron
562:         parseJSONObjectAsDictionary: '{
563: "京都府" : "京都市",
564: "大阪府" : "大阪市",
565: "北海道" : "札幌市",
566: "青森県" : "青森市"
567: }'
568: 
569: ------------------------------------------------------------
570: 
571: SynapseNeuron class method for 'instance creation'
572: 
573: fromConstructorNode: constructorNode
574: 
575:     | neuronName arguments neuralStemCell aSelector |
576:     neuronName := self neuronNameOf: constructorNode.
577:     arguments := self argumentsOf: constructorNode.
578:     aSelector := self selectorDictionary at: neuronName
579:                 ifAbsent: [self error: 'Unexpected Constructor ''' , neuronName , '''.'].
580:     neuralStemCell := self new.
581:     (MessageSend
582:         receiver: neuralStemCell
583:         selector: aSelector
584:         arguments: (Array with: arguments)) evaluate.
585:     ^neuralStemCell
586: 
587: ------------------------------------------------------------
588: 
589: SynapseNeuron class method for 'utilities'
590: 
591: neuronNameOf: constructorNode
592: 
593:     | constructorNameNode idNode |
594:     constructorNameNode := constructorNode subNodes first.
595:     idNode := constructorNameNode subNode.
596:     ^idNode token tokenString
597: 
598: ------------------------------------------------------------
599: 
600: SynapseNeuron class method for 'instance creation'
601: 
602: new
603: 
604:     ^(super new)
605:         initialize;
606:         yourself
607: 
608: ------------------------------------------------------------
609: 
610: SynapseNeuron class method for 'utilities'
611: 
612: parseJSONObjectAsDictionary: aString
613: 
614:     | escapeDictionary stringBlock aDictionary key value currentStatus aStream |
615:     escapeDictionary := (Dictionary new)
616:                 add: $" -> $";
617:                 add: $\ -> $\;
618:                 add: $/ -> $/;
619:                 add: $b -> Character backspace;
620:                 add: $f -> Character newPage;
621:                 add: $n -> Character lf;
622:                 add: $r -> Character cr;
623:                 add: $t -> Character tab;
624:                 yourself.
625:     stringBlock :=
626:             [:readStream |
627:             | theString aBoolean |
628:             theString := String new writeStream.
629:             readStream next = $" ifFalse: [self error: 'Invalid string literal.'].
630:             aBoolean := true.
631:             [aBoolean] whileTrue: 
632:                     [| aCharacter |
633:                     aCharacter := readStream next.
634:                     aCharacter = $\
635:                         ifTrue: 
636:                             [| nextCharacter |
637:                             nextCharacter := readStream next.
638:                             (escapeDictionary keys includes: nextCharacter)
639:                                 ifTrue: [theString nextPut: (escapeDictionary at: nextCharacter)]
640:                                 ifFalse: [theString nextPut: nextCharacter]]
641:                         ifFalse: [aCharacter = $" ifTrue: [aBoolean := false] ifFalse: [theString nextPut: aCharacter]]].
642:             theString contents].
643:     aDictionary := Dictionary new.
644:     key := nil.
645:     value := nil.
646:     currentStatus := #initialStatus.
647:     aStream := aString readStream.
648:     [aStream atEnd] whileFalse: 
649:             [| nextStatus aCharacter |
650:             nextStatus := nil.
651:             aCharacter := aStream peek.
652:             aCharacter isSeparator
653:                 ifTrue: 
654:                     [aStream next.
655:                     nextStatus := currentStatus].
656:             (currentStatus = #initialStatus and: [aCharacter = ${])
657:                 ifTrue: 
658:                     [aStream next.
659:                     nextStatus := #startOfKey].
660:             ((currentStatus = #startOfKey or: [currentStatus = #startOfValue]) and: [aCharacter = $"])
661:                 ifTrue: 
662:                     [key
663:                         ifNil: 
664:                             [key := stringBlock value: aStream.
665:                             nextStatus := #endOfKey]
666:                         ifNotNil: 
667:                             [value := stringBlock value: aStream.
668:                             aDictionary add: key asSymbol -> value.
669:                             key := nil.
670:                             value := nil.
671:                             nextStatus := #endOfValue]].
672:             (currentStatus = #endOfKey and: [aCharacter = $:])
673:                 ifTrue: 
674:                     [aStream next.
675:                     nextStatus := #startOfValue].
676:             currentStatus = #endOfValue
677:                 ifTrue: 
678:                     [aStream next.
679:                     aCharacter = $} ifTrue: [nextStatus := #exitStatus].
680:                     aCharacter = $, ifTrue: [nextStatus := #startOfKey]].
681:             nextStatus
682:                 ifNil: 
683:                     [| errorStream |
684:                     errorStream := (String new writeStream)
685:                                 nextPutAll: 'Unexpected character ''';
686:                                 nextPut: aCharacter;
687:                                 nextPutAll: ''' on status ''';
688:                                 nextPutAll: currentStatus asString;
689:                                 nextPutAll: '''.';
690:                                 yourself.
691:                     self error: errorStream contents].
692:             currentStatus := nextStatus].
693:     aStream close.
694:     ^aDictionary
695: 
696: ------------------------------------------------------------
697: 
698: SynapseNeuron class method for 'utilities'
699: 
700: parseString: quotedString
701: 
702:     | readStream writeStream |
703:     readStream := (quotedString copyFrom: 2 to: quotedString size - 1) readStream.
704:     writeStream := String new writeStream.
705:     [readStream atEnd] whileFalse: 
706:             [| aCharacter |
707:             aCharacter := readStream next.
708:             writeStream nextPut: aCharacter.
709:             (aCharacter = $" and: [readStream peek = $"]) ifTrue: [readStream next]].
710:     readStream close.
711:     writeStream close.
712:     ^writeStream contents
713: 
714: ------------------------------------------------------------
715: 
716: SynapseNeuron class method for 'defaults'
717: 
718: selectorDictionary
719: 
720:     ^(Dictionary new)
721:         add: 'File' -> #file:;
722:         add: 'Files' -> #files:;
723:         add: 'Metrics' -> #metrics:;
724:         add: 'Transcript' -> #transcript:;
725:         add: 'Value' -> #value:;
726:         add: 'Values' -> #values:;
727:         yourself
728: 
729: ------------------------------------------------------------
730: 
731: SynapseNeuron class method for 'utilities'
732: 
733: separateBySpaces: aString
734: 
735:     | aCollection aBuffer |
736:     aCollection := OrderedCollection new.
737:     aBuffer := String new writeStream.
738:     aString do: 
739:             [:aCharacter |
740:             aCharacter isSeparator
741:                 ifTrue: 
742:                     [aBuffer isEmpty
743:                         ifFalse: 
744:                             [aCollection add: aBuffer contents.
745:                             aBuffer close.
746:                             aBuffer := String new writeStream]]
747:                 ifFalse: [aBuffer nextPut: aCharacter]].
748:     ^aCollection
749: 
750: ================================================================================

This document was generated by KSU.TextDoclet on 2013/02/22 at 01:01:17.