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