9fans - fans of the OS Plan 9 from Bell Labs
 help / color / mirror / Atom feed
From: Philippe Anel <philippe.anel@noos.fr>
To: 9fans@cse.psu.edu
Subject: [9fans] (no subject)
Date: Sun, 12 Aug 2001 23:38:27 +0200	[thread overview]
Message-ID: <5.1.0.14.0.20010812233754.00a60bf0@pop.wanadoo.fr> (raw)

[-- Attachment #1: Type: text/plain, Size: 1142 bytes --]


Hi everybody out there,

	I took the last week to write a driver for my Matrox G400.
	I'll send another files this week to support the G450.
      	I think it wouldn't take much work to enhance the actual driver so that
	it supports the G200 serie. I'll give it a try once I get hold of this
	card (around the end of august).

	I'm currently working on the 2d accel feature (which isn't supported
	as of yet).
	Though, the source code isn't very clean, and probably needs a complete
	rewrite, It works fairly well on my computer. I'll rewrite it properly
	some time later.
	At now, there only the 8 bits mode which works correctly.
	(Quite a lot of misfeatures in the end :()

	Now, is there any project around regarding the OpenGL support ?, also,
	for the Overlays support ?.

  	Does someone know about a driver beeing under developpment for the Radeon
	video card (ATI). Or if it is already supported.
	Either way, does/will it support 2D acceleration features ?.

  	If none of this exists, I'd gladly start this project myself.
  	I'll welcome any comment regarding this project.

Regards,
  	Philippe Anel,

[-- Attachment #2: vgamga4xx.c --]
[-- Type: text/plain, Size: 5330 bytes --]

/* Philippe Anel : philippe.anel@noos.fr */ 

#include "u.h"
#include "../port/lib.h"
#include "mem.h"
#include "dat.h"
#include "fns.h"
#include "io.h"
#include "../port/error.h"

#define	Image	IMAGE
#include <draw.h>
#include <memdraw.h>
#include <cursor.h>
#include "screen.h"

/*
 * Matrox G400 and G450.
 */

enum {
	/* pci chip manufacturer */
	MATROX		= 0x102B,

	/* agp/pci chip device id */
	MGA4xx		= 0x0525
};

static Pcidev*
mgapcimatch(void)
{
	Pcidev*	p;
	
	p = pcimatch(nil, MATROX, MGA4xx);
	if (0 && p)
		print("MGA 4xx found : rev %d\n", p->rid);
	return p;
}

static ulong
mga4xxlinear(VGAscr* scr, int* size, int* align)
{
	ulong aperture, oaperture;
	int oapsize, wasupamem;
	Pcidev *p;

	oaperture = scr->aperture;
	oapsize = scr->apsize;
	wasupamem = scr->isupamem;

	if(p = mgapcimatch()){
		aperture = p->mem[0].bar & ~0x0F;
		*size = 32*1024*1024;
	}
	else
		aperture = 0;

	if(wasupamem) {
		if(oaperture == aperture)
			return oaperture;
		upafree(oaperture, oapsize);
	}
	scr->isupamem = 0;

	aperture = upamalloc(aperture, *size, *align);
	if(aperture == 0){
		if(wasupamem && upamalloc(oaperture, oapsize, 0)) {
			aperture = oaperture;
			scr->isupamem = 1;
		}
		else
			scr->isupamem = 0;
	}
	else
		scr->isupamem = 1;

	return aperture;
}

static void
mga4xxenable(VGAscr* scr)
{
	Pcidev *	p;
	Physseg 	seg;
	int 		size, align;
	ulong 	aperture;

	/*
	 * Only once, can't be disabled for now.
	 * scr->io holds the virtual address of
	 * the MMIO registers.
	 */
	if(scr->io)
		return;

	p = mgapcimatch();
	if(p == nil)
		return;

	scr->io = upamalloc(p->mem[1].bar & ~0x0F, 16*1024, 0);
	if(scr->io == 0)
		return;

	memset(&seg, 0, sizeof(seg));
	seg.attr = SG_PHYSICAL;
	seg.name = smalloc(NAMELEN);
	snprint(seg.name, NAMELEN, "mga4xxmmio");
	seg.pa = scr->io;
	seg.size = p->mem[1].size;
	addphysseg(&seg);

	scr->io = (ulong)KADDR(scr->io);

	/* need to map frame buffer here too, so vga can find memory size */
	size = 32*1024*1024;
	align = 0;
	aperture = mga4xxlinear(scr, &size, &align);
	if(aperture) {
		scr->aperture = aperture;
		scr->apsize = size;
		memset(&seg, 0, sizeof(seg));
		seg.attr = SG_PHYSICAL;
		seg.name = smalloc(NAMELEN);
		snprint(seg.name, NAMELEN, "mga4xxscreen");
		seg.pa = aperture;
		seg.size = size;
		addphysseg(&seg);
	}
}

enum {
	Index		= 0x00,		/* Index */
	Data		= 0x0A,		/* Data */

	Cxlsb		= 0x0C,		/* Cursor X LSB */
	Cxmsb		= 0x0D,		/* Cursor X MSB */
	Cylsb		= 0x0E,		/* Cursor Y LSB */
	Cymsb		= 0x0F,		/* Cursor Y MSB */

	Icuradrl	= 0x04,		/* Cursor Base Address Low */	
	Icuradrh	= 0x05,		/* Cursor Base Address High */
	Icctl		= 0x06,		/* Indirect Cursor Control */
};

static void
dac4xxdisable(VGAscr* scr)
{
	uchar * dac4xx;
	
	if(scr->io == 0)
		return;

	dac4xx = KADDR(scr->io+0x3C00);
	
	*(dac4xx+Index) = Icctl;
	*(dac4xx+Data) = 0x00;
}

static void
dac4xxload(VGAscr* scr, Cursor* curs)
{
	int x, y;
	uchar *p;
	uchar * dac4xx;

	if(scr->io == 0)
		return;

	dac4xx = KADDR(scr->io+0x3C00);
	
	dac4xxdisable(scr);

	p = KADDR(scr->storage);
	for(y = 0; y < 64; y++){
		*p++ = 0;
		*p++ = 0;
		*p++ = 0;
		*p++ = 0;
		*p++ = 0;
		*p++ = 0;
		if(y <16){
			*p++ = curs->set[1+y*2]|curs->clr[1+2*y];
			*p++ = curs->set[y*2]|curs->clr[2*y];
		} else{
			*p++ = 0;
			*p++ = 0;
		}

		*p++ = 0;
		*p++ = 0;
		*p++ = 0;
		*p++ = 0;
		*p++ = 0;
		*p++ = 0;
		if(y <16){
			*p++ = curs->set[1+y*2];
			*p++ = curs->set[y*2];
		} else{
			*p++ = 0;
			*p++ = 0;
		}
	}
	scr->offset.x = 64 + curs->offset.x;
	scr->offset.y = 64 + curs->offset.y;

	*(dac4xx+Index) = Icctl;
	*(dac4xx+Data) = 0x03;
}

static int
dac4xxmove(VGAscr* scr, Point p)
{
	int 	x, y;
	uchar *	dac4xx;

	if(scr->io == 0)
		return 1;

	dac4xx = KADDR(scr->io + 0x3C00);

	x = p.x + scr->offset.x;
	y = p.y + scr->offset.y;

	*(dac4xx+Cxlsb) = x & 0xFF;
	*(dac4xx+Cxmsb) = (x>>8) & 0x0F;

	*(dac4xx+Cylsb) = y & 0xFF;
	*(dac4xx+Cymsb) = (y>>8) & 0x0F;

	return 0;
}

static void
dac4xxenable(VGAscr* scr)
{
	uchar *	dac4xx;
	ulong	storage;
	
	if(scr->io == 0)
		return;
	dac4xx = KADDR(scr->io+0x3C00);

	dac4xxdisable(scr);

	storage = (32*1024*1024 - 4096) & ~0x3ff;

	*(dac4xx+Index) = Icuradrl;
	*(dac4xx+Data) = 0xff & (storage >> 10);
	*(dac4xx+Index) = Icuradrh;
	*(dac4xx+Data) = 0xff & (storage >> 18);		

	scr->storage = (ulong) KADDR((ulong)scr->aperture + (ulong)storage);

	/* Show X11-Like Cursor */
	*(dac4xx+Index) = Icctl;
	*(dac4xx+Data) = 0x03;

	/* Cursor Color 0 : White */
	*(dac4xx+Index) = 0x08;
	*(dac4xx+Data)  = 0xff;
	*(dac4xx+Index) = 0x09;
	*(dac4xx+Data)  = 0xff;
	*(dac4xx+Index) = 0x0a;
	*(dac4xx+Data)  = 0xff;

	/* Cursor Color 1 : Black */
	*(dac4xx+Index) = 0x0c;
	*(dac4xx+Data)  = 0x00;
	*(dac4xx+Index) = 0x0d;
	*(dac4xx+Data)  = 0x00;
	*(dac4xx+Index) = 0x0e;
	*(dac4xx+Data)  = 0x00;

	/* Cursor Color 2 : Red */
	*(dac4xx+Index) = 0x10;
	*(dac4xx+Data)  = 0xff;
	*(dac4xx+Index) = 0x11;
	*(dac4xx+Data)  = 0x00;
	*(dac4xx+Index) = 0x12;
	*(dac4xx+Data)  = 0x00;

	/*
	 * Load, locate and enable the
	 * 64x64 cursor in 3-colour mode.
	 */
	dac4xxload(scr, &arrow);
	dac4xxmove(scr, ZP);
}

VGAdev vgamga4xxdev = {
	"mga4xx",

	mga4xxenable,		/* enable */
	0,			/* disable */
	0,			/* page */
	mga4xxlinear,		/* linear */
};

VGAcur vgamga4xxcur = {
	"mga4xxhwgc",
	dac4xxenable,
	dac4xxdisable,
	dac4xxload,
	dac4xxmove,
};

[-- Attachment #3: Mga4xx.c --]
[-- Type: text/plain, Size: 24772 bytes --]

/* Philippe Anel : philippe.anel@noos.fr */ 

#include <u.h>
#include <libc.h>
#include <bio.h>

#include "vga.h"
#include "pci.h"

/*
 * Matrox G4xx 3D graphics accelerators
 */
enum {
	Kilo				= 1024,
	Meg				= 1024*1024,
	
	MATROX			= 0x102B,		/* pci chip manufacturer */
	MGA4XX			= 0x0525,		/* pci chip device ids */

	/* Pci configuration space mapping */
	PCfgMgaFBAA		= 0x10,		/* Frame buffer Aperture Address */
	PCfgMgaCAA		= 0x14,		/* Control Aperture Address base */
	PCfgMgaIAA		= 0x18,		/* ILOAD Aperture base Address */
	PCfgMgaOption1	= 0x40,		/* Option Register 1 */
	PCfgMgaOption2	= 0x50,		/* Option Register 2 */
	PCfgMgaOption3	= 0x54,		/* Option Register 3 */
	PCfgMgaDevCtrl	= 0x04,		/* Device Control */

	/* control aperture offsets */
	DMAWIN			= 0x0000,		/* 7KByte Pseudo-DMA Window */

	STATUS0			= 0x1FC2,		/* Input Status 0 */
	STATUS1			= 0x1FDA,	/* Input Status 1 */
	
	SEQIDX			= 0x1FC4,		/* Sequencer Index */
	SEQDATA			= 0x1FC5,		/* Sequencer Data */

	MISC_W			= 0x1FC2,		/* Misc. WO */
	MISC_R			= 0x1FCC,	/* Misc. RO */

	GCTLIDX			= 0x1FCE,		/* Graphic Controler Index */
	GCTLDATA		= 0x1FCF,		/* Graphic Controler Data */

	CRTCIDX			= 0x1FD4,	/* CRTC Index */
	CRTCDATA		= 0x1FD5,	/* CRTC Data */

	CRTCEXTIDX		= 0x1FDE,		/* CRTC Extension Index */
	CRTCEXTDATA		= 0x1FDF,		/* CRTC Extension Data */
	
	RAMDACIDX		= 0x3C00,	/* RAMDAC registers Index */
	RAMDACDATA		= 0x3C0A,	/* RAMDAC Indexed Data */
	RAMDACPALDATA		= 0x3C01,

	ATTRIDX			= 0x1FC0,		/* Attribute Index */
	ATTRDATA		= 0x1FC1,		/* Attribute Data */

	CACHEFLUSH		= 0x1FFF,

	C2_CTL			= 0X3C10,
	MGA_STATUS		= 0X1E14,
	Z_DEPTH_ORG		= 0X1C0C,
	
};

typedef struct {
	Pcidev*	pci;
	int		devid;
	int		revid;
	
	ulong	mmio;
	ulong	mmfb;
	int		fbsize;
	ulong	iload;

	uchar	syspll_m;
	uchar	syspll_n;
	uchar	syspll_p;
	uchar	syspll_s;

	uchar	pixpll_m;
	uchar	pixpll_n;
	uchar	pixpll_p;
	uchar	pixpll_s;

	ulong	option1;
	ulong	option2;
	ulong	option3;

	/* From plan9.ini */
	uchar	sdram;
	uchar	colorkey;
	uchar	maskkey;
	ulong	maxpclk;

	uchar	graphics[9];	
	uchar	attribute[0x14];	
	uchar	sequencer[5];
	uchar	crtc[0x19];
	uchar	crtcext[9];

	ulong	htotal;
	ulong	hdispend;
	ulong	hblkstr;
	ulong	hblkend;
	ulong	hsyncstr;
	ulong	hsyncend;
	ulong	vtotal;
	ulong	vdispend;
	ulong	vblkstr;
	ulong	vblkend;
	ulong	vsyncstr;
	ulong	vsyncend;
	ulong	linecomp;
	ulong	hsyncsel;
	ulong	startadd;
	ulong	offset;
	ulong	maxscan;
	ulong 	curloc;
	ulong	prowscan;
	ulong	currowstr;
	ulong	currowend;
	ulong	curoff;
	ulong	undrow;
	ulong	curskew;
	ulong	conv2t4;
	ulong	interlace;
	ulong	hsyncdel;
	ulong	hdispskew;
	ulong	bytepan;
	ulong	dotclkrt;
	ulong	dword;
	ulong	wbmode;
	ulong	addwrap;
	ulong	selrowscan;
	ulong	cms;
	ulong	csynccen;
	ulong	hrsten;
	ulong	vrsten;
	ulong	vinten;
	ulong	vintclr;
	ulong	hsyncoff;
	ulong	vsyncoff;
	ulong	crtcrstN;
	ulong	mgamode;
	ulong	scale;
	ulong	hiprilvl;
	ulong	maxhipri;
	ulong	c2hiprilvl;
	ulong	c2maxhipri;
	ulong	misc;
	ulong	crtcprotect;
	ulong	winsize;
	ulong	winfreq;
} Mga;


static void
mgawrite32(Mga* mga, int index, ulong val)
{
	((ulong*)mga->mmio)[index] = val;
}

static ulong
mgaread32(Mga* mga, int index)
{
	return ((ulong*)mga->mmio)[index];
}

static void
mgawrite8(Mga* mga, int index, uchar val)
{
	((uchar*)mga->mmio)[index] = val;
}

static uchar
mgaread8(Mga* mga, int index)
{
	return ((uchar*)mga->mmio)[index];
}

static uchar
seqget(Mga* mga, int index)
{
	mgawrite8(mga, SEQIDX, index);
	return mgaread8(mga, SEQDATA);
}

static uchar
seqset(Mga* mga, int index, uchar set, uchar clr)
{
	uchar	tmp;

	mgawrite8(mga, SEQIDX, index);
	tmp = mgaread8(mga, SEQDATA);
	mgawrite8(mga, SEQIDX, index);
	mgawrite8(mga, SEQDATA, (tmp & ~clr) | set);
	return tmp;
}

static uchar
crtcget(Mga* mga, int index)
{
	mgawrite8(mga, CRTCIDX, index);
	return mgaread8(mga, CRTCDATA);
}

static uchar
crtcset(Mga* mga, int index, uchar set, uchar clr)
{
	uchar	tmp;

	mgawrite8(mga, CRTCIDX, index);
	tmp = mgaread8(mga, CRTCDATA);
	mgawrite8(mga, CRTCIDX, index);
	mgawrite8(mga, CRTCDATA, (tmp & ~clr) | set);
	return tmp;
}

static uchar
crtcextget(Mga* mga, int index)
{
	mgawrite8(mga, CRTCEXTIDX, index);
	return mgaread8(mga, CRTCEXTDATA);
}

static uchar
crtcextset(Mga* mga, int index, uchar set, uchar clr)
{
	uchar	tmp;

	mgawrite8(mga, CRTCEXTIDX, index);
	tmp = mgaread8(mga, CRTCEXTDATA);
	mgawrite8(mga, CRTCEXTIDX, index);
	mgawrite8(mga, CRTCEXTDATA, (tmp & ~clr) | set);
	return tmp;
}

static uchar
dacget(Mga* mga, int index)
{
	mgawrite8(mga, RAMDACIDX, index);
	return mgaread8(mga, RAMDACDATA);
}

static uchar
dacset(Mga* mga, int index, uchar set, uchar clr)
{
	uchar	tmp;

	mgawrite8(mga, RAMDACIDX, index);
	tmp = mgaread8(mga, RAMDACDATA);
	mgawrite8(mga, RAMDACIDX, index);
	mgawrite8(mga, RAMDACDATA, (tmp & ~clr) | set);
	return	tmp;
}

static uchar
gctlget(Mga* mga, int index)
{
	mgawrite8(mga, GCTLIDX, index);
	return mgaread8(mga, GCTLDATA);
}

static uchar
gctlset(Mga* mga, int index, uchar set, uchar clr)
{
	uchar	tmp;

	mgawrite8(mga, GCTLIDX, index);
	tmp = mgaread8(mga, GCTLDATA);
	mgawrite8(mga, GCTLIDX, index);
	mgawrite8(mga, GCTLDATA, (tmp & ~clr) | set);
	return	tmp;
}

static uchar
attrget(Mga* mga, int index)
{
	mgawrite8(mga, ATTRIDX, index);
	return mgaread8(mga, ATTRDATA);
}

static uchar
attrset(Mga* mga, int index, uchar set, uchar clr)
{
	uchar	tmp;

	mgawrite8(mga, ATTRIDX, index);
	tmp = mgaread8(mga, ATTRDATA);
	mgawrite8(mga, ATTRIDX, index);
	mgawrite8(mga, ATTRDATA, (tmp & ~clr) | set);
	return	tmp;
}

static uchar
miscget(Mga* mga)
{
	return mgaread8(mga, MISC_R);
}

static uchar
miscset(Mga* mga, uchar set, uchar clr)
{
	uchar	tmp;

	tmp = mgaread8(mga, MISC_R);
	mgawrite8(mga, MISC_W, (tmp & ~clr) | set);
	return	tmp;
}

/* ************************************************************ */

static void
dump_all_regs(Mga* mga)
{
	int	i;

	for (i = 0; i < 25; i++)
		trace("crtc[%d] = 0x%x\n", i, crtcget(mga, i));
	for (i = 0; i < 9; i++)
		trace("crtcext[%d] = 0x%x\n", i, crtcextget(mga, i));
	for (i = 0; i < 5; i++)
		trace("seq[%d] = 0x%x\n", i, seqget(mga, i));
	for (i = 0; i < 9; i++)
		trace("gctl[%d] = 0x%x\n", i, gctlget(mga, i));
	trace("misc = 0x%x\n", mgaread8(mga, MISC_R));
	for (i = 0; i < 0x87; i++)
		trace("dac[%d] = 0x%x\n", i, dacget(mga, i));
}

/* ************************************************************ */

static void
dump(Vga* vga, Ctlr* ctlr)
{
	dump_all_regs(vga->private);
	ctlr->flag |= Fdump;
}

static void
mapmga4xx(Vga* vga, Ctlr* ctlr)
{
	int 		f;
	long 		m;
	Mga *	mga;

	if(vga->private == nil)
		error("%s: g4xxio: no *mga4xx\n", ctlr->name);
	mga = vga->private;

	f = open("#v/vgactl", OWRITE);
	if(f < 0)
		error("%s: can't open vgactl\n", ctlr->name);

	if(write(f, "type mga4xx", 11) != 11)
		error("%s: can't set mga type\n", ctlr->name);
	
	m = segattach(0, "mga4xxmmio", 0, 16*Kilo);
	if(m == -1)
		error("%s: can't attach mga4xxmmio segment\n", ctlr->name);
	mga->mmio = m;
	trace("%s: mmio at 0x%lx\n", ctlr->name, mga->mmio);

	m = segattach(0, "mga4xxscreen", 0, 32*Meg);
	if(m == -1)
		error("%s: can't attach mga4xxscreen segment\n", ctlr->name);
	mga->mmfb = m;
	trace("%s: frame buffer at 0x%lx\n", ctlr->name, mga->mmfb);

	/* TODO : When needed ... map ILOAD too ... */
}

static void
snarf(Vga* vga, Ctlr* ctlr)
{
	int 	i, k, n;
	uchar *	p;
	uchar	x[16];
	Pcidev *	pci;
	Mga *	mga;
	uchar	crtcext3;

	trace("%s->snarf\n", ctlr->name);
	if(vga->private == nil) {
		pci = pcimatch(nil, MATROX, MGA4XX);
		if(pci == nil)
			error("%s: no Pcidev with Vid=0x102B, Did=0x0525\n", ctlr->name);

		trace("%s: G4%d0 rev %d\n", ctlr->name, pci->rid&0x80?5:0, pci->rid&(~0x80));
		i = pcicfgr32(pci, PCfgMgaDevCtrl);
		if ((i & 2) != 2)
			error("%s: Memory Space not enabled ... Aborting ...\n", ctlr->name);	

		vga->private = alloc(sizeof(Mga));
		mga = (Mga*)vga->private;
		mga->devid = 	pci->did;
		mga->revid =	pci->rid;	
		mga->pci = 	pci;

		mapmga4xx(vga, ctlr);
	}
	else {
		mga = (Mga*)vga->private;
	}

	/* Find out how much memory is here, some multiple of 2Meg */

	/* First Set MGA Mode ... */
	crtcext3 = crtcextset(mga, 3, 0x80, 0xff);

	p = (uchar*)mga->mmfb;
	n = 16;
	for (i = 0; i < n; i++) {
		k = (2*i+1)*Meg;
		p[k] = 0;
		p[k] = i+1;
		*((uchar*)(mga->mmio + CACHEFLUSH)) = 0;
		x[i] = p[k];
		trace("x[%d]=%d\n", i, x[i]);
	}
	for(i = 1; i < n; i++)
		if(x[i] != i+1)
			break;
	vga->vmz = mga->fbsize = 2*i*Meg;
	trace("probe found %d megabytes\n", 2*i);

	crtcextset(mga, 3, crtcext3, 0xff);

	ctlr->flag |= Fsnarf;
}

static void
options(Vga* vga, Ctlr* ctlr)
{
	Mode *mode;

	mode = vga->mode;
	if(mode->x % 128){
		mode->x = (mode->x/128)*128;
		sprint(mode->size, "%dx%dx%d", mode->x, mode->y, mode->z);
	}
	ctlr->flag |= Foptions;
}

/*
	calcclock - Calculate the PLL settings (m, n, p, s).
*/
static double
calcclock(Mga* mga, long Fneeded)
{
	double		Fpll;
	double		Fvco;
	double 		Fref;
	int		pixpll_m_min;
	int		pixpll_m_max;
	int		pixpll_n_min;
	int		pixpll_n_max;
	int		pixpll_p_max;
	int		pll_min;
	int		pll_max;
	double 		Ferr, Fcalc;
	int		m, n, p;
		
	/* These values are taken from Matrox G400 Specification - p 4-91 */
	Fref     	= 27000000.0;
	pixpll_n_min 	= 7;
	pixpll_n_max 	= 127;
	pixpll_m_min	= 1;
	pixpll_m_max	= 31;
	pixpll_p_max 	= 7;
	pll_min		= 50000;
	pll_max		= mga->maxpclk;

	if (Fneeded < pll_min)
		error("mga: Too little Frequency %ld : Minimum supported by PLL is %d", 
			Fneeded, pll_min);

	if (Fneeded > pll_max)
		error("mga: Too big Frequency %ld : Maximum supported by PLL is %d",
			Fneeded, pll_max);

	Fvco = ( double ) Fneeded;
	for (p = 0;  p <= pixpll_p_max && Fvco < pll_max; p = p * 2 + 1, Fvco *= 2.0)
		;
	mga->pixpll_p = p;

	Ferr = Fneeded;
	for ( m = pixpll_m_min ; m <= pixpll_m_max ; m++ )
		for ( n = pixpll_n_min; n <= pixpll_n_max; n++ )
		{ 
			Fcalc = Fref * (n + 1) / (m + 1) ;

			/*
			 * Pick the closest frequency.
			 */
			if ( abs(Fcalc - Fvco) < Ferr ) {
				Ferr = abs(Fcalc - Fvco);
				mga->pixpll_m = m;
				mga->pixpll_n = n;
			}
		}
	
	Fvco = Fref * (mga->pixpll_n + 1) / (mga->pixpll_m + 1);

	if ( (50000000.0 <= Fvco) && (Fvco < 110000000.0) )
		mga->pixpll_p |= 0;	
	if ( (110000000.0 <= Fvco) && (Fvco < 170000000.0) )
		mga->pixpll_p |= (1<<3);	
	if ( (170000000.0 <= Fvco) && (Fvco < 240000000.0) )
		mga->pixpll_p |= (2<<3);	
	if ( (240000000.0 <= Fvco) )
		mga->pixpll_p |= (3<<3);	

	Fpll = Fvco / (p + 1);

	return Fpll;
}

static void
init(Vga* vga, Ctlr* ctlr)
{
	Mode*	mode;
	Mga*	mga;
	double	Fpll;
	Ctlr*	c;
	int	i;
	ulong	t;

	mga = vga->private;
	mode = vga->mode;

	trace("mga mmio at %lx\n", mga->mmio);

	ctlr->flag |= Ulinear;

	if ((mode->z != 32) && (mode->z != 8))
		error("depth %d not supported !\n", mode->z);

	if (mode->interlace)
		error("interlaced mode not supported !\n");

	trace("%s: Initializing mode %dx%dx%d on %s\n", ctlr->name, mode->x, mode->y, mode->z, mode->type);
	trace("%s: Suggested Dot Clock : %d\n", 	ctlr->name, mode->frequency);
	trace("%s: Horizontal Total = %d\n", 		ctlr->name, mode->ht);
	trace("%s: Start Horizontal Blank = %d\n", 	ctlr->name, mode->shb);
	trace("%s: End Horizontal Blank = %d\n", 	ctlr->name, mode->ehb);
	trace("%s: Vertical Total = %d\n", 		ctlr->name, mode->vt);
	trace("%s: Vertical Retrace Start = %d\n", 	ctlr->name, mode->vrs);
	trace("%s: Vertical Retrace End = %d\n", 	ctlr->name, mode->vre);
	trace("%s: Start Horizontal Sync = %d\n", 	ctlr->name, mode->shs);
	trace("%s: End Horizontal Sync = %d\n", 	ctlr->name, mode->ehs);
	trace("%s: HSync = %c\n", 			ctlr->name, mode->hsync);
	trace("%s: VSync = %c\n", 			ctlr->name, mode->vsync);
	trace("%s: Interlace = %d\n", 			ctlr->name, mode->interlace);

	mga->maxpclk	= 300000000;

	Fpll = calcclock(mga, mode->frequency);
	trace("Fpll set to %f\n", Fpll);
	trace("pixclks : n = %d m = %d p = %d\n", mga->pixpll_n, mga->pixpll_m, mga->pixpll_p & 0x7);

	trace("PCI Option1 = 0x%x\n", pcicfgr32(mga->pci, PCfgMgaOption1));
	trace("PCI Option2 = 0x%x\n", pcicfgr32(mga->pci, PCfgMgaOption2));
	trace("PCI Option3 = 0x%x\n", pcicfgr32(mga->pci, PCfgMgaOption3));

	mga->htotal =		(mode->ht >> 3) - 5;
	mga->hdispend =		(mode->x >> 3) - 1;
	if (1)
	{
		mga->hblkstr =		mga->hdispend; 		/* (mode->shb >> 3); */
		mga->hblkend =		mga->htotal + 4;	/* (mode->ehb >> 3); */
	} else
	{
		mga->hblkstr =		(mode->shb >> 3);
		mga->hblkend =		(mode->ehb >> 3); 
	}
	mga->hsyncstr =		(mode->shs >> 3);
	mga->hsyncend =		(mode->ehs >> 3);
	mga->hsyncdel = 	0;
	mga->vtotal =		mode->vt - 2;
	mga->vdispend = 	mode->y - 1;
	mga->vblkstr = 		mode->y - 1;
	mga->vblkend = 		mode->vt - 1;
	mga->vsyncstr = 	mode->vrs;
	mga->vsyncend = 	mode->vre;
	mga->linecomp =		mode->y;
	mga->hsyncsel = 	0;	/* Do not double lines ... */
	mga->startadd =		0;
	mga->offset =		(mode->x * mode->z) / 128;
	/* No Zoom */
	mga->maxscan = 		0;
	/* Not used in Power Graphic mode */
	mga->curloc =		0;
	mga->prowscan = 	0;
	mga->currowstr = 	0;
	mga->currowend = 	0;
	mga->curoff = 		1;
	mga->undrow = 		0;
	mga->curskew = 		0;
	mga->conv2t4 = 		0;
	mga->interlace =	0;
	mga->hdispskew =	0;
	mga->bytepan = 		0;
	mga->dotclkrt = 	0;
	mga->dword =		0;
	mga->wbmode =		1;
	mga->addwrap = 		0;	/* Not Used ! */
	mga->selrowscan =	1;
	mga->cms =		1;
	mga->csynccen =		0; 	/* Disable composite sync */

	/* VIDRST Pin */
	mga->hrsten =		1;
	mga->vrsten =		1;

	/* vertical interrupt control */
	mga->vinten = 		1;
	mga->vintclr = 		1;

	/* Let [hv]sync run freely */
	mga->hsyncoff =		0;
	mga->vsyncoff =		0;

	mga->crtcrstN =		1;

	mga->mgamode = 		1;
	mga->scale =		(mode->z == 8) ? 0 : 3;	/* 8 or 32 bits mode */
	
	mga->crtcprotect =	1;
	mga->winsize = 		0;
	mga->winfreq = 		0;

	if ((mga->htotal == 0)
	    || (mga->hblkend <= (mga->hblkstr + 1))
	    || ((mga->htotal - mga->hdispend) == 0)
	    || ((mga->htotal - mga->bytepan + 2) <= mga->hdispend)
	    || (mga->hsyncstr <= (mga->hdispend + 2))
	    || (mga->vtotal == 0))
	{
		error("Invalid Power Graphic Mode :\n"
		      "mga->htotal = %ld\n"
		      "mga->hdispend = %ld\n"
		      "mga->hblkstr = %ld\n"
		      "mga->hblkend = %ld\n"
		      "mga->hsyncstr = %ld\n"
		      "mga->hsyncend = %ld\n"
		      "mga->hsyncdel = %ld\n"
		      "mga->vtotal = %ld\n"
		      "mga->vdispend = %ld\n"
		      "mga->vblkstr = %ld\n"
		      "mga->vblkend = %ld\n"
		      "mga->vsyncstr = %ld\n"
		      "mga->vsyncend = %ld\n"
		      "mga->linecomp = %ld\n",
		      mga->htotal,
		      mga->hdispend,
		      mga->hblkstr,
		      mga->hblkend,
		      mga->hsyncstr,
		      mga->hsyncend,
		      mga->hsyncdel,
		      mga->vtotal,
		      mga->vdispend,
		      mga->vblkstr,
		      mga->vblkend,
		      mga->vsyncstr,
		      mga->vsyncend,
		      mga->linecomp
		      );
	}

	mga->hiprilvl = 0;
	mga->maxhipri = 0;
	mga->c2hiprilvl = 0;
	mga->c2maxhipri = 0;

	mga->misc = ((mode->hsync != '-')?0:(1<<6)) | ((mode->vsync != '-')?0:(1<<7));

	mga->crtc[0x00] = 0xff & mga->htotal;
	mga->crtc[0x01] = 0xff & mga->hdispend;
	mga->crtc[0x02] = 0xff & mga->hblkstr;
	mga->crtc[0x03] = (0x1f & mga->hblkend) 
		| ((0x03 & mga->hdispskew) << 5)
		| 0x80	/* cf 3-304 */
		;
	mga->crtc[0x04] = 0xff & mga->hsyncstr;
	mga->crtc[0x05] = (0x1f & mga->hsyncend) 
		| ((0x03 & mga->hsyncdel) << 5) 
		| ((0x01 & (mga->hblkend >> 5)) << 7)
		;
	mga->crtc[0x06] = 0xff & mga->vtotal;
	t = ((0x01 & (mga->vtotal >> 8)) << 0)
	  | ((0x01 & (mga->vdispend >> 8)) << 1)
	  | ((0x01 & (mga->vsyncstr >> 8)) << 2)
	  | ((0x01 & (mga->vblkstr >> 8)) << 3)
	  | ((0x01 & (mga->linecomp >> 8)) << 4)
	  | ((0x01 & (mga->vtotal >> 9)) << 5)
	  | ((0x01 & (mga->vdispend >> 9)) << 6)
	  | ((0x01 & (mga->vsyncstr >> 9)) << 7)
	  ;
	mga->crtc[0x07] = 0xff & t;
	trace("*************");
	trace("crtc 0x07 = %lx\n", t);
	trace("mga->vtotal = %lx\n", mga->vtotal);
	trace("mga->vdispend = %lx\n", mga->vdispend);
	trace("mga->vsyncstr = %lx\n", mga->vsyncstr);
	trace("mga->vblkstr = %lx\n", mga->vblkstr);
	trace("mga->linecomp = %lx\n", mga->linecomp);
	trace("*************");

	mga->crtc[0x08] = (0x1f & mga->prowscan) 
		| ((0x03 & mga->bytepan) << 5);
	mga->crtc[0x09] = (0x1f & mga->maxscan) 
		| ((0x01 & (mga->vblkstr >> 9)) << 5)
		| ((0x01 & (mga->linecomp >> 9)) << 6)
		| ((0x01 & mga->conv2t4) << 7)
		;
	mga->crtc[0x0a] = (0x1f & mga->currowstr)
		| ((0x01 & mga->curoff) << 5)
		;
	mga->crtc[0x0b] = (0x1f & mga->currowend)
		| ((0x03 & mga->curskew) << 5)
		;
	mga->crtc[0x0c] = 0xff & (mga->startadd >> 8);
	mga->crtc[0x0d] = 0xff & mga->startadd;
	mga->crtc[0x0e] = 0xff & (mga->curloc >> 8);
	mga->crtc[0x0f] = 0xff & mga->curloc;
	mga->crtc[0x10] = 0xff & mga->vsyncstr;
	mga->crtc[0x11] = (0x0f & mga->vsyncend)
		| ((0x01 & mga->vintclr) << 4)
		| ((0x01 & mga->vinten) << 5)
		| ((0x01 & mga->crtcprotect) << 7)
		;
	mga->crtc[0x12] = 0xff & mga->vdispend;
	mga->crtc[0x13] = 0xff & mga->offset;
	mga->crtc[0x14] = 0x1f & mga->undrow;	/* vga only */
	mga->crtc[0x15] = 0xff & mga->vblkstr;
	mga->crtc[0x16] = 0xff & mga->vblkend;
	mga->crtc[0x17] = ((0x01 & mga->cms) << 0)
		| ((0x01 & mga->selrowscan) << 1)
		| ((0x01 & mga->hsyncsel) << 2)
		| ((0x01 & mga->addwrap) << 5)
		| ((0x01 & mga->wbmode) << 6)
		| ((0x01 & mga->crtcrstN) << 7)
		;
	mga->crtc[0x18] = mga->linecomp;
	
	mga->crtcext[0] = (0x0f & (mga->startadd >> 16))
		| ((0x03 & (mga->offset >> 8)) << 4)
		| ((0x01 & (mga->startadd >> 20)) << 6)
		| ((0x01 & mga->interlace) << 7)
		;
	mga->crtcext[1] = ((0x01 & (mga->htotal >> 8)) << 0)
		| ((0x01 & (mga->hblkstr >> 8)) << 1)
		| ((0x01 & (mga->hsyncstr >> 8)) << 2)
		| ((0x01 & mga->hrsten) << 3)
		| ((0x01 & mga->hsyncoff) << 4)
		| ((0x01 & mga->vsyncoff) << 5)
		| ((0x01 & (mga->hblkend >> 6)) << 6)
		| ((0x01 & mga->vrsten) << 7)
		;
	mga->crtcext[2] = ((0x03 & (mga->vtotal >> 10)) << 0)
		| ((0x01 & (mga->vdispend >> 10)) << 2)
		| ((0x03 & (mga->vblkstr >> 10)) << 3)
		| ((0x03 & (mga->vsyncstr >> 10)) << 5)
		| ((0x01 & (mga->linecomp >> 10)) << 7)
		;
	mga->crtcext[3] = ((0x07 & mga->scale) << 0)
		| ((0x01 & mga->csynccen) << 6)
		| ((0x01 & mga->mgamode) << 7)
		;
	mga->crtcext[4] = 0;	/* memory page ... not used in Power Graphic Mode */
	mga->crtcext[5] = 0;	/* Not used in interlaced mode */
	mga->crtcext[6] = ((0x07 & mga->hiprilvl) << 0)
		| ((0x07 & mga->maxhipri) << 4)
		;
	mga->crtcext[7] = ((0x07 & mga->winsize) << 1)
		| ((0x07 & mga->winfreq) << 5)
		;
	mga->crtcext[8] = (0x01 & (mga->startadd >> 21)) << 0;

	/* Initialize Sequencer */
	mga->sequencer[0] = 0;
	mga->sequencer[1] = 0;
	mga->sequencer[2] = 0x03;
	mga->sequencer[3] = 0;
	mga->sequencer[4] = 0x02;

	/* Graphic Control registers are ignored when not using 0xA0000 aperture */	
	for (i = 0; i < 9; i++)
		mga->graphics[i] = 0;	

	/* The Attribute Controler is not available in Power Graphics mode */
	for (i = 0; i < 0x15; i++)
		mga->attribute[i] = i;	

	/* disable vga load (want to do fields in different order) */
	for(c = vga->link; c; c = c->link)
		if (strncmp(c->name, "vga", 3) == 0)
			c->load = nil;
}

enum
{
	Seq_ClockingMode =	1,
		Dotmode =	(1<<0),
		Shftldrt =	(1<<2),
		Dotclkrt =	(1<<3),
		Shiftfour =	(1<<4),
		Scroff =	(1<<5),

	CrtcExt_Horizontcount =	1,
		Htotal =	(1<<0),
		Hblkstr =	(1<<1),
		Hsyncstr =	(1<<2),
		Hrsten =	(1<<3),
		Hsyncoff =	(1<<4),
		Vsyncoff =	(1<<5),
		Hblkend =	(1<<6),
		Vrsten =	(1<<7),

	CrtcExt_Miscellaneous =	3,
		Mgamode =	(1<<7),

	Dac_Xpixclkctrl =	0x1a,
		Pixclksl = 		(3<<0),
		Pixclkdis =	(1<<2),
		Pixpllpdn =	(1<<3),

	Dac_Xpixpllstat =	0x4f,
		Pixlock = 		(1<<6),
	
	Dac_Xpixpllan =		0x45,
	Dac_Xpixpllbn =		0x49,
	Dac_Xpixpllcn =		0x4d,

	Dac_Xpixpllam =		0x44, 
	Dac_Xpixpllbm =		0x48,
	Dac_Xpixpllcm =		0x4c,

	Dac_Xpixpllap =		0x46,
	Dac_Xpixpllbp =		0x4a,
	Dac_Xpixpllcp =		0x4e,

	Dac_Xmulctrl =		0x19,
		ColorDepth =	(7<<0),
			_8bitsPerPixel = 	0,
			_15bitsPerPixel =	1,
			_16bitsPerPixel =	2,
			_24bitsPerPixel =	3,
			_32bitsPerPixelWithOv = 4,
			_32bitsPerPixel	=	7,

	Dac_Xpanelmode =	0x1f,

	Dac_Xmiscctrl =		0x1e,
		Dacpdn =	(1<<0),
		Mfcsel =	(3<<1),
		Vga8dac =	(1<<3),
		Ramcs =		(1<<4),
		Vdoutsel =	(7<<5),

	Dac_Xcurctrl =		0x06,
		CursorDis = 	0,
		Cursor3Color = 	1,
		CursorXGA = 	2,
		CursorX11 = 	3,
		Cursor16Color = 4,

	Dac_Xzoomctrl =		0x38,

	Misc_loaddsel =		(1<<0),
	Misc_rammapen =		(1<<1),
	Misc_clksel =		(3<<2),
	Misc_videodis =		(1<<4),
	Misc_hpgoddev = 	(1<<5),
	Misc_hsyncpol =		(1<<6),
	Misc_vsyncpol =		(1<<7),
};

static void
load(Vga* vga, Ctlr* ctlr)
{
	Mga*	mga;
	int	i;
	uchar*	p;
	Mode*	mode;
	uchar	cursor;

	mga = vga->private;
	mode = vga->mode;

	trace("mga: Loading ...\n");
	dump_all_regs(mga);

	trace("mga mmio at %lx\n", mga->mmio);


	trace("mga: loading vga registers ...\n" );

	/* Initialize Sequencer registers */
	for(i = 0; i < 5; i++)
		seqset(mga, i, mga->sequencer[i], 0xff);

	/* Initialize Attribute register */
	for(i = 0; i < 0x15; i++)
		attrset(mga, i, mga->attribute[i], 0xff);

	/* Initialize Graphic Control registers */
	for(i = 0; i < 9; i++)
		gctlset(mga, i, mga->graphics[i], 0xff);

	/* Wait VSYNC */
	while (mgaread8(mga, STATUS1) & 0x08);
	while (! (mgaread8(mga, STATUS1) & ~0x08));

	/* Turn off the video. */
	seqset(mga, Seq_ClockingMode, Scroff, 0);

	/* Crtc2 Off */
	mgawrite32(mga, C2_CTL, 0);

	/* Disable Cursor */
	cursor = dacset(mga, Dac_Xcurctrl, CursorDis, 0xff);

	/* Pixel Pll UP and set Pixel clock source to Pixel Clock PLL */
	dacset(mga, Dac_Xpixclkctrl, 0x01 | 0x08, 0x0f);

	trace("mga: waiting for the clock source becomes stable ...\n");
	while ((dacget(mga, Dac_Xpixpllstat) & Pixlock) != Pixlock)
		;
	trace("mga: pixpll locked !\n");

	/* Enable LUT, Disable MAFC */
	dacset(mga, Dac_Xmiscctrl, Ramcs | Mfcsel, Vdoutsel);

	/* Initialize Z Buffer ... (useful?) */
	mgawrite32(mga, Z_DEPTH_ORG, 0);

	/* Disable Dac */
	dacset(mga, Dac_Xmiscctrl, 0, Dacpdn);

	/* Initialize Panel Mode */
	dacset(mga, Dac_Xpanelmode, 0, 0xff);

	/* Disable the PIXCLK and set Pixel clock source to Pixel Clock PLL */
	dacset(mga, Dac_Xpixclkctrl, Pixclkdis | 0x01, 0x3);

	/* Disable mapping of the memory */ 
	miscset(mga, 0, Misc_rammapen);

	/* Enable 8 bit palette */
	dacset(mga, Dac_Xmiscctrl, Vga8dac, 0);

	/* Select MGA Pixel Clock */
	miscset(mga, Misc_clksel, 0);

	/* Wait */
	for (i = 0; i < 50; i++)
		mgaread32(mga, MGA_STATUS);

	/* Reprogram the desired PLL registers */
	dacset(mga, Dac_Xpixpllcm, mga->pixpll_m, 0xff);
	dacset(mga, Dac_Xpixpllcn, mga->pixpll_n, 0xff);
	dacset(mga, Dac_Xpixpllcp, mga->pixpll_p, 0xff);
	
	/* Wait until new clock becomes stable */
	trace("mga: waiting for the clock source becomes stable ...\n");
	while ((dacget(mga, Dac_Xpixpllstat) & Pixlock) != Pixlock)
		;
	trace("mga: pixpll locked !\n");

	/* Enable Pixel Clock Oscillation */
	dacset(mga, Dac_Xpixclkctrl, 0, Pixclkdis);

	/* Enable Dac */
	dacset(mga, Dac_Xmiscctrl, Dacpdn, 0);

	/* Set Video Mode */
	if (mode->z != 8)
		dacset(mga, Dac_Xmulctrl, _32bitsPerPixel, ColorDepth);	/* 32 bits mode ... */
	else
		dacset(mga, Dac_Xmulctrl, _8bitsPerPixel, ColorDepth);	/* 8 bits mode ... */

	/* Wait */
	for (i = 0; i < 50; i++)
		mgaread32(mga, MGA_STATUS);

	/* Set Video Mode */
	if (mode->z != 8)
		dacset(mga, Dac_Xmulctrl, _32bitsPerPixel, ColorDepth);	/* 32 bits mode ... */
	else
		dacset(mga, Dac_Xmulctrl, _8bitsPerPixel, ColorDepth);	/* 8 bits mode ... */

	/* Wait until new clock becomes stable */
	trace("mga: waiting for the clock source becomes stable ...\n");
	while ((dacget(mga, Dac_Xpixpllstat) & Pixlock) != Pixlock)
		;
	trace("mga: pixpll locked !\n");

	/* Initialize CRTC registers and remove irq */
	crtcset(mga, 0x11, (1<<4), (1<<5)|0x80);
	for (i = 0; i < 25; i++)
		crtcset(mga, i, mga->crtc[i], 0xff);

	/* Initialize CRTC Extension registers */
	for (i = 0; i < 9; i++)
		crtcextset(mga, i, mga->crtcext[i], 0xff);

	/* Initialize Palette */
	mgawrite8(mga, RAMDACIDX, 0);
	for (i = 0; i < 0xff; i++)
		mgawrite8(mga, RAMDACPALDATA, i);

	/* Disable Zoom */
	dacset(mga, Dac_Xzoomctrl, 0, 0xff);

	/* Enable mga mode again ... Just in case :) */
	crtcextset(mga, CrtcExt_Miscellaneous, Mgamode, 0);

	/* Set final misc ... enable mapping ... */
	miscset(mga, mga->misc | Misc_rammapen, 0);

	/* Enable Screen */
	seqset(mga, 1, 0, 0xff);

	p = (uchar*)mga->mmfb;
	for (i = 0; i < mga->fbsize; i++)
		*p++ = (0xff & i);

	trace("mga: Loaded !\n" );
	dump_all_regs(mga);

	trace("mga: Loaded [bis]!\n" );

	/* Reenable Cursor */
	dacset(mga, Dac_Xcurctrl, cursor, 0xff);

	ctlr->flag |= Fload;
}

Ctlr mga4xx = {
	"mga4xx",			/* name */
	snarf,				/* snarf */
	options,				/* options */
	init,					/* init */
	load,					/* load */
	dump,				/* dump */
};

Ctlr mga4xxhwgc = {
	"mga4xxhwgc",		/* name */
	0,					/* snarf */
	0,					/* options */
	0,					/* init */
	0,					/* load */
	dump,				/* dump */
};

             reply	other threads:[~2001-08-12 21:38 UTC|newest]

Thread overview: 433+ messages / expand[flat|nested]  mbox.gz  Atom feed  top
2001-08-12 21:38 Philippe Anel [this message]
2001-08-13  7:45 ` andrey mirtchovski
2001-08-14  9:44   ` Ralph Corderoy
  -- strict thread matches above, loose matches on Subject: below --
2018-04-02 15:27 Steve Simon
2018-04-02 21:08 ` Digby R.S. Tarvin
2018-01-04 20:11 Steve Simon
2018-01-04 20:22 ` Lyndon Nerenberg
2018-01-04 21:20   ` Steve Simon
2018-01-04 22:27     ` Joseph Stewart
2018-01-04 23:22       ` Rob Pike
2018-01-04 23:37 ` Greg Lewin
2017-08-30 14:12 Steve Simon
2017-08-30 16:36 ` Steven Stallion
2016-12-02 11:44 Steve Simon
2016-12-02 19:12 ` Bakul Shah
2016-07-29  0:01 kokamoto
2014-11-25  4:20 trebol
2014-07-31  5:18 kokamoto
2014-07-05  0:38 kokamoto
2014-06-21 19:45 Steve Simon
2014-06-21 23:39 ` cinap_lenrek
2014-06-22  6:54   ` Steve Simon
2014-04-16  1:52 sl
2014-04-16  9:39 ` Ingo Krabbe
2014-04-15 14:41 Steve Simon
2014-04-15 15:36 ` Anthony Sorace
2014-04-15 18:18   ` sl
2014-04-15 22:42     ` erik quanstrom
2014-04-15 23:40       ` arisawa
2014-04-16  1:20     ` Anthony Sorace
2014-04-15 15:50 ` erik quanstrom
2014-04-15 17:46   ` Aram Hăvărneanu
2014-04-15 17:53     ` erik quanstrom
2014-03-19 18:44 Jacob Todd
2014-03-15 23:07 Steve Simon
2014-03-15 23:26 ` Jacob Todd
2014-03-16 14:51   ` erik quanstrom
2014-03-16  1:51 ` Jeff Sickel
2013-11-17 23:04 Steve Simon
2013-06-03 15:43 sl
2013-04-30 15:56 lucio
2013-04-30 17:11 ` erik quanstrom
2012-10-19  9:46 Sophit4
2012-09-03 11:16 yaroslav
2012-09-03 11:40 ` Charles Forsyth
2012-04-11  9:38 陈俊秀
2011-12-30 18:08 erik quanstrom, erik quanstrom
2011-12-30 18:49 ` Jack Norton
2011-12-30 19:24   ` erik quanstrom
2011-12-30 20:35 ` Aram Hăvărneanu
2011-12-30 21:28   ` Bakul Shah
2011-12-30 21:34     ` Charles Forsyth
2011-12-30 21:38       ` Aram Hăvărneanu
2011-12-30 21:53       ` Bakul Shah
2011-12-30 21:56         ` Aram Hăvărneanu
2011-12-30 22:41           ` Charles Forsyth
2011-12-30 23:00             ` Lyndon Nerenberg
     [not found] ` <CAEAzY38puVSzEnn90mmi+Bq4hnL9WpbBsnysjJYvXYw3xvE=xA@mail.gmail.c>
2011-12-30 21:05   ` erik quanstrom
2011-12-30 21:39     ` Jack Norton
2011-12-31  5:31       ` erik quanstrom
2011-12-31 17:40         ` Aram Hăvărneanu
     [not found]         ` <CAEAzY39S9z6mKtun68DGFbEkA6y8kaqTEyDCkW6ydHK8aHFG5A@mail.gmail.c>
2011-12-31 19:32           ` erik quanstrom
2012-01-05 18:03             ` Aram Hăvărneanu
2011-11-22 18:32 Steve Simon
2011-08-09 12:40 Steve Simon
2011-08-09 12:54 ` erik quanstrom
2011-08-09 13:07   ` Steve Simon
2011-08-09 14:52     ` erik quanstrom
2011-08-09 18:21     ` Lyndon Nerenberg (VE6BBM/VE7TFX)
2011-08-09 18:31       ` Steve Simon
2011-08-09 14:12 ` Russ Cox
2011-04-06  9:09 Stanley Lieber
2011-04-25  7:42 ` Steve Simon
2011-04-25 13:11   ` erik quanstrom
     [not found] <96cc26fe3002748983b3fc16cc949bab@quintile.net>
2011-03-28 13:56 ` erik quanstrom
2011-03-28 14:50   ` cinap_lenrek at gmx.de
2011-03-28 15:18     ` ron minnich
2011-03-28 22:57       ` erik quanstrom
2010-12-21  3:43 erik quanstrom, erik quanstrom
2010-05-06 19:55 erik quanstrom
2010-03-08  4:22 lucio
2010-03-08  4:49 ` ron minnich
2010-03-08  4:58   ` lucio
2010-03-08  6:17     ` Russ Cox
2010-03-08  6:22       ` lucio
2010-03-08 15:13     ` Patrick Kelly
2010-03-08 15:57       ` Francisco J Ballesteros
2010-03-08  8:54 ` Richard Miller
2010-03-08  9:31   ` lucio
2010-03-08 22:53 ` Sascha Retzki
2010-03-08 18:01   ` lucio
2010-03-08 19:20     ` Lyndon Nerenberg (VE6BBM/VE7TFX)
2010-03-09  4:20       ` lucio
2010-03-09  5:26         ` Lyndon Nerenberg (VE6BBM/VE7TFX)
2010-03-09  5:32           ` erik quanstrom
2010-03-09  5:50             ` Lyndon Nerenberg (VE6BBM/VE7TFX)
2010-03-09 20:08               ` Patrick Kelly
2010-03-08 19:41     ` erik quanstrom
2010-03-08 22:19     ` James Tomaschke
2010-03-09  4:34       ` lucio
     [not found] <mailman.26991.1268008023.1512.9fans@9fans.net>
2010-03-08  0:54 ` - Choc -
2010-03-07 17:47 lucio
2010-03-07 18:37 ` John Floren
2010-03-07 19:16   ` lucio
2010-03-07 19:57     ` erik quanstrom
2010-03-08  4:29       ` lucio
2010-03-06  9:32 [9fans] nb—search and index notes in files by keyword Peter A. Cejchan
2010-03-07  4:30 ` [9fans] (no subject) lucio
2010-03-07  5:05   ` Anthony Sorace
2010-03-07 17:31     ` ron minnich
2010-03-07 17:43       ` erik quanstrom
2010-03-07 18:14         ` lucio
2010-03-07 19:25           ` cinap_lenrek
2010-03-07 17:42     ` lucio
2010-03-07 17:53       ` erik quanstrom
2010-03-07 18:06         ` lucio
2010-03-07 18:59       ` Iruata Souza
2010-03-07 19:26         ` lucio
2010-03-07 19:36           ` ron minnich
2010-03-07  9:14   ` Skip Tavakkolian
2010-03-07 11:04     ` lucio
2010-02-05  1:53 erik quanstrom
2010-01-18 21:55 erik quanstrom
2009-09-29 23:25 [9fans] acme without a heavy grid (SFW) Jason Catena
2009-10-01 16:49 ` J.R. Mauro
2009-10-01 17:18   ` [9fans] (no subject) Pablo Alonso Salas Alvarez
2009-09-15 22:34 erik quanstrom
2009-07-24 17:18 erik quanstrom
2009-07-24 17:20 ` erik quanstrom
2009-07-24 16:14 [9fans] Does "as little software as possible" include a modern maht
2009-07-24 17:16 ` [9fans] (no subject) erik quanstrom
2009-07-17 21:09 drivers
2009-05-28 11:08 Gregory Pavelcak
2009-04-23 11:38 Steve Simon
2009-04-23 12:34 ` Charles Forsyth
2009-04-23 13:07   ` Devon H. O'Dell
2009-04-23 17:13   ` lucio
2009-04-23 17:17     ` erik quanstrom
2009-04-23 17:28       ` David Leimbach
2009-04-23 19:32 ` lucio
2009-04-27  4:42 ` lucio
2009-04-27 11:57   ` lucio
2009-04-27 21:30   ` Steve Simon
2009-02-24  0:29 mattmobile
2009-02-24  0:48 ` ron minnich
2009-02-24  1:02   ` Jeff Sickel
2009-02-24  1:25     ` sixforty
2009-02-24  2:13       ` Anthony Sorace
2009-02-23  0:13 [9fans] actionfs mattmobile
2009-03-05 13:16 ` [9fans] (no subject) cej
2009-01-02  2:30 erik quanstrom
2008-12-06 19:28 Dave Eckhardt
2008-12-06 23:42 ` Roman Shaposhnik
2008-12-07  0:04   ` erik quanstrom
2008-11-21 18:28 erik quanstrom
2008-11-21 21:33 ` Kenji Arisawa
2008-11-21 22:55   ` erik quanstrom
2008-08-14 19:09 akumar
2008-08-14 19:14 ` andrey mirtchovski
2008-07-19  2:37 [9fans] 9vx and local file systems Russ Cox
2008-07-21 13:26 ` [9fans] (no subject) kokamoto
2008-07-21 14:45   ` a
2008-03-19  5:03 Skip Tavakkolian
2008-03-19 12:41 ` erik quanstrom
2008-03-19 17:16   ` Lyndon Nerenberg
2007-12-14 23:02 Joshua Wood
2007-11-15 20:00 erik quanstrom
2007-08-24  1:54 YAMANASHI Takeshi
2007-08-24  2:04 ` erik quanstrom
2007-07-08 12:37 Gregory Pavelcak
2007-07-08 14:08 ` erik quanstrom
2007-07-08 14:50   ` erik quanstrom
2007-07-12 20:57     ` erik quanstrom
2007-05-25 23:29 ozan s. yigit
2007-05-25 23:42 ` Charles Forsyth
2007-05-26  0:09   ` ozan s. yigit
2007-05-28 12:36   ` Lluís Batlle
2007-05-11  6:57 Lyndon Nerenberg
2007-05-08 23:02 Steve Simon
2007-04-13 22:16 devon.odell
2007-04-14 11:17 ` W B Hacker
2007-01-15 23:24 steve
2006-12-12 21:20 Steve Simon
2006-12-10 13:49 sape
2006-09-13  7:28 Aw: " chuckf
2006-09-13  7:55 ` Sascha Retzki
2006-09-12 20:44 Chuck Foreman
2006-09-12 20:47 ` David Hendricks
2006-09-12 20:55 ` Federico Benavento
2006-09-02 11:16 lucio
2006-09-02 17:49 ` Gorka guardiola
2006-09-02 18:38   ` Gorka guardiola
2006-09-03  5:46     ` geoff
2006-09-03 10:51       ` Álvaro Jurado Cuevas
2006-08-21 12:43 Steve Simon
2006-08-22 17:56 ` Sergey Zhilkin
2006-04-21  4:09 Rafeek Raja
2006-02-10 15:30 quanstro
2006-02-10 14:10 quanstro
2006-02-10 15:17 ` jmk
2006-02-07 17:09 Riza Dindir
2005-09-09 18:46 Fco. J. Ballesteros
2005-08-07 22:24 Steve Simon
2005-08-08 13:25 ` Sape Mullender
2005-05-31  3:53 焕宇 苏
2005-05-30 19:01 quanstro
2005-02-10 15:28 tapique
2005-02-11 18:12 ` Bruce Ellis
2004-12-14 20:33 Charles Forsyth
2004-12-14 21:02 ` Bruce Ellis
2004-12-14 21:19 ` Ronald G. Minnich
2004-12-14 21:33   ` boyd, rounin
2004-12-14 21:38   ` Charles Forsyth
2004-12-14 22:01     ` Ronald G. Minnich
2004-12-14 22:12       ` andrey mirtchovski
2004-12-14 22:25         ` Ronald G. Minnich
2004-12-14 22:16       ` Charles Forsyth
2004-12-14 22:26         ` Ronald G. Minnich
2004-12-14 22:26           ` boyd, rounin
2004-12-14 22:36             ` jim
2004-12-14 22:48               ` Dan Cross
2004-12-14 22:47                 ` boyd, rounin
2004-12-14 23:00                 ` jim
2004-12-14 23:07                   ` boyd, rounin
2004-12-14 23:27                   ` Dan Cross
2004-12-14 22:50               ` Brantley Coile
2004-12-14 23:08                 ` jim
2004-12-14 23:12                   ` Brantley Coile
2004-12-14 22:55               ` andrey mirtchovski
2004-12-14 23:35               ` Ronald G. Minnich
2004-12-14 23:35                 ` boyd, rounin
2004-12-14 23:41                 ` andrey mirtchovski
2004-12-01 10:57 Steve Simon
2004-12-01 11:03 ` Tiit Lankots
2004-12-01 18:37 ` Jack Johnson
2004-12-01 18:47   ` Christopher Nielsen
2004-11-09 13:28 cej
2004-07-28  2:10 YAMANASHI Takeshi
2004-07-27  9:08 Steve Simon
2004-07-27  9:38 ` Kenji Okamoto
2004-07-27  9:44   ` Lucio De Re
2004-07-27 10:54   ` Steve Simon
2004-07-27 13:36     ` Boris Maryshev
2004-07-27 15:23       ` Justin Herald
2004-07-27 19:55     ` Francisco Ballesteros
2004-07-27 20:22     ` Skip Tavakkolian
2004-07-28  4:08     ` Dan Cross
2004-07-28  4:39       ` Justin Herald
2004-07-26 17:59 steve
2004-07-26 17:48 The Post Office
2004-07-26 17:30 join-jibjab
2004-07-26 17:18 melinda.proost
2004-07-26 16:58 Mail Delivery Subsystem
2004-07-26 16:21 swe
2004-07-26 16:06 library
2004-07-26 15:59 justin.jaffe
2004-07-26 15:44 The Post Office
2004-07-26 15:25 andrewm
2004-07-26 15:20 Automatic Email Delivery Software
2004-07-26 15:14 newswire
2004-07-19  8:17 judge
2004-07-16 11:38 Chris
2004-07-15  3:46 Michelle
2004-07-13 15:19 Fco. J. Ballesteros
2004-07-09 17:25 Steven
2004-07-07  1:49 Pam Moran
2004-07-03 22:23 Joseph
2004-07-02 12:05 Don
2004-06-28 12:49 Steve Simon
2004-06-22 20:43 Pete
2004-05-17 15:50 matt lawless
2004-05-18  8:31 ` john grove
2004-05-19  8:31 ` john grove
2004-04-19  8:29 Steve Simon
2004-04-13 11:54 matt
2004-04-13 21:25 ` Geoff Collyer
2004-04-13 21:28   ` boyd, rounin
2004-03-23 16:12 David Presotto
2004-03-04 17:57 David Presotto
2004-03-04 18:12 ` Charles Forsyth
2004-03-04 18:21   ` Dave Lukes
2004-03-04 18:29     ` Charles Forsyth
2004-03-04 22:21     ` boyd, rounin
2004-02-22 20:07 Russ Cox
2004-02-17 14:26 David Presotto
2004-02-17 16:13 ` Rob Pike
2004-02-17 16:17   ` David Presotto
2004-02-17 16:29     ` Rob Pike
2004-02-18  3:52   ` boyd, rounin
2004-02-17 21:25 ` C H Forsyth
2004-02-17 23:57 ` Charles Forsyth
2004-02-18  0:03   ` David Presotto
2004-02-18  6:58   ` 9nut
2004-02-18 16:56   ` rog
2004-02-01  0:34 sam
2004-01-30 18:10 engineering
2004-01-27 12:47 ravi
2004-01-22 15:22 Sape Mullender
2003-12-11 21:38 David Presotto
2003-11-25 15:18 Steve Simon
2003-11-02 21:12 andrey mirtchovski
2003-11-02 21:29 ` David Presotto
2003-10-19 14:22 David Presotto
2003-10-16 13:13 David Presotto
2003-10-14 12:11 David Presotto
2003-10-14 14:40 ` a
2003-10-14 15:43   ` Dan Cross
2003-10-12  0:43 matt
2003-10-11 23:43 ` David Presotto
2003-10-12  0:52   ` matt
2003-10-09 16:46 David Presotto
2003-10-09 16:52 ` Richard Miller
2003-09-25 14:24 steve.simon
2003-09-24  0:11 matt
2003-09-24  0:15 ` matt
2003-09-24  0:11 matt
2003-09-16  1:16 David Presotto
2003-09-16  7:38 ` Charles Forsyth
2003-09-01 23:47 matt
2003-09-01 19:14 ` David Presotto
2003-09-01 19:24   ` Skip Tavakkolian
2003-09-02  0:42   ` boyd, rounin
2003-09-01 14:08 David Presotto
2003-08-31 23:46 David Presotto
2003-07-26 16:11 David Presotto
2003-07-23 15:34 Vincenzo Volpe
2003-07-23 16:36 ` jmk
2003-07-26  0:46   ` David Presotto
2003-08-01  9:02     ` Vincenzo Volpe
2003-08-01 17:53       ` David Presotto
2003-06-21 19:15 David Presotto
2003-06-19 13:57 David Presotto
2003-06-19 14:16 ` boyd, rounin
2003-05-10  5:24 Andrew Simmons
2003-04-21 17:54 bigfoot
2003-04-21 18:12 ` David Presotto
2003-04-21 19:06   ` Russ Cox
2003-04-21 19:08     ` rsc
2003-04-25 10:40     ` vic zandy
2003-04-19 13:02 David Presotto
2003-02-25 12:40 Steve Simon
2003-02-24 16:52 Steve Simon
2003-02-24 16:06 ` Wayne Walker
2003-02-24 17:18   ` William Josephson
2003-02-24 19:37 ` northern snowfall
2003-02-24 13:49 David Presotto
2003-02-24 15:11 ` Sam
     [not found] <2ba8f07c025d45604e247b27a02d4123@plan9.bell-labs.com>
2003-02-23  6:14 ` Leendert van Doorn
2003-02-17 15:30 Steve Simon
2003-02-14 16:19 Steve Simon
2003-02-12 15:41 David Presotto
2003-02-12 15:37 David Presotto
2003-02-12 15:34 David Presotto
2003-02-10 17:20 Steve Simon
2003-02-10 18:26 ` Russ Cox
2002-12-03  9:02 Ian Dichkovsky
2002-12-01 20:33 bwc
2002-12-01 17:38 Skip Tavakkolian
2002-12-01 15:46 presotto
2002-11-19 20:04 presotto
2002-11-19 19:36 bwc
2002-11-19 19:50 ` George Michaelson
2002-11-19  1:44 bwc
2002-11-18 21:40 bwc
2002-11-18 21:39 bwc
2002-11-18 21:39 bwc
2002-10-17  3:49 rob pike, esq.
2002-09-30 23:48 Adrian L. Thiele
2002-09-19 17:54 Sape Mullender
     [not found] <20020814092910.8DBA973C99@wintermute.cse.psu.edu>
     [not found] ` <3D5AC220.F7A7ED77@null.net>
2002-08-15  9:55   ` matt
2002-08-15 16:24   ` Ronald G Minnich
2002-08-15 17:08   ` Dennis Davis
2002-07-19  0:59 presotto
2002-07-16 19:21 presotto
2002-07-03 13:17 presotto
2002-06-10 19:10 Russ Cox
2002-04-12 17:43 Russ Cox
2002-04-12 17:20 /dev/null
2002-03-12  1:04 markp
2002-03-12  9:42 ` Thomas Bushnell, BSG
2002-03-13 10:04   ` bs
2002-03-11 18:33 Russ Cox
2002-03-12  9:42 ` Thomas Bushnell, BSG
2002-03-11 16:28 bwc
2002-03-11 16:24 bwc
2002-03-11 15:57 presotto
2002-03-11 17:51 ` Thomas Bushnell, BSG
2002-03-12  9:42   ` ozan s yigit
2002-03-11 19:51 ` Sam Ducksworth
2002-03-11 19:53 ` Andrew Simmons
2002-03-12 11:05 ` Anthony Mandic
2002-03-13 10:05 ` Douglas A. Gwyn
2002-02-28 11:26 sape
2002-03-04  6:51 ` Sean Quinlan
2002-02-27 22:47 presotto
2002-02-27 17:57 stanv
2001-12-13 14:35 presotto
2001-12-13 15:10 ` Ronald G Minnich
2001-12-13 15:47 ` Lucio De Re
2001-12-11 18:27 bwc
2001-12-11 18:17 Russ Cox
2001-12-11 18:17 bwc
2001-12-11 16:24 Russ Cox
2001-12-11 16:33 ` Boyd Roberts
2001-12-09 14:48 rob pike
2001-12-11 10:07 ` Douglas A. Gwyn
2001-12-11 11:55   ` Boyd Roberts
2001-12-12  9:47     ` Douglas A. Gwyn
2002-01-02 10:04       ` John R. Strohm
2002-01-03  9:52         ` Douglas A. Gwyn
2001-12-12  9:48   ` Thomas Bushnell, BSG
2001-12-12 11:14     ` Boyd Roberts
2001-12-09  8:22 arisawa
2001-11-30 14:14 steve.simon
2001-11-30 14:30 ` Boyd Roberts
2001-11-01 21:27 presotto
2001-11-01 21:26 presotto
2001-10-26 18:10 presotto
2001-10-26 14:45 peh
2001-09-07 13:48 Peter Bosch
2001-09-05  7:25 Fco.J.Ballesteros
2001-09-04 13:30 Fco.J.Ballesteros
2001-09-04 20:51 ` Martin Harriss
2001-09-04 12:08 geoff
2001-08-14 11:10 Usenet News system
2001-08-05 14:02 jmk
2001-05-20  1:41 rob pike
2001-05-20  6:31 ` Dan Cross
2001-05-20 12:40   ` Donald Brownlee
2001-05-20 13:16     ` Boyd Roberts
2001-05-20 19:38     ` Dan Cross
2001-05-20 19:57       ` Richard Elberger
2001-05-21  4:56         ` Jonathan Sergent
2001-04-09 14:52 presotto
2001-04-09 13:47 forsyth
2001-04-09 13:26 presotto
2001-03-30 15:56 presotto
2001-03-22 15:09 Gorka Guardiola Muzquiz
2001-03-06 14:44 presotto
2000-11-29  8:03 Russ Cox

Reply instructions:

You may reply publicly to this message via plain-text email
using any one of the following methods:

* Save the following mbox file, import it into your mail client,
  and reply-to-all from there: mbox

  Avoid top-posting and favor interleaved quoting:
  https://en.wikipedia.org/wiki/Posting_style#Interleaved_style

* Reply using the --to, --cc, and --in-reply-to
  switches of git-send-email(1):

  git send-email \
    --in-reply-to=5.1.0.14.0.20010812233754.00a60bf0@pop.wanadoo.fr \
    --to=philippe.anel@noos.fr \
    --cc=9fans@cse.psu.edu \
    /path/to/YOUR_REPLY

  https://kernel.org/pub/software/scm/git/docs/git-send-email.html

* If your mail client supports setting the In-Reply-To header
  via mailto: links, try the mailto: link
Be sure your reply has a Subject: header at the top and a blank line before the message body.
This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for NNTP newsgroup(s).