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