xref: /csrg-svn/sys/ufs/lfs/lfs_segment.c (revision 51188)
1*51188Sbostic /*
2*51188Sbostic  * Copyright (c) 1991 Regents of the University of California.
3*51188Sbostic  * All rights reserved.
4*51188Sbostic  *
5*51188Sbostic  * %sccs.include.redist.c%
6*51188Sbostic  *
7*51188Sbostic  *	@(#)lfs_segment.c	5.1 (Berkeley) 09/25/91
8*51188Sbostic  */
9*51188Sbostic 
10*51188Sbostic #include "param.h"
11*51188Sbostic #include "systm.h"
12*51188Sbostic #include "namei.h"
13*51188Sbostic #include "resourcevar.h"
14*51188Sbostic #include "kernel.h"
15*51188Sbostic #include "file.h"
16*51188Sbostic #include "stat.h"
17*51188Sbostic #include "buf.h"
18*51188Sbostic #include "proc.h"
19*51188Sbostic #include "conf.h"
20*51188Sbostic #include "vnode.h"
21*51188Sbostic #include "specdev.h"
22*51188Sbostic #include "fifo.h"
23*51188Sbostic #include "malloc.h"
24*51188Sbostic #include "mount.h"
25*51188Sbostic #include "../ufs/lockf.h"
26*51188Sbostic #include "../ufs/quota.h"
27*51188Sbostic #include "../ufs/inode.h"
28*51188Sbostic #include "../ufs/dir.h"
29*51188Sbostic #include "../ufs/ufsmount.h"
30*51188Sbostic #include "lfs.h"
31*51188Sbostic #include "lfs_extern.h"
32*51188Sbostic 
33*51188Sbostic /*
34*51188Sbostic Need to write the inodes out.
35*51188Sbostic The indirect buffers need to be marked dirty
36*51188Sbostic What about sync?  How do you wait on the last I/O?
37*51188Sbostic Need to keep vnode v_numoutput up to date for pending writes.
38*51188Sbostic */
39*51188Sbostic 
40*51188Sbostic static int	 lfs_biocallback __P((BUF *));
41*51188Sbostic static void	 lfs_endsum __P((LFS *, SEGMENT *, int));
42*51188Sbostic static BUF	*lfs_newbuf __P((LFS *, daddr_t, size_t));
43*51188Sbostic static SEGMENT	*lfs_newseg __P((LFS *));
44*51188Sbostic static void	 lfs_newsum __P((LFS *, SEGMENT *));
45*51188Sbostic static daddr_t	 lfs_nextseg __P((LFS *));
46*51188Sbostic static int	 lfs_updatemeta __P((LFS *, INODE *, FINFO *, BUF **));
47*51188Sbostic static SEGMENT	*lfs_writefile __P((SEGMENT *, LFS *, VNODE *));
48*51188Sbostic static void	 lfs_writemeta __P((void));
49*51188Sbostic static void	 lfs_writeseg __P((LFS *, SEGMENT *));
50*51188Sbostic static void	 shellsort __P((BUF **, u_long *, register int));
51*51188Sbostic 
52*51188Sbostic /*
53*51188Sbostic  * XXX -- when we add fragments in here, we will need to allocate a larger
54*51188Sbostic  * buffer pointer array (sp->bpp).
55*51188Sbostic  */
56*51188Sbostic int
57*51188Sbostic lfs_segwrite(mp)
58*51188Sbostic 	MOUNT *mp;
59*51188Sbostic {
60*51188Sbostic 	FINFO *fip;			/* current file info structure */
61*51188Sbostic 	INODE *ip;
62*51188Sbostic 	LFS *fs;
63*51188Sbostic 	VNODE *vp;
64*51188Sbostic 	SEGMENT *sp;
65*51188Sbostic 
66*51188Sbostic printf("lfs_segwrite: %s %s\n", mp->mnt_stat.f_mntonname, mp->mnt_stat.f_mntfromname);
67*51188Sbostic 	fs = VFSTOUFS(mp)->um_lfs;
68*51188Sbostic 
69*51188Sbostic 	sp = lfs_newseg(fs);
70*51188Sbostic loop:
71*51188Sbostic 	for (vp = mp->mnt_mounth; vp; vp = vp->v_mountf) {
72*51188Sbostic 		/*
73*51188Sbostic 		 * If the vnode that we are about to sync is no longer
74*51188Sbostic 		 * associated with this mount point, start over.
75*51188Sbostic 		 */
76*51188Sbostic printf("lfs_segwrite: processing inum %d\n", VTOI(vp)->i_number);
77*51188Sbostic 		if (vp->v_mount != mp)
78*51188Sbostic 			goto loop;
79*51188Sbostic 		if (VOP_ISLOCKED(vp))
80*51188Sbostic 			continue;
81*51188Sbostic 		ip = VTOI(vp);
82*51188Sbostic 		if (ip->i_number == LFS_IFILE_INUM)
83*51188Sbostic 			continue;
84*51188Sbostic 		if ((ip->i_flag & (IMOD|IACC|IUPD|ICHG)) == 0 &&
85*51188Sbostic 		    vp->v_dirtyblkhd == NULL)
86*51188Sbostic 			continue;
87*51188Sbostic 		if (vget(vp))
88*51188Sbostic 			goto loop;
89*51188Sbostic 		sp = lfs_writefile(sp, fs, vp);
90*51188Sbostic 
91*51188Sbostic 		/* Need to take care of inode now */
92*51188Sbostic printf("lfs_segwrite: need to add dinode %d to seg\n", ip->i_din.di_inum);
93*51188Sbostic 		vput(vp);
94*51188Sbostic 	}
95*51188Sbostic 	/*
96*51188Sbostic 	 * Force stale file system control information to be flushed.
97*51188Sbostic 	 */
98*51188Sbostic 	lfs_writeseg(fs, sp);
99*51188Sbostic /*	vflushbuf(ump->um_devvp, waitfor == MNT_WAIT ? B_SYNC : 0); */
100*51188Sbostic printf("lfs_segwrite: returning from segwrite\n");
101*51188Sbostic 	return (0);
102*51188Sbostic }
103*51188Sbostic 
104*51188Sbostic static int
105*51188Sbostic lfs_biocallback(bp)
106*51188Sbostic 	BUF *bp;
107*51188Sbostic {
108*51188Sbostic 	LFS *fs;
109*51188Sbostic 	SEGMENT *sp, *next_sp;
110*51188Sbostic 	UFSMOUNT *ump;
111*51188Sbostic 	VNODE *devvp;
112*51188Sbostic 
113*51188Sbostic 	ump = VFSTOUFS(bp->b_vp->v_mount);
114*51188Sbostic 	fs = ump->um_lfs;
115*51188Sbostic 	devvp = ump->um_devvp;
116*51188Sbostic 							/* XXX splbio(); */
117*51188Sbostic printf("lfs_biocallback: iocount: %d\n", fs->lfs_iocount);
118*51188Sbostic 	if (--fs->lfs_iocount) {
119*51188Sbostic 		/* Fire off summary writes */
120*51188Sbostic 		for (sp = fs->lfs_seglist; sp; sp = next_sp) {
121*51188Sbostic 			next_sp = sp->nextp;
122*51188Sbostic 			(*(devvp->v_op->vop_strategy))(*(sp->cbpp - 1));
123*51188Sbostic printf("free: segsum %x bpp %x sp %x\n", sp->segsum, sp->bpp, sp);
124*51188Sbostic 			free(sp->segsum, M_SEGMENT);
125*51188Sbostic 			free(sp->bpp, M_SEGMENT);
126*51188Sbostic 			free(sp, M_SEGMENT);
127*51188Sbostic 		}
128*51188Sbostic 	}
129*51188Sbostic }
130*51188Sbostic 
131*51188Sbostic 
132*51188Sbostic static void
133*51188Sbostic lfs_endsum(fs, sp, calc_next)
134*51188Sbostic 	LFS *fs;
135*51188Sbostic 	SEGMENT *sp;
136*51188Sbostic 	int calc_next;		/* if 1, calculate next, else -1 */
137*51188Sbostic {
138*51188Sbostic 	BUF *bp;
139*51188Sbostic 	SEGSUM *ssp;
140*51188Sbostic 	daddr_t next_addr;
141*51188Sbostic 	int npages, nseg_pages;
142*51188Sbostic 
143*51188Sbostic printf("lfs_endsum\n");
144*51188Sbostic 	ssp = sp->segsum;
145*51188Sbostic 	if (!calc_next)
146*51188Sbostic 		ssp->ss_nextsum = (daddr_t) -1;
147*51188Sbostic 
148*51188Sbostic 	nseg_pages = sp->sum_num / (fs->lfs_bsize / LFS_SUMMARY_SIZE);
149*51188Sbostic 	if ((sp->sum_num % (fs->lfs_bsize / LFS_SUMMARY_SIZE)) == 0) {
150*51188Sbostic 		/*
151*51188Sbostic 		 * May need to change the nextsum field on the previous
152*51188Sbostic 		 * summary header in which case we need to recompute the
153*51188Sbostic 		 * checksum as well.
154*51188Sbostic 		 */
155*51188Sbostic 		npages = nseg_pages + (sp->ninodes + INOPB(fs) - 1) / INOPB(fs);
156*51188Sbostic 		next_addr = fs->lfs_sboffs[0] +
157*51188Sbostic 		    (sp->seg_number + 1) * fsbtodb(fs, fs->lfs_ssize)
158*51188Sbostic 		    - fsbtodb(fs, npages) - LFS_SUMMARY_SIZE / DEV_BSIZE;
159*51188Sbostic 		if (calc_next)
160*51188Sbostic 			ssp->ss_nextsum = next_addr;
161*51188Sbostic 		ssp->ss_cksum = cksum(&ssp->ss_cksum,
162*51188Sbostic 		    LFS_SUMMARY_SIZE - sizeof(ssp->ss_cksum));
163*51188Sbostic 		bp = lfs_newbuf(fs, sp->sum_addr, fs->lfs_bsize);
164*51188Sbostic 		bcopy(sp->segsum, bp->b_un.b_words, fs->lfs_bsize);
165*51188Sbostic 		bp->b_flags |= B_BUSY;
166*51188Sbostic 		if (nseg_pages != 1) {
167*51188Sbostic 			bp->b_flags |= B_CALL;
168*51188Sbostic 			bp->b_iodone = lfs_biocallback;
169*51188Sbostic 		}
170*51188Sbostic 		brelse(bp);
171*51188Sbostic 		sp->bpp[fs->lfs_ssize - npages] = bp;
172*51188Sbostic 		sp->segsum = (SEGSUM *)(sp->segsum + fs->lfs_bsize -
173*51188Sbostic 		    LFS_SUMMARY_SIZE);
174*51188Sbostic 		sp->sum_addr = next_addr;
175*51188Sbostic 	} else {
176*51188Sbostic 		sp->sum_addr -= LFS_SUMMARY_SIZE / DEV_BSIZE;
177*51188Sbostic 		ssp->ss_nextsum = sp->sum_addr;
178*51188Sbostic 		/* Calculate cksum on previous segment summary */
179*51188Sbostic 		ssp->ss_cksum = cksum(&ssp->ss_cksum,
180*51188Sbostic 		    LFS_SUMMARY_SIZE - sizeof(ssp->ss_cksum));
181*51188Sbostic 		sp->segsum -= LFS_SUMMARY_SIZE;
182*51188Sbostic 	}
183*51188Sbostic }
184*51188Sbostic 
185*51188Sbostic static BUF *
186*51188Sbostic lfs_newbuf(fs, daddr, size)
187*51188Sbostic 	LFS *fs;
188*51188Sbostic 	daddr_t daddr;
189*51188Sbostic 	size_t size;
190*51188Sbostic {
191*51188Sbostic 	BUF *bp;
192*51188Sbostic 	VNODE *devvp;
193*51188Sbostic 
194*51188Sbostic printf("lfs_newbuf\n");
195*51188Sbostic 	bp = getnewbuf();
196*51188Sbostic 	bremhash(bp);
197*51188Sbostic 
198*51188Sbostic 	/*
199*51188Sbostic 	 * XXX
200*51188Sbostic 	 * Need a devvp, but this isn't a particularly clean way to get one.
201*51188Sbostic 	 */
202*51188Sbostic 	devvp = VTOI(fs->lfs_ivnode)->i_devvp;
203*51188Sbostic 	bgetvp(devvp, bp);
204*51188Sbostic 	bp->b_bcount = 0;
205*51188Sbostic 	bp->b_lblkno = daddr;
206*51188Sbostic 	bp->b_blkno = daddr;
207*51188Sbostic 	bp->b_error = 0;
208*51188Sbostic 	bp->b_resid = 0;
209*51188Sbostic 	binshash(bp, BUFHASH(devvp, daddr));
210*51188Sbostic 	allocbuf(bp, size);
211*51188Sbostic 	return (bp);
212*51188Sbostic }
213*51188Sbostic 
214*51188Sbostic 
215*51188Sbostic /*
216*51188Sbostic  * Start a new segment
217*51188Sbostic  */
218*51188Sbostic static SEGMENT *
219*51188Sbostic lfs_newseg(fs)
220*51188Sbostic 	LFS *fs;
221*51188Sbostic {
222*51188Sbostic 	SEGMENT *sp;
223*51188Sbostic 	SEGUSE *sup;
224*51188Sbostic 
225*51188Sbostic printf("lfs_newseg\n");
226*51188Sbostic 	/* Get buffer space to write out a segment */
227*51188Sbostic 	sp = malloc(sizeof(SEGMENT), M_SEGMENT, M_WAITOK);
228*51188Sbostic 	sp->cbpp = sp->bpp =
229*51188Sbostic 	    malloc(fs->lfs_ssize * sizeof(BUF *), M_SEGMENT, M_WAITOK);
230*51188Sbostic 	sp->nextp = NULL;
231*51188Sbostic 	sp->sum_bytes_left = LFS_SUMMARY_SIZE;
232*51188Sbostic 	sp->seg_bytes_left = (fs->lfs_segmask + 1) - LFS_SUMMARY_SIZE;
233*51188Sbostic 	sp->saddr = fs->lfs_nextseg;
234*51188Sbostic 	sp->sum_addr = sp->saddr + sp->seg_bytes_left / DEV_BSIZE;
235*51188Sbostic 	sp->ninodes = 0;
236*51188Sbostic 	sp->sum_num = -1;
237*51188Sbostic 	sp->seg_number = (sp->saddr - fs->lfs_sboffs[0]) /
238*51188Sbostic 	    fsbtodb(fs, fs->lfs_ssize);
239*51188Sbostic 
240*51188Sbostic 	/* initialize segment summary info */
241*51188Sbostic 	lfs_newsum(fs, sp);
242*51188Sbostic 	sup = fs->lfs_segtab + sp->seg_number;
243*51188Sbostic 
244*51188Sbostic 	if (sup->su_nbytes != 0) {
245*51188Sbostic 		/* This is a segment containing a super block */
246*51188Sbostic 		FINFO *fip;
247*51188Sbostic 		daddr_t lbn, *lbnp;
248*51188Sbostic 
249*51188Sbostic 		fip = sp->fip;
250*51188Sbostic 		fip->fi_nblocks = LFS_SBPAD >> fs->lfs_bshift;
251*51188Sbostic 		fip->fi_version = 1;
252*51188Sbostic 		fip->fi_ino = LFS_UNUSED_INUM;
253*51188Sbostic 		sp->saddr += fsbtodb(fs, fip->fi_nblocks);
254*51188Sbostic 		lbnp = fip->fi_blocks;
255*51188Sbostic 		for (lbn = 0; lbn < fip->fi_nblocks; lbn++)
256*51188Sbostic 			*lbnp++ = lbn;
257*51188Sbostic 		sp->seg_bytes_left -= sup->su_nbytes;
258*51188Sbostic 		sp->sum_bytes_left -=
259*51188Sbostic 		    sizeof(FINFO) + (fip->fi_nblocks - 1) * sizeof(daddr_t);
260*51188Sbostic 		sp->fip = (FINFO *)lbnp;
261*51188Sbostic 	}
262*51188Sbostic 	return(sp);
263*51188Sbostic }
264*51188Sbostic 
265*51188Sbostic 
266*51188Sbostic static void
267*51188Sbostic lfs_newsum(fs, sp)
268*51188Sbostic 	LFS *fs;
269*51188Sbostic 	SEGMENT *sp;
270*51188Sbostic {
271*51188Sbostic 	SEGSUM *ssp;
272*51188Sbostic 	void *sum;
273*51188Sbostic 
274*51188Sbostic printf("lfs_newsum\n");
275*51188Sbostic 	sp->sum_num++;
276*51188Sbostic 	if (sp->sum_num == 0) {
277*51188Sbostic 		sum = malloc(fs->lfs_bsize, M_SEGMENT, M_WAITOK);
278*51188Sbostic 		sp->segsum = sum + fs->lfs_bsize - LFS_SUMMARY_SIZE;
279*51188Sbostic 		ssp = sp->segsum;
280*51188Sbostic 		ssp->ss_next = fs->lfs_nextseg = lfs_nextseg(fs);
281*51188Sbostic 		ssp->ss_prev = fs->lfs_lastseg;
282*51188Sbostic 	} else {
283*51188Sbostic 		lfs_endsum(fs, sp, 1);
284*51188Sbostic 		ssp = sp->segsum;
285*51188Sbostic 		ssp->ss_next = ssp->ss_next;
286*51188Sbostic 		ssp->ss_prev = ssp->ss_prev;
287*51188Sbostic 	}
288*51188Sbostic 
289*51188Sbostic 	/* Initialize segment summary info. */
290*51188Sbostic 	sp->fip = (FINFO *)(sp->segsum + sizeof(SEGSUM));
291*51188Sbostic 	ssp->ss_nextsum = (daddr_t)-1;
292*51188Sbostic 	ssp->ss_create = time.tv_sec;
293*51188Sbostic 
294*51188Sbostic 	ssp->ss_nfinfo = 0;
295*51188Sbostic 	ssp->ss_ninos = 0;
296*51188Sbostic 	sp->sum_bytes_left -= LFS_SUMMARY_SIZE;
297*51188Sbostic 	sp->seg_bytes_left -= LFS_SUMMARY_SIZE;
298*51188Sbostic }
299*51188Sbostic 
300*51188Sbostic #define seginc(fs, sn)	((sn + 1) % fs->lfs_nseg)
301*51188Sbostic static daddr_t
302*51188Sbostic lfs_nextseg(fs)
303*51188Sbostic 	LFS *fs;
304*51188Sbostic {
305*51188Sbostic 	int segnum, sn;
306*51188Sbostic 	SEGUSE *sup;
307*51188Sbostic 
308*51188Sbostic printf("lfs_nextseg\n");
309*51188Sbostic 	segnum = satosn(fs, fs->lfs_nextseg);
310*51188Sbostic 	for (sn = seginc(fs, sn); sn != segnum; sn = seginc(fs, sn)) {
311*51188Sbostic 		sup = &fs->lfs_segtab[sn];
312*51188Sbostic 		if (!(sup->su_flags & SEGUSE_DIRTY))
313*51188Sbostic 			break;
314*51188Sbostic 	}
315*51188Sbostic 	if (sn == segnum)
316*51188Sbostic 		panic("lfs_nextseg: file system full");		/* XXX */
317*51188Sbostic 	return(sntosa(fs, sn));
318*51188Sbostic }
319*51188Sbostic 
320*51188Sbostic /*
321*51188Sbostic  * Update the metadata that points to the blocks listed in the FIP
322*51188Sbostic  * array.
323*51188Sbostic  */
324*51188Sbostic static
325*51188Sbostic lfs_updatemeta(fs, ip, fip, bpp)
326*51188Sbostic 	LFS *fs;
327*51188Sbostic 	INODE *ip;
328*51188Sbostic 	FINFO *fip;
329*51188Sbostic 	BUF **bpp;
330*51188Sbostic {
331*51188Sbostic 	SEGUSE *segup;
332*51188Sbostic 	BUF **lbpp, *bp;
333*51188Sbostic 	daddr_t da, iblkno;
334*51188Sbostic 	int error, i, oldsegnum;
335*51188Sbostic 	long lbn, *lbp;
336*51188Sbostic 
337*51188Sbostic printf("lfs_updatemeta\n");
338*51188Sbostic 	for (lbpp= bpp, lbp = fip->fi_blocks, i = 0;
339*51188Sbostic 	    i < fip->fi_nblocks; i++, lbp++, bp++) {
340*51188Sbostic 		lbn = *lbp;
341*51188Sbostic 		if (error = lfs_bmap(ip, lbn, &da))
342*51188Sbostic 			return(error);
343*51188Sbostic 
344*51188Sbostic 		if (da) {
345*51188Sbostic 			oldsegnum = (da - fs->lfs_sboffs[0]) /
346*51188Sbostic 			    fsbtodb(fs, fs->lfs_ssize);
347*51188Sbostic 			segup = fs->lfs_segtab+oldsegnum;
348*51188Sbostic 			segup->su_lastmod = time.tv_sec;
349*51188Sbostic 			if ((segup->su_nbytes -= fs->lfs_bsize) < 0)
350*51188Sbostic 				printf("lfs_updatemeta: negative bytes %s %d\n",
351*51188Sbostic 					"in segment", oldsegnum);
352*51188Sbostic 		}
353*51188Sbostic 
354*51188Sbostic 		/* Now change whoever points to lbn */
355*51188Sbostic 		if (lbn < NDADDR)
356*51188Sbostic 			ip->i_din.di_db[lbn] = (*lbpp)->b_blkno;
357*51188Sbostic 		else if ((lbn -= NDADDR) < NINDIR(fs)) {
358*51188Sbostic printf("lfs_updatemeta: changing indirect block %d\n", S_INDIR);
359*51188Sbostic 			error = bread(ITOV(ip), S_INDIR, fs->lfs_bsize,
360*51188Sbostic 			    NOCRED, &bp);
361*51188Sbostic 			if (error)
362*51188Sbostic 				return(error);
363*51188Sbostic 			bp->b_un.b_daddr[lbn] = (*lbpp)->b_blkno;
364*51188Sbostic 			brelse(bp);
365*51188Sbostic 		} else if ( (lbn = (lbn - NINDIR(fs)) / NINDIR(fs)) <
366*51188Sbostic 			    NINDIR(fs)) {
367*51188Sbostic 
368*51188Sbostic 			iblkno = - (lbn + NIADDR + 1);
369*51188Sbostic printf("lfs_updatemeta: changing indirect block %d\n", iblkno);
370*51188Sbostic 			error = bread(ITOV(ip), iblkno, fs->lfs_bsize, NOCRED,
371*51188Sbostic 			    &bp);
372*51188Sbostic 			if (error)
373*51188Sbostic 				return(error);
374*51188Sbostic 			bp->b_un.b_daddr[lbn % NINDIR(fs)] = (*lbpp)->b_blkno;
375*51188Sbostic 		}
376*51188Sbostic 		else
377*51188Sbostic 			return(EFBIG);
378*51188Sbostic 	}
379*51188Sbostic 	return(0);
380*51188Sbostic }
381*51188Sbostic 
382*51188Sbostic /*
383*51188Sbostic  * Returns 0 if the entire file fit into the current segment and
384*51188Sbostic  * summary region, 1 if not.
385*51188Sbostic  * XXX -- I think we need to figure out what to do if we write
386*51188Sbostic  * the segment and find more dirty blocks when we're done.
387*51188Sbostic  */
388*51188Sbostic static SEGMENT *
389*51188Sbostic lfs_writefile(sp, fs, vp)
390*51188Sbostic 	SEGMENT *sp;
391*51188Sbostic 	LFS *fs;
392*51188Sbostic 	VNODE *vp;
393*51188Sbostic {
394*51188Sbostic 	register BUF *bp;
395*51188Sbostic 	BUF **bpp, *nbp;
396*51188Sbostic 	FINFO *fip;
397*51188Sbostic 	INODE *ip;
398*51188Sbostic 	int db_per_fsb, error, i;
399*51188Sbostic 	int ret_val, s;
400*51188Sbostic 	long *lbp;
401*51188Sbostic 
402*51188Sbostic 	/* initialize the FINFO structure */
403*51188Sbostic 	ip = VTOI(vp);
404*51188Sbostic printf("lfs_writefile: node %d\n", ip->i_number);
405*51188Sbostic loop:
406*51188Sbostic 	fip = sp->fip;
407*51188Sbostic 	fip->fi_nblocks = 0;
408*51188Sbostic 	fip->fi_ino = ip->i_number;
409*51188Sbostic 	fip->fi_version = lfs_getversion(fs, ip->i_number);
410*51188Sbostic 	lbp = fip->fi_blocks;
411*51188Sbostic 
412*51188Sbostic 	bpp = sp->cbpp;
413*51188Sbostic 	s = splbio();
414*51188Sbostic 	for (bp = vp->v_dirtyblkhd; bp; bp = nbp) {
415*51188Sbostic 		nbp = bp->b_blockf;
416*51188Sbostic printf("lfs_writefile: disk block num %d flags %x\n", bp->b_blkno, bp->b_flags);
417*51188Sbostic 		if ((bp->b_flags & B_BUSY))
418*51188Sbostic 			continue;
419*51188Sbostic 		if ((bp->b_flags & B_DELWRI) == 0)
420*51188Sbostic 			panic("lfs_write: not dirty");
421*51188Sbostic 		bremfree(bp);
422*51188Sbostic 		bp->b_flags |= (B_BUSY | B_CALL);
423*51188Sbostic 		bp->b_iodone = lfs_biocallback;
424*51188Sbostic 
425*51188Sbostic 		/* UFS does the bawrites and bwrites here; we don't */
426*51188Sbostic 		*lbp++ = bp->b_lblkno;		/* UPDATE META HERE */
427*51188Sbostic 		*sp->cbpp++ = bp;
428*51188Sbostic 		fip->fi_nblocks++;
429*51188Sbostic 		sp->sum_bytes_left -= sizeof(daddr_t);
430*51188Sbostic 		sp->seg_bytes_left -= bp->b_bufsize;
431*51188Sbostic 		if (sp->sum_bytes_left < sizeof(daddr_t) ||
432*51188Sbostic 		    sp->seg_bytes_left < fs->lfs_bsize) {
433*51188Sbostic 			/*
434*51188Sbostic 			 * We are about to allocate a new summary block
435*51188Sbostic 			 * and possibly a new segment.  So, we need to
436*51188Sbostic 			 * sort the blocks we've done so far, and assign
437*51188Sbostic 			 * the disk addresses, so we can start a new block
438*51188Sbostic 			 * correctly.  We may be doing I/O so we need to
439*51188Sbostic 			 * release the s lock before doing anything.
440*51188Sbostic 			 */
441*51188Sbostic 			splx(s);
442*51188Sbostic 			if (error = lfs_updatemeta(fs, ip, fip, bpp))
443*51188Sbostic 				panic("lfs_writefile: error from lfs_updatemeta\n");
444*51188Sbostic 
445*51188Sbostic 			/* Put this file in the segment summary */
446*51188Sbostic 			((SEGSUM *)(sp->segsum))->ss_nfinfo++;
447*51188Sbostic 
448*51188Sbostic 			if (sp->seg_bytes_left < fs->lfs_bsize) {
449*51188Sbostic 				lfs_writeseg(fs, sp);
450*51188Sbostic 				sp = lfs_newseg(fs);
451*51188Sbostic 			} else if (sp->sum_bytes_left < sizeof(daddr_t))
452*51188Sbostic 				lfs_newsum(fs, sp);
453*51188Sbostic 			fip = sp->fip;
454*51188Sbostic 			s = splbio();
455*51188Sbostic 		}
456*51188Sbostic 
457*51188Sbostic 	}
458*51188Sbostic 	splx(s);
459*51188Sbostic 	db_per_fsb = 1 << fs->lfs_fsbtodb;
460*51188Sbostic 	shellsort(bpp, (u_long *)fip->fi_blocks, fip->fi_nblocks);
461*51188Sbostic 	for (bp = *bpp, i = 0; i < fip->fi_nblocks; i++, bp++) {
462*51188Sbostic 		bp->b_blkno = sp->saddr;
463*51188Sbostic 		sp->saddr += db_per_fsb;
464*51188Sbostic 		/*
465*51188Sbostic 		 * Update the meta data now for this file.  If we've filled
466*51188Sbostic 		 * a segment, then we'll have to wait until the next segment
467*51188Sbostic 		 * to write out the updated metadata.
468*51188Sbostic 		 */
469*51188Sbostic 		lfs_writemeta();
470*51188Sbostic 	}
471*51188Sbostic (void)printf("lfs_writefile: adding %d blocks to segment\n", fip->fi_nblocks);
472*51188Sbostic 	if (fip->fi_nblocks) {
473*51188Sbostic 		((SEGSUM *)(sp->segsum))->ss_nfinfo++;
474*51188Sbostic 		sp->fip = (FINFO *)((u_long)fip + sizeof(FINFO) +
475*51188Sbostic 		    sizeof(u_long) * (fip->fi_nblocks - 1));
476*51188Sbostic 	}
477*51188Sbostic 	return(sp);
478*51188Sbostic }
479*51188Sbostic 
480*51188Sbostic static void
481*51188Sbostic lfs_writemeta()
482*51188Sbostic {
483*51188Sbostic 	printf("lfs_writemeta (STUB)\n");
484*51188Sbostic }
485*51188Sbostic 
486*51188Sbostic static void
487*51188Sbostic lfs_writeseg(fs, sp)
488*51188Sbostic 	LFS *fs;
489*51188Sbostic 	SEGMENT *sp;
490*51188Sbostic {
491*51188Sbostic 	BUF **bpp, *bp;
492*51188Sbostic 	SEGSUM *ssp;
493*51188Sbostic 	SEGUSE *sup;
494*51188Sbostic 	VNODE *devvp;
495*51188Sbostic 	int nblocks, nbuffers, ninode_blocks, nsegsums, nsum_pb;
496*51188Sbostic 	int i, metaoff, nmeta;
497*51188Sbostic 
498*51188Sbostic printf("lfs_writeseg\n");
499*51188Sbostic 	ssp = sp->segsum;
500*51188Sbostic 	nsum_pb = fs->lfs_bsize / LFS_SUMMARY_SIZE;
501*51188Sbostic 	/*
502*51188Sbostic 	 * This is a hack because we're currently allocating summary segments
503*51188Sbostic 	 * in full blocks.  It will go away when we do fragments, when we'll
504*51188Sbostic 	 * allocate fragment sized summary blocks.
505*51188Sbostic 	 */
506*51188Sbostic 	do {
507*51188Sbostic 		sp->sum_num++;
508*51188Sbostic 		lfs_endsum(fs, sp, 0);
509*51188Sbostic 	} while (sp->sum_num % nsum_pb);
510*51188Sbostic 	nbuffers = sp->cbpp - sp->bpp;
511*51188Sbostic 	nsegsums = (sp->sum_num + nsum_pb - 1) / nsum_pb;
512*51188Sbostic 	ninode_blocks = (sp->ninodes + INOPB(fs) - 1)/INOPB(fs);
513*51188Sbostic 
514*51188Sbostic 	/* Do checksum for last segment summary */
515*51188Sbostic 	ssp->ss_cksum = cksum(&ssp->ss_cksum,
516*51188Sbostic 		    LFS_SUMMARY_SIZE - sizeof(ssp->ss_cksum));
517*51188Sbostic 
518*51188Sbostic 	/* Finish off any inodes */
519*51188Sbostic 
520*51188Sbostic 	/*
521*51188Sbostic 	 * Copy inode and summary block buffer pointers down so they are
522*51188Sbostic 	 * contiguous with the page buffer pointers
523*51188Sbostic 	 */
524*51188Sbostic 	nmeta = 1 + ninode_blocks + nsegsums;
525*51188Sbostic 	metaoff = fs->lfs_ssize - nmeta;
526*51188Sbostic 	if (sp->bpp + metaoff != sp->cbpp)
527*51188Sbostic 		bcopy(sp->bpp+metaoff, sp->cbpp, sizeof(BUF *)  * nmeta);
528*51188Sbostic 
529*51188Sbostic 	nblocks = nbuffers + ninode_blocks + nsegsums;
530*51188Sbostic 
531*51188Sbostic 	sup = fs->lfs_segtab + sp->seg_number;
532*51188Sbostic 	sup->su_nbytes = nblocks << fs->lfs_bshift;
533*51188Sbostic 	sup->su_lastmod = time.tv_sec;
534*51188Sbostic 	sup->su_flags = SEGUSE_DIRTY;
535*51188Sbostic 
536*51188Sbostic 	/*
537*51188Sbostic 	 * Since we need to guarantee that our last buffer gets written last,
538*51188Sbostic 	 * we issue the writes in two sets.  The first n-1 buffers first, and
539*51188Sbostic 	 * then, after they've completed, the last 1 buffer.  Only when that
540*51188Sbostic 	 * final write completes is the segment actually written.
541*51188Sbostic 	 */
542*51188Sbostic 	devvp = VFSTOUFS(fs->lfs_ivnode->v_mount)->um_devvp;
543*51188Sbostic /* MIS -- THIS COULD BE BAD IF WE GOT INTERRUPTED IN THE MIDDLE OF THIS */
544*51188Sbostic 	fs->lfs_iocount += nblocks - 1;
545*51188Sbostic 	sp->nextp = fs->lfs_seglist;
546*51188Sbostic 	fs->lfs_seglist = sp;
547*51188Sbostic 	for (bpp = sp->bpp, i = 0; i < (nblocks - 1); i++) {
548*51188Sbostic 		bp = *bpp;
549*51188Sbostic printf("lfs_writeseg: buffer: ino %d lbn %d flags %lx\n", VTOI(bp->b_vp)->i_number, bp->b_lblkno, bp->b_flags);
550*51188Sbostic 		(*(devvp->v_op->vop_strategy))(*bpp++);
551*51188Sbostic 	}
552*51188Sbostic }
553*51188Sbostic 
554*51188Sbostic /*
555*51188Sbostic  * Shellsort (diminishing increment sort) from Data Structures and
556*51188Sbostic  * Algorithms, Aho, Hopcraft and Ullman, 1983 Edition, page 290;
557*51188Sbostic  * see also Knuth Vol. 3, page 84.  The increments are selected from
558*51188Sbostic  * formula (8), page 95.  Roughly O(N^3/2).
559*51188Sbostic  */
560*51188Sbostic /*
561*51188Sbostic  * This is our own private copy of shellsort because we want to sort
562*51188Sbostic  * two parallel arrays (the array of buffer pointers and the array of
563*51188Sbostic  * logical block numbers) simultaneously.  Note that we cast the array
564*51188Sbostic  * of logical block numbers to a unsigned in this routine so that the
565*51188Sbostic  * negative block numbers (meta data blocks) sort AFTER the data blocks.
566*51188Sbostic  */
567*51188Sbostic static void
568*51188Sbostic shellsort(bp_array, lb_array, nmemb)
569*51188Sbostic 	BUF **bp_array;
570*51188Sbostic 	u_long *lb_array;
571*51188Sbostic 	register int nmemb;
572*51188Sbostic {
573*51188Sbostic 	static int __rsshell_increments[] = { 4, 1, 0 };
574*51188Sbostic 	register int incr, *incrp, t1, t2;
575*51188Sbostic 	BUF *bp_temp;
576*51188Sbostic 	u_long lb_temp;
577*51188Sbostic 
578*51188Sbostic 	for (incrp = __rsshell_increments; incr = *incrp++;)
579*51188Sbostic 		for (t1 = incr; t1 < nmemb; ++t1)
580*51188Sbostic 			for (t2 = t1 - incr; t2 >= 0;)
581*51188Sbostic 				if (lb_array[t2] > lb_array[t2 + incr]) {
582*51188Sbostic 					lb_temp = lb_array[t2];
583*51188Sbostic 					lb_array[t2] = lb_array[t2 + incr];
584*51188Sbostic 					lb_array[t2 + incr] = lb_temp;
585*51188Sbostic 					bp_temp = bp_array[t2];
586*51188Sbostic 					bp_array[t2] = bp_array[t2 + incr];
587*51188Sbostic 					bp_array[t2 + incr] = bp_temp;
588*51188Sbostic 					t2 -= incr;
589*51188Sbostic 				} else
590*51188Sbostic 					break;
591*51188Sbostic }
592