Fixes for Terminal code to work with new comma syntax.
[cslatevm.git] / src / lib / terminal.slate
blob7fb1943bdee1de71d39cdef0b8688a113e950f8b
2 prototypes ensureNamespace: #terminals &delegate: True.
4 terminals define: #Backend &parents: {PrettyPrinterMixin. Stream WrapperStream}.
5 "The device object/handle used for the terminal."
7 _@(Backend traits) defaultColumns [80].
8 _@(Backend traits) defaultRows [24].
10 _@(Backend traits) display: lineString cursorAt: index
11 "The basic method for line-oriented display and interaction."
12 [overrideThis].
14 b@(Backend traits) events
15 "Return a stream of events"
16 [overrideThis].
18 terminals define: #Terminal &parents: {Backend}
19   &slots: {#console "The underlying console object"}.
20 "The abstract terminal type."
21 Terminal addLazySlot: #commandEditor initializer: [| :t | t LineEditor newOn: t]. "A line editor instance on demand"
23 Terminal traits define: #KeyboardInterrupt &parents: {Condition}
24  &slots: {#terminal}.
26 c@(Terminal KeyboardInterrupt traits) newFor: t
28   c new `>> [terminal: t. ]
31 t@(Terminal traits) interrupted
32 [(t KeyboardInterrupt newFor: t) signal].
34 _@(Terminal traits) newBasedOn: console@(ExternalResource traits)
36   (DumbTerminal newOn: console interactor) `>> [
37     console: console.
38   ]
41 _@(Terminal traits) newBasedOn: console@(SmartConsole traits)
43   (SmartTerminal newOn: console interactor) `>> [
44     console: console.
45   ]
48 t@(Terminal traits) events [t console events].
50 t@(Terminal traits) sessionDo: block
52   t resource sessionDo: [| :r | block applyWith: t]
55 t@(Terminal traits) isSmart
56 "Answer whether all of certain cursor movement signals are defined."
57 [False].
59 t@(Terminal traits) echoes
60 [True].
62 t@(Terminal traits) columnLast
63 [t columns - 1].
65 t@(Terminal traits) columns
66 [t defaultColumns].
68 t@(Terminal traits) rowLast
69 [t rows - 1].
71 t@(Terminal traits) rows
72 [t defaultRows].
74 t@(Terminal traits) flush
75 [t console flush].
77 t@(Terminal traits) beep
78 "Send the beep/BEL character."
80   "TODO: on cygwin it doesn't work in raw mode, only prints ^G"
81   "Terminal traits define: #bell -> ({$\a code} as: ByteArray).
82   t console write: 1 from: t bell."
83   t flush.
86 t@(Terminal traits) page
87 "Display a simple header and page-down; exit if Q is pressed."
88 [| chord |
89   t writer ; '--More--'.
90   t flush.
91   chord: t nextChord.
92   t newLine.
93   (chord = $q \/ [chord = $Q]) not
96 t@(Terminal traits) newLine
97 "Terminate the current line."
98 [t nextPut: $\n].
100 t@(Terminal traits) newColumn
101 [t nextPut: $\s].
103 terminals define: #DumbTerminal &parents: {Terminal}.
104 "The simple terminal type, not even VT100."
106 t@(DumbTerminal traits) display: line cursorAt: index
108   "That's all we can do..."
111 terminals define: #SmartTerminal &parents: {Terminal}
112   &slots: {#basePosition -> Tuple new*, 0, 0 "The screen coordinate where line editing started"}.
113 "The terminal type that understands control- and escape-sequences for redraws, etc."
115 t@(SmartTerminal traits) isSmart
116 "Answer whether all of certain cursor movement signals are defined."
117 [True].
119 t@(SmartTerminal traits) echoes
120 [False].
122 t@(SmartTerminal traits) newLine
123 [| console |
124   console: t console.
125   console isCursorAtLastRow
126     ifTrue: [console scroll].
127   console moveCursorToBONL.
128   t
131 t@(SmartTerminal traits) columns
132 [t console columns].
134 t@(SmartTerminal traits) rows
135 [t console rows].
137 t@(SmartTerminal traits) display: cmd cursorAt: cursorPos &incremental: incremental
138 [| console scroll |
139   console: t console.
140   incremental ifNil: [incremental: False].
141   incremental ifFalse: [
142     console moveCursorTo: t basePosition. "TODO more then a page long lines (baseline < 0)"
143     t nextPutAll: cmd].
144   "Ideally basePosition update should be done with scroll callbacks. It does not handle
145   newlines in the command this way, and the console already keeps track of its state."
146   scroll: t basePosition second + ((t basePosition first + cmd size) // console width) - console rowLast.
147   scroll > 0 ifTrue: [t basePosition at: 1 put: t basePosition second - scroll].
148   incremental ifFalse: [console clearToEOS].
149   t moveCursorTo: cursorPos inCommand: cmd.
152 "TODO take control chars like \n's in cmd into account? generalize into SmartConsole"
153 t@(SmartTerminal traits) moveCursorTo: pos inCommand: cmd
154 [| cols |
155   cols: t columns.
156   pos: pos + t basePosition first.
157   t console moveCursorTo: (Tuple new*, (pos rem: cols), t basePosition second + (pos // cols)).
160 terminals define: #ConsoleLineEditor &parents: {Cloneable} &slots:
161  {#terminal.
162   #position -> 0. "Cursor position"
163   #currentHistoryIndex -> 0.
164   #killRing -> LinkedList new.
165   #insertMode -> True.
166   #mark.
167   #currentYank.
168   #lastYank.
169   #prompt -> Nil.
170   #currentWord -> Nil.
171   #currentCompletions -> {}.
172   #history -> ({ExtensibleArray new} as: ExtensibleArray new)}.
173 "A line editor, used to manage some terminal interactions, and having editing
174 state and behavior."
175 ConsoleLineEditor addLazySlot: #reader initializer: [| :e | e ReadStream newOn: e].
176 ConsoleLineEditor traits `>> [
177   define: #keymap &builder: [Dictionary new].
178   define: #controlKeymap &builder: [Dictionary new].
179   define: #modifierKeymap &builder: [Dictionary new].
180   define: #maxHistorySize -> 50.
183 e@(ConsoleLineEditor traits) newOn: terminal
185   e clone `>> [
186     history: [ExtensibleArray new `>> [addFirst: ExtensibleArray new. ]] do.
187     on: terminal.
188   ]
191 e@(ConsoleLineEditor traits) on: terminal
193   e terminal: terminal.
194   e
197 e@(ConsoleLineEditor traits) lineString
199   e history at: e currentHistoryIndex
202 e@(ConsoleLineEditor traits) prepareToEditLine
203 "Take the current history item, duplicate it, and addFirst:
204 to edit a copy rather then the item in the history."
206   e currentHistoryIndex > 0 ifTrue: [| current |
207     current: (e history at: e currentHistoryIndex).
208     e history first size = 0 ifTrue: [e history removeFirst].
209     e history addFirst: (ExtensibleArray newWithAll: current).
210     [e history size > e maxHistorySize]
211       whileTrue: [e history removeLast].
212     e currentHistoryIndex: 0].
215 e@(ConsoleLineEditor traits) markCursorAsBasePosition
217   e terminal basePosition: e terminal console cursorPosition
220 e@(ConsoleLineEditor traits) readLine &echoNewLine: echoNewLine &showPrompt: prompt
222   prompt ifNil: [prompt: True].
223   e history first size > 0
224     ifTrue: [
225       e history at: 0 infect: [| :value | value as: String].
226       e history addFirst: ExtensibleArray new.
227       [e history size > e maxHistorySize]
228         whileTrue: [e history removeLast]].
229   e currentHistoryIndex: 0.
230   e position: 0.
231   prompt /\ [e prompt isNotNil] ifTrue: [e terminal ; e prompt].
232   e markCursorAsBasePosition.
233   e redrawLine.
234   e continue &echoNewLine: echoNewLine
237 e@(ConsoleLineEditor traits) moveCursorTo: pos
239   e position: pos.
240   e updateCursor.
243 e@(ConsoleLineEditor traits) hasInput
244 "Answer if the editor has events waiting to be processed"
246   e terminal events hasNext
249 e@(ConsoleLineEditor traits) continue &echoNewLine: echoNewLine
250 [| terminal |
251   echoNewLine ifNil: [echoNewLine: False].
252   terminal: e terminal.
253   terminal events do: [| :event |
254     [
255       (event is: SmartConsole KeyDownEvent) ifTrue: [
256         event keyName = #Enter ifTrue: [
257           echoNewLine ifTrue: [terminal newLine].
258           ^ (e lineString as: terminal collectionType)]].
259       (e processEvent: event) ifTrue: [e redrawLine].
260       terminal flush.
261     ] on: Terminal KeyboardInterrupt do: [| :_ | e clear]].
264 e@(ConsoleLineEditor traits) clear
266   e lineString clear.
267   e position: 0.
268   e redrawLine.
271 e@(ConsoleLineEditor traits) processEvent: event@(SmartConsole ResizeEvent traits)
273   True "Simply force a redraw"
276 e@(ConsoleLineEditor traits) processEvent: event
277 "Process the event and return True if redraw is needed"
278 [| skipRedraw keymap value |
279   skipRedraw: False.
281   "Choose value between keyName and char"
282   event keyName
283     ifNil: [event char ifNotNil: [value: event char]]
284     ifNotNil: [value: event keyName].
286   "Select keymap based on modifier keys"
287   event controlState
288     ifTrue: [keymap: e controlKeymap]
289     ifFalse: [event altState
290                ifTrue: [keymap: e modifierKeymap]
291                ifFalse: [keymap: e keymap]].
293   "Look for a mapping and execute handler if found"
294   keymap at: value
295     ifPresent: [| :handler |
296       handler edits ifTrue: [e prepareToEditLine].
297       skipRedraw: (e handle: handler)]
298     ifAbsent: [
299       event char ifNotNil: [
300         e prepareToEditLine.
301         skipRedraw: (e handle: (e AddCharacter newFor: event char))]].
303   skipRedraw = Nil \/ [skipRedraw = False]
306 e@(ConsoleLineEditor traits) redrawLine &incremental: incremental
307 "Re-run the display sequence for the current line."
309   e terminal display: e lineString cursorAt: e position &incremental: incremental
312 e@(ConsoleLineEditor traits) updateCursor
314   e terminal moveCursorTo: e position inCommand: e lineString
317 e@(ConsoleLineEditor traits) toggleInsert
318 "Toggle insert mode."
320   e insertMode: e insertMode not
323 e@(ConsoleLineEditor traits) wordStart &dynamic: dynamic
324 "Answer the position of the start of the nearest word (right under the cursor).
325 Dynamic means that if the cursor is already on the start of a word then it leaves that
326 word and goes one word back."
327 [| line pos |
328   line: e lineString.
329   pos: e position.
330   dynamic ifNil: [dynamic: False].
332   pos > line indexLast
333     ifTrue: [pos: line indexLast]
334     ifFalse: [dynamic ifTrue: [pos: pos - 1. pos < 0 ifTrue: [^ 0]]].
335   [pos > 0 /\
336     [(line at: pos) isDelimiter]]
337       whileTrue: [pos: pos - 1].
338   [pos >= 0 /\
339     [(line at: pos) isDelimiter not]]
340       whileTrue: [pos: pos - 1].
341   (line includesKey: pos + 1)
342     ifTrue: [pos + 1]
343     ifFalse: [pos]
346 e@(ConsoleLineEditor traits) wordEnd &dynamic: dynamic
347 "Answer the position of the end of the nearest word (right under the cursor).
348 Dynamic means that if the cursor is already on the end of a word then it leaves that
349 word and goes one word forward."
350 [| line size pos |
351   line: e lineString.
352   pos: e position.
353   size: line size.
354   dynamic ifNil: [dynamic: False].
356   pos > line indexLast
357     ifTrue: [pos: line indexLast]
358     ifFalse: [dynamic ifTrue: [pos: pos + 1. pos >= size ifTrue: [^ size]]].
359   (line at: pos) isDelimiter ifTrue: [^ pos].
360   [pos < line indexLast /\
361     [(line at: pos) isDelimiter]]
362       whileTrue: [pos: pos + 1].
363   [pos < size /\
364     [(line at: pos) isDelimiter not]]
365       whileTrue: [pos: pos + 1].
366   pos
369 e@(ConsoleLineEditor traits) word
370 "Answer the word under the cursor, relying on wordStart and wordEnd."
372   e lineString copyFrom: e wordStart to: e wordEnd - 1
375 e@(ConsoleLineEditor traits) completionsFor: word
376 "Answer the completions for the given word."
377 [overrideThis].
379 e@(ConsoleLineEditor traits) flushCompletions
380 [e currentCompletions: e currentCompletions new].
382 e@(ConsoleLineEditor traits) complete: word
383 "Answer a collection of the valid completions for a given word; this should
384 allow for varying strategies per context."
386   word = e currentWord
387     ifTrue: [e currentCompletions isEmpty
388               ifTrue: [e currentCompletions: (e completionsFor: word)]]
389     ifFalse: [e currentWord: word.
390               e currentCompletions: (e completionsFor: word)].
391   e currentCompletions
394 e@(ConsoleLineEditor traits) complete
395 "Answer a collection of valid completions for the word under the cursor."
397   e complete: e word
400 e@(ConsoleLineEditor traits) rememberYank
402   e currentYank: e position
405 e@(ConsoleLineEditor traits) forgetYank
407   e lastYank: e yank.
408   e currentYank: Nil
411 e@(ConsoleLineEditor traits) tryYank
413   e currentYank: e lastYank
416 e@(ConsoleLineEditor traits) yank
418   e rememberYank.
419   e killRing next
420     ifNil: [e terminal beep. e position]
421     ifNotNilDo:
422       [| :kill |
423        e lineString: (e lineString copyFrom: 0 to: e currentYank)
424          ; kill ; (e lineString copyFrom: e position).
425        e position: e currentYank + kill size]
428 e@(ConsoleLineEditor traits) replaceWordWith: word
429 "Replace the word under the cursor with the given word.
430 Move cursor to end of the new word."
431 [| start end |
432   start: e wordStart.
433   end: e wordEnd.
434   end >= start ifTrue: [e lineString at: start remove: end - start].
435   e lineString at: start insertAll: word.
436   e position: start.
437   e position: e wordEnd.
440 e@(ConsoleLineEditor traits) isCursorInQuotedString
441 "A simple test to see if the cursor is between quotes."
442 [| start |
443   start: e wordStart.
444   start isNotNil
445     /\ [start isPositive]
446     /\ [(e lineString at: start - 1) isQuote]
449 "Commands"
450 "TODO: refactor to re-use the UI Command abstraction?"
452 ConsoleLineEditor define: #Command &parents: {Cloneable}
453   &slots: {#edits -> False}.
455 e@(ConsoleLineEditor traits) handle: _@(ConsoleLineEditor Command traits)
456 [overrideThis].
458 e@(ConsoleLineEditor traits) addCommand: name
459 "Defines and returns a new attribute-named command object, with no slots.
460 If one already exists, this re-uses it and ensures the slot properties."
461 [| command |
462   command: ((e traits hasSlotNamed: name)
463    ifTrue: [e traits atSlotNamed: name]
464    ifFalse: [e Command clone]).
465   e traits addImmutableSlot: name valued: command.
466   command
469 e@(ConsoleLineEditor traits) addEditingCommand: name
470 [| result |
471   result: (e addCommand: name).
472   result edits: True.
473   result
476 ConsoleLineEditor define: #AddCharacter
477                   &parents: {ConsoleLineEditor Command} &slots:
478   {#char -> $\0. #edits -> True}.
480 c@(ConsoleLineEditor AddCharacter traits) newFor: char
481 [c clone `setting: #(char) to: {char}].
483 e@(ConsoleLineEditor traits) handle: c@(ConsoleLineEditor AddCharacter traits)
484 [| result |
485   e insertMode 
486     ifTrue: [e lineString at: e position insert: c char]
487     ifFalse: [
488       e position = e lineString size
489         ifTrue: [e lineString addLast: c char]
490         ifFalse: [e lineString at: e position put: c char]].
491   e position: e position + 1.
492   e position = e lineString size /\ [e terminal console autoScrollsAtBottom]
493     ifTrue: [e terminal nextPut: c char.
494              e redrawLine &incremental: True. ^ True].
497 e@(ConsoleLineEditor traits)
498   handle: _@(ConsoleLineEditor addEditingCommand: #DeleteCharBackwards)
500   e position = 0 ifTrue: [^ True].
501   e position: e position - 1.
502   e lineString removeAt: e position.
505 e@(ConsoleLineEditor traits)
506   handle: _@(ConsoleLineEditor addEditingCommand: #DeleteCharForwards)
508   e position >= e lineString size ifTrue: [^ True].
509   e lineString removeAt: e position.
512 e@(ConsoleLineEditor traits)
513   handle: _@(ConsoleLineEditor addCommand: #EOF)
515   e lineString isEmpty
516     ifTrue: [e reader exhausted]
517     ifFalse: [e terminal beep].
520 e@(ConsoleLineEditor traits)
521   handle: _@(ConsoleLineEditor addCommand: #KeyboardInterrupt)
523   e terminal interrupted.
526 e@(ConsoleLineEditor traits)
527   handle: _@(ConsoleLineEditor addEditingCommand: #DeleteWordBackwards)
528 [| start |
529   start: e wordStart.
530   start > 0 ifTrue: [start: start - 1].
531   e lineString at: start remove: e position - start.
532   e position: start.
535 e@(ConsoleLineEditor traits)
536   handle: _@(ConsoleLineEditor addEditingCommand: #DeleteWordForwards)
537 [| end |
538   end: e wordEnd.
539   end < e lineString size ifTrue: [end: end + 1].
540   e lineString at: e position remove: end - e position.
543 e@(ConsoleLineEditor traits)
544   handle: _@(ConsoleLineEditor addEditingCommand: #UpcaseWord)
545 [| end |
546   end: e wordEnd.
547   (e lineString sliceFrom: e position below: end)
548     infect: [| :char | char toUppercase].
549   e position: end.
552 e@(ConsoleLineEditor traits)
553   handle: _@(ConsoleLineEditor addEditingCommand: #DowncaseWord)
554 [| end |
555   end: e wordEnd.
556   (e lineString sliceFrom: e position below: end)
557     infect: [| :char | char toLowercase].
558   e position: end.
561 e@(ConsoleLineEditor traits)
562   handle: _@(ConsoleLineEditor addCommand: #CursorToBOL)
564   e moveCursorTo: 0.
565   True
568 e@(ConsoleLineEditor traits)
569   handle: _@(ConsoleLineEditor addCommand: #CursorToEOL)
571   e moveCursorTo: e lineString size.
572   True
575 e@(ConsoleLineEditor traits)
576   handle: _@(ConsoleLineEditor addCommand: #CursorCharForwards)
578   e position < e lineString size ifTrue: [
579     e moveCursorTo: e position + 1.
580   ].
581   True
584 e@(ConsoleLineEditor traits)
585   handle: _@(ConsoleLineEditor addCommand: #CursorCharBackwards)
587   e position > 0 ifTrue: [
588     e moveCursorTo: e position - 1.
589   ].
590   True
593 e@(ConsoleLineEditor traits)
594   handle: _@(ConsoleLineEditor addCommand: #CursorWordForwards)
596   e moveCursorTo: e wordEnd.
597   True
600 e@(ConsoleLineEditor traits)
601   handle: _@(ConsoleLineEditor addCommand: #CursorWordBackwards)
603   e moveCursorTo: (e wordStart &dynamic: True).
604   True
607 e@(ConsoleLineEditor traits)
608   handle: _@(ConsoleLineEditor addCommand: #Undo)
609 [e rewindState]. "FIX"
611 e@(ConsoleLineEditor traits)
612   handle: _@(ConsoleLineEditor addCommand: #ToggleInsert)
613 [e toggleInsert].
615 e@(ConsoleLineEditor traits)
616   handle: _@(ConsoleLineEditor addCommand: #HistoryPrevious)
618   e currentHistoryIndex < e history indexLast
619     ifTrue: [e currentHistoryIndex: e currentHistoryIndex + 1.
620       e position: e lineString size]
621     ifFalse: [e terminal beep. ^ True].
624 e@(ConsoleLineEditor traits)
625   handle: _@(ConsoleLineEditor addCommand: #HistoryNext)
627   e currentHistoryIndex > 0
628     ifTrue: [e currentHistoryIndex: e currentHistoryIndex - 1.
629       e position: e lineString size]
630     ifFalse: [e terminal beep. ^ True].
633 e@(ConsoleLineEditor traits)
634   handle: _@(ConsoleLineEditor addEditingCommand: #KillToEOL)
636   e killRing addLast: (e lineString copyFrom: e position).
637   e lineString: (e lineString copyFrom: 0 to: e position).
640 e@(ConsoleLineEditor traits)
641   handle: _@(ConsoleLineEditor addEditingCommand: #KillToBOL)
643   e killRing addLast: (e lineString copyFrom: 0 to: e position).
644   e lineString: (e lineString copyFrom: e position).
647 e@(ConsoleLineEditor traits) handle: _@(ConsoleLineEditor addCommand: #Yank)
649   e tryYank
652 e@(ConsoleLineEditor traits)
653   handle: _@(ConsoleLineEditor addEditingCommand: #CopyRegion)
654 [| start end |
655   e mark ifNil: [^ e position].
656   start: (e mark min: e position).
657   end: (e mark max: e position).
658   e killRing addLast: (e lineString copyFrom: start to: end).
659   e mark: Nil.
660   e position
663 e@(ConsoleLineEditor traits)
664   handle: _@(ConsoleLineEditor addEditingCommand: #CutRegion)
665 [| start end |
666   e mark ifNil: [^ e position].
667   start: (e mark min: e position).
668   end: (e mark max: e position).
669   e killRing addLast: (e lineString copyFrom: start to: end).
670   e mark: Nil.
671   e lineString: (e lineString copyFrom: 0 to: start)
672     ; (e lineString copyFrom: end).
673   e position: start
676 e@(ConsoleLineEditor traits) handle: _@(ConsoleLineEditor addCommand: #SetMark)
678   e mark: e position.
681 e@(ConsoleLineEditor traits) handle: _@(ConsoleLineEditor addCommand: #Help)
685 e@(ConsoleLineEditor traits)
686   handle: _@(ConsoleLineEditor addEditingCommand: #Complete)
687 [| completions |
688   completions: e complete.
689   completions isEmpty ifTrue: [e terminal beep. ^ Nil].
690   completions size = 1 ifTrue: [^ (e replaceWordWith: completions first)].
691   e printInColumns: completions.
692   e terminal newLine.
693   e prompt ifNotNil: [e terminal ; e prompt].
694   e markCursorAsBasePosition.
695   e redrawLine.
698 e@(ConsoleLineEditor traits) printInColumns: col
699 "TODO: Oly prints one column for now.
700 Could reuse some UI layouting algorithm"
701 [| term |
702   term: e terminal.
703   term newLine.
704   col
705     do: [| :each | term ; '  ' ; each]
706     separatedBy: [e terminal newLine].
710  $a -> ConsoleLineEditor CursorToBOL.
711  $b -> ConsoleLineEditor CursorCharBackwards.
712  $d -> ConsoleLineEditor EOF.
713  $e -> ConsoleLineEditor CursorToEOL.
714  $f -> ConsoleLineEditor CursorCharForwards.
715  $k -> ConsoleLineEditor KillToEOL.
716  $n -> ConsoleLineEditor HistoryNext.
717  $p -> ConsoleLineEditor HistoryPrevious.
718  $u -> ConsoleLineEditor CutRegion.
719  $y -> ConsoleLineEditor Yank.
720  $c -> ConsoleLineEditor KeyboardInterrupt.
721  $- -> ConsoleLineEditor Undo.
722  #Backspace -> ConsoleLineEditor DeleteWordBackwards.
723  #Delete -> ConsoleLineEditor DeleteWordForwards.
724  "Ctrl+Space can't be detected with ncurses (or with unix terminals in general?)"
725  #Space     -> ConsoleLineEditor SetMark.
726 } do: [| :assoc | ConsoleLineEditor controlKeymap add: assoc].
729  $b -> ConsoleLineEditor CursorWordBackwards.
730  $f -> ConsoleLineEditor CursorWordForwards.
731  $l -> ConsoleLineEditor DowncaseWord.
732  $u -> ConsoleLineEditor UpcaseWord.
733  $w -> ConsoleLineEditor CopyRegion.
734 } do: [| :assoc | ConsoleLineEditor modifierKeymap add: assoc].
737  #Tab         -> ConsoleLineEditor Complete.
738  #Backspace   -> ConsoleLineEditor DeleteCharBackwards.
739 "It must be special-cased because we can't easily return from a non-toplevel method"
740 "#Return      -> ConsoleLineEditor FinishInput."
741  #UpArrow     -> ConsoleLineEditor HistoryPrevious.
742  #DownArrow   -> ConsoleLineEditor HistoryNext.
743  #RightArrow  -> ConsoleLineEditor CursorCharForwards.
744  #LeftArrow   -> ConsoleLineEditor CursorCharBackwards.
745  #Insert      -> ConsoleLineEditor ToggleInsert.
746  #Delete      -> ConsoleLineEditor DeleteCharForwards.
747  #Home        -> ConsoleLineEditor CursorToBOL.
748  #End         -> ConsoleLineEditor CursorToEOL
749 } do: [| :assoc | ConsoleLineEditor keymap add: assoc].
751 ConsoleLineEditor traits define: #ReadStream &parents: {ReadStream}
752   &slots: {#editor. #line. #position. #closed -> False}.
754 s@(ConsoleLineEditor ReadStream traits) on: editor
756   s editor: editor.
757   s
760 s@(ConsoleLineEditor ReadStream traits) isAtEnd [s closed].
761 s@(ConsoleLineEditor ReadStream traits) elementType [s terminal elementType].
762 s@(ConsoleLineEditor ReadStream traits) collectionType [s terminal collectionType].
764 s@(ConsoleLineEditor ReadStream traits) next
765 [| result |
766   [s line isNil \/ [s line isEmpty]]
767     whileTrue: [
768       s line: (s editor readLine &echoNewLine: True).
769       s line ifNil: [
770         s closed: True.
771         s exhausted.
772         ^ Nil].
773       s line: (s line ; '\n').
774       s position: 0].
775   result: (s line at: s position).
776   s position: s position + 1.
777   s position = s line size ifTrue:
778     [s line: Nil].
779   result
782 "This is the default LineEditor that can be overridden by
783 adding a slot to terminal instances."
784 SmartTerminal traits define: #LineEditor -> ConsoleLineEditor.