;;(declaim (inline ,el (setf ,el)))
(defun ,el (ptr &optional (index 0))
(declare (optimize (speed 3)))
- (sb-sys:without-gcing
+ (sb-sys:with-pinned-objects (ptr)
,(template 'prog1 nil)))
(defconstant ,(intern (format nil "OFFSET-OF-~A" el)) ,offset)
(defun (setf ,el) (newval ptr &optional (index 0))
(declare (optimize (speed 3)))
- (sb-sys:without-gcing
+ (sb-sys:with-pinned-objects (ptr)
,(template 'setf 'newval)))))))
(loop for i from 0 to 3
do (setf (sockint::in-addr-addr packed-addr i) (elt address i)))
(make-host-ent
- (sb-sys:without-gcing
+ (sb-sys:with-pinned-objects (packed-addr)
(sockint::gethostbyaddr (sockint::array-data-address packed-addr)
4
sockint::af-inet)))))
(defmethod socket-bind ((socket socket)
&rest address)
(let ((sockaddr (apply #'make-sockaddr-for socket nil address)))
- (if (= (sb-sys:without-gcing
+ (if (= (sb-sys:with-pinned-objects (sockaddr)
(sockint::bind (socket-file-descriptor socket)
(sockint::array-data-address sockaddr)
(size-of-sockaddr socket)))
values"))
(defmethod socket-accept ((socket socket))
- (let* ((sockaddr (make-sockaddr-for socket))
- (fd (sb-sys:without-gcing
- (sockint::accept (socket-file-descriptor socket)
- (sockint::array-data-address sockaddr)
- (size-of-sockaddr socket)))))
- (apply #'values
- (if (= fd -1)
- (socket-error "accept")
- (let ((s (make-instance (class-of socket)
- :type (socket-type socket)
- :protocol (socket-protocol socket)
- :descriptor fd)))
- (sb-ext:finalize s (lambda () (sockint::close fd)))))
- (multiple-value-list (bits-of-sockaddr socket sockaddr)))))
-
+ (let ((sockaddr (make-sockaddr-for socket)))
+ (sb-ext::with-pointers-preserved (sockaddr)
+ (let ((fd (sockint::accept (socket-file-descriptor socket)
+ (sockint::array-data-address sickint)
+ (size-of-sockaddr socket))))
+ (apply #'values
+ (if (= fd -1)
+ (socket-error "accept")
+ (let ((s (make-instance (class-of socket)
+ :type (socket-type socket)
+ :protocol (socket-protocol socket)
+ :descriptor fd)))
+ (sb-ext:finalize s (lambda () (sockint::close fd)))))
+ (multiple-value-list (bits-of-sockaddr socket sockaddr)))))))
+
(defgeneric socket-connect (socket &rest address)
(:documentation "Perform the connect(2) call to connect SOCKET to a
remote PEER. No useful return value."))
(defmethod socket-connect ((socket socket) &rest peer)
(let* ((sockaddr (apply #'make-sockaddr-for socket nil peer)))
- (if (= (sb-sys:without-gcing
+ (if (= (sb-sys:with-pinned-objects (sockaddr)
(sockint::connect (socket-file-descriptor socket)
(sockint::array-data-address sockaddr)
(size-of-sockaddr socket)))
(defmethod socket-peername ((socket socket))
(let* ((sockaddr (make-sockaddr-for socket)))
- (when (= (sb-sys:without-gcing
+ (when (= (sb-sys:with-pinned-objects (sockaddr)
(sockint::getpeername (socket-file-descriptor socket)
(sockint::array-data-address sockaddr)
(size-of-sockaddr socket)))
(defmethod socket-name ((socket socket))
(let* ((sockaddr (make-sockaddr-for socket)))
- (when (= (sb-sys:without-gcing
+ (when (= (sb-sys:with-pinned-objects (sockaddr)
(sockint::getsockname (socket-file-descriptor socket)
(sockint::array-data-address sockaddr)
(size-of-sockaddr socket)))
(setf buffer (make-array length :element-type element-type)))
(sb-alien:with-alien ((sa-len (array (sb-alien:unsigned 32) 2)))
(setf (sb-alien:deref sa-len 0) (size-of-sockaddr socket))
- (sb-sys:without-gcing
+ (sb-sys:with-pinned-objects (buffer sockaddr)
(let ((len
(sockint::recvfrom (socket-file-descriptor socket)
(sockint::array-data-address buffer)
(and (slot-boundp socket 'stream) (slot-value socket 'stream))))
(unless stream
(setf stream (apply #'sb-sys:make-fd-stream
- (socket-file-descriptor socket) args))
+ (socket-file-descriptor socket)
+ :name "a constant string"
+ args))
(setf (slot-value socket 'stream) stream)
(sb-ext:cancel-finalization socket))
stream))
<sect2><title>Threading (a.k.a Multiprocessing)</>
-<para>&SBCL; (as of version 0.x.y, on Linux x86 only) supports a
+<para>&SBCL; (as of version 0.8.3, on Linux x86 only) supports a
fairly low-level threading interface that maps onto the host operating
system's concept of threads or lightweight processes.
<para>&SBCL; at present will alway have at least two tasks running as
seen from Linux: when the first process has done startup
initialization (mapping files in place, installing signal handlers
-etc) it creates a new thread to run the Lisp startup and initial listener.
-The original thread is then used to run GC and to reap dead subthreads
-when they exit.
+etc) it creates a new thread to run the Lisp startup and initial
+listener. The original thread stays around to reap dead subthreads
+and deallocate their resources (e.g. stacks) when they exit.
<para>Garbage collection is done with the existing Conservative
Generational GC. Allocation is done in small (typically 8k) regions :
each thread has its own region so this involves no stopping. However,
when a region fills, a lock must be obtained while another is
allocated, and when a collection is required, all processes are
-stopped. This is achieved using <function>ptrace()</function>, so you
-should be very careful if you wish to examine an &SBCL; worker thread
-using <command>strace</command>, <command>truss</command>,
-<command>gdb</command> or similar. It may be prudent to disable GC
-before doing so.
+stopped. This is achieved by sending them signals, which may make for
+interesting behaviour if they are interrupted in system calls. The
+streams interface is believed to handle the required system call
+restarting correctly, but this may be a consideration when making
+other blocking calls e.g. from foreign library code.
<para>Large amounts of the &SBCL; library have not been inspected for
thread-safety. Some of the obviously unsafe areas have large locks
process group, including Lisp threads that &SBCL; considers to be
notionally `background'. This is undesirable, so background threads
are set to ignore the SIGINT signal. Arbitration for the input stream
-is managed by locking on sb-thread::*session-lock*
+is managed by locking on <varname>sb-thread::*session-lock*</varname>
<para>A thread can be created in a new Lisp 'session' (new terminal or
window) using <function>sb-thread:make-listener-thread</function>.
</para></listitem>
</itemizedlist>
-<para>&SBCL;, like &CMUCL; before it,
-relies primarily on the automatic conversion and direct manipulation
-approaches. Foreign values of simple scalar types are automatically
-converted, complex types are directly manipulated in their foreign
-representation. Furthermore, Lisp strings are represented internally
-with null termination bytes so that they can be passed directly to
-C interfaces without allocating new zero-terminated copies.</para>
+<para>&SBCL;, like &CMUCL; before it, relies primarily on the
+automatic conversion and direct manipulation approaches. The SB-ALIEN
+package provices a facility wherein foreign values of simple scalar
+types are automatically converted and complex types are directly
+manipulated in their foreign representation. Additionally the
+lower-level System Area Pointers (or SAPs) can be used where
+necessary to provide untyped access to foreign memory.</para>
<para>Any foreign objects that can't automatically be converted into
Lisp values are represented by objects of type <type>alien-value</>.
null-terminated string, and is automatically converted into a
Lisp string when accessed; or if the pointer is C <literal>NULL</>
or <literal>0</>, then accessing it gives Lisp <literal>nil</>.
+ Lisp strings are stored with a trailing NUL termination, so no
+ copying (either by the user or the implementation) is necessary
+ when passing them to foreign code.
</para>
<para>
Assigning a Lisp string to a <type>c-string</> structure field or
not be a compile-time constant (but only constant slot accesses are
efficiently compiled.)</para>
-</sect2>
+<sect3><title>Untyped memory</>
+
+<para>As noted at the beginning of the chapter, the System Area
+Pointer facilities allow untyped access to foreign memory. SAPs can
+be converted to and from the usual typed foreign values using
+<function>sap-alien</function> and <function>alien-sap</function>
+(described elsewhere), and also to and from integers - raw machine
+addresses. They should thus be used with caution; corrupting the Lisp
+heap or other memory with SAPs is trivial.</para>
+
+<synopsis>(sb-sys:int-sap machine-address)</>
+
+<para>Creates a SAP pointing at the virtual address
+<varname>machine-address</varname>. </para>
+
+<synopsis>(sb-sys:sap-ref-32 sap offset)</>
+
+<para>Access the value of the memory location at
+<varname>offset</varname> bytes from <varname>sap</varname>. This form
+may also be used with <function>setf</function> to alter the memory at
+that location.</para>
+
+<synopsis>(sb-sys:sap= sap1 sap2)</>
+
+<para>Compare <varname>sap1</varname> and <varname>sap2</varname> for
+equality.</para>
+
+<para>Similarly named functions exist for accessing other sizes of
+word, other comparisons, and other conversions. The reader is invited
+to use <function>apropos</function> and <function>describe</function>
+for more details</para>
+<programlisting>
+(apropos "sap" :sb-sys)
+</programlisting>
+</sect3></sect2>
<sect2><title>Coercing Foreign Values</>
<para>The <function>sb-alien:sap-alien</> function converts <varname>sap</>
(a system area pointer) to a foreign value with the specified
<varname>type</>. <varname>type</> is not evaluated.
-As of &SBCL; 0.7.6, it looks as though this and other SAP functionality
-may become deprecated, since it shouldn't be needed by user code.
</para>
<para>The <varname>type</> must be some foreign pointer, array, or
<para>The <function>sb-alien:alien-sap</> function
returns the SAP which points to <varname>alien-value</>'s data.
-As of &SBCL; 0.7.6, it looks as though this and other SAP functionality
-may become deprecated, since it shouldn't be needed by user code.
</para>
<para>The <varname>foreign-value</> must be of some foreign pointer,
<para>
The foreign function call interface allows a Lisp program to call
-functions written in other languages using the C calling convention.
+many functions written in languages that use the C calling convention.
</para>
<para>
-Lisp sets up various interrupt handling routines and other environment
+Lisp sets up various signal handling routines and other environment
information when it first starts up, and expects these to be in place
-at all times. The C functions called by Lisp should either not change
-the environment, especially the interrupt entry points, or should make
-sure that these entry points are restored when the C function returns
-to Lisp. If a C function makes changes without restoring things to the
-way they were when the C function was entered, there is no telling
-what will happen.
-</para>
+at all times. The C functions called by Lisp should not change the
+environment, especially the signal handlers: the signal handlers
+installed by Lisp typically have interesting flags set (e.g to request
+machine context information, or for signal delivery on an alternate
+stack) which the Lisp runtime relies on for correct operation.
+Precise details of how this works may change without notice between
+versions; the source, or the brain of a friendly &SBCL; developer,
+is the only documentation. Users of a Lisp built with the :sb-thread
+feature should also read the Threading section
+<!-- FIXME I'm sure docbook has some syntax for internal links -->
+of this manual</para>
<sect2><title>The <function>alien-funcall</> Primitive</title>
arguments must be valid &SBCL; object descriptors (so that
e.g. fixnums must be
left-shifted by 2.) As of &SBCL; 0.7.5, the format
-of object descriptors is documented only by the source code and
+of object descriptors is documented only by the source code and, in parts,
by the old &CMUCL; "INTERNALS" documentation.</para>
<para> Note that the garbage collector moves objects, and won't be
-able to fix up any references in C variables, so either turn GC off or
-don't keep Lisp pointers in C data unless they are to statically
-allocated objects. It is possible to use the
-<function>sb-ext:purify</> function to place live data structures in
-static space so that they won't move during GC. </para>
+able to fix up any references in C variables. There are three
+mechanisms for coping with this:
+<orderedlist>
+
+<listitem><para>The <function>sb-ext:purify</> moves all live Lisp
+data into static or read-only areas such that it will never be moved
+(or freed) again in the life of the Lisp session</para></listitem>
+
+<listitem><para><function>sb-sys:with-pinned-objects</function> is a
+macro which arranges for some set of objects to be pinned in memory
+for the dynamic extent of its body forms. On ports which use the
+generational garbage collector (as of &SBCL; 0.8.3, only the x86) this
+has a page granularity - i.e. the entire 4k page or pages containing
+the objects will be locked down. On other ports it is implemented by
+turning off GC for the duration (so could be said to have a
+whole-world granularity). </para></listitem>
+
+<listitem><para>Disable GC, using the <function>without-gcing</function>
+macro or <function>gc-off</function> call.</para></listitem>
+</orderedlist>
<!-- FIXME: This is a "changebar" section from the CMU CL manual.
I (WHN 2002-07-14) am not very familiar with this content, so
LaTeX use and this memory is typically about 8 MB above the start of the C
LaTeX heap. Thus, only about 8 MB of memory can be dynamically
LaTeX allocated.}.
+
+Empirically determined to be considerably >8Mb on this x86 linux
+machine, but I don't know what the actual values are - dan 2003.09.01
+
+Note that this technique is used in SB-GROVEL in the SBCL contrib
+
LaTeX
LaTeX To overcome this limitation, it is possible to access the content of
LaTeX Lisp arrays which are limited only by the amount of physical memory
= runtime stuff
+
+
SB-VM:*STATIC-SPACE-FREE-POINTER*
SB-VM:*INITIAL-DYNAMIC-SPACE-FREE-POINTER*
SB-VM:*CURRENT-CATCH-BLOCK*
SB-VM:*STATIC-SYMBOLS*
-SB-VM:*CONTROL-STACK-START* ; bound at thread entry
+SB-VM:*CONTROL-STACK-START* ; safe, bound at thread entry
SB-VM:*READ-ONLY-SPACE-FREE-POINTER*
-SB-VM:*BINDING-STACK-START*
-SB-VM:*CONTROL-STACK-END*
+SB-VM:*BINDING-STACK-START* ; safe, bound at thread entry
+SB-VM:*CONTROL-STACK-END* ; safe, bound at thread entry
SB-VM::*CURRENT-UNWIND-PROTECT-BLOCK*
SB-VM::*FREE-TLS-INDEX*
SB-VM::*BINDING-STACK-POINTER*
SB-IMPL::*READ-ONLY-SPACE-FREE-POINTER*
SB-VM::*ALIEN-STACK*
+SB-IMPL::*OBJECTS-PENDING-FINALIZATION* ; needs locking for writers
+
*GC-NOTIFY-STREAM* ; going away
*BEFORE-GC-HOOKS* ; must be global
*AFTER-GC-HOOKS* ; ditto
SB-IMPL::*MERGE-SORT-TEMP-VECTOR*
SB-IMPL::*PROFILE-HASH-CACHE*
SB-IMPL::*FIXNUM-POWER--1*
-SB-IMPL::*OBJECTS-PENDING-FINALIZATION*
SB-IMPL::*SHARP-EQUAL-CIRCLE-TABLE*
SB-IMPL::*SOFTWARE-INTERRUPT-VECTOR* ; suspect unused
SB-IMPL::*INSPECT-UNBOUND-OBJECT-MARKER*
<para>Other major changes since the fork from &CMUCL; include
<itemizedlist>
<listitem><para>&SBCL; has dropped support for many &CMUCL; extensions,
- (e.g. remote procedure call, Unix system interface, and X11
- interface).</para></listitem>
+ (e.g. IP networking, remote procedure call, Unix system interface, and X11
+ interface). Some of these are now available as contributed or
+ third-party modules.</para></listitem>
<listitem><para>&SBCL; has deleted or deprecated
some nonstandard features and code complexity which helped
efficiency at the price of maintainability. For example, the
"SYSTEM-AREA-POINTER" "SYSTEM-AREA-POINTER-P" "VECTOR-SAP"
"WAIT-UNTIL-FD-USABLE" "WITH-ENABLED-INTERRUPTS"
"WITH-FD-HANDLER"
- "WITH-INTERRUPTS" "WITHOUT-GCING"
+ "WITH-INTERRUPTS" "WITH-PINNED-OBJECTS" "WITHOUT-GCING"
"WITHOUT-INTERRUPTS" "WORDS"
"ALLOCATE-SYSTEM-MEMORY-AT"
"GET-DYNAMIC-FOREIGN-SYMBOL-ADDRESS"))
(inst stq_u temp (- (* ,offset n-word-bytes)
(* index ,scale) ,lowtag) object))))
(move value result))))))
+
+(defmacro sb!sys::with-pinned-objects ((&rest objects) &body body)
+ "Arrange with the garbage collector that the pages occupied by
+OBJECTS will not be moved in memory for the duration of BODY.
+Useful for e.g. foreign calls where another thread may trigger
+garbage collection. This is currently implemented by disabling GC"
+ (declare (ignore objects)) ;should we eval these for side-effect?
+ `(without-gcing
+ ,@body))
(defknown %setnth (unsigned-byte list t) t (unsafe))
(defknown %set-fill-pointer (vector index) index (unsafe))
\f
+;;;; ALIEN and call-out-to-C stuff
+
+;;; 'call' attribute because we store the arg on the stack, which is in
+;;; some sense 'passing it upwards'
+(defknown sb!vm::push-word-on-c-stack (system-area-pointer) (values) (call))
+(defknown sb!vm::pop-words-from-c-stack (index) (values) (call))
+
;;;; miscellaneous internal utilities
(defknown %fun-name (function) t (flushable))
object)
(move value result))))))
+
+(defmacro sb!sys::with-pinned-objects ((&rest objects) &body body)
+ "Arrange with the garbage collector that the pages occupied by
+OBJECTS will not be moved in memory for the duration of BODY.
+Useful for e.g. foreign calls where another thread may trigger
+garbage collection. This is currently implemented by disabling GC"
+ (declare (ignore objects)) ;should we eval these for side-effect?
+ `(without-gcing
+ ,@body))
(- (+ (* ,offset n-word-bytes) (* index ,scale)) ,lowtag))
(move result value))))))
+
+(defmacro sb!sys::with-pinned-objects ((&rest objects) &body body)
+ "Arrange with the garbage collector that the pages occupied by
+OBJECTS will not be moved in memory for the duration of BODY.
+Useful for e.g. foreign calls where another thread may trigger
+garbage collection. This is currently implemented by disabling GC"
+ (declare (ignore objects)) ;should we eval these for side-effect?
+ `(without-gcing
+ ,@body))
+
+(defmacro sb!sys::with-pinned-objects ((&rest objects) &body body)
+ "Arrange with the garbage collector that the pages occupied by
+OBJECTS will not be moved in memory for the duration of BODY.
+Useful for e.g. foreign calls where another thread may trigger
+garbage collection. This is currently implemented by disabling GC"
+ (declare (ignore objects)) ;should we eval these for side-effect?
+ `(without-gcing
+ ,@body))
(inst andcc zero-tn alloc-tn 3)
;; The C code needs to process this correctly and fixup alloc-tn.
(inst t :ne pseudo-atomic-trap)))))
+
+
+(defmacro sb!sys::with-pinned-objects ((&rest objects) &body body)
+ "Arrange with the garbage collector that the pages occupied by
+OBJECTS will not be moved in memory for the duration of BODY.
+Useful for e.g. foreign calls where another thread may trigger
+garbage collection. This is currently implemented by disabling GC"
+ (declare (ignore objects)) ;should we eval these for side-effect?
+ `(without-gcing
+ ,@body))
(ash symbol-value-slot word-shift)
(- other-pointer-lowtag)))
delta)))))
+
+;;; these are not strictly part of the c-call convention, but are
+;;; needed for the WITH-PRESERVED-POINTERS macro used for "locking
+;;; down" lisp objects so that GC won't move them while foreign
+;;; functions go to work.
+
+(define-vop (push-word-on-c-stack)
+ (:translate push-word-on-c-stack)
+ (:args (val :scs (sap-reg)))
+ (:policy :fast-safe)
+ (:arg-types system-area-pointer)
+ (:generator 2
+ (inst push val)))
+
+(define-vop (pop-words-from-c-stack)
+ (:translate pop-words-from-c-stack)
+ (:args)
+ (:arg-types (:constant (unsigned-byte 29)))
+ (:info number)
+ (:policy :fast-safe)
+ (:generator 2
+ (inst add esp-tn (fixnumize number))))
+
\f
;;;; allocation helpers
-;;; Two allocation approaches are implemented. A call into C can be
-;;; used, and in that case special care can be taken to disable
-;;; interrupts. Alternatively with gencgc inline allocation is possible
-;;; although it isn't interrupt safe.
-
-;;; For GENCGC it is possible to inline object allocation, to permit
-;;; this set the following variable to True.
-;;;
-;;; FIXME: The comment above says that this isn't interrupt safe. Is that
-;;; right? If so, do we want to do this? And surely we don't want to do this by
-;;; default? How much time does it save to do this? Is it any different in the
-;;; current CMU CL version instead of the one that I grabbed in 1998?
-;;; (Later observation: In order to be interrupt safe, it'd probably
-;;; have to use PSEUDO-ATOMIC, so it's probably not -- yuck. Try benchmarks
-;;; with and without inline allocation, and unless the inline allocation
-;;; wins by a whole lot, it's not likely to be worth messing with. If
-;;; we want to hack up memory allocation for performance, effort spent
-;;; on DYNAMIC-EXTENT would probably give a better payoff.)
-(defvar *maybe-use-inline-allocation* t)
+;;; All allocation is done by calls to assembler routines that
+;;; eventually invoke the C alloc() function. Once upon a time
+;;; (before threads) allocation within an alloc_region could also be
+;;; done inline, with the aid of two C symbols storing the current
+;;; allocation region boundaries; however, C cymbols are global.
+
+;;; C calls for allocation don't /seem/ to make an awful lot of
+;;; difference to speed. Guessing from historical context, it looks
+;;; like inline allocation was introduced before pseudo-atomic, at
+;;; which time all calls to alloc() would have needed a syscall to
+;;; mask signals for the duration. Now we have pseudoatomic there's
+;;; no need for that overhead. Still, inline alloc would be a neat
+;;; addition someday
+
+(defvar *maybe-use-inline-allocation* t) ; FIXME unused
;;; Emit code to allocate an object with a size in bytes given by
;;; Size. The size may be an integer of a TN. If Inline is a VOP
;;; node-var then it is used to make an appropriate speed vs size
;;; decision.
-;;;
-;;; FIXME: We call into C.. except when inline allocation is enabled..?
-;;;
-;;; FIXME: Also, calls to
-;;; ALLOCATION are always wrapped with PSEUDO-ATOMIC -- why? Is it to
-;;; make sure that no GC happens between the time of allocation and the
-;;; time that the allocated memory has its tag bits set correctly?
-;;; If so, then ALLOCATION itself might as well set the PSEUDO-ATOMIC
-;;; bits, so that the caller need only clear them. Check whether it's
-;;; true that every ALLOCATION is surrounded by PSEUDO-ATOMIC, and
-;;; that every PSEUDO-ATOMIC contains a single ALLOCATION, which is
-;;; its first instruction. If so, the connection should probably be
-;;; formalized, in documentation and in macro definition,
-;;; with the macro becoming e.g. PSEUDO-ATOMIC-ALLOCATION.
+
+;;; This macro should only be used inside a pseudo-atomic section,
+;;; which should also cover subsequent initialization of the
+;;; object.
(defun allocation (alloc-tn size &optional inline)
;; FIXME: since it appears that inline allocation is gone, we should
- ;; remove the INLINE parameter, and all the above comments.
+ ;; remove the INLINE parameter and *MAYBE-USE-INLINE-ALLOCATION*
(declare (ignore inline))
(flet ((load-size (dst-tn size)
(unless (and (tn-p size) (location= alloc-tn size))
\f
;;;; PSEUDO-ATOMIC
+;;; This is used to wrap operations which leave untagged memory lying
+;;; around. It's an operation which the AOP weenies would describe as
+;;; having "cross-cutting concerns", meaning it appears all over the
+;;; place and there's no logical single place to attach documentation.
+;;; grep (mostly in src/runtime) is your friend
+
;;; FIXME: *PSEUDO-ATOMIC-FOO* could be made into *PSEUDO-ATOMIC-BITS*,
;;; set with a single operation and cleared with SHR *PSEUDO-ATOMIC-BITS*,-2;
;;; the ATOMIC bit is bit 0, the INTERRUPTED bit is bit 1, and you check
;;; the C flag after the shift to see whether you were interrupted.
-;;; FIXME: It appears that PSEUDO-ATOMIC is used to wrap operations which leave
-;;; untagged memory lying around, but some documentation would be nice.
#!+sb-thread
(defmacro pseudo-atomic (&rest forms)
(with-unique-names (label)
value)
(move result value)))))
+;;; helper for alien stuff
+(defmacro sb!sys::with-pinned-objects ((&rest objects) &body body)
+ "Arrange with the garbage collector that the pages occupied by
+OBJECTS will not be moved in memory for the duration of BODY.
+Useful for e.g. foreign calls where another thread may trigger
+garbage collection"
+ `(multiple-value-prog1
+ (progn
+ ,@(loop for p in objects
+ collect `(push-word-on-c-stack
+ (int-sap (sb!kernel:get-lisp-obj-address ,p))))
+ ,@body)
+ (pop-words-from-c-stack ,(length objects))))
gc_assert(page_table[page].allocated != FREE_PAGE);
gc_assert(page_table[page].bytes_used != 0);
- /* Skip if it's already write-protected or an unboxed page. */
+ /* Skip if it's already write-protected, pinned, or unboxed */
if (page_table[page].write_protected
+ || page_table[page].dont_move
|| (page_table[page].allocated & UNBOXED_PAGE))
return (0);
for (i = 0; i < last_free_page; i++)
if ((page_table[i].allocated == BOXED_PAGE)
&& (page_table[i].bytes_used != 0)
+ && !page_table[i].dont_move
&& (page_table[i].gen == generation)) {
void *page_start;
/* Before any pointers are preserved, the dont_move flags on the
* pages need to be cleared. */
for (i = 0; i < last_free_page; i++)
- page_table[i].dont_move = 0;
+ if(page_table[i].gen==from_space)
+ page_table[i].dont_move = 0;
/* Un-write-protect the old-space pages. This is essential for the
* promoted pages as they may contain pointers into the old-space
;;; checkins which aren't released. (And occasionally for internal
;;; versions, especially for internal versions off the main CVS
;;; branch, it gets hairier, e.g. "0.pre7.14.flaky4.13".)
-"0.8.3.22"
+"0.8.3.23"