syscons.c revision 36735
1/*-
2 * Copyright (c) 1992-1997 S�ren Schmidt
3 * All rights reserved.
4 *
5 * Redistribution and use in source and binary forms, with or without
6 * modification, are permitted provided that the following conditions
7 * are met:
8 * 1. Redistributions of source code must retain the above copyright
9 *    notice, this list of conditions and the following disclaimer
10 *    in this position and unchanged.
11 * 2. Redistributions in binary form must reproduce the above copyright
12 *    notice, this list of conditions and the following disclaimer in the
13 *    documentation and/or other materials provided with the distribution.
14 * 3. The name of the author may not be used to endorse or promote products
15 *    derived from this software withough specific prior written permission
16 *
17 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
18 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
19 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
20 * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
21 * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
22 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
23 * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
24 * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
25 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
26 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
27 *
28 *  $Id: syscons.c,v 1.261 1998/05/17 11:52:18 phk Exp $
29 */
30
31#include "sc.h"
32#include "apm.h"
33#include "opt_ddb.h"
34#include "opt_devfs.h"
35#include "opt_syscons.h"
36
37#if NSC > 0
38#include <sys/param.h>
39#include <sys/systm.h>
40#include <sys/conf.h>
41#include <sys/proc.h>
42#include <sys/signalvar.h>
43#include <sys/tty.h>
44#include <sys/kernel.h>
45#include <sys/malloc.h>
46#ifdef	DEVFS
47#include <sys/devfsext.h>
48#endif
49
50#include <machine/clock.h>
51#include <machine/cons.h>
52#include <machine/console.h>
53#include <machine/mouse.h>
54#include <machine/md_var.h>
55#include <machine/psl.h>
56#include <machine/frame.h>
57#include <machine/pc/display.h>
58#include <machine/apm_bios.h>
59#include <machine/random.h>
60#include <machine/bootinfo.h>
61
62#include <vm/vm.h>
63#include <vm/vm_param.h>
64#include <vm/pmap.h>
65
66#include <i386/isa/isa.h>
67#include <i386/isa/isa_device.h>
68#include <i386/isa/timerreg.h>
69#include <i386/isa/kbdtables.h>
70#include <i386/isa/kbdio.h>
71#include <i386/isa/syscons.h>
72
73#if !defined(MAXCONS)
74#define MAXCONS 16
75#endif
76
77#if !defined(SC_MAX_HISTORY_SIZE)
78#define SC_MAX_HISTORY_SIZE	(1000 * MAXCONS)
79#endif
80
81#if !defined(SC_HISTORY_SIZE)
82#define SC_HISTORY_SIZE		(ROW * 4)
83#endif
84
85#if (SC_HISTORY_SIZE * MAXCONS) > SC_MAX_HISTORY_SIZE
86#undef SC_MAX_HISTORY_SIZE
87#define SC_MAX_HISTORY_SIZE	(SC_HISTORY_SIZE * MAXCONS)
88#endif
89
90#if !defined(SC_MOUSE_CHAR)
91#define SC_MOUSE_CHAR		(0xd0)
92#endif
93
94#define COLD 0
95#define WARM 1
96
97#define MODE_MAP_SIZE		(M_VGA_CG320 + 1)
98#define MODE_PARAM_SIZE		64
99
100/* for backward compatibility */
101#define OLD_CONS_MOUSECTL	_IOWR('c', 10, old_mouse_info_t)
102
103typedef struct old_mouse_data {
104    int x;
105    int y;
106    int buttons;
107} old_mouse_data_t;
108
109typedef struct old_mouse_info {
110    int operation;
111    union {
112	struct old_mouse_data data;
113	struct mouse_mode mode;
114    } u;
115} old_mouse_info_t;
116
117/* XXX use sc_bcopy where video memory is concerned */
118extern void generic_bcopy(const void *, void *, size_t);
119
120static default_attr user_default = {
121    (FG_LIGHTGREY | BG_BLACK) << 8,
122    (FG_BLACK | BG_LIGHTGREY) << 8
123};
124
125static default_attr kernel_default = {
126    (FG_WHITE | BG_BLACK) << 8,
127    (FG_BLACK | BG_LIGHTGREY) << 8
128};
129
130static  scr_stat    	main_console;
131static  scr_stat    	*console[MAXCONS];
132#ifdef DEVFS
133static	void		*sc_devfs_token[MAXCONS];
134static	void		*sc_mouse_devfs_token;
135static	void		*sc_console_devfs_token;
136#endif
137	scr_stat    	*cur_console;
138static  scr_stat    	*new_scp, *old_scp;
139static  term_stat   	kernel_console;
140static  default_attr    *current_default;
141static  int     	flags = 0;
142static  int		sc_port = IO_KBD;
143static  KBDC		sc_kbdc = NULL;
144static  char        	init_done = COLD;
145static  u_short		sc_buffer[ROW*COL];
146static  char        	font_loading_in_progress = FALSE;
147static  char        	switch_in_progress = FALSE;
148static  char        	write_in_progress = FALSE;
149static  char        	blink_in_progress = FALSE;
150static  int        	blinkrate = 0;
151	u_int       	crtc_addr = MONO_BASE;
152	char		crtc_type = KD_MONO;
153	char        	crtc_vga = FALSE;
154static  u_char      	shfts = 0, ctls = 0, alts = 0, agrs = 0, metas = 0;
155static  u_char		accents = 0;
156static  u_char      	nlkcnt = 0, clkcnt = 0, slkcnt = 0, alkcnt = 0;
157static  const u_int     n_fkey_tab = sizeof(fkey_tab) / sizeof(*fkey_tab);
158static  int     	delayed_next_scr = FALSE;
159static  long        	scrn_blank_time = 0;    /* screen saver timeout value */
160	int     	scrn_blanked = 0;       /* screen saver active flag */
161static  struct timeval 	scrn_time_stamp;
162	u_char      	scr_map[256];
163	u_char      	scr_rmap[256];
164	char        	*video_mode_ptr = NULL;
165static	int		vesa_mode;
166	int     	fonts_loaded = 0
167#ifdef STD8X16FONT
168	| FONT_16
169#endif
170	;
171
172	char        	font_8[256*8];
173	char		font_14[256*14];
174#ifdef STD8X16FONT
175extern
176#endif
177	unsigned char	font_16[256*16];
178	char        	palette[256*3];
179static  char		*mode_map[MODE_MAP_SIZE];
180static  char		vgaregs[MODE_PARAM_SIZE];
181static  char		vgaregs2[MODE_PARAM_SIZE];
182static  int		rows_offset = 1;
183static	char 		*cut_buffer;
184static	int		mouse_level = 0;	/* sysmouse protocol level */
185static	mousestatus_t	mouse_status = { 0, 0, 0, 0, 0, 0 };
186static  u_short 	mouse_and_mask[16] = {
187				0xc000, 0xe000, 0xf000, 0xf800,
188				0xfc00, 0xfe00, 0xff00, 0xff80,
189				0xfe00, 0x1e00, 0x1f00, 0x0f00,
190				0x0f00, 0x0000, 0x0000, 0x0000
191			};
192static  u_short 	mouse_or_mask[16] = {
193				0x0000, 0x4000, 0x6000, 0x7000,
194				0x7800, 0x7c00, 0x7e00, 0x6800,
195				0x0c00, 0x0c00, 0x0600, 0x0600,
196				0x0000, 0x0000, 0x0000, 0x0000
197			};
198
199static int		extra_history_size =
200			    SC_MAX_HISTORY_SIZE - SC_HISTORY_SIZE * MAXCONS;
201
202static void    		none_saver(int blank) { }
203static void    		(*current_saver)(int blank) = none_saver;
204int  			(*sc_user_ioctl)(dev_t dev, int cmd, caddr_t data,
205					 int flag, struct proc *p) = NULL;
206
207/* OS specific stuff */
208#ifdef not_yet_done
209#define VIRTUAL_TTY(x)  (sccons[x] = ttymalloc(sccons[x]))
210struct  CONSOLE_TTY 	(sccons[MAXCONS] = ttymalloc(sccons[MAXCONS]))
211struct  MOUSE_TTY 	(sccons[MAXCONS+1] = ttymalloc(sccons[MAXCONS+1]))
212struct  tty         	*sccons[MAXCONS+2];
213#else
214#define VIRTUAL_TTY(x)  &sccons[x]
215#define CONSOLE_TTY 	&sccons[MAXCONS]
216#define MOUSE_TTY 	&sccons[MAXCONS+1]
217static struct tty     	sccons[MAXCONS+2];
218#endif
219#define SC_MOUSE 	128
220#define SC_CONSOLE	255
221#define MONO_BUF    	pa_to_va(0xB0000)
222#define CGA_BUF     	pa_to_va(0xB8000)
223u_short         	*Crtat;
224static const int	nsccons = MAXCONS+2;
225
226#define WRAPHIST(scp, pointer, offset)\
227    ((scp->history) + ((((pointer) - (scp->history)) + (scp->history_size)\
228    + (offset)) % (scp->history_size)))
229#define ISSIGVALID(sig)	((sig) > 0 && (sig) < NSIG)
230
231/* this should really be in `rtc.h' */
232#define RTC_EQUIPMENT		0x14
233
234/* prototypes */
235static int scattach(struct isa_device *dev);
236static int scparam(struct tty *tp, struct termios *t);
237static int scprobe(struct isa_device *dev);
238static int scvidprobe(int unit, int flags);
239static int sckbdprobe(int unit, int flags);
240static void scstart(struct tty *tp);
241static void scmousestart(struct tty *tp);
242static void scinit(void);
243static void map_mode_table(char *map[], char *table, int max);
244static u_char map_mode_num(u_char mode);
245static char *get_mode_param(scr_stat *scp, u_char mode);
246static u_int scgetc(u_int flags);
247#define SCGETC_CN	1
248#define SCGETC_NONBLOCK	2
249static void sccnupdate(scr_stat *scp);
250static scr_stat *get_scr_stat(dev_t dev);
251static scr_stat *alloc_scp(void);
252static void init_scp(scr_stat *scp);
253static void sc_bcopy(u_short *p, int from, int to, int mark);
254static int get_scr_num(void);
255static timeout_t scrn_timer;
256static void scrn_update(scr_stat *scp, int show_cursor);
257static void stop_scrn_saver(void (*saver)(int));
258static int wait_scrn_saver_stop(void);
259static void clear_screen(scr_stat *scp);
260static int switch_scr(scr_stat *scp, u_int next_scr);
261static void exchange_scr(void);
262static void move_crsr(scr_stat *scp, int x, int y);
263static void scan_esc(scr_stat *scp, u_char c);
264static void draw_cursor_image(scr_stat *scp);
265static void remove_cursor_image(scr_stat *scp);
266static void ansi_put(scr_stat *scp, u_char *buf, int len);
267static u_char *get_fstr(u_int c, u_int *len);
268static void history_to_screen(scr_stat *scp);
269static int history_up_line(scr_stat *scp);
270static int history_down_line(scr_stat *scp);
271static int mask2attr(struct term_stat *term);
272static void set_keyboard(int command, int data);
273static void update_leds(int which);
274static void set_vgaregs(char *modetable);
275static void read_vgaregs(char *buf);
276#define COMP_IDENTICAL	0
277#define COMP_SIMILAR	1
278#define COMP_DIFFERENT	2
279static int comp_vgaregs(u_char *buf1, u_char *buf2);
280static void dump_vgaregs(u_char *buf);
281#define PARAM_BUFSIZE	6
282static void set_font_mode(u_char *buf);
283static void set_normal_mode(u_char *buf);
284static void set_destructive_cursor(scr_stat *scp);
285static void set_mouse_pos(scr_stat *scp);
286static int skip_spc_right(scr_stat *scp, u_short *p);
287static int skip_spc_left(scr_stat *scp, u_short *p);
288static void mouse_cut(scr_stat *scp);
289static void mouse_cut_start(scr_stat *scp);
290static void mouse_cut_end(scr_stat *scp);
291static void mouse_cut_word(scr_stat *scp);
292static void mouse_cut_line(scr_stat *scp);
293static void mouse_cut_extend(scr_stat *scp);
294static void mouse_paste(scr_stat *scp);
295static void draw_mouse_image(scr_stat *scp);
296static void remove_mouse_image(scr_stat *scp);
297static void draw_cutmarking(scr_stat *scp);
298static void remove_cutmarking(scr_stat *scp);
299static void save_palette(void);
300static void do_bell(scr_stat *scp, int pitch, int duration);
301static timeout_t blink_screen;
302#ifdef SC_SPLASH_SCREEN
303static void toggle_splash_screen(scr_stat *scp);
304#endif
305
306struct  isa_driver scdriver = {
307    scprobe, scattach, "sc", 1
308};
309
310static	d_open_t	scopen;
311static	d_close_t	scclose;
312static	d_read_t	scread;
313static	d_write_t	scwrite;
314static	d_ioctl_t	scioctl;
315static	d_devtotty_t	scdevtotty;
316static	d_mmap_t	scmmap;
317
318#define CDEV_MAJOR 12
319static	struct cdevsw	scdevsw = {
320	scopen,		scclose,	scread,		scwrite,
321	scioctl,	nullstop,	noreset,	scdevtotty,
322	ttpoll,		scmmap,		nostrategy,	"sc",	NULL,	-1 };
323
324/*
325 * These functions need to be before calls to them so they can be inlined.
326 */
327static void
328draw_cursor_image(scr_stat *scp)
329{
330    u_short cursor_image, *ptr = Crtat + (scp->cursor_pos - scp->scr_buf);
331    u_short prev_image;
332
333    if (vesa_mode) {
334	sc_bcopy(scp->scr_buf, scp->cursor_pos - scp->scr_buf,
335	  scp->cursor_pos - scp->scr_buf, 1);
336	return;
337    }
338
339    /* do we have a destructive cursor ? */
340    if (flags & CHAR_CURSOR) {
341	prev_image = scp->cursor_saveunder;
342	cursor_image = *ptr & 0x00ff;
343	if (cursor_image == DEAD_CHAR)
344	    cursor_image = prev_image & 0x00ff;
345	cursor_image |= *(scp->cursor_pos) & 0xff00;
346	scp->cursor_saveunder = cursor_image;
347	/* update the cursor bitmap if the char under the cursor has changed */
348	if (prev_image != cursor_image)
349	    set_destructive_cursor(scp);
350	/* modify cursor_image */
351	if (!(flags & BLINK_CURSOR)||((flags & BLINK_CURSOR)&&(blinkrate & 4))){
352	    /*
353	     * When the mouse pointer is at the same position as the cursor,
354	     * the cursor bitmap needs to be updated even if the char under
355	     * the cursor hasn't changed, because the mouse pionter may
356	     * have moved by a few dots within the cursor cel.
357	     */
358	    if ((prev_image == cursor_image)
359		    && (cursor_image != *(scp->cursor_pos)))
360	        set_destructive_cursor(scp);
361	    cursor_image &= 0xff00;
362	    cursor_image |= DEAD_CHAR;
363	}
364    } else {
365	cursor_image = (*(ptr) & 0x00ff) | *(scp->cursor_pos) & 0xff00;
366	scp->cursor_saveunder = cursor_image;
367	if (!(flags & BLINK_CURSOR)||((flags & BLINK_CURSOR)&&(blinkrate & 4))){
368	    if ((cursor_image & 0x7000) == 0x7000) {
369		cursor_image &= 0x8fff;
370		if(!(cursor_image & 0x0700))
371		    cursor_image |= 0x0700;
372	    } else {
373		cursor_image |= 0x7000;
374		if ((cursor_image & 0x0700) == 0x0700)
375		    cursor_image &= 0xf0ff;
376	    }
377	}
378    }
379    *ptr = cursor_image;
380}
381
382static void
383remove_cursor_image(scr_stat *scp)
384{
385    if (vesa_mode)
386	sc_bcopy(scp->scr_buf, scp->cursor_oldpos - scp->scr_buf,
387	  scp->cursor_oldpos - scp->scr_buf, 0);
388    else
389	*(Crtat + (scp->cursor_oldpos - scp->scr_buf)) = scp->cursor_saveunder;
390}
391
392static void
393move_crsr(scr_stat *scp, int x, int y)
394{
395    if (x < 0)
396	x = 0;
397    if (y < 0)
398	y = 0;
399    if (x >= scp->xsize)
400	x = scp->xsize-1;
401    if (y >= scp->ysize)
402	y = scp->ysize-1;
403    scp->xpos = x;
404    scp->ypos = y;
405    scp->cursor_pos = scp->scr_buf + scp->ypos * scp->xsize + scp->xpos;
406}
407
408static int
409scprobe(struct isa_device *dev)
410{
411    if (!scvidprobe(dev->id_unit, dev->id_flags)) {
412	if (bootverbose)
413	    printf("sc%d: no video adapter is found.\n", dev->id_unit);
414	return (0);
415    }
416
417    sc_port = dev->id_iobase;
418    if (sckbdprobe(dev->id_unit, dev->id_flags))
419	return (IO_KBDSIZE);
420    else
421        return ((dev->id_flags & DETECT_KBD) ? 0 : IO_KBDSIZE);
422}
423
424/* probe video adapters, return TRUE if found */
425static int
426scvidprobe(int unit, int flags)
427{
428    /*
429     * XXX don't try to `printf' anything here, the console may not have
430     * been configured yet.
431     */
432    u_short volatile *cp;
433    u_short was;
434    u_long  pa;
435    u_long  segoff;
436
437    /* do this test only once */
438    if (init_done != COLD)
439	return (Crtat != 0);
440
441    /*
442     * Finish defaulting crtc variables for a mono screen.  Crtat is a
443     * bogus common variable so that it can be shared with pcvt, so it
444     * can't be statically initialized.  XXX.
445     */
446    Crtat = (u_short *)MONO_BUF;
447    crtc_type = KD_MONO;
448    /* If CGA memory seems to work, switch to color.  */
449    cp = (u_short *)CGA_BUF;
450    was = *cp;
451    *cp = (u_short) 0xA55A;
452    if (bootinfo.bi_vesa == 0x102) {
453	vesa_mode = bootinfo.bi_vesa;
454	Crtat  = (u_short *)pa_to_va(0xA0000);
455	crtc_type = KD_PIXEL;
456        bzero(Crtat, 800*600/8);
457    } else if (*cp == 0xA55A) {
458	Crtat = (u_short *)CGA_BUF;
459	crtc_addr = COLOR_BASE;
460	crtc_type = KD_CGA;
461    } else {
462        cp = Crtat;
463	was = *cp;
464	*cp = (u_short) 0xA55A;
465	if (*cp != 0xA55A) {
466	    /* no screen at all, bail out */
467	    Crtat = 0;
468	    return FALSE;
469	}
470    }
471    *cp = was;
472
473    if (crtc_type != KD_PIXEL) {
474	/*
475	 * Check rtc and BIOS date area.
476	 * XXX: don't use BIOSDATA_EQUIPMENT, it is not a dead copy
477	 * of RTC_EQUIPMENT. The bit 4 and 5 of the ETC_EQUIPMENT are
478	 * zeros for EGA and VGA. However, the EGA/VGA BIOS will set
479	 * these bits in BIOSDATA_EQUIPMENT according to the monitor
480	 * type detected.
481	 */
482	switch ((rtcin(RTC_EQUIPMENT) >> 4) & 3) {	/* bit 4 and 5 */
483	case 0: /* EGA/VGA, or nothing */
484	    crtc_type = KD_EGA;
485	    /* the color adapter may be in the 40x25 mode... XXX */
486	    break;
487	case 1: /* CGA 40x25 */
488	    /* switch to the 80x25 mode? XXX */
489	    /* FALL THROUGH */
490	case 2: /* CGA 80x25 */
491	    /* `crtc_type' has already been set... */
492	    /* crtc_type = KD_CGA; */
493	    break;
494	case 3: /* MDA */
495	    /* `crtc_type' has already been set... */
496	    /* crtc_type = KD_MONO; */
497	    break;
498	}
499
500	/* is this a VGA or higher ? */
501	outb(crtc_addr, 7);
502	if (inb(crtc_addr) == 7) {
503
504	    crtc_type = KD_VGA;
505	    crtc_vga = TRUE;
506	    read_vgaregs(vgaregs);
507
508	    /* Get the BIOS video mode pointer */
509	    segoff = *(u_long *)pa_to_va(0x4a8);
510	    pa = (((segoff & 0xffff0000) >> 12) + (segoff & 0xffff));
511	    if (ISMAPPED(pa, sizeof(u_long))) {
512		segoff = *(u_long *)pa_to_va(pa);
513		pa = (((segoff & 0xffff0000) >> 12) + (segoff & 0xffff));
514		if (ISMAPPED(pa, MODE_PARAM_SIZE))
515		    video_mode_ptr = (char *)pa_to_va(pa);
516	    }
517	}
518    }
519
520    return TRUE;
521}
522
523/* probe the keyboard, return TRUE if found */
524static int
525sckbdprobe(int unit, int flags)
526{
527    int codeset;
528    int c = -1;
529    int m;
530
531    sc_kbdc = kbdc_open(sc_port);
532
533    if (!kbdc_lock(sc_kbdc, TRUE)) {
534	/* driver error? */
535	printf("sc%d: unable to lock the controller.\n", unit);
536        return ((flags & DETECT_KBD) ? FALSE : TRUE);
537    }
538
539    /* discard anything left after UserConfig */
540    empty_both_buffers(sc_kbdc, 10);
541
542    /* save the current keyboard controller command byte */
543    m = kbdc_get_device_mask(sc_kbdc) & ~KBD_KBD_CONTROL_BITS;
544    c = get_controller_command_byte(sc_kbdc);
545    if (c == -1) {
546	/* CONTROLLER ERROR */
547	printf("sc%d: unable to get the current command byte value.\n", unit);
548	goto fail;
549    }
550    if (bootverbose)
551	printf("sc%d: the current keyboard controller command byte %04x\n",
552	    unit, c);
553#if 0
554    /* override the keyboard lock switch */
555    c |= KBD_OVERRIDE_KBD_LOCK;
556#endif
557
558    /*
559     * The keyboard may have been screwed up by the boot block.
560     * We may just be able to recover from error by testing the controller
561     * and the keyboard port. The controller command byte needs to be saved
562     * before this recovery operation, as some controllers seem to set
563     * the command byte to particular values.
564     */
565    test_controller(sc_kbdc);
566    test_kbd_port(sc_kbdc);
567
568    /* enable the keyboard port, but disable the keyboard intr. */
569    if (!set_controller_command_byte(sc_kbdc,
570            KBD_KBD_CONTROL_BITS,
571            KBD_ENABLE_KBD_PORT | KBD_DISABLE_KBD_INT)) {
572	/* CONTROLLER ERROR
573	 * there is very little we can do...
574	 */
575	printf("sc%d: unable to set the command byte.\n", unit);
576	goto fail;
577     }
578
579     /*
580      * Check if we have an XT keyboard before we attempt to reset it.
581      * The procedure assumes that the keyboard and the controller have
582      * been set up properly by BIOS and have not been messed up
583      * during the boot process.
584      */
585     codeset = -1;
586     if (flags & XT_KEYBD)
587	 /* the user says there is a XT keyboard */
588	 codeset = 1;
589#ifdef DETECT_XT_KEYBOARD
590     else if ((c & KBD_TRANSLATION) == 0) {
591	 /* SET_SCANCODE_SET is not always supported; ignore error */
592	 if (send_kbd_command_and_data(sc_kbdc, KBDC_SET_SCANCODE_SET, 0)
593		 == KBD_ACK)
594	     codeset = read_kbd_data(sc_kbdc);
595     }
596     if (bootverbose)
597         printf("sc%d: keyboard scancode set %d\n", unit, codeset);
598#endif /* DETECT_XT_KEYBOARD */
599
600    if (flags & KBD_NORESET) {
601        write_kbd_command(sc_kbdc, KBDC_ECHO);
602        if (read_kbd_data(sc_kbdc) != KBD_ECHO) {
603            empty_both_buffers(sc_kbdc, 10);
604            test_controller(sc_kbdc);
605            test_kbd_port(sc_kbdc);
606            if (bootverbose)
607                printf("sc%d: failed to get response from the keyboard.\n",
608		    unit);
609	    goto fail;
610	}
611    } else {
612        /* reset keyboard hardware */
613        if (!reset_kbd(sc_kbdc)) {
614            /* KEYBOARD ERROR
615             * Keyboard reset may fail either because the keyboard doen't
616             * exist, or because the keyboard doesn't pass the self-test,
617             * or the keyboard controller on the motherboard and the keyboard
618             * somehow fail to shake hands. It is just possible, particularly
619             * in the last case, that the keyoard controller may be left
620             * in a hung state. test_controller() and test_kbd_port() appear
621             * to bring the keyboard controller back (I don't know why and
622             * how, though.)
623             */
624            empty_both_buffers(sc_kbdc, 10);
625            test_controller(sc_kbdc);
626            test_kbd_port(sc_kbdc);
627            /* We could disable the keyboard port and interrupt... but,
628             * the keyboard may still exist (see above).
629             */
630            if (bootverbose)
631                printf("sc%d: failed to reset the keyboard.\n", unit);
632            goto fail;
633        }
634    }
635
636    /*
637     * Allow us to set the XT_KEYBD flag in UserConfig so that keyboards
638     * such as those on the IBM ThinkPad laptop computers can be used
639     * with the standard console driver.
640     */
641    if (codeset == 1) {
642	if (send_kbd_command_and_data(
643	        sc_kbdc, KBDC_SET_SCANCODE_SET, codeset) == KBD_ACK) {
644	    /* XT kbd doesn't need scan code translation */
645	    c &= ~KBD_TRANSLATION;
646	} else {
647	    /* KEYBOARD ERROR
648	     * The XT kbd isn't usable unless the proper scan code set
649	     * is selected.
650	     */
651	    printf("sc%d: unable to set the XT keyboard mode.\n", unit);
652	    goto fail;
653	}
654    }
655    /* enable the keyboard port and intr. */
656    if (!set_controller_command_byte(sc_kbdc,
657            KBD_KBD_CONTROL_BITS | KBD_TRANSLATION | KBD_OVERRIDE_KBD_LOCK,
658	    (c & (KBD_TRANSLATION | KBD_OVERRIDE_KBD_LOCK))
659	        | KBD_ENABLE_KBD_PORT | KBD_ENABLE_KBD_INT)) {
660	/* CONTROLLER ERROR
661	 * This is serious; we are left with the disabled keyboard intr.
662	 */
663	printf("sc%d: unable to enable the keyboard port and intr.\n", unit);
664	goto fail;
665    }
666
667    kbdc_set_device_mask(sc_kbdc, m | KBD_KBD_CONTROL_BITS),
668    kbdc_lock(sc_kbdc, FALSE);
669    return TRUE;
670
671fail:
672    if (c != -1)
673        /* try to restore the command byte as before, if possible */
674        set_controller_command_byte(sc_kbdc, 0xff, c);
675    kbdc_set_device_mask(sc_kbdc,
676        (flags & DETECT_KBD) ? m : m | KBD_KBD_CONTROL_BITS);
677    kbdc_lock(sc_kbdc, FALSE);
678    return FALSE;
679}
680
681#if NAPM > 0
682static int
683scresume(void *dummy)
684{
685	shfts = ctls = alts = agrs = metas = accents = 0;
686	return 0;
687}
688#endif
689
690static int
691scattach(struct isa_device *dev)
692{
693    scr_stat *scp;
694    dev_t cdev = makedev(CDEV_MAJOR, 0);
695    char *p;
696#ifdef DEVFS
697    int vc;
698#endif
699
700    scinit();
701    flags = dev->id_flags;
702    if (!crtc_vga)
703	flags &= ~CHAR_CURSOR;
704
705    scp = console[0];
706
707    if (crtc_vga) {
708    	cut_buffer = (char *)malloc(scp->xsize*scp->ysize, M_DEVBUF, M_NOWAIT);
709    }
710
711    scp->scr_buf = (u_short *)malloc(scp->xsize*scp->ysize*sizeof(u_short),
712				     M_DEVBUF, M_NOWAIT);
713
714    /* copy temporary buffer to final buffer */
715    bcopy(sc_buffer, scp->scr_buf, scp->xsize * scp->ysize * sizeof(u_short));
716
717    scp->cursor_pos = scp->cursor_oldpos =
718	scp->scr_buf + scp->xpos + scp->ypos * scp->xsize;
719    scp->mouse_pos = scp->mouse_oldpos =
720	scp->scr_buf + ((scp->mouse_ypos/scp->font_size)*scp->xsize +
721	    		scp->mouse_xpos/8);
722
723    /* initialize history buffer & pointers */
724    scp->history_head = scp->history_pos =
725	(u_short *)malloc(scp->history_size*sizeof(u_short),
726			  M_DEVBUF, M_NOWAIT);
727    if (scp->history_head != NULL)
728        bzero(scp->history_head, scp->history_size*sizeof(u_short));
729    scp->history = scp->history_head;
730
731    /* initialize cursor stuff */
732    if (!(scp->status & UNKNOWN_MODE))
733    	draw_cursor_image(scp);
734
735    /* get screen update going */
736    scrn_timer(NULL);
737
738    update_leds(scp->status);
739
740    if ((crtc_type == KD_VGA) && bootverbose) {
741        printf("sc%d: BIOS video mode:%d\n",
742	    dev->id_unit, *(u_char *)pa_to_va(0x449));
743        printf("sc%d: VGA registers upon power-up\n", dev->id_unit);
744        dump_vgaregs(vgaregs);
745        printf("sc%d: video mode:%d\n", dev->id_unit, scp->mode);
746        printf("sc%d: VGA registers in BIOS for mode:%d\n",
747		dev->id_unit, scp->mode);
748        dump_vgaregs(vgaregs2);
749	p = get_mode_param(scp, scp->mode);
750        if (p != NULL) {
751            printf("sc%d: VGA registers to be used for mode:%d\n",
752		dev->id_unit, scp->mode);
753            dump_vgaregs(p);
754        }
755        printf("sc%d: rows_offset:%d\n", dev->id_unit, rows_offset);
756    }
757    if ((crtc_type == KD_VGA) && (video_mode_ptr == NULL))
758        printf("sc%d: WARNING: video mode switching is only partially supported\n",
759	        dev->id_unit);
760
761    printf("sc%d: ", dev->id_unit);
762    switch(crtc_type) {
763    case KD_VGA:
764	if (crtc_addr == MONO_BASE)
765	    printf("VGA mono");
766	else
767	    printf("VGA color");
768	break;
769    case KD_EGA:
770	if (crtc_addr == MONO_BASE)
771	    printf("EGA mono");
772	else
773	    printf("EGA color");
774	break;
775    case KD_CGA:
776	printf("CGA");
777	break;
778    case KD_PIXEL:
779	printf("Graphics display (VESA mode = 0x%x)", vesa_mode);
780	break;
781    case KD_MONO:
782    case KD_HERCULES:
783    default:
784	printf("MDA/hercules");
785	break;
786    }
787    printf(" <%d virtual consoles, flags=0x%x>\n", MAXCONS, flags);
788
789#if NAPM > 0
790    scp->r_hook.ah_fun = scresume;
791    scp->r_hook.ah_arg = NULL;
792    scp->r_hook.ah_name = "system keyboard";
793    scp->r_hook.ah_order = APM_MID_ORDER;
794    apm_hook_establish(APM_HOOK_RESUME , &scp->r_hook);
795#endif
796
797    cdevsw_add(&cdev, &scdevsw, NULL);
798
799#ifdef DEVFS
800    for (vc = 0; vc < MAXCONS; vc++)
801        sc_devfs_token[vc] = devfs_add_devswf(&scdevsw, vc, DV_CHR,
802				UID_ROOT, GID_WHEEL, 0600, "ttyv%n", vc);
803    sc_mouse_devfs_token = devfs_add_devswf(&scdevsw, SC_MOUSE, DV_CHR,
804				UID_ROOT, GID_WHEEL, 0600, "sysmouse");
805    sc_console_devfs_token = devfs_add_devswf(&scdevsw, SC_CONSOLE, DV_CHR,
806				UID_ROOT, GID_WHEEL, 0600, "consolectl");
807#endif
808    return 0;
809}
810
811struct tty
812*scdevtotty(dev_t dev)
813{
814    int unit = minor(dev);
815
816    if (init_done == COLD)
817	return(NULL);
818    if (unit == SC_CONSOLE)
819	return CONSOLE_TTY;
820    if (unit == SC_MOUSE)
821	return MOUSE_TTY;
822    if (unit >= MAXCONS || unit < 0)
823	return(NULL);
824    return VIRTUAL_TTY(unit);
825}
826
827int
828scopen(dev_t dev, int flag, int mode, struct proc *p)
829{
830    struct tty *tp = scdevtotty(dev);
831
832    if (!tp)
833	return(ENXIO);
834
835    tp->t_oproc = (minor(dev) == SC_MOUSE) ? scmousestart : scstart;
836    tp->t_param = scparam;
837    tp->t_dev = dev;
838    if (!(tp->t_state & TS_ISOPEN)) {
839	ttychars(tp);
840        /* Use the current setting of the <-- key as default VERASE. */
841        /* If the Delete key is preferable, an stty is necessary     */
842        tp->t_cc[VERASE] = key_map.key[0x0e].map[0];
843	tp->t_iflag = TTYDEF_IFLAG;
844	tp->t_oflag = TTYDEF_OFLAG;
845	tp->t_cflag = TTYDEF_CFLAG;
846	tp->t_lflag = TTYDEF_LFLAG;
847	tp->t_ispeed = tp->t_ospeed = TTYDEF_SPEED;
848	scparam(tp, &tp->t_termios);
849	ttsetwater(tp);
850	(*linesw[tp->t_line].l_modem)(tp, 1);
851    	if (minor(dev) == SC_MOUSE)
852	    mouse_level = 0;		/* XXX */
853    }
854    else
855	if (tp->t_state & TS_XCLUDE && p->p_ucred->cr_uid != 0)
856	    return(EBUSY);
857    if (minor(dev) < MAXCONS && !console[minor(dev)]) {
858	console[minor(dev)] = alloc_scp();
859    }
860    if (minor(dev)<MAXCONS && !tp->t_winsize.ws_col && !tp->t_winsize.ws_row) {
861	tp->t_winsize.ws_col = console[minor(dev)]->xsize;
862	tp->t_winsize.ws_row = console[minor(dev)]->ysize;
863    }
864    return ((*linesw[tp->t_line].l_open)(dev, tp));
865}
866
867int
868scclose(dev_t dev, int flag, int mode, struct proc *p)
869{
870    struct tty *tp = scdevtotty(dev);
871    struct scr_stat *scp;
872
873    if (!tp)
874	return(ENXIO);
875    if (minor(dev) < MAXCONS) {
876	scp = get_scr_stat(tp->t_dev);
877	if (scp->status & SWITCH_WAIT_ACQ)
878	    wakeup((caddr_t)&scp->smode);
879#if not_yet_done
880	if (scp == &main_console) {
881	    scp->pid = 0;
882	    scp->proc = NULL;
883	    scp->smode.mode = VT_AUTO;
884	}
885	else {
886	    free(scp->scr_buf, M_DEVBUF);
887	    if (scp->history != NULL) {
888		free(scp->history, M_DEVBUF);
889		if (scp->history_size / scp->xsize
890			> imax(SC_HISTORY_SIZE, scp->ysize))
891		    extra_history_size += scp->history_size / scp->xsize
892			- imax(SC_HISTORY_SIZE, scp->ysize);
893	    }
894	    free(scp, M_DEVBUF);
895	    console[minor(dev)] = NULL;
896	}
897#else
898	scp->pid = 0;
899	scp->proc = NULL;
900	scp->smode.mode = VT_AUTO;
901#endif
902    }
903    spltty();
904    (*linesw[tp->t_line].l_close)(tp, flag);
905    ttyclose(tp);
906    spl0();
907    return(0);
908}
909
910int
911scread(dev_t dev, struct uio *uio, int flag)
912{
913    struct tty *tp = scdevtotty(dev);
914
915    if (!tp)
916	return(ENXIO);
917    return((*linesw[tp->t_line].l_read)(tp, uio, flag));
918}
919
920int
921scwrite(dev_t dev, struct uio *uio, int flag)
922{
923    struct tty *tp = scdevtotty(dev);
924
925    if (!tp)
926	return(ENXIO);
927    return((*linesw[tp->t_line].l_write)(tp, uio, flag));
928}
929
930void
931scintr(int unit)
932{
933    static struct tty *cur_tty;
934    int c, len;
935    u_char *cp;
936
937    /*
938     * Loop while there is still input to get from the keyboard.
939     * I don't think this is nessesary, and it doesn't fix
940     * the Xaccel-2.1 keyboard hang, but it can't hurt.		XXX
941     */
942    while ((c = scgetc(SCGETC_NONBLOCK)) != NOKEY) {
943
944	cur_tty = VIRTUAL_TTY(get_scr_num());
945	if (!(cur_tty->t_state & TS_ISOPEN))
946	    if (!((cur_tty = CONSOLE_TTY)->t_state & TS_ISOPEN))
947		continue;
948
949	switch (c & 0xff00) {
950	case 0x0000: /* normal key */
951	    (*linesw[cur_tty->t_line].l_rint)(c & 0xFF, cur_tty);
952	    break;
953	case FKEY:  /* function key, return string */
954	    if (cp = get_fstr((u_int)c, (u_int *)&len)) {
955	    	while (len-- >  0)
956		    (*linesw[cur_tty->t_line].l_rint)(*cp++ & 0xFF, cur_tty);
957	    }
958	    break;
959	case MKEY:  /* meta is active, prepend ESC */
960	    (*linesw[cur_tty->t_line].l_rint)(0x1b, cur_tty);
961	    (*linesw[cur_tty->t_line].l_rint)(c & 0xFF, cur_tty);
962	    break;
963	case BKEY:  /* backtab fixed sequence (esc [ Z) */
964	    (*linesw[cur_tty->t_line].l_rint)(0x1b, cur_tty);
965	    (*linesw[cur_tty->t_line].l_rint)('[', cur_tty);
966	    (*linesw[cur_tty->t_line].l_rint)('Z', cur_tty);
967	    break;
968	}
969    }
970
971    if (cur_console->status & MOUSE_ENABLED) {
972	cur_console->status &= ~MOUSE_VISIBLE;
973	remove_mouse_image(cur_console);
974    }
975}
976
977static int
978scparam(struct tty *tp, struct termios *t)
979{
980    tp->t_ispeed = t->c_ispeed;
981    tp->t_ospeed = t->c_ospeed;
982    tp->t_cflag = t->c_cflag;
983    return 0;
984}
985
986int
987scioctl(dev_t dev, u_long cmd, caddr_t data, int flag, struct proc *p)
988{
989    int error;
990    u_int i;
991    struct tty *tp;
992    scr_stat *scp;
993    u_short *usp;
994    char *mp;
995    int s;
996
997    tp = scdevtotty(dev);
998    if (!tp)
999	return ENXIO;
1000    scp = get_scr_stat(tp->t_dev);
1001
1002    /* If there is a user_ioctl function call that first */
1003    if (sc_user_ioctl) {
1004	if (error = (*sc_user_ioctl)(dev, cmd, data, flag, p))
1005	    return error;
1006    }
1007
1008    switch (cmd) {  		/* process console hardware related ioctl's */
1009
1010    case GIO_ATTR:      	/* get current attributes */
1011	*(int*)data = (scp->term.cur_attr >> 8) & 0xFF;
1012	return 0;
1013
1014    case GIO_COLOR:     	/* is this a color console ? */
1015	if (crtc_addr == COLOR_BASE)
1016	    *(int*)data = 1;
1017	else
1018	    *(int*)data = 0;
1019	return 0;
1020
1021    case CONS_CURRENT:  	/* get current adapter type */
1022	*(int *)data = crtc_type;
1023	return 0;
1024
1025    case CONS_GET:      	/* get current video mode */
1026	*(int*)data = scp->mode;
1027	return 0;
1028
1029    case CONS_BLANKTIME:    	/* set screen saver timeout (0 = no saver) */
1030	if (*(int *)data < 0)
1031            return EINVAL;
1032	scrn_blank_time = *(int *)data;
1033	if (scrn_blank_time == 0)
1034	    getmicrouptime(&scrn_time_stamp);
1035	return 0;
1036
1037    case CONS_CURSORTYPE:   	/* set cursor type blink/noblink */
1038	if ((*(int*)data) & 0x01)
1039	    flags |= BLINK_CURSOR;
1040	else
1041	    flags &= ~BLINK_CURSOR;
1042	if ((*(int*)data) & 0x02) {
1043	    if (!crtc_vga)
1044		return ENXIO;
1045	    flags |= CHAR_CURSOR;
1046	} else
1047	    flags &= ~CHAR_CURSOR;
1048	/*
1049	 * The cursor shape is global property; all virtual consoles
1050	 * are affected. Update the cursor in the current console...
1051	 */
1052	if (!(cur_console->status & UNKNOWN_MODE)) {
1053            remove_cursor_image(cur_console);
1054	    if (flags & CHAR_CURSOR)
1055	        set_destructive_cursor(cur_console);
1056	    draw_cursor_image(cur_console);
1057	}
1058	return 0;
1059
1060    case CONS_BELLTYPE: 	/* set bell type sound/visual */
1061	if (*data)
1062	    flags |= VISUAL_BELL;
1063	else
1064	    flags &= ~VISUAL_BELL;
1065	return 0;
1066
1067    case CONS_HISTORY:  	/* set history size */
1068	if (*(int *)data > 0) {
1069	    int lines;	/* buffer size to allocate */
1070	    int lines0;	/* current buffer size */
1071
1072	    lines = imax(*(int *)data, scp->ysize);
1073	    lines0 = (scp->history != NULL) ?
1074		      scp->history_size / scp->xsize : scp->ysize;
1075	    /*
1076	     * syscons unconditionally allocates buffers upto SC_HISTORY_SIZE
1077	     * lines or scp->ysize lines, whichever is larger. A value
1078	     * greater than that is allowed, subject to extra_history_size.
1079	     */
1080	    if (lines > imax(lines0, SC_HISTORY_SIZE) + extra_history_size)
1081                return EINVAL;
1082            if (cur_console->status & BUFFER_SAVED)
1083                return EBUSY;
1084	    usp = scp->history;
1085	    scp->history = NULL;
1086	    if (usp != NULL)
1087		free(usp, M_DEVBUF);
1088	    scp->history_size = lines * scp->xsize;
1089	    /*
1090	     * extra_history_size +=
1091	     *    (lines0 > imax(SC_HISTORY_SIZE, scp->ysize)) ?
1092	     *     lines0 - imax(SC_HISTORY_SIZE, scp->ysize)) : 0;
1093	     * extra_history_size -=
1094	     *    (lines > imax(SC_HISTORY_SIZE, scp->ysize)) ?
1095	     *	   lines - imax(SC_HISTORY_SIZE, scp->ysize)) : 0;
1096	     * lines0 >= ysize && lines >= ysize... Hey, the above can be
1097	     * reduced to the following...
1098	     */
1099	    extra_history_size +=
1100		imax(lines0, SC_HISTORY_SIZE) - imax(lines, SC_HISTORY_SIZE);
1101	    usp = (u_short *)malloc(scp->history_size * sizeof(u_short),
1102				    M_DEVBUF, M_WAITOK);
1103	    bzero(usp, scp->history_size * sizeof(u_short));
1104	    scp->history_head = scp->history_pos = usp;
1105	    scp->history = usp;
1106	    return 0;
1107	}
1108	else
1109	    return EINVAL;
1110
1111    case CONS_MOUSECTL:		/* control mouse arrow */
1112    case OLD_CONS_MOUSECTL:
1113    {
1114	/* MOUSE_BUTTON?DOWN -> MOUSE_MSC_BUTTON?UP */
1115	static butmap[8] = {
1116            MOUSE_MSC_BUTTON1UP | MOUSE_MSC_BUTTON2UP
1117		| MOUSE_MSC_BUTTON3UP,
1118            MOUSE_MSC_BUTTON2UP | MOUSE_MSC_BUTTON3UP,
1119            MOUSE_MSC_BUTTON1UP | MOUSE_MSC_BUTTON3UP,
1120            MOUSE_MSC_BUTTON3UP,
1121            MOUSE_MSC_BUTTON1UP | MOUSE_MSC_BUTTON2UP,
1122            MOUSE_MSC_BUTTON2UP,
1123            MOUSE_MSC_BUTTON1UP,
1124            0,
1125	};
1126	mouse_info_t *mouse = (mouse_info_t*)data;
1127	mouse_info_t buf;
1128
1129	if (!crtc_vga)
1130	    return ENODEV;
1131
1132	if (cmd == OLD_CONS_MOUSECTL) {
1133	    static unsigned char swapb[] = { 0, 4, 2, 6, 1, 5, 3, 7 };
1134	    old_mouse_info_t *old_mouse = (old_mouse_info_t *)data;
1135
1136	    mouse = &buf;
1137	    mouse->operation = old_mouse->operation;
1138	    switch (mouse->operation) {
1139	    case MOUSE_MODE:
1140		mouse->u.mode = old_mouse->u.mode;
1141		break;
1142	    case MOUSE_SHOW:
1143	    case MOUSE_HIDE:
1144		break;
1145	    case MOUSE_MOVEABS:
1146	    case MOUSE_MOVEREL:
1147	    case MOUSE_ACTION:
1148		mouse->u.data.x = old_mouse->u.data.x;
1149		mouse->u.data.y = old_mouse->u.data.y;
1150		mouse->u.data.z = 0;
1151		mouse->u.data.buttons = swapb[old_mouse->u.data.buttons & 0x7];
1152		break;
1153	    case MOUSE_GETINFO:
1154		old_mouse->u.data.x = scp->mouse_xpos;
1155		old_mouse->u.data.y = scp->mouse_ypos;
1156		old_mouse->u.data.buttons = swapb[scp->mouse_buttons & 0x7];
1157		break;
1158	    default:
1159		return EINVAL;
1160	    }
1161	}
1162
1163	switch (mouse->operation) {
1164	case MOUSE_MODE:
1165	    if (ISSIGVALID(mouse->u.mode.signal)) {
1166		scp->mouse_signal = mouse->u.mode.signal;
1167		scp->mouse_proc = p;
1168		scp->mouse_pid = p->p_pid;
1169	    }
1170	    else {
1171		scp->mouse_signal = 0;
1172		scp->mouse_proc = NULL;
1173		scp->mouse_pid = 0;
1174	    }
1175	    break;
1176
1177	case MOUSE_SHOW:
1178	    if (!(scp->status & MOUSE_ENABLED)) {
1179		scp->status |= (MOUSE_ENABLED | MOUSE_VISIBLE);
1180		scp->mouse_oldpos = scp->mouse_pos;
1181		mark_all(scp);
1182	    }
1183	    else
1184		return EINVAL;
1185	    break;
1186
1187	case MOUSE_HIDE:
1188	    if (scp->status & MOUSE_ENABLED) {
1189		scp->status &= ~(MOUSE_ENABLED | MOUSE_VISIBLE);
1190		mark_all(scp);
1191	    }
1192	    else
1193		return EINVAL;
1194	    break;
1195
1196	case MOUSE_MOVEABS:
1197	    scp->mouse_xpos = mouse->u.data.x;
1198	    scp->mouse_ypos = mouse->u.data.y;
1199	    set_mouse_pos(scp);
1200	    break;
1201
1202	case MOUSE_MOVEREL:
1203	    scp->mouse_xpos += mouse->u.data.x;
1204	    scp->mouse_ypos += mouse->u.data.y;
1205	    set_mouse_pos(scp);
1206	    break;
1207
1208	case MOUSE_GETINFO:
1209	    mouse->u.data.x = scp->mouse_xpos;
1210	    mouse->u.data.y = scp->mouse_ypos;
1211	    mouse->u.data.z = 0;
1212	    mouse->u.data.buttons = scp->mouse_buttons;
1213	    break;
1214
1215	case MOUSE_ACTION:
1216	case MOUSE_MOTION_EVENT:
1217	    /* this should maybe only be settable from /dev/consolectl SOS */
1218	    /* send out mouse event on /dev/sysmouse */
1219
1220	    mouse_status.dx += mouse->u.data.x;
1221	    mouse_status.dy += mouse->u.data.y;
1222	    mouse_status.dz += mouse->u.data.z;
1223	    if (mouse->operation == MOUSE_ACTION)
1224	        mouse_status.button = mouse->u.data.buttons;
1225	    mouse_status.flags |=
1226		((mouse->u.data.x || mouse->u.data.y || mouse->u.data.z) ?
1227		    MOUSE_POSCHANGED : 0)
1228		| (mouse_status.obutton ^ mouse_status.button);
1229
1230	    if (cur_console->status & MOUSE_ENABLED)
1231	    	cur_console->status |= MOUSE_VISIBLE;
1232
1233	    if ((MOUSE_TTY)->t_state & TS_ISOPEN) {
1234		u_char buf[MOUSE_SYS_PACKETSIZE];
1235		int j;
1236
1237		/* the first five bytes are compatible with MouseSystems' */
1238		buf[0] = MOUSE_MSC_SYNC
1239		    | butmap[mouse_status.button & MOUSE_STDBUTTONS];
1240		j = imax(imin(mouse->u.data.x, 255), -256);
1241		buf[1] = j >> 1;
1242		buf[3] = j - buf[1];
1243		j = -imax(imin(mouse->u.data.y, 255), -256);
1244		buf[2] = j >> 1;
1245		buf[4] = j - buf[2];
1246		for (j = 0; j < MOUSE_MSC_PACKETSIZE; j++)
1247	    		(*linesw[(MOUSE_TTY)->t_line].l_rint)(buf[j],MOUSE_TTY);
1248		if (mouse_level >= 1) { 	/* extended part */
1249		    j = imax(imin(mouse->u.data.z, 127), -128);
1250		    buf[5] = (j >> 1) & 0x7f;
1251		    buf[6] = (j - (j >> 1)) & 0x7f;
1252		    /* buttons 4-10 */
1253		    buf[7] = (~mouse_status.button >> 3) & 0x7f;
1254		    for (j = MOUSE_MSC_PACKETSIZE;
1255			 j < MOUSE_SYS_PACKETSIZE; j++)
1256	    		(*linesw[(MOUSE_TTY)->t_line].l_rint)(buf[j],MOUSE_TTY);
1257		}
1258	    }
1259
1260	    if (cur_console->mouse_signal) {
1261		cur_console->mouse_buttons = mouse->u.data.buttons;
1262    		/* has controlling process died? */
1263		if (cur_console->mouse_proc &&
1264		    (cur_console->mouse_proc != pfind(cur_console->mouse_pid))){
1265		    	cur_console->mouse_signal = 0;
1266			cur_console->mouse_proc = NULL;
1267			cur_console->mouse_pid = 0;
1268		}
1269		else
1270		    psignal(cur_console->mouse_proc, cur_console->mouse_signal);
1271	    }
1272	    else if (mouse->operation == MOUSE_ACTION) {
1273		/* process button presses */
1274		if ((cur_console->mouse_buttons ^ mouse->u.data.buttons) &&
1275		    !(cur_console->status & UNKNOWN_MODE)) {
1276		    cur_console->mouse_buttons = mouse->u.data.buttons;
1277		    if (cur_console->mouse_buttons & MOUSE_BUTTON1DOWN)
1278			mouse_cut_start(cur_console);
1279		    else
1280			mouse_cut_end(cur_console);
1281		    if (cur_console->mouse_buttons & MOUSE_BUTTON2DOWN ||
1282			cur_console->mouse_buttons & MOUSE_BUTTON3DOWN)
1283			mouse_paste(cur_console);
1284		}
1285	    }
1286
1287	    if (mouse->u.data.x != 0 || mouse->u.data.y != 0) {
1288		cur_console->mouse_xpos += mouse->u.data.x;
1289		cur_console->mouse_ypos += mouse->u.data.y;
1290		set_mouse_pos(cur_console);
1291	    }
1292
1293	    break;
1294
1295	case MOUSE_BUTTON_EVENT:
1296	    if ((mouse->u.event.id & MOUSE_BUTTONS) == 0)
1297		return EINVAL;
1298	    if (mouse->u.event.value < 0)
1299		return EINVAL;
1300
1301	    if (mouse->u.event.value > 0) {
1302	        cur_console->mouse_buttons |= mouse->u.event.id;
1303	        mouse_status.button |= mouse->u.event.id;
1304	    } else {
1305	        cur_console->mouse_buttons &= ~mouse->u.event.id;
1306	        mouse_status.button &= ~mouse->u.event.id;
1307	    }
1308	    mouse_status.flags |=
1309		((mouse->u.data.x || mouse->u.data.y || mouse->u.data.z) ?
1310		    MOUSE_POSCHANGED : 0)
1311		| (mouse_status.obutton ^ mouse_status.button);
1312
1313	    if (cur_console->status & MOUSE_ENABLED)
1314	    	cur_console->status |= MOUSE_VISIBLE;
1315
1316	    if ((MOUSE_TTY)->t_state & TS_ISOPEN) {
1317		u_char buf[8];
1318		int i;
1319
1320		buf[0] = MOUSE_MSC_SYNC
1321			 | butmap[mouse_status.button & MOUSE_STDBUTTONS];
1322		buf[7] = (~mouse_status.button >> 3) & 0x7f;
1323		buf[1] = buf[2] = buf[3] = buf[4] = buf[5] = buf[6] = 0;
1324		for (i = 0;
1325		     i < ((mouse_level >= 1) ? MOUSE_SYS_PACKETSIZE
1326					     : MOUSE_MSC_PACKETSIZE); i++)
1327	    	    (*linesw[(MOUSE_TTY)->t_line].l_rint)(buf[i],MOUSE_TTY);
1328	    }
1329
1330	    if (cur_console->mouse_signal) {
1331		if (cur_console->mouse_proc &&
1332		    (cur_console->mouse_proc != pfind(cur_console->mouse_pid))){
1333		    	cur_console->mouse_signal = 0;
1334			cur_console->mouse_proc = NULL;
1335			cur_console->mouse_pid = 0;
1336		}
1337		else
1338		    psignal(cur_console->mouse_proc, cur_console->mouse_signal);
1339		break;
1340	    }
1341
1342	    if (cur_console->status & UNKNOWN_MODE)
1343		break;
1344
1345	    switch (mouse->u.event.id) {
1346	    case MOUSE_BUTTON1DOWN:
1347	        switch (mouse->u.event.value % 4) {
1348		case 0:	/* up */
1349		    mouse_cut_end(cur_console);
1350		    break;
1351		case 1:
1352		    mouse_cut_start(cur_console);
1353		    break;
1354		case 2:
1355		    mouse_cut_word(cur_console);
1356		    break;
1357		case 3:
1358		    mouse_cut_line(cur_console);
1359		    break;
1360		}
1361		break;
1362	    case MOUSE_BUTTON2DOWN:
1363	        switch (mouse->u.event.value) {
1364		case 0:	/* up */
1365		    break;
1366		default:
1367		    mouse_paste(cur_console);
1368		    break;
1369		}
1370		break;
1371	    case MOUSE_BUTTON3DOWN:
1372	        switch (mouse->u.event.value) {
1373		case 0:	/* up */
1374		    if (!(cur_console->mouse_buttons & MOUSE_BUTTON1DOWN))
1375		        mouse_cut_end(cur_console);
1376		    break;
1377		default:
1378		    mouse_cut_extend(cur_console);
1379		    break;
1380		}
1381		break;
1382	    }
1383	    break;
1384
1385	default:
1386	    return EINVAL;
1387	}
1388	/* make screensaver happy */
1389	getmicrouptime(&scrn_time_stamp);
1390	return 0;
1391    }
1392
1393    /* MOUSE_XXX: /dev/sysmouse ioctls */
1394    case MOUSE_GETHWINFO:	/* get device information */
1395    {
1396	mousehw_t *hw = (mousehw_t *)data;
1397
1398	if (tp != MOUSE_TTY)
1399	    return ENOTTY;
1400	hw->buttons = 10;		/* XXX unknown */
1401	hw->iftype = MOUSE_IF_SYSMOUSE;
1402	hw->type = MOUSE_MOUSE;
1403	hw->model = MOUSE_MODEL_GENERIC;
1404	hw->hwid = 0;
1405	return 0;
1406    }
1407
1408    case MOUSE_GETMODE:		/* get protocol/mode */
1409    {
1410	mousemode_t *mode = (mousemode_t *)data;
1411
1412	if (tp != MOUSE_TTY)
1413	    return ENOTTY;
1414	mode->level = mouse_level;
1415	switch (mode->level) {
1416	case 0:
1417	    /* at this level, sysmouse emulates MouseSystems protocol */
1418	    mode->protocol = MOUSE_PROTO_MSC;
1419	    mode->rate = -1;		/* unknown */
1420	    mode->resolution = -1;	/* unknown */
1421	    mode->accelfactor = 0;	/* disabled */
1422	    mode->packetsize = MOUSE_MSC_PACKETSIZE;
1423	    mode->syncmask[0] = MOUSE_MSC_SYNCMASK;
1424	    mode->syncmask[1] = MOUSE_MSC_SYNC;
1425	    break;
1426
1427	case 1:
1428	    /* at this level, sysmouse uses its own protocol */
1429	    mode->protocol = MOUSE_PROTO_SYSMOUSE;
1430	    mode->rate = -1;
1431	    mode->resolution = -1;
1432	    mode->accelfactor = 0;
1433	    mode->packetsize = MOUSE_SYS_PACKETSIZE;
1434	    mode->syncmask[0] = MOUSE_SYS_SYNCMASK;
1435	    mode->syncmask[1] = MOUSE_SYS_SYNC;
1436	    break;
1437	}
1438	return 0;
1439    }
1440
1441    case MOUSE_SETMODE:		/* set protocol/mode */
1442    {
1443	mousemode_t *mode = (mousemode_t *)data;
1444
1445	if (tp != MOUSE_TTY)
1446	    return ENOTTY;
1447	if ((mode->level < 0) || (mode->level > 1))
1448	    return EINVAL;
1449	mouse_level = mode->level;
1450	return 0;
1451    }
1452
1453    case MOUSE_GETLEVEL:	/* get operation level */
1454	if (tp != MOUSE_TTY)
1455	    return ENOTTY;
1456	*(int *)data = mouse_level;
1457	return 0;
1458
1459    case MOUSE_SETLEVEL:	/* set operation level */
1460	if (tp != MOUSE_TTY)
1461	    return ENOTTY;
1462	if ((*(int *)data  < 0) || (*(int *)data > 1))
1463	    return EINVAL;
1464	mouse_level = *(int *)data;
1465	return 0;
1466
1467    case MOUSE_GETSTATUS:	/* get accumulated mouse events */
1468	if (tp != MOUSE_TTY)
1469	    return ENOTTY;
1470	s = spltty();
1471	*(mousestatus_t *)data = mouse_status;
1472	mouse_status.flags = 0;
1473	mouse_status.obutton = mouse_status.button;
1474	mouse_status.dx = 0;
1475	mouse_status.dy = 0;
1476	mouse_status.dz = 0;
1477	splx(s);
1478	return 0;
1479
1480#if notyet
1481    case MOUSE_GETVARS:		/* get internal mouse variables */
1482    case MOUSE_SETVARS:		/* set internal mouse variables */
1483	if (tp != MOUSE_TTY)
1484	    return ENOTTY;
1485	return ENODEV;
1486#endif
1487
1488    case MOUSE_READSTATE:	/* read status from the device */
1489    case MOUSE_READDATA:	/* read data from the device */
1490	if (tp != MOUSE_TTY)
1491	    return ENOTTY;
1492	return ENODEV;
1493
1494    case CONS_GETINFO:  	/* get current (virtual) console info */
1495    {
1496	vid_info_t *ptr = (vid_info_t*)data;
1497	if (ptr->size == sizeof(struct vid_info)) {
1498	    ptr->m_num = get_scr_num();
1499	    ptr->mv_col = scp->xpos;
1500	    ptr->mv_row = scp->ypos;
1501	    ptr->mv_csz = scp->xsize;
1502	    ptr->mv_rsz = scp->ysize;
1503	    ptr->mv_norm.fore = (scp->term.std_color & 0x0f00)>>8;
1504	    ptr->mv_norm.back = (scp->term.std_color & 0xf000)>>12;
1505	    ptr->mv_rev.fore = (scp->term.rev_color & 0x0f00)>>8;
1506	    ptr->mv_rev.back = (scp->term.rev_color & 0xf000)>>12;
1507	    ptr->mv_grfc.fore = 0;      /* not supported */
1508	    ptr->mv_grfc.back = 0;      /* not supported */
1509	    ptr->mv_ovscan = scp->border;
1510	    ptr->mk_keylock = scp->status & LOCK_KEY_MASK;
1511	    return 0;
1512	}
1513	return EINVAL;
1514    }
1515
1516    case CONS_GETVERS:  	/* get version number */
1517	*(int*)data = 0x200;    /* version 2.0 */
1518	return 0;
1519
1520    /* VGA TEXT MODES */
1521    case SW_VGA_C40x25:
1522    case SW_VGA_C80x25: case SW_VGA_M80x25:
1523    case SW_VGA_C80x30: case SW_VGA_M80x30:
1524    case SW_VGA_C80x50: case SW_VGA_M80x50:
1525    case SW_VGA_C80x60: case SW_VGA_M80x60:
1526    case SW_B40x25:     case SW_C40x25:
1527    case SW_B80x25:     case SW_C80x25:
1528    case SW_ENH_B40x25: case SW_ENH_C40x25:
1529    case SW_ENH_B80x25: case SW_ENH_C80x25:
1530    case SW_ENH_B80x43: case SW_ENH_C80x43:
1531    case SW_EGAMONO80x25:
1532
1533	if (!crtc_vga)
1534 	    return ENODEV;
1535 	mp = get_mode_param(scp, cmd & 0xff);
1536 	if (mp == NULL)
1537 	    return ENODEV;
1538
1539	s = spltty();
1540	if ((error = wait_scrn_saver_stop())) {
1541	    splx(s);
1542	    return error;
1543	}
1544
1545	scp->status &= ~MOUSE_VISIBLE;
1546	remove_cutmarking(scp);
1547	if (scp->history != NULL)
1548	    i = imax(scp->history_size / scp->xsize
1549		     - imax(SC_HISTORY_SIZE, scp->ysize), 0);
1550	else
1551	    i = 0;
1552	switch (cmd & 0xff) {
1553	case M_VGA_C80x60: case M_VGA_M80x60:
1554	    if (!(fonts_loaded & FONT_8)) {
1555		splx(s);
1556		return EINVAL;
1557	    }
1558	    /*
1559	     * This is a kludge to fend off scrn_update() while we
1560	     * muck around with scp. XXX
1561	     */
1562	    scp->status |= UNKNOWN_MODE;
1563	    scp->xsize = 80;
1564	    scp->ysize = 60;
1565	    scp->font_size = 8;
1566	    break;
1567	case M_VGA_C80x50: case M_VGA_M80x50:
1568	    if (!(fonts_loaded & FONT_8)) {
1569		splx(s);
1570		return EINVAL;
1571	    }
1572	    scp->status |= UNKNOWN_MODE;
1573	    scp->xsize = 80;
1574	    scp->ysize = 50;
1575	    scp->font_size = 8;
1576	    break;
1577	case M_ENH_B80x43: case M_ENH_C80x43:
1578	    if (!(fonts_loaded & FONT_8)) {
1579		splx(s);
1580		return EINVAL;
1581	    }
1582	    scp->status |= UNKNOWN_MODE;
1583	    scp->xsize = 80;
1584	    scp->ysize = 43;
1585	    scp->font_size = 8;
1586	    break;
1587	case M_VGA_C80x30: case M_VGA_M80x30:
1588	    scp->status |= UNKNOWN_MODE;
1589	    scp->xsize = 80;
1590	    scp->ysize = 30;
1591	    scp->font_size = mp[2];
1592	    break;
1593	case M_ENH_C40x25: case M_ENH_B40x25:
1594	case M_ENH_C80x25: case M_ENH_B80x25:
1595	case M_EGAMONO80x25:
1596	    if (!(fonts_loaded & FONT_14)) {
1597		splx(s);
1598		return EINVAL;
1599	    }
1600	    /* FALL THROUGH */
1601	default:
1602	    if ((cmd & 0xff) > M_VGA_CG320) {
1603		splx(s);
1604		return EINVAL;
1605	    }
1606	    scp->status |= UNKNOWN_MODE;
1607            scp->xsize = mp[0];
1608            scp->ysize = mp[1] + rows_offset;
1609	    scp->font_size = mp[2];
1610	    break;
1611	}
1612
1613	scp->mode = cmd & 0xff;
1614	scp->xpixel = scp->xsize * 8;
1615	scp->ypixel = scp->ysize * scp->font_size;
1616	free(scp->scr_buf, M_DEVBUF);
1617	scp->scr_buf = (u_short *)
1618	    malloc(scp->xsize*scp->ysize*sizeof(u_short), M_DEVBUF, M_WAITOK);
1619	/* move the text cursor to the home position */
1620	move_crsr(scp, 0, 0);
1621	/* move the mouse cursor at the center of the screen */
1622	scp->mouse_xpos = scp->xpixel / 2;
1623	scp->mouse_ypos = scp->ypixel / 2;
1624    	scp->mouse_pos = scp->mouse_oldpos =
1625	    scp->scr_buf + (scp->mouse_ypos / scp->font_size) * scp->xsize
1626	    + scp->mouse_xpos / 8;
1627	free(cut_buffer, M_DEVBUF);
1628    	cut_buffer = (char *)malloc(scp->xsize*scp->ysize, M_DEVBUF, M_NOWAIT);
1629	cut_buffer[0] = 0x00;
1630	splx(s);
1631
1632	usp = scp->history;
1633	scp->history = NULL;
1634	if (usp != NULL) {
1635	    free(usp, M_DEVBUF);
1636	    extra_history_size += i;
1637	}
1638	scp->history_size = imax(SC_HISTORY_SIZE, scp->ysize) * scp->xsize;
1639	usp = (u_short *)malloc(scp->history_size * sizeof(u_short),
1640				M_DEVBUF, M_NOWAIT);
1641	if (usp != NULL)
1642	    bzero(usp, scp->history_size * sizeof(u_short));
1643	scp->history_head = scp->history_pos = usp;
1644	scp->history = usp;
1645	if (scp == cur_console)
1646	    set_mode(scp);
1647	clear_screen(scp);
1648	scp->status &= ~UNKNOWN_MODE;
1649
1650	if (tp->t_winsize.ws_col != scp->xsize
1651	    || tp->t_winsize.ws_row != scp->ysize) {
1652	    tp->t_winsize.ws_col = scp->xsize;
1653	    tp->t_winsize.ws_row = scp->ysize;
1654	    pgsignal(tp->t_pgrp, SIGWINCH, 1);
1655	}
1656	return 0;
1657
1658    /* GRAPHICS MODES */
1659    case SW_BG320:     case SW_BG640:
1660    case SW_CG320:     case SW_CG320_D:   case SW_CG640_E:
1661    case SW_CG640x350: case SW_ENH_CG640:
1662    case SW_BG640x480: case SW_CG640x480: case SW_VGA_CG320:
1663
1664	if (!crtc_vga)
1665	    return ENODEV;
1666	mp = get_mode_param(scp, cmd & 0xff);
1667	if (mp == NULL)
1668	    return ENODEV;
1669
1670	s = spltty();
1671	if ((error = wait_scrn_saver_stop())) {
1672	    splx(s);
1673	    return error;
1674	}
1675
1676	scp->status &= ~MOUSE_VISIBLE;
1677	remove_cutmarking(scp);
1678	scp->status |= UNKNOWN_MODE;    /* graphics mode */
1679	scp->mode = cmd & 0xFF;
1680	scp->xpixel = mp[0] * 8;
1681	scp->ypixel = (mp[1] + rows_offset) * mp[2];
1682	scp->font_size = FONT_NONE;
1683	/* move the mouse cursor at the center of the screen */
1684	scp->mouse_xpos = scp->xpixel / 2;
1685	scp->mouse_ypos = scp->ypixel / 2;
1686	splx(s);
1687
1688	if (scp == cur_console)
1689	    set_mode(scp);
1690	/* clear_graphics();*/
1691
1692	if (tp->t_winsize.ws_xpixel != scp->xpixel
1693	    || tp->t_winsize.ws_ypixel != scp->ypixel) {
1694	    tp->t_winsize.ws_xpixel = scp->xpixel;
1695	    tp->t_winsize.ws_ypixel = scp->ypixel;
1696	    pgsignal(tp->t_pgrp, SIGWINCH, 1);
1697	}
1698	return 0;
1699
1700    case SW_VGA_MODEX:
1701	if (!crtc_vga)
1702	    return ENODEV;
1703	mp = get_mode_param(scp, cmd & 0xff);
1704	if (mp == NULL)
1705	    return ENODEV;
1706
1707	s = spltty();
1708	if ((error = wait_scrn_saver_stop())) {
1709	    splx(s);
1710	    return error;
1711	}
1712
1713	scp->status &= ~MOUSE_VISIBLE;
1714	remove_cutmarking(scp);
1715	scp->status |= UNKNOWN_MODE;    /* graphics mode */
1716	scp->mode = cmd & 0xFF;
1717	scp->xpixel = 320;
1718	scp->ypixel = 240;
1719	scp->font_size = FONT_NONE;
1720	splx(s);
1721
1722	if (scp == cur_console)
1723	    set_mode(scp);
1724	/* clear_graphics();*/
1725	if (tp->t_winsize.ws_xpixel != scp->xpixel
1726	    || tp->t_winsize.ws_ypixel != scp->ypixel) {
1727	    tp->t_winsize.ws_xpixel = scp->xpixel;
1728	    tp->t_winsize.ws_ypixel = scp->ypixel;
1729	    pgsignal(tp->t_pgrp, SIGWINCH, 1);
1730	}
1731	return 0;
1732
1733    case VT_SETMODE:    	/* set screen switcher mode */
1734    {
1735	struct vt_mode *mode;
1736
1737	mode = (struct vt_mode *)data;
1738	if (ISSIGVALID(mode->relsig) && ISSIGVALID(mode->acqsig) &&
1739	    ISSIGVALID(mode->frsig)) {
1740	    bcopy(data, &scp->smode, sizeof(struct vt_mode));
1741	    if (scp->smode.mode == VT_PROCESS) {
1742		scp->proc = p;
1743		scp->pid = scp->proc->p_pid;
1744	    }
1745	    return 0;
1746	} else
1747	    return EINVAL;
1748    }
1749
1750    case VT_GETMODE:    	/* get screen switcher mode */
1751	bcopy(&scp->smode, data, sizeof(struct vt_mode));
1752	return 0;
1753
1754    case VT_RELDISP:    	/* screen switcher ioctl */
1755	switch(*data) {
1756	case VT_FALSE:  	/* user refuses to release screen, abort */
1757	    if (scp == old_scp && (scp->status & SWITCH_WAIT_REL)) {
1758		old_scp->status &= ~SWITCH_WAIT_REL;
1759		switch_in_progress = FALSE;
1760		return 0;
1761	    }
1762	    return EINVAL;
1763
1764	case VT_TRUE:   	/* user has released screen, go on */
1765	    if (scp == old_scp && (scp->status & SWITCH_WAIT_REL)) {
1766		scp->status &= ~SWITCH_WAIT_REL;
1767		exchange_scr();
1768		if (new_scp->smode.mode == VT_PROCESS) {
1769		    new_scp->status |= SWITCH_WAIT_ACQ;
1770		    psignal(new_scp->proc, new_scp->smode.acqsig);
1771		}
1772		else
1773		    switch_in_progress = FALSE;
1774		return 0;
1775	    }
1776	    return EINVAL;
1777
1778	case VT_ACKACQ: 	/* acquire acknowledged, switch completed */
1779	    if (scp == new_scp && (scp->status & SWITCH_WAIT_ACQ)) {
1780		scp->status &= ~SWITCH_WAIT_ACQ;
1781		switch_in_progress = FALSE;
1782		return 0;
1783	    }
1784	    return EINVAL;
1785
1786	default:
1787	    return EINVAL;
1788	}
1789	/* NOT REACHED */
1790
1791    case VT_OPENQRY:    	/* return free virtual console */
1792	for (i = 0; i < MAXCONS; i++) {
1793	    tp = VIRTUAL_TTY(i);
1794	    if (!(tp->t_state & TS_ISOPEN)) {
1795		*data = i + 1;
1796		return 0;
1797	    }
1798	}
1799	return EINVAL;
1800
1801    case VT_ACTIVATE:   	/* switch to screen *data */
1802	return switch_scr(scp, (*data) - 1);
1803
1804    case VT_WAITACTIVE: 	/* wait for switch to occur */
1805	if (*data > MAXCONS || *data < 0)
1806	    return EINVAL;
1807	if (minor(dev) == (*data) - 1)
1808	    return 0;
1809	if (*data == 0) {
1810	    if (scp == cur_console)
1811		return 0;
1812	}
1813	else
1814	    scp = console[(*data) - 1];
1815	while ((error=tsleep((caddr_t)&scp->smode, PZERO|PCATCH,
1816			     "waitvt", 0)) == ERESTART) ;
1817	return error;
1818
1819    case VT_GETACTIVE:
1820	*data = get_scr_num()+1;
1821	return 0;
1822
1823    case KDENABIO:      	/* allow io operations */
1824	error = suser(p->p_ucred, &p->p_acflag);
1825	if (error != 0)
1826	    return error;
1827	if (securelevel > 0)
1828	    return EPERM;
1829	p->p_md.md_regs->tf_eflags |= PSL_IOPL;
1830	return 0;
1831
1832    case KDDISABIO:     	/* disallow io operations (default) */
1833	p->p_md.md_regs->tf_eflags &= ~PSL_IOPL;
1834	return 0;
1835
1836    case KDSETMODE:     	/* set current mode of this (virtual) console */
1837	switch (*data) {
1838	case KD_TEXT:   	/* switch to TEXT (known) mode */
1839	    /* restore fonts & palette ! */
1840	    if (crtc_vga) {
1841#if 0
1842		/*
1843		 * FONT KLUDGE
1844		 * Don't load fonts for now... XXX
1845		 */
1846		if (fonts_loaded & FONT_8)
1847		    copy_font(LOAD, FONT_8, font_8);
1848		if (fonts_loaded & FONT_14)
1849		    copy_font(LOAD, FONT_14, font_14);
1850		if (fonts_loaded & FONT_16)
1851		    copy_font(LOAD, FONT_16, font_16);
1852#endif
1853		load_palette(palette);
1854	    }
1855
1856	    /* move hardware cursor out of the way */
1857	    outb(crtc_addr, 14);
1858	    outb(crtc_addr + 1, 0xff);
1859	    outb(crtc_addr, 15);
1860	    outb(crtc_addr + 1, 0xff);
1861
1862	    /* FALL THROUGH */
1863
1864	case KD_TEXT1:  	/* switch to TEXT (known) mode */
1865	    s = spltty();
1866	    if ((error = wait_scrn_saver_stop())) {
1867		splx(s);
1868		return error;
1869	    }
1870	    scp->status &= ~MOUSE_VISIBLE;
1871	    remove_cutmarking(scp);
1872	    scp->status |= UNKNOWN_MODE;
1873	    splx(s);
1874	    /* no restore fonts & palette */
1875	    if (crtc_vga)
1876		set_mode(scp);
1877	    scp->status &= ~UNKNOWN_MODE;
1878	    clear_screen(scp);
1879	    return 0;
1880
1881	case KD_GRAPHICS:	/* switch to GRAPHICS (unknown) mode */
1882	    s = spltty();
1883	    if ((error = wait_scrn_saver_stop())) {
1884		splx(s);
1885		return error;
1886	    }
1887	    scp->status &= ~MOUSE_VISIBLE;
1888	    remove_cutmarking(scp);
1889	    scp->status |= UNKNOWN_MODE;
1890	    splx(s);
1891	    return 0;
1892	default:
1893	    return EINVAL;
1894	}
1895	/* NOT REACHED */
1896
1897    case KDGETMODE:     	/* get current mode of this (virtual) console */
1898	*data = (scp->status & UNKNOWN_MODE) ? KD_GRAPHICS : KD_TEXT;
1899	return 0;
1900
1901    case KDSBORDER:     	/* set border color of this (virtual) console */
1902	scp->border = *data;
1903	if (scp == cur_console)
1904	    set_border(scp->border);
1905	return 0;
1906
1907    case KDSKBSTATE:    	/* set keyboard state (locks) */
1908	if (*data >= 0 && *data <= LOCK_KEY_MASK) {
1909	    scp->status &= ~LOCK_KEY_MASK;
1910	    scp->status |= *data;
1911	    if (scp == cur_console)
1912		update_leds(scp->status);
1913	    return 0;
1914	}
1915	return EINVAL;
1916
1917    case KDGKBSTATE:    	/* get keyboard state (locks) */
1918	*data = scp->status & LOCK_KEY_MASK;
1919	return 0;
1920
1921    case KDSETRAD:      	/* set keyboard repeat & delay rates */
1922	if (*data & 0x80)
1923	    return EINVAL;
1924	if (sc_kbdc != NULL)
1925	    set_keyboard(KBDC_SET_TYPEMATIC, *data);
1926	return 0;
1927
1928    case KDSKBMODE:     	/* set keyboard mode */
1929	switch (*data) {
1930	case K_RAW: 		/* switch to RAW scancode mode */
1931	    scp->status &= ~KBD_CODE_MODE;
1932	    scp->status |= KBD_RAW_MODE;
1933	    return 0;
1934
1935	case K_CODE: 		/* switch to CODE mode */
1936	    scp->status &= ~KBD_RAW_MODE;
1937	    scp->status |= KBD_CODE_MODE;
1938	    return 0;
1939
1940	case K_XLATE:   	/* switch to XLT ascii mode */
1941	    if (scp == cur_console && scp->status & KBD_RAW_MODE)
1942		shfts = ctls = alts = agrs = metas = accents = 0;
1943	    scp->status &= ~(KBD_RAW_MODE | KBD_CODE_MODE);
1944	    return 0;
1945	default:
1946	    return EINVAL;
1947	}
1948	/* NOT REACHED */
1949
1950    case KDGKBMODE:     	/* get keyboard mode */
1951	*data = (scp->status & KBD_RAW_MODE) ? K_RAW :
1952		((scp->status & KBD_CODE_MODE) ? K_CODE : K_XLATE);
1953	return 0;
1954
1955    case KDMKTONE:      	/* sound the bell */
1956	if (*(int*)data)
1957	    do_bell(scp, (*(int*)data)&0xffff,
1958		    (((*(int*)data)>>16)&0xffff)*hz/1000);
1959	else
1960	    do_bell(scp, scp->bell_pitch, scp->bell_duration);
1961	return 0;
1962
1963    case KIOCSOUND:     	/* make tone (*data) hz */
1964	if (scp == cur_console) {
1965	    if (*(int*)data) {
1966		int pitch = timer_freq / *(int*)data;
1967
1968		/* set command for counter 2, 2 byte write */
1969		if (acquire_timer2(TIMER_16BIT|TIMER_SQWAVE))
1970		    return EBUSY;
1971
1972		/* set pitch */
1973		outb(TIMER_CNTR2, pitch);
1974		outb(TIMER_CNTR2, (pitch>>8));
1975
1976		/* enable counter 2 output to speaker */
1977		outb(IO_PPI, inb(IO_PPI) | 3);
1978	    }
1979	    else {
1980		/* disable counter 2 output to speaker */
1981		outb(IO_PPI, inb(IO_PPI) & 0xFC);
1982		release_timer2();
1983	    }
1984	}
1985	return 0;
1986
1987    case KDGKBTYPE:     	/* get keyboard type */
1988	*data = 0;  		/* type not known (yet) */
1989	return 0;
1990
1991    case KDSETLED:      	/* set keyboard LED status */
1992	if (*data >= 0 && *data <= LED_MASK) {
1993	    scp->status &= ~LED_MASK;
1994	    scp->status |= *data;
1995	    if (scp == cur_console)
1996		update_leds(scp->status);
1997	    return 0;
1998	}
1999	return EINVAL;
2000
2001    case KDGETLED:      	/* get keyboard LED status */
2002	*data = scp->status & LED_MASK;
2003	return 0;
2004
2005    case GETFKEY:       	/* get functionkey string */
2006	if (*(u_short*)data < n_fkey_tab) {
2007	    fkeyarg_t *ptr = (fkeyarg_t*)data;
2008	    bcopy(&fkey_tab[ptr->keynum].str, ptr->keydef,
2009		  fkey_tab[ptr->keynum].len);
2010	    ptr->flen = fkey_tab[ptr->keynum].len;
2011	    return 0;
2012	}
2013	else
2014	    return EINVAL;
2015
2016    case SETFKEY:       	/* set functionkey string */
2017	if (*(u_short*)data < n_fkey_tab) {
2018	    fkeyarg_t *ptr = (fkeyarg_t*)data;
2019	    bcopy(ptr->keydef, &fkey_tab[ptr->keynum].str,
2020		  min(ptr->flen, MAXFK));
2021	    fkey_tab[ptr->keynum].len = min(ptr->flen, MAXFK);
2022	    return 0;
2023	}
2024	else
2025	    return EINVAL;
2026
2027    case GIO_SCRNMAP:   	/* get output translation table */
2028	bcopy(&scr_map, data, sizeof(scr_map));
2029	return 0;
2030
2031    case PIO_SCRNMAP:   	/* set output translation table */
2032	bcopy(data, &scr_map, sizeof(scr_map));
2033	for (i=0; i<sizeof(scr_map); i++)
2034	    scr_rmap[scr_map[i]] = i;
2035	return 0;
2036
2037    case GIO_KEYMAP:    	/* get keyboard translation table */
2038	bcopy(&key_map, data, sizeof(key_map));
2039	return 0;
2040
2041    case PIO_KEYMAP:    	/* set keyboard translation table */
2042	accents = 0;
2043	bzero(&accent_map, sizeof(accent_map));
2044	bcopy(data, &key_map, sizeof(key_map));
2045	return 0;
2046
2047    case GIO_DEADKEYMAP:    	/* get accent key translation table */
2048	bcopy(&accent_map, data, sizeof(accent_map));
2049	return 0;
2050
2051    case PIO_DEADKEYMAP:    	/* set accent key translation table */
2052	accents = 0;
2053	bcopy(data, &accent_map, sizeof(accent_map));
2054	return 0;
2055
2056    case PIO_FONT8x8:   	/* set 8x8 dot font */
2057	if (!crtc_vga)
2058	    return ENXIO;
2059	bcopy(data, font_8, 8*256);
2060	fonts_loaded |= FONT_8;
2061	/*
2062	 * FONT KLUDGE
2063	 * Always use the font page #0. XXX
2064	 * Don't load if the current font size is not 8x8.
2065	 */
2066	if (!(cur_console->status & UNKNOWN_MODE)
2067	    && (cur_console->font_size < 14)) {
2068	    copy_font(LOAD, FONT_8, font_8);
2069	    if (flags & CHAR_CURSOR)
2070	        set_destructive_cursor(cur_console);
2071	}
2072	return 0;
2073
2074    case GIO_FONT8x8:   	/* get 8x8 dot font */
2075	if (!crtc_vga)
2076	    return ENXIO;
2077	if (fonts_loaded & FONT_8) {
2078	    bcopy(font_8, data, 8*256);
2079	    return 0;
2080	}
2081	else
2082	    return ENXIO;
2083
2084    case PIO_FONT8x14:  	/* set 8x14 dot font */
2085	if (!crtc_vga)
2086	    return ENXIO;
2087	bcopy(data, font_14, 14*256);
2088	fonts_loaded |= FONT_14;
2089	/*
2090	 * FONT KLUDGE
2091	 * Always use the font page #0. XXX
2092	 * Don't load if the current font size is not 8x14.
2093	 */
2094	if (!(cur_console->status & UNKNOWN_MODE)
2095	    && (cur_console->font_size >= 14) && (cur_console->font_size < 16)) {
2096	    copy_font(LOAD, FONT_14, font_14);
2097	    if (flags & CHAR_CURSOR)
2098	        set_destructive_cursor(cur_console);
2099	}
2100	return 0;
2101
2102    case GIO_FONT8x14:  	/* get 8x14 dot font */
2103	if (!crtc_vga)
2104	    return ENXIO;
2105	if (fonts_loaded & FONT_14) {
2106	    bcopy(font_14, data, 14*256);
2107	    return 0;
2108	}
2109	else
2110	    return ENXIO;
2111
2112    case PIO_FONT8x16:  	/* set 8x16 dot font */
2113	if (!crtc_vga && crtc_type != KD_PIXEL)
2114	    return ENXIO;
2115	bcopy(data, font_16, 16*256);
2116	fonts_loaded |= FONT_16;
2117	/*
2118	 * FONT KLUDGE
2119	 * Always use the font page #0. XXX
2120	 * Don't load if the current font size is not 8x16.
2121	 */
2122	if (crtc_vga && !(cur_console->status & UNKNOWN_MODE)
2123	    && (cur_console->font_size >= 16)) {
2124	    copy_font(LOAD, FONT_16, font_16);
2125	    if (flags & CHAR_CURSOR)
2126	        set_destructive_cursor(cur_console);
2127	}
2128	return 0;
2129
2130    case GIO_FONT8x16:  	/* get 8x16 dot font */
2131	if (!crtc_vga && crtc_type != KD_PIXEL)
2132	    return ENXIO;
2133	if (fonts_loaded & FONT_16) {
2134	    bcopy(font_16, data, 16*256);
2135	    return 0;
2136	}
2137	else
2138	    return ENXIO;
2139    default:
2140	break;
2141    }
2142
2143    error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag, p);
2144    if (error != ENOIOCTL)
2145	return(error);
2146    error = ttioctl(tp, cmd, data, flag);
2147    if (error != ENOIOCTL)
2148	return(error);
2149    return(ENOTTY);
2150}
2151
2152static void
2153scstart(struct tty *tp)
2154{
2155    struct clist *rbp;
2156    int s, len;
2157    u_char buf[PCBURST];
2158    scr_stat *scp = get_scr_stat(tp->t_dev);
2159
2160    if (scp->status & SLKED || blink_in_progress)
2161	return; /* XXX who repeats the call when the above flags are cleared? */
2162    s = spltty();
2163    if (!(tp->t_state & (TS_TIMEOUT | TS_BUSY | TS_TTSTOP))) {
2164	tp->t_state |= TS_BUSY;
2165	rbp = &tp->t_outq;
2166	while (rbp->c_cc) {
2167	    len = q_to_b(rbp, buf, PCBURST);
2168	    splx(s);
2169	    ansi_put(scp, buf, len);
2170	    s = spltty();
2171	}
2172	tp->t_state &= ~TS_BUSY;
2173	ttwwakeup(tp);
2174    }
2175    splx(s);
2176}
2177
2178static void
2179scmousestart(struct tty *tp)
2180{
2181    struct clist *rbp;
2182    int s;
2183    u_char buf[PCBURST];
2184
2185    s = spltty();
2186    if (!(tp->t_state & (TS_TIMEOUT | TS_BUSY | TS_TTSTOP))) {
2187	tp->t_state |= TS_BUSY;
2188	rbp = &tp->t_outq;
2189	while (rbp->c_cc) {
2190	    q_to_b(rbp, buf, PCBURST);
2191	}
2192	tp->t_state &= ~TS_BUSY;
2193	ttwwakeup(tp);
2194    }
2195    splx(s);
2196}
2197
2198void
2199sccnprobe(struct consdev *cp)
2200{
2201    struct isa_device *dvp;
2202
2203    /*
2204     * Take control if we are the highest priority enabled display device.
2205     */
2206    dvp = find_display();
2207    if (dvp == NULL || dvp->id_driver != &scdriver) {
2208	cp->cn_pri = CN_DEAD;
2209	return;
2210    }
2211
2212    if (!scvidprobe(dvp->id_unit, dvp->id_flags)) {
2213	cp->cn_pri = CN_DEAD;
2214	return;
2215    }
2216
2217    /* initialize required fields */
2218    cp->cn_dev = makedev(CDEV_MAJOR, SC_CONSOLE);
2219    cp->cn_pri = CN_INTERNAL;
2220
2221    sc_kbdc = kbdc_open(sc_port);
2222}
2223
2224void
2225sccninit(struct consdev *cp)
2226{
2227    scinit();
2228}
2229
2230void
2231sccnputc(dev_t dev, int c)
2232{
2233    u_char buf[1];
2234    int s;
2235    scr_stat *scp = console[0];
2236    term_stat save = scp->term;
2237
2238    scp->term = kernel_console;
2239    current_default = &kernel_default;
2240    if (scp == cur_console && !(scp->status & UNKNOWN_MODE))
2241	remove_cursor_image(scp);
2242    buf[0] = c;
2243    ansi_put(scp, buf, 1);
2244    kernel_console = scp->term;
2245    current_default = &user_default;
2246    scp->term = save;
2247
2248    s = spltty();	/* block scintr and scrn_timer */
2249    sccnupdate(scp);
2250    splx(s);
2251}
2252
2253int
2254sccngetc(dev_t dev)
2255{
2256    int s = spltty();	/* block scintr and scrn_timer while we poll */
2257    int c;
2258
2259    /*
2260     * Stop the screen saver and update the screen if necessary.
2261     * What if we have been running in the screen saver code... XXX
2262     */
2263    sccnupdate(cur_console);
2264
2265    c = scgetc(SCGETC_CN);
2266    splx(s);
2267    return(c);
2268}
2269
2270int
2271sccncheckc(dev_t dev)
2272{
2273    int s = spltty();	/* block scintr and scrn_timer while we poll */
2274    int c;
2275
2276    sccnupdate(cur_console);
2277    c = scgetc(SCGETC_CN | SCGETC_NONBLOCK);
2278    splx(s);
2279    return(c == NOKEY ? -1 : c);	/* c == -1 can't happen */
2280}
2281
2282static void
2283sccnupdate(scr_stat *scp)
2284{
2285    if (scp == cur_console && !font_loading_in_progress) {
2286	if (scrn_blanked > 0)
2287            stop_scrn_saver(current_saver);
2288	if (!(scp->status & UNKNOWN_MODE) && scrn_blanked <= 0
2289	    && !blink_in_progress && !switch_in_progress)
2290	    scrn_update(scp, TRUE);
2291    }
2292}
2293
2294static scr_stat
2295*get_scr_stat(dev_t dev)
2296{
2297    int unit = minor(dev);
2298
2299    if (unit == SC_CONSOLE)
2300	return console[0];
2301    if (unit >= MAXCONS || unit < 0)
2302	return(NULL);
2303    return console[unit];
2304}
2305
2306static int
2307get_scr_num()
2308{
2309    int i = 0;
2310
2311    while ((i < MAXCONS) && (cur_console != console[i]))
2312	i++;
2313    return i < MAXCONS ? i : 0;
2314}
2315
2316static void
2317scrn_timer(void *arg)
2318{
2319    struct timeval tv;
2320    scr_stat *scp = cur_console;
2321    int s;
2322
2323    /* don't do anything when we are touching font */
2324    if (font_loading_in_progress) {
2325	timeout(scrn_timer, NULL, hz / 10);
2326	return;
2327    }
2328    s = spltty();
2329
2330    /*
2331     * With release 2.1 of the Xaccel server, the keyboard is left
2332     * hanging pretty often. Apparently an interrupt from the
2333     * keyboard is lost, and I don't know why (yet).
2334     * This ugly hack calls scintr if input is ready for the keyboard
2335     * and conveniently hides the problem.			XXX
2336     */
2337    /* Try removing anything stuck in the keyboard controller; whether
2338     * it's a keyboard scan code or mouse data. `scintr()' doesn't
2339     * read the mouse data directly, but `kbdio' routines will, as a
2340     * side effect.
2341     */
2342    if (kbdc_lock(sc_kbdc, TRUE)) {
2343	/*
2344	 * We have seen the lock flag is not set. Let's reset the flag early;
2345	 * otherwise `update_led()' failes which may want the lock
2346	 * during `scintr()'.
2347	 */
2348	kbdc_lock(sc_kbdc, FALSE);
2349	if (kbdc_data_ready(sc_kbdc))
2350	    scintr(0);
2351    }
2352
2353    /* should we stop the screen saver? */
2354    getmicrouptime(&tv);
2355    if (panicstr)
2356	scrn_time_stamp = tv;
2357    if (tv.tv_sec <= scrn_time_stamp.tv_sec + scrn_blank_time)
2358	if (scrn_blanked > 0)
2359            stop_scrn_saver(current_saver);
2360
2361    /* should we just return ? */
2362    if ((scp->status&UNKNOWN_MODE) || blink_in_progress || switch_in_progress) {
2363	timeout(scrn_timer, NULL, hz / 10);
2364	splx(s);
2365	return;
2366    }
2367
2368    /* Update the screen */
2369    scp = cur_console;
2370    if (scrn_blanked <= 0)
2371	scrn_update(scp, TRUE);
2372
2373    /* should we activate the screen saver? */
2374    if ((scrn_blank_time != 0)
2375	    && (tv.tv_sec > scrn_time_stamp.tv_sec + scrn_blank_time))
2376	(*current_saver)(TRUE);
2377
2378    timeout(scrn_timer, NULL, hz / 25);
2379    splx(s);
2380}
2381
2382static void
2383scrn_update(scr_stat *scp, int show_cursor)
2384{
2385    /* update screen image */
2386    if (scp->start <= scp->end)
2387        sc_bcopy(scp->scr_buf, scp->start, scp->end, 0);
2388
2389    /* we are not to show the cursor and the mouse pointer... */
2390    if (!show_cursor) {
2391        scp->end = 0;
2392        scp->start = scp->xsize*scp->ysize - 1;
2393	return;
2394    }
2395
2396    /* update "pseudo" mouse pointer image */
2397    if (scp->status & MOUSE_VISIBLE) {
2398        /* did mouse move since last time ? */
2399        if (scp->status & MOUSE_MOVED) {
2400            /* do we need to remove old mouse pointer image ? */
2401            if (scp->mouse_cut_start != NULL ||
2402                (scp->mouse_pos-scp->scr_buf) <= scp->start ||
2403                (scp->mouse_pos+scp->xsize + 1 - scp->scr_buf) >= scp->end) {
2404                remove_mouse_image(scp);
2405            }
2406            scp->status &= ~MOUSE_MOVED;
2407            draw_mouse_image(scp);
2408        }
2409        else {
2410            /* mouse didn't move, has it been overwritten ? */
2411            if ((scp->mouse_pos+scp->xsize + 1 - scp->scr_buf) >= scp->start &&
2412                (scp->mouse_pos - scp->scr_buf) <= scp->end) {
2413                draw_mouse_image(scp);
2414            }
2415        }
2416    }
2417
2418    /* update cursor image */
2419    if (scp->status & CURSOR_ENABLED) {
2420        /* did cursor move since last time ? */
2421        if (scp->cursor_pos != scp->cursor_oldpos) {
2422            /* do we need to remove old cursor image ? */
2423            if ((scp->cursor_oldpos - scp->scr_buf) < scp->start ||
2424                ((scp->cursor_oldpos - scp->scr_buf) > scp->end)) {
2425                remove_cursor_image(scp);
2426            }
2427            scp->cursor_oldpos = scp->cursor_pos;
2428            draw_cursor_image(scp);
2429        }
2430        else {
2431            /* cursor didn't move, has it been overwritten ? */
2432            if (scp->cursor_pos - scp->scr_buf >= scp->start &&
2433                scp->cursor_pos - scp->scr_buf <= scp->end) {
2434                draw_cursor_image(scp);
2435            } else {
2436                /* if its a blinking cursor, we may have to update it */
2437                if (flags & BLINK_CURSOR)
2438                    draw_cursor_image(scp);
2439            }
2440        }
2441        blinkrate++;
2442    }
2443
2444    if (scp->mouse_cut_start != NULL)
2445        draw_cutmarking(scp);
2446
2447    scp->end = 0;
2448    scp->start = scp->xsize*scp->ysize - 1;
2449}
2450
2451int
2452add_scrn_saver(void (*this_saver)(int))
2453{
2454    if (current_saver != none_saver)
2455	return EBUSY;
2456    current_saver = this_saver;
2457    return 0;
2458}
2459
2460int
2461remove_scrn_saver(void (*this_saver)(int))
2462{
2463    if (current_saver != this_saver)
2464	return EINVAL;
2465
2466    /*
2467     * In order to prevent `current_saver' from being called by
2468     * the timeout routine `scrn_timer()' while we manipulate
2469     * the saver list, we shall set `current_saver' to `none_saver'
2470     * before stopping the current saver, rather than blocking by `splXX()'.
2471     */
2472    current_saver = none_saver;
2473    if (scrn_blanked > 0)
2474        stop_scrn_saver(this_saver);
2475
2476    return 0;
2477}
2478
2479static void
2480stop_scrn_saver(void (*saver)(int))
2481{
2482    (*saver)(FALSE);
2483    getmicrouptime(&scrn_time_stamp);
2484    mark_all(cur_console);
2485    wakeup((caddr_t)&scrn_blanked);
2486}
2487
2488static int
2489wait_scrn_saver_stop(void)
2490{
2491    int error = 0;
2492
2493    getmicrouptime(&scrn_time_stamp);
2494    while (scrn_blanked > 0) {
2495	error = tsleep((caddr_t)&scrn_blanked, PZERO | PCATCH, "scrsav", 0);
2496	getmicrouptime(&scrn_time_stamp);
2497	if (error != ERESTART)
2498	    break;
2499    }
2500    return error;
2501}
2502
2503static void
2504clear_screen(scr_stat *scp)
2505{
2506    move_crsr(scp, 0, 0);
2507    scp->cursor_oldpos = scp->cursor_pos;
2508    fillw(scp->term.cur_color | scr_map[0x20], scp->scr_buf,
2509	  scp->xsize * scp->ysize);
2510    mark_all(scp);
2511    remove_cutmarking(scp);
2512}
2513
2514static int
2515switch_scr(scr_stat *scp, u_int next_scr)
2516{
2517    if (switch_in_progress && (cur_console->proc != pfind(cur_console->pid)))
2518	switch_in_progress = FALSE;
2519
2520    if (next_scr >= MAXCONS || switch_in_progress ||
2521	(cur_console->smode.mode == VT_AUTO
2522	 && cur_console->status & UNKNOWN_MODE)) {
2523	do_bell(scp, BELL_PITCH, BELL_DURATION);
2524	return EINVAL;
2525    }
2526
2527    /* is the wanted virtual console open ? */
2528    if (next_scr) {
2529	struct tty *tp = VIRTUAL_TTY(next_scr);
2530	if (!(tp->t_state & TS_ISOPEN)) {
2531	    do_bell(scp, BELL_PITCH, BELL_DURATION);
2532	    return EINVAL;
2533	}
2534    }
2535
2536    /* delay switch if actively updating screen */
2537    if (write_in_progress || blink_in_progress) {
2538	delayed_next_scr = next_scr+1;
2539	return 0;
2540    }
2541
2542    /* Stop the screensaver */
2543    if (scrn_blanked > 0)
2544      stop_scrn_saver(current_saver);
2545
2546    switch_in_progress = TRUE;
2547    old_scp = cur_console;
2548    new_scp = console[next_scr];
2549    wakeup((caddr_t)&new_scp->smode);
2550    if (new_scp == old_scp) {
2551	switch_in_progress = FALSE;
2552	delayed_next_scr = FALSE;
2553	return 0;
2554    }
2555
2556    /* has controlling process died? */
2557    if (old_scp->proc && (old_scp->proc != pfind(old_scp->pid)))
2558	old_scp->smode.mode = VT_AUTO;
2559    if (new_scp->proc && (new_scp->proc != pfind(new_scp->pid)))
2560	new_scp->smode.mode = VT_AUTO;
2561
2562    /* check the modes and switch appropriately */
2563    if (old_scp->smode.mode == VT_PROCESS) {
2564	old_scp->status |= SWITCH_WAIT_REL;
2565	psignal(old_scp->proc, old_scp->smode.relsig);
2566    }
2567    else {
2568	exchange_scr();
2569	if (new_scp->smode.mode == VT_PROCESS) {
2570	    new_scp->status |= SWITCH_WAIT_ACQ;
2571	    psignal(new_scp->proc, new_scp->smode.acqsig);
2572	}
2573	else
2574	    switch_in_progress = FALSE;
2575    }
2576    return 0;
2577}
2578
2579static void
2580exchange_scr(void)
2581{
2582    move_crsr(old_scp, old_scp->xpos, old_scp->ypos);
2583    cur_console = new_scp;
2584    if (old_scp->mode != new_scp->mode || (old_scp->status & UNKNOWN_MODE)){
2585	if (crtc_vga)
2586	    set_mode(new_scp);
2587    }
2588    move_crsr(new_scp, new_scp->xpos, new_scp->ypos);
2589    if (!(new_scp->status & UNKNOWN_MODE) && (flags & CHAR_CURSOR))
2590	set_destructive_cursor(new_scp);
2591    if ((old_scp->status & UNKNOWN_MODE) && crtc_vga)
2592	load_palette(palette);
2593    if (old_scp->status & KBD_RAW_MODE || new_scp->status & KBD_RAW_MODE ||
2594        old_scp->status & KBD_CODE_MODE || new_scp->status & KBD_CODE_MODE)
2595	shfts = ctls = alts = agrs = metas = accents = 0;
2596    set_border(new_scp->border);
2597    update_leds(new_scp->status);
2598    delayed_next_scr = FALSE;
2599    mark_all(new_scp);
2600    if (vesa_mode == 0x102) {
2601	bzero(Crtat, 800*600/8);
2602    }
2603}
2604
2605static void
2606scan_esc(scr_stat *scp, u_char c)
2607{
2608    static u_char ansi_col[16] =
2609	{0, 4, 2, 6, 1, 5, 3, 7, 8, 12, 10, 14, 9, 13, 11, 15};
2610    int i, n;
2611    u_short *src, *dst, count;
2612
2613    if (scp->term.esc == 1) {	/* seen ESC */
2614	switch (c) {
2615
2616	case '7':   /* Save cursor position */
2617	    scp->saved_xpos = scp->xpos;
2618	    scp->saved_ypos = scp->ypos;
2619	    break;
2620
2621	case '8':   /* Restore saved cursor position */
2622	    if (scp->saved_xpos >= 0 && scp->saved_ypos >= 0)
2623		move_crsr(scp, scp->saved_xpos, scp->saved_ypos);
2624	    break;
2625
2626	case '[':   /* Start ESC [ sequence */
2627	    scp->term.esc = 2;
2628	    scp->term.last_param = -1;
2629	    for (i = scp->term.num_param; i < MAX_ESC_PAR; i++)
2630		scp->term.param[i] = 1;
2631	    scp->term.num_param = 0;
2632	    return;
2633
2634	case 'M':   /* Move cursor up 1 line, scroll if at top */
2635	    if (scp->ypos > 0)
2636		move_crsr(scp, scp->xpos, scp->ypos - 1);
2637	    else {
2638		bcopy(scp->scr_buf, scp->scr_buf + scp->xsize,
2639		       (scp->ysize - 1) * scp->xsize * sizeof(u_short));
2640		fillw(scp->term.cur_color | scr_map[0x20],
2641		      scp->scr_buf, scp->xsize);
2642    		mark_all(scp);
2643	    }
2644	    break;
2645#if notyet
2646	case 'Q':
2647	    scp->term.esc = 4;
2648	    return;
2649#endif
2650	case 'c':   /* Clear screen & home */
2651	    clear_screen(scp);
2652	    break;
2653
2654	case '(':   /* iso-2022: designate 94 character set to G0 */
2655	    scp->term.esc = 5;
2656	    return;
2657	}
2658    }
2659    else if (scp->term.esc == 2) {	/* seen ESC [ */
2660	if (c >= '0' && c <= '9') {
2661	    if (scp->term.num_param < MAX_ESC_PAR) {
2662	    if (scp->term.last_param != scp->term.num_param) {
2663		scp->term.last_param = scp->term.num_param;
2664		scp->term.param[scp->term.num_param] = 0;
2665	    }
2666	    else
2667		scp->term.param[scp->term.num_param] *= 10;
2668	    scp->term.param[scp->term.num_param] += c - '0';
2669	    return;
2670	    }
2671	}
2672	scp->term.num_param = scp->term.last_param + 1;
2673	switch (c) {
2674
2675	case ';':
2676	    if (scp->term.num_param < MAX_ESC_PAR)
2677		return;
2678	    break;
2679
2680	case '=':
2681	    scp->term.esc = 3;
2682	    scp->term.last_param = -1;
2683	    for (i = scp->term.num_param; i < MAX_ESC_PAR; i++)
2684		scp->term.param[i] = 1;
2685	    scp->term.num_param = 0;
2686	    return;
2687
2688	case 'A':   /* up n rows */
2689	    n = scp->term.param[0]; if (n < 1) n = 1;
2690	    move_crsr(scp, scp->xpos, scp->ypos - n);
2691	    break;
2692
2693	case 'B':   /* down n rows */
2694	    n = scp->term.param[0]; if (n < 1) n = 1;
2695	    move_crsr(scp, scp->xpos, scp->ypos + n);
2696	    break;
2697
2698	case 'C':   /* right n columns */
2699	    n = scp->term.param[0]; if (n < 1) n = 1;
2700	    move_crsr(scp, scp->xpos + n, scp->ypos);
2701	    break;
2702
2703	case 'D':   /* left n columns */
2704	    n = scp->term.param[0]; if (n < 1) n = 1;
2705	    move_crsr(scp, scp->xpos - n, scp->ypos);
2706	    break;
2707
2708	case 'E':   /* cursor to start of line n lines down */
2709	    n = scp->term.param[0]; if (n < 1) n = 1;
2710	    move_crsr(scp, 0, scp->ypos + n);
2711	    break;
2712
2713	case 'F':   /* cursor to start of line n lines up */
2714	    n = scp->term.param[0]; if (n < 1) n = 1;
2715	    move_crsr(scp, 0, scp->ypos - n);
2716	    break;
2717
2718	case 'f':   /* Cursor move */
2719	case 'H':
2720	    if (scp->term.num_param == 0)
2721		move_crsr(scp, 0, 0);
2722	    else if (scp->term.num_param == 2)
2723		move_crsr(scp, scp->term.param[1] - 1, scp->term.param[0] - 1);
2724	    break;
2725
2726	case 'J':   /* Clear all or part of display */
2727	    if (scp->term.num_param == 0)
2728		n = 0;
2729	    else
2730		n = scp->term.param[0];
2731	    switch (n) {
2732	    case 0: /* clear form cursor to end of display */
2733		fillw(scp->term.cur_color | scr_map[0x20],
2734		      scp->cursor_pos,
2735		      scp->scr_buf + scp->xsize * scp->ysize - scp->cursor_pos);
2736    		mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
2737    		mark_for_update(scp, scp->xsize * scp->ysize);
2738		remove_cutmarking(scp);
2739		break;
2740	    case 1: /* clear from beginning of display to cursor */
2741		fillw(scp->term.cur_color | scr_map[0x20],
2742		      scp->scr_buf,
2743		      scp->cursor_pos - scp->scr_buf);
2744    		mark_for_update(scp, 0);
2745    		mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
2746		remove_cutmarking(scp);
2747		break;
2748	    case 2: /* clear entire display */
2749		fillw(scp->term.cur_color | scr_map[0x20], scp->scr_buf,
2750		      scp->xsize * scp->ysize);
2751		mark_all(scp);
2752		remove_cutmarking(scp);
2753		break;
2754	    }
2755	    break;
2756
2757	case 'K':   /* Clear all or part of line */
2758	    if (scp->term.num_param == 0)
2759		n = 0;
2760	    else
2761		n = scp->term.param[0];
2762	    switch (n) {
2763	    case 0: /* clear form cursor to end of line */
2764		fillw(scp->term.cur_color | scr_map[0x20],
2765		      scp->cursor_pos,
2766		      scp->xsize - scp->xpos);
2767    		mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
2768    		mark_for_update(scp, scp->cursor_pos - scp->scr_buf +
2769				scp->xsize - scp->xpos);
2770		break;
2771	    case 1: /* clear from beginning of line to cursor */
2772		fillw(scp->term.cur_color | scr_map[0x20],
2773		      scp->cursor_pos - scp->xpos,
2774		      scp->xpos + 1);
2775    		mark_for_update(scp, scp->ypos * scp->xsize);
2776    		mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
2777		break;
2778	    case 2: /* clear entire line */
2779		fillw(scp->term.cur_color | scr_map[0x20],
2780		      scp->cursor_pos - scp->xpos,
2781		      scp->xsize);
2782    		mark_for_update(scp, scp->ypos * scp->xsize);
2783    		mark_for_update(scp, (scp->ypos + 1) * scp->xsize);
2784		break;
2785	    }
2786	    break;
2787
2788	case 'L':   /* Insert n lines */
2789	    n = scp->term.param[0]; if (n < 1) n = 1;
2790	    if (n > scp->ysize - scp->ypos)
2791		n = scp->ysize - scp->ypos;
2792	    src = scp->scr_buf + scp->ypos * scp->xsize;
2793	    dst = src + n * scp->xsize;
2794	    count = scp->ysize - (scp->ypos + n);
2795	    bcopy(src, dst, count * scp->xsize * sizeof(u_short));
2796	    fillw(scp->term.cur_color | scr_map[0x20], src,
2797		  n * scp->xsize);
2798	    mark_for_update(scp, scp->ypos * scp->xsize);
2799	    mark_for_update(scp, scp->xsize * scp->ysize);
2800	    break;
2801
2802	case 'M':   /* Delete n lines */
2803	    n = scp->term.param[0]; if (n < 1) n = 1;
2804	    if (n > scp->ysize - scp->ypos)
2805		n = scp->ysize - scp->ypos;
2806	    dst = scp->scr_buf + scp->ypos * scp->xsize;
2807	    src = dst + n * scp->xsize;
2808	    count = scp->ysize - (scp->ypos + n);
2809	    bcopy(src, dst, count * scp->xsize * sizeof(u_short));
2810	    src = dst + count * scp->xsize;
2811	    fillw(scp->term.cur_color | scr_map[0x20], src,
2812		  n * scp->xsize);
2813	    mark_for_update(scp, scp->ypos * scp->xsize);
2814	    mark_for_update(scp, scp->xsize * scp->ysize);
2815	    break;
2816
2817	case 'P':   /* Delete n chars */
2818	    n = scp->term.param[0]; if (n < 1) n = 1;
2819	    if (n > scp->xsize - scp->xpos)
2820		n = scp->xsize - scp->xpos;
2821	    dst = scp->cursor_pos;
2822	    src = dst + n;
2823	    count = scp->xsize - (scp->xpos + n);
2824	    bcopy(src, dst, count * sizeof(u_short));
2825	    src = dst + count;
2826	    fillw(scp->term.cur_color | scr_map[0x20], src, n);
2827	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
2828	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf + n + count);
2829	    break;
2830
2831	case '@':   /* Insert n chars */
2832	    n = scp->term.param[0]; if (n < 1) n = 1;
2833	    if (n > scp->xsize - scp->xpos)
2834		n = scp->xsize - scp->xpos;
2835	    src = scp->cursor_pos;
2836	    dst = src + n;
2837	    count = scp->xsize - (scp->xpos + n);
2838	    bcopy(src, dst, count * sizeof(u_short));
2839	    fillw(scp->term.cur_color | scr_map[0x20], src, n);
2840	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
2841	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf + n + count);
2842	    break;
2843
2844	case 'S':   /* scroll up n lines */
2845	    n = scp->term.param[0]; if (n < 1)  n = 1;
2846	    if (n > scp->ysize)
2847		n = scp->ysize;
2848	    bcopy(scp->scr_buf + (scp->xsize * n),
2849		   scp->scr_buf,
2850		   scp->xsize * (scp->ysize - n) * sizeof(u_short));
2851	    fillw(scp->term.cur_color | scr_map[0x20],
2852		  scp->scr_buf + scp->xsize * (scp->ysize - n),
2853		  scp->xsize * n);
2854    	    mark_all(scp);
2855	    break;
2856
2857	case 'T':   /* scroll down n lines */
2858	    n = scp->term.param[0]; if (n < 1)  n = 1;
2859	    if (n > scp->ysize)
2860		n = scp->ysize;
2861	    bcopy(scp->scr_buf,
2862		  scp->scr_buf + (scp->xsize * n),
2863		  scp->xsize * (scp->ysize - n) *
2864		  sizeof(u_short));
2865	    fillw(scp->term.cur_color | scr_map[0x20],
2866		  scp->scr_buf, scp->xsize * n);
2867    	    mark_all(scp);
2868	    break;
2869
2870	case 'X':   /* erase n characters in line */
2871	    n = scp->term.param[0]; if (n < 1)  n = 1;
2872	    if (n > scp->xsize - scp->xpos)
2873		n = scp->xsize - scp->xpos;
2874	    fillw(scp->term.cur_color | scr_map[0x20],
2875		  scp->cursor_pos, n);
2876	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
2877	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf + n);
2878	    break;
2879
2880	case 'Z':   /* move n tabs backwards */
2881	    n = scp->term.param[0]; if (n < 1)  n = 1;
2882	    if ((i = scp->xpos & 0xf8) == scp->xpos)
2883		i -= 8*n;
2884	    else
2885		i -= 8*(n-1);
2886	    if (i < 0)
2887		i = 0;
2888	    move_crsr(scp, i, scp->ypos);
2889	    break;
2890
2891	case '`':   /* move cursor to column n */
2892	    n = scp->term.param[0]; if (n < 1)  n = 1;
2893	    move_crsr(scp, n - 1, scp->ypos);
2894	    break;
2895
2896	case 'a':   /* move cursor n columns to the right */
2897	    n = scp->term.param[0]; if (n < 1)  n = 1;
2898	    move_crsr(scp, scp->xpos + n, scp->ypos);
2899	    break;
2900
2901	case 'd':   /* move cursor to row n */
2902	    n = scp->term.param[0]; if (n < 1)  n = 1;
2903	    move_crsr(scp, scp->xpos, n - 1);
2904	    break;
2905
2906	case 'e':   /* move cursor n rows down */
2907	    n = scp->term.param[0]; if (n < 1)  n = 1;
2908	    move_crsr(scp, scp->xpos, scp->ypos + n);
2909	    break;
2910
2911	case 'm':   /* change attribute */
2912	    if (scp->term.num_param == 0) {
2913		scp->term.attr_mask = NORMAL_ATTR;
2914		scp->term.cur_attr =
2915		    scp->term.cur_color = scp->term.std_color;
2916		break;
2917	    }
2918	    for (i = 0; i < scp->term.num_param; i++) {
2919		switch (n = scp->term.param[i]) {
2920		case 0: /* back to normal */
2921		    scp->term.attr_mask = NORMAL_ATTR;
2922		    scp->term.cur_attr =
2923			scp->term.cur_color = scp->term.std_color;
2924		    break;
2925		case 1: /* bold */
2926		    scp->term.attr_mask |= BOLD_ATTR;
2927		    scp->term.cur_attr = mask2attr(&scp->term);
2928		    break;
2929		case 4: /* underline */
2930		    scp->term.attr_mask |= UNDERLINE_ATTR;
2931		    scp->term.cur_attr = mask2attr(&scp->term);
2932		    break;
2933		case 5: /* blink */
2934		    scp->term.attr_mask |= BLINK_ATTR;
2935		    scp->term.cur_attr = mask2attr(&scp->term);
2936		    break;
2937		case 7: /* reverse video */
2938		    scp->term.attr_mask |= REVERSE_ATTR;
2939		    scp->term.cur_attr = mask2attr(&scp->term);
2940		    break;
2941		case 30: case 31: /* set fg color */
2942		case 32: case 33: case 34:
2943		case 35: case 36: case 37:
2944		    scp->term.attr_mask |= FOREGROUND_CHANGED;
2945		    scp->term.cur_color =
2946			(scp->term.cur_color&0xF000) | (ansi_col[(n-30)&7]<<8);
2947		    scp->term.cur_attr = mask2attr(&scp->term);
2948		    break;
2949		case 40: case 41: /* set bg color */
2950		case 42: case 43: case 44:
2951		case 45: case 46: case 47:
2952		    scp->term.attr_mask |= BACKGROUND_CHANGED;
2953		    scp->term.cur_color =
2954			(scp->term.cur_color&0x0F00) | (ansi_col[(n-40)&7]<<12);
2955		    scp->term.cur_attr = mask2attr(&scp->term);
2956		    break;
2957		}
2958	    }
2959	    break;
2960
2961	case 's':   /* Save cursor position */
2962	    scp->saved_xpos = scp->xpos;
2963	    scp->saved_ypos = scp->ypos;
2964	    break;
2965
2966	case 'u':   /* Restore saved cursor position */
2967	    if (scp->saved_xpos >= 0 && scp->saved_ypos >= 0)
2968		move_crsr(scp, scp->saved_xpos, scp->saved_ypos);
2969	    break;
2970
2971	case 'x':
2972	    if (scp->term.num_param == 0)
2973		n = 0;
2974	    else
2975		n = scp->term.param[0];
2976	    switch (n) {
2977	    case 0:     /* reset attributes */
2978		scp->term.attr_mask = NORMAL_ATTR;
2979		scp->term.cur_attr =
2980		    scp->term.cur_color = scp->term.std_color =
2981		    current_default->std_color;
2982		scp->term.rev_color = current_default->rev_color;
2983		break;
2984	    case 1:     /* set ansi background */
2985		scp->term.attr_mask &= ~BACKGROUND_CHANGED;
2986		scp->term.cur_color = scp->term.std_color =
2987		    (scp->term.std_color & 0x0F00) |
2988		    (ansi_col[(scp->term.param[1])&0x0F]<<12);
2989		scp->term.cur_attr = mask2attr(&scp->term);
2990		break;
2991	    case 2:     /* set ansi foreground */
2992		scp->term.attr_mask &= ~FOREGROUND_CHANGED;
2993		scp->term.cur_color = scp->term.std_color =
2994		    (scp->term.std_color & 0xF000) |
2995		    (ansi_col[(scp->term.param[1])&0x0F]<<8);
2996		scp->term.cur_attr = mask2attr(&scp->term);
2997		break;
2998	    case 3:     /* set ansi attribute directly */
2999		scp->term.attr_mask &= ~(FOREGROUND_CHANGED|BACKGROUND_CHANGED);
3000		scp->term.cur_color = scp->term.std_color =
3001		    (scp->term.param[1]&0xFF)<<8;
3002		scp->term.cur_attr = mask2attr(&scp->term);
3003		break;
3004	    case 5:     /* set ansi reverse video background */
3005		scp->term.rev_color =
3006		    (scp->term.rev_color & 0x0F00) |
3007		    (ansi_col[(scp->term.param[1])&0x0F]<<12);
3008		scp->term.cur_attr = mask2attr(&scp->term);
3009		break;
3010	    case 6:     /* set ansi reverse video foreground */
3011		scp->term.rev_color =
3012		    (scp->term.rev_color & 0xF000) |
3013		    (ansi_col[(scp->term.param[1])&0x0F]<<8);
3014		scp->term.cur_attr = mask2attr(&scp->term);
3015		break;
3016	    case 7:     /* set ansi reverse video directly */
3017		scp->term.rev_color =
3018		    (scp->term.param[1]&0xFF)<<8;
3019		scp->term.cur_attr = mask2attr(&scp->term);
3020		break;
3021	    }
3022	    break;
3023
3024	case 'z':   /* switch to (virtual) console n */
3025	    if (scp->term.num_param == 1)
3026		switch_scr(scp, scp->term.param[0]);
3027	    break;
3028	}
3029    }
3030    else if (scp->term.esc == 3) {	/* seen ESC [0-9]+ = */
3031	if (c >= '0' && c <= '9') {
3032	    if (scp->term.num_param < MAX_ESC_PAR) {
3033	    if (scp->term.last_param != scp->term.num_param) {
3034		scp->term.last_param = scp->term.num_param;
3035		scp->term.param[scp->term.num_param] = 0;
3036	    }
3037	    else
3038		scp->term.param[scp->term.num_param] *= 10;
3039	    scp->term.param[scp->term.num_param] += c - '0';
3040	    return;
3041	    }
3042	}
3043	scp->term.num_param = scp->term.last_param + 1;
3044	switch (c) {
3045
3046	case ';':
3047	    if (scp->term.num_param < MAX_ESC_PAR)
3048		return;
3049	    break;
3050
3051	case 'A':   /* set display border color */
3052	    if (scp->term.num_param == 1) {
3053		scp->border=scp->term.param[0] & 0xff;
3054		if (scp == cur_console)
3055		    set_border(scp->border);
3056            }
3057	    break;
3058
3059	case 'B':   /* set bell pitch and duration */
3060	    if (scp->term.num_param == 2) {
3061		scp->bell_pitch = scp->term.param[0];
3062		scp->bell_duration = scp->term.param[1]*10;
3063	    }
3064	    break;
3065
3066	case 'C':   /* set cursor type & shape */
3067	    if (scp->term.num_param == 1) {
3068		if (scp->term.param[0] & 0x01)
3069		    flags |= BLINK_CURSOR;
3070		else
3071		    flags &= ~BLINK_CURSOR;
3072		if ((scp->term.param[0] & 0x02) && crtc_vga)
3073		    flags |= CHAR_CURSOR;
3074		else
3075		    flags &= ~CHAR_CURSOR;
3076	    }
3077	    else if (scp->term.num_param == 2) {
3078		scp->cursor_start = scp->term.param[0] & 0x1F;
3079		scp->cursor_end = scp->term.param[1] & 0x1F;
3080	    }
3081	    /*
3082	     * The cursor shape is global property; all virtual consoles
3083	     * are affected. Update the cursor in the current console...
3084	     */
3085	    if (!(cur_console->status & UNKNOWN_MODE)) {
3086		remove_cursor_image(cur_console);
3087		if (crtc_vga && (flags & CHAR_CURSOR))
3088	            set_destructive_cursor(cur_console);
3089		draw_cursor_image(cur_console);
3090	    }
3091	    break;
3092
3093	case 'F':   /* set ansi foreground */
3094	    if (scp->term.num_param == 1) {
3095		scp->term.attr_mask &= ~FOREGROUND_CHANGED;
3096		scp->term.cur_color = scp->term.std_color =
3097		    (scp->term.std_color & 0xF000)
3098		    | ((scp->term.param[0] & 0x0F) << 8);
3099		scp->term.cur_attr = mask2attr(&scp->term);
3100	    }
3101	    break;
3102
3103	case 'G':   /* set ansi background */
3104	    if (scp->term.num_param == 1) {
3105		scp->term.attr_mask &= ~BACKGROUND_CHANGED;
3106		scp->term.cur_color = scp->term.std_color =
3107		    (scp->term.std_color & 0x0F00)
3108		    | ((scp->term.param[0] & 0x0F) << 12);
3109		scp->term.cur_attr = mask2attr(&scp->term);
3110	    }
3111	    break;
3112
3113	case 'H':   /* set ansi reverse video foreground */
3114	    if (scp->term.num_param == 1) {
3115		scp->term.rev_color =
3116		    (scp->term.rev_color & 0xF000)
3117		    | ((scp->term.param[0] & 0x0F) << 8);
3118		scp->term.cur_attr = mask2attr(&scp->term);
3119	    }
3120	    break;
3121
3122	case 'I':   /* set ansi reverse video background */
3123	    if (scp->term.num_param == 1) {
3124		scp->term.rev_color =
3125		    (scp->term.rev_color & 0x0F00)
3126		    | ((scp->term.param[0] & 0x0F) << 12);
3127		scp->term.cur_attr = mask2attr(&scp->term);
3128	    }
3129	    break;
3130	}
3131    }
3132#if notyet
3133    else if (scp->term.esc == 4) {	/* seen ESC Q */
3134	/* to be filled */
3135    }
3136#endif
3137    else if (scp->term.esc == 5) {	/* seen ESC ( */
3138	switch (c) {
3139	case 'B':   /* iso-2022: desginate ASCII into G0 */
3140	    break;
3141	/* other items to be filled */
3142	default:
3143	    break;
3144	}
3145    }
3146    scp->term.esc = 0;
3147}
3148
3149static void
3150ansi_put(scr_stat *scp, u_char *buf, int len)
3151{
3152    u_char *ptr = buf;
3153
3154    /* make screensaver happy */
3155    if (scp == cur_console)
3156	getmicrouptime(&scrn_time_stamp);
3157
3158    write_in_progress++;
3159outloop:
3160    if (scp->term.esc) {
3161	scan_esc(scp, *ptr++);
3162	len--;
3163    }
3164    else if (PRINTABLE(*ptr)) {     /* Print only printables */
3165 	int cnt = len <= (scp->xsize-scp->xpos) ? len : (scp->xsize-scp->xpos);
3166 	u_short cur_attr = scp->term.cur_attr;
3167 	u_short *cursor_pos = scp->cursor_pos;
3168	do {
3169	    /*
3170	     * gcc-2.6.3 generates poor (un)sign extension code.  Casting the
3171	     * pointers in the following to volatile should have no effect,
3172	     * but in fact speeds up this inner loop from 26 to 18 cycles
3173	     * (+ cache misses) on i486's.
3174	     */
3175#define	UCVP(ucp)	((u_char volatile *)(ucp))
3176	    *cursor_pos++ = UCVP(scr_map)[*UCVP(ptr)] | cur_attr;
3177	    ptr++;
3178	    cnt--;
3179	} while (cnt && PRINTABLE(*ptr));
3180	len -= (cursor_pos - scp->cursor_pos);
3181	scp->xpos += (cursor_pos - scp->cursor_pos);
3182	mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
3183	mark_for_update(scp, cursor_pos - scp->scr_buf);
3184	scp->cursor_pos = cursor_pos;
3185	if (scp->xpos >= scp->xsize) {
3186	    scp->xpos = 0;
3187	    scp->ypos++;
3188	}
3189    }
3190    else  {
3191	switch(*ptr) {
3192	case 0x07:
3193	    do_bell(scp, scp->bell_pitch, scp->bell_duration);
3194	    break;
3195
3196	case 0x08:      /* non-destructive backspace */
3197	    if (scp->cursor_pos > scp->scr_buf) {
3198	    	mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
3199		scp->cursor_pos--;
3200	    	mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
3201		if (scp->xpos > 0)
3202		    scp->xpos--;
3203		else {
3204		    scp->xpos += scp->xsize - 1;
3205		    scp->ypos--;
3206		}
3207	    }
3208	    break;
3209
3210	case 0x09:  /* non-destructive tab */
3211	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
3212	    scp->cursor_pos += (8 - scp->xpos % 8u);
3213	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
3214	    if ((scp->xpos += (8 - scp->xpos % 8u)) >= scp->xsize) {
3215	        scp->xpos = 0;
3216	        scp->ypos++;
3217	    }
3218	    break;
3219
3220	case 0x0a:  /* newline, same pos */
3221	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
3222	    scp->cursor_pos += scp->xsize;
3223	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
3224	    scp->ypos++;
3225	    break;
3226
3227	case 0x0c:  /* form feed, clears screen */
3228	    clear_screen(scp);
3229	    break;
3230
3231	case 0x0d:  /* return, return to pos 0 */
3232	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
3233	    scp->cursor_pos -= scp->xpos;
3234	    mark_for_update(scp, scp->cursor_pos - scp->scr_buf);
3235	    scp->xpos = 0;
3236	    break;
3237
3238	case 0x1b:  /* start escape sequence */
3239	    scp->term.esc = 1;
3240	    scp->term.num_param = 0;
3241	    break;
3242	}
3243	ptr++; len--;
3244    }
3245    /* do we have to scroll ?? */
3246    if (scp->cursor_pos >= scp->scr_buf + scp->ysize * scp->xsize) {
3247	remove_cutmarking(scp);
3248	if (scp->history) {
3249	    bcopy(scp->scr_buf, scp->history_head,
3250		   scp->xsize * sizeof(u_short));
3251	    scp->history_head += scp->xsize;
3252	    if (scp->history_head + scp->xsize >
3253		scp->history + scp->history_size)
3254		scp->history_head = scp->history;
3255	}
3256	bcopy(scp->scr_buf + scp->xsize, scp->scr_buf,
3257	       scp->xsize * (scp->ysize - 1) * sizeof(u_short));
3258	fillw(scp->term.cur_color | scr_map[0x20],
3259	      scp->scr_buf + scp->xsize * (scp->ysize - 1),
3260	      scp->xsize);
3261	scp->cursor_pos -= scp->xsize;
3262	scp->ypos--;
3263    	mark_all(scp);
3264    }
3265    if (len)
3266	goto outloop;
3267    write_in_progress--;
3268    if (delayed_next_scr)
3269	switch_scr(scp, delayed_next_scr - 1);
3270}
3271
3272static void
3273scinit(void)
3274{
3275    u_int hw_cursor;
3276    u_int i;
3277
3278    if (init_done != COLD)
3279	return;
3280    init_done = WARM;
3281
3282    /*
3283     * Ensure a zero start address.  This is mainly to recover after
3284     * switching from pcvt using userconfig().  The registers are w/o
3285     * for old hardware so it's too hard to relocate the active screen
3286     * memory.
3287     */
3288    outb(crtc_addr, 12);
3289    outb(crtc_addr + 1, 0);
3290    outb(crtc_addr, 13);
3291    outb(crtc_addr + 1, 0);
3292
3293    /* extract cursor location */
3294    outb(crtc_addr, 14);
3295    hw_cursor = inb(crtc_addr + 1) << 8;
3296    outb(crtc_addr, 15);
3297    hw_cursor |= inb(crtc_addr + 1);
3298
3299    /*
3300     * Validate cursor location.  It may be off the screen.  Then we must
3301     * not use it for the initial buffer offset.
3302     */
3303    if (hw_cursor >= ROW * COL)
3304	hw_cursor = (ROW - 1) * COL;
3305
3306    /* move hardware cursor out of the way */
3307    outb(crtc_addr, 14);
3308    outb(crtc_addr + 1, 0xff);
3309    outb(crtc_addr, 15);
3310    outb(crtc_addr + 1, 0xff);
3311
3312    /* set up the first console */
3313    current_default = &user_default;
3314    console[0] = &main_console;
3315    init_scp(console[0]);
3316    cur_console = console[0];
3317
3318    /* discard the video mode table if we are not familiar with it... */
3319    if (video_mode_ptr) {
3320        bzero(mode_map, sizeof(mode_map));
3321	bcopy(video_mode_ptr + MODE_PARAM_SIZE*console[0]->mode,
3322	      vgaregs2, sizeof(vgaregs2));
3323        switch (comp_vgaregs(vgaregs, video_mode_ptr
3324                    + MODE_PARAM_SIZE*console[0]->mode)) {
3325        case COMP_IDENTICAL:
3326            map_mode_table(mode_map, video_mode_ptr, M_VGA_CG320 + 1);
3327            /*
3328             * This is a kludge for Toshiba DynaBook SS433 whose BIOS video
3329             * mode table entry has the actual # of rows at the offset 1;
3330	     * BIOSes from other manufacturers store the # of rows - 1 there.
3331	     * XXX
3332             */
3333	    rows_offset = vgaregs[1] + 1
3334		- video_mode_ptr[MODE_PARAM_SIZE*console[0]->mode + 1];
3335            break;
3336        case COMP_SIMILAR:
3337            map_mode_table(mode_map, video_mode_ptr, M_VGA_CG320 + 1);
3338            mode_map[console[0]->mode] = vgaregs;
3339	    rows_offset = vgaregs[1] + 1
3340		- video_mode_ptr[MODE_PARAM_SIZE*console[0]->mode + 1];
3341            vgaregs[1] -= rows_offset - 1;
3342            break;
3343        case COMP_DIFFERENT:
3344        default:
3345            video_mode_ptr = NULL;
3346            mode_map[console[0]->mode] = vgaregs;
3347	    rows_offset = 1;
3348            break;
3349        }
3350    }
3351
3352    /* copy screen to temporary buffer */
3353    if (crtc_type != KD_PIXEL)
3354	    generic_bcopy(Crtat, sc_buffer,
3355		   console[0]->xsize * console[0]->ysize * sizeof(u_short));
3356
3357    console[0]->scr_buf = console[0]->mouse_pos = console[0]->mouse_oldpos
3358	= sc_buffer;
3359    console[0]->cursor_pos = console[0]->cursor_oldpos = sc_buffer + hw_cursor;
3360    console[0]->cursor_saveunder = *console[0]->cursor_pos;
3361    console[0]->xpos = hw_cursor % COL;
3362    console[0]->ypos = hw_cursor / COL;
3363    for (i=1; i<MAXCONS; i++)
3364	console[i] = NULL;
3365    kernel_console.esc = 0;
3366    kernel_console.attr_mask = NORMAL_ATTR;
3367    kernel_console.cur_attr =
3368	kernel_console.cur_color = kernel_console.std_color =
3369	kernel_default.std_color;
3370    kernel_console.rev_color = kernel_default.rev_color;
3371
3372    /* initialize mapscrn arrays to a one to one map */
3373    for (i=0; i<sizeof(scr_map); i++) {
3374	scr_map[i] = scr_rmap[i] = i;
3375    }
3376
3377    /* Save font and palette if VGA */
3378    if (crtc_vga) {
3379	if (fonts_loaded & FONT_16) {
3380		copy_font(LOAD, FONT_16, font_16);
3381	} else {
3382		copy_font(SAVE, FONT_16, font_16);
3383		fonts_loaded = FONT_16;
3384	}
3385	save_palette();
3386	set_destructive_cursor(console[0]);
3387    }
3388
3389#ifdef SC_SPLASH_SCREEN
3390    /*
3391     * Now put up a graphics image, and maybe cycle a
3392     * couble of palette entries for simple animation.
3393     */
3394    toggle_splash_screen(cur_console);
3395#endif
3396}
3397
3398static void
3399map_mode_table(char *map[], char *table, int max)
3400{
3401    int i;
3402
3403    for(i = 0; i < max; ++i)
3404	map[i] = table + i*MODE_PARAM_SIZE;
3405    for(; i < MODE_MAP_SIZE; ++i)
3406	map[i] = NULL;
3407}
3408
3409static u_char
3410map_mode_num(u_char mode)
3411{
3412    static struct {
3413        u_char from;
3414        u_char to;
3415    } mode_map[] = {
3416        { M_ENH_B80x43, M_ENH_B80x25 },
3417        { M_ENH_C80x43, M_ENH_C80x25 },
3418        { M_VGA_M80x30, M_VGA_M80x25 },
3419        { M_VGA_C80x30, M_VGA_C80x25 },
3420        { M_VGA_M80x50, M_VGA_M80x25 },
3421        { M_VGA_C80x50, M_VGA_C80x25 },
3422        { M_VGA_M80x60, M_VGA_M80x25 },
3423        { M_VGA_C80x60, M_VGA_C80x25 },
3424        { M_VGA_MODEX,  M_VGA_CG320 },
3425    };
3426    int i;
3427
3428    for (i = 0; i < sizeof(mode_map)/sizeof(mode_map[0]); ++i) {
3429        if (mode_map[i].from == mode)
3430            return mode_map[i].to;
3431    }
3432    return mode;
3433}
3434
3435static char
3436*get_mode_param(scr_stat *scp, u_char mode)
3437{
3438    if (mode >= MODE_MAP_SIZE)
3439	mode = map_mode_num(mode);
3440    if (mode < MODE_MAP_SIZE)
3441	return mode_map[mode];
3442    else
3443	return NULL;
3444}
3445
3446static scr_stat
3447*alloc_scp()
3448{
3449    scr_stat *scp;
3450
3451    scp = (scr_stat *)malloc(sizeof(scr_stat), M_DEVBUF, M_WAITOK);
3452    init_scp(scp);
3453    scp->scr_buf = scp->cursor_pos = scp->cursor_oldpos =
3454	(u_short *)malloc(scp->xsize*scp->ysize*sizeof(u_short),
3455			  M_DEVBUF, M_WAITOK);
3456    scp->mouse_pos = scp->mouse_oldpos =
3457	scp->scr_buf + ((scp->mouse_ypos/scp->font_size)*scp->xsize +
3458			scp->mouse_xpos/8);
3459    scp->history_head = scp->history_pos =
3460	(u_short *)malloc(scp->history_size*sizeof(u_short),
3461			  M_DEVBUF, M_WAITOK);
3462    bzero(scp->history_head, scp->history_size*sizeof(u_short));
3463    scp->history = scp->history_head;
3464/* SOS
3465    if (crtc_vga && video_mode_ptr)
3466	set_mode(scp);
3467*/
3468    clear_screen(scp);
3469    scp->cursor_saveunder = *scp->cursor_pos;
3470    return scp;
3471}
3472
3473static void
3474init_scp(scr_stat *scp)
3475{
3476    switch(crtc_type) {
3477    case KD_VGA:
3478	if (crtc_addr == MONO_BASE)
3479	    scp->mode = M_VGA_M80x25;
3480	else
3481	    scp->mode = M_VGA_C80x25;
3482	scp->font_size = 16;
3483	break;
3484    case KD_CGA:
3485	if (crtc_addr == MONO_BASE)
3486	    scp->mode = M_B80x25;
3487	else
3488	    scp->mode = M_C80x25;
3489	scp->font_size = 8;
3490	break;
3491    case KD_EGA:
3492	if (crtc_addr == MONO_BASE)
3493	    scp->mode = M_B80x25;
3494	else
3495	    scp->mode = M_C80x25;
3496	scp->font_size = 14;
3497	break;
3498    case KD_MONO:
3499    case KD_HERCULES:
3500    default:
3501	scp->mode = M_EGAMONO80x25;
3502	scp->font_size = 14;
3503	break;
3504    }
3505    scp->initial_mode = scp->mode;
3506
3507    scp->xsize = COL;
3508    scp->ysize = ROW;
3509    scp->xpixel = scp->xsize * 8;
3510    scp->ypixel = scp->ysize * scp->font_size;
3511    scp->xpos = scp->ypos = 0;
3512    scp->saved_xpos = scp->saved_ypos = -1;
3513    scp->start = scp->xsize * scp->ysize;
3514    scp->end = 0;
3515    scp->term.esc = 0;
3516    scp->term.attr_mask = NORMAL_ATTR;
3517    scp->term.cur_attr =
3518	scp->term.cur_color = scp->term.std_color =
3519	current_default->std_color;
3520    scp->term.rev_color = current_default->rev_color;
3521    scp->border = BG_BLACK;
3522    scp->cursor_start = *(char *)pa_to_va(0x461);
3523    scp->cursor_end = *(char *)pa_to_va(0x460);
3524    scp->mouse_xpos = scp->xsize*8/2;
3525    scp->mouse_ypos = scp->ysize*scp->font_size/2;
3526    scp->mouse_cut_start = scp->mouse_cut_end = NULL;
3527    scp->mouse_signal = 0;
3528    scp->mouse_pid = 0;
3529    scp->mouse_proc = NULL;
3530    scp->bell_pitch = BELL_PITCH;
3531    scp->bell_duration = BELL_DURATION;
3532    scp->status = (*(char *)pa_to_va(0x417) & 0x20) ? NLKED : 0;
3533    scp->status |= CURSOR_ENABLED;
3534    scp->pid = 0;
3535    scp->proc = NULL;
3536    scp->smode.mode = VT_AUTO;
3537    scp->history_head = scp->history_pos = scp->history = NULL;
3538    scp->history_size = imax(SC_HISTORY_SIZE, scp->ysize) * scp->xsize;
3539}
3540
3541static u_char
3542*get_fstr(u_int c, u_int *len)
3543{
3544    u_int i;
3545
3546    if (!(c & FKEY))
3547	return(NULL);
3548    i = (c & 0xFF) - F_FN;
3549    if (i > n_fkey_tab)
3550	return(NULL);
3551    *len = fkey_tab[i].len;
3552    return(fkey_tab[i].str);
3553}
3554
3555static void
3556history_to_screen(scr_stat *scp)
3557{
3558    int i;
3559
3560    for (i=0; i<scp->ysize; i++)
3561	bcopy(scp->history + (((scp->history_pos - scp->history) +
3562	       scp->history_size-((i+1)*scp->xsize))%scp->history_size),
3563	       scp->scr_buf + (scp->xsize * (scp->ysize-1 - i)),
3564	       scp->xsize * sizeof(u_short));
3565    mark_all(scp);
3566}
3567
3568static int
3569history_up_line(scr_stat *scp)
3570{
3571    if (WRAPHIST(scp, scp->history_pos, -(scp->xsize*scp->ysize)) !=
3572	scp->history_head) {
3573	scp->history_pos = WRAPHIST(scp, scp->history_pos, -scp->xsize);
3574	history_to_screen(scp);
3575	return 0;
3576    }
3577    else
3578	return -1;
3579}
3580
3581static int
3582history_down_line(scr_stat *scp)
3583{
3584    if (scp->history_pos != scp->history_head) {
3585	scp->history_pos = WRAPHIST(scp, scp->history_pos, scp->xsize);
3586	history_to_screen(scp);
3587	return 0;
3588    }
3589    else
3590	return -1;
3591}
3592
3593/*
3594 * scgetc(flags) - get character from keyboard.
3595 * If flags & SCGETC_CN, then avoid harmful side effects.
3596 * If flags & SCGETC_NONBLOCK, then wait until a key is pressed, else
3597 * return NOKEY if there is nothing there.
3598 */
3599static u_int
3600scgetc(u_int flags)
3601{
3602    struct key_t *key;
3603    u_char scancode, keycode;
3604    u_int state, action;
3605    int c;
3606    static u_char esc_flag = 0, compose = 0;
3607    static u_int chr = 0;
3608
3609next_code:
3610    /* first see if there is something in the keyboard port */
3611    if (flags & SCGETC_NONBLOCK) {
3612	c = read_kbd_data_no_wait(sc_kbdc);
3613	if (c == -1)
3614	    return(NOKEY);
3615    } else {
3616	do {
3617	    c = read_kbd_data(sc_kbdc);
3618	} while(c == -1);
3619    }
3620    scancode = (u_char)c;
3621
3622    /* make screensaver happy */
3623    if (!(scancode & 0x80))
3624	getmicrouptime(&scrn_time_stamp);
3625
3626    if (!(flags & SCGETC_CN)) {
3627	/* do the /dev/random device a favour */
3628	add_keyboard_randomness(scancode);
3629
3630	if (cur_console->status & KBD_RAW_MODE)
3631	    return scancode;
3632    }
3633
3634    keycode = scancode & 0x7F;
3635    switch (esc_flag) {
3636    case 0x00:      /* normal scancode */
3637	switch(scancode) {
3638	case 0xB8:  /* left alt (compose key) */
3639	    if (compose) {
3640		compose = 0;
3641		if (chr > 255) {
3642		    do_bell(cur_console,
3643			BELL_PITCH, BELL_DURATION);
3644		    chr = 0;
3645		}
3646	    }
3647	    break;
3648	case 0x38:
3649	    if (!compose) {
3650		compose = 1;
3651		chr = 0;
3652	    }
3653	    break;
3654	case 0xE0:
3655	case 0xE1:
3656	    esc_flag = scancode;
3657	    goto next_code;
3658	}
3659	break;
3660    case 0xE0:      /* 0xE0 prefix */
3661	esc_flag = 0;
3662	switch (keycode) {
3663	case 0x1C:  /* right enter key */
3664	    keycode = 0x59;
3665	    break;
3666	case 0x1D:  /* right ctrl key */
3667	    keycode = 0x5A;
3668	    break;
3669	case 0x35:  /* keypad divide key */
3670	    keycode = 0x5B;
3671	    break;
3672	case 0x37:  /* print scrn key */
3673	    keycode = 0x5C;
3674	    break;
3675	case 0x38:  /* right alt key (alt gr) */
3676	    keycode = 0x5D;
3677	    break;
3678	case 0x47:  /* grey home key */
3679	    keycode = 0x5E;
3680	    break;
3681	case 0x48:  /* grey up arrow key */
3682	    keycode = 0x5F;
3683	    break;
3684	case 0x49:  /* grey page up key */
3685	    keycode = 0x60;
3686	    break;
3687	case 0x4B:  /* grey left arrow key */
3688	    keycode = 0x61;
3689	    break;
3690	case 0x4D:  /* grey right arrow key */
3691	    keycode = 0x62;
3692	    break;
3693	case 0x4F:  /* grey end key */
3694	    keycode = 0x63;
3695	    break;
3696	case 0x50:  /* grey down arrow key */
3697	    keycode = 0x64;
3698	    break;
3699	case 0x51:  /* grey page down key */
3700	    keycode = 0x65;
3701	    break;
3702	case 0x52:  /* grey insert key */
3703	    keycode = 0x66;
3704	    break;
3705	case 0x53:  /* grey delete key */
3706	    keycode = 0x67;
3707	    break;
3708
3709	/* the following 3 are only used on the MS "Natural" keyboard */
3710	case 0x5b:  /* left Window key */
3711	    keycode = 0x69;
3712	    break;
3713	case 0x5c:  /* right Window key */
3714	    keycode = 0x6a;
3715	    break;
3716	case 0x5d:  /* menu key */
3717	    keycode = 0x6b;
3718	    break;
3719	default:    /* ignore everything else */
3720	    goto next_code;
3721	}
3722	break;
3723    case 0xE1:      /* 0xE1 prefix */
3724	esc_flag = 0;
3725	if (keycode == 0x1D)
3726	    esc_flag = 0x1D;
3727	goto next_code;
3728	/* NOT REACHED */
3729    case 0x1D:      /* pause / break */
3730	esc_flag = 0;
3731	if (keycode != 0x45)
3732	    goto next_code;
3733	keycode = 0x68;
3734	break;
3735    }
3736
3737    if (!(flags & SCGETC_CN) && (cur_console->status & KBD_CODE_MODE))
3738	return (keycode | (scancode & 0x80));
3739
3740    /* if scroll-lock pressed allow history browsing */
3741    if (cur_console->history && cur_console->status & SLKED) {
3742	int i;
3743
3744	cur_console->status &= ~CURSOR_ENABLED;
3745	if (!(cur_console->status & BUFFER_SAVED)) {
3746	    cur_console->status |= BUFFER_SAVED;
3747	    cur_console->history_save = cur_console->history_head;
3748
3749	    /* copy screen into top of history buffer */
3750	    for (i=0; i<cur_console->ysize; i++) {
3751		bcopy(cur_console->scr_buf + (cur_console->xsize * i),
3752		       cur_console->history_head,
3753		       cur_console->xsize * sizeof(u_short));
3754		cur_console->history_head += cur_console->xsize;
3755		if (cur_console->history_head + cur_console->xsize >
3756		    cur_console->history + cur_console->history_size)
3757		    cur_console->history_head=cur_console->history;
3758	    }
3759	    cur_console->history_pos = cur_console->history_head;
3760	    history_to_screen(cur_console);
3761	}
3762	switch (scancode) {
3763	case 0x47:  /* home key */
3764	    cur_console->history_pos = cur_console->history_head;
3765	    history_to_screen(cur_console);
3766	    goto next_code;
3767
3768	case 0x4F:  /* end key */
3769	    cur_console->history_pos =
3770		WRAPHIST(cur_console, cur_console->history_head,
3771			 cur_console->xsize*cur_console->ysize);
3772	    history_to_screen(cur_console);
3773	    goto next_code;
3774
3775	case 0x48:  /* up arrow key */
3776	    if (history_up_line(cur_console))
3777		do_bell(cur_console, BELL_PITCH, BELL_DURATION);
3778	    goto next_code;
3779
3780	case 0x50:  /* down arrow key */
3781	    if (history_down_line(cur_console))
3782		do_bell(cur_console, BELL_PITCH, BELL_DURATION);
3783	    goto next_code;
3784
3785	case 0x49:  /* page up key */
3786	    for (i=0; i<cur_console->ysize; i++)
3787	    if (history_up_line(cur_console)) {
3788		do_bell(cur_console, BELL_PITCH, BELL_DURATION);
3789		break;
3790	    }
3791	    goto next_code;
3792
3793	case 0x51:  /* page down key */
3794	    for (i=0; i<cur_console->ysize; i++)
3795	    if (history_down_line(cur_console)) {
3796		do_bell(cur_console, BELL_PITCH, BELL_DURATION);
3797		break;
3798	    }
3799	    goto next_code;
3800	}
3801    }
3802
3803    if (compose) {
3804	switch (scancode) {
3805	/* key pressed process it */
3806	case 0x47: case 0x48: case 0x49:    /* keypad 7,8,9 */
3807	    chr = (scancode - 0x40) + chr*10;
3808	    goto next_code;
3809	case 0x4B: case 0x4C: case 0x4D:    /* keypad 4,5,6 */
3810	    chr = (scancode - 0x47) + chr*10;
3811	    goto next_code;
3812	case 0x4F: case 0x50: case 0x51:    /* keypad 1,2,3 */
3813	    chr = (scancode - 0x4E) + chr*10;
3814	    goto next_code;
3815	case 0x52:              /* keypad 0 */
3816	    chr *= 10;
3817	    goto next_code;
3818
3819	/* key release, no interest here */
3820	case 0xC7: case 0xC8: case 0xC9:    /* keypad 7,8,9 */
3821	case 0xCB: case 0xCC: case 0xCD:    /* keypad 4,5,6 */
3822	case 0xCF: case 0xD0: case 0xD1:    /* keypad 1,2,3 */
3823	case 0xD2:              /* keypad 0 */
3824	    goto next_code;
3825
3826	case 0x38:              /* left alt key */
3827	    break;
3828	default:
3829	    if (chr) {
3830		compose = chr = 0;
3831		do_bell(cur_console, BELL_PITCH, BELL_DURATION);
3832		goto next_code;
3833	    }
3834	    break;
3835	}
3836    }
3837
3838    state = (shfts ? 1 : 0 ) | (2 * (ctls ? 1 : 0)) | (4 * (alts ? 1 : 0));
3839    if ((!agrs && (cur_console->status & ALKED))
3840	|| (agrs && !(cur_console->status & ALKED)))
3841	keycode += ALTGR_OFFSET;
3842    key = &key_map.key[keycode];
3843    if ( ((key->flgs & FLAG_LOCK_C) && (cur_console->status & CLKED))
3844	 || ((key->flgs & FLAG_LOCK_N) && (cur_console->status & NLKED)) )
3845	state ^= 1;
3846
3847    /* Check for make/break */
3848    action = key->map[state];
3849    if (scancode & 0x80) {      /* key released */
3850	if (key->spcl & (0x80>>state)) {
3851	    switch (action) {
3852	    case LSH:
3853		shfts &= ~1;
3854		break;
3855	    case RSH:
3856		shfts &= ~2;
3857		break;
3858	    case LCTR:
3859		ctls &= ~1;
3860		break;
3861	    case RCTR:
3862		ctls &= ~2;
3863		break;
3864	    case LALT:
3865		alts &= ~1;
3866		break;
3867	    case RALT:
3868		alts &= ~2;
3869		break;
3870	    case NLK:
3871		nlkcnt = 0;
3872		break;
3873	    case CLK:
3874		clkcnt = 0;
3875		break;
3876	    case SLK:
3877		slkcnt = 0;
3878		break;
3879	    case ASH:
3880		agrs = 0;
3881		break;
3882	    case ALK:
3883		alkcnt = 0;
3884		break;
3885	    case META:
3886		metas = 0;
3887		break;
3888	    }
3889	}
3890	if (chr && !compose) {
3891	    action = chr;
3892	    chr = 0;
3893	    return(action);
3894	}
3895    } else {
3896	/* key pressed */
3897	if (key->spcl & (0x80>>state)) {
3898	    switch (action) {
3899	    /* LOCKING KEYS */
3900	    case NLK:
3901#ifdef SC_SPLASH_SCREEN
3902		toggle_splash_screen(cur_console); /* SOS XXX */
3903#endif
3904		if (!nlkcnt) {
3905		    nlkcnt++;
3906		    if (cur_console->status & NLKED)
3907			cur_console->status &= ~NLKED;
3908		    else
3909			cur_console->status |= NLKED;
3910		    update_leds(cur_console->status);
3911		}
3912		break;
3913	    case CLK:
3914		if (!clkcnt) {
3915		    clkcnt++;
3916		    if (cur_console->status & CLKED)
3917			cur_console->status &= ~CLKED;
3918		    else
3919			cur_console->status |= CLKED;
3920		    update_leds(cur_console->status);
3921		}
3922		break;
3923	    case SLK:
3924		if (!slkcnt) {
3925		    slkcnt++;
3926		    if (cur_console->status & SLKED) {
3927			cur_console->status &= ~SLKED;
3928			if (cur_console->status & BUFFER_SAVED){
3929			    int i;
3930			    u_short *ptr = cur_console->history_save;
3931
3932			    for (i=0; i<cur_console->ysize; i++) {
3933				bcopy(ptr,
3934				       cur_console->scr_buf +
3935				       (cur_console->xsize*i),
3936				       cur_console->xsize * sizeof(u_short));
3937				ptr += cur_console->xsize;
3938				if (ptr + cur_console->xsize >
3939				    cur_console->history +
3940				    cur_console->history_size)
3941				    ptr = cur_console->history;
3942			    }
3943			    cur_console->status &= ~BUFFER_SAVED;
3944			    cur_console->history_head=cur_console->history_save;
3945			    cur_console->status |= CURSOR_ENABLED;
3946			    mark_all(cur_console);
3947			}
3948			scstart(VIRTUAL_TTY(get_scr_num()));
3949		    }
3950		    else
3951			cur_console->status |= SLKED;
3952		    update_leds(cur_console->status);
3953		}
3954		break;
3955	    case ALK:
3956		if (!alkcnt) {
3957		    alkcnt++;
3958		    if (cur_console->status & ALKED)
3959			cur_console->status &= ~ALKED;
3960		    else
3961			cur_console->status |= ALKED;
3962		    update_leds(cur_console->status);
3963		}
3964		break;
3965
3966	    /* NON-LOCKING KEYS */
3967	    case NOP:
3968		break;
3969	    case SPSC:
3970#ifdef SC_SPLASH_SCREEN
3971		accents = 0;
3972		toggle_splash_screen(cur_console);
3973#endif
3974		break;
3975	    case RBT:
3976#ifndef SC_DISABLE_REBOOT
3977		accents = 0;
3978		shutdown_nice();
3979#endif
3980		break;
3981	    case SUSP:
3982#if NAPM > 0
3983		accents = 0;
3984		apm_suspend();
3985#endif
3986		break;
3987
3988	    case DBG:
3989#ifdef DDB          /* try to switch to console 0 */
3990		accents = 0;
3991		if (cur_console->smode.mode == VT_AUTO &&
3992		    console[0]->smode.mode == VT_AUTO)
3993		    switch_scr(cur_console, 0);
3994		Debugger("manual escape to debugger");
3995#else
3996		printf("No debugger in kernel\n");
3997#endif
3998		break;
3999	    case LSH:
4000		shfts |= 1;
4001		break;
4002	    case RSH:
4003		shfts |= 2;
4004		break;
4005	    case LCTR:
4006		ctls |= 1;
4007		break;
4008	    case RCTR:
4009		ctls |= 2;
4010		break;
4011	    case LALT:
4012		alts |= 1;
4013		break;
4014	    case RALT:
4015		alts |= 2;
4016		break;
4017	    case ASH:
4018		agrs = 1;
4019		break;
4020	    case META:
4021		metas = 1;
4022		break;
4023	    case NEXT:
4024		{
4025		int next, this = get_scr_num();
4026		accents = 0;
4027		for (next = this+1; next != this; next = (next+1)%MAXCONS) {
4028		    struct tty *tp = VIRTUAL_TTY(next);
4029		    if (tp->t_state & TS_ISOPEN) {
4030			switch_scr(cur_console, next);
4031			break;
4032		    }
4033		}
4034		}
4035		break;
4036	    case BTAB:
4037		accents = 0;
4038		return(BKEY);
4039	    default:
4040		if (action >= F_ACC && action <= L_ACC) {
4041		    /* turn it into an index */
4042		    action -= F_ACC - 1;
4043		    if ((action > accent_map.n_accs)
4044			|| (accent_map.acc[action - 1].accchar == 0)) {
4045			/*
4046			 * The index is out of range or pointing to an
4047			 * empty entry.
4048			 */
4049			accents = 0;
4050			do_bell(cur_console, BELL_PITCH, BELL_DURATION);
4051		    }
4052		    /*
4053		     * If the same accent key has been hit twice,
4054		     * produce the accent char itself.
4055		     */
4056		    if (action == accents) {
4057			action = accent_map.acc[accents - 1].accchar;
4058			accents = 0;
4059			if (metas)
4060			    action |= MKEY;
4061			return (action);
4062		    }
4063		    /* remember the index and wait for the next key stroke */
4064		    accents = action;
4065		    break;
4066		}
4067		if (accents > 0) {
4068		    accents = 0;
4069		    do_bell(cur_console, BELL_PITCH, BELL_DURATION);
4070		}
4071		if (action >= F_SCR && action <= L_SCR) {
4072		    switch_scr(cur_console, action - F_SCR);
4073		    break;
4074		}
4075		if (action >= F_FN && action <= L_FN)
4076		    action |= FKEY;
4077		return(action);
4078	    }
4079	}
4080	else {
4081	    if (accents) {
4082		struct acc_t *acc;
4083		int i;
4084
4085		acc = &accent_map.acc[accents - 1];
4086		accents = 0;
4087		/*
4088		 * If the accent key is followed by the space key,
4089		 * produce the accent char itself.
4090		 */
4091		if (action == ' ') {
4092		    action = acc->accchar;
4093		    if (metas)
4094			action |= MKEY;
4095		    return (action);
4096		}
4097		for (i = 0; i < NUM_ACCENTCHARS; ++i) {
4098		    if (acc->map[i][0] == 0)	/* end of the map entry */
4099			break;
4100		    if (acc->map[i][0] == action) {
4101			action = acc->map[i][1];
4102			if (metas)
4103			    action |= MKEY;
4104			return (action);
4105		    }
4106		}
4107		do_bell(cur_console, BELL_PITCH, BELL_DURATION);
4108		goto next_code;
4109	    }
4110	    if (metas)
4111		action |= MKEY;
4112	    return(action);
4113	}
4114    }
4115    goto next_code;
4116}
4117
4118int
4119scmmap(dev_t dev, int offset, int nprot)
4120{
4121    if (offset > 0x20000 - PAGE_SIZE)
4122	return -1;
4123    return i386_btop((VIDEOMEM + offset));
4124}
4125
4126/*
4127 * Calculate hardware attributes word using logical attributes mask and
4128 * hardware colors
4129 */
4130
4131static int
4132mask2attr(struct term_stat *term)
4133{
4134    int attr, mask = term->attr_mask;
4135
4136    if (mask & REVERSE_ATTR) {
4137	attr = ((mask & FOREGROUND_CHANGED) ?
4138		((term->cur_color & 0xF000) >> 4) :
4139		(term->rev_color & 0x0F00)) |
4140	       ((mask & BACKGROUND_CHANGED) ?
4141		((term->cur_color & 0x0F00) << 4) :
4142		(term->rev_color & 0xF000));
4143    } else
4144	attr = term->cur_color;
4145
4146    /* XXX: underline mapping for Hercules adapter can be better */
4147    if (mask & (BOLD_ATTR | UNDERLINE_ATTR))
4148	attr ^= 0x0800;
4149    if (mask & BLINK_ATTR)
4150	attr ^= 0x8000;
4151
4152    return attr;
4153}
4154
4155static void
4156set_keyboard(int command, int data)
4157{
4158    int s;
4159
4160    if (sc_kbdc == NULL)
4161	return;
4162
4163    /* prevent the timeout routine from polling the keyboard */
4164    if (!kbdc_lock(sc_kbdc, TRUE))
4165	return;
4166
4167    /* disable the keyboard and mouse interrupt */
4168    s = spltty();
4169#if 0
4170    c = get_controller_command_byte(sc_kbdc);
4171    if ((c == -1)
4172	|| !set_controller_command_byte(sc_kbdc,
4173            kbdc_get_device_mask(sc_kbdc),
4174            KBD_DISABLE_KBD_PORT | KBD_DISABLE_KBD_INT
4175                | KBD_DISABLE_AUX_PORT | KBD_DISABLE_AUX_INT)) {
4176	/* CONTROLLER ERROR */
4177        kbdc_lock(sc_kbdc, FALSE);
4178	splx(s);
4179	return;
4180    }
4181    /*
4182     * Now that the keyboard controller is told not to generate
4183     * the keyboard and mouse interrupts, call `splx()' to allow
4184     * the other tty interrupts. The clock interrupt may also occur,
4185     * but the timeout routine (`scrn_timer()') will be blocked
4186     * by the lock flag set via `kbdc_lock()'
4187     */
4188    splx(s);
4189#endif
4190
4191    if (send_kbd_command_and_data(sc_kbdc, command, data) != KBD_ACK)
4192        send_kbd_command(sc_kbdc, KBDC_ENABLE_KBD);
4193
4194#if 0
4195    /* restore the interrupts */
4196    if (!set_controller_command_byte(sc_kbdc,
4197            kbdc_get_device_mask(sc_kbdc),
4198	    c & (KBD_KBD_CONTROL_BITS | KBD_AUX_CONTROL_BITS))) {
4199	/* CONTROLLER ERROR */
4200    }
4201#else
4202    splx(s);
4203#endif
4204    kbdc_lock(sc_kbdc, FALSE);
4205}
4206
4207static void
4208update_leds(int which)
4209{
4210    static u_char xlate_leds[8] = { 0, 4, 2, 6, 1, 5, 3, 7 };
4211
4212    /* replace CAPS led with ALTGR led for ALTGR keyboards */
4213    if (key_map.n_keys > ALTGR_OFFSET) {
4214	if (which & ALKED)
4215	    which |= CLKED;
4216	else
4217	    which &= ~CLKED;
4218    }
4219
4220    set_keyboard(KBDC_SET_LEDS, xlate_leds[which & LED_MASK]);
4221}
4222
4223void
4224set_mode(scr_stat *scp)
4225{
4226    char special_modetable[MODE_PARAM_SIZE];
4227    char *mp;
4228    int s;
4229    int i;
4230
4231    if (scp != cur_console)
4232	return;
4233
4234    /*
4235     * even if mode switching is disabled, we can change back
4236     * to the initial mode or the custom mode based on the initial
4237     * mode if we have saved register values upon start-up.
4238     */
4239    mp = get_mode_param(scp, scp->mode);
4240    if (mp == NULL)
4241	return;
4242    bcopy(mp, &special_modetable, sizeof(special_modetable));
4243
4244    /* setup video hardware for the given mode */
4245    switch (scp->mode) {
4246    case M_VGA_C80x60: case M_VGA_M80x60:
4247	special_modetable[2]  = 0x08;
4248	special_modetable[19] = 0x47;
4249	goto special_480l;
4250
4251    case M_VGA_C80x30: case M_VGA_M80x30:
4252	special_modetable[19] = 0x4f;
4253special_480l:
4254	special_modetable[9] |= 0xc0;
4255	special_modetable[16] = 0x08;
4256	special_modetable[17] = 0x3e;
4257	special_modetable[26] = 0xea;
4258	special_modetable[28] = 0xdf;
4259	special_modetable[31] = 0xe7;
4260	special_modetable[32] = 0x04;
4261	goto setup_mode;
4262
4263    case M_ENH_C80x43: case M_ENH_B80x43:
4264	special_modetable[28] = 87;
4265	goto special_80x50;
4266
4267    case M_VGA_C80x50: case M_VGA_M80x50:
4268special_80x50:
4269	special_modetable[2] = 8;
4270	special_modetable[19] = 7;
4271	goto setup_mode;
4272
4273    case M_VGA_C40x25: case M_VGA_C80x25:
4274    case M_VGA_M80x25:
4275    case M_B40x25:     case M_C40x25:
4276    case M_B80x25:     case M_C80x25:
4277    case M_ENH_B40x25: case M_ENH_C40x25:
4278    case M_ENH_B80x25: case M_ENH_C80x25:
4279    case M_EGAMONO80x25:
4280
4281setup_mode:
4282	set_vgaregs(special_modetable);
4283	scp->font_size = special_modetable[2];
4284
4285	/* set font type (size) */
4286	if (scp->font_size < 14) {
4287	    if (fonts_loaded & FONT_8)
4288		copy_font(LOAD, FONT_8, font_8);
4289	    i = 0x0a;				/* font 2 */
4290	} else if (scp->font_size >= 16) {
4291	    if (fonts_loaded & FONT_16)
4292		copy_font(LOAD, FONT_16, font_16);
4293	    i = 0x00;				/* font 0 */
4294	} else {
4295	    if (fonts_loaded & FONT_14)
4296		copy_font(LOAD, FONT_14, font_14);
4297	    i = 0x05;				/* font 1 */
4298	}
4299	/*
4300	 * FONT KLUDGE:
4301	 * This is an interim kludge to display correct font.
4302	 * Always use the font page #0 on the video plane 2.
4303	 * Somehow we cannot show the font in other font pages on
4304	 * some video cards... XXX
4305	 */
4306	i = 0x00;
4307	s = splhigh();
4308	outb(TSIDX, 0x00); outb(TSREG, 0x01);
4309	outb(TSIDX, 0x03); outb(TSREG, i);
4310	outb(TSIDX, 0x00); outb(TSREG, 0x03);
4311	splx(s);
4312	if (flags & CHAR_CURSOR)
4313	    set_destructive_cursor(scp);
4314	mark_all(scp);
4315	break;
4316
4317    case M_VGA_MODEX:
4318	/* "unchain" the VGA mode */
4319	special_modetable[5-1+0x04] &= 0xf7;
4320	special_modetable[5-1+0x04] |= 0x04;
4321	/* turn off doubleword mode */
4322	special_modetable[10+0x14] &= 0xbf;
4323	/* turn off word adressing */
4324	special_modetable[10+0x17] |= 0x40;
4325	/* set logical screen width */
4326	special_modetable[10+0x13] = 80;
4327	/* set 240 lines */
4328	special_modetable[10+0x11] = 0x2c;
4329	special_modetable[10+0x06] = 0x0d;
4330	special_modetable[10+0x07] = 0x3e;
4331	special_modetable[10+0x10] = 0xea;
4332	special_modetable[10+0x11] = 0xac;
4333	special_modetable[10+0x12] = 0xdf;
4334	special_modetable[10+0x15] = 0xe7;
4335	special_modetable[10+0x16] = 0x06;
4336	/* set vertical sync polarity to reflect aspect ratio */
4337	special_modetable[9] = 0xe3;
4338	goto setup_grmode;
4339
4340    case M_BG320:     case M_CG320:     case M_BG640:
4341    case M_CG320_D:   case M_CG640_E:
4342    case M_CG640x350: case M_ENH_CG640:
4343    case M_BG640x480: case M_CG640x480: case M_VGA_CG320:
4344
4345setup_grmode:
4346	set_vgaregs(special_modetable);
4347	scp->font_size = FONT_NONE;
4348	break;
4349
4350    default:
4351	/* call user defined function XXX */
4352	break;
4353    }
4354
4355    /* set border color for this (virtual) console */
4356    set_border(scp->border);
4357    return;
4358}
4359
4360void
4361set_border(u_char color)
4362{
4363    switch (crtc_type) {
4364    case KD_EGA:
4365    case KD_VGA:
4366        inb(crtc_addr + 6);		/* reset flip-flop */
4367        outb(ATC, 0x31); outb(ATC, color);
4368	break;
4369    case KD_CGA:
4370	outb(crtc_addr + 5, color & 0x0f); /* color select register */
4371	break;
4372    case KD_MONO:
4373    case KD_HERCULES:
4374    default:
4375	break;
4376    }
4377}
4378
4379static void
4380set_vgaregs(char *modetable)
4381{
4382    int i, s = splhigh();
4383
4384    outb(TSIDX, 0x00); outb(TSREG, 0x01);   	/* stop sequencer */
4385    for (i=0; i<4; i++) {           		/* program sequencer */
4386	outb(TSIDX, i+1);
4387	outb(TSREG, modetable[i+5]);
4388    }
4389    outb(MISC, modetable[9]);       		/* set dot-clock */
4390    outb(TSIDX, 0x00); outb(TSREG, 0x03);   	/* start sequencer */
4391    outb(crtc_addr, 0x11);
4392    outb(crtc_addr+1, inb(crtc_addr+1) & 0x7F);
4393    for (i=0; i<25; i++) {          		/* program crtc */
4394	outb(crtc_addr, i);
4395	if (i == 14 || i == 15)     		/* no hardware cursor */
4396	    outb(crtc_addr+1, 0xff);
4397	else
4398	    outb(crtc_addr+1, modetable[i+10]);
4399    }
4400    inb(crtc_addr+6);           		/* reset flip-flop */
4401    for (i=0; i<20; i++) {          		/* program attribute ctrl */
4402	outb(ATC, i);
4403	outb(ATC, modetable[i+35]);
4404    }
4405    for (i=0; i<9; i++) {           		/* program graph data ctrl */
4406	outb(GDCIDX, i);
4407	outb(GDCREG, modetable[i+55]);
4408    }
4409    inb(crtc_addr+6);           		/* reset flip-flop */
4410    outb(ATC, 0x20);            		/* enable palette */
4411    splx(s);
4412}
4413
4414static void
4415read_vgaregs(char *buf)
4416{
4417    int i, j;
4418    int s;
4419
4420    bzero(buf, MODE_PARAM_SIZE);
4421
4422    s = splhigh();
4423
4424    outb(TSIDX, 0x00); outb(TSREG, 0x01);   	/* stop sequencer */
4425    for (i=0, j=5; i<4; i++) {
4426	outb(TSIDX, i+1);
4427	buf[j++] = inb(TSREG);
4428    }
4429    buf[9] = inb(MISC + 10);      		/* dot-clock */
4430    outb(TSIDX, 0x00); outb(TSREG, 0x03);   	/* start sequencer */
4431
4432    for (i=0, j=10; i<25; i++) {       		/* crtc */
4433	outb(crtc_addr, i);
4434	buf[j++] = inb(crtc_addr+1);
4435    }
4436    for (i=0, j=35; i<20; i++) {          	/* attribute ctrl */
4437        inb(crtc_addr+6);           		/* reset flip-flop */
4438	outb(ATC, i);
4439	buf[j++] = inb(ATC + 1);
4440    }
4441    for (i=0, j=55; i<9; i++) {           	/* graph data ctrl */
4442	outb(GDCIDX, i);
4443	buf[j++] = inb(GDCREG);
4444    }
4445    inb(crtc_addr+6);           		/* reset flip-flop */
4446    outb(ATC, 0x20);            		/* enable palette */
4447
4448    buf[0] = *(char *)pa_to_va(0x44a);		/* COLS */
4449    buf[1] = *(char *)pa_to_va(0x484);		/* ROWS */
4450    buf[2] = *(char *)pa_to_va(0x485);		/* POINTS */
4451    buf[3] = *(char *)pa_to_va(0x44c);
4452    buf[4] = *(char *)pa_to_va(0x44d);
4453
4454    splx(s);
4455}
4456
4457static int
4458comp_vgaregs(u_char *buf1, u_char *buf2)
4459{
4460    static struct {
4461        u_char mask;
4462    } params[MODE_PARAM_SIZE] = {
4463	0xff, 0x00, 0xff, 		/* COLS, ROWS, POINTS */
4464	0xff, 0xff, 			/* page length */
4465	0xfe, 0xff, 0xff, 0xff,		/* sequencer registers */
4466	0xf3,				/* misc register */
4467	0xff, 0xff, 0xff, 0x7f, 0xff,	/* CRTC */
4468	0xff, 0xff, 0xff, 0x7f, 0xff,
4469	0x00, 0x00, 0x00, 0x00, 0x00,
4470	0x00, 0xff, 0x7f, 0xff, 0xff,
4471	0x7f, 0xff, 0xff, 0xef, 0xff,
4472	0xff, 0xff, 0xff, 0xff, 0xff,	/* attribute controller registers */
4473	0xff, 0xff, 0xff, 0xff, 0xff,
4474	0xff, 0xff, 0xff, 0xff, 0xff,
4475	0xff, 0xff, 0xff, 0xff, 0xf0,
4476	0xff, 0xff, 0xff, 0xff, 0xff,	/* GDC register */
4477	0xff, 0xff, 0xff, 0xff,
4478    };
4479    int identical = TRUE;
4480    int i;
4481
4482    for (i = 0; i < sizeof(params)/sizeof(params[0]); ++i) {
4483	if (params[i].mask == 0)	/* don't care */
4484	    continue;
4485	if ((buf1[i] & params[i].mask) != (buf2[i] & params[i].mask))
4486	    return COMP_DIFFERENT;
4487	if (buf1[i] != buf2[i])
4488	    identical = FALSE;
4489    }
4490    return (identical) ? COMP_IDENTICAL : COMP_SIMILAR;
4491
4492#if 0
4493    for(i = 0; i < 20; ++i) {
4494	if (*buf1++ != *buf2++)
4495	    return COMP_DIFFERENT;
4496    }
4497    buf1 += 2;  /* skip the cursor shape */
4498    buf2 += 2;
4499    for(i = 22; i < 24; ++i) {
4500	if (*buf1++ != *buf2++)
4501	    return COMP_DIFFERENT;
4502    }
4503    buf1 += 2;  /* skip the cursor position */
4504    buf2 += 2;
4505    for(i = 26; i < MODE_PARAM_SIZE; ++i) {
4506	if (*buf1++ != *buf2++)
4507	    return COMP_DIFFERENT;
4508    }
4509    return COMP_IDENTICAL;
4510#endif
4511}
4512
4513static void
4514dump_vgaregs(u_char *buf)
4515{
4516    int i;
4517
4518    for(i = 0; i < MODE_PARAM_SIZE;) {
4519	printf("%02x ", buf[i]);
4520	if ((++i % 16) == 0)
4521	    printf("\n");
4522    }
4523}
4524
4525static void
4526set_font_mode(u_char *buf)
4527{
4528    int s = splhigh();
4529
4530    font_loading_in_progress = TRUE;
4531
4532    /* save register values */
4533    outb(TSIDX, 0x02); buf[0] = inb(TSREG);
4534    outb(TSIDX, 0x04); buf[1] = inb(TSREG);
4535    outb(GDCIDX, 0x04); buf[2] = inb(GDCREG);
4536    outb(GDCIDX, 0x05); buf[3] = inb(GDCREG);
4537    outb(GDCIDX, 0x06); buf[4] = inb(GDCREG);
4538    inb(crtc_addr + 6);
4539    outb(ATC, 0x10); buf[5] = inb(ATC + 1);
4540
4541    /* setup vga for loading fonts */
4542    inb(crtc_addr+6);           		/* reset flip-flop */
4543    outb(ATC, 0x10); outb(ATC, buf[5] & ~0x01);
4544    inb(crtc_addr+6);               		/* reset flip-flop */
4545    outb(ATC, 0x20);            		/* enable palette */
4546
4547#if SLOW_VGA
4548    outb(TSIDX, 0x00); outb(TSREG, 0x01);
4549    outb(TSIDX, 0x02); outb(TSREG, 0x04);
4550    outb(TSIDX, 0x04); outb(TSREG, 0x07);
4551    outb(TSIDX, 0x00); outb(TSREG, 0x03);
4552    outb(GDCIDX, 0x04); outb(GDCREG, 0x02);
4553    outb(GDCIDX, 0x05); outb(GDCREG, 0x00);
4554    outb(GDCIDX, 0x06); outb(GDCREG, 0x04);
4555#else
4556    outw(TSIDX, 0x0100);
4557    outw(TSIDX, 0x0402);
4558    outw(TSIDX, 0x0704);
4559    outw(TSIDX, 0x0300);
4560    outw(GDCIDX, 0x0204);
4561    outw(GDCIDX, 0x0005);
4562    outw(GDCIDX, 0x0406);               /* addr = a0000, 64kb */
4563#endif
4564    splx(s);
4565}
4566
4567static void
4568set_normal_mode(u_char *buf)
4569{
4570    char *modetable;
4571    int s = splhigh();
4572
4573    /* setup vga for normal operation mode again */
4574    inb(crtc_addr+6);           		/* reset flip-flop */
4575    outb(ATC, 0x10); outb(ATC, buf[5]);
4576    inb(crtc_addr+6);               		/* reset flip-flop */
4577    outb(ATC, 0x20);            		/* enable palette */
4578
4579#if SLOW_VGA
4580    outb(TSIDX, 0x00); outb(TSREG, 0x01);
4581    outb(TSIDX, 0x02); outb(TSREG, buf[0]);
4582    outb(TSIDX, 0x04); outb(TSREG, buf[1]);
4583    outb(TSIDX, 0x00); outb(TSREG, 0x03);
4584    outb(GDCIDX, 0x04); outb(GDCREG, buf[2]);
4585    outb(GDCIDX, 0x05); outb(GDCREG, buf[3]);
4586    if (crtc_addr == MONO_BASE) {
4587	outb(GDCIDX, 0x06); outb(GDCREG,(buf[4] & 0x03) | 0x08);
4588    } else {
4589	outb(GDCIDX, 0x06); outb(GDCREG,(buf[4] & 0x03) | 0x0c);
4590    }
4591#else
4592    outw(TSIDX, 0x0100);
4593    outw(TSIDX, 0x0002 | (buf[0] << 8));
4594    outw(TSIDX, 0x0004 | (buf[1] << 8));
4595    outw(TSIDX, 0x0300);
4596    outw(GDCIDX, 0x0004 | (buf[2] << 8));
4597    outw(GDCIDX, 0x0005 | (buf[3] << 8));
4598    if (crtc_addr == MONO_BASE)
4599        outw(GDCIDX, 0x0006 | (((buf[4] & 0x03) | 0x08)<<8));
4600    else
4601        outw(GDCIDX, 0x0006 | (((buf[4] & 0x03) | 0x0c)<<8));
4602#endif
4603
4604    font_loading_in_progress = FALSE;
4605    splx(s);
4606}
4607
4608void
4609copy_font(int operation, int font_type, char* font_image)
4610{
4611    int ch, line, segment, fontsize;
4612    u_char buf[PARAM_BUFSIZE];
4613    u_char val;
4614
4615    switch (font_type) {
4616    default:
4617    case FONT_8:
4618	segment = 0x8000;
4619	fontsize = 8;
4620	break;
4621    case FONT_14:
4622	segment = 0x4000;
4623	fontsize = 14;
4624	break;
4625    case FONT_16:
4626	segment = 0x0000;
4627	fontsize = 16;
4628	break;
4629    }
4630    /*
4631     * FONT KLUDGE
4632     * Always use the font page #0. XXX
4633     */
4634    segment = 0x0000;
4635    outb(TSIDX, 0x01); val = inb(TSREG);        /* disable screen */
4636    outb(TSIDX, 0x01); outb(TSREG, val | 0x20);
4637    set_font_mode(buf);
4638    for (ch=0; ch < 256; ch++)
4639	for (line=0; line < fontsize; line++)
4640	if (operation)
4641	    *(char *)pa_to_va(VIDEOMEM+(segment)+(ch*32)+line) =
4642		    font_image[(ch*fontsize)+line];
4643	else
4644	    font_image[(ch*fontsize)+line] =
4645	    *(char *)pa_to_va(VIDEOMEM+(segment)+(ch*32)+line);
4646    set_normal_mode(buf);
4647    outb(TSIDX, 0x01); outb(TSREG, val & 0xDF); /* enable screen */
4648}
4649
4650static void
4651set_destructive_cursor(scr_stat *scp)
4652{
4653    u_char buf[PARAM_BUFSIZE];
4654    u_char cursor[32];
4655    caddr_t address;
4656    int i;
4657    char *font_buffer;
4658
4659    if (scp->font_size < 14) {
4660	font_buffer = font_8;
4661	address = (caddr_t)VIDEOMEM + 0x8000;
4662    }
4663    else if (scp->font_size >= 16) {
4664	font_buffer = font_16;
4665	address = (caddr_t)VIDEOMEM;
4666    }
4667    else {
4668	font_buffer = font_14;
4669	address = (caddr_t)VIDEOMEM + 0x4000;
4670    }
4671    /*
4672     * FONT KLUDGE
4673     * Always use the font page #0. XXX
4674     */
4675    address = (caddr_t)VIDEOMEM;
4676
4677    if (scp->status & MOUSE_VISIBLE) {
4678	if ((scp->cursor_saveunder & 0xff) == SC_MOUSE_CHAR)
4679    	    bcopy(&scp->mouse_cursor[0], cursor, scp->font_size);
4680	else if ((scp->cursor_saveunder & 0xff) == SC_MOUSE_CHAR + 1)
4681    	    bcopy(&scp->mouse_cursor[32], cursor, scp->font_size);
4682	else if ((scp->cursor_saveunder & 0xff) == SC_MOUSE_CHAR + 2)
4683    	    bcopy(&scp->mouse_cursor[64], cursor, scp->font_size);
4684	else if ((scp->cursor_saveunder & 0xff) == SC_MOUSE_CHAR + 3)
4685    	    bcopy(&scp->mouse_cursor[96], cursor, scp->font_size);
4686	else
4687	    bcopy(font_buffer+((scp->cursor_saveunder & 0xff)*scp->font_size),
4688 	       	   cursor, scp->font_size);
4689    }
4690    else
4691    	bcopy(font_buffer + ((scp->cursor_saveunder & 0xff) * scp->font_size),
4692 	       cursor, scp->font_size);
4693    for (i=0; i<32; i++)
4694	if ((i >= scp->cursor_start && i <= scp->cursor_end) ||
4695	    (scp->cursor_start >= scp->font_size && i == scp->font_size - 1))
4696	    cursor[i] |= 0xff;
4697#if 1
4698    while (!(inb(crtc_addr+6) & 0x08)) /* wait for vertical retrace */ ;
4699#endif
4700    set_font_mode(buf);
4701    generic_bcopy(cursor, (char *)pa_to_va(address) + DEAD_CHAR * 32, 32);
4702    set_normal_mode(buf);
4703}
4704
4705static void
4706set_mouse_pos(scr_stat *scp)
4707{
4708    static int last_xpos = -1, last_ypos = -1;
4709
4710    if (scp->mouse_xpos < 0)
4711	scp->mouse_xpos = 0;
4712    if (scp->mouse_ypos < 0)
4713	scp->mouse_ypos = 0;
4714    if (scp->status & UNKNOWN_MODE) {
4715        if (scp->mouse_xpos > scp->xpixel-1)
4716	    scp->mouse_xpos = scp->xpixel-1;
4717        if (scp->mouse_ypos > scp->ypixel-1)
4718	    scp->mouse_ypos = scp->ypixel-1;
4719	return;
4720    }
4721    if (scp->mouse_xpos > (scp->xsize*8)-1)
4722	scp->mouse_xpos = (scp->xsize*8)-1;
4723    if (scp->mouse_ypos > (scp->ysize*scp->font_size)-1)
4724	scp->mouse_ypos = (scp->ysize*scp->font_size)-1;
4725
4726    if (scp->mouse_xpos != last_xpos || scp->mouse_ypos != last_ypos) {
4727	scp->status |= MOUSE_MOVED;
4728
4729    	scp->mouse_pos = scp->scr_buf +
4730	    ((scp->mouse_ypos/scp->font_size)*scp->xsize + scp->mouse_xpos/8);
4731
4732	if ((scp->status & MOUSE_VISIBLE) && (scp->status & MOUSE_CUTTING))
4733	    mouse_cut(scp);
4734    }
4735}
4736
4737#define isspace(c)	(((c) & 0xff) == ' ')
4738
4739static int
4740skip_spc_right(scr_stat *scp, u_short *p)
4741{
4742    int i;
4743
4744    for (i = (p - scp->scr_buf) % scp->xsize; i < scp->xsize; ++i) {
4745	if (!isspace(*p))
4746	    break;
4747	++p;
4748    }
4749    return i;
4750}
4751
4752static int
4753skip_spc_left(scr_stat *scp, u_short *p)
4754{
4755    int i;
4756
4757    for (i = (p-- - scp->scr_buf) % scp->xsize - 1; i >= 0; --i) {
4758	if (!isspace(*p))
4759	    break;
4760	--p;
4761    }
4762    return i;
4763}
4764
4765static void
4766mouse_cut(scr_stat *scp)
4767{
4768    u_short *end;
4769    u_short *p;
4770    int i = 0;
4771    int j = 0;
4772
4773    scp->mouse_cut_end = (scp->mouse_pos >= scp->mouse_cut_start) ?
4774	scp->mouse_pos + 1 : scp->mouse_pos;
4775    end = (scp->mouse_cut_start > scp->mouse_cut_end) ?
4776	scp->mouse_cut_start : scp->mouse_cut_end;
4777    for (p = (scp->mouse_cut_start > scp->mouse_cut_end) ?
4778	    scp->mouse_cut_end : scp->mouse_cut_start; p < end; ++p) {
4779	cut_buffer[i] = *p & 0xff;
4780	/* remember the position of the last non-space char */
4781	if (!isspace(cut_buffer[i++]))
4782	    j = i;
4783	/* trim trailing blank when crossing lines */
4784	if (((p - scp->scr_buf) % scp->xsize) == (scp->xsize - 1)) {
4785	    cut_buffer[j++] = '\n';
4786	    i = j;
4787	}
4788    }
4789    cut_buffer[i] = '\0';
4790
4791    /* scan towards the end of the last line */
4792    --p;
4793    for (i = (p - scp->scr_buf) % scp->xsize; i < scp->xsize; ++i) {
4794	if (!isspace(*p))
4795	    break;
4796	++p;
4797    }
4798    /* if there is nothing but blank chars, trim them, but mark towards eol */
4799    if (i >= scp->xsize) {
4800	if (scp->mouse_cut_start > scp->mouse_cut_end)
4801	    scp->mouse_cut_start = p;
4802	else
4803	    scp->mouse_cut_end = p;
4804	cut_buffer[j++] = '\n';
4805	cut_buffer[j] = '\0';
4806    }
4807
4808    mark_for_update(scp, scp->mouse_cut_start - scp->scr_buf);
4809    mark_for_update(scp, scp->mouse_cut_end - scp->scr_buf);
4810}
4811
4812static void
4813mouse_cut_start(scr_stat *scp)
4814{
4815    int i;
4816
4817    if (scp->status & MOUSE_VISIBLE) {
4818	if (scp->mouse_pos == scp->mouse_cut_start &&
4819	    scp->mouse_cut_start == scp->mouse_cut_end - 1) {
4820	    cut_buffer[0] = '\0';
4821	    remove_cutmarking(scp);
4822	} else if (skip_spc_right(scp, scp->mouse_pos) >= scp->xsize) {
4823	    /* if the pointer is on trailing blank chars, mark towards eol */
4824	    i = skip_spc_left(scp, scp->mouse_pos) + 1;
4825	    scp->mouse_cut_start = scp->scr_buf +
4826	        ((scp->mouse_pos - scp->scr_buf) / scp->xsize) * scp->xsize + i;
4827	    scp->mouse_cut_end = scp->scr_buf +
4828	        ((scp->mouse_pos - scp->scr_buf) / scp->xsize + 1) * scp->xsize;
4829	    cut_buffer[0] = '\n';
4830	    cut_buffer[1] = '\0';
4831	    scp->status |= MOUSE_CUTTING;
4832	} else {
4833	    scp->mouse_cut_start = scp->mouse_pos;
4834	    scp->mouse_cut_end = scp->mouse_cut_start + 1;
4835	    cut_buffer[0] = *scp->mouse_cut_start & 0xff;
4836	    cut_buffer[1] = '\0';
4837	    scp->status |= MOUSE_CUTTING;
4838	}
4839    	mark_all(scp);
4840	/* delete all other screens cut markings */
4841	for (i=0; i<MAXCONS; i++) {
4842	    if (console[i] == NULL || console[i] == scp)
4843		continue;
4844	    remove_cutmarking(console[i]);
4845	}
4846    }
4847}
4848
4849static void
4850mouse_cut_end(scr_stat *scp)
4851{
4852    if (scp->status & MOUSE_VISIBLE) {
4853	scp->status &= ~MOUSE_CUTTING;
4854    }
4855}
4856
4857static void
4858mouse_cut_word(scr_stat *scp)
4859{
4860    u_short *p;
4861    u_short *sol;
4862    u_short *eol;
4863    int i;
4864
4865    /*
4866     * Because we don't have locale information in the kernel,
4867     * we only distinguish space char and non-space chars.  Punctuation
4868     * chars, symbols and other regular chars are all treated alike.
4869     */
4870    if (scp->status & MOUSE_VISIBLE) {
4871	sol = scp->scr_buf
4872	    + ((scp->mouse_pos - scp->scr_buf) / scp->xsize) * scp->xsize;
4873	eol = sol + scp->xsize;
4874	if (isspace(*scp->mouse_pos)) {
4875	    for (p = scp->mouse_pos; p >= sol; --p)
4876	        if (!isspace(*p))
4877		    break;
4878	    scp->mouse_cut_start = ++p;
4879	    for (p = scp->mouse_pos; p < eol; ++p)
4880	        if (!isspace(*p))
4881		    break;
4882	    scp->mouse_cut_end = p;
4883	} else {
4884	    for (p = scp->mouse_pos; p >= sol; --p)
4885	        if (isspace(*p))
4886		    break;
4887	    scp->mouse_cut_start = ++p;
4888	    for (p = scp->mouse_pos; p < eol; ++p)
4889	        if (isspace(*p))
4890		    break;
4891	    scp->mouse_cut_end = p;
4892	}
4893	for (i = 0, p = scp->mouse_cut_start; p < scp->mouse_cut_end; ++p)
4894	    cut_buffer[i++] = *p & 0xff;
4895	cut_buffer[i] = '\0';
4896	scp->status |= MOUSE_CUTTING;
4897    }
4898}
4899
4900static void
4901mouse_cut_line(scr_stat *scp)
4902{
4903    u_short *p;
4904    int i;
4905
4906    if (scp->status & MOUSE_VISIBLE) {
4907	scp->mouse_cut_start = scp->scr_buf
4908	    + ((scp->mouse_pos - scp->scr_buf) / scp->xsize) * scp->xsize;
4909	scp->mouse_cut_end = scp->mouse_cut_start + scp->xsize;
4910	for (i = 0, p = scp->mouse_cut_start; p < scp->mouse_cut_end; ++p)
4911	    cut_buffer[i++] = *p & 0xff;
4912	cut_buffer[i++] = '\n';
4913	cut_buffer[i] = '\0';
4914	scp->status |= MOUSE_CUTTING;
4915    }
4916}
4917
4918static void
4919mouse_cut_extend(scr_stat *scp)
4920{
4921    if ((scp->status & MOUSE_VISIBLE) && !(scp->status & MOUSE_CUTTING)
4922	&& (scp->mouse_cut_start != NULL)) {
4923	mouse_cut(scp);
4924	scp->status |= MOUSE_CUTTING;
4925    }
4926}
4927
4928static void
4929mouse_paste(scr_stat *scp)
4930{
4931    if (scp->status & MOUSE_VISIBLE) {
4932	struct tty *tp;
4933	u_char *ptr = cut_buffer;
4934
4935	tp = VIRTUAL_TTY(get_scr_num());
4936	while (*ptr)
4937	    (*linesw[tp->t_line].l_rint)(scr_rmap[*ptr++], tp);
4938    }
4939}
4940
4941static void
4942draw_mouse_image(scr_stat *scp)
4943{
4944    caddr_t address;
4945    int i;
4946    char *font_buffer;
4947    u_char buf[PARAM_BUFSIZE];
4948    u_short buffer[32];
4949    u_short xoffset, yoffset;
4950    u_short *crt_pos = Crtat + (scp->mouse_pos - scp->scr_buf);
4951    int font_size = scp->font_size;
4952
4953    if (font_size < 14) {
4954	font_buffer = font_8;
4955	address = (caddr_t)VIDEOMEM + 0x8000;
4956    }
4957    else if (font_size >= 16) {
4958	font_buffer = font_16;
4959	address = (caddr_t)VIDEOMEM;
4960    }
4961    else {
4962	font_buffer = font_14;
4963	address = (caddr_t)VIDEOMEM + 0x4000;
4964    }
4965    /*
4966     * FONT KLUDGE
4967     * Always use the font page #0. XXX
4968     */
4969    address = (caddr_t)VIDEOMEM;
4970
4971    xoffset = scp->mouse_xpos % 8;
4972    yoffset = scp->mouse_ypos % font_size;
4973
4974    /* prepare mousepointer char's bitmaps */
4975    bcopy(font_buffer + ((*(scp->mouse_pos) & 0xff) * font_size),
4976	   &scp->mouse_cursor[0], font_size);
4977    bcopy(font_buffer + ((*(scp->mouse_pos+1) & 0xff) * font_size),
4978	   &scp->mouse_cursor[32], font_size);
4979    bcopy(font_buffer + ((*(scp->mouse_pos+scp->xsize) & 0xff) * font_size),
4980	   &scp->mouse_cursor[64], font_size);
4981    bcopy(font_buffer + ((*(scp->mouse_pos+scp->xsize+1) & 0xff) * font_size),
4982	   &scp->mouse_cursor[96], font_size);
4983    for (i=0; i<font_size; i++) {
4984	buffer[i] = scp->mouse_cursor[i]<<8 | scp->mouse_cursor[i+32];
4985	buffer[i+font_size]=scp->mouse_cursor[i+64]<<8|scp->mouse_cursor[i+96];
4986    }
4987
4988    /* now and-or in the mousepointer image */
4989    for (i=0; i<16; i++) {
4990	buffer[i+yoffset] =
4991	    ( buffer[i+yoffset] & ~(mouse_and_mask[i] >> xoffset))
4992	    | (mouse_or_mask[i] >> xoffset);
4993    }
4994    for (i=0; i<font_size; i++) {
4995	scp->mouse_cursor[i] = (buffer[i] & 0xff00) >> 8;
4996	scp->mouse_cursor[i+32] = buffer[i] & 0xff;
4997	scp->mouse_cursor[i+64] = (buffer[i+font_size] & 0xff00) >> 8;
4998	scp->mouse_cursor[i+96] = buffer[i+font_size] & 0xff;
4999    }
5000
5001    scp->mouse_oldpos = scp->mouse_pos;
5002
5003#if 1
5004    /* wait for vertical retrace to avoid jitter on some videocards */
5005    while (!(inb(crtc_addr+6) & 0x08)) /* idle */ ;
5006#endif
5007    set_font_mode(buf);
5008    generic_bcopy(scp->mouse_cursor, (char *)pa_to_va(address) + SC_MOUSE_CHAR * 32, 128);
5009    set_normal_mode(buf);
5010    *(crt_pos) = (*(scp->mouse_pos) & 0xff00) | SC_MOUSE_CHAR;
5011    *(crt_pos+scp->xsize) =
5012	(*(scp->mouse_pos + scp->xsize) & 0xff00) | (SC_MOUSE_CHAR + 2);
5013    if (scp->mouse_xpos < (scp->xsize-1)*8) {
5014    	*(crt_pos + 1) = (*(scp->mouse_pos + 1) & 0xff00) | (SC_MOUSE_CHAR + 1);
5015    	*(crt_pos+scp->xsize + 1) =
5016	    (*(scp->mouse_pos + scp->xsize + 1) & 0xff00) | (SC_MOUSE_CHAR + 3);
5017    }
5018    mark_for_update(scp, scp->mouse_pos - scp->scr_buf);
5019    mark_for_update(scp, scp->mouse_pos + scp->xsize + 1 - scp->scr_buf);
5020}
5021
5022static void
5023remove_mouse_image(scr_stat *scp)
5024{
5025    u_short *crt_pos = Crtat + (scp->mouse_oldpos - scp->scr_buf);
5026
5027    *(crt_pos) = *(scp->mouse_oldpos);
5028    *(crt_pos+1) = *(scp->mouse_oldpos+1);
5029    *(crt_pos+scp->xsize) = *(scp->mouse_oldpos+scp->xsize);
5030    *(crt_pos+scp->xsize+1) = *(scp->mouse_oldpos+scp->xsize+1);
5031    mark_for_update(scp, scp->mouse_oldpos - scp->scr_buf);
5032    mark_for_update(scp, scp->mouse_oldpos + scp->xsize + 1 - scp->scr_buf);
5033}
5034
5035static void
5036draw_cutmarking(scr_stat *scp)
5037{
5038    u_short *ptr;
5039    u_short och, nch;
5040
5041    for (ptr=scp->scr_buf; ptr<=(scp->scr_buf+(scp->xsize*scp->ysize)); ptr++) {
5042	nch = och = *(Crtat + (ptr - scp->scr_buf));
5043	/* are we outside the selected area ? */
5044	if ( ptr < (scp->mouse_cut_start > scp->mouse_cut_end ?
5045	            scp->mouse_cut_end : scp->mouse_cut_start) ||
5046	     ptr >= (scp->mouse_cut_start > scp->mouse_cut_end ?
5047	            scp->mouse_cut_start : scp->mouse_cut_end)) {
5048	    if (ptr != scp->cursor_pos)
5049		nch = (och & 0xff) | (*ptr & 0xff00);
5050	}
5051	else {
5052	    /* are we clear of the cursor image ? */
5053	    if (ptr != scp->cursor_pos)
5054		nch = (och & 0x88ff) | (*ptr & 0x7000)>>4 | (*ptr & 0x0700)<<4;
5055	    else {
5056		if (flags & CHAR_CURSOR)
5057		    nch = (och & 0x88ff)|(*ptr & 0x7000)>>4|(*ptr & 0x0700)<<4;
5058		else
5059		    if (!(flags & BLINK_CURSOR))
5060		        nch = (och & 0xff) | (*ptr & 0xff00);
5061	    }
5062	}
5063	if (nch != och)
5064	    *(Crtat + (ptr - scp->scr_buf)) = nch;
5065    }
5066}
5067
5068static void
5069remove_cutmarking(scr_stat *scp)
5070{
5071    scp->mouse_cut_start = scp->mouse_cut_end = NULL;
5072    scp->status &= ~MOUSE_CUTTING;
5073    mark_all(scp);
5074}
5075
5076static void
5077save_palette(void)
5078{
5079    int i;
5080
5081    outb(PALRADR, 0x00);
5082    for (i=0x00; i<0x300; i++)
5083	palette[i] = inb(PALDATA);
5084    inb(crtc_addr+6);           /* reset flip/flop */
5085}
5086
5087void
5088load_palette(char *palette)
5089{
5090    int i;
5091
5092    outb(PIXMASK, 0xFF);            /* no pixelmask */
5093    outb(PALWADR, 0x00);
5094    for (i=0x00; i<0x300; i++)
5095	 outb(PALDATA, palette[i]);
5096    inb(crtc_addr+6);           /* reset flip/flop */
5097    outb(ATC, 0x20);            /* enable palette */
5098}
5099
5100static void
5101do_bell(scr_stat *scp, int pitch, int duration)
5102{
5103    if (cold)
5104	return;
5105
5106    if (flags & VISUAL_BELL) {
5107	if (blink_in_progress)
5108	    return;
5109	blink_in_progress = 4;
5110	if (scp != cur_console)
5111	    blink_in_progress += 2;
5112	blink_screen(cur_console);
5113    } else {
5114	if (scp != cur_console)
5115	    pitch *= 2;
5116	sysbeep(pitch, duration);
5117    }
5118}
5119
5120static void
5121blink_screen(void *arg)
5122{
5123    scr_stat *scp = arg;
5124
5125    if ((scp->status & UNKNOWN_MODE) || (blink_in_progress <= 1)) {
5126	blink_in_progress = FALSE;
5127    	mark_all(scp);
5128	if (delayed_next_scr)
5129	    switch_scr(scp, delayed_next_scr - 1);
5130    }
5131    else {
5132	if (blink_in_progress & 1)
5133	    fillw(kernel_default.std_color | scr_map[0x20],
5134		  Crtat, scp->xsize * scp->ysize);
5135	else
5136	    fillw(kernel_default.rev_color | scr_map[0x20],
5137		  Crtat, scp->xsize * scp->ysize);
5138	blink_in_progress--;
5139	timeout(blink_screen, scp, hz / 10);
5140    }
5141}
5142
5143void
5144sc_bcopy(u_short *p, int from, int to, int mark)
5145{
5146    if (!vesa_mode) {
5147	generic_bcopy(p+from, Crtat+from, (to-from+1)*sizeof (u_short));
5148    } else if (vesa_mode == 0x102) {
5149	u_char *d, *e;
5150	int i,j;
5151
5152	if (mark)
5153		mark = 255;
5154	d = (u_char *)Crtat;
5155	d += 10 + 6*16*100 + (from%80) + 16*100*(from/80);
5156	for (i = from ; i <= to ; i++) {
5157	    e = d;
5158	    for (j = 0 ; j < 16; j++) {
5159	        *e = mark^font_16[(p[i]&0xff)*16+j];
5160		e+=100;
5161	    }
5162	    d++;
5163	    if ((i % 80) == 79)
5164		d += 20 + 15*100;
5165	}
5166    }
5167}
5168
5169#ifdef SC_SPLASH_SCREEN
5170static void
5171toggle_splash_screen(scr_stat *scp)
5172{
5173    static int toggle = 0;
5174    static u_char save_mode;
5175    int s;
5176
5177    if (video_mode_ptr == NULL)
5178	return;
5179
5180    s = splhigh();
5181    if (toggle) {
5182	scp->mode = save_mode;
5183	scp->status &= ~UNKNOWN_MODE;
5184	set_mode(scp);
5185	load_palette(palette);
5186	toggle = 0;
5187    }
5188    else {
5189	save_mode = scp->mode;
5190	scp->mode = M_VGA_CG320;
5191	scp->status |= UNKNOWN_MODE;
5192	set_mode(scp);
5193	/* load image */
5194	toggle = 1;
5195    }
5196    splx(s);
5197}
5198#endif
5199#endif /* NSC */
5200