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