fix fault in vdreset_ctlr when unit isn't configured (null pointer)
[unix-history] / usr / src / sys / tahoe / vba / vxm.c
CommitLineData
e6453f14 1/* vxm.c 1.3 86/01/12 */
dc2dfe78
SL
2
3#include "vx.h"
4#if NVX > 0
5/*
6 * VIOC-X Modem control
7 */
8
e6453f14
SL
9#include "param.h"
10#include "file.h"
11#include "ioctl.h"
12#include "tty.h"
13#include "conf.h"
14
9d915fad 15#include "../tahoevba/vioc.h"
dc2dfe78
SL
16#include "vbsc.h"
17#if NVBSC > 0
e6453f14
SL
18#include "../tahoebsc/bscio.h"
19#include "../tahoebsc/bsc.h"
dc2dfe78
SL
20extern char bscport[];
21#endif
22
23
24extern struct vcx vcx[] ;
25extern struct tty vx_tty[];
26extern struct vcmds v_cmds[] ;
27
28extern int vxstart() ;
29extern struct vxcmd *vobtain() ;
30extern struct vxcmd *nextcmd() ;
31
32
33vcmodem(dev,flag)
34dev_t dev ;
35{
36 struct tty *tp ;
37 register struct vxcmd *cp ;
38 register struct vcx *xp ;
39 register struct vblok *kp ;
40 register port ;
41
42 port = minor(dev) ;
43 tp = &vx_tty[port] ;
44 port &= 017 ;
45 xp = (struct vcx *)tp->t_addr ;
46 cp = vobtain(xp) ;
47 kp = VBAS(xp->v_nbr) ;
48
49 /*
50 * Issue MODEM command
51 */
52 cp->cmd = MDMCTL ;
53 cp->par[0] = (flag == VMOD_ON) ? V_ENAB : V_DISAB ;
54 cp->par[1] = port;
9d915fad 55 vcmd(xp->v_nbr, (caddr_t)&cp->cmd) ;
dc2dfe78
SL
56 port -= xp->v_loport ;
57 if((kp->v_dcd >> port) & 1) {
58 if(flag == VMOD_ON)
59 tp->t_state |= TS_CARR_ON ;
60 return(1) ;
61 }
62 return(0) ;
63}
64
65
66/*
67 * VCMINTR called when an unsolicited interrup occurs signaling
68 * some change of modem control state.
69 */
70vcmintr(n)
71register n ; /* viocx number */
72{
73 register struct vblok *kp ;
74 register struct tty *tp ;
75 register port ;
76
77 kp = VBAS( n ) ;
78 port = kp->v_usdata[0] & 017 ;
79 tp = &vx_tty[port+n*16] ;
80
81#if NVBSC > 0
82 /*
83 * Check for change in DSR for BISYNC port.
84 */
85 if ((kp->v_ustat & DSR_CHG) && (bscport[port+n*16] & BISYNC)) {
86 register struct vcx *xp ;
87 register struct bsc *bp ;
88 extern struct bsc bsc[] ;
89
90 xp = (struct vcx *)tp->t_addr ;
91 bp = &bsc[minor(tp->t_dev)] ;
92 bp->b_hlflgs &= ~BSC_DSR ;
93 if (kp->v_ustat & DSR_ON)
94 bp->b_hlflgs |= BSC_DSR ;
95/*debug*/printf("BSC DSR Chg: %x\n", kp->v_ustat & DSR_CHG);
96 }
97 if (bscport[port+n*16] & BISYNC) return;
98#endif
99 if((kp->v_ustat & DCD_ON) && ((tp->t_state & TS_CARR_ON) == 0) ) {
100 tp->t_state |= TS_CARR_ON ;
101 wakeup((caddr_t)&tp->t_canq) ;
102 return ;
103 }
104
105 if((kp->v_ustat & DCD_OFF) && (tp->t_state & TS_CARR_ON)) {
106 tp->t_state &= ~TS_CARR_ON ;
107 if(tp->t_state & TS_ISOPEN) {
108 register struct vcx *xp ;
109 register struct vcmds *cp ;
110 register struct vxcmd *cmdp ;
111
112 ttyflush(tp, FREAD|FWRITE);
113 /* clear all pending trnansmits */
114 xp = &vcx[n];
115 if(tp->t_state&(TS_BUSY|TS_FLUSH) && xp->v_vers==V_NEW) {
116 int i, cmdfound = 0;
117 cp = &v_cmds[n];
118 for(i = cp->v_empty; i!=cp->v_fill; ) {
119 cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
120 if((cmdp->cmd==XMITDTA || cmdp->cmd==XMITIMM)
121 && ((struct vxmit *)cmdp->par)->line == port) {
122 cmdfound++;
123 cmdp->cmd = FDTATOX ;
124 cmdp->par[1] = port ;
125 }
126 if(++i >= VC_CMDBUFL)
127 i = 0;
128 }
129 if(cmdfound)
130 tp->t_state &= ~(TS_BUSY|TS_FLUSH);
131 /* cmd is already in vioc, have to flush it */
132 else {
133 cmdp = vobtain(xp);
134 cmdp->cmd = FDTATOX ;
135 cmdp->par[1] = port ;
9d915fad 136 vcmd(n, (caddr_t)&cmdp->cmd);
dc2dfe78
SL
137 }
138 }
139 if((tp->t_flags&NOHANG)==0) {
140 gsignal(tp->t_pgrp, SIGHUP) ;
141 gsignal(tp->t_pgrp, SIGCONT);
142 }
143 }
144 return ;
145 }
146
147 if((kp->v_ustat & BRK_CHR) && (tp->t_state & TS_ISOPEN) ) {
148 (*linesw[tp->t_line].l_rint)(tp->t_intrc & 0377, tp) ;
149 return ;
150 }
151}
152#endif