xref: /csrg-svn/sys/kern/kern_synch.c (revision 33)
1*33Sbill /*	kern_synch.c	3.1	10/14/12	*/
2*33Sbill 
3*33Sbill #include "../h/param.h"
4*33Sbill #include "../h/systm.h"
5*33Sbill #include "../h/dir.h"
6*33Sbill #include "../h/user.h"
7*33Sbill #include "../h/proc.h"
8*33Sbill #include "../h/file.h"
9*33Sbill #include "../h/inode.h"
10*33Sbill #include "../h/vm.h"
11*33Sbill #include "../h/pte.h"
12*33Sbill 
13*33Sbill #ifdef FASTVAX
14*33Sbill asm(" .globl _eintr");
15*33Sbill #endif
16*33Sbill 
17*33Sbill #define SQSIZE 0100	/* Must be power of 2 */
18*33Sbill #define HASH(x)	(( (int) x >> 5) & (SQSIZE-1))
19*33Sbill struct proc *slpque[SQSIZE];
20*33Sbill 
21*33Sbill /*
22*33Sbill  * Give up the processor till a wakeup occurs
23*33Sbill  * on chan, at which time the process
24*33Sbill  * enters the scheduling queue at priority pri.
25*33Sbill  * The most important effect of pri is that when
26*33Sbill  * pri<=PZERO a signal cannot disturb the sleep;
27*33Sbill  * if pri>PZERO signals will be processed.
28*33Sbill  * Callers of this routine must be prepared for
29*33Sbill  * premature return, and check that the reason for
30*33Sbill  * sleeping has gone away.
31*33Sbill  */
32*33Sbill sleep(chan, pri)
33*33Sbill caddr_t chan;
34*33Sbill {
35*33Sbill 	register struct proc *rp;
36*33Sbill 	register s, h;
37*33Sbill 
38*33Sbill 	rp = u.u_procp;
39*33Sbill 	s = spl6();
40*33Sbill 	if (chan==0 || rp->p_stat != SRUN || rp->p_rlink)
41*33Sbill 		panic("sleep");
42*33Sbill 	rp->p_stat = SSLEEP;
43*33Sbill 	rp->p_wchan = chan;
44*33Sbill 	rp->p_slptime = 0;
45*33Sbill 	rp->p_pri = pri;
46*33Sbill 	h = HASH(chan);
47*33Sbill 	rp->p_link = slpque[h];
48*33Sbill 	slpque[h] = rp;
49*33Sbill 	if(pri > PZERO) {
50*33Sbill 		if(rp->p_sig && issig()) {
51*33Sbill 			rp->p_wchan = 0;
52*33Sbill 			rp->p_stat = SRUN;
53*33Sbill 			slpque[h] = rp->p_link;
54*33Sbill 			VOID spl0();
55*33Sbill 			goto psig;
56*33Sbill 		}
57*33Sbill 		VOID spl0();
58*33Sbill 		if(runin != 0) {
59*33Sbill 			runin = 0;
60*33Sbill 			wakeup((caddr_t)&runin);
61*33Sbill 		}
62*33Sbill 		swtch();
63*33Sbill 		if(rp->p_sig && issig())
64*33Sbill 			goto psig;
65*33Sbill 	} else {
66*33Sbill 		VOID spl0();
67*33Sbill 		swtch();
68*33Sbill 	}
69*33Sbill 	splx(s);
70*33Sbill 	return;
71*33Sbill 
72*33Sbill 	/*
73*33Sbill 	 * If priority was low (>PZERO) and
74*33Sbill 	 * there has been a signal,
75*33Sbill 	 * execute non-local goto to
76*33Sbill 	 * the qsav location.
77*33Sbill 	 * (see trap1/trap.c)
78*33Sbill 	 */
79*33Sbill psig:
80*33Sbill #ifndef FASTVAX
81*33Sbill 	longjmp(u.u_qsav);
82*33Sbill #else
83*33Sbill 	asm(".set U_SSAV,140");
84*33Sbill 	asm("movl _u+U_SSAV,fp");
85*33Sbill 	asm("movl _u+U_SSAV+4,sp");
86*33Sbill 	asm("movl _u+U_SSAV+8,r11");
87*33Sbill 	u.u_error = EINTR;
88*33Sbill 	asm("jmp _eintr");
89*33Sbill #endif
90*33Sbill 	/*NOTREACHED*/
91*33Sbill }
92*33Sbill 
93*33Sbill /*
94*33Sbill  * Wake up all processes sleeping on chan.
95*33Sbill  */
96*33Sbill wakeup(chan)
97*33Sbill register caddr_t chan;
98*33Sbill {
99*33Sbill 	register struct proc *p, *q;
100*33Sbill 	register i;
101*33Sbill 	int s;
102*33Sbill 
103*33Sbill 	s = spl6();
104*33Sbill 	i = HASH(chan);
105*33Sbill restart:
106*33Sbill 	p = slpque[i];
107*33Sbill 	q = NULL;
108*33Sbill 	while(p != NULL) {
109*33Sbill 		if (p->p_rlink || p->p_stat != SSLEEP)
110*33Sbill 			panic("wakeup");
111*33Sbill 		if (p->p_wchan==chan && p->p_stat!=SZOMB) {
112*33Sbill 			if (q == NULL)
113*33Sbill 				slpque[i] = p->p_link;
114*33Sbill 			else
115*33Sbill 				q->p_link = p->p_link;
116*33Sbill 			p->p_wchan = 0;
117*33Sbill 			p->p_slptime = 0;
118*33Sbill 			/* OPTIMIZED INLINE EXPANSION OF setrun(p) */
119*33Sbill 			p->p_stat = SRUN;
120*33Sbill 			if (p->p_flag & SLOAD) {
121*33Sbill #ifndef FASTVAX
122*33Sbill 				p->p_link = runq;
123*33Sbill 				runq = p->p_link;
124*33Sbill #else
125*33Sbill 				setrq(p);
126*33Sbill #endif
127*33Sbill 			}
128*33Sbill 			if(p->p_pri < curpri)
129*33Sbill 				runrun++;
130*33Sbill 			if(runout != 0 && (p->p_flag&SLOAD) == 0) {
131*33Sbill 				runout = 0;
132*33Sbill 				wakeup((caddr_t)&runout);
133*33Sbill 			}
134*33Sbill 			/* END INLINE EXPANSION */
135*33Sbill 			goto restart;
136*33Sbill 		}
137*33Sbill 		q = p;
138*33Sbill 		p = p->p_link;
139*33Sbill 	}
140*33Sbill 	splx(s);
141*33Sbill }
142*33Sbill 
143*33Sbill #ifdef FASTVAX
144*33Sbill /*
145*33Sbill  * Initialize the (doubly-linked) run queues
146*33Sbill  * to be empty.
147*33Sbill  */
148*33Sbill rqinit()
149*33Sbill {
150*33Sbill 	register int i;
151*33Sbill 
152*33Sbill 	for (i = 0; i < NQS; i++)
153*33Sbill 		qs[i].ph_link = qs[i].ph_rlink = (struct proc *)&qs[i];
154*33Sbill }
155*33Sbill #endif
156*33Sbill 
157*33Sbill /*
158*33Sbill  * Set the process running;
159*33Sbill  * arrange for it to be swapped in if necessary.
160*33Sbill  */
161*33Sbill setrun(p)
162*33Sbill register struct proc *p;
163*33Sbill {
164*33Sbill 	register caddr_t w;
165*33Sbill 	register s;
166*33Sbill 
167*33Sbill 	s = spl6();
168*33Sbill 	switch (p->p_stat) {
169*33Sbill 
170*33Sbill 	case 0:
171*33Sbill 	case SWAIT:
172*33Sbill 	case SRUN:
173*33Sbill 	case SZOMB:
174*33Sbill 	default:
175*33Sbill 		panic("setrun");
176*33Sbill 
177*33Sbill 	case SSLEEP:
178*33Sbill 		if (w = p->p_wchan) {
179*33Sbill 			wakeup(w);
180*33Sbill 			splx(s);
181*33Sbill 			return;
182*33Sbill 		}
183*33Sbill 		break;
184*33Sbill 
185*33Sbill 	case SIDL:
186*33Sbill 	case SSTOP:
187*33Sbill 		break;
188*33Sbill 	}
189*33Sbill 	p->p_stat = SRUN;
190*33Sbill 	if (p->p_flag & SLOAD)
191*33Sbill 		setrq(p);
192*33Sbill 	splx(s);
193*33Sbill 	if(p->p_pri < curpri)
194*33Sbill 		runrun++;
195*33Sbill 	if(runout != 0 && (p->p_flag&SLOAD) == 0) {
196*33Sbill 		runout = 0;
197*33Sbill 		wakeup((caddr_t)&runout);
198*33Sbill 	}
199*33Sbill }
200*33Sbill 
201*33Sbill /*
202*33Sbill  * Set user priority.
203*33Sbill  * The rescheduling flag (runrun)
204*33Sbill  * is set if the priority is better
205*33Sbill  * than the currently running process.
206*33Sbill  */
207*33Sbill setpri(pp)
208*33Sbill register struct proc *pp;
209*33Sbill {
210*33Sbill 	register p;
211*33Sbill 
212*33Sbill 	p = (pp->p_cpu & 0377)/16;
213*33Sbill 	p += PUSER + pp->p_nice - NZERO;
214*33Sbill 	if(p > 127)
215*33Sbill 		p = 127;
216*33Sbill 	if(p < curpri)
217*33Sbill 		runrun++;
218*33Sbill 	pp->p_usrpri = p;
219*33Sbill 	return(p);
220*33Sbill }
221*33Sbill 
222*33Sbill /*
223*33Sbill  * Create a new process-- the internal version of
224*33Sbill  * sys fork.
225*33Sbill  * It returns 1 in the new process, 0 in the old.
226*33Sbill  */
227*33Sbill newproc(isvfork)
228*33Sbill {
229*33Sbill 	register struct proc *p;
230*33Sbill 	register struct proc *rpp, *rip;
231*33Sbill 	register int n;
232*33Sbill 
233*33Sbill 	p = NULL;
234*33Sbill 	/*
235*33Sbill 	 * First, just locate a slot for a process
236*33Sbill 	 * and copy the useful info from this process into it.
237*33Sbill 	 * The panic "cannot happen" because fork has already
238*33Sbill 	 * checked for the existence of a slot.
239*33Sbill 	 */
240*33Sbill retry:
241*33Sbill 	mpid++;
242*33Sbill 	if(mpid >= 30000) {
243*33Sbill 		mpid = 0;
244*33Sbill 		goto retry;
245*33Sbill 	}
246*33Sbill 	for(rpp = &proc[0]; rpp < &proc[NPROC]; rpp++) {
247*33Sbill 		if(rpp->p_stat == NULL && p==NULL)
248*33Sbill 			p = rpp;
249*33Sbill 		if (rpp->p_pid==mpid || rpp->p_pgrp==mpid)
250*33Sbill 			goto retry;
251*33Sbill 	}
252*33Sbill 	if ((rpp = p)==NULL)
253*33Sbill 		panic("no procs");
254*33Sbill 
255*33Sbill 	/*
256*33Sbill 	 * make proc entry for new proc
257*33Sbill 	 */
258*33Sbill 
259*33Sbill 	rip = u.u_procp;
260*33Sbill 	rpp->p_stat = SIDL;
261*33Sbill 	rpp->p_clktim = 0;
262*33Sbill 	rpp->p_flag = SLOAD | (rip->p_flag & SPAGI);
263*33Sbill 	if (isvfork) {
264*33Sbill 		rpp->p_flag |= SVFORK;
265*33Sbill 		rpp->p_ndx = rip->p_ndx;
266*33Sbill 	} else
267*33Sbill 		rpp->p_ndx = rpp - proc;
268*33Sbill 	rpp->p_uid = rip->p_uid;
269*33Sbill 	rpp->p_pgrp = rip->p_pgrp;
270*33Sbill 	rpp->p_nice = rip->p_nice;
271*33Sbill 	rpp->p_textp = isvfork ? 0 : rip->p_textp;
272*33Sbill 	rpp->p_pid = mpid;
273*33Sbill 	rpp->p_ppid = rip->p_pid;
274*33Sbill 	rpp->p_time = 0;
275*33Sbill 	rpp->p_cpu = 0;
276*33Sbill 	if (isvfork) {
277*33Sbill 		rpp->p_tsize = rpp->p_dsize = rpp->p_ssize = 0;
278*33Sbill 		rpp->p_szpt = clrnd(ctopt(UPAGES));
279*33Sbill 		forkstat.cntvfork++;
280*33Sbill 		forkstat.sizvfork += rip->p_dsize + rip->p_ssize;
281*33Sbill 	} else {
282*33Sbill 		rpp->p_tsize = rip->p_tsize;
283*33Sbill 		rpp->p_dsize = rip->p_dsize;
284*33Sbill 		rpp->p_ssize = rip->p_ssize;
285*33Sbill 		rpp->p_szpt = rip->p_szpt;
286*33Sbill 		forkstat.cntfork++;
287*33Sbill 		forkstat.sizfork += rip->p_dsize + rip->p_ssize;
288*33Sbill 	}
289*33Sbill 	rpp->p_rssize = 0;
290*33Sbill 	rpp->p_wchan = 0;
291*33Sbill 	rpp->p_slptime = 0;
292*33Sbill 	rpp->p_aveflt = rip->p_aveflt;
293*33Sbill 	rate.v_pgin += rip->p_aveflt;
294*33Sbill 	rpp->p_faults = 0;
295*33Sbill 	n = PIDHASH(rpp->p_pid);
296*33Sbill 	p->p_idhash = pidhash[n];
297*33Sbill 	pidhash[n] = rpp - proc;
298*33Sbill 
299*33Sbill 	/*
300*33Sbill 	 * make duplicate entries
301*33Sbill 	 * where needed
302*33Sbill 	 */
303*33Sbill 
304*33Sbill 	multprog++;
305*33Sbill 
306*33Sbill 	for(n=0; n<NOFILE; n++)
307*33Sbill 		if(u.u_ofile[n] != NULL) {
308*33Sbill 			u.u_ofile[n]->f_count++;
309*33Sbill 			if(!isvfork && u.u_vrpages[n])
310*33Sbill 				u.u_ofile[n]->f_inode->i_vfdcnt++;
311*33Sbill 		}
312*33Sbill 
313*33Sbill 	u.u_cdir->i_count++;
314*33Sbill 	if (u.u_rdir)
315*33Sbill 		u.u_rdir->i_count++;
316*33Sbill 	/*
317*33Sbill 	 * Partially simulate the environment
318*33Sbill 	 * of the new process so that when it is actually
319*33Sbill 	 * created (by copying) it will look right.
320*33Sbill 	 */
321*33Sbill 
322*33Sbill 	rip->p_flag |= SKEEP;	/* prevent parent from being swapped */
323*33Sbill 
324*33Sbill 	if (procdup(rpp, isvfork))
325*33Sbill 		return (1);
326*33Sbill 
327*33Sbill 	spl6();
328*33Sbill 	rpp->p_stat = SRUN;
329*33Sbill 	setrq(rpp);
330*33Sbill 	spl0();
331*33Sbill 	/* THE SSWAP BIT IS REPLACED BY u.u_pcb.pcb_sswap SEE procdup */
332*33Sbill 	/* rpp->p_flag |= SSWAP; */
333*33Sbill 	rip->p_flag &= ~SKEEP;
334*33Sbill 	if (isvfork) {
335*33Sbill 		u.u_procp->p_xlink = rpp;
336*33Sbill 		u.u_procp->p_flag |= SNOVM;
337*33Sbill 		while (rpp->p_flag & SVFORK)
338*33Sbill 			sleep((caddr_t)rpp, PZERO - 1);
339*33Sbill 		if ((rpp->p_flag & SLOAD) == 0)
340*33Sbill 			panic("newproc vfork");
341*33Sbill 		uaccess(rpp, Vfmap, &vfutl);
342*33Sbill 		u.u_procp->p_xlink = 0;
343*33Sbill 		vpassvm(rpp, u.u_procp, &vfutl, &u, Vfmap);
344*33Sbill 		for (n = 0; n < NOFILE; n++)
345*33Sbill 			if (vfutl.u_vrpages[n]) {
346*33Sbill 				if ((u.u_vrpages[n] = vfutl.u_vrpages[n] - 1) == 0)
347*33Sbill 					if (--u.u_ofile[n]->f_inode->i_vfdcnt < 0)
348*33Sbill 						panic("newproc i_vfdcnt");
349*33Sbill 				vfutl.u_vrpages[n] = 0;
350*33Sbill 			}
351*33Sbill 		u.u_procp->p_flag &= ~SNOVM;
352*33Sbill 		rpp->p_ndx = rpp - proc;
353*33Sbill 		rpp->p_flag |= SVFDONE;
354*33Sbill 		wakeup((caddr_t)rpp);
355*33Sbill 	}
356*33Sbill 	return (0);
357*33Sbill }
358