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