1: \ command line edit and history support 16oct94py
2:
3: \ Copyright (C) 1995,2000,2003,2004,2005,2006 Free Software Foundation, Inc.
4:
5: \ This file is part of Gforth.
6:
7: \ Gforth is free software; you can redistribute it and/or
8: \ modify it under the terms of the GNU General Public License
9: \ as published by the Free Software Foundation; either version 2
10: \ of the License, or (at your option) any later version.
11:
12: \ This program is distributed in the hope that it will be useful,
13: \ but WITHOUT ANY WARRANTY; without even the implied warranty of
14: \ MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15: \ GNU General Public License for more details.
16:
17: \ You should have received a copy of the GNU General Public License
18: \ along with this program; if not, write to the Free Software
19: \ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111, USA.
20:
21: :noname
22: char [char] @ - ;
23: :noname
24: char [char] @ - postpone Literal ;
25: interpret/compile: ctrl ( "<char>" -- ctrl-code )
26:
27: \ command line editing 16oct94py
28:
29: : >string ( span addr pos1 -- span addr pos1 addr2 len )
30: over 3 pick 2 pick chars /string ;
31:
32: : bindkey ( xt key -- ) cells ctrlkeys + ! ;
33:
34: \ history support 16oct94py
35:
36: 0 Value history \ history file fid
37:
38: 2Variable forward^
39: 2Variable backward^
40: 2Variable end^
41:
42: : force-open ( addr len -- fid )
43: 2dup r/w open-file
44: IF
45: drop r/w create-file throw
46: ELSE
47: nip nip
48: THEN ;
49:
50: s" os-class" environment? [IF] s" unix" str= [ELSE] true [THEN]
51: [IF]
52: : history-file ( -- addr u )
53: s" GFORTHHIST" getenv dup 0= IF
54: 2drop s" ~/.gforth-history"
55: THEN ;
56: [ELSE]
57:
58: : history-dir ( -- addr u )
59: s" TMP" getenv ?dup ?EXIT drop
60: s" TEMP" getenv ?dup ?EXIT drop
61: s" c:/" ;
62:
63: : history-file ( -- addr u )
64: s" GFORTHHIST" getenv ?dup ?EXIT
65: drop
66: history-dir pad place
67: s" /ghist.fs" pad +place pad count ;
68: [THEN]
69:
70: \ moving in history file 16oct94py
71:
72: defer back-restore ( u -- )
73: defer cur-correct ( addr u -- )
74: ' backspaces IS back-restore
75: ' 2drop IS cur-correct
76:
77: [IFDEF] x-width
78: : clear-line ( max span addr pos1 -- max addr )
79: back-restore over over swap x-width spaces swap back-restore ;
80: [ELSE]
81: : clear-line ( max span addr pos1 -- max addr )
82: back-restore over spaces swap back-restore ;
83: [THEN]
84: \ : clear-tib ( max span addr pos -- max 0 addr 0 false )
85: \ clear-line 0 tuck dup ;
86:
87: : hist-pos ( -- ud ) history file-position drop ( throw ) ;
88: : hist-setpos ( ud -- ) history reposition-file drop ( throw ) ;
89:
90: : get-line ( addr len -- len' flag )
91: swap history read-line throw ;
92:
93: : next-line ( max span addr pos1 -- max span addr pos2 false )
94: clear-line
95: forward^ 2@ 2dup hist-setpos backward^ 2!
96: 2dup get-line drop
97: hist-pos forward^ 2!
98: tuck 2dup type 2dup cur-correct 0 ;
99:
100: : find-prev-line ( max addr -- max span addr pos2 )
101: backward^ 2@ forward^ 2!
102: over 2 + negate s>d backward^ 2@ d+ 0. dmax 2dup hist-setpos
103: BEGIN
104: backward^ 2! 2dup get-line WHILE
105: hist-pos 2dup forward^ 2@ d< WHILE
106: rot drop
107: REPEAT 2drop THEN tuck ;
108:
109: : prev-line ( max span addr pos1 -- max span addr pos2 false )
110: clear-line find-prev-line 2dup type 2dup cur-correct 0 ;
111:
112: \ Create lfpad #lf c,
113:
114: : (enter) ( max span addr pos1 -- max span addr pos2 true )
115: >r end^ 2@ hist-setpos
116: 2dup swap history write-line drop ( throw ) \ don't worry about errors
117: hist-pos 2dup backward^ 2! end^ 2!
118: r> (ret) ;
119:
120: : extract-word ( addr len -- addr' len' ) dup >r
121: BEGIN 1- dup 0>= WHILE 2dup + c@ bl = UNTIL THEN 1+
122: tuck + r> rot - ;
123:
124: Create prefix-found 0 , 0 ,
125:
126: : sgn ( n -- -1/0/1 )
127: dup 0= IF EXIT THEN 0< 2* 1+ ;
128:
129: : capscomp ( c_addr1 u c_addr2 -- n )
130: swap bounds
131: ?DO dup c@ I c@ <>
132: IF dup c@ toupper I c@ toupper =
133: ELSE true THEN WHILE 1+ LOOP drop 0
134: ELSE c@ toupper I c@ toupper - unloop THEN sgn ;
135:
136: : word-lex ( nfa1 nfa2 -- -1/0/1 )
137: dup 0=
138: IF
139: 2drop 1 EXIT
140: THEN
141: name>string 2>r name>string
142: dup r@ =
143: IF
144: rdrop r> capscomp 0<= EXIT
145: THEN
146: r> <
147: nip rdrop ;
148:
149: : search-voc ( addr len nfa1 nfa2 -- addr len nfa3 )
150: >r
151: BEGIN
152: dup
153: WHILE
154: >r dup r@ name>string nip <=
155: IF
156: 2dup r@ name>string drop capscomp 0=
157: IF
158: r> dup r@ word-lex
159: IF
160: dup prefix-found @ word-lex
161: 0>=
162: IF
163: rdrop dup >r
164: THEN
165: THEN
166: >r
167: THEN
168: THEN
169: r> @
170: REPEAT
171: drop r> ;
172:
173: : prefix-off ( -- ) 0 0 prefix-found 2! ;
174:
175: : prefix-string ( addr len nfa -- addr' len' )
176: dup prefix-found ! ?dup
177: IF
178: name>string rot /string rot drop
179: dup 1+ prefix-found cell+ !
180: ELSE
181: 2drop s" " prefix-off
182: THEN ;
183:
184: : search-prefix ( addr1 len1 -- addr2 len2 )
185: 0 vp dup @ 1- cells over +
186: DO I 2@ <>
187: IF I cell+ @ wordlist-id @ swap search-voc THEN
188: [ -1 cells ] Literal +LOOP
189: prefix-string ;
190:
191: : tib-full? ( max span addr pos addr' len' -- max span addr pos addr1 u flag )
192: 5 pick over 4 pick + prefix-found @ 0<> - < ;
193:
194: : kill-prefix ( key -- key )
195: dup #tab <> IF prefix-off THEN ;
196:
197: \ UTF-8 support
198:
199: require utf-8.fs
200:
201: [IFUNDEF] #esc 27 Constant #esc [THEN]
202:
203: Variable curpos
204:
205: s" os-type" environment? [IF] s" cygwin" str= [IF]
206: : cygwin? ( -- flag ) s" TERM" getenv s" cygwin" str= ;
207: : at-xy? ( -- x y )
208: key? drop
209: #esc emit ." [6n" 0 0
210: BEGIN key dup 'R <> WHILE
211: dup '; = IF drop swap ELSE
212: dup '0 '9 1+ within IF '0 - swap 10 * + ELSE
213: drop THEN THEN
214: REPEAT drop 1- swap 1- ;
215: : cursor@ ( -- n ) at-xy? form nip * + ;
216: : cursor! ( n -- ) form nip /mod at-xy ;
217: : xcur-correct ( addr u -- )
218: cygwin? IF 2drop EXIT THEN
219: x-width curpos @ + cursor@ -
220: form nip >r r@ 2/ + r@ / r> * negate curpos +! ;
221: : save-cursor ( -- )
222: cygwin? IF #esc emit '7 emit ELSE cursor@ curpos ! THEN ;
223: : restore-cursor ( -- )
224: cygwin? IF #esc emit '8 emit ELSE curpos @ cursor! THEN ;
225: [ELSE]
226: : at-xy? ( -- x y )
227: key? drop
228: #esc emit ." [6n" 0 0
229: BEGIN key dup 'R <> WHILE
230: dup '; = IF drop swap ELSE
231: dup '0 '9 1+ within IF '0 - swap 10 * + ELSE
232: drop THEN THEN
233: REPEAT drop 1- swap 1- ;
234: : cursor@ ( -- n ) at-xy? form nip * + ;
235: : cursor! ( n -- ) form nip /mod at-xy ;
236: : xcur-correct ( addr u -- ) x-width curpos @ + cursor@ -
237: form nip >r r@ 2/ + r@ / r> * negate curpos +! ;
238: : save-cursor ( -- ) cursor@ curpos ! ;
239: : restore-cursor ( -- ) curpos @ cursor! ;
240: [THEN] [THEN]
241: ' xcur-correct IS cur-correct
242:
243: : .rest ( addr pos1 -- addr pos1 )
244: key? ?EXIT
245: restore-cursor 2dup type 2dup cur-correct ;
246: : .all ( span addr pos1 -- span addr pos1 )
247: key? ?EXIT
248: restore-cursor >r 2dup swap type 2dup swap cur-correct r> ;
249: : xback-restore ( u -- )
250: drop key? ?EXIT
251: restore-cursor ;
252:
253: \ In the following, addr max is the buffer, addr span is the current
254: \ string in the buffer, and pos1 is the cursor position in the buffer.
255:
256: : <xins> ( max span addr pos1 xc -- max span addr pos2 )
257: >r 2over r@ xc-size + u< IF ( max span addr pos1 R:xc )
258: rdrop bell EXIT THEN
259: >string over r@ xc-size + swap move
260: 2dup chars + r@ swap r@ xc-size xc!+? 2drop drop
261: r> xc-size >r rot r@ chars + -rot r> chars + ;
262: : (xins) ( max span addr pos1 xc -- max span addr pos2 )
263: <xins> .all .rest ;
264: : xback ( max span addr pos1 -- max span addr pos2 f )
265: dup IF over + xchar- over - 0 max .all .rest
266: ELSE bell THEN 0 ;
267: : xforw ( max span addr pos1 -- max span addr pos2 f )
268: 2 pick over <> IF over + xc@+ xemit over - ELSE bell THEN 0 ;
269: : (xdel) ( max span addr pos1 -- max span addr pos2 )
270: over + dup xchar- tuck - >r over -
271: >string over r@ + -rot move
272: rot r> - -rot ;
273: : ?xdel ( max span addr pos1 -- max span addr pos2 0 )
274: dup IF (xdel) .all 2 spaces .rest THEN 0 ;
275: : <xdel> ( max span addr pos1 -- max span addr pos2 0 )
276: 2 pick over <>
277: IF xforw drop (xdel) .all 2 spaces .rest
278: ELSE bell THEN 0 ;
279: : xeof 2 pick over or 0= IF bye ELSE <xdel> THEN ;
280:
281: : xfirst-pos ( max span addr pos1 -- max span addr 0 0 )
282: drop 0 .all .rest 0 ;
283: : xend-pos ( max span addr pos1 -- max span addr span 0 )
284: drop over .all 0 ;
285:
286:
287: : xclear-line ( max span addr pos1 -- max addr )
288: drop restore-cursor swap spaces restore-cursor ;
289: : xclear-tib ( max span addr pos -- max 0 addr 0 false )
290: xclear-line 0 tuck dup ;
291:
292: : (xenter) ( max span addr pos1 -- max span addr pos2 true )
293: >r end^ 2@ hist-setpos
294: 2dup swap history write-line drop ( throw ) \ don't worry about errors
295: hist-pos 2dup backward^ 2! end^ 2!
296: r> .all space true ;
297:
298: : xkill-expand ( max span addr pos1 -- max span addr pos2 )
299: prefix-found cell+ @ ?dup IF >r
300: r@ - >string over r@ + -rot move
301: rot r@ - -rot .all r> spaces .rest THEN ;
302:
303: : insert ( string length buffer size -- )
304: rot over min >r r@ - ( left over )
305: over dup r@ + rot move r> move ;
306:
307: : xtab-expand ( max span addr pos1 -- max span addr pos2 0 )
308: key? IF #tab (xins) 0 EXIT THEN
309: xkill-expand 2dup extract-word dup 0= IF nip EXIT THEN
310: search-prefix tib-full?
311: IF bell 2drop prefix-off
312: ELSE dup >r
313: 2>r >string r@ + 2r> 2swap insert
314: r@ + rot r> + -rot
315: THEN
316: prefix-found @ IF bl (xins) ELSE .all .rest THEN 0 ;
317:
318: : xchar-history ( -- )
319: ['] xforw ctrl F bindkey
320: ['] xback ctrl B bindkey
321: ['] ?xdel ctrl H bindkey
322: ['] xeof ctrl D bindkey
323: ['] <xdel> ctrl X bindkey
324: ['] xclear-tib ctrl K bindkey
325: ['] xfirst-pos ctrl A bindkey
326: ['] xend-pos ctrl E bindkey
327: history IF ['] (xenter) #lf bindkey THEN
328: history IF ['] (xenter) #cr bindkey THEN
329: ['] xtab-expand #tab bindkey
330: ['] (xins) IS insert-char
331: ['] kill-prefix IS everychar
332: ['] save-cursor IS everyline
333: ['] xback-restore IS back-restore
334: ['] xcur-correct IS cur-correct
335: ;
336:
337: xchar-history
338:
339: \ initializing history
340:
341: : get-history ( addr len -- )
342: ['] force-open catch
343: ?dup-if
344: \ !! >stderr
345: \ history-file type ." : " .error cr
346: drop 2drop 0 to history
347: ['] false ['] false ['] (ret)
348: else
349: to history
350: history file-size throw
351: 2dup forward^ 2! 2dup backward^ 2! end^ 2!
352: ['] next-line ['] prev-line ['] (enter)
353: endif
354: dup #lf bindkey
355: #cr bindkey
356: ctrl P bindkey
357: ctrl N bindkey
358: ;
359:
360: : history-cold ( -- )
361: history-file get-history xchar-history ;
362:
363: :noname ( -- )
364: defers 'cold
365: history-cold
366: ; is 'cold
367:
368: history-cold
369:
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>