xref: /csrg-svn/lib/libc/stdlib/malloc.c (revision 13259)
1*13259Sroot #ifndef lint
2*13259Sroot static char sccsid[] = "@(#)malloc.c	4.1 (Berkeley) 06/22/83";
3*13259Sroot #endif
4*13259Sroot #ifdef debug
5*13259Sroot #define ASSERT(p) if(!(p))botch("p");else
6*13259Sroot botch(s)
7*13259Sroot char *s;
8*13259Sroot {
9*13259Sroot 	printf("assertion botched: %s\n",s);
10*13259Sroot 	abort();
11*13259Sroot }
12*13259Sroot #else
13*13259Sroot #define ASSERT(p)
14*13259Sroot #endif
15*13259Sroot 
16*13259Sroot /*	avoid break bug */
17*13259Sroot #ifdef pdp11
18*13259Sroot #define GRANULE 64
19*13259Sroot #else
20*13259Sroot #define GRANULE 0
21*13259Sroot #endif
22*13259Sroot /*	C storage allocator
23*13259Sroot  *	circular first-fit strategy
24*13259Sroot  *	works with noncontiguous, but monotonically linked, arena
25*13259Sroot  *	each block is preceded by a ptr to the (pointer of)
26*13259Sroot  *	the next following block
27*13259Sroot  *	blocks are exact number of words long
28*13259Sroot  *	aligned to the data type requirements of ALIGN
29*13259Sroot  *	pointers to blocks must have BUSY bit 0
30*13259Sroot  *	bit in ptr is 1 for busy, 0 for idle
31*13259Sroot  *	gaps in arena are merely noted as busy blocks
32*13259Sroot  *	last block of arena (pointed to by alloct) is empty and
33*13259Sroot  *	has a pointer to first
34*13259Sroot  *	idle blocks are coalesced during space search
35*13259Sroot  *
36*13259Sroot  *	a different implementation may need to redefine
37*13259Sroot  *	ALIGN, NALIGN, BLOCK, BUSY, INT
38*13259Sroot  *	where INT is integer type to which a pointer can be cast
39*13259Sroot */
40*13259Sroot #define INT int
41*13259Sroot #define ALIGN int
42*13259Sroot #define NALIGN 1
43*13259Sroot #define WORD sizeof(union store)
44*13259Sroot #define BLOCK 1024	/* a multiple of WORD*/
45*13259Sroot #define BUSY 1
46*13259Sroot #define NULL 0
47*13259Sroot #define testbusy(p) ((INT)(p)&BUSY)
48*13259Sroot #define setbusy(p) (union store *)((INT)(p)|BUSY)
49*13259Sroot #define clearbusy(p) (union store *)((INT)(p)&~BUSY)
50*13259Sroot 
51*13259Sroot union store { union store *ptr;
52*13259Sroot 	      ALIGN dummy[NALIGN];
53*13259Sroot 	      int calloc;	/*calloc clears an array of integers*/
54*13259Sroot };
55*13259Sroot 
56*13259Sroot static	union store allocs[2];	/*initial arena*/
57*13259Sroot static	union store *allocp;	/*search ptr*/
58*13259Sroot static	union store *alloct;	/*arena top*/
59*13259Sroot static	union store *allocx;	/*for benefit of realloc*/
60*13259Sroot char	*sbrk();
61*13259Sroot 
62*13259Sroot char *
63*13259Sroot malloc(nbytes)
64*13259Sroot unsigned nbytes;
65*13259Sroot {
66*13259Sroot 	register union store *p, *q;
67*13259Sroot 	register nw;
68*13259Sroot 	static temp;	/*coroutines assume no auto*/
69*13259Sroot 
70*13259Sroot 	if(allocs[0].ptr==0) {	/*first time*/
71*13259Sroot 		allocs[0].ptr = setbusy(&allocs[1]);
72*13259Sroot 		allocs[1].ptr = setbusy(&allocs[0]);
73*13259Sroot 		alloct = &allocs[1];
74*13259Sroot 		allocp = &allocs[0];
75*13259Sroot 	}
76*13259Sroot 	nw = (nbytes+WORD+WORD-1)/WORD;
77*13259Sroot 	ASSERT(allocp>=allocs && allocp<=alloct);
78*13259Sroot 	ASSERT(allock());
79*13259Sroot 	for(p=allocp; ; ) {
80*13259Sroot 		for(temp=0; ; ) {
81*13259Sroot 			if(!testbusy(p->ptr)) {
82*13259Sroot 				while(!testbusy((q=p->ptr)->ptr)) {
83*13259Sroot 					ASSERT(q>p&&q<alloct);
84*13259Sroot 					p->ptr = q->ptr;
85*13259Sroot 				}
86*13259Sroot 				if(q>=p+nw && p+nw>=p)
87*13259Sroot 					goto found;
88*13259Sroot 			}
89*13259Sroot 			q = p;
90*13259Sroot 			p = clearbusy(p->ptr);
91*13259Sroot 			if(p>q)
92*13259Sroot 				ASSERT(p<=alloct);
93*13259Sroot 			else if(q!=alloct || p!=allocs) {
94*13259Sroot 				ASSERT(q==alloct&&p==allocs);
95*13259Sroot 				return(NULL);
96*13259Sroot 			} else if(++temp>1)
97*13259Sroot 				break;
98*13259Sroot 		}
99*13259Sroot 		temp = ((nw+BLOCK/WORD)/(BLOCK/WORD))*(BLOCK/WORD);
100*13259Sroot 		q = (union store *)sbrk(0);
101*13259Sroot 		if(q+temp+GRANULE < q) {
102*13259Sroot 			return(NULL);
103*13259Sroot 		}
104*13259Sroot 		q = (union store *)sbrk(temp*WORD);
105*13259Sroot 		if((INT)q == -1) {
106*13259Sroot 			return(NULL);
107*13259Sroot 		}
108*13259Sroot 		ASSERT(q>alloct);
109*13259Sroot 		alloct->ptr = q;
110*13259Sroot 		if(q!=alloct+1)
111*13259Sroot 			alloct->ptr = setbusy(alloct->ptr);
112*13259Sroot 		alloct = q->ptr = q+temp-1;
113*13259Sroot 		alloct->ptr = setbusy(allocs);
114*13259Sroot 	}
115*13259Sroot found:
116*13259Sroot 	allocp = p + nw;
117*13259Sroot 	ASSERT(allocp<=alloct);
118*13259Sroot 	if(q>allocp) {
119*13259Sroot 		allocx = allocp->ptr;
120*13259Sroot 		allocp->ptr = p->ptr;
121*13259Sroot 	}
122*13259Sroot 	p->ptr = setbusy(allocp);
123*13259Sroot 	return((char *)(p+1));
124*13259Sroot }
125*13259Sroot 
126*13259Sroot /*	freeing strategy tuned for LIFO allocation
127*13259Sroot */
128*13259Sroot free(ap)
129*13259Sroot register char *ap;
130*13259Sroot {
131*13259Sroot 	register union store *p = (union store *)ap;
132*13259Sroot 
133*13259Sroot 	ASSERT(p>clearbusy(allocs[1].ptr)&&p<=alloct);
134*13259Sroot 	ASSERT(allock());
135*13259Sroot 	allocp = --p;
136*13259Sroot 	ASSERT(testbusy(p->ptr));
137*13259Sroot 	p->ptr = clearbusy(p->ptr);
138*13259Sroot 	ASSERT(p->ptr > allocp && p->ptr <= alloct);
139*13259Sroot }
140*13259Sroot 
141*13259Sroot /*	realloc(p, nbytes) reallocates a block obtained from malloc()
142*13259Sroot  *	and freed since last call of malloc()
143*13259Sroot  *	to have new size nbytes, and old content
144*13259Sroot  *	returns new location, or 0 on failure
145*13259Sroot */
146*13259Sroot 
147*13259Sroot char *
148*13259Sroot realloc(p, nbytes)
149*13259Sroot register union store *p;
150*13259Sroot unsigned nbytes;
151*13259Sroot {
152*13259Sroot 	register union store *q;
153*13259Sroot 	union store *s, *t;
154*13259Sroot 	register unsigned nw;
155*13259Sroot 	unsigned onw;
156*13259Sroot 
157*13259Sroot 	if(testbusy(p[-1].ptr))
158*13259Sroot 		free((char *)p);
159*13259Sroot 	onw = p[-1].ptr - p;
160*13259Sroot 	q = (union store *)malloc(nbytes);
161*13259Sroot 	if(q==NULL || q==p)
162*13259Sroot 		return((char *)q);
163*13259Sroot 	s = p;
164*13259Sroot 	t = q;
165*13259Sroot 	nw = (nbytes+WORD-1)/WORD;
166*13259Sroot 	if(nw<onw)
167*13259Sroot 		onw = nw;
168*13259Sroot 	while(onw--!=0)
169*13259Sroot 		*t++ = *s++;
170*13259Sroot 	if(q<p && q+nw>=p)
171*13259Sroot 		(q+(q+nw-p))->ptr = allocx;
172*13259Sroot 	return((char *)q);
173*13259Sroot }
174*13259Sroot 
175*13259Sroot #ifdef debug
176*13259Sroot allock()
177*13259Sroot {
178*13259Sroot #ifdef longdebug
179*13259Sroot 	register union store *p;
180*13259Sroot 	int x;
181*13259Sroot 	x = 0;
182*13259Sroot 	for(p= &allocs[0]; clearbusy(p->ptr) > p; p=clearbusy(p->ptr)) {
183*13259Sroot 		if(p==allocp)
184*13259Sroot 			x++;
185*13259Sroot 	}
186*13259Sroot 	ASSERT(p==alloct);
187*13259Sroot 	return(x==1|p==allocp);
188*13259Sroot #else
189*13259Sroot 	return(1);
190*13259Sroot #endif
191*13259Sroot }
192*13259Sroot #endif
193