1 ;;;; Lisp-side allocation (used currently only for direct allocation
2 ;;;; to static and immobile spaces).
4 ;;;; This software is part of the SBCL system. See the README file for
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
15 #!-sb-fluid
(declaim (inline store-word
))
16 (defun store-word (word base
&optional
(offset 0) (lowtag 0))
17 (declare (type (unsigned-byte #.n-word-bits
) word base offset
)
18 (type (unsigned-byte #.n-lowtag-bits
) lowtag
))
19 (setf (sap-ref-word (int-sap base
) (- (ash offset word-shift
) lowtag
)) word
))
21 (defun allocate-static-vector (widetag length words
)
22 (declare (type (unsigned-byte #.n-widetag-bits
) widetag
)
23 (type (unsigned-byte #.n-word-bits
) words
)
25 ;; WITHOUT-GCING implies WITHOUT-INTERRUPTS
28 (let* ((pointer (sap-int *static-space-free-pointer
*))
29 (vector (logior pointer other-pointer-lowtag
))
30 (nbytes (pad-data-block (+ words vector-data-offset
)))
31 (new-pointer (+ pointer nbytes
)))
32 (when (> static-space-end new-pointer
)
34 vector
0 other-pointer-lowtag
)
35 (store-word (fixnumize length
)
36 vector vector-length-slot other-pointer-lowtag
)
37 (store-word 0 new-pointer
)
38 (setf *static-space-free-pointer
* (int-sap new-pointer
))
39 (%make-lisp-obj vector
))))
40 (error 'simple-storage-condition
41 :format-control
"Not enough memory left in static space to ~
47 (defglobal *immobile-space-mutex
* (sb!thread
:make-mutex
:name
"Immobile space"))
49 (eval-when (:compile-toplevel
)
50 (assert (eql code-code-size-slot
1))
51 (assert (eql code-debug-info-slot
2)))
53 (define-alien-variable "varyobj_holes" long
)
54 (define-alien-variable "varyobj_page_touched_bits" (* (unsigned 32)))
55 (define-alien-variable "varyobj_page_scan_start_offset" (* (unsigned 16)))
56 (define-alien-variable "varyobj_page_gens" (* (unsigned 8)))
57 (define-alien-routine "find_preceding_object" long
(where long
))
59 ;;; Lazily created freelist, used only when unallocate is called:
60 ;;; A cons whose car is a sorted list of hole sizes available
61 ;;; and whose cdr is a hashtable.
62 ;;; The keys in the hashtable are hole sizes, values are lists of holes.
63 ;;; A better structure would be just a sorted array of sizes
64 ;;; with each entry pointing to the holes which are threaded through
65 ;;; some bytes in the storage itself rather than through cons cells.
66 (!defglobal
*immobile-freelist
* nil
)
68 ;;; Return the zero-based index within the varyobj subspace of immobile space.
69 (defun varyobj-page-index (address)
70 (declare (type (and fixnum unsigned-byte
) address
))
71 (values (floor (- address varyobj-space-start
) immobile-card-bytes
)))
73 (defun varyobj-page-address (index)
74 (+ varyobj-space-start
(* index immobile-card-bytes
)))
76 ;;; Convert a zero-based varyobj page index into a scan start address.
77 (defun varyobj-page-scan-start (index)
78 (- (+ varyobj-space-start
(* (1+ index
) immobile-card-bytes
))
79 (* 2 n-word-bytes
(deref varyobj-page-scan-start-offset index
))))
81 (declaim (inline hole-p
))
82 (defun hole-p (raw-address)
83 (eql (sap-ref-32 (int-sap raw-address
) 0)
84 (logior (ash 2 n-widetag-bits
) code-header-widetag
)))
86 (defun freed-hole-p (address)
88 ;; A hole is not considered to have been freed until it is
89 ;; no longer in the chain of objects linked through
90 ;; the debug_info slot.
91 (eql (sap-ref-word (int-sap address
)
92 (ash code-debug-info-slot word-shift
))
95 (declaim (inline hole-size
))
96 (defun hole-size (hole-address) ; in bytes
97 (+ (sap-ref-lispobj (int-sap hole-address
) (ash code-code-size-slot word-shift
))
98 (ash 2 word-shift
))) ; add 2 boxed words
100 (declaim (inline (setf hole-size
)))
101 (defun (setf hole-size
) (new-size hole
) ; NEW-SIZE is in bytes
102 (setf (sap-ref-lispobj (int-sap hole
) (ash code-code-size-slot word-shift
))
103 (- new-size
(ash 2 word-shift
)))) ; account for 2 boxed words
105 (declaim (inline hole-end-address
))
106 (defun hole-end-address (hole-address)
107 (+ hole-address
(hole-size hole-address
)))
109 (defun sorted-list-insert (item list key-fn
)
110 (declare (function key-fn
))
111 (let ((key (funcall key-fn item
)) (tail list
) prev
)
114 (let ((new-tail (list item
)))
115 (return (cond ((not prev
) new-tail
)
116 (t (setf (cdr prev
) new-tail
) list
)))))
117 (let ((head (car tail
)))
118 (when (< key
(funcall key-fn head
))
120 (rplacd tail
(cons head
(cdr tail
)))
122 (setq prev tail tail
(cdr tail
)))))
124 ;;; These routines are not terribly efficient, but very straightforward
125 ;;; since we can assume the existence of hashtables.
126 (defun add-to-freelist (hole)
127 (let* ((size (hole-size hole
))
128 (freelist *immobile-freelist
*)
129 (table (cdr freelist
))
130 (old (gethash (hole-size hole
) table
)))
131 ;; Check for double-free error
132 #!+immobile-space-debug
(aver (not (member hole
(gethash size table
))))
135 (sorted-list-insert size
(car freelist
) #'identity
)))
136 (setf (gethash size table
) (cons hole old
))))
138 (defun remove-from-freelist (hole)
139 (let* ((key (hole-size hole
))
140 (freelist *immobile-freelist
*)
141 (table (cdr freelist
))
142 (list (gethash key table
))
143 (old-length (length list
))
144 (new (delete hole list
:count
1)))
145 (declare (ignorable old-length
))
146 #!+immobile-space-debug
(aver (= (length new
) (1- old-length
)))
148 (setf (gethash key table
) new
))
150 (setf (car freelist
) (delete key
(car freelist
) :count
1))
151 (remhash key table
)))))
153 (defun find-in-freelist (size test
)
154 (let* ((freelist *immobile-freelist
*)
157 (let ((sizes (member size
(car freelist
) :test
'<=)))
159 (return-from find-in-freelist nil
))
162 (found (car (gethash hole-size
(cdr freelist
)))))
164 (remove-from-freelist found
))
167 (defun set-varyobj-space-free-pointer (free-ptr)
168 (declare (type (and fixnum unsigned-byte
) free-ptr
))
169 (setq *varyobj-space-free-pointer
* (int-sap free-ptr
))
170 ;; When the free pointer is not page-aligned - it usually won't be -
171 ;; then we create an unboxed array from the pointer to the page end
172 ;; so that it appears as one contiguous object when scavenging.
173 ;; instead of a bunch of cons cells.
174 (when (logtest free-ptr
(1- immobile-card-bytes
))
175 (let ((n-trailing-bytes
176 (- (nth-value 1 (ceiling free-ptr immobile-card-bytes
)))))
177 (setf (sap-ref-word (int-sap free-ptr
) 0) simple-array-fixnum-widetag
178 (sap-ref-word (int-sap free-ptr
) n-word-bytes
)
179 ;; Convert bytes to words, subtract the header and vector length.
180 (ash (- (ash n-trailing-bytes
(- word-shift
)) 2)
181 n-fixnum-tag-bits
)))))
183 (defun unallocate (hole)
184 #!+immobile-space-debug
185 (awhen *in-use-bits
* (mark-range it hole
(hole-size hole
) nil
))
186 (let* ((hole-end (hole-end-address hole
))
187 (end-is-free-ptr (eql hole-end
(sap-int *varyobj-space-free-pointer
*))))
188 ;; First, ensure that no page's scan-start points to this hole.
189 ;; For smaller-than-page objects, this will do nothing if the hole
190 ;; was not the scan-start. For larger-than-page, we have to update
191 ;; a range of pages. Example:
192 ;; | page1 | page2 | page3 | page4 |
193 ;; |-- hole A ------ | -- hole B --
194 ;; If page1 had an object preceding the hole, then it is not empty,
195 ;; but if it pointed to the hole, and the hole extended to the end
196 ;; of the first page, then that page is empty.
197 ;; Pages (1+ first-page) through (1- last-page) inclusive
198 ;; must become empty. last-page may or may not be depending
199 ;; on whether another object can be found on it.
200 (let ((first-page (varyobj-page-index hole
))
201 (last-page (varyobj-page-index (1- hole-end
))))
202 (when (and (eql (varyobj-page-scan-start first-page
) hole
)
203 (< first-page last-page
))
204 (setf (deref varyobj-page-scan-start-offset first-page
) 0))
205 (loop for page from
(1+ first-page
) below last-page
206 do
(setf (deref varyobj-page-scan-start-offset page
) 0))
207 ;; Only touch the offset for the last page if it pointed to this hole.
208 ;; If the following object is a hole that is in the pending free list,
209 ;; it's ok, but if it's a hole that is already in the freelist,
210 ;; it's not OK, so look beyond that object. We don't have to iterate,
211 ;; since there can't be two consecutive holes - so it's either the
212 ;; object after this hole, or the one after that.
213 (when (eql (varyobj-page-scan-start last-page
) hole
)
214 (let* ((page-end (varyobj-page-address (1+ last-page
)))
215 (new-scan-start (cond (end-is-free-ptr page-end
)
216 ((freed-hole-p hole-end
)
217 (hole-end-address hole-end
))
219 (setf (deref varyobj-page-scan-start-offset last-page
)
220 (if (< new-scan-start page-end
)
221 ;; Compute new offset backwards relative to the page end.
222 (/ (- page-end new-scan-start
) (* 2 n-word-bytes
))
223 0))))) ; Page becomes empty
225 (unless *immobile-freelist
*
226 (setf *immobile-freelist
* (cons nil
(make-hash-table :test
#'eq
))))
228 ;; find-preceding is the most expensive operation in this sequence
229 ;; of steps. Not sure how to improve it, but I doubt it's a problem.
230 (let* ((predecessor (find-preceding-object hole
))
231 (pred-is-free (and (not (eql predecessor
0))
232 (freed-hole-p predecessor
))))
234 (remove-from-freelist predecessor
)
235 (setf hole predecessor
))
236 (when end-is-free-ptr
237 ;; Give back space below the free pointer for better space conservation.
238 ;; Consider when the hole touching the free pointer is equal in size
239 ;; to another hole that could have been used instead. Taking space at
240 ;; the free pointer diminishes the opportunity to use the frontier
241 ;; to later allocate a larger object that would not have fit
242 ;; into any existing hole.
243 (set-varyobj-space-free-pointer hole
)
244 (return-from unallocate
))
245 (let* ((successor hole-end
)
246 (succ-is-free (freed-hole-p successor
)))
248 (setf hole-end
(hole-end-address successor
))
249 (remove-from-freelist successor
)))
250 ;; The hole must be an integral number of doublewords.
251 (aver (zerop (rem (- hole-end hole
) 16)))
252 (setf (hole-size hole
) (- hole-end hole
))))
253 (add-to-freelist hole
))
255 (defun allocate-immobile-bytes (n-bytes word0 word1 lowtag
)
256 (declare (type (and fixnum unsigned-byte
) n-bytes
))
257 (setq n-bytes
(logandc2 (+ n-bytes
(1- (* 2 n-word-bytes
)))
258 (1- (* 2 n-word-bytes
))))
259 ;; Can't allocate fewer than 4 words due to min hole size.
260 (aver (>= n-bytes
(* 4 n-word-bytes
)))
261 (sb!thread
::with-system-mutex
(*immobile-space-mutex
* :without-gcing t
)
262 (unless (zerop varyobj-holes
)
263 ;; If deferred sweep needs to happen, do so now.
264 ;; Concurrency could potentially be improved here: at most one thread
265 ;; should do this step, but it doesn't need to be exclusive with GC
266 ;; as long as we can atomically pop items off the list of holes.
267 (let ((hole-addr varyobj-holes
))
268 (setf varyobj-holes
0)
270 (let ((next (sap-ref-word (int-sap hole-addr
)
271 (ash code-debug-info-slot word-shift
))))
272 (setf (sap-ref-word (int-sap hole-addr
)
273 (ash code-debug-info-slot word-shift
))
275 (unallocate hole-addr
)
276 (if (eql (setq hole-addr next
) 0) (return))))))
278 (or (and *immobile-freelist
*
279 (or (find-in-freelist n-bytes
'=) ; 1. Exact match?
280 ;; 2. Try splitting a hole, adding some slack so that
281 ;; both pieces can potentially be used.
282 (let ((found (find-in-freelist (+ n-bytes
192) '<=)))
284 (let* ((actual-size (hole-size found
))
285 (remaining (- actual-size n-bytes
)))
286 (aver (zerop (rem actual-size
16)))
287 (setf (hole-size found
) remaining
) ; Shorten the lower piece
288 (add-to-freelist found
)
289 (+ found remaining
)))))) ; Consume the upper piece
290 ;; 3. Extend the frontier.
291 (let* ((addr (sap-int *varyobj-space-free-pointer
*))
292 (free-ptr (+ addr n-bytes
))
293 (limit (+ varyobj-space-start varyobj-space-size
)))
294 (when (> free-ptr limit
)
295 (format t
"~&Immobile space exhausted~%")
297 (set-varyobj-space-free-pointer free-ptr
)
299 (aver (not (logtest addr lowtag-mask
))) ; Assert proper alignment
300 ;; Compute the start and end of the first page consumed.
301 (let* ((page-start (logandc2 addr
(1- immobile-card-bytes
)))
302 (page-end (+ page-start immobile-card-bytes
))
303 (index (varyobj-page-index addr
))
304 (obj-end (+ addr n-bytes
)))
305 ;; Mark the page as being used by a nursery object.
306 (setf (deref varyobj-page-gens index
)
307 (logior (deref varyobj-page-gens index
) 1))
308 ;; On the object's first page, set the scan start only if addr
309 ;; is lower than the current page-scan-start object.
310 ;; Note that offsets are expressed in doublewords backwards from
311 ;; page end, so that we can direct the scan start to any doubleword
312 ;; on the page or in the preceding 1MiB (approximately).
313 (when (< addr
(varyobj-page-scan-start index
))
314 (setf (deref varyobj-page-scan-start-offset index
)
315 (ash (- page-end addr
) (- (1+ word-shift
)))))
316 ;; On subsequent pages, always set the scan start, since there can not
317 ;; be a lower-addressed object touching those pages.
319 (setq page-start page-end
)
320 (incf page-end immobile-card-bytes
)
322 (when (>= page-start obj-end
) (return))
323 (setf (deref varyobj-page-scan-start-offset index
)
324 (ash (- page-end addr
) (- (1+ word-shift
))))))
325 #!+immobile-space-debug
; "address sanitizer"
326 (awhen *in-use-bits
* (mark-range it addr n-bytes t
))
327 (setf (sap-ref-word (int-sap addr
) 0) word0
328 (sap-ref-word (int-sap addr
) n-word-bytes
) word1
)
329 ;; 0-fill the remainder of the object
330 (#!+64-bit system-area-ub64-fill
331 #!-
64-bit system-area-ub32-fill
332 0 (int-sap addr
) 2 (- (ash n-bytes
(- word-shift
)) 2))
333 (%make-lisp-obj
(logior addr lowtag
)))))
335 (defun allocate-immobile-vector (widetag length words
)
336 (allocate-immobile-bytes (pad-data-block (+ words vector-data-offset
))
339 other-pointer-lowtag
))
341 (defun allocate-immobile-simple-vector (n-elements)
342 (allocate-immobile-vector simple-vector-widetag n-elements n-elements
))
343 (defun allocate-immobile-bit-vector (n-elements)
344 (allocate-immobile-vector simple-bit-vector-widetag n-elements
345 (ceiling n-elements n-word-bits
)))
346 (defun allocate-immobile-byte-vector (n-elements)
347 (allocate-immobile-vector simple-array-unsigned-byte-8-widetag n-elements
348 (ceiling n-elements n-word-bytes
)))
349 (defun allocate-immobile-word-vector (n-elements)
350 (allocate-immobile-vector #!+64-bit simple-array-unsigned-byte-64-widetag
351 #!-
64-bit simple-array-unsigned-byte-32-widetag
352 n-elements n-elements
))
354 ;;; This is called when we're already inside WITHOUT-GCing
355 (defun allocate-immobile-code (n-boxed-words n-unboxed-bytes
)
356 (let* ((unrounded-header-n-words (+ code-constants-offset n-boxed-words
))
357 (rounded-header-words (* 2 (ceiling unrounded-header-n-words
2)))
358 (total-bytes (+ (* rounded-header-words n-word-bytes
)
359 (logandc2 (+ n-unboxed-bytes lowtag-mask
) lowtag-mask
)))
360 (code (allocate-immobile-bytes
362 (logior (ash rounded-header-words n-widetag-bits
) code-header-widetag
)
363 (ash n-unboxed-bytes n-fixnum-tag-bits
)
364 other-pointer-lowtag
)))
365 (setf (%code-debug-info code
) nil
)