Updated release image date.
[cslatevm.git] / src / lib / terminal.slate
blob431e64f4d1000dd8eb4dac73018c98739663da6e
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."
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
124   (console ::= t console) isCursorAtLastRow ifTrue:
125     [console scroll].
126   console moveCursorToBONL.
127   t
130 t@(SmartTerminal traits) columns
131 [t console columns].
133 t@(SmartTerminal traits) rows
134 [t console rows].
136 t@(SmartTerminal traits) display: cmd cursorAt: cursorPos &incremental
138   console ::= t console.
139   (incremental `defaultsTo: False) ifFalse:
140     [console moveCursorTo: t basePosition.
141      "TODO more then a page long lines (baseline < 0)"
142      t nextPutAll: cmd].
143   "Ideally basePosition update should be done with scroll callbacks. It does not handle
144   newlines in the command this way, and the console already keeps track of its state."
145   (scroll ::= t basePosition second
146      + ((t basePosition first + cmd size) // console width)
147      - console rowLast) isPositive ifTrue:
148        [t basePosition at: 1 put: t basePosition second - scroll].
149   incremental ifFalse:
150     [console clearToEOS].
151   t moveCursorTo: cursorPos inCommand: cmd.
154 "TODO take control chars like \n's in cmd into account? generalize into SmartConsole"
155 t@(SmartTerminal traits) moveCursorTo: pos inCommand: cmd
157   cols ::= t columns.
158   pos += t basePosition first.
159   t console moveCursorTo: (Tuple new*, (pos rem: cols), t basePosition second + (pos // cols)).
162 terminals define: #ConsoleLineEditor &parents: {Cloneable} &slots: {
163   #terminal.
164   #position -> 0. "Cursor position"
165   #currentHistoryIndex -> 0.
166   #killRing -> LinkedList new.
167   #insertMode -> True.
168   #mark.
169   #currentYank.
170   #lastYank.
171   #prompt -> Nil.
172   #currentWord -> Nil.
173   #currentCompletions -> {}.
174   #history -> ({ExtensibleArray new} as: ExtensibleArray new)
176 "A line editor, used to manage some terminal interactions, and having editing
177 state and behavior."
178 ConsoleLineEditor addLazySlot: #reader initializer: [| :e | e ReadStream newOn: e].
179 ConsoleLineEditor traits keymap ::= Dictionary new.
180 ConsoleLineEditor traits controlKeymap ::= Dictionary new.
181 ConsoleLineEditor traits modifierKeymap ::= Dictionary new.
182 ConsoleLineEditor traits maxHistorySize ::= 50.
184 e@(ConsoleLineEditor traits) newOn: terminal
186   e clone `>>
187     [history := ExtensibleArray new*, (ExtensibleArray new).
188      on: terminal. ]
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) lineString: line
204   e history at: e currentHistoryIndex put: line
207 e@(ConsoleLineEditor traits) prepareToEditLine
208 "Take the current history item, duplicate it, and addFirst:
209 to edit a copy rather then the item in the history."
210 [| current |
211   e currentHistoryIndex isPositive ifTrue:
212     [current := e history at: e currentHistoryIndex.
213      e history first isEmpty ifTrue:
214        [e history removeFirst].
215      e history addFirst: (ExtensibleArray newWithAll: current).
216     [e history size > e maxHistorySize] whileTrue:
217       [e history removeLast].
218     e currentHistoryIndex := 0].
221 e@(ConsoleLineEditor traits) markCursorAsBasePosition
223   e terminal basePosition := e terminal console cursorPosition
226 e@(ConsoleLineEditor traits) readLine &echoNewLine &showPrompt: prompt
228   prompt `defaultsTo: True.
229   e history first isEmpty ifFalse:
230     [e history at: 0 infect: #(as: String) `er.
231      e history addFirst: ExtensibleArray new.
232      [e history size > e maxHistorySize]
233        whileTrue: [e history removeLast]].
234   e currentHistoryIndex := 0.
235   e position := 0.
236   prompt /\ [e prompt isNotNil] ifTrue: [e terminal ; e prompt].
237   e markCursorAsBasePosition.
238   e redrawLine.
239   e continue &echoNewLine
242 e@(ConsoleLineEditor traits) moveCursorTo: pos
244   e position := pos.
245   e updateCursor.
248 e@(ConsoleLineEditor traits) hasInput
249 "Answer if the editor has events waiting to be processed"
251   e terminal events hasNext
254 e@(ConsoleLineEditor traits) continue &echoNewLine
256   echoNewLine `defaultsTo: False.
257   (terminal ::= e terminal) events do:
258     [| :event |
259      [(event is: SmartConsole KeyDownEvent) ifTrue:
260         [event keyName = #Enter ifTrue:
261            [echoNewLine ifTrue: [terminal newLine].
262             ^ (e lineString as: terminal collectionType)]].
263       (e processEvent: event) ifTrue: [e redrawLine].
264       terminal flush]
265        on: Terminal KeyboardInterrupt do: [| :_ | e clear]].
268 e@(ConsoleLineEditor traits) clear
270   e lineString clear.
271   e position := 0.
272   e redrawLine.
275 e@(ConsoleLineEditor traits) processEvent: event@(SmartConsole ResizeEvent traits)
277   True "Simply force a redraw"
280 e@(ConsoleLineEditor traits) processEvent: event
281 "Process the event and return True if redraw is needed"
282 [| skipRedraw value |
283   skipRedraw := False.
285   "Choose value between keyName and char"
286   event keyName
287     ifNil: [event char ifNotNil: [value := event char]]
288     ifNotNil: [value := event keyName].
290   "Select keymap based on modifier keys"
291   keymap ::= event controlState
292     ifTrue: [e controlKeymap]
293     ifFalse:
294       [event altState
295          ifTrue: [e modifierKeymap]
296          ifFalse: [e keymap]].
298   "Look for a mapping and execute handler if found"
299   keymap at: value
300     ifPresent: [| :handler |
301       handler edits ifTrue: [e prepareToEditLine].
302       skipRedraw := e handle: handler]
303     ifAbsent:
304       [event char ifNotNil:
305          [e prepareToEditLine.
306           skipRedraw := e handle: (e AddCharacter newFor: event char)]].
308   skipRedraw isNil \/ [skipRedraw not]
311 e@(ConsoleLineEditor traits) redrawLine &incremental
312 "Re-run the display sequence for the current line."
314   e terminal display: e lineString cursorAt: e position &incremental: incremental
317 e@(ConsoleLineEditor traits) updateCursor
319   e terminal moveCursorTo: e position inCommand: e lineString
322 e@(ConsoleLineEditor traits) toggleInsert
323 "Toggle insert mode."
325   e insertMode := e insertMode not
328 e@(ConsoleLineEditor traits) wordStart &dynamic
329 "Answer the position of the start of the nearest word (right under the cursor).
330 Dynamic means that if the cursor is already on the start of a word then it leaves that
331 word and goes one word back."
332 [| pos |
333   line ::= e lineString.
334   pos := e position.
335   dynamic `defaultsTo: False.
337   pos > line indexLast
338     ifTrue: [pos := line indexLast]
339     ifFalse: [dynamic ifTrue: [pos -= 1. pos isNegative ifTrue: [^ 0]]].
340   [pos isPositive /\
341     [(line at: pos) isDelimiter]]
342       whileTrue: [pos -= 1].
343   [pos >= 0 /\
344     [(line at: pos) isDelimiter not]]
345       whileTrue: [pos -= 1].
346   (line includesKey: pos + 1)
347     ifTrue: [pos + 1]
348     ifFalse: [pos]
351 e@(ConsoleLineEditor traits) wordEnd &dynamic
352 "Answer the position of the end of the nearest word (right under the cursor).
353 Dynamic means that if the cursor is already on the end of a word then it leaves that
354 word and goes one word forward."
355 [| pos |
356   line ::= e lineString.
357   size ::= line size.
358   pos := e position.
359   dynamic `defaultsTo: False.
361   pos > line indexLast
362     ifTrue: [pos := line indexLast]
363     ifFalse: [dynamic ifTrue: [pos += 1. pos >= size ifTrue: [^ size]]].
364   (line at: pos) isDelimiter ifTrue: [^ pos].
365   [pos < line indexLast /\
366     [(line at: pos) isDelimiter]]
367       whileTrue: [pos += 1].
368   [pos < size /\
369     [(line at: pos) isDelimiter not]]
370       whileTrue: [pos += 1].
371   pos
374 e@(ConsoleLineEditor traits) word
375 "Answer the word under the cursor, relying on wordStart and wordEnd."
377   e lineString copyFrom: e wordStart to: e wordEnd - 1
380 e@(ConsoleLineEditor traits) completionsFor: word
381 "Answer the completions for the given word."
382 [overrideThis].
384 e@(ConsoleLineEditor traits) flushCompletions
385 [e currentCompletions: e currentCompletions new].
387 e@(ConsoleLineEditor traits) complete: word
388 "Answer a collection of the valid completions for a given word; this should
389 allow for varying strategies per context."
391   word = e currentWord
392     ifTrue: [e currentCompletions isEmpty
393               ifTrue: [e currentCompletions := e completionsFor: word]]
394     ifFalse: [e currentWord := word.
395               e currentCompletions := e completionsFor: word].
396   e currentCompletions
399 e@(ConsoleLineEditor traits) complete
400 "Answer a collection of valid completions for the word under the cursor."
402   e complete: e word
405 e@(ConsoleLineEditor traits) rememberYank
407   e currentYank := e position
410 e@(ConsoleLineEditor traits) forgetYank
412   e lastYank := e yank.
413   e currentYank := Nil
416 e@(ConsoleLineEditor traits) tryYank
418   e currentYank := e lastYank
421 e@(ConsoleLineEditor traits) yank
423   e rememberYank.
424   e killRing next
425     ifNil: [e terminal beep. e position]
426     ifNotNilDo:
427       [| :kill |
428        e lineString := (e lineString copyFrom: 0 to: e currentYank)
429          ; kill ; (e lineString copyFrom: e position).
430        e position := e currentYank + kill size]
433 e@(ConsoleLineEditor traits) replaceWordWith: word
434 "Replace the word under the cursor with the given word.
435 Move cursor to end of the new word."
437   (start ::= e wordStart) <= (end ::= e wordEnd)
438     ifTrue: [e lineString at: start remove: end - start].
439   e lineString at: start insertAll: word.
440   e position := start.
441   e position := e wordEnd.
444 e@(ConsoleLineEditor traits) isCursorInQuotedString
445 "A simple test to see if the cursor is between quotes."
447   (start ::= e wordStart) isNotNil
448     /\ [start isPositive]
449     /\ [(e lineString at: start - 1) isQuote]
452 "Commands"
453 "TODO: refactor to re-use the UI Command abstraction?"
455 ConsoleLineEditor define: #Command &parents: {Cloneable}
456   &slots: {#edits -> False}.
458 e@(ConsoleLineEditor traits) handle: _@(ConsoleLineEditor Command traits)
459 [overrideThis].
461 e@(ConsoleLineEditor traits) addCommand: name
462 "Defines and returns a new attribute-named command object, with no slots.
463 If one already exists, this re-uses it and ensures the slot properties."
465   command ::= (e traits hasSlotNamed: name)
466    ifTrue: [e traits atSlotNamed: name]
467    ifFalse: [e Command clone].
468   e traits addImmutableSlot: name valued: command.
469   command
472 e@(ConsoleLineEditor traits) addEditingCommand: name
474   (e addCommand: name) `>> [edits := True. ]
477 ConsoleLineEditor define: #AddCharacter &parents: {ConsoleLineEditor Command} &slots: {
478   #char -> $\0.
479   #edits -> True
482 c@(ConsoleLineEditor AddCharacter traits) newFor: char
483 [c clone `setting: #{#char} to: {char}].
485 e@(ConsoleLineEditor traits) handle: c@(ConsoleLineEditor AddCharacter traits)
487   e insertMode 
488     ifTrue: [e lineString at: e position insert: c char]
489     ifFalse: [
490       e position = e lineString size
491         ifTrue: [e lineString addLast: c char]
492         ifFalse: [e lineString at: e position put: c char]].
493   (e position += 1) = e lineString size /\ [e terminal console autoScrollsAtBottom]
494     ifTrue: [e terminal nextPut: c char.
495              e redrawLine &incremental: True. ^ True].
498 e@(ConsoleLineEditor traits)
499   handle: _@(ConsoleLineEditor addEditingCommand: #DeleteCharBackwards)
501   e position isZero ifTrue: [^ True].
502   e position := e position - 1.
503   e lineString removeAt: e position.
506 e@(ConsoleLineEditor traits)
507   handle: _@(ConsoleLineEditor addEditingCommand: #DeleteCharForwards)
509   e position >= e lineString size ifTrue: [^ True].
510   e lineString removeAt: e position.
513 e@(ConsoleLineEditor traits)
514   handle: _@(ConsoleLineEditor addCommand: #EOF)
516   e lineString isEmpty
517     ifTrue: [e reader exhausted]
518     ifFalse: [e terminal beep].
521 e@(ConsoleLineEditor traits)
522   handle: _@(ConsoleLineEditor addCommand: #KeyboardInterrupt)
524   e terminal interrupted.
527 e@(ConsoleLineEditor traits)
528   handle: _@(ConsoleLineEditor addEditingCommand: #DeleteWordBackwards)
529 [| start |
530   (start := e wordStart) > 0 ifTrue:
531     [start -= 1].
532   e lineString at: start remove: e position - start.
533   e position := start.
536 e@(ConsoleLineEditor traits)
537   handle: _@(ConsoleLineEditor addEditingCommand: #DeleteWordForwards)
538 [| end |
539   (end := e wordEnd) < e lineString size ifTrue:
540     [end += 1].
541   e lineString at: e position remove: end - e position.
544 e@(ConsoleLineEditor traits)
545   handle: _@(ConsoleLineEditor addEditingCommand: #UpcaseWord)
547   end ::= e wordEnd.
548   (e lineString sliceFrom: e position below: end)
549     infect: #toUppercase `er.
550   e position := end.
553 e@(ConsoleLineEditor traits)
554   handle: _@(ConsoleLineEditor addEditingCommand: #DowncaseWord)
556   end ::= e wordEnd.
557   (e lineString sliceFrom: e position below: end)
558     infect: #toLowercase `er.
559   e position := end.
562 e@(ConsoleLineEditor traits)
563   handle: _@(ConsoleLineEditor addCommand: #CursorToBOL)
565   e moveCursorTo: 0.
566   True
569 e@(ConsoleLineEditor traits)
570   handle: _@(ConsoleLineEditor addCommand: #CursorToEOL)
572   e moveCursorTo: e lineString size.
573   True
576 e@(ConsoleLineEditor traits)
577   handle: _@(ConsoleLineEditor addCommand: #CursorCharForwards)
579   e position < e lineString size ifTrue: [
580     e moveCursorTo: e position + 1.
581   ].
582   True
585 e@(ConsoleLineEditor traits)
586   handle: _@(ConsoleLineEditor addCommand: #CursorCharBackwards)
588   e position isPositive ifTrue: [
589     e moveCursorTo: e position - 1.
590   ].
591   True
594 e@(ConsoleLineEditor traits)
595   handle: _@(ConsoleLineEditor addCommand: #CursorWordForwards)
597   e moveCursorTo: e wordEnd.
598   True
601 e@(ConsoleLineEditor traits)
602   handle: _@(ConsoleLineEditor addCommand: #CursorWordBackwards)
604   e moveCursorTo: (e wordStart &dynamic: True).
605   True
608 e@(ConsoleLineEditor traits)
609   handle: _@(ConsoleLineEditor addCommand: #Undo)
610 [e rewindState]. "FIX"
612 e@(ConsoleLineEditor traits)
613   handle: _@(ConsoleLineEditor addCommand: #ToggleInsert)
614 [e toggleInsert].
616 e@(ConsoleLineEditor traits)
617   handle: _@(ConsoleLineEditor addCommand: #HistoryPrevious)
619   e currentHistoryIndex < e history indexLast
620     ifTrue: [e currentHistoryIndex := e currentHistoryIndex + 1.
621       e position := e lineString size]
622     ifFalse: [e terminal beep. ^ True].
625 e@(ConsoleLineEditor traits)
626   handle: _@(ConsoleLineEditor addCommand: #HistoryNext)
628   e currentHistoryIndex > 0
629     ifTrue: [e currentHistoryIndex := e currentHistoryIndex - 1.
630       e position := e lineString size]
631     ifFalse: [e terminal beep. ^ True].
634 e@(ConsoleLineEditor traits)
635   handle: _@(ConsoleLineEditor addEditingCommand: #KillToEOL)
637   e killRing addLast: (e lineString copyFrom: e position).
638   e lineString := e lineString copyFrom: 0 to: e position.
641 e@(ConsoleLineEditor traits)
642   handle: _@(ConsoleLineEditor addEditingCommand: #KillToBOL)
644   e killRing addLast: (e lineString copyFrom: 0 to: e position).
645   e lineString := e lineString copyFrom: e position.
648 e@(ConsoleLineEditor traits) handle: _@(ConsoleLineEditor addCommand: #Yank)
650   e tryYank
653 e@(ConsoleLineEditor traits)
654   handle: _@(ConsoleLineEditor addEditingCommand: #CopyRegion)
656   e mark ifNotNil: [^ e position].
657   start ::= e mark min: e position.
658   end ::= e mark max: e position.
659   e killRing addLast: (e lineString copyFrom: start to: end).
660   e mark := Nil.
661   e position
664 e@(ConsoleLineEditor traits)
665   handle: _@(ConsoleLineEditor addEditingCommand: #CutRegion)
667   e mark ifNil: [^ e position].
668   start ::= e mark min: e position.
669   end ::= e mark max: e position.
670   e killRing addLast: (e lineString copyFrom: start to: end).
671   e mark := Nil.
672   e lineString := (e lineString copyFrom: 0 to: start)
673     ; (e lineString copyFrom: end).
674   e position := start
677 e@(ConsoleLineEditor traits) handle: _@(ConsoleLineEditor addCommand: #SetMark)
679   e mark := e position.
682 e@(ConsoleLineEditor traits) handle: _@(ConsoleLineEditor addCommand: #Help)
686 e@(ConsoleLineEditor traits)
687   handle: _@(ConsoleLineEditor addEditingCommand: #Complete)
689   (completions ::= e complete) size caseOf: {
690     0 -> [e terminal beep. ].
691     1 -> [e replaceWordWith: completions first]
692   } otherwise:
693     [e printInColumns: completions.
694      e terminal newLine.
695      e prompt ifNotNil: [e terminal ; e prompt].
696      e markCursorAsBasePosition.
697      e redrawLine. ]
700 e@(ConsoleLineEditor traits) printInColumns: col
701 "TODO: Oly prints one column for now.
702 Could reuse some UI layouting algorithm"
704   (term ::= e terminal) newLine.
705   col
706     do: [| :each | term ; '  ' ; each]
707     separatedBy: [e terminal newLine].
710 [| :assoc | ConsoleLineEditor controlKeymap add: assoc] for: {
711   $a -> ConsoleLineEditor CursorToBOL.
712   $b -> ConsoleLineEditor CursorCharBackwards.
713   $d -> ConsoleLineEditor EOF.
714   $e -> ConsoleLineEditor CursorToEOL.
715   $f -> ConsoleLineEditor CursorCharForwards.
716   $k -> ConsoleLineEditor KillToEOL.
717   $n -> ConsoleLineEditor HistoryNext.
718   $p -> ConsoleLineEditor HistoryPrevious.
719   $u -> ConsoleLineEditor CutRegion.
720   $y -> ConsoleLineEditor Yank.
721   $c -> ConsoleLineEditor KeyboardInterrupt.
722   $- -> ConsoleLineEditor Undo.
723   #Backspace -> ConsoleLineEditor DeleteWordBackwards.
724   #Delete -> ConsoleLineEditor DeleteWordForwards.
725   "Ctrl+Space can't be detected with ncurses (or with unix terminals in general?)"
726   #Space     -> ConsoleLineEditor SetMark.
729 [| :assoc | ConsoleLineEditor modifierKeymap add: assoc] for: {
730   $b -> ConsoleLineEditor CursorWordBackwards.
731   $f -> ConsoleLineEditor CursorWordForwards.
732   $l -> ConsoleLineEditor DowncaseWord.
733   $u -> ConsoleLineEditor UpcaseWord.
734   $w -> ConsoleLineEditor CopyRegion.
737 [| :assoc | ConsoleLineEditor keymap add: assoc] for: {
738   #Tab         -> ConsoleLineEditor Complete.
739   #Backspace   -> ConsoleLineEditor DeleteCharBackwards.
740   "It must be special-cased because we can't easily return from a non-toplevel method"
741   "#Return      -> ConsoleLineEditor FinishInput."
742   #UpArrow     -> ConsoleLineEditor HistoryPrevious.
743   #DownArrow   -> ConsoleLineEditor HistoryNext.
744   #RightArrow  -> ConsoleLineEditor CursorCharForwards.
745   #LeftArrow   -> ConsoleLineEditor CursorCharBackwards.
746   #Insert      -> ConsoleLineEditor ToggleInsert.
747   #Delete      -> ConsoleLineEditor DeleteCharForwards.
748   #Home        -> ConsoleLineEditor CursorToBOL.
749   #End         -> ConsoleLineEditor CursorToEOL
752 ConsoleLineEditor traits define: #ReadStream &parents: {ReadStream} &slots: {
753   #editor.
754   #line.
755   #position.
756   #closed -> False
759 s@(ConsoleLineEditor ReadStream traits) on: editor
761   s editor := editor.
762   s
765 s@(ConsoleLineEditor ReadStream traits) isAtEnd [s closed].
766 s@(ConsoleLineEditor ReadStream traits) elementType [s terminal elementType].
767 s@(ConsoleLineEditor ReadStream traits) collectionType [s terminal collectionType].
769 s@(ConsoleLineEditor ReadStream traits) next
771   [s line isNil \/ [s line isEmpty]] whileTrue:
772     [(s line := s editor readLine &echoNewLine: True) ifNil:
773        [s closed := True.
774         s exhausted.
775         ^ Nil].
776      s line := s line ; '\n'.
777      s position := 0].
778   result ::= s line at: s position.
779   (s position += 1) = s line size ifTrue:
780     [s line := Nil].
781   result
784 "This is the default LineEditor that can be overridden by
785 adding a slot to terminal instances."
786 SmartTerminal traits LineEditor ::= ConsoleLineEditor.