xref: /csrg-svn/sys/tahoe/vba/mpreg.h (revision 32632)
1*32632Ssam /*	mpreg.h	1.1	87/11/17	*/
2*32632Ssam 
3*32632Ssam /*
4*32632Ssam  * MPCC Asynchronous Communications Interface.
5*32632Ssam  */
6*32632Ssam #define MPINTRBASE	0xa0		/* base vector for interupts */
7*32632Ssam #define MPMAGIC		1969		/* magic number for mblok */
8*32632Ssam #define MPMAXPORT	32		/* maximum number of ports on an MPCC */
9*32632Ssam 
10*32632Ssam /*
11*32632Ssam  * MPCC's are capable of supporting one of a
12*32632Ssam  * the protocols listed below.  This driver
13*32632Ssam  * supports only the async terminal protocol.
14*32632Ssam  */
15*32632Ssam #define MPPROTO_UNUSED	0	/* port not in use */
16*32632Ssam #define MPPROTO_ASYNC	1	/* async protocol */
17*32632Ssam #define MPPROTO_X25	2	/* x25 protocol (unsupported) */
18*32632Ssam #define MPPROTO_BISYNC	3	/* bisync protocol (unsupported) */
19*32632Ssam #define MPPROTO_SNA  	4	/* sna protocol (unsupported) */
20*32632Ssam 
21*32632Ssam #define NMPPROTO	5	/* max protocols supported by MPCC */
22*32632Ssam 
23*32632Ssam #define MPINSET        8
24*32632Ssam #define MPOUTSET       8
25*32632Ssam 
26*32632Ssam /*
27*32632Ssam  * Host Interface Structure
28*32632Ssam  */
29*32632Ssam struct his {
30*32632Ssam 	u_char	semaphore;
31*32632Ssam #define MPSEMA_AVAILABLE	1
32*32632Ssam #define MPSEMA_WORK		4
33*32632Ssam 	u_char	imok;
34*32632Ssam #define MPIMOK_ALIVE	0x01
35*32632Ssam #define MPIMOK_DEAD	0x80
36*32632Ssam 	u_char	brdnum;		/* Virtual brd number for protocol */
37*32632Ssam 	u_char	unused;
38*32632Ssam 	struct {
39*32632Ssam 		char	inbdone[MPMAXPORT];	/* Ports w/ inbound completed */
40*32632Ssam 		char	outbdone[MPMAXPORT];	/* Ports w/ outbound available */
41*32632Ssam 		u_int	fill[2];
42*32632Ssam 	} proto[NMPPROTO];
43*32632Ssam };
44*32632Ssam 
45*32632Ssam #define MPPORT_EOL	-1		/* end of port list */
46*32632Ssam 
47*32632Ssam /*
48*32632Ssam  * Async host transmit list structure.
49*32632Ssam  */
50*32632Ssam #define MPXMIT	4	/* # of transmit ptrs/MP_WRITE event */
51*32632Ssam 
52*32632Ssam struct	hxmtl {
53*32632Ssam 	caddr_t	dblock[MPXMIT];	/* ptrs to data blocks */
54*32632Ssam 	u_short	size[MPXMIT];	/* size of each block */
55*32632Ssam };
56*32632Ssam 
57*32632Ssam /*
58*32632Ssam  * MPCC asynchronous protocol events.
59*32632Ssam  */
60*32632Ssam struct mpevent {
61*32632Ssam 	u_char	ev_status;	/* Go Status */
62*32632Ssam 	u_char	ev_cmd;		/* Optional Op-code */
63*32632Ssam 	u_short	ev_opts;	/* Optional flags */
64*32632Ssam 	u_short	ev_error;	/* error status returned */
65*32632Ssam 	u_short	ev_flags;	/* optional event flags field */
66*32632Ssam 	caddr_t	ev_params;	/* pointer to event parameters */
67*32632Ssam 	union {
68*32632Ssam 		struct	hxmtl *hxl;	/* pointer to host xmit list */
69*32632Ssam 		u_char	*rcvblk;	/* pointer to receive block */
70*32632Ssam 	} ev_un;
71*32632Ssam 	u_short	ev_count;	/* # ptrs in xmit list/# receive chars  */
72*32632Ssam 	u_short	ev_unused;	/* round to longword */
73*32632Ssam 	u_int	ev_unused2;	/* round to size of BSC struct. GROT!! */
74*32632Ssam };
75*32632Ssam 
76*32632Ssam /* defines for ev_status */
77*32632Ssam #define EVSTATUS_FREE	0
78*32632Ssam #define EVSTATUS_GO	1
79*32632Ssam #define EVSTATUS_BUSY	2
80*32632Ssam #define EVSTATUS_DONE	4
81*32632Ssam 
82*32632Ssam /* defines for ev_cmd */
83*32632Ssam #define EVCMD_OPEN	1
84*32632Ssam #define EVCMD_CLOSE	2
85*32632Ssam #define EVCMD_RESET	3
86*32632Ssam #define EVCMD_IOCTL	4
87*32632Ssam #define EVCMD_WRITE	5
88*32632Ssam #define EVCMD_READ	6
89*32632Ssam #define EVCMD_STATUS	7
90*32632Ssam #define EVCMD_EVENT	8
91*32632Ssam 
92*32632Ssam /*
93*32632Ssam  * Host-MPCC interface block.
94*32632Ssam  */
95*32632Ssam struct	mblok {
96*32632Ssam 	u_char	mb_status;		/* mpcc status */
97*32632Ssam 	u_char	mb_ivec;		/* host interrupt vector */
98*32632Ssam 	u_short	mb_magic;
99*32632Ssam 	u_char	mb_diagswitch[2];	/* run diagnostics/application */
100*32632Ssam 	u_char	mb_softerr;		/* soft error code */
101*32632Ssam 	u_char	mb_harderr;		/* hard error code */
102*32632Ssam 	struct mpdl {		/* download/config area */
103*32632Ssam 		u_char	mpdl_status;	/* control/status */
104*32632Ssam 		u_char	mpdl_cmd;	/* request type */
105*32632Ssam 		u_short	mpdl_count;	/* size of parameter block */
106*32632Ssam 		caddr_t	mpdl_data;	/* command parameters */
107*32632Ssam 	} mb_dl;
108*32632Ssam 	u_char	mb_hiport, mb_loport;	/* high-low mpcc port numbers */
109*32632Ssam 	u_char	mb_unit;		/* mpcc unit number */
110*32632Ssam 	u_char	mb_hndshk;		/* handshaking timer */
111*32632Ssam 	caddr_t	mb_imokclk;		/* handshaking clock */
112*32632Ssam 	u_char	mb_nointcnt;		/* no interrupt from handshake */
113*32632Ssam 	u_char	mb_mpintcnt;		/* # outstanding interupts to MPCC */
114*32632Ssam 	short	mb_unused;
115*32632Ssam 	caddr_t	mb_mpintclk;		/* MPCC interrupt clock */
116*32632Ssam 	struct	his mb_hostint;		/* To Talk with Host */
117*32632Ssam 	u_char	mb_proto[MPMAXPORT];	/* per-port protocols */
118*32632Ssam 	u_char	mb_intr[MPMAXPORT];	/* per-port host->mpcc int flags */
119*32632Ssam 	struct	mpport {	/* per-port structure */
120*32632Ssam 		u_short	mp_proto;	/* protocol of port */
121*32632Ssam 		u_char	mp_on;		/* Next available entry on Host */
122*32632Ssam 		u_char	mp_off;		/* Next expected 'DONE' entry on Host */
123*32632Ssam 		struct	mpevent mp_recvq[MPINSET]; /* queue of events to host */
124*32632Ssam 		struct	mpevent mp_sendq[MPOUTSET];/* queue of events to mpcc */
125*32632Ssam 		u_char	mp_nextrcv;	/* next expected 'DONE' entry on Host */
126*32632Ssam 		u_char	mp_flags;	/* host flags */
127*32632Ssam 		short	mp_unused;
128*32632Ssam 		caddr_t	mp_data;	/* pointer to data for port */
129*32632Ssam 	} mb_port[MPMAXPORT];
130*32632Ssam };
131*32632Ssam 
132*32632Ssam /* status defines for mblok.status */
133*32632Ssam #define MP_DLPEND	1
134*32632Ssam #define MP_DLOPEN	2
135*32632Ssam #define MP_DLDONE	3
136*32632Ssam #define MP_OPCLOSE	4
137*32632Ssam #define MP_OPOPEN	5
138*32632Ssam #define MP_DLTIME	6
139*32632Ssam #define MP_DLERROR	(-1)
140*32632Ssam 
141*32632Ssam /* hard error status values loaded into mblock.herr */
142*32632Ssam #define NOHERR		0	/* no error */
143*32632Ssam #define MPBUSERR	1	/* bus error */
144*32632Ssam #define ADDRERR		2	/* address error */
145*32632Ssam #define UNDECC		3	/* undefined ecc interrupt */
146*32632Ssam #define UNDINT		4	/* undefined interrupt */
147*32632Ssam #define PWRFL		5	/* power fail occurred */
148*32632Ssam #define NOXENTRY	6	/* xdone was enterred w/o xmit entry on queue */
149*32632Ssam #define TWOFTMRS	7	/* tried to start two fast timers on one port */
150*32632Ssam #define INTQFULL	8	/* interupt queue full */
151*32632Ssam #define INTQERR		9	/* interupt queue ack error */
152*32632Ssam #define CBPERR		10	/* uncorrectable DMA parity error */
153*32632Ssam #define ACPDEAD		11	/* acap has died */
154*32632Ssam /* additional panic codes not listed */
155*32632Ssam 
156*32632Ssam /* soft error status values loaded into mblock.serr */
157*32632Ssam #define NOSERR	0		/* no error */
158*32632Ssam #define DMAPERR	1		/* dma parity error */
159*32632Ssam #define ECCERR	2		/* local memory ecc error */
160*32632Ssam 
161*32632Ssam /* Defines for flags */
162*32632Ssam #define MP_PROGRESS	1	/* Open or Close is in progress */
163*32632Ssam #define MP_PORTUP	2	/* link is up for port */
164*32632Ssam #define MP_REMBSY	4	/* remote station busy */
165*32632Ssam 
166*32632Ssam /*
167*32632Ssam  * Asynchronous Terminal Protocol Definitions.
168*32632Ssam  */
169*32632Ssam #define A_RCVTIM	2	/* default max tix for receive event (~20ms) */
170*32632Ssam #define ACPTMR		300	/* approx. 5 secs to wait for acap     */
171*32632Ssam #define A_MAXEVTP	3	/* maximum # of L1 or Host Events to    */
172*32632Ssam 				/* process per port at one time	 */
173*32632Ssam #define A_MAXRCV	128	/* max # of chars in rcv event - enough */
174*32632Ssam 				/* to hold 20ms of chars at 19.2KB      */
175*32632Ssam #define A_NUMRCV	32	/* number of rcv buffers per port       */
176*32632Ssam #define A_NUMXMT	2	/* max number of concurrent xmits/port  */
177*32632Ssam #define A_NUMEVT	32	/* number of evt bufs for status evts   */
178*32632Ssam 				/* and L2 to L1 transmit evts	   */
179*32632Ssam #define WR5	5		/* SCC Write Reg 5		      */
180*32632Ssam #define TXENBL	0x08		/* mask to enable transmitter in WR 5   */
181*32632Ssam #define RTSON	0x02		/* mask to turn on RTS in wreg 5	*/
182*32632Ssam #define CHR5MSK	0x1F		/* mask for 5-bit transmit data	 */
183*32632Ssam 
184*32632Ssam /*
185*32632Ssam  * macro to adjust a circular buffer ptr
186*32632Ssam  *      x  = pointer or index
187*32632Ssam  *      sz = size of circular buffer
188*32632Ssam  */
189*32632Ssam #define adjptr(x,sz)	((x) = ((++(x) == (sz)) ? 0 : (x)))
190*32632Ssam #define adjptrbk(x,sz)	((x) = ((x) == 0) ? (sz) : --(x))
191*32632Ssam 
192*32632Ssam /*
193*32632Ssam  * Events from ASYNC Level 1 to Level 2
194*32632Ssam  */
195*32632Ssam #define RCVDTA	10	/* normal receive data available */
196*32632Ssam #define PARERR	11	/* receive data with parity error */
197*32632Ssam #define OVRNERR	12	/* receive data with overrun error */
198*32632Ssam #define OVFERR	13	/* receive data with overflow error */
199*32632Ssam #define FRAMERR	14	/* receive data with framing error */
200*32632Ssam #define ACKXMT	15	/* successful completion of transmit */
201*32632Ssam #define NORBUF	16	/* No Receive Buffers available	 */
202*32632Ssam #define NOEBUF	17	/* No Event Buffers available */
203*32632Ssam #define BRKASRT	18	/* Break condition detected */
204*32632Ssam 
205*32632Ssam /* defines for error conditions */
206*32632Ssam #define A_OK		0	/* No Errors */
207*32632Ssam #define A_INVEVT	1	/* Invalid Event Error */
208*32632Ssam #define A_IOCERR	2	/* Error while configuring port */
209*32632Ssam #define A_SIZERR	3	/* Error in count of data chars to xmt */
210*32632Ssam #define A_NXBERR	4	/* Transmit Incomplete due to lack of bufs */
211*32632Ssam 
212*32632Ssam /*
213*32632Ssam  * Modem control signal control structure.
214*32632Ssam  */
215*32632Ssam struct mdmctl {
216*32632Ssam         u_char	mc_rngdsr;	/* ring or dsr */
217*32632Ssam         u_char	mc_rts;		/* request to send */
218*32632Ssam         u_char	mc_rate;
219*32632Ssam         u_char	mc_dcd;		/* data carrier detect */
220*32632Ssam         u_char	mc_sectx;	/* secondary transmit */
221*32632Ssam         u_char	mc_cts;		/* clear to send */
222*32632Ssam         u_char	mc_secrx;	/* secondary receive */
223*32632Ssam         u_char	mc_dtr;		/* data terminal ready */
224*32632Ssam };
225*32632Ssam 
226*32632Ssam /* defines for modem control lines */
227*32632Ssam #define ASSERT	1		/* line asserted */
228*32632Ssam #define DROP	2		/* line dropped */
229*32632Ssam #define AUTO	3		/* auto mode enabled, rts only */
230*32632Ssam 
231*32632Ssam /*
232*32632Ssam  * Async parameter structure.
233*32632Ssam  */
234*32632Ssam struct asyncparam {
235*32632Ssam 	u_char	ap_xon, ap_xoff;	/* xon-xoff characters */
236*32632Ssam 	u_char	ap_xena;		/* xon/xoff enabled */
237*32632Ssam 	u_char	ap_xany;		/* any received char enables xmitter */
238*32632Ssam 	struct	mdmctl ap_modem;	/* port modem control lines */
239*32632Ssam 	struct	mdmctl ap_intena;	/* modem signals which generate */
240*32632Ssam 					/* status change events */
241*32632Ssam 	u_char	ap_data;		/* number of data bits */
242*32632Ssam 	u_char	ap_stop;		/* number of stop bits */
243*32632Ssam 	u_char	ap_baud;		/* baud rate */
244*32632Ssam 	u_char	ap_parity;		/* even/odd/no parity */
245*32632Ssam 	u_char	ap_loop;		/* enable for local loopback */
246*32632Ssam 	u_char	ap_rtimer;		/* receive timer value (msec) */
247*32632Ssam 	short	ap_fill;		/* round to longword */
248*32632Ssam };
249*32632Ssam 
250*32632Ssam /* enable/disable signal codes */
251*32632Ssam #define MPA_ENA	1		/* condition enabled */
252*32632Ssam #define MPA_DIS	2		/* condition disabled */
253*32632Ssam 
254*32632Ssam /* defines for ap_data */
255*32632Ssam #define MPCHAR_5	0	/* 5 bits per character */
256*32632Ssam #define MPCHAR_6	2	/* 6 bits per character */
257*32632Ssam #define MPCHAR_7	1	/* 7 bits per character */
258*32632Ssam #define MPCHAR_8 	3	/* 8 bits per character */
259*32632Ssam 
260*32632Ssam /* defines for ap_stop */
261*32632Ssam #define MPSTOP_1	1	/* 1 stop bit per character */
262*32632Ssam #define MPSTOP_1_5	2	/* 1 1/2 stop bits per character */
263*32632Ssam #define MPSTOP_2	3	/* 2 stop bits per character */
264*32632Ssam 
265*32632Ssam /* defines for ap_baud */
266*32632Ssam #define MODEM	0
267*32632Ssam #define M0	0		/* baud rate = 0 */
268*32632Ssam #define M50	1		/* baud rate = 50 */
269*32632Ssam #define M75	2		/* baud rate = 75 */
270*32632Ssam #define M110	3		/* baud rate = 110 */
271*32632Ssam #define M134_5	4		/* baud rate = 134.5 */
272*32632Ssam #define M150	5		/* baud rate = 150 */
273*32632Ssam #define M200	6		/* baud rate = 200 */
274*32632Ssam #define M300	7		/* baud rate = 300 */
275*32632Ssam #define M600	8		/* baud rate = 600 */
276*32632Ssam #define M1200	9		/* baud rate = 1200 */
277*32632Ssam #define M1800	10		/* baud rate = 1800 */
278*32632Ssam #define M2400	11		/* baud rate = 2400 */
279*32632Ssam #define M4800	12		/* baud rate = 4800 */
280*32632Ssam #define M9600	13		/* baud rate = 9600 */
281*32632Ssam #define MEXTA	14		/* baud rate = Ext A */
282*32632Ssam #define MEXTB	15		/* baud rate = Ext B */
283*32632Ssam #define M2000	16		/* baud rate = 2000 */
284*32632Ssam #define M3600	17		/* baud rate = 3600 */
285*32632Ssam #define M7200	18		/* baud rate = 7200 */
286*32632Ssam #define M19200	19		/* baud rate = 19,200 */
287*32632Ssam #define M24000	20		/* baud rate = 24,000 */
288*32632Ssam #define M28400	21		/* baud rate = 28,400 */
289*32632Ssam #define M37800	22		/* baud rate = 37,800 */
290*32632Ssam #define M40300	23		/* baud rate = 40,300 */
291*32632Ssam #define M48000	24		/* baud rate = 48,000 */
292*32632Ssam #define M52000	25		/* baud rate = 52,000 */
293*32632Ssam #define M56800	26		/* baud rate = 56,800 */
294*32632Ssam 
295*32632Ssam /* defines for ap_parity */
296*32632Ssam #define MPPAR_NONE	0	/* no parity */
297*32632Ssam #define MPPAR_ODD	1	/* odd parity */
298*32632Ssam #define MPPAR_EVEN	3	/* even parity */
299*32632Ssam 
300*32632Ssam /* possible flags for Host MP_IOCTL Events */
301*32632Ssam #define A_CHGX		1	/* IOCTL is only chging xonxoff params */
302*32632Ssam #define A_MDMCHG	2	/* change modem control lines */
303*32632Ssam #define A_MDMGET	3	/* get current state of modem ctl lines */
304*32632Ssam #define A_CHGL1P	4	/* IOCTL is changing changing L1 params */
305*32632Ssam #define A_BRKON		5	/* set port break bit */
306*32632Ssam #define A_BRKOFF	6	/* clear port break bit */
307*32632Ssam #define A_CHGALL	7	/* IOCTL is changing xonxoff params, */
308*32632Ssam 				/* pcnfg struct, & modem ctl structs */
309*32632Ssam #define A_DISABX	8	/* disable port transmitter (ctl-s) */
310*32632Ssam #define A_ENABLX	9	/* enable port transmitter (ctl-q) */
311*32632Ssam 
312*32632Ssam /* possible flags for Host MP_WRITE Events */
313*32632Ssam #define A_FLUSH		1	/* flush any queued transmit events */
314*32632Ssam #define A_SSTOP		2	/* transmit a port stop (xoff) char */
315*32632Ssam 				/* before sending rest of event xmts */
316*32632Ssam #define A_SSTART	3	/* transmit a port start (xon) char */
317*32632Ssam 				/* before sending rest of event xmts */
318*32632Ssam 
319*32632Ssam /* possible flags for Outbound MP_READ Events */
320*32632Ssam #define A_XOFF		1	/* transmitter stopped from by xoff char */
321*32632Ssam 
322*32632Ssam /* Perpos flags for modem control fields */
323*32632Ssam #define A_RNGDSR	00001
324*32632Ssam #define A_RTS		00002
325*32632Ssam #define A_RATE		00004
326*32632Ssam #define A_DCD		00010
327*32632Ssam #define A_SECTX		00020
328*32632Ssam #define A_CTS		00040
329*32632Ssam #define A_SECRX		00100
330*32632Ssam #define A_DTR		00200
331*32632Ssam 
332*32632Ssam /* error messages printed at console , board & port # filled in later */
333*32632Ssam #define A_INVSTS	"\n#### Invalid Status Event "
334*32632Ssam #define A_INVCMD	"\n#### Invalid Event From the MPCC "
335*32632Ssam #define A_NORBUF	"\n#### No More Available Receive Buffers "
336*32632Ssam #define A_NOEBUF	"\n#### No More Available Event Buffers "
337*32632Ssam #define A_OVRN		"\n#### Overrun Error Detected "
338*32632Ssam #define A_OVRF		"\n#### Overflow Error Detected "
339*32632Ssam #define A_NOXBUF	"\n#### No More Available Transmit Event Buffers "
340*32632Ssam #define A_XSIZE		"\n#### Transmit Data Block Size Exceeds Event Data Buffer Size "
341*32632Ssam #define A_NOFREIN	"\n#### No Available Inbound Entries to Send Close Event "
342*32632Ssam 
343*32632Ssam #define DCDASRT		100	/* data carrier detect asserted */
344*32632Ssam #define DTRASRT		101	/* data terminal ready asserted */
345*32632Ssam #define RNGASRT		102	/* ring indicator asserted */
346*32632Ssam #define DSRASRT		102	/* data set ready asserted */
347*32632Ssam #define CTSASRT		103	/* clear to send asserted */
348*32632Ssam #define RTSASRT		104	/* ready to send asserted */
349*32632Ssam #define STXASRT		105	/* secondary transmit asserted */
350*32632Ssam #define SRXASRT		106	/* secondary recieve asserted */
351*32632Ssam #define RATEASRT	107	/* rate signal asserted */
352*32632Ssam #define DCDDROP		108	/* data carrier detect dropped */
353*32632Ssam #define DTRDROP		109	/* data terminal ready dropped */
354*32632Ssam #define RNGDROP		110	/* ring indicator dropped */
355*32632Ssam #define MPDSRDROP	110	/* data set ready dropped */
356*32632Ssam #define CTSDROP		111	/* clear to send dropped */
357*32632Ssam #define RTSDROP		112	/* ready to send dropped */
358*32632Ssam #define STXDROP		113	/* secondary transmit dropped */
359*32632Ssam #define SRXDROP		114	/* secondary recieve dropped */
360*32632Ssam #define RATEDROP	115	/* rate signal dropped */
361*32632Ssam 
362*32632Ssam /* Defines for filters and intena in portstat */
363*32632Ssam #define MDM_OFF	0
364*32632Ssam #define MDM_ON	1
365*32632Ssam 
366*32632Ssam /* Modem on/off flags */
367*32632Ssam #define MMOD_OFF 0
368*32632Ssam #define MMOD_ON 1
369*32632Ssam 
370*32632Ssam /* defintions for DL interface */
371*32632Ssam 
372*32632Ssam #define MPDLBUFSIZE       1024
373*32632Ssam 
374*32632Ssam 
375*32632Ssam /*      mpdlioctl command defines       */
376*32632Ssam 
377*32632Ssam struct protports {
378*32632Ssam 	char protoport[MPMAXPORT];
379*32632Ssam } ;
380*32632Ssam 
381*32632Ssam struct abdcf {
382*32632Ssam         short   xmtbsz;         /* transmit buffer size - should */
383*32632Ssam                                 /* equal # of chars in a cblock  */
384*32632Ssam };
385*32632Ssam 
386*32632Ssam struct bdcf {
387*32632Ssam 	char    loadname[NMPPROTO+1];
388*32632Ssam 	char    protoports[MPMAXPORT];
389*32632Ssam 	char    fccstimer;      /* powerfail timer */
390*32632Ssam 	char    fccsports;      /* ports to affect */
391*32632Ssam 	char    fccssoc;        /* ports which will 'switch on close' */
392*32632Ssam };
393*32632Ssam 
394*32632Ssam 
395*32632Ssam /* These ioctls are for the dlmpcc command */
396*32632Ssam #define MPIOPORTMAP         _IOW(m,1, struct protports)
397*32632Ssam #define MPIOHILO            _IOW(m,3, short)
398*32632Ssam #define MPIOENDCODE         _IO(m,4)
399*32632Ssam #define MPIOASYNCNF         _IOW(m,7, struct abdcf)
400*32632Ssam #define MPIOENDDL           _IO(m,10)
401*32632Ssam #define MPIOSTARTDL         _IO(m,11)
402*32632Ssam #define MPIORESETBOARD      _IO(m,12)
403*32632Ssam 
404*32632Ssam /*      mpdlwrite opcode defines        */
405*32632Ssam 
406*32632Ssam #define MPDLCMD_NORMAL          1
407*32632Ssam 
408