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