1 /*  Part of SWI-Prolog
2 
3     Author:        Jan Wielemaker
4     E-mail:        J.Wielemaker@vu.nl
5     WWW:           http://www.swi-prolog.org
6     Copyright (c)  1999-2016, University of Amsterdam
7                               VU University Amsterdam
8     All rights reserved.
9 
10     Redistribution and use in source and binary forms, with or without
11     modification, are permitted provided that the following conditions
12     are met:
13 
14     1. Redistributions of source code must retain the above copyright
15        notice, this list of conditions and the following disclaimer.
16 
17     2. Redistributions in binary form must reproduce the above copyright
18        notice, this list of conditions and the following disclaimer in
19        the documentation and/or other materials provided with the
20        distribution.
21 
22     THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
23     "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
24     LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
25     FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
26     COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
27     INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
28     BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
29     LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
30     CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
31     LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
32     ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
33     POSSIBILITY OF SUCH DAMAGE.
34 */
35 
36 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
37 This file defines a console for porting (unix) stream-based applications
38 to MS-Windows. It has been developed for  SWI-Prolog. The main source is
39 part of SWI-Prolog.
40 
41 The SWI-Prolog source is at http://www.swi-prolog.org
42 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
43 
44 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
45 Thread design:
46 
47 <written as a mail to Lutz Wohlrab>
48 
49 There are two threads. The Prolog engine   runs  in the main thread. The
50 other thread deals with the window.   Basically, it processes events and
51 if anything is typed it puts it into a queue.
52 
53 The main thread  at  some  stage   forks  the  display  thread,  running
54 window_loop().  This  thread  initialises  the   input  and  then  sends
55 WM_RLC_READY to the main thread to indicate it is ready to accept data.
56 
57 If data is to be written,  Prolog   calls  rlc_write(),  which posts the
58 WM_RLC_WRITE to the display thread, waiting  on the termination. If data
59 is to be read, rlc_read() posts  a   WM_RLC_FLUSH,  and then waits while
60 dispatching events, for the display-thread to   fill the buffer and send
61 WM_RLC_INPUT (which is just sent  to   make  GetMessage()  in rlc_read()
62 return).
63 
64 Towards an MT version on Windows
65 --------------------------------
66 
67 If we want to move towards a  multi-threaded version for MS-Windows, the
68 console code needs to be changed significantly, as we need to be able to
69 create multiple consoles to support thread_attach_console/0.
70 
71 The most logical solution seems to   be to reverse the thread-structure,
72 Prolog starting and running in the   main-thread  and creating a console
73 creates a new thread for this console. There  are two ways to keep track
74 of the console to use. Cleanest might be to add an argument denoting the
75 allocated console and alternatively we could   use thread-local data. We
76 can also combine the two: add an  additional argument, but allow passing
77 NULL to use the default console for this thread.
78 
79 Menus
80 -----
81 
82 The current console provides a menu that can be extended from Prolog.
83 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
84 
85 #ifdef O_DEBUG_HEAP
86 static void initHeapDebug(void);
87 #include <crtdbg.h>
88 #else
89 #define initHeapDebug()
90 #endif
91 
92 #include <windows.h>
93 #include <tchar.h>
94 #ifndef WM_MOUSEWHEEL			/* sometimes not defined */
95 #define WM_MOUSEWHEEL 0x020A
96 #endif
97 #ifndef WM_UNICHAR
98 #define WM_UNICHAR 0x109
99 #define UNICODE_NOCHAR 0xFFFF
100 #endif
101 
102 #ifdef _MSC_VER
103 #pragma warning(disable : 4996)	/* deprecate open() etc */
104 #endif
105 
106 #include <stdlib.h>
107 #include <io.h>
108 #include <string.h>
109 #include <malloc.h>
110 #define _MAKE_DLL 1
111 #undef _export
112 #include "console.h"
113 #include "menu.h"
114 #include "common.h"
115 #include <signal.h>
116 #include <ctype.h>
117 #include <stdio.h>
118 
119 #ifndef isletter
120 #define isletter(c) (_istalpha(c) || (c) == '_')
121 #endif
122 
123 #ifndef MAXPATHLEN
124 #define MAXPATHLEN 256
125 #endif
126 
127 #ifndef CHAR_MAX
128 #define CHAR_MAX 256
129 #endif
130 
131 #define MAXLINE	     1024		/* max chars per line */
132 
133 #define CMD_INITIAL	0
134 #define CMD_ESC		1
135 #define CMD_ANSI	2
136 
137 #define GWL_DATA	0		/* offset for client data */
138 
139 #define CHG_RESET	0		/* unchenged */
140 #define CHG_CHANGED	1		/* changed, but no clear */
141 #define CHG_CLEAR	2		/* clear */
142 #define CHG_CARET	4		/* caret has moved */
143 
144 #define SEL_CHAR	0		/* character-unit selection */
145 #define SEL_WORD	1		/* word-unit selection */
146 #define SEL_LINE	2		/* line-unit selection */
147 
148 #ifndef EOS
149 #define EOS 0
150 #endif
151 
152 #define ESC 27				/* the escape character */
153 
154 #define WM_RLC_INPUT	 WM_USER+10	/* Just somewhere ... */
155 #define WM_RLC_WRITE	 WM_USER+11	/* write data */
156 #define WM_RLC_FLUSH	 WM_USER+12	/* flush buffered data */
157 #define WM_RLC_READY	 WM_USER+13	/* Window thread is ready */
158 #define WM_RLC_CLOSEWIN  WM_USER+14	/* Close the window */
159 /*#define WM_RLC_MENU	 WM_USER+15	   Insert a menu (defined in menu.h) */
160 
161 #define IMODE_RAW	1		/* char-by-char */
162 #define IMODE_COOKED	2		/* line-by-line */
163 
164 #define NextLine(b, i) ((i) < (b)->height-1 ? (i)+1 : 0)
165 #define PrevLine(b, i) ((i) > 0 ? (i)-1 : (b)->height-1)
166 #define Bounds(v, mn, mx) ((v) < (mn) ? (mn) : (v) > (mx) ? (mx) : (v))
167 
168 #define Control(x) ((x) - '@')
169 
170 #define streq(s, q) (_tcscmp((s), (q)) == 0)
171 
172 #include "console_i.h"			/* internal package stuff */
173 
174 #define OPT_SIZE	0x01
175 #define OPT_POSITION	0x02
176 
177 		 /*******************************
178 		 *	       DATA		*
179 		 *******************************/
180 
181        RlcData  _rlc_stdio = NULL;	/* the main buffer */
182 static int      _rlc_show;		/* initial show */
183 static char	_rlc_word_chars[CHAR_MAX]; /* word-characters (selection) */
184 static const TCHAR *	_rlc_program;		/* name of the program */
185 static HANDLE   _rlc_hinstance;		/* Global instance */
186 static HICON    _rlc_hicon;		/* Global icon */
187 
188 
189 
190 		 /*******************************
191 		 *	     FUNCTIONS		*
192 		 *******************************/
193 
194 static LRESULT WINAPI rlc_wnd_proc(HWND win, UINT msg, WPARAM wP, LPARAM lP);
195 
196 static void	rcl_setup_ansi_colors(RlcData b);
197 static void	rlc_place_caret(RlcData b);
198 static void	rlc_resize_pixel_units(RlcData b, int w, int h);
199 static RlcData	rlc_make_buffer(int w, int h);
200 static int	rlc_count_lines(RlcData b, int from, int to);
201 static void	rlc_add_line(RlcData b);
202 static void	rlc_open_line(RlcData b);
203 static void	rlc_update_scrollbar(RlcData b);
204 static void	rlc_paste(RlcData b);
205 static void	rlc_init_text_dimensions(RlcData b, HFONT f);
206 static void	rlc_save_font_options(HFONT f, rlc_console_attr *attr);
207 static void	rlc_get_options(rlc_console_attr *attr);
208 static HKEY	rlc_option_key(rlc_console_attr *attr, int create);
209 static void	rlc_progbase(TCHAR *path, TCHAR *base);
210 static int	rlc_add_queue(RlcData b, RlcQueue q, int chr);
211 static int	rlc_add_lines(RlcData b, int here, int add);
212 static void	rlc_start_selection(RlcData b, int x, int y);
213 static void	rlc_extend_selection(RlcData b, int x, int y);
214 static void	rlc_word_selection(RlcData b, int x, int y);
215 static int	rlc_has_selection(RlcData b);
216 static void	rlc_set_selection(RlcData b, int sl, int sc, int el, int ec);
217 static void	rlc_copy(RlcData b);
218 static void	rlc_destroy(RlcData b);
219 static void	rlc_request_redraw(RlcData b);
220 static void	rlc_redraw(RlcData b);
221 static int	rlc_breakargs(TCHAR *line, TCHAR **argv);
222 static void	rlc_resize(RlcData b, int w, int h);
223 static void	rlc_adjust_line(RlcData b, int line);
224 static int	text_width(RlcData b, HDC hdc, const text_char *text, int len);
225 static int	tchar_width(RlcData b, HDC hdc, const TCHAR *text, int len);
226 static void	rlc_queryfont(RlcData b);
227 static void     rlc_do_write(RlcData b, TCHAR *buf, int count);
228 static void     rlc_reinit_line(RlcData b, int line);
229 static void	rlc_free_line(RlcData b, int line);
230 static int	rlc_between(RlcData b, int f, int t, int v);
231 static void	free_user_data(RlcData b);
232 
233 static RlcQueue	rlc_make_queue(int size);
234 static int	rlc_from_queue(RlcQueue q);
235 static int	rlc_is_empty_queue(RlcQueue q);
236 
237 extern int	main();
238 
239 static RlcUpdateHook	_rlc_update_hook;
240 static RlcTimerHook	_rlc_timer_hook;
241 static RlcRenderHook	_rlc_render_hook;
242 static RlcRenderAllHook _rlc_render_all_hook;
243 static RlcInterruptHook _rlc_interrupt_hook;
244 static RlcResizeHook    _rlc_resize_hook;
245 static RlcMenuHook	_rlc_menu_hook;
246 static RlcMessageHook	_rlc_message_hook;
247 static int _rlc_copy_output_to_debug_output=0;	/* != 0: copy to debugger */
248 static int	emulate_three_buttons;
249 static HWND	emu_hwnd;		/* Emulating for this window */
250 
251 static void _rlc_create_kill_window(RlcData b);
252 static DWORD WINAPI window_loop(LPVOID arg);	/* console window proc */
253 
254 #ifdef _DEBUG
255 #include <stdarg.h>
256 static void Dprintf(const TCHAR *fmt, ...);
257 static void Dprint_lines(RlcData b, int from, int to);
258 #define DEBUG(Code) Code
259 
260 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
261 It might look a bit weird not to  use <assert.h>, but for some reason it
262 looks as if the application thread continues if the asserting is trapped
263 using  the  normal  assert()!?  Just  but    a  debugger  breakpoint  on
264 rlc_assert() and all functions normally.
265 
266 rlc_check_assertions() is a (very) incomplete   check that everything we
267 expect to be true about the data is indeed the case.
268 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
269 
270 void
rlc_assert(const TCHAR * msg)271 rlc_assert(const TCHAR *msg)
272 { MessageBox(NULL, msg, _T("Console assertion failed"), MB_OK|MB_TASKMODAL);
273 }
274 
275 void
rlc_check_assertions(RlcData b)276 rlc_check_assertions(RlcData b)
277 { int window_last = rlc_add_lines(b, b->window_start, b->window_size-1);
278   int y;
279 
280   assert(b->last != b->first || b->first == 0);
281   assert(b->caret_x >= 0 && b->caret_x < b->width);
282 					/* TBD: debug properly */
283 /*assert(rlc_between(b, b->window_start, window_last, b->caret_y));*/
284 
285   for(y=0; y<b->height; y++)
286   { TextLine tl = &b->lines[y];
287 
288     assert(tl->size >= 0 && tl->size <= b->width);
289   }
290 }
291 
292 #else
293 
294 #define DEBUG(Code) ((void)0)
295 #define rlc_check_assertions(b)
296 #endif
297 
298 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
299 rlc_long_name(TCHAR *buffer)
300 	Translate a filename, possibly holding 8+3 abbreviated parts into
301 	the `real' filename.  I couldn't find a direct call for this.  If
302 	you have it, I'd be glad to receive a better implementation.
303 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
304 
305 static void
rlc_long_name(TCHAR * file)306 rlc_long_name(TCHAR *file)
307 { TCHAR buf[MAXPATHLEN];
308   TCHAR *i = file;
309   TCHAR *o = buf;
310   TCHAR *ok = buf;
311   int changed = 0;
312 
313   while(*i)
314   { int dirty = FALSE;
315 
316     while(*i && *i != '\\')
317     { if ( *i == '~' )
318 	dirty++;
319       *o++ = *i++;
320     }
321     if ( dirty )
322     { WIN32_FIND_DATA data;
323       HANDLE h;
324 
325       *o = '\0';
326       if ( (h=FindFirstFile(buf, &data)) != INVALID_HANDLE_VALUE )
327       { _tcscpy(ok, data.cFileName);
328 	FindClose(h);
329 	o = ok + _tcslen(ok);
330 	changed++;
331       }
332     }
333     if ( *i )
334       *o++ = *i++;
335     ok = o;
336   }
337 
338   if ( changed )
339   { *o = '\0';
340     _tcscpy(file, buf);
341   }
342 }
343 
344 
345 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
346 If %PLTERM_CLASS% is in the environment, this   value is used as Windows
347 class identifier for the console window.   This allows external programs
348 to start PLWIN.EXE and find the window it  has started in order to embed
349 it.
350 
351 In old versions this was fixed to "RlcConsole"
352 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
353 
354 static TCHAR *
rlc_window_class(HICON icon)355 rlc_window_class(HICON icon)
356 { static TCHAR winclassname[32];
357   static WNDCLASS wndClass;
358   HINSTANCE instance = _rlc_hinstance;
359 
360   if ( !winclassname[0] )
361   { if ( !GetEnvironmentVariable(_T("PLTERM_CLASS"),
362 				 winclassname, sizeof(winclassname)) )
363       _snwprintf(winclassname, sizeof(winclassname)/sizeof(TCHAR),
364 		 _T("PlTerm-%d"), (int)(intptr_t)instance);
365 
366     wndClass.lpszClassName	= winclassname;
367     wndClass.style		= CS_HREDRAW|CS_VREDRAW|CS_DBLCLKS;
368     wndClass.lpfnWndProc	= (LPVOID) rlc_wnd_proc;
369     wndClass.cbClsExtra		= 0;
370     wndClass.cbWndExtra		= sizeof(intptr_t);
371     wndClass.hInstance		= instance;
372     if ( icon )
373       wndClass.hIcon		= icon;
374     else
375       wndClass.hIcon		= LoadIcon(NULL, IDI_APPLICATION);
376     wndClass.hCursor		= LoadCursor(NULL, IDC_IBEAM);
377     wndClass.hbrBackground	= (HBRUSH) NULL;
378     wndClass.lpszMenuName	= NULL;
379 
380     RegisterClass(&wndClass);
381   }
382 
383   return winclassname;
384 }
385 
386 
387 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
388 There are two ways to get the commandline.   It  is passed to WinMain as
389 8-bit string. This version does *not* include  the command itself. It is
390 also available through GetCommandLine(), which  does include the command
391 itself and returns LPTSTR (Unicode/ANSI). We assume the latter.
392 
393 Nevertheless, for backward compatibility as well  as easy to extract the
394 full pathname of the  executable,  we   replace  argv[0]  with  the intptr_t
395 filename version of the current module, so argv[0] is guaranteed to be a
396 full path refering to the .exe file.
397 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
398 
399 int
rlc_main(HANDLE hInstance,HANDLE hPrevInstance,LPTSTR lpszCmdLine,int nCmdShow,RlcMain mainfunc,HICON icon)400 rlc_main(HANDLE hInstance, HANDLE hPrevInstance,
401 	 LPTSTR lpszCmdLine, int nCmdShow,
402 	 RlcMain mainfunc, HICON icon)
403 { TCHAR *	    argv[100];
404   int		    argc;
405   TCHAR		    program[MAXPATHLEN];
406   TCHAR		    progbase[100];
407   RlcData           b;
408   rlc_console_attr  attr;
409 
410   initHeapDebug();
411 
412   _rlc_hinstance = hInstance;
413   _rlc_show = nCmdShow;
414   _rlc_hicon = icon;
415 
416   GetModuleFileName(hInstance, program, sizeof(program));
417   rlc_long_name(program);
418   argc = rlc_breakargs(lpszCmdLine, argv);
419   argv[0] = program;
420   rlc_progbase(argv[0], progbase);
421 
422   memset(&attr, 0, sizeof(attr));
423   _rlc_program = attr.title = progbase;
424   _rlc_stdio = b = rlc_create_console(&attr);
425 
426   if ( mainfunc )
427     return (*mainfunc)(b, argc, argv);
428   else
429     return 0;
430 }
431 
432 
433 
434 rlc_console
rlc_create_console(rlc_console_attr * attr)435 rlc_create_console(rlc_console_attr *attr)
436 { RlcData b;
437   MSG msg;
438   const TCHAR *title;
439 
440   rlc_get_options(attr);
441 
442   if ( attr->title )
443     title = attr->title;
444   else
445     title = _T("Untitled");
446 
447   b = rlc_make_buffer(attr->width, attr->savelines);
448   b->create_attributes = attr;
449   _tcscpy(b->current_title, title);
450   if ( attr->key )
451   { b->regkey_name = _tcsdup(attr->key);
452   }
453 
454   rlc_init_text_dimensions(b, NULL);
455   _rlc_create_kill_window(b);
456 
457   DuplicateHandle(GetCurrentProcess(),
458 		  GetCurrentThread(),
459 		  GetCurrentProcess(),
460 		  &b->application_thread,
461 		  0,
462 		  FALSE,
463 		  DUPLICATE_SAME_ACCESS);
464   b->application_thread_id = GetCurrentThreadId();
465   b->console_thread = CreateThread(NULL,			/* security */
466 				   2048,			/* stack */
467 				   window_loop, b,		/* proc+arg */
468 				   0,				/* flags */
469 				   &b->console_thread_id);	/* id */
470 					/* wait till the window is created */
471   GetMessage(&msg, NULL, WM_RLC_READY, WM_RLC_READY);
472   b->create_attributes = NULL;		/* release this data */
473 
474   return b;
475 }
476 
477 
478 static void
rlc_create_window(RlcData b)479 rlc_create_window(RlcData b)
480 { HWND hwnd;
481   rlc_console_attr *a = b->create_attributes;
482   RECT rect;
483   DWORD style = (WS_OVERLAPPEDWINDOW|WS_VSCROLL);
484 
485 /* One would assume AdjustWindowRect() uses WS_VSCROLL to add the width of
486    the scrollbar.  I think this isn't true, but maybe there is another reason
487    for getting 2 characters shorter each invocation ...
488 */
489 
490   rect.left   = a->x;
491   rect.top    = a->y;
492   rect.right  = a->x + (a->width+2) * b->cw + GetSystemMetrics(SM_CXVSCROLL);
493   rect.bottom = a->y + a->height * b->ch;
494 
495   AdjustWindowRect(&rect, style, TRUE);
496   hwnd = CreateWindow(rlc_window_class(_rlc_hicon), b->current_title,
497 		      style,
498 		      a->x, a->y,
499 		      rect.right - rect.left,
500 		      rect.bottom - rect.top,
501 		      NULL, NULL, _rlc_hinstance, NULL);
502 
503   b->window = hwnd;
504   SetWindowLongPtr(hwnd, GWL_DATA, (LONG_PTR) b);
505   SetScrollRange(hwnd, SB_VERT, 0, b->sb_lines, FALSE);
506   SetScrollPos(hwnd, SB_VERT, b->sb_start, TRUE);
507 
508   b->queue    = rlc_make_queue(256);
509   b->sb_lines = rlc_count_lines(b, b->first, b->last);
510   b->sb_start = rlc_count_lines(b, b->first, b->window_start);
511 
512   rcl_setup_ansi_colors(b);
513   b->foreground = GetSysColor(COLOR_WINDOWTEXT);
514   b->background = GetSysColor(COLOR_WINDOW);
515   b->sel_foreground = GetSysColor(COLOR_HIGHLIGHTTEXT);
516   b->sel_background = GetSysColor(COLOR_HIGHLIGHT);
517   if ( GetSystemMetrics(SM_CMOUSEBUTTONS) == 2 )
518     emulate_three_buttons = 120;
519 
520   rlc_add_menu_bar(b->window);
521 
522   ShowWindow(hwnd, _rlc_show);
523   UpdateWindow(hwnd);
524 }
525 
526 
527 int
rlc_iswin32s()528 rlc_iswin32s()
529 { if( GetVersion() & 0x80000000 && (GetVersion() & 0xFF) ==3)
530     return TRUE;
531   else
532     return FALSE;
533 }
534 
535 
536 static void
rlc_progbase(TCHAR * path,TCHAR * base)537 rlc_progbase(TCHAR *path, TCHAR *base)
538 { TCHAR *s;
539   TCHAR *e;
540 
541   if ( !(s=_tcsrchr(path, '\\')) )
542     s = path;				/* takes the filename part */
543   else
544     s++;
545   if ( !(e = _tcschr(s, '.')) )
546     _tcscpy(base, s);
547   else
548   { _tcsncpy(base, s, e-s);
549     base[e-s] = '\0';
550   }
551 }
552 
553 		 /*******************************
554 		 *	  HIDDEN WINDOW		*
555 		 *******************************/
556 
557 static LRESULT WINAPI
rlc_kill_wnd_proc(HWND hwnd,UINT message,UINT wParam,LONG lParam)558 rlc_kill_wnd_proc(HWND hwnd, UINT message, UINT wParam, LONG lParam)
559 { switch(message)
560   { case WM_DESTROY:
561       PostQuitMessage(0);
562       return 0;
563   }
564 
565   return DefWindowProc(hwnd, message, wParam, lParam);
566 }
567 
568 static TCHAR *
rlc_kill_window_class()569 rlc_kill_window_class()
570 { static TCHAR winclassname[32];
571   static WNDCLASS wndClass;
572   HINSTANCE instance = _rlc_hinstance;
573 
574   if ( !winclassname[0] )
575   { _snwprintf(winclassname, sizeof(winclassname)/sizeof(TCHAR),
576 	       _T("Console-hidden-win%d"), (int)(intptr_t)instance);
577 
578     wndClass.style		= 0;
579     wndClass.lpfnWndProc	= (LPVOID) rlc_kill_wnd_proc;
580     wndClass.cbClsExtra		= 0;
581     wndClass.cbWndExtra		= 0;
582     wndClass.hInstance		= instance;
583     wndClass.hIcon		= NULL;
584     wndClass.hCursor		= NULL;
585     wndClass.hbrBackground	= GetStockObject(WHITE_BRUSH);
586     wndClass.lpszMenuName	= NULL;
587     wndClass.lpszClassName	= winclassname;
588 
589     RegisterClass(&wndClass);
590   }
591 
592   return winclassname;
593 }
594 
595 
596 static void
_rlc_create_kill_window(RlcData b)597 _rlc_create_kill_window(RlcData b)
598 { b->kill_window = CreateWindow(rlc_kill_window_class(),
599 				_T("Console hidden window"),
600 				0,
601 				0, 0, 32, 32,
602 				NULL, NULL, _rlc_hinstance, NULL);
603 }
604 
605 
606 		 /*******************************
607 		 *     REGISTRY COMMUNICATION	*
608 		 *******************************/
609 
610 #define MAXREGSTRLEN 1024
611 
612 static void
reg_save_int(HKEY key,const TCHAR * name,int value)613 reg_save_int(HKEY key, const TCHAR *name, int value)
614 { DWORD val = value;
615 
616   if ( RegSetValueEx(key, name, 0,
617 		     REG_DWORD_LITTLE_ENDIAN,
618 		     (LPBYTE)&val, sizeof(val)) != ERROR_SUCCESS )
619     DEBUG(MessageBox(NULL, _T("Failed to save int setting"),
620 		     _T("Error"), MB_OK));
621 }
622 
623 static void
reg_save_str(HKEY key,const TCHAR * name,TCHAR * value)624 reg_save_str(HKEY key, const TCHAR *name, TCHAR *value)
625 { if ( RegSetValueEx(key, name, 0, REG_SZ,
626 		     (LPBYTE)value, (DWORD)(_tcslen(value)+1)*sizeof(TCHAR)) != ERROR_SUCCESS )
627     DEBUG(MessageBox(NULL, _T("Failed to save string setting"), _T("Error"), MB_OK));
628 }
629 
630 
631 static void
rlc_save_options(RlcData b)632 rlc_save_options(RlcData b)
633 { HKEY key;
634   rlc_console_attr attr;
635 
636   memset(&attr, 0, sizeof(attr));
637   attr.key = b->regkey_name;
638 
639   if ( !(key = rlc_option_key(&attr, TRUE)) )
640     return;
641 
642   reg_save_int(key, _T("SaveLines"),  b->height);
643   if ( b->modified_options & OPT_SIZE )
644   { reg_save_int(key, _T("Width"),    b->width);
645     reg_save_int(key, _T("Height"),   b->window_size);
646   }
647   if ( b->modified_options & OPT_POSITION )
648   { reg_save_int(key, _T("X"),	  b->win_x);
649     reg_save_int(key, _T("Y"),	  b->win_y);
650   }
651 
652   rlc_save_font_options(b->hfont, &attr);
653   if ( attr.face_name[0] )
654   { reg_save_str(key, _T("FaceName"),    attr.face_name);
655     reg_save_int(key, _T("FontFamily"),  attr.font_family);
656     reg_save_int(key, _T("FontSize"),    attr.font_size);
657     reg_save_int(key, _T("FontWeight"),  attr.font_weight);
658     reg_save_int(key, _T("FontCharSet"), attr.font_char_set);
659   }
660 
661   RegCloseKey(key);
662 }
663 
664 
665 static void
reg_get_int(HKEY key,const TCHAR * name,int mn,int def,int mx,int * value)666 reg_get_int(HKEY key, const TCHAR *name, int mn, int def, int mx, int *value)
667 { DWORD type;
668   BYTE  data[8];
669   DWORD len = sizeof(data);
670 
671   if ( *value )
672     return;				/* use default */
673 
674   if ( RegQueryValueEx(key, name, NULL, &type, data, &len) == ERROR_SUCCESS )
675   { switch(type)
676     { /*case REG_DWORD:*/		/* Same case !? */
677       case REG_DWORD_LITTLE_ENDIAN:
678       { DWORD *valp = (DWORD *)data;
679 	int v = *valp;
680 
681 	if ( mn < mx )
682 	{ if ( v < mn )
683 	    v = mn;
684 	  else if ( v > mx )
685 	    v = mx;
686 	}
687 
688 	*value = v;
689       }
690     }
691   } else
692     *value = def;
693 }
694 
695 
696 static void
reg_get_str(HKEY key,const TCHAR * name,TCHAR * value,int length)697 reg_get_str(HKEY key, const TCHAR *name, TCHAR *value, int length)
698 { DWORD type;
699   BYTE  data[MAXREGSTRLEN*sizeof(TCHAR)];
700   DWORD len = sizeof(data);
701 
702   if ( *value )
703     return;				/* use default */
704 
705   if ( RegQueryValueEx(key, name, NULL, &type, data, &len) == ERROR_SUCCESS )
706   { switch(type)
707     { case REG_SZ:
708       { TCHAR *val = (TCHAR*)data;
709 	_tcsncpy(value, val, length-1);
710 	value[length-1] = '\0';
711       }
712     }
713   }
714 }
715 
716 
717 HKEY
reg_open_key(TCHAR ** which,int create)718 reg_open_key(TCHAR **which, int create)
719 { HKEY key = HKEY_CURRENT_USER;
720   DWORD disp;
721   LONG rval;
722 
723   for( ; *which; which++)
724   { HKEY tmp;
725 
726     if ( which[1] )
727     { if ( RegOpenKeyEx(key, which[0], 0L, KEY_READ, &tmp) == ERROR_SUCCESS )
728       { key = tmp;
729 	continue;
730       }
731 
732       if ( !create )
733 	return NULL;
734     }
735 
736     rval = RegCreateKeyEx(key, which[0], 0, _T(""), 0,
737 			  KEY_ALL_ACCESS, NULL, &tmp, &disp);
738     RegCloseKey(key);
739     if ( rval == ERROR_SUCCESS )
740       key = tmp;
741     else
742       return NULL;
743   }
744 
745   return key;
746 }
747 
748 
749 static HKEY
rlc_option_key(rlc_console_attr * attr,int create)750 rlc_option_key(rlc_console_attr *attr, int create)
751 { TCHAR Prog[256];
752   TCHAR *address[] = { _T("Software"),
753 		      RLC_VENDOR,
754 		      Prog,
755 		      _T("Console"),
756 		      (TCHAR *)attr->key,	/* possible secondary key */
757 		      NULL
758 		    };
759   const TCHAR *s;
760   TCHAR *q;
761 
762   for(s=_rlc_program, q=Prog; *s; s++, q++) /* capitalise the key */
763   { *q = (s==_rlc_program ? _totupper(*s) : _totlower(*s));
764   }
765   *q = EOS;
766 
767   return reg_open_key(address, create);
768 }
769 
770 
771 static void
rlc_get_options(rlc_console_attr * attr)772 rlc_get_options(rlc_console_attr *attr)
773 { HKEY key;
774 
775   if ( !(key = rlc_option_key(attr, FALSE)) )
776   { if ( !attr->width  )    attr->width = 80;
777     if ( !attr->height )    attr->height = 24;
778     if ( !attr->savelines ) attr->savelines = 200;
779 
780     return;
781   }
782 
783 { int minx, miny, maxx, maxy;
784   RECT rect;
785 
786   SystemParametersInfo(SPI_GETWORKAREA, 0, &rect, 0);
787   minx = rect.top;
788   miny = rect.left;
789   maxx = rect.right  - 40;
790   maxy = rect.bottom - 40;
791 
792   reg_get_int(key, _T("SaveLines"),   200,  200, 100000, &attr->savelines);
793   reg_get_int(key, _T("Width"),        20,	 80,    300, &attr->width);
794   reg_get_int(key, _T("Height"),        5,	 24,    100, &attr->height);
795   reg_get_int(key, _T("X"),		 minx, minx,   maxx, &attr->x);
796   reg_get_int(key, _T("Y"),	         miny, miny,   maxy, &attr->y);
797 }
798 
799   reg_get_str(key, _T("FaceName"), attr->face_name,
800 	      sizeof(attr->face_name)/sizeof(TCHAR));
801   reg_get_int(key, _T("FontFamily"),    0,  0,  0, &attr->font_family);
802   reg_get_int(key, _T("FontSize"),      0,  0,  0, &attr->font_size);
803   reg_get_int(key, _T("FontWeight"),    0,  0,  0, &attr->font_weight);
804   reg_get_int(key, _T("FontCharSet"),   0,  0,  0, &attr->font_char_set);
805 
806   RegCloseKey(key);
807 }
808 
809 
810 
811 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
812 Windows-'95 appears to quote  names  of   files  because  files may hold
813 spaces. rlc_breakargs() will pass a quoted   strings as one argument. If
814 it can't find the closing quote, it  will   tread  the quote as a normal
815 character.
816 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
817 
818 static int
rlc_breakargs(TCHAR * line,TCHAR ** argv)819 rlc_breakargs(TCHAR *line, TCHAR **argv)
820 { int argc = 0;
821 
822   while(*line)
823   { int q;
824 
825     while(*line && _istspace(*line))
826       line++;
827 
828     if ( (q = *line) == '"' || q == '\'' )	/* quoted arguments */
829     { TCHAR *start = line+1;
830       TCHAR *end = start;
831 
832       while( *end && *end != q )
833 	end++;
834       if ( *end == q )
835       { *end = '\0';
836         argv[argc++] = start;
837 	line = end+1;
838 	continue;
839       }
840     }
841 
842     if ( *line )
843     { argv[argc++] = line;
844       while(*line && !_istspace(*line))
845 	line++;
846       if ( *line )
847 	*line++ = '\0';
848     }
849   }
850   argv[argc] = NULL;			/* add trailing NULL pointer to argv */
851 
852   return argc;
853 }
854 
855 
856 		 /*******************************
857 		 *	    ANSI COLORS		*
858 		 *******************************/
859 
860 /* See http://en.wikipedia.org/wiki/ANSI_escape_code */
861 
862 static void
rcl_setup_ansi_colors(RlcData b)863 rcl_setup_ansi_colors(RlcData b)
864 { b->sgr_flags = TF_DEFAULT;
865 
866 #ifdef ANSI_VGA_COLORS
867 					/* normal versions */
868   b->ansi_color[0]  = RGB(  0,  0,  0);	/* black */
869   b->ansi_color[1]  = RGB(170,  0,  0);	/* red */
870   b->ansi_color[2]  = RGB(0,  170,  0);	/* green */
871   b->ansi_color[3]  = RGB(170, 85,  0);	/* yellow */
872   b->ansi_color[4]  = RGB(  0,  0,170);	/* blue */
873   b->ansi_color[5]  = RGB(170,  0,170);	/* magenta */
874   b->ansi_color[6]  = RGB(  0,170,170);	/* cyan */
875   b->ansi_color[7]  = RGB(170,170,170);	/* white */
876 					/* bright/light versions */
877   b->ansi_color[8]  = RGB( 85, 85, 85);	/* black */
878   b->ansi_color[9]  = RGB(255, 85, 85);	/* red */
879   b->ansi_color[10] = RGB( 85,255, 85);	/* green */
880   b->ansi_color[11] = RGB(255,255, 85);	/* yellow */
881   b->ansi_color[12] = RGB( 85, 85,255);	/* blue */
882   b->ansi_color[13] = RGB(255, 85,255);	/* magenta */
883   b->ansi_color[14] = RGB( 85,255,255);	/* cyan */
884   b->ansi_color[15] = RGB(255,255,255);	/* white */
885 #else /*XTERM*/
886 					/* normal versions */
887   b->ansi_color[0]  = RGB(  0,  0,  0);	/* black */
888   b->ansi_color[1]  = RGB(205,  0,  0);	/* red */
889   b->ansi_color[2]  = RGB(0,  205,  0);	/* green */
890   b->ansi_color[3]  = RGB(205,205,  0);	/* yellow */
891   b->ansi_color[4]  = RGB(  0,  0,238);	/* blue */
892   b->ansi_color[5]  = RGB(205,  0,205);	/* magenta */
893   b->ansi_color[6]  = RGB(  0,205,205);	/* cyan */
894   b->ansi_color[7]  = RGB(229,229,229);	/* white */
895 					/* bright/light versions */
896   b->ansi_color[8]  = RGB(127,127,127);	/* black */
897   b->ansi_color[9]  = RGB(255,  0,  0);	/* red */
898   b->ansi_color[10] = RGB(  0,255,  0);	/* green */
899   b->ansi_color[11] = RGB(255,255,  0);	/* yellow */
900   b->ansi_color[12] = RGB( 92, 92,255);	/* blue */
901   b->ansi_color[13] = RGB(255,  0,255);	/* magenta */
902   b->ansi_color[14] = RGB(  0,255,255);	/* cyan */
903   b->ansi_color[15] = RGB(255,255,255);	/* white */
904 #endif
905 }
906 
907 
908 
909 		 /*******************************
910 		 *	     ATTRIBUTES		*
911 		 *******************************/
912 
913 COLORREF
rlc_color(rlc_console con,int which,COLORREF c)914 rlc_color(rlc_console con, int which, COLORREF c)
915 { HDC hdc;
916   COLORREF old;
917   RlcData b = rlc_get_data(con);
918 
919   hdc = GetDC(NULL);
920   c = GetNearestColor(hdc, c);
921   ReleaseDC(NULL, hdc);
922 
923   switch(which)
924   { case RLC_WINDOW:
925       old = b->background;
926       b->background = c;
927       break;
928     case RLC_TEXT:
929       old = b->foreground;
930       b->foreground = c;
931       break;
932     case RLC_HIGHLIGHT:
933       old = b->sel_background;
934       b->sel_background = c;
935       break;
936     case RLC_HIGHLIGHTTEXT:
937       old = b->sel_foreground;
938       b->sel_foreground = c;
939       break;
940     default:
941       return (COLORREF)-1;
942   }
943 
944   if ( b->window )
945     InvalidateRect(b->window, NULL, TRUE);
946 
947   return old;
948 }
949 
950 
951 static int
rlc_kill(RlcData b)952 rlc_kill(RlcData b)
953 { DWORD_PTR result;
954 
955   switch(b->closing++)
956   { case 0:
957       b->queue->flags |= RLC_EOF;
958       PostThreadMessage(b->application_thread_id, WM_RLC_INPUT, 0, 0);
959       return TRUE;
960     case 1:
961       if ( _rlc_interrupt_hook )
962       { (*_rlc_interrupt_hook)(b, SIGINT);
963 	return TRUE;
964       }
965     default:
966       if ( !SendMessageTimeout(b->kill_window,
967 			       WM_DESTROY,
968 			       0, 0,
969 			       SMTO_ABORTIFHUNG,
970 			       5000,
971 			       &result) )
972       { if ( b->window )
973 	{ switch( MessageBox(b->window,
974 			     _T("Main task is not responding.")
975 			     _T("Click \"OK\" to terminate it"),
976 			     _T("Error"),
977 			     MB_OKCANCEL|MB_ICONEXCLAMATION|MB_APPLMODAL) )
978 	  { case IDCANCEL:
979 	      return FALSE;
980 	  }
981 	  TerminateThread(b->application_thread, 1);
982 
983 	  return TRUE;
984 	}
985       }
986   }
987 
988   return FALSE;
989 }
990 
991 
992 static void
rlc_interrupt(RlcData b)993 rlc_interrupt(RlcData b)
994 { if ( _rlc_interrupt_hook )
995     (*_rlc_interrupt_hook)((rlc_console)b, SIGINT);
996   else
997     raise(SIGINT);
998 }
999 
1000 
1001 static void
typed_char(RlcData b,int chr)1002 typed_char(RlcData b, int chr)
1003 { if ( chr == Control('C') && rlc_has_selection(b) )
1004   { rlc_copy(b);
1005     return;
1006   }
1007 
1008   rlc_set_selection(b, 0, 0, 0, 0);
1009 
1010   if ( chr == Control('C') )
1011     rlc_interrupt(b);
1012   else if ( chr == Control('V') || chr == Control('Y') )
1013     rlc_paste(b);
1014   else if ( b->queue )
1015     rlc_add_queue(b, b->queue, chr);
1016 }
1017 
1018 
1019 		 /*******************************
1020 		 *	 WINDOW PROCEDURE	*
1021 		 *******************************/
1022 
1023 #undef MAKEPOINTS
1024 
1025 static inline POINTS
MAKEPOINTS(LPARAM lParam)1026 MAKEPOINTS(LPARAM lParam)
1027 { union
1028   { LPARAM p;
1029     POINTS pt;
1030   } u;
1031 
1032   u.p = lParam;
1033   return u.pt;
1034 }
1035 
1036 
1037 static void
rlc_destroy(RlcData b)1038 rlc_destroy(RlcData b)
1039 { if ( b && b->window )
1040   { DestroyWindow(b->window);
1041     b->window = NULL;
1042     b->closing = 3;
1043   }
1044 }
1045 
1046 
1047 static int
IsDownKey(int code)1048 IsDownKey(int code)
1049 { short mask = GetKeyState(code);
1050 
1051   return mask & 0x8000;
1052 }
1053 
1054 
1055 static LRESULT WINAPI
rlc_wnd_proc(HWND hwnd,UINT message,WPARAM wParam,LPARAM lParam)1056 rlc_wnd_proc(HWND hwnd, UINT message, WPARAM wParam, LPARAM lParam)
1057 { RlcData b = (RlcData) GetWindowLongPtr(hwnd, GWL_DATA);
1058 
1059   switch(message)
1060   { case WM_CREATE:
1061       return 0;
1062 
1063     case WM_SIZE:
1064       if ( wParam != SIZE_MINIMIZED )
1065       { rlc_resize_pixel_units(b, LOWORD(lParam), HIWORD(lParam));
1066 	b->modified_options |= OPT_SIZE;
1067       }
1068       return 0;
1069 
1070     case WM_MOVE:
1071     { WINDOWPLACEMENT placement;
1072 
1073       placement.length = sizeof(placement);
1074       GetWindowPlacement(hwnd, &placement);
1075 
1076       if ( placement.showCmd == SW_SHOWNORMAL )
1077       { b->win_x = placement.rcNormalPosition.left;
1078 	b->win_y = placement.rcNormalPosition.top;
1079 
1080 	b->modified_options |= OPT_POSITION;
1081       }
1082 
1083       return 0;
1084     }
1085 
1086     case WM_SETFOCUS:
1087       b->has_focus = TRUE;
1088       CreateCaret(hwnd, NULL, b->fixedfont ? b->cw : 3, b->ch-1);
1089       rlc_place_caret(b);
1090       return 0;
1091 
1092     case WM_KILLFOCUS:
1093       b->has_focus = FALSE;
1094       b->caret_is_shown = FALSE;
1095       HideCaret(hwnd);
1096       DestroyCaret();
1097       return 0;
1098 
1099     case WM_PAINT:
1100       rlc_redraw(b);
1101       return 0;
1102 
1103     case WM_COMMAND:
1104     { UINT  item  = (UINT) LOWORD(wParam);
1105       const TCHAR *name;
1106 
1107       switch( item )
1108       { case IDM_PASTE:
1109 	  rlc_paste(b);
1110 	  return 0;
1111 	case IDM_COPY:
1112 	  rlc_copy(b);
1113 	  return 0;			/* no op: already done */
1114 	case IDM_CUT:
1115 	  break;			/* TBD: cut */
1116 	case IDM_BREAK:
1117 	  rlc_interrupt(b);
1118 	  break;
1119 	case IDM_FONT:
1120 	  rlc_queryfont(b);
1121 	  return 0;
1122 	case IDM_EXIT:
1123 	  if ( rlc_kill(b) )
1124 	    return 0;
1125 	  break;
1126       }
1127 
1128       if ( (name = lookupMenuId(item)) )
1129       { if ( _rlc_menu_hook )
1130 	{ (*_rlc_menu_hook)(b, name);
1131 	}
1132 
1133 	return 0;
1134       }
1135 
1136       break;
1137     }
1138 
1139   { int chr;
1140 
1141     case WM_KEYDOWN:			/* up is sent only once */
1142     { switch((int) wParam)
1143       { case VK_DELETE:	chr = 127;		break;
1144 	case VK_LEFT:	chr = Control('B');	break;
1145 	case VK_RIGHT:	chr = Control('F');	break;
1146 	case VK_UP:	chr = Control('P');	break;
1147 	case VK_DOWN:	chr = Control('N');	break;
1148 	case VK_HOME:	chr = Control('A');	break;
1149 	case VK_END:	chr = Control('E');	break;
1150         case VK_CANCEL: rlc_interrupt(b);       return 0;
1151 
1152         case VK_PRIOR:			/* page up */
1153 	{ int maxdo = rlc_count_lines(b, b->first, b->window_start);
1154 	  int pagdo = b->window_size - 1;
1155 	  b->window_start = rlc_add_lines(b, b->window_start,
1156 					  -min(maxdo, pagdo));
1157 
1158 	scrolledbykey:
1159 	  rlc_update_scrollbar(b);
1160 	  InvalidateRect(hwnd, NULL, FALSE);
1161 
1162 	  return 0;
1163 	}
1164 	case VK_NEXT:			/* page down */
1165 	{ int maxup = rlc_count_lines(b, b->window_start, b->last);
1166 	  int pagup = b->window_size - 1;
1167 	  b->window_start = rlc_add_lines(b, b->window_start,
1168 					  min(maxup, pagup));
1169 	  goto scrolledbykey;
1170 	}
1171 	default:
1172 	  goto break2;
1173       }
1174       if ( chr > 0 )
1175       { if ( IsDownKey(VK_CONTROL) )
1176 	  typed_char(b, ESC);
1177 
1178 	typed_char(b, chr);
1179 
1180 	return 0;
1181       }
1182     break2:
1183       break;
1184     }
1185 	case WM_UNICHAR:
1186 	  chr = (int)wParam;
1187 	  typed_char(b, chr);
1188 	  return 0;
1189     case WM_SYSCHAR:	typed_char(b, ESC); /* Play escape-something */
1190     case WM_CHAR:	chr = (int)wParam;
1191 
1192       typed_char(b, chr);
1193 
1194       return 0;
1195   }
1196 
1197 					/* selection handling */
1198     case WM_MBUTTONDOWN:
1199     middle_down:
1200       return 0;
1201 
1202     case WM_MBUTTONUP:
1203     middle_up:
1204       rlc_paste(b);
1205 
1206       return 0;
1207 
1208     case WM_LBUTTONDOWN:
1209     { POINTS pt;
1210 
1211       if ( emulate_three_buttons )
1212       { MSG msg;
1213 
1214 	Sleep(emulate_three_buttons);
1215 	if ( PeekMessage(&msg, hwnd,
1216 			 WM_RBUTTONDOWN, WM_RBUTTONDOWN, PM_REMOVE) )
1217 	{ emu_hwnd = hwnd;
1218 	  goto middle_down;
1219 	}
1220       }
1221 
1222       pt = MAKEPOINTS(lParam);
1223       rlc_start_selection(b, pt.x, pt.y);
1224 
1225       return 0;
1226     }
1227 
1228     case WM_LBUTTONUP:
1229     case WM_RBUTTONUP:
1230     if ( emu_hwnd == hwnd )
1231     { if ( wParam & (MK_RBUTTON|MK_LBUTTON) )
1232 	goto middle_up;
1233       else
1234       { emu_hwnd = 0;
1235 	return 0;
1236       }
1237     } else
1238     { rlc_copy(b);
1239 
1240       return 0;
1241     }
1242 
1243     case WM_LBUTTONDBLCLK:
1244     { POINTS pt = MAKEPOINTS(lParam);
1245 
1246       rlc_word_selection(b, pt.x, pt.y);
1247 
1248       return 0;
1249     }
1250 
1251     case WM_RBUTTONDOWN:
1252     { POINTS pt;
1253 
1254       if ( emulate_three_buttons )
1255       { MSG msg;
1256 
1257 	Sleep(emulate_three_buttons);
1258 	if ( PeekMessage(&msg, hwnd,
1259 			 WM_LBUTTONDOWN, WM_LBUTTONDOWN, PM_REMOVE) )
1260 	{ emu_hwnd = hwnd;
1261 	  goto middle_down;
1262 	}
1263       }
1264 
1265       pt = MAKEPOINTS(lParam);
1266       rlc_extend_selection(b, pt.x, pt.y);
1267 
1268       return 0;
1269     }
1270 
1271     case WM_MOUSEMOVE:
1272     { POINTS pt = MAKEPOINTS(lParam);
1273 
1274       if ( (wParam & (MK_LBUTTON|MK_RBUTTON)) &&
1275 	   (wParam & (MK_LBUTTON|MK_RBUTTON)) != (MK_LBUTTON|MK_RBUTTON) )
1276       { rlc_extend_selection(b, pt.x, pt.y);
1277 
1278 	return 0;
1279       }
1280 
1281       break;
1282     }
1283 
1284     case WM_MOUSEWHEEL:
1285     { short angle = (short)HIWORD(wParam);
1286 
1287       if ( angle < 0 )
1288       { if ( b->window_start != b->last )
1289 	  b->window_start = NextLine(b, b->window_start);
1290       } else
1291       { if ( b->window_start != b->first )
1292 	  b->window_start = PrevLine(b, b->window_start);
1293       }
1294 
1295       rlc_update_scrollbar(b);
1296       InvalidateRect(hwnd, NULL, FALSE);
1297 
1298       return 0;
1299     }
1300 					/* scrolling */
1301     case WM_VSCROLL:
1302     { switch( LOWORD(wParam) )
1303       { case SB_LINEUP:
1304 	  if ( b->window_start != b->first )
1305 	    b->window_start = PrevLine(b, b->window_start);
1306 	  break;
1307 	case SB_LINEDOWN:
1308 	  if ( b->window_start != b->last )
1309 	    b->window_start = NextLine(b, b->window_start);
1310 	  break;
1311 	case SB_PAGEUP:
1312 	{ int maxdo = rlc_count_lines(b, b->first, b->window_start);
1313 	  int pagdo = b->window_size - 1;
1314 	  b->window_start = rlc_add_lines(b, b->window_start,
1315 					  -min(maxdo, pagdo));
1316 	  break;
1317 	}
1318 	case SB_PAGEDOWN:
1319 	{ int maxup = rlc_count_lines(b, b->window_start, b->last);
1320 	  int pagup = b->window_size - 1;
1321 	  b->window_start = rlc_add_lines(b, b->window_start,
1322 					  min(maxup, pagup));
1323 	  break;
1324 	}
1325 	case SB_THUMBTRACK:
1326 	  b->window_start = rlc_add_lines(b, b->first, HIWORD(wParam));
1327 	  break;
1328       }
1329 
1330       rlc_update_scrollbar(b);
1331       InvalidateRect(hwnd, NULL, FALSE);
1332 
1333       return 0;
1334     }
1335 
1336     case WM_TIMER:
1337       if ( _rlc_timer_hook && wParam >= RLC_APPTIMER_ID )
1338       { (*_rlc_timer_hook)((int) wParam);
1339 
1340 	return 0;
1341       }
1342       break;
1343 
1344     case WM_RENDERALLFORMATS:
1345       if ( _rlc_render_all_hook )
1346       { (*_rlc_render_all_hook)();
1347 
1348         return 0;
1349       }
1350       break;
1351 
1352     case WM_RENDERFORMAT:
1353       if ( _rlc_render_hook && (*_rlc_render_hook)(wParam) )
1354         return 0;
1355 
1356       break;
1357 
1358     case WM_ERASEBKGND:
1359     { HDC hdc = (HDC) wParam;
1360       RECT rect;
1361       HBRUSH hbrush;
1362       COLORREF rgb = b->background;
1363 
1364       hbrush = CreateSolidBrush(rgb);
1365       GetClipBox(hdc, &rect);
1366       FillRect(hdc, &rect, hbrush);
1367       DeleteObject(hbrush);
1368 
1369       return 1;				/* non-zero: I've erased it */
1370     }
1371 
1372     case WM_SYSCOLORCHANGE:
1373       b->foreground     = GetSysColor(COLOR_WINDOWTEXT);
1374       b->background     = GetSysColor(COLOR_WINDOW);
1375       b->sel_foreground = GetSysColor(COLOR_HIGHLIGHTTEXT);
1376       b->sel_background = GetSysColor(COLOR_HIGHLIGHT);
1377       return 0;
1378 
1379     case WM_RLC_WRITE:
1380     { int count = (int)wParam;
1381       TCHAR *buf = (TCHAR *)lParam;
1382 
1383       if ( OQSIZE - b->output_queued > count )
1384       { _tcsncpy(&b->output_queue[b->output_queued], buf, count);
1385 	b->output_queued += count;
1386       } else
1387       { if ( b->output_queued > 0 )
1388 	  rlc_flush_output(b);
1389 
1390 	if ( count <= OQSIZE )
1391 	{ _tcsncpy(b->output_queue, buf, count);
1392 	  b->output_queued = count;
1393 	} else
1394 	  rlc_do_write(b, buf, count);
1395       }
1396 
1397       return 0;
1398     }
1399 
1400     case WM_RLC_FLUSH:
1401     { rlc_flush_output(b);
1402       return 0;
1403     }
1404 
1405     case WM_RLC_MENU:
1406     { rlc_menu_action((rlc_console) b, (struct menu_data*)lParam);
1407 
1408       return 0;
1409     }
1410 
1411     case WM_RLC_CLOSEWIN:
1412       return 0;
1413 
1414     case WM_CLOSE:
1415       if ( rlc_kill(b) )
1416         return 0;
1417       break;
1418 
1419     case WM_DESTROY:
1420       b->window = NULL;
1421       PostQuitMessage(0);
1422       return 0;
1423   }
1424 
1425   return DefWindowProc(hwnd, message, wParam, lParam);
1426 }
1427 
1428 static int
rlc_get_message(MSG * msg,HWND hwnd,UINT low,UINT high)1429 rlc_get_message(MSG *msg, HWND hwnd, UINT low, UINT high)
1430 { int rc;
1431 again:
1432   if ( (rc=GetMessage(msg, hwnd, low, high)) )
1433   { if ( _rlc_message_hook &&
1434 	 (*_rlc_message_hook)(msg->hwnd, msg->message,
1435 			      msg->wParam, msg->lParam) )
1436       goto again;
1437   }
1438 
1439   return rc;
1440 }
1441 
1442 
1443 static void
rlc_dispatch(RlcData b)1444 rlc_dispatch(RlcData b)
1445 { MSG msg;
1446 
1447   if ( rlc_get_message(&msg, NULL, 0, 0) && msg.message != WM_RLC_CLOSEWIN )
1448   { /* DEBUG(Dprintf("Thread %x got message 0x%04x\n",
1449 		     GetCurrentThreadId(), msg.message));
1450     */
1451     TranslateMessage(&msg);
1452     DispatchMessage(&msg);
1453     rlc_flush_output(b);
1454     return;
1455   } else
1456   { DEBUG(Dprintf(_T("Thread %x got WM_RLC_CLOSEWIN\n"),
1457 		  GetCurrentThreadId()));
1458     b->queue->flags |= RLC_EOF;
1459   }
1460 }
1461 
1462 
1463 void
rlc_yield()1464 rlc_yield()
1465 { MSG msg;
1466 
1467   while ( PeekMessage(&msg, NULL, 0, 0, PM_REMOVE) )
1468   { TranslateMessage(&msg);
1469     DispatchMessage(&msg);
1470   }
1471 }
1472 
1473 		 /*******************************
1474 		 *	 CHARACTER TYPES	*
1475 		 *******************************/
1476 
1477 static void
rlc_init_word_chars()1478 rlc_init_word_chars()
1479 { int i;
1480 
1481   for(i=0; i<CHAR_MAX; i++)
1482     _rlc_word_chars[i] = (isalnum(i) || i == '_') ? TRUE : FALSE;
1483 }
1484 
1485 
1486 void
rlc_word_char(int chr,int isword)1487 rlc_word_char(int chr, int isword)
1488 { if ( chr > 0 && chr < CHAR_MAX )
1489     _rlc_word_chars[chr] = isword;
1490 }
1491 
1492 
1493 int
rlc_is_word_char(int chr)1494 rlc_is_word_char(int chr)
1495 { if ( chr > 0 && chr < CHAR_MAX )
1496     return _rlc_word_chars[chr];
1497 
1498   return _istalnum((wint_t)chr);	/* only UNICODE version */
1499 }
1500 
1501 
1502 		 /*******************************
1503 		 *	    SELECTION		*
1504 		 *******************************/
1505 
1506 #define SelLT(l1, c1, l2, c2) ((l1) < (l2) || ((l1) == (l2) && (c1) < (c2)))
1507 #define SelEQ(l1, c1, l2, c2) ((l1) == (l2) && (c1) == (c2))
1508 
1509 static int
rlc_min(RlcData b,int x,int y)1510 rlc_min(RlcData b, int x, int y)
1511 { if ( rlc_count_lines(b, b->first, x) < rlc_count_lines(b, b->first, y) )
1512     return x;
1513 
1514   return y;
1515 }
1516 
1517 
1518 static int
rlc_max(RlcData b,int x,int y)1519 rlc_max(RlcData b, int x, int y)
1520 { if ( rlc_count_lines(b, b->first, x) > rlc_count_lines(b, b->first, y) )
1521     return x;
1522 
1523   return y;
1524 }
1525 
1526 
1527 static void
rlc_changed_line(RlcData b,int i,int mask)1528 rlc_changed_line(RlcData b, int i, int mask)
1529 { b->lines[i].changed |= mask;
1530 }
1531 
1532 
1533 static void
rlc_set_selection(RlcData b,int sl,int sc,int el,int ec)1534 rlc_set_selection(RlcData b, int sl, int sc, int el, int ec)
1535 { int sch = rlc_min(b, sl, b->sel_start_line);
1536   int ech = rlc_max(b, el, b->sel_end_line);
1537   int nel = NextLine(b, el);
1538   int nsel= NextLine(b, b->sel_end_line);
1539   int i;
1540   int innow  = FALSE;
1541   int insoon = FALSE;
1542 
1543 					/* find the lines that changed */
1544   for(i=sch; ; i = NextLine(b, i))
1545   { if ( i == sl )
1546     { insoon = TRUE;
1547       if ( i == b->sel_start_line )
1548       { innow = TRUE;
1549 	if ( sc != b->sel_start_char ||
1550 	     (i == el && i != b->sel_end_line) ||
1551 	     (i == b->sel_end_line && i != el) )
1552 	  rlc_changed_line(b, i, CHG_CHANGED);
1553       } else
1554 	rlc_changed_line(b, i, CHG_CHANGED);
1555     } else if ( i == b->sel_start_line )
1556     { innow = TRUE;
1557       rlc_changed_line(b, i, CHG_CHANGED);
1558     }
1559 
1560     if ( i == b->sel_end_line )
1561     { if ( (i == el && ec != b->sel_end_char) || el != i )
1562 	rlc_changed_line(b, i, CHG_CHANGED);
1563     }
1564 
1565     if ( innow != insoon )
1566       rlc_changed_line(b, i, CHG_CHANGED);
1567 
1568     if ( i == nel )
1569     { insoon = FALSE;
1570       if ( i == nsel )
1571 	innow = FALSE;
1572       else
1573 	rlc_changed_line(b, i, CHG_CHANGED);
1574     } else if ( i == nsel )
1575     { innow = FALSE;
1576       rlc_changed_line(b, i, CHG_CHANGED);
1577     }
1578 
1579     if ( i == ech )
1580       break;
1581   }
1582 
1583 					/* update the attributes */
1584   b->sel_start_line = sl;
1585   b->sel_start_char = sc;
1586   b->sel_end_line   = el;
1587   b->sel_end_char   = ec;
1588 
1589 					/* ... and request a repaint */
1590   rlc_request_redraw(b);
1591 }
1592 
1593 
1594 void
rlc_translate_mouse(RlcData b,int x,int y,int * line,int * chr)1595 rlc_translate_mouse(RlcData b, int x, int y, int *line, int *chr)
1596 { int ln = b->window_start;
1597   int n = b->window_size;		/* # lines */
1598   TextLine tl;
1599   x-= b->cw;				/* margin */
1600 
1601   if ( !b->window )
1602     return;
1603 
1604   while( y > b->ch && ln != b->last && n-- > 0 )
1605   { ln = NextLine(b, ln);
1606     y -= b->ch;
1607   }
1608   *line = ln;
1609   tl = &b->lines[ln];
1610 
1611   if ( b->fixedfont )
1612   { *chr = min(x/b->cw, tl->size);
1613   } else if ( tl->size == 0 )
1614   { *chr = 0;
1615   } else
1616   { text_char *s = tl->text;
1617     HDC hdc = GetDC(b->window);
1618     int f = 0;
1619     int t = tl->size;
1620     int m = (f+t)/2;
1621     int i;
1622 
1623     SelectObject(hdc, b->hfont);
1624 
1625     for(i=10; --i > 0; m=(f+t)/2)
1626     { int w;
1627 
1628       w = text_width(b, hdc, s, m);
1629       if ( x > w )
1630       { int cw;
1631 
1632 	GetCharWidth32(hdc, s[m].code, s[m].code, &cw);
1633 	if ( x < w+cw )
1634 	{ *chr = m;
1635 	  return;
1636 	}
1637 	f = m+1;
1638       } else
1639       { t = m;
1640       }
1641     }
1642 
1643     *chr = m;
1644   }
1645 }
1646 
1647 
1648 static void
rlc_start_selection(RlcData b,int x,int y)1649 rlc_start_selection(RlcData b, int x, int y)
1650 { int l, c;
1651 
1652   rlc_translate_mouse(b, x, y, &l, &c);
1653   b->sel_unit = SEL_CHAR;
1654   b->sel_org_line = l;
1655   b->sel_org_char = c;
1656   rlc_set_selection(b, l, c, l, c);
1657 }
1658 
1659 
1660 static int				/* v >= f && v <= t */
rlc_between(RlcData b,int f,int t,int v)1661 rlc_between(RlcData b, int f, int t, int v)
1662 { int h = rlc_count_lines(b, b->first, v);
1663 
1664   if ( h >= rlc_count_lines(b, b->first, f) &&
1665        h <= rlc_count_lines(b, b->first, t) )
1666     return TRUE;
1667 
1668   return FALSE;
1669 }
1670 
1671 
1672 static void
rlc_word_selection(RlcData b,int x,int y)1673 rlc_word_selection(RlcData b, int x, int y)
1674 { int l, c;
1675 
1676   rlc_translate_mouse(b, x, y, &l, &c);
1677   if ( rlc_between(b, b->first, b->last, l) )
1678   { TextLine tl = &b->lines[l];
1679 
1680     if ( c < tl->size && rlc_is_word_char(tl->text[c].code) )
1681     { int f, t;
1682 
1683       for(f=c; f>0 && rlc_is_word_char(tl->text[f-1].code); f--)
1684 	;
1685       for(t=c; t<tl->size && rlc_is_word_char(tl->text[t].code); t++)
1686 	;
1687       rlc_set_selection(b, l, f, l, t);
1688     }
1689   }
1690 
1691   b->sel_unit = SEL_WORD;
1692 }
1693 
1694 
1695 static void
rlc_extend_selection(RlcData b,int x,int y)1696 rlc_extend_selection(RlcData b, int x, int y)
1697 { int l, c;
1698   int el = b->sel_org_line;
1699   int ec = b->sel_org_char;
1700 
1701   rlc_translate_mouse(b, x, y, &l, &c);
1702   if ( SelLT(l, c, b->sel_org_line, b->sel_org_char) )
1703   { if ( b->sel_unit == SEL_WORD )
1704     { if ( rlc_between(b, b->first, b->last, l) )
1705       { TextLine tl = &b->lines[l];
1706 
1707 	if ( c < tl->size && rlc_is_word_char(tl->text[c].code) )
1708 	  for(; c > 0 && rlc_is_word_char(tl->text[c-1].code); c--)
1709 	    ;
1710       }
1711       if ( rlc_between(b, b->first, b->last, el) )
1712       { TextLine tl = &b->lines[el];
1713 
1714 	if ( ec < tl->size && rlc_is_word_char(tl->text[ec].code) )
1715 	  for(; ec < tl->size && rlc_is_word_char(tl->text[ec].code); ec++)
1716 	    ;
1717       }
1718     } else if ( b->sel_unit == SEL_LINE )
1719       c = 0;
1720     rlc_set_selection(b, l, c, el, ec);
1721   } else if ( SelLT(b->sel_org_line, b->sel_org_char, l, c) )
1722   { if ( b->sel_unit == SEL_WORD )
1723     { if ( rlc_between(b, b->first, b->last, l) )
1724       { TextLine tl = &b->lines[l];
1725 
1726 	if ( c < tl->size && rlc_is_word_char(tl->text[c].code) )
1727 	  for(; c < tl->size && rlc_is_word_char(tl->text[c].code); c++)
1728 	    ;
1729       }
1730       if ( rlc_between(b, b->first, b->last, el) )
1731       { TextLine tl = &b->lines[el];
1732 
1733 	if ( ec < tl->size && rlc_is_word_char(tl->text[ec].code) )
1734 	  for(; ec > 0 && rlc_is_word_char(tl->text[ec-1].code); ec--)
1735 	    ;
1736       }
1737     } else if ( b->sel_unit == SEL_LINE )
1738       c = b->width;
1739     rlc_set_selection(b, el, ec, l, c);
1740   }
1741 }
1742 
1743 
1744 static TCHAR *
rlc_read_from_window(RlcData b,int sl,int sc,int el,int ec)1745 rlc_read_from_window(RlcData b, int sl, int sc, int el, int ec)
1746 { int bufsize = 256;
1747   TCHAR *buf;
1748   int i = 0;
1749 
1750   if ( el < sl || (el == sl && ec < sc) )
1751     return NULL;			/* invalid region */
1752   if ( !(buf = rlc_malloc(bufsize * sizeof(TCHAR))) )
1753     return NULL;			/* not enough memory */
1754 
1755   for( ; ; sc = 0, sl = NextLine(b, sl))
1756   { TextLine tl = &b->lines[sl];
1757     if ( tl )
1758     { int e = (sl == el ? ec : tl->size);
1759 
1760       if ( e > tl->size )
1761 	e = tl->size;
1762 
1763       while(sc < e)
1764       { if ( i+1 >= bufsize )
1765 	{ bufsize *= 2;
1766 	  if ( !(buf = rlc_realloc(buf, bufsize * sizeof(TCHAR))) )
1767 	    return NULL;		/* not enough memory */
1768 	}
1769 	buf[i++] = tl->text[sc++].code;
1770       }
1771     }
1772 
1773     if ( sl == el || sl == b->last )
1774     { buf[i++] = '\0';			/* Always room for the 0 */
1775       return buf;
1776     }
1777 
1778     if ( tl && !tl->softreturn )
1779     { if ( i+2 >= bufsize )
1780       { bufsize *= 2;
1781 	if ( !(buf = rlc_realloc(buf, bufsize * sizeof(TCHAR))) )
1782 	  return NULL;			/* not enough memory */
1783       }
1784       buf[i++] = '\r';			/* Bill ... */
1785       buf[i++] = '\n';
1786     }
1787   }
1788 }
1789 
1790 
1791 static int
rlc_has_selection(RlcData b)1792 rlc_has_selection(RlcData b)
1793 { if ( SelEQ(b->sel_start_line, b->sel_start_char,
1794 	     b->sel_end_line,   b->sel_end_char) )
1795     return FALSE;
1796   return TRUE;
1797 }
1798 
1799 
1800 static TCHAR *
rlc_selection(RlcData b)1801 rlc_selection(RlcData b)
1802 { if ( rlc_has_selection(b) )
1803     return rlc_read_from_window(b,
1804 				b->sel_start_line, b->sel_start_char,
1805 				b->sel_end_line,   b->sel_end_char);
1806   return NULL;
1807 }
1808 
1809 
1810 static void
rlc_copy(RlcData b)1811 rlc_copy(RlcData b)
1812 { TCHAR *sel = rlc_selection(b);
1813 
1814   if ( sel && b->window )
1815   { size_t size = _tcslen(sel);
1816     HGLOBAL mem = GlobalAlloc(GMEM_MOVEABLE, (size + 1)*sizeof(TCHAR));
1817     TCHAR far *data;
1818     size_t i;
1819 
1820     if ( !mem )
1821     { MessageBox(NULL, _T("Not enough memory to copy"), _T("Error"), MB_OK);
1822       return;
1823     }
1824     data = GlobalLock(mem);
1825 
1826     for(i=0; i<size; i++)
1827       *data++ = sel[i];
1828     *data = '\0';
1829 
1830     GlobalUnlock(mem);
1831     OpenClipboard(b->window);
1832     EmptyClipboard();
1833 #ifdef UNICODE
1834     SetClipboardData(CF_UNICODETEXT, mem);
1835 #else
1836     SetClipboardData(CF_TEXT, mem);
1837 #endif
1838     CloseClipboard();
1839 
1840     rlc_free(sel);
1841   }
1842 }
1843 
1844 
1845 
1846 		 /*******************************
1847 		 *           REPAINT		*
1848 		 *******************************/
1849 
1850 static void
rlc_place_caret(RlcData b)1851 rlc_place_caret(RlcData b)
1852 { if ( b->has_focus && b->window )
1853   { int line = rlc_count_lines(b, b->window_start, b->caret_y);
1854 
1855     if ( line < b->window_size )
1856     { if ( b->fixedfont )
1857       { SetCaretPos((b->caret_x + 1) * b->cw, line * b->ch);
1858       } else
1859       { HDC hdc = GetDC(b->window);
1860 	int tw;
1861 	TextLine tl = &b->lines[b->caret_y];
1862 	HFONT old;
1863 
1864 	old = SelectObject(hdc, b->hfont);
1865 	tw = text_width(b, hdc, tl->text, b->caret_x);
1866 	SelectObject(hdc, old);
1867 	ReleaseDC(b->window, hdc);
1868 
1869 	SetCaretPos(b->cw + tw, line * b->ch);
1870       }
1871       if ( !b->caret_is_shown )
1872       { ShowCaret(b->window);
1873 	b->caret_is_shown = TRUE;
1874 
1875 	return;
1876       }
1877     } else
1878     { if ( b->caret_is_shown == TRUE )
1879       { HideCaret(b->window);
1880 	b->caret_is_shown = FALSE;
1881       }
1882     }
1883   }
1884 
1885   b->caret_is_shown = FALSE;
1886 }
1887 
1888 
1889 static void
rlc_update_scrollbar(RlcData b)1890 rlc_update_scrollbar(RlcData b)
1891 { if ( b->window )
1892   { int nsb_lines = rlc_count_lines(b, b->first, b->last);
1893     int nsb_start = rlc_count_lines(b, b->first, b->window_start);
1894 
1895     if ( nsb_lines != b->sb_lines ||
1896 	 nsb_start != b->sb_start )
1897     { SetScrollRange(b->window, SB_VERT, 0, nsb_lines, FALSE);
1898       SetScrollPos(  b->window, SB_VERT, nsb_start, TRUE);
1899 
1900       b->sb_lines = nsb_lines;
1901       b->sb_start = nsb_start;
1902     }
1903   }
1904 }
1905 
1906 
1907 static void
rcl_paint_text(RlcData b,HDC hdc,TextLine tl,int from,int to,int ty,int * cx,int insel)1908 rcl_paint_text(RlcData b, HDC hdc,
1909 	       TextLine tl, int from, int to,
1910 	       int ty, int *cx, int insel)
1911 { text_char *chars, *s;
1912   text_char buf[MAXLINE];
1913   TCHAR text[MAXLINE];
1914   TCHAR *t;
1915   int len = to-from;
1916   int i;
1917 
1918   if ( len <= 0 )
1919     return;
1920 
1921   if ( tl->text && to <= tl->size )
1922   { chars = &tl->text[from];
1923   } else
1924   { text_char *o;
1925     int copy;
1926 
1927     o = chars = buf;
1928     s = &tl->text[from];
1929     copy = tl->text ? tl->size-from : 0;
1930     for(i=0; i<copy; i++)
1931       *o++ = *s++;
1932     for(; i<len; i++, o++)
1933     { o->code = ' ';
1934       o->flags = TF_DEFAULT;
1935     }
1936   }
1937 
1938   for(t=text, s=chars, i=0; i < len; i++, t++, s++)
1939     *t = s->code;
1940 
1941   if ( insel )					/* TBD: Cache */
1942   { SetBkColor(hdc, b->sel_background);
1943     SetTextColor(hdc, b->sel_foreground);
1944     TextOut(hdc, *cx, ty, text, len);
1945     *cx += tchar_width(b, hdc, text, len);
1946   } else
1947   { int start, segment;
1948 
1949     for(start=0, s=chars, t=text;
1950 	start<len;
1951 	start+=segment, s+=segment, t+=segment)
1952     { text_flags flags = s->flags;
1953       int left = len-start;
1954 
1955       for(segment=0; s[segment].flags == flags && segment<left; segment++)
1956 	;
1957 
1958       if ( TF_FG(flags) == ANSI_COLOR_DEFAULT )
1959 	SetTextColor(hdc, b->foreground);
1960       else
1961 	SetTextColor(hdc, b->ansi_color[TF_FG(flags)]);
1962 
1963       if ( TF_BG(flags) == ANSI_COLOR_DEFAULT )
1964 	SetBkColor(hdc, b->background);
1965       else
1966 	SetBkColor(hdc, b->ansi_color[TF_BG(flags)]);
1967 
1968       TextOut(hdc, *cx, ty, t, segment);
1969       if ( TF_BOLD(flags) )
1970       { SetBkMode(hdc, TRANSPARENT);
1971 	TextOut(hdc, (*cx)+1, ty, t, segment);
1972 	TextOut(hdc, *cx, ty+1, t, segment);
1973 	SetBkMode(hdc, OPAQUE);
1974       }
1975       *cx += tchar_width(b, hdc, t, segment);
1976     }
1977   }
1978 }
1979 
1980 
1981 static void
rlc_redraw(RlcData b)1982 rlc_redraw(RlcData b)
1983 { PAINTSTRUCT ps;
1984   HDC hdc = BeginPaint(b->window, &ps);
1985   int sl = max(0, ps.rcPaint.top/b->ch);
1986   int el = min(b->window_size, ps.rcPaint.bottom/b->ch);
1987   int l = rlc_add_lines(b, b->window_start, sl);
1988   int pl = sl;				/* physical line */
1989   RECT rect;
1990   HBRUSH bg;
1991   int stockbg;
1992   int insel = FALSE;			/* selected lines? */
1993 
1994   SelectObject(hdc, b->hfont);
1995   SetTextColor(hdc, b->foreground);
1996   SetBkColor(hdc, b->background);
1997 
1998   if ( b->background == RGB(255, 255, 255) )
1999   { bg = GetStockObject(WHITE_BRUSH);
2000     stockbg = TRUE;
2001   } else
2002   { bg = CreateSolidBrush(b->background);
2003     stockbg = FALSE;
2004   }
2005 
2006   if ( b->has_focus && b->caret_is_shown )
2007   { HideCaret(b->window);
2008     b->caret_is_shown = FALSE;
2009   }
2010 
2011   if ( rlc_count_lines(b, b->first, b->sel_start_line) <
2012        rlc_count_lines(b, b->first, l) &&
2013        rlc_count_lines(b, b->first, b->sel_end_line) >=
2014        rlc_count_lines(b, b->first, l) )
2015     insel = TRUE;
2016 
2017   if ( insel )
2018   { SetBkColor(hdc, b->sel_background);
2019     SetTextColor(hdc, b->sel_foreground);
2020   }
2021 
2022   for(; pl <= el; l = NextLine(b, l), pl++)
2023   { TextLine tl = &b->lines[l];
2024     int ty = b->ch * pl;
2025     int cx = b->cw;
2026 
2027     rect.top    = ty;
2028     rect.bottom = rect.top + b->ch;
2029 
2030 					/* compute selection */
2031     if ( l == b->sel_start_line )
2032     { int cf = b->sel_start_char;
2033       int ce = (b->sel_end_line != b->sel_start_line ? b->width
2034 						     : b->sel_end_char);
2035 
2036       rcl_paint_text(b, hdc, tl,  0, cf, ty, &cx, insel);
2037       insel = TRUE;
2038       rcl_paint_text(b, hdc, tl, cf, ce, ty, &cx, insel);
2039       if ( l == b->sel_end_line )
2040       { insel = FALSE;
2041 	rcl_paint_text(b, hdc, tl, ce, b->width, ty, &cx, insel);
2042       } else
2043 	insel = TRUE;
2044     } else if ( l == b->sel_end_line )	/* end of selection */
2045     { int ce = b->sel_end_char;
2046 
2047       rcl_paint_text(b, hdc, tl, 0, ce, ty, &cx, insel);
2048       insel = FALSE;
2049       rcl_paint_text(b, hdc, tl, ce, b->width, ty, &cx, insel);
2050     } else				/* entire line in/out selection */
2051     { rcl_paint_text(b, hdc, tl, 0, b->width, ty, &cx, insel);
2052     }
2053 
2054 					/* clear remainder of line */
2055     if ( cx < b->width * (b->cw+1) )
2056     { rect.left   = cx;
2057       rect.right  = b->width * (b->cw+1);
2058       rect.top    = b->ch * pl;
2059       rect.bottom = rect.top + b->ch;
2060       FillRect(hdc, &rect, bg);
2061     }
2062 
2063     tl->changed = CHG_RESET;
2064 
2065     if ( l == b->last )			/* clear to end of window */
2066     { rect.left   = b->cw;
2067       rect.right  = b->width * (b->cw+1);
2068       rect.top    = b->ch * (pl+1);
2069       rect.bottom = b->ch * (el+1);
2070       FillRect(hdc, &rect, bg);
2071 
2072       break;
2073     }
2074   }
2075   rlc_place_caret(b);
2076 
2077   b->changed = CHG_RESET;
2078   if ( !stockbg )
2079     DeleteObject(bg);
2080 
2081   EndPaint(b->window, &ps);
2082 
2083   rlc_update_scrollbar(b);
2084 }
2085 
2086 
2087 static void
rlc_request_redraw(RlcData b)2088 rlc_request_redraw(RlcData b)
2089 { if ( b->changed & CHG_CHANGED )
2090   { if ( b->window )
2091       InvalidateRect(b->window, NULL, FALSE);
2092   } else
2093   { int i = b->window_start;
2094     int y = 0;
2095     RECT rect;
2096     int first = TRUE;
2097 
2098     rect.left = b->cw;
2099     rect.right = (b->width+1) * b->cw;
2100 
2101     for(; y < b->window_size; y++, i = NextLine(b, i))
2102     { TextLine l = &b->lines[i];
2103 
2104       if ( l->changed & CHG_CHANGED )
2105       { if ( first )
2106 	{ rect.top = y * b->ch;
2107 	  rect.bottom = rect.top + b->ch;
2108 	  first = FALSE;
2109 	} else
2110 	  rect.bottom = (y+1) * b->ch;
2111       }
2112       if ( i == b->last )
2113 	break;
2114     }
2115 
2116     if ( !first && b->window )
2117       InvalidateRect(b->window, &rect, FALSE);
2118     else if ( b->changed & CHG_CARET )
2119       rlc_place_caret(b);
2120   }
2121 }
2122 
2123 
2124 static void
rlc_normalise(RlcData b)2125 rlc_normalise(RlcData b)
2126 { if ( rlc_count_lines(b, b->window_start, b->caret_y) >= b->window_size )
2127   { b->window_start = rlc_add_lines(b, b->caret_y, -(b->window_size-1));
2128     b->changed |= CHG_CARET|CHG_CLEAR|CHG_CHANGED;
2129     rlc_request_redraw(b);
2130   }
2131 }
2132 
2133 
2134 static void
rlc_resize_pixel_units(RlcData b,int w,int h)2135 rlc_resize_pixel_units(RlcData b, int w, int h)
2136 { int nw = max(20, w/b->cw)-2;		/* 1 character space for margins */
2137   int nh = max(1, h/b->ch);
2138 
2139   DEBUG(Dprintf(_T("rlc_resize_pixel_units(%p, %d, %d) (%dx%d)\n"),
2140 		b, w, h, nw, nh));
2141 
2142   if ( b->width == nw && b->window_size == nh )
2143     return;				/* no real change */
2144 
2145   rlc_resize(b, nw, nh);
2146 
2147   if ( _rlc_resize_hook )
2148     (*_rlc_resize_hook)(b->width, b->window_size);
2149   else
2150   {
2151 #ifdef SIGWINCH
2152     raise(SIGWINCH);
2153 #endif
2154   }
2155 
2156   rlc_request_redraw(b);
2157 }
2158 
2159 		 /*******************************
2160 		 *	       FONT		*
2161 		 *******************************/
2162 
2163 static void
rlc_init_text_dimensions(RlcData b,HFONT font)2164 rlc_init_text_dimensions(RlcData b, HFONT font)
2165 { HDC hdc;
2166   TEXTMETRIC tm;
2167 
2168   if ( font )
2169   { b->hfont = font;
2170   } else if ( b->create_attributes )
2171   { rlc_console_attr *a = b->create_attributes;
2172     if ( !a->face_name[0] )
2173       b->hfont = GetStockObject(ANSI_FIXED_FONT);
2174     else
2175     { LOGFONT lfont;
2176 
2177       memset(&lfont, 0, sizeof(lfont));
2178 
2179       lfont.lfHeight          = a->font_size;
2180       lfont.lfWeight          = a->font_weight;
2181       lfont.lfPitchAndFamily  = a->font_family;
2182       lfont.lfCharSet	      = a->font_char_set;
2183       _tcsncpy(lfont.lfFaceName, a->face_name, 31);
2184 
2185       if ( !(b->hfont = CreateFontIndirect(&lfont)) )
2186 	b->hfont = GetStockObject(ANSI_FIXED_FONT);
2187     }
2188   } else
2189     b->hfont = GetStockObject(ANSI_FIXED_FONT);
2190 
2191 					/* test for fixed?*/
2192   hdc = GetDC(NULL);
2193   SelectObject(hdc, b->hfont);
2194   GetTextMetrics(hdc, &tm);
2195   b->cw = tm.tmAveCharWidth;
2196   b->cb = tm.tmHeight;
2197   b->ch = tm.tmHeight + tm.tmExternalLeading;
2198   b->fixedfont = (tm.tmPitchAndFamily & TMPF_FIXED_PITCH ? FALSE : TRUE);
2199   ReleaseDC(NULL, hdc);
2200 
2201   if ( b->window )
2202   { RECT rect;
2203 
2204     if ( b->has_focus == TRUE )
2205     { CreateCaret(b->window, NULL, b->fixedfont ? b->cw : 3, b->ch-1);
2206       rlc_place_caret(b);
2207     }
2208 
2209     GetClientRect(b->window, &rect);
2210     rlc_resize_pixel_units(b, rect.right - rect.left, rect.bottom - rect.top);
2211   }
2212 }
2213 
2214 
2215 static int
text_width(RlcData b,HDC hdc,const text_char * text,int len)2216 text_width(RlcData b, HDC hdc, const text_char *text, int len)
2217 { if ( b->fixedfont )
2218   { return len * b->cw;
2219   } else
2220   { SIZE size;
2221     TCHAR tmp[MAXLINE];
2222     int i;
2223 
2224     for(i=0; i<len; i++)
2225       tmp[i] = text[i].code;
2226 
2227     GetTextExtentPoint32(hdc, tmp, len, &size);
2228     return size.cx;
2229   }
2230 }
2231 
2232 
2233 static int
tchar_width(RlcData b,HDC hdc,const TCHAR * text,int len)2234 tchar_width(RlcData b, HDC hdc, const TCHAR *text, int len)
2235 { if ( b->fixedfont )
2236   { return len * b->cw;
2237   } else
2238   { SIZE size;
2239 
2240     GetTextExtentPoint32(hdc, text, len, &size);
2241     return size.cx;
2242   }
2243 }
2244 
2245 
2246 static void
rlc_save_font_options(HFONT font,rlc_console_attr * attr)2247 rlc_save_font_options(HFONT font, rlc_console_attr *attr)
2248 { if ( font == GetStockObject(ANSI_FIXED_FONT) )
2249   { attr->face_name[0] = '\0';
2250   } else
2251   { LOGFONT lf;
2252 
2253     if ( GetObject(font, sizeof(lf), &lf) )
2254     { memcpy(attr->face_name, lf.lfFaceName, sizeof(attr->face_name)-1);
2255 
2256       attr->font_family   = lf.lfPitchAndFamily;
2257       attr->font_size     = lf.lfHeight;
2258       attr->font_weight   = lf.lfWeight;
2259       attr->font_char_set = lf.lfCharSet;
2260     }
2261   }
2262 }
2263 
2264 
2265 		 /*******************************
2266 		 *	   FONT SELECTION	*
2267 		 *******************************/
2268 
2269 static void
rlc_queryfont(RlcData b)2270 rlc_queryfont(RlcData b)
2271 { CHOOSEFONT cf;
2272   LOGFONT lf;
2273 
2274   memset(&cf, 0, sizeof(cf));
2275   memset(&lf, 0, sizeof(lf));
2276 
2277   lf.lfHeight          = 16;
2278   lf.lfWeight          = FW_NORMAL;
2279   lf.lfPitchAndFamily  = FIXED_PITCH|FF_MODERN;
2280 
2281   cf.lStructSize = sizeof(cf);
2282   cf.hwndOwner   = b->window;
2283   cf.lpLogFont   = &lf;
2284   cf.Flags       = CF_SCREENFONTS|
2285 		   CF_NOVERTFONTS|
2286 		   CF_NOSIMULATIONS|
2287 		   CF_FORCEFONTEXIST|
2288 		   CF_INITTOLOGFONTSTRUCT;
2289   cf.nFontType   = SCREEN_FONTTYPE;
2290 
2291   if ( ChooseFont(&cf) )
2292   { HFONT f;
2293     if ( (f = CreateFontIndirect(&lf)) )
2294     { rlc_init_text_dimensions(b, f);
2295 
2296       InvalidateRect(b->window, NULL, TRUE);
2297     }
2298   }
2299 }
2300 
2301 
2302 
2303 		 /*******************************
2304 		 *     BUFFER INITIALISATION	*
2305 		 *******************************/
2306 
2307 static RlcData
rlc_make_buffer(int w,int h)2308 rlc_make_buffer(int w, int h)
2309 { RlcData b = rlc_malloc(sizeof(rlc_data));
2310   int i;
2311 
2312   memset(b, 0, sizeof(*b));
2313   b->magic = RLC_MAGIC;
2314 
2315   b->height         = h;
2316   b->width          = w;
2317   b->window_size    = 25;
2318   b->lines          = rlc_malloc(sizeof(text_line) * h);
2319   b->cmdstat	    = CMD_INITIAL;
2320   b->changed	    = CHG_CARET|CHG_CHANGED|CHG_CLEAR;
2321   b->imode	    = IMODE_COOKED;	/* switch on first rlc_read() call */
2322   b->imodeswitch    = FALSE;
2323   b->lhead	    = NULL;
2324   b->ltail	    = NULL;
2325 
2326   memset(b->lines, 0, sizeof(text_line) * h);
2327   for(i=0; i<h; i++)
2328     b->lines[i].adjusted = TRUE;
2329 
2330   rlc_init_word_chars();
2331 
2332   return b;
2333 }
2334 
2335 
2336 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2337 Copy all lines one `back' (i.e.  towards   older  lines).  If the oldest
2338 (first) line is adjacent to the last, throw it away.
2339 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
2340 
2341 static void
rlc_shift_lines_down(RlcData b,int line)2342 rlc_shift_lines_down(RlcData b, int line)
2343 { int i = b->first;
2344   int p = PrevLine(b, i);
2345 
2346   if ( p != b->last )			/* move first (oldest line) */
2347   { b->first = p;
2348     b->lines[p] = b->lines[i];
2349   } else				/* delete first (oldest) line */
2350     rlc_free_line(b, b->first);
2351 					/* copy the lines */
2352   for(p=i, i = NextLine(b, i); p != line; p=i, i = NextLine(b, i))
2353     b->lines[p] = b->lines[i];
2354 
2355   b->lines[line].text       = NULL;	/* make this one `free' */
2356   b->lines[line].size       = 0;
2357   b->lines[line].adjusted   = TRUE;
2358   b->lines[line].softreturn = FALSE;
2359 }
2360 
2361 
2362 static void
rlc_shift_lines_up(RlcData b,int line)2363 rlc_shift_lines_up(RlcData b, int line)
2364 { int prev = PrevLine(b, line);
2365 
2366   while(line != b->first)
2367   { b->lines[line] = b->lines[prev];
2368     line = prev;
2369     prev = PrevLine(b, prev);
2370   }
2371 
2372   rlc_reinit_line(b, b->first);
2373   b->first = NextLine(b, b->first);
2374 }
2375 
2376 
2377 
2378 static void
rlc_resize(RlcData b,int w,int h)2379 rlc_resize(RlcData b, int w, int h)
2380 { int i;
2381 
2382   if ( b->width == w && b->window_size == h )
2383     return;				/* no real change */
2384 
2385   DEBUG(Dprintf(_T("Resizing %dx%d --> %dx%d\n"),
2386 		b->width, b->window_size, w, h));
2387 
2388   b->window_size = h;
2389   b->width = w;
2390 
2391   for(i = b->first; /*i != b->last*/; i = NextLine(b, i))
2392   { TextLine tl = &b->lines[i];
2393 
2394     if ( tl->text && tl->adjusted == FALSE )
2395       rlc_adjust_line(b, i);
2396 
2397     if ( tl->size > w )
2398     { if ( !tl->softreturn )		/* hard --> soft */
2399       { TextLine pl;
2400 
2401 	rlc_shift_lines_down(b, i);
2402 	DEBUG(Dprint_lines(b, b->first, b->first));
2403 	DEBUG(Dprintf(_T("b->first = %d, b->last = %d\n"), b->first, b->last));
2404 	pl = &b->lines[PrevLine(b, i)];	/* this is the moved line */
2405 	tl->text = rlc_malloc((pl->size - w)*sizeof(text_char));
2406 	memmove(tl->text, &pl->text[w], (pl->size - w)*sizeof(text_char));
2407 	DEBUG(Dprintf(_T("Copied %d chars from line %d to %d\n"),
2408 		      pl->size - w, pl - b->lines, i));
2409 	tl->size = pl->size - w;
2410 	tl->adjusted = TRUE;
2411 	tl->softreturn = FALSE;
2412 	pl->softreturn = TRUE;
2413 	pl->text = rlc_realloc(pl->text, w * sizeof(text_char));
2414 	pl->size = w;
2415 	pl->adjusted = TRUE;
2416 	i = (int)(pl - b->lines);
2417 	DEBUG(Dprint_lines(b, b->first, b->last));
2418       } else				/* put in next line */
2419       { TextLine nl;
2420 	int move = tl->size - w;
2421 
2422 	if ( i == b->last )
2423 	  rlc_add_line(b);
2424 	nl = &b->lines[NextLine(b, i)];
2425 	nl->text = rlc_realloc(nl->text, (nl->size + move)*sizeof(text_char));
2426 	memmove(&nl->text[move], nl->text, nl->size*sizeof(text_char));
2427 	memmove(nl->text, &tl->text[w], move*sizeof(text_char));
2428 	nl->size += move;
2429 	tl->size = w;
2430       }
2431     } else if ( tl->text && tl->softreturn && tl->size < w )
2432     { TextLine nl;
2433 
2434       if ( i == b->last )
2435 	rlc_add_line(b);
2436       nl = &b->lines[NextLine(b, i)];
2437 
2438       nl->text = rlc_realloc(nl->text, (nl->size + tl->size)*sizeof(text_char));
2439       memmove(&nl->text[tl->size], nl->text, nl->size*sizeof(text_char));
2440       memmove(nl->text, tl->text, tl->size*sizeof(text_char));
2441       nl->size += tl->size;
2442       nl->adjusted = TRUE;
2443       rlc_shift_lines_up(b, i);
2444     }
2445 
2446     if ( i == b->last )
2447       break;
2448   }
2449 
2450   for(i = NextLine(b, i); i != b->first; i = NextLine(b, i))
2451     rlc_free_line(b, i);
2452 
2453   if ( rlc_count_lines(b, b->first, b->last) < h )
2454     b->window_start = b->first;
2455   else
2456     b->window_start = rlc_add_lines(b, b->last, -(h-1));
2457 
2458   b->caret_y = b->last;
2459   b->caret_x = b->lines[b->last].size;
2460 
2461   b->changed |= CHG_CARET|CHG_CHANGED|CHG_CLEAR;
2462 
2463   rlc_check_assertions(b);
2464 }
2465 
2466 
2467 static void
rlc_reinit_line(RlcData b,int line)2468 rlc_reinit_line(RlcData b, int line)
2469 { TextLine tl = &b->lines[line];
2470 
2471   tl->text	 = NULL;
2472   tl->adjusted   = FALSE;
2473   tl->size       = 0;
2474   tl->softreturn = FALSE;
2475 }
2476 
2477 
2478 static void
rlc_free_line(RlcData b,int line)2479 rlc_free_line(RlcData b, int line)
2480 { TextLine tl = &b->lines[line];
2481   if ( tl->text )
2482   { rlc_free(tl->text);
2483     rlc_reinit_line(b, line);
2484   }
2485 }
2486 
2487 
2488 static void
rlc_adjust_line(RlcData b,int line)2489 rlc_adjust_line(RlcData b, int line)
2490 { TextLine tl = &b->lines[line];
2491 
2492   if ( tl->text && !tl->adjusted )
2493   { tl->text = rlc_realloc(tl->text, tl->size == 0
2494 				? sizeof(text_char)
2495 				: tl->size * sizeof(text_char));
2496     tl->adjusted = TRUE;
2497   }
2498 }
2499 
2500 
2501 static void
rlc_unadjust_line(RlcData b,int line)2502 rlc_unadjust_line(RlcData b, int line)
2503 { TextLine tl = &b->lines[line];
2504 
2505   if ( tl->text )
2506   { if ( tl->adjusted )
2507     { tl->text = rlc_realloc(tl->text, (b->width + 1)*sizeof(text_char));
2508       tl->adjusted = FALSE;
2509     }
2510   } else
2511   { tl->text = rlc_malloc((b->width + 1)*sizeof(text_char));
2512     tl->adjusted = FALSE;
2513     tl->size = 0;
2514   }
2515 }
2516 
2517 
2518 static void
rlc_open_line(RlcData b)2519 rlc_open_line(RlcData b)
2520 { int i = b->last;
2521 
2522   if ( i == b->sel_start_line )
2523     rlc_set_selection(b, 0, 0, 0, 0);	/* clear the selection */
2524   if ( i == b->first )
2525   { rlc_free_line(b, b->first);
2526     b->first = NextLine(b, b->first);
2527   }
2528 
2529   b->lines[i].text       = rlc_malloc((b->width + 1)*sizeof(text_char));
2530   b->lines[i].adjusted   = FALSE;
2531   b->lines[i].size       = 0;
2532   b->lines[i].softreturn = FALSE;
2533 }
2534 
2535 
2536 static void
rlc_add_line(RlcData b)2537 rlc_add_line(RlcData b)
2538 { b->last = NextLine(b, b->last);
2539   rlc_open_line(b);
2540 }
2541 
2542 		 /*******************************
2543 		 *	   CALCULATIONS		*
2544 		 *******************************/
2545 
2546 static int
rlc_count_lines(RlcData b,int from,int to)2547 rlc_count_lines(RlcData b, int from, int to)
2548 { if ( to >= from )
2549     return to-from;
2550 
2551   return to + b->height - from;
2552 }
2553 
2554 
2555 static int
rlc_add_lines(RlcData b,int here,int add)2556 rlc_add_lines(RlcData b, int here, int add)
2557 { here += add;
2558   while ( here < 0 )
2559     here += b->height;
2560   while ( here >= b->height )
2561     here -= b->height;
2562 
2563   return here;
2564 }
2565 
2566 
2567 		 /*******************************
2568 		 *    ANSI SEQUENCE HANDLING	*
2569 		 *******************************/
2570 
2571 static void
rlc_need_arg(RlcData b,int arg,int def)2572 rlc_need_arg(RlcData b, int arg, int def)
2573 { if ( b->argc < arg )
2574   { b->argv[arg-1] = def;
2575     b->argc = arg;
2576   }
2577 }
2578 
2579 
2580 static void
rlc_caret_up(RlcData b,int arg)2581 rlc_caret_up(RlcData b, int arg)
2582 { while(arg-- > 0 && b->caret_y != b->first)
2583     b->caret_y = PrevLine(b, b->caret_y);
2584 
2585   b->changed |= CHG_CARET;
2586 }
2587 
2588 
2589 static void
rlc_caret_down(RlcData b,int arg)2590 rlc_caret_down(RlcData b, int arg)
2591 { while ( arg-- > 0 )
2592   { if ( b->caret_y == b->last )
2593       rlc_add_line(b);
2594     b->caret_y = NextLine(b, b->caret_y);
2595     b->lines[b->caret_y].softreturn = FALSE; /* ? why not only on open? */
2596   }
2597   b->changed |= CHG_CARET;
2598 					/* scroll? */
2599   if ( rlc_count_lines(b, b->window_start, b->caret_y) >= b->window_size )
2600   { b->window_start = rlc_add_lines(b, b->caret_y, -(b->window_size-1));
2601     b->changed |= CHG_CHANGED|CHG_CLEAR;
2602   }
2603 
2604   rlc_check_assertions(b);
2605 }
2606 
2607 
2608 static void
rlc_caret_forward(RlcData b,int arg)2609 rlc_caret_forward(RlcData b, int arg)
2610 { while(arg-- > 0)
2611   { if ( ++b->caret_x >= b->width )
2612     { b->lines[b->caret_y].softreturn = TRUE;
2613       b->caret_x = 0;
2614       rlc_caret_down(b, 1);
2615     }
2616   }
2617 
2618   b->changed |= CHG_CARET;
2619 }
2620 
2621 
2622 static void
rlc_caret_backward(RlcData b,int arg)2623 rlc_caret_backward(RlcData b, int arg)
2624 { while(arg-- > 0)
2625   { if ( b->caret_x-- == 0 )
2626     { rlc_caret_up(b, 1);
2627       b->caret_x = b->width-1;
2628     }
2629   }
2630 
2631   b->changed |= CHG_CARET;
2632 }
2633 
2634 
2635 static void
rlc_cariage_return(RlcData b)2636 rlc_cariage_return(RlcData b)
2637 { b->caret_x = 0;
2638 
2639   b->changed |= CHG_CARET;
2640 }
2641 
2642 
2643 static void
rlc_tab(RlcData b)2644 rlc_tab(RlcData b)
2645 { TextLine tl = &b->lines[b->caret_y];
2646 
2647   do
2648   { rlc_caret_forward(b, 1);
2649   } while( (b->caret_x % 8) != 0 );
2650 
2651   if ( tl->size < b->caret_x )
2652   { rlc_unadjust_line(b, b->caret_y);
2653 
2654     while ( tl->size < b->caret_x )
2655     { text_char *tc = &tl->text[tl->size++];
2656 
2657       tc->code = ' ';
2658       tc->flags = b->sgr_flags;
2659     }
2660   }
2661 
2662   b->changed |= CHG_CARET;
2663 }
2664 
2665 
2666 static void
rlc_set_caret(RlcData b,int x,int y)2667 rlc_set_caret(RlcData b, int x, int y)
2668 { int cy = rlc_count_lines(b, b->window_start, b->caret_y);
2669 
2670   y = Bounds(y, 0, b->window_size);
2671 
2672   if ( y < cy )
2673     b->caret_y = rlc_add_lines(b, b->window_start, y);
2674   else
2675     rlc_caret_down(b, y-cy);
2676 
2677   b->caret_x = Bounds(x, 0, b->width-1);
2678 
2679   b->changed |= CHG_CARET;
2680 }
2681 
2682 
2683 static void
rlc_save_caret_position(RlcData b)2684 rlc_save_caret_position(RlcData b)
2685 { b->scaret_y = rlc_count_lines(b, b->window_start, b->caret_y);
2686   b->scaret_x = b->caret_x;
2687 }
2688 
2689 
2690 static void
rlc_restore_caret_position(RlcData b)2691 rlc_restore_caret_position(RlcData b)
2692 { rlc_set_caret(b, b->scaret_x, b->scaret_y);
2693 }
2694 
2695 
2696 static void
rlc_erase_display(RlcData b)2697 rlc_erase_display(RlcData b)
2698 { int i = b->window_start;
2699   int last = rlc_add_lines(b, b->window_start, b->window_size);
2700 
2701   do
2702   { b->lines[i].size = 0;
2703     i = NextLine(b, i);
2704   } while ( i != last );
2705 
2706   b->changed |= CHG_CHANGED|CHG_CLEAR|CHG_CARET;
2707 
2708   rlc_set_caret(b, 0, 0);
2709 }
2710 
2711 
2712 static void
rlc_erase_line(RlcData b)2713 rlc_erase_line(RlcData b)
2714 { TextLine tl = &b->lines[b->caret_y];
2715 
2716   tl->size = b->caret_x;
2717   tl->changed |= CHG_CHANGED|CHG_CLEAR;
2718 }
2719 
2720 
2721 static void
rlc_sgr(RlcData b,int sgr)2722 rlc_sgr(RlcData b, int sgr)
2723 { if ( sgr == 0 )
2724   { b->sgr_flags = TF_DEFAULT;
2725   } else if ( sgr >= 30 && sgr <= 39 )
2726   { b->sgr_flags = TF_SET_FG(b->sgr_flags,
2727 			     sgr == 39 ? ANSI_COLOR_DEFAULT : sgr-30);
2728   } else if ( sgr >= 40 && sgr <= 49 )
2729   { b->sgr_flags = TF_SET_BG(b->sgr_flags,
2730 			     sgr == 49 ? ANSI_COLOR_DEFAULT : sgr-40);
2731   } else if ( sgr >= 90 && sgr <= 99 )
2732   { b->sgr_flags = TF_SET_FG(b->sgr_flags,
2733 			     sgr == 99 ? ANSI_COLOR_DEFAULT : sgr-90+8);
2734   } else if ( sgr >= 100 && sgr <= 109 )
2735   { b->sgr_flags = TF_SET_BG(b->sgr_flags,
2736 			     sgr == 109 ? ANSI_COLOR_DEFAULT : sgr-100+8);
2737   } else if ( sgr == 1 )
2738   { b->sgr_flags = TF_SET_BOLD(b->sgr_flags, 1);
2739   } else if ( sgr == 4 )
2740   { b->sgr_flags = TF_SET_UNDERLINE(b->sgr_flags, 1);
2741   }
2742 }
2743 
2744 
2745 static void
rlc_put(RlcData b,int chr)2746 rlc_put(RlcData b, int chr)
2747 { TextLine tl = &b->lines[b->caret_y];
2748   text_char *tc;
2749 
2750   rlc_unadjust_line(b, b->caret_y);
2751   while( tl->size < b->caret_x )
2752   { tc = &tl->text[tl->size++];
2753 
2754     tc->code  = ' ';
2755     tc->flags = b->sgr_flags;
2756   }
2757   tc = &tl->text[b->caret_x];
2758   tc->code = chr;
2759   tc->flags = b->sgr_flags;
2760   if ( tl->size <= b->caret_x )
2761     tl->size = b->caret_x + 1;
2762   tl->changed |= CHG_CHANGED;
2763 
2764   rlc_caret_forward(b, 1);
2765 }
2766 
2767 #ifdef _DEBUG
2768 #define CMD(c) {cmd = _T(#c); c;}
2769 #else
2770 #define CMD(c) {c;}
2771 #endif
2772 
2773 static void
rlc_putansi(RlcData b,int chr)2774 rlc_putansi(RlcData b, int chr)
2775 {
2776 #ifdef _DEBUG
2777   TCHAR *cmd;
2778 #endif
2779 
2780   switch(b->cmdstat)
2781   { case CMD_INITIAL:
2782       switch(chr)
2783       { case '\b':
2784 	  CMD(rlc_caret_backward(b, 1));
2785 	  break;
2786         case Control('G'):
2787 	  MessageBeep(MB_ICONEXCLAMATION);
2788 	  break;
2789 	case '\r':
2790 	  CMD(rlc_cariage_return(b));
2791 	  break;
2792 	case '\n':
2793 	  CMD(rlc_caret_down(b, 1));
2794 	  break;
2795 	case '\t':
2796 	  CMD(rlc_tab(b));
2797 	  break;
2798 	case 27:			/* ESC */
2799 	  b->cmdstat = CMD_ESC;
2800 	  break;
2801 	default:
2802 	  CMD(rlc_put(b, chr));
2803 	  break;
2804       }
2805       break;
2806     case CMD_ESC:
2807       switch(chr)
2808       { case '[':
2809 	  b->cmdstat = CMD_ANSI;
2810 	  b->argc    = 0;
2811 	  b->argstat = 0;		/* no arg */
2812 	  break;
2813 	default:
2814 	  b->cmdstat = CMD_INITIAL;
2815 	  break;
2816       }
2817       break;
2818     case CMD_ANSI:			/* ESC [ */
2819       if ( _istdigit((wint_t)chr) )
2820       { if ( !b->argstat )
2821 	{ b->argv[b->argc] = (chr - '0');
2822 	  b->argstat = 1;		/* positive */
2823 	} else
2824 	{ b->argv[b->argc] = b->argv[b->argc] * 10 + (chr - '0');
2825 	}
2826 
2827 	break;
2828       }
2829       if ( !b->argstat && chr == '-' )
2830       { b->argstat = -1;		/* negative */
2831 	break;
2832       }
2833       if ( b->argstat )
2834       { b->argv[b->argc] *= b->argstat;
2835 	if ( b->argc < (ANSI_MAX_ARGC-1) )
2836 	  b->argc++;			/* silently discard more of them */
2837 	b->argstat = 0;
2838       }
2839       switch(chr)
2840       { case ';':
2841 	  return;			/* wait for more args */
2842 	case 'H':
2843 	case 'f':
2844 	  rlc_need_arg(b, 1, 0);
2845 	  rlc_need_arg(b, 2, 0);
2846 	  CMD(rlc_set_caret(b, b->argv[0], b->argv[1]));
2847 	  break;
2848 	case 'A':
2849 	  rlc_need_arg(b, 1, 1);
2850 	  CMD(rlc_caret_up(b, b->argv[0]));
2851 	  break;
2852 	case 'B':
2853 	  rlc_need_arg(b, 1, 1);
2854 	  CMD(rlc_caret_down(b, b->argv[0]));
2855 	  break;
2856 	case 'C':
2857 	  rlc_need_arg(b, 1, 1);
2858 	  CMD(rlc_caret_forward(b, b->argv[0]));
2859 	  break;
2860 	case 'D':
2861 	  rlc_need_arg(b, 1, 1);
2862 	  CMD(rlc_caret_backward(b, b->argv[0]));
2863 	  break;
2864 	case 's':
2865 	  CMD(rlc_save_caret_position(b));
2866 	  break;
2867 	case 'u':
2868 	  CMD(rlc_restore_caret_position(b));
2869 	  break;
2870 	case 'J':
2871 	  if ( b->argv[0] == 2 )
2872 	    CMD(rlc_erase_display(b));
2873 	  break;
2874 	case 'K':
2875 	  CMD(rlc_erase_line(b));
2876 	  break;
2877 	case 'm':
2878 	  { int i;
2879 	    rlc_need_arg(b, 1, 0);
2880 
2881 	    for(i=0; i<b->argc; i++)
2882 	      CMD(rlc_sgr(b, b->argv[i]));
2883 	    break;
2884 	  }
2885       }
2886       b->cmdstat = CMD_INITIAL;
2887   }
2888 
2889   rlc_check_assertions(b);
2890 }
2891 
2892 
2893 		 /*******************************
2894 		 *	      CUT/PASTE		*
2895 		 *******************************/
2896 
2897 static void
rlc_paste(RlcData b)2898 rlc_paste(RlcData b)
2899 { HGLOBAL mem;
2900 
2901   if ( b->window )
2902   { OpenClipboard(b->window);
2903     if ( (mem = GetClipboardData(CF_UNICODETEXT)) )
2904     { wchar_t *data = GlobalLock(mem);
2905       int i;
2906       RlcQueue q = b->queue;
2907 
2908       if ( q )
2909       { for(i=0; data[i]; i++)
2910 	{ rlc_add_queue(b, q, data[i]);
2911 	  if ( data[i] == '\r' && data[i+1] == '\n' )
2912 	    i++;
2913 	}
2914       }
2915 
2916       GlobalUnlock(mem);
2917     } else if ( (mem = GetClipboardData(CF_TEXT)) )
2918     { char far *data = GlobalLock(mem);
2919       int i;
2920       RlcQueue q = b->queue;
2921 
2922       if ( q )
2923       { for(i=0; data[i]; i++)
2924 	{ rlc_add_queue(b, q, data[i]);
2925 	  if ( data[i] == '\r' && data[i+1] == '\n' )
2926 	    i++;
2927 	}
2928       }
2929 
2930       GlobalUnlock(mem);
2931     }
2932     CloseClipboard();
2933   }
2934 }
2935 
2936 		 /*******************************
2937 		 *	LINE-READ SUPPORT	*
2938 		 *******************************/
2939 
2940 void
rlc_get_mark(rlc_console c,RlcMark m)2941 rlc_get_mark(rlc_console c, RlcMark m)
2942 { RlcData b = rlc_get_data(c);
2943 
2944   m->mark_x = b->caret_x;
2945   m->mark_y = b->caret_y;
2946 }
2947 
2948 
2949 void
rlc_goto_mark(rlc_console c,RlcMark m,const TCHAR * data,size_t offset)2950 rlc_goto_mark(rlc_console c, RlcMark m, const TCHAR *data, size_t offset)
2951 { RlcData b = rlc_get_data(c);
2952 
2953   b->caret_x = m->mark_x;
2954   b->caret_y = m->mark_y;
2955 
2956   for( ; offset-- > 0; data++ )
2957   { switch(*data)
2958     { case '\t':
2959 	rlc_tab(b);
2960 	break;
2961       case '\n':
2962 	b->caret_x = 0;
2963         rlc_caret_down(b, 1);
2964 	break;
2965       default:
2966 	rlc_caret_forward(b, 1);
2967     }
2968   }
2969 }
2970 
2971 
2972 void
rlc_erase_from_caret(rlc_console c)2973 rlc_erase_from_caret(rlc_console c)
2974 { RlcData b = rlc_get_data(c);
2975   int i = b->caret_y;
2976   int x = b->caret_x;
2977   int last = rlc_add_lines(b, b->window_start, b->window_size);
2978 
2979   do
2980   { TextLine tl = &b->lines[i];
2981 
2982     if ( tl->size != x )
2983     { tl->size = x;
2984       tl->changed |= CHG_CHANGED|CHG_CLEAR;
2985     }
2986 
2987     i = NextLine(b, i);
2988     x = 0;
2989   } while ( i != last );
2990 }
2991 
2992 
2993 void
rlc_putchar(rlc_console c,int chr)2994 rlc_putchar(rlc_console c, int chr)
2995 { RlcData b = rlc_get_data(c);
2996 
2997   rlc_putansi(b, chr);
2998 }
2999 
3000 
3001 TCHAR *
rlc_read_screen(rlc_console c,RlcMark f,RlcMark t)3002 rlc_read_screen(rlc_console c, RlcMark f, RlcMark t)
3003 { RlcData b = rlc_get_data(c);
3004   TCHAR *buf;
3005 
3006   buf = rlc_read_from_window(b, f->mark_y, f->mark_x, t->mark_y, t->mark_x);
3007 
3008   return buf;
3009 }
3010 
3011 
3012 void
rlc_update(rlc_console c)3013 rlc_update(rlc_console c)
3014 { RlcData b = rlc_get_data(c);
3015 
3016   if ( b->window )
3017   { rlc_normalise(b);
3018     rlc_request_redraw(b);
3019     UpdateWindow(b->window);
3020   }
3021 }
3022 
3023 		 /*******************************
3024 		 *	  UPDATE THREAD		*
3025 		 *******************************/
3026 
3027 DWORD WINAPI
window_loop(LPVOID arg)3028 window_loop(LPVOID arg)
3029 { RlcData b = (RlcData) arg;
3030 
3031   rlc_create_window(b);
3032 					/* if we do not do this, all windows */
3033 					/* created by Prolog (XPCE) will be */
3034 					/* in the background and inactive! */
3035   if ( !AttachThreadInput(b->application_thread_id,
3036 			  b->console_thread_id, TRUE) )
3037     rlc_putansi(b, '!');
3038 
3039   PostThreadMessage(b->application_thread_id, WM_RLC_READY, 0, 0);
3040 
3041   while(!b->closing)
3042   { switch( b->imode )
3043     { case IMODE_COOKED:
3044       { TCHAR *line = read_line(b);
3045 
3046 	if ( line != RL_CANCELED_CHARP )
3047 	{ LQueued lq = rlc_malloc(sizeof(lqueued));
3048 
3049 	  lq->next = NULL;
3050 	  lq->line = line;
3051 
3052 	  if ( b->ltail )
3053 	  { b->ltail->next = lq;
3054 	    b->ltail = lq;
3055 	  } else
3056 	  { b->lhead = b->ltail = lq;
3057 					      /* awake main thread */
3058 	    PostThreadMessage(b->application_thread_id, WM_RLC_INPUT, 0, 0);
3059 	  }
3060 	}
3061 
3062 	break;
3063       }
3064       case IMODE_RAW:
3065       { MSG msg;
3066 
3067 	if ( rlc_get_message(&msg, NULL, 0, 0) )
3068 	{ TranslateMessage(&msg);
3069 	  DispatchMessage(&msg);
3070 	  rlc_flush_output(b);
3071 	} else
3072 	  goto out;
3073 
3074 	if ( b->imodeswitch )
3075 	{ b->imodeswitch = FALSE;
3076 	}
3077       }
3078     }
3079   }
3080 
3081   if ( b->closing <= 2 )
3082   { MSG msg;
3083     TCHAR *waiting = _T("\r\nWaiting for Prolog. ")
3084 		     _T("Close again to force termination ..");
3085 
3086     rlc_write(b, waiting, _tcslen(waiting));
3087 
3088     while ( b->closing <= 2 && rlc_get_message(&msg, NULL, 0, 0) )
3089     { TranslateMessage(&msg);
3090       DispatchMessage(&msg);
3091       rlc_flush_output(b);
3092     }
3093   }
3094 
3095 out:
3096 { DWORD appthread = b->application_thread_id;
3097   rlc_destroy(b);
3098 
3099   PostThreadMessage(appthread, WM_RLC_READY, 0, 0);
3100 }
3101   return 0;
3102 }
3103 
3104 
3105 		 /*******************************
3106 		 *	  WATCOM/DOS I/O	*
3107 		 *******************************/
3108 
3109 int
getch(rlc_console c)3110 getch(rlc_console c)
3111 { RlcData b = rlc_get_data(c);
3112   RlcQueue q = b->queue;
3113   int fromcon = (GetCurrentThreadId() == b->console_thread_id);
3114 
3115   while( rlc_is_empty_queue(q) )
3116   { if ( q->flags & RLC_EOF )
3117       return EOF;
3118 
3119     if ( !fromcon )
3120     { MSG msg;
3121 
3122       if ( rlc_get_message(&msg, NULL, 0, 0) )
3123       { TranslateMessage(&msg);
3124 	DispatchMessage(&msg);
3125       } else
3126 	return EOF;
3127     } else
3128     { rlc_dispatch(b);
3129       if ( b->imodeswitch )
3130       { b->imodeswitch = FALSE;
3131 	return IMODE_SWITCH_CHAR;
3132       }
3133     }
3134   }
3135 
3136   return rlc_from_queue(q);
3137 }
3138 
3139 
3140 int
getche(rlc_console c)3141 getche(rlc_console c)
3142 { RlcData b = rlc_get_data(c);
3143   int chr = getch(b);
3144 
3145   rlc_putansi(b, chr);
3146   return chr;
3147 }
3148 
3149 
3150 		 /*******************************
3151 		 *        GO32 FUNCTIONS	*
3152 		 *******************************/
3153 
3154 int
getkey(rlc_console con)3155 getkey(rlc_console con)
3156 { int c;
3157   RlcData b = rlc_get_data(con);
3158   int fromcon = (GetCurrentThreadId() == b->console_thread_id);
3159 
3160   if ( !fromcon && b->imode != IMODE_RAW )
3161   { int old = b->imode;
3162 
3163     b->imode = IMODE_RAW;
3164     b->imodeswitch = TRUE;
3165     c = getch(b);
3166     b->imode = old;
3167     b->imodeswitch = TRUE;
3168   } else
3169     c = getch(b);
3170 
3171   return c;
3172 }
3173 
3174 
3175 int
kbhit(rlc_console c)3176 kbhit(rlc_console c)
3177 { RlcData b = rlc_get_data(c);
3178 
3179   return !rlc_is_empty_queue(b->queue);
3180 }
3181 
3182 
3183 void
ScreenGetCursor(rlc_console c,int * row,int * col)3184 ScreenGetCursor(rlc_console c, int *row, int *col)
3185 { RlcData b = rlc_get_data(c);
3186 
3187   *row = rlc_count_lines(b, b->window_start, b->caret_y) + 1;
3188   *col = b->caret_x + 1;
3189 }
3190 
3191 
3192 void
ScreenSetCursor(rlc_console c,int row,int col)3193 ScreenSetCursor(rlc_console c, int row, int col)
3194 { RlcData b = rlc_get_data(c);
3195 
3196   rlc_set_caret(b, col-1, row-1);
3197 }
3198 
3199 
3200 int
ScreenCols(rlc_console c)3201 ScreenCols(rlc_console c)
3202 { RlcData b = rlc_get_data(c);
3203 
3204   return b->width;
3205 }
3206 
3207 
3208 int
ScreenRows(rlc_console c)3209 ScreenRows(rlc_console c)
3210 { RlcData b = rlc_get_data(c);
3211 
3212   return b->window_size;
3213 }
3214 
3215 		 /*******************************
3216 		 *	      QUEUE		*
3217 		 *******************************/
3218 
3219 #define QN(q, i) ((i)+1 >= (q)->size ? 0 : (i)+1)
3220 
3221 
3222 RlcQueue
rlc_make_queue(int size)3223 rlc_make_queue(int size)
3224 { RlcQueue q;
3225 
3226   if ( (q = rlc_malloc(sizeof(rlc_queue))) )
3227   { q->first = q->last = 0;
3228     q->size = size;
3229     q->flags = 0;
3230 
3231     if ( (q->buffer = rlc_malloc(sizeof(TCHAR) * size)) )
3232       return q;
3233   }
3234 
3235   return NULL;				/* not enough memory */
3236 }
3237 
3238 
3239 static int
rlc_resize_queue(RlcQueue q,int size)3240 rlc_resize_queue(RlcQueue q, int size)
3241 { TCHAR *newbuf;
3242 
3243   if ( (newbuf = rlc_malloc(size*sizeof(TCHAR))) )
3244   { TCHAR *o = newbuf;
3245     int c;
3246 
3247     while( (c=rlc_from_queue(q)) != -1 )
3248       *o++ = c;
3249 
3250     if ( q->buffer )
3251       rlc_free(q->buffer);
3252     q->buffer = newbuf;
3253     q->first = 0;
3254     q->last  = (int)(o-newbuf);
3255     q->size  = size;
3256 
3257     return TRUE;
3258   }
3259 
3260   return FALSE;
3261 }
3262 
3263 
3264 static int
rlc_add_queue(RlcData b,RlcQueue q,int chr)3265 rlc_add_queue(RlcData b, RlcQueue q, int chr)
3266 { int empty = (q->first == q->last);
3267 
3268   while(q->size < 50000)
3269   { if ( QN(q, q->last) != q->first )
3270     { q->buffer[q->last] = chr;
3271       q->last = QN(q, q->last);
3272 
3273       if ( empty )
3274 	PostThreadMessage(b->application_thread_id, WM_RLC_INPUT, 0, 0);
3275 
3276       return TRUE;
3277     }
3278 
3279     rlc_resize_queue(q, q->size*2);
3280   }
3281 
3282   return FALSE;
3283 }
3284 
3285 
3286 int
rlc_is_empty_queue(RlcQueue q)3287 rlc_is_empty_queue(RlcQueue q)
3288 { if ( q->first == q->last )
3289     return TRUE;
3290 
3291   return FALSE;
3292 }
3293 
3294 
3295 static int
rlc_from_queue(RlcQueue q)3296 rlc_from_queue(RlcQueue q)
3297 { if ( q->first != q->last )
3298   { int chr = q->buffer[q->first];
3299 
3300     q->first = QN(q, q->first);
3301 
3302     return chr;
3303   }
3304 
3305   return -1;
3306 }
3307 
3308 
3309 		 /*******************************
3310 		 *	   BUFFERED I/O		*
3311 		 *******************************/
3312 
3313 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
3314 When using UNICODE, count is in bytes!
3315 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
3316 
3317 size_t
rlc_read(rlc_console c,TCHAR * buf,size_t count)3318 rlc_read(rlc_console c, TCHAR *buf, size_t count)
3319 { RlcData d = rlc_get_data(c);
3320   size_t give;
3321   MSG msg;
3322 
3323   if ( d->closing )
3324     return 0;				/* signal EOF when closing */
3325 
3326   PostThreadMessage(d->console_thread_id,
3327 		    WM_RLC_FLUSH,
3328 		    0, 0);
3329   if ( _rlc_update_hook )
3330     (*_rlc_update_hook)();
3331 
3332   d->promptbuf[d->promptlen] = EOS;
3333   _tcscpy(d->prompt, d->promptbuf);
3334 
3335   if ( d->read_buffer.given >= d->read_buffer.length )
3336   { if ( d->read_buffer.line )
3337     { rlc_free(d->read_buffer.line);
3338       d->read_buffer.line = NULL;
3339     }
3340 
3341     if ( d->imode != IMODE_COOKED )
3342     { d->imode = IMODE_COOKED;
3343       d->imodeswitch = TRUE;
3344     }
3345 
3346     while(!d->lhead)
3347     { if ( rlc_get_message(&msg, NULL, 0, 0) )
3348       { TranslateMessage(&msg);
3349 	DispatchMessage(&msg);
3350       } else
3351 	return -1;
3352     }
3353 
3354     { LQueued lq = d->lhead;
3355       d->read_buffer.line = lq->line;
3356       if ( lq->next )
3357 	d->lhead = lq->next;
3358       else
3359 	d->lhead = d->ltail = NULL;
3360 
3361       rlc_free(lq);
3362     }
3363 
3364     d->read_buffer.length = _tcslen(d->read_buffer.line);
3365     d->read_buffer.given = 0;
3366   }
3367 
3368   if ( d->read_buffer.length - d->read_buffer.given > count )
3369     give = count;
3370   else
3371     give = d->read_buffer.length - d->read_buffer.given;
3372 
3373   _tcsncpy(buf, d->read_buffer.line+d->read_buffer.given, give);
3374   d->read_buffer.given += give;
3375 
3376   return give;
3377 }
3378 
3379 
3380 static void
rlc_do_write(RlcData b,TCHAR * buf,int count)3381 rlc_do_write(RlcData b, TCHAR *buf, int count)
3382 { if ( count > 0 )
3383   { int n = 0;
3384     TCHAR *s = buf;
3385 
3386     while(n++ < count)
3387     { int chr = *s++;
3388 
3389       if ( chr == '\n' )
3390 	rlc_putansi(b, '\r');
3391       rlc_putansi(b, chr);
3392     }
3393 
3394     rlc_normalise(b);
3395     if ( b->window )
3396     { rlc_request_redraw(b);
3397       UpdateWindow(b->window);
3398     }
3399   }
3400 }
3401 
3402 
3403 int
rlc_flush_output(rlc_console c)3404 rlc_flush_output(rlc_console c)
3405 { RlcData b = rlc_get_data(c);
3406 
3407   if ( !b )
3408     return -1;
3409 
3410   if ( b->output_queued )
3411   { rlc_do_write(b, b->output_queue, b->output_queued);
3412 
3413     b->output_queued = 0;
3414   }
3415 
3416   return 0;
3417 }
3418 
3419 
3420 size_t
rlc_write(rlc_console c,TCHAR * buf,size_t count)3421 rlc_write(rlc_console c, TCHAR *buf, size_t count)
3422 { DWORD_PTR result;
3423   TCHAR *e, *s;
3424   RlcData b = rlc_get_data(c);
3425 
3426   if ( !b )
3427     return -1;
3428 
3429   for(s=buf, e=&buf[count]; s<e; s++)
3430   { if ( *s == '\n' )
3431       b->promptlen = 0;
3432     else if ( b->promptlen < MAXPROMPT-1 )
3433       b->promptbuf[b->promptlen++] = *s;
3434   }
3435 
3436   if ( b->window )
3437   { if ( SendMessageTimeout(b->window,
3438 			    WM_RLC_WRITE,
3439 			    (WPARAM)count,
3440 			    (LPARAM)buf,
3441 			    SMTO_NORMAL,
3442 			    10000,
3443 			    &result) )
3444     { PostMessage(b->window,
3445 		  WM_RLC_FLUSH,
3446 		  0, 0);
3447       return count;
3448     }
3449   }
3450 
3451   return -1;				/* I/O error */
3452 }
3453 
3454 
3455 static void
free_rlc_data(RlcData b)3456 free_rlc_data(RlcData b)
3457 { b->magic = 42;			/* so next gets errors */
3458 
3459   if ( b->lines )
3460   { int i;
3461 
3462     for(i=0; i<b->height; i++)
3463     { if ( b->lines[i].text )
3464 	free(b->lines[i].text);
3465     }
3466 
3467     free(b->lines);
3468   }
3469   if ( b->read_buffer.line )
3470     free(b->read_buffer.line);
3471 
3472   free(b);
3473 }
3474 
3475 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
3476 rlc_close() tries to gracefully get rid of   the console thread. It does
3477 so by posting WM_RLC_CLOSEWIN and then waiting for a WM_RLC_READY reply.
3478 It waits for a maximum of  1.5  second,   which  should  be  fine as the
3479 console thread should not have intptr_t-lasting activities.
3480 
3481 If the timeout expires it hopes for the best. This was the old situation
3482 and proved to be sound on Windows-NT, but not on 95 and '98.
3483 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
3484 
3485 int
rlc_close(rlc_console c)3486 rlc_close(rlc_console c)
3487 { RlcData b = (RlcData)c;
3488   MSG msg;
3489   int i;
3490 
3491   if ( b->magic != RLC_MAGIC )
3492     return -1;
3493 
3494   rlc_save_options(b);
3495   b->closing = 3;
3496   PostMessage(b->window, WM_RLC_CLOSEWIN, 0, 0);
3497 
3498 					/* wait for termination */
3499   for(i=0; i<30; i++)
3500   { if ( PeekMessage(&msg, NULL, WM_RLC_READY, WM_RLC_READY, PM_REMOVE) )
3501       break;
3502     Sleep(50);
3503   }
3504 
3505   b->magic = 0;
3506   free_user_data(c);
3507   free_rlc_data(b);
3508 
3509   return 0;
3510 }
3511 
3512 
3513 const TCHAR *
rlc_prompt(rlc_console c,const TCHAR * new)3514 rlc_prompt(rlc_console c, const TCHAR *new)
3515 { RlcData b = rlc_get_data(c);
3516 
3517   if ( b )
3518   { if ( new )
3519     { _tcsncpy(b->prompt, new, MAXPROMPT);
3520       b->prompt[MAXPROMPT-1] = EOS;
3521     }
3522 
3523     return b->prompt;
3524   }
3525 
3526   return _T("");
3527 }
3528 
3529 
3530 void
rlc_clearprompt(rlc_console c)3531 rlc_clearprompt(rlc_console c)
3532 { RlcData b = rlc_get_data(c);
3533 
3534   if ( b )
3535   { b->promptlen = 0;
3536     b->prompt[0] = EOS;
3537   }
3538 }
3539 
3540 
3541 		 /*******************************
3542 		 *	    MISC STUFF		*
3543 		 *******************************/
3544 
3545 void
rlc_title(rlc_console c,TCHAR * title,TCHAR * old,int size)3546 rlc_title(rlc_console c, TCHAR *title, TCHAR *old, int size)
3547 { RlcData b = rlc_get_data(c);
3548 
3549   if ( old )
3550     memmove(old, b->current_title, size*sizeof(TCHAR));
3551 
3552   if ( title )
3553   { if ( b->window )
3554       SetWindowText(b->window, title);
3555 
3556     memmove(b->current_title, title, RLC_TITLE_MAX*sizeof(TCHAR));
3557   }
3558 }
3559 
3560 
3561 void
rlc_icon(rlc_console c,HICON icon)3562 rlc_icon(rlc_console c, HICON icon)
3563 {
3564   SetClassLongPtr(rlc_hwnd(c), GCLP_HICON, (LONG_PTR) icon);
3565 }
3566 
3567 
3568 int
rlc_window_pos(rlc_console c,HWND hWndInsertAfter,int x,int y,int w,int h,UINT flags)3569 rlc_window_pos(rlc_console c,
3570 	       HWND hWndInsertAfter,
3571 	       int x, int y, int w, int h,
3572 	       UINT flags)
3573 { RlcData b = rlc_get_data(c);
3574 
3575   if ( b )
3576   { w *= b->cw;
3577     h *= b->ch;
3578 
3579     SetWindowPos(b->window, hWndInsertAfter,
3580 		 x, y, w, h,
3581 		 flags);
3582 
3583     return TRUE;
3584   }
3585 
3586   return FALSE;
3587 }
3588 
3589 
3590 HANDLE
rlc_hinstance()3591 rlc_hinstance()
3592 { return _rlc_hinstance;
3593 }
3594 
3595 
3596 HWND
rlc_hwnd(rlc_console c)3597 rlc_hwnd(rlc_console c)
3598 { RlcData b = rlc_get_data(c);
3599 
3600   return b ? b->window : (HWND)NULL;
3601 }
3602 
3603 		 /*******************************
3604 		 *	 SETTING OPTIONS	*
3605 		 *******************************/
3606 
3607 int
rlc_copy_output_to_debug_output(int new)3608 rlc_copy_output_to_debug_output(int new)
3609 { int old = _rlc_copy_output_to_debug_output;
3610 
3611   _rlc_copy_output_to_debug_output = new;
3612 
3613   return old;
3614 }
3615 
3616 RlcUpdateHook
rlc_update_hook(RlcUpdateHook new)3617 rlc_update_hook(RlcUpdateHook new)
3618 { RlcUpdateHook old = _rlc_update_hook;
3619 
3620   _rlc_update_hook = new;
3621   return old;
3622 }
3623 
3624 RlcTimerHook
rlc_timer_hook(RlcTimerHook new)3625 rlc_timer_hook(RlcTimerHook new)
3626 { RlcTimerHook old = _rlc_timer_hook;
3627 
3628   _rlc_timer_hook = new;
3629   return old;
3630 }
3631 
3632 RlcRenderHook
rlc_render_hook(RlcRenderHook new)3633 rlc_render_hook(RlcRenderHook new)
3634 { RlcRenderHook old = _rlc_render_hook;
3635 
3636   _rlc_render_hook = new;
3637   return old;
3638 }
3639 
3640 RlcRenderAllHook
rlc_render_all_hook(RlcRenderAllHook new)3641 rlc_render_all_hook(RlcRenderAllHook new)
3642 { RlcRenderAllHook old = _rlc_render_all_hook;
3643 
3644   _rlc_render_all_hook = new;
3645   return old;
3646 }
3647 
3648 RlcInterruptHook
rlc_interrupt_hook(RlcInterruptHook new)3649 rlc_interrupt_hook(RlcInterruptHook new)
3650 { RlcInterruptHook old = _rlc_interrupt_hook;
3651 
3652   _rlc_interrupt_hook = new;
3653   return old;
3654 }
3655 
3656 RlcResizeHook
rlc_resize_hook(RlcResizeHook new)3657 rlc_resize_hook(RlcResizeHook new)
3658 { RlcResizeHook old = _rlc_resize_hook;
3659 
3660   _rlc_resize_hook = new;
3661   return old;
3662 }
3663 
3664 RlcMenuHook
rlc_menu_hook(RlcMenuHook new)3665 rlc_menu_hook(RlcMenuHook new)
3666 { RlcMenuHook old = _rlc_menu_hook;
3667 
3668   _rlc_menu_hook = new;
3669   return old;
3670 }
3671 
3672 
3673 RlcMessageHook
rlc_message_hook(RlcMessageHook new)3674 rlc_message_hook(RlcMessageHook new)
3675 { RlcMessageHook old = _rlc_message_hook;
3676 
3677   _rlc_message_hook = new;
3678   return old;
3679 }
3680 
3681 
3682 int
rlc_set(rlc_console c,int what,uintptr_t data,RlcFreeDataHook hook)3683 rlc_set(rlc_console c, int what, uintptr_t data, RlcFreeDataHook hook)
3684 { RlcData b = rlc_get_data(c);
3685 
3686   switch(what)
3687   { default:
3688       if ( what >= RLC_VALUE(0) &&
3689 	   what <= RLC_VALUE(MAX_USER_VALUES) )
3690       { b->values[what-RLC_VALUE(0)].data = data;
3691 	b->values[what-RLC_VALUE(0)].hook = hook;
3692         return TRUE;
3693       }
3694       return FALSE;
3695   }
3696 }
3697 
3698 
3699 int
rlc_get(rlc_console c,int what,uintptr_t * data)3700 rlc_get(rlc_console c, int what, uintptr_t *data)
3701 { RlcData b = (RlcData)c;
3702 
3703   if ( !b )
3704     return FALSE;
3705 
3706   switch(what)
3707   { case RLC_APPLICATION_THREAD:
3708       *data = (uintptr_t)b->application_thread;
3709       return TRUE;
3710     case RLC_APPLICATION_THREAD_ID:
3711       *data = (uintptr_t)b->application_thread_id;
3712       return TRUE;
3713     default:
3714       if ( what >= RLC_VALUE(0) &&
3715 	   what <= RLC_VALUE(MAX_USER_VALUES) )
3716       { *data = b->values[what-RLC_VALUE(0)].data;
3717         return TRUE;
3718       }
3719       return FALSE;
3720   }
3721 }
3722 
3723 
3724 static void
free_user_data(RlcData b)3725 free_user_data(RlcData b)
3726 { user_data *d = b->values;
3727   int i;
3728 
3729   for(i=0; i<MAX_USER_VALUES; i++, d++)
3730   { RlcFreeDataHook hook;
3731 
3732     if ( (hook=d->hook) )
3733     { uintptr_t data = d->data;
3734       d->hook = NULL;
3735       d->data = 0L;
3736       (*hook)(data);
3737     }
3738   }
3739 }
3740 
3741 		 /*******************************
3742 		 *	       UTIL		*
3743 		 *******************************/
3744 
3745 static void
noMemory()3746 noMemory()
3747 { MessageBox(NULL, _T("Not enough memory"), _T("Console"), MB_OK|MB_TASKMODAL);
3748 
3749   ExitProcess(1);
3750 }
3751 
3752 
3753 void *
rlc_malloc(size_t size)3754 rlc_malloc(size_t size)
3755 { void *ptr = malloc(size);
3756 
3757   if ( !ptr && size > 0 )
3758     noMemory();
3759 
3760 #ifdef _DEBUG
3761   memset(ptr, 0xbf, size);
3762 #endif
3763   return ptr;
3764 }
3765 
3766 
3767 void *
rlc_realloc(void * ptr,size_t size)3768 rlc_realloc(void *ptr, size_t size)
3769 { void *ptr2 = realloc(ptr, size);
3770 
3771   if ( !ptr2 && size > 0 )
3772     noMemory();
3773 
3774   return ptr2;
3775 }
3776 
3777 
3778 void
rlc_free(void * ptr)3779 rlc_free(void *ptr)
3780 { free(ptr);
3781 }
3782 
3783 #ifndef initHeapDebug
3784 
3785 		 /*******************************
3786 		 *	       DEBUG		*
3787 		 *******************************/
3788 
3789 static void
initHeapDebug(void)3790 initHeapDebug(void)
3791 { int tmpFlag = _CrtSetDbgFlag( _CRTDBG_REPORT_FLAG );
3792 
3793   if ( !(tmpFlag & _CRTDBG_CHECK_ALWAYS_DF) )
3794   { /*MessageBox(NULL,
3795 	       "setting malloc() debugging",
3796 	       "SWI-Prolog console",
3797 	       MB_OK|MB_TASKMODAL);*/
3798     tmpFlag |= _CRTDBG_CHECK_ALWAYS_DF;
3799     _CrtSetDbgFlag(tmpFlag);
3800   } else
3801   {
3802     /*MessageBox(NULL,
3803 	       "malloc() debugging lready set",
3804 	       "SWI-Prolog console",
3805 	       MB_OK|MB_TASKMODAL);*/
3806   }
3807 }
3808 
3809 #endif /*initHeapDebug*/
3810 
3811 #ifdef _DEBUG
3812 
3813 static void
Dprintf(const TCHAR * fmt,...)3814 Dprintf(const TCHAR *fmt, ...)
3815 { TCHAR buf[1024];
3816   va_list args;
3817 
3818   va_start(args, fmt);
3819   vswprintf(buf, sizeof(buf)/sizeof(TCHAR), fmt, args);
3820   va_end(args);
3821 
3822   OutputDebugString(buf);
3823 }
3824 
3825 static void
Dprint_lines(RlcData b,int from,int to)3826 Dprint_lines(RlcData b, int from, int to)
3827 { TCHAR buf[1024];
3828 
3829   for( ; ; from = NextLine(b, from))
3830   { TextLine tl = &b->lines[from];
3831 
3832     memcpy(buf, tl->text, tl->size);
3833     buf[tl->size] = EOS;
3834     Dprintf(_T("%03d: (0x%08x) \"%s\"\n"), from, tl->text, buf);
3835 
3836     if ( from == to )
3837       break;
3838   }
3839 }
3840 
3841 #endif
3842