From c6ccb6a9c9292730e85181fb48b98b0ec35c713a Mon Sep 17 00:00:00 2001
From: cer <cer>
Date: Mon, 24 Feb 1992 13:18:29 +0000
Subject: [PATCH] Initial revision

---
 clim/graphics-recording.lisp      |  532 +++++++++++
 clim/lucid-after.lisp             |   52 ++
 clim/recording-protocol.lisp      | 1416 +++++++++++++++++++++++++++++
 clim/text-recording.lisp          |  447 +++++++++
 silica/db-border.lisp             |   58 ++
 utils/extended-regions.lisp       |  375 ++++++++
 utils/lucid-before.lisp           |   54 ++
 utils/lucid-stream-functions.lisp |  385 ++++++++
 8 files changed, 3319 insertions(+)
 create mode 100644 clim/graphics-recording.lisp
 create mode 100644 clim/lucid-after.lisp
 create mode 100644 clim/recording-protocol.lisp
 create mode 100644 clim/text-recording.lisp
 create mode 100644 silica/db-border.lisp
 create mode 100644 utils/extended-regions.lisp
 create mode 100644 utils/lucid-before.lisp
 create mode 100644 utils/lucid-stream-functions.lisp

diff --git a/clim/graphics-recording.lisp b/clim/graphics-recording.lisp
new file mode 100644
index 00000000..3daa0935
--- /dev/null
+++ b/clim/graphics-recording.lisp
@@ -0,0 +1,532 @@
+;;; -*- Mode: Lisp; Syntax: ANSI-Common-Lisp; Package: CLIM-INTERNALS; Base: 10; Lowercase: Yes -*-
+
+;; $fiHeader: graphics-recording.lisp,v 1.4 92/01/31 14:58:27 cer Exp $
+
+(in-package :clim-internals)
+
+"Copyright (c) 1990, 1991, 1992 Symbolics, Inc.  All rights reserved.
+ Portions copyright (c) 1991, 1992 Franz, Inc.  All rights reserved.
+ Portions copyright (c) 1989, 1990 International Lisp Associates."
+
+(defmacro define-output-recorder (class name medium-components 
+				  &key bounding-rectangle
+				       highlighting-test
+				       highlighting-function)
+  (destructuring-bind (function-args
+		       &key points-to-transform point-sequences-to-transform
+			    distances-to-transform
+		       &allow-other-keys)
+      (get-drawing-function-description name)
+    ;; Gross me right out!
+    (setq function-args
+	  (mapcar #'(lambda (x) (intern (symbol-name x) *package*))
+		  function-args))
+    (setq points-to-transform
+	  (mapcar #'(lambda (x) (intern (symbol-name x) *package*))
+		  points-to-transform))
+    (setq point-sequences-to-transform
+	  (mapcar #'(lambda (x) (intern (symbol-name x) *package*))
+		  point-sequences-to-transform))
+    (setq distances-to-transform
+	  (mapcar #'(lambda (x) (intern (symbol-name x) *package*))
+		  distances-to-transform))
+    (let* ((medium-graphics-function*
+	     (intern (format nil "~A~A*" 'medium- name)))
+	   (superclasses '(output-record-element-mixin 
+			   graphics-displayed-output-record))
+	   (slots
+	     (remove 'filled (append medium-components function-args)))
+	   (slot-descs 
+	     (mapcar #'(lambda (x)
+			 (list x :initarg (intern (symbol-name x) *keyword-package*)))
+			 slots)))
+      `(progn
+	 (defclass ,class ,superclasses ,slot-descs)
+	 ;;--- Need to define a speedy constructor
+	 (defmethod ,medium-graphics-function* :around
+		    ((medium output-recording-mixin) ,@function-args)
+	   (when (stream-recording-p medium)
+	     (let ((transformation (medium-transformation medium))
+		   ,@(mapcar #'(lambda (medium-component)
+					  (list medium-component
+						`(,(fintern"~A~A" 'medium- medium-component)
+						  medium)))
+			     medium-components))
+	       ;; Overload FILLED and LINE-STYLE -- when FILLED is T,
+	       ;; the LINE-STYLE is ignored and must be NIL
+	       ,@(when (and (member 'filled function-args)
+			    (member 'line-style medium-components))
+		   `((when filled (setq line-style nil))))
+	       (multiple-value-bind (abs-x abs-y)
+		   (point-position* (stream-output-history-position medium))
+		 (declare (type coordinate abs-x abs-y))
+		 ,@(mapcar #'(lambda (p)
+			       `(transform-point-sequence (transformation) ,p))
+			   point-sequences-to-transform)
+		 (transform-points (transformation) ,@points-to-transform)
+		 (transform-distances (transformation) ,@distances-to-transform)
+		 (let ((record
+			 (make-instance ',class
+			   ,@(mapcan #'(lambda (x)
+					 (list (intern (symbol-name x) *keyword-package*) x))
+				     slots))))
+		   (multiple-value-bind (lf tp rt bt)
+		       (progn ,bounding-rectangle)
+		     (declare (type coordinate lf tp rt bt))
+		     (bounding-rectangle-set-edges
+		       record
+		       (- lf abs-x) (- tp abs-y) (- rt abs-x) (- bt abs-y))
+		     (multiple-value-bind (cx cy) (stream-cursor-position* medium)
+		       (declare (type coordinate cx cy))
+		       ;; Doing this directly beats calling
+		       ;; OUTPUT-RECORD-SET-START-CURSOR-POSITION*
+		       (with-slots (start-x start-y) record
+			 (setq start-x (- cx abs-x)
+			       start-y (- cy abs-y))))
+		     ;; Adjust the stored coordinates by the current cursor position
+		     ,@(mapcar #'(lambda (p)
+				   `(with-slots (,p) record
+				      (setf ,p (adjust-point-sequence ,p abs-x abs-y))))
+			       point-sequences-to-transform)
+		     ,@(when points-to-transform
+			 `((with-slots ,points-to-transform record
+			     (setf ,@(do ((p points-to-transform (cddr p))
+					  r)
+					 ((null p) (nreverse r))
+				       (push (first p) r)
+				       (push `(- ,(first p) abs-x) r)
+				       (push (second p) r)
+				       (push `(- ,(second p) abs-y) r)))))))
+		   (stream-add-output-record medium record)))))
+	   (when (stream-drawing-p medium)
+	     (call-next-method)))
+
+	 (defmethod replay-output-record ((record ,class) stream 
+					  &optional region (x-offset 0) (y-offset 0))
+	   (declare (ignore region))
+	   (with-slots (,@slots) record
+	     (letf-globally (((medium-transformation stream) +identity-transformation+))
+	       (with-drawing-options 
+		   (stream ,@(mapcan #'(lambda (medium-component)
+					 (list (intern (symbol-name medium-component)
+						       *keyword-package*)
+					       medium-component))
+				     medium-components))
+		 (let (,@(when (and (member 'filled function-args)
+				    (member 'line-style medium-components))
+			   `((filled (not line-style))))
+		       ,@(mapcar #'(lambda (p) (list p p))
+				 points-to-transform)
+		       ,@(mapcar #'(lambda (p) (list p p))
+				 point-sequences-to-transform))
+		   ,@(mapcar #'(lambda (p)
+				 `(setq ,p (adjust-point-sequence 
+					     ,p (- x-offset) (- y-offset))))
+			     point-sequences-to-transform)
+		   (setf ,@(do ((p points-to-transform (cddr p))
+				r)
+			       ((null p) (nreverse r))
+			     (push (first p) r)
+			     (push `(+ ,(first p) x-offset) r)
+			     (push (second p) r)
+			     (push `(+ ,(second p) y-offset) r)))
+		   (with-sheet-medium (medium stream)
+		     (,medium-graphics-function* medium ,@function-args)))))))
+	 
+	 ,@(when highlighting-test
+	     (let ((args (first highlighting-test))
+		   (body (rest highlighting-test)))
+	       `((defmethod output-record-refined-sensitivity-test ((record ,class) ,@args)
+		   ,@body))))
+
+	 ,@(when highlighting-function
+	     (let ((args (first highlighting-function))
+		   (body (rest highlighting-function)))
+	       `((defmethod highlight-output-record-1 ((record ,class) ,@args)
+		   ,@body))))))))
+
+(defmacro with-half-thickness ((lthickness rthickness) line-style &body body)
+  (let ((ls '#:line-style)
+	(thickness '#:thickness))
+    `(let* ((,ls ,line-style)
+	    (,thickness  (if ,ls (line-style-thickness ,ls) 0))
+	    (,lthickness (floor ,thickness 2))
+	    (,rthickness (- ,thickness ,lthickness)))
+       ,@body)))
+
+
+;;; Designs
+
+(defun make-design-from-output-record (record)
+  (multiple-value-bind (xoff yoff) (compute-output-record-offsets record)
+    (make-design-from-output-record-1 record xoff yoff)))
+
+(defmethod make-design-from-output-record-1
+	   ((record output-record-mixin) x-offset y-offset)
+  (let ((designs nil))
+    (flet ((make-design (record)
+	     (multiple-value-bind (xoff yoff) (output-record-position* record)
+	       (declare (type coordinate xoff yoff))
+	       (let ((design
+		       (make-design-from-output-record-1
+			 record
+			 (+ x-offset xoff) (+ y-offset yoff))))
+		 (when design (push design designs))))))
+      (declare (dynamic-extent #'make-design))
+      (map-over-output-records #'make-design record))
+    (make-instance 'composite-over :designs (apply #'vector designs))))
+
+(defgeneric draw-design (design stream &rest args)
+  (declare (arglist design stream &key . #.(all-drawing-options-lambda-list nil))))
+
+
+;;; Simple composite designs
+(defmethod draw-design ((composite composite-over) stream &rest args)
+  (declare (dynamic-extent args))
+  (with-slots ((designs clim-utils::designs)) composite
+    (dovector (design designs :from-end t)
+      (apply #'draw-design design stream args))))
+
+(defmethod draw-design ((composite composite-in) stream &rest args &key ink &allow-other-keys)
+  (declare (dynamic-extent args))
+  (with-slots ((designs clim-utils::designs)) composite
+    (let ((ink (or ink (aref designs 0)))	;should be COMPOSE-OVER
+	  (design (aref designs 1)))
+      ;; Clips INK to the inside of DESIGN.
+      (apply #'draw-design design stream :ink ink args))))
+
+(defmethod draw-design ((composite composite-out) stream &rest args &key ink &allow-other-keys)
+  (declare (dynamic-extent args))
+  (with-slots ((designs clim-utils::designs)) composite
+    (let ((ink (or ink (aref designs 0)))	;should be COMPOSE-OVER
+	  (design (aref designs 1)))
+      ;;--- Should clip INK to the outside of DESIGN, but I don't know how
+      (nyi))))
+
+(defmethod draw-design ((region standard-region-union) stream &rest args)
+  (declare (dynamic-extent args))
+  (with-slots ((regions clim-utils::regions)) region
+    (dolist (region regions)
+      (apply #'draw-design region stream args))))
+
+(defmethod draw-design ((region standard-region-intersection) stream &rest args)
+  (declare (dynamic-extent args))
+  (with-slots ((regions clim-utils::regions)) region
+    ;;--- Should draw just the intersection, but I dunno how to do that in general
+    (nyi)))
+
+(defmethod draw-design ((region standard-region-difference) stream &rest args)
+  (declare (dynamic-extent args))
+  (with-slots ((region1 clim-utils::region1)
+	       (region2 clim-utils::region2)) region
+    ;;--- Should draw just the difference, but I dunno how to do that in general
+    (nyi)))
+
+
+(define-output-recorder point-output-record draw-point (ink line-style)
+  :bounding-rectangle 
+    (with-half-thickness (lthickness rthickness) line-style
+      (values (- x lthickness)
+	      (- y lthickness)
+	      (+ x rthickness)
+	      (+ y rthickness))))
+
+(defmethod make-design-from-output-record-1
+	   ((point point-output-record) x-offset y-offset)
+  (with-slots (x y ink) point
+    (compose-in
+      ink
+      (make-point (+ x x-offset) (+ y y-offset)))))
+
+(defmethod draw-design ((point standard-point) stream &rest args &key ink line-style)
+  (declare (dynamic-extent args)
+	   (ignore ink line-style))
+  (multiple-value-bind (x y) (point-position* point)
+    (apply #'draw-point* stream x y args)))
+
+
+(define-output-recorder line-output-record draw-line (ink line-style)
+  :bounding-rectangle 
+    (with-half-thickness (lthickness rthickness) line-style
+      (values (- (min x1 x2) lthickness)
+	      (- (min y1 y2) lthickness)
+	      (+ (max x1 x2) rthickness)
+	      (+ (max y1 y2) rthickness)))
+  :highlighting-test
+    ((x y)
+     (with-slots (x1 y1 x2 y2 line-style) record
+       (point-close-to-line-p x y x1 y1 x2 y2 (line-style-thickness line-style))))
+  :highlighting-function
+    ((stream state)
+     (declare (ignore state))					;for now.
+     (multiple-value-bind (xoff yoff)
+	 (convert-from-relative-to-absolute-coordinates
+	   stream (output-record-parent record))
+       (with-slots (x1 y1 x2 y2 line-style) record
+	 (outline-line-with-hexagon stream xoff yoff
+				    x1 y1 x2 y2 (line-style-thickness line-style))))))
+
+(defmethod make-design-from-output-record-1
+	   ((line line-output-record) x-offset y-offset)
+  (with-slots (x1 x2 y1 y2 ink) line
+    (compose-in
+      ink
+      (make-line* (+ x1 x-offset) (+ y1 y-offset)
+		  (+ x2 x-offset) (+ y2 y-offset)))))
+
+(defmethod draw-design ((line standard-line) stream &rest args &key ink line-style)
+  (declare (dynamic-extent args)
+	   (ignore ink line-style))
+  (multiple-value-bind (x1 y1) (line-start-point* line)
+    (multiple-value-bind (x2 y2) (line-end-point* line)
+      (apply #'draw-line* stream x1 y1 x2 y2 args))))
+
+(defun outline-line-with-hexagon (stream xoff yoff
+				  from-x from-y to-x to-y &optional (thickness 1))
+  (let ((distance (1+ (round thickness 2))))
+    (multiple-value-bind (x1 y1 x2 y2 x3 y3 x4 y4 x5 y5 x6 y6)
+	(cond ((eq (minusp (- to-x from-x)) (minusp (- to-y from-y)))
+	       (values (- from-x distance) (- from-y distance)
+		       (- from-x distance) (+ from-y distance)
+		       (- to-x distance) (+ to-y distance)
+		       (+ to-x distance) (+ to-y distance)
+		       (+ to-x distance) (- to-y distance)
+		       (+ from-x distance) (- from-y distance)))
+	      (t
+	       (when (> to-y from-y)
+		 ;; Make line go down to right.
+		 (rotatef to-x from-x)
+		 (rotatef to-y from-y))
+	       (values (- from-x distance) (+ from-y distance)
+		       (- from-x distance) (- from-y distance)
+		       (- to-x distance) (- to-y distance)
+		       (+ to-x distance) (- to-y distance)
+		       (+ to-x distance) (+ to-y distance)
+		       (+ from-x distance) (+ from-y distance))))
+      (macrolet ((line (x1 y1 x2 y2)
+		   `(draw-line-internal stream xoff yoff
+					,x1 ,y1 ,x2 ,y2
+					+flipping-ink+ +highlighting-line-style+)))
+	(with-output-recording-options (stream :record nil)
+	  (line x1 y1 x2 y2)
+	  (line x2 y2 x3 y3)
+	  (line x3 y3 x4 y4)
+	  (line x4 y4 x5 y5)
+	  (line x5 y5 x6 y6)
+	  (line x6 y6 x1 y1))))))
+
+
+(define-output-recorder rectangle-output-record draw-rectangle (ink line-style)
+  :bounding-rectangle
+    (with-half-thickness (lthickness rthickness) line-style
+      (values (- (min x1 x2) lthickness)
+	      (- (min y1 y2) lthickness)
+	      (+ (max x1 x2) rthickness)
+	      (+ (max y1 y2) rthickness)))
+  :highlighting-test
+    ((x y)
+     (with-slots (x1 y1 x2 y2 line-style) record
+       (or (null line-style)
+	   (with-half-thickness (lthickness rthickness) line-style
+	     ;; Don't use LTRB-CONTAINS-POINT*-P, since that expects fixnums
+	     ;;---- Not any more!
+	     (not (and (<= (+ x1 rthickness) x)
+		       (<= (+ y1 rthickness) y)
+		       (>= (- x2 lthickness) x)
+		       (>= (- y2 lthickness) y)))))))
+  :highlighting-function
+    ((stream state)
+     (declare (ignore state))
+     (multiple-value-bind (xoff yoff)
+	 (convert-from-relative-to-absolute-coordinates
+	   stream (output-record-parent record))
+       (with-slots (x1 y1 x2 y2 line-style) record
+	 (with-output-recording-options (stream :record nil)
+	   (with-half-thickness (lthickness rthickness) line-style
+	     (draw-rectangle-internal
+	       stream xoff yoff
+	       (- x1 lthickness 1) (- y1 lthickness 1)
+	       (+ x2 rthickness 1) (+ y2 rthickness 1)
+	       +flipping-ink+ +highlighting-line-style+)))))))
+
+(defmethod make-design-from-output-record-1
+	   ((rectangle rectangle-output-record) x-offset y-offset)
+  (with-slots (x1 x2 y1 y2 line-style ink) rectangle
+    (compose-in
+      ink
+      (if (null line-style)
+	  (make-rectangle* (+ x1 x-offset) (+ y1 y-offset)
+			   (+ x2 x-offset) (+ y2 y-offset))
+          (make-polyline* (list (+ x1 x-offset) (+ y1 y-offset)
+				(+ x2 x-offset) (+ y1 y-offset)
+				(+ x2 x-offset) (+ y2 y-offset)
+				(+ x1 x-offset) (+ y2 y-offset))
+			  :closed t)))))
+
+(defmethod draw-design ((rectangle standard-rectangle) stream &rest args &key ink line-style)
+  (declare (dynamic-extent args)
+	   (ignore ink line-style))
+  (multiple-value-bind (x1 y1 x2 y2) (rectangle-edges* rectangle)
+    (apply #'draw-rectangle* stream x1 y1 x2 y2 :filled t args))) 
+
+
+;;--- This needs a :HIGHLIGHTING-TEST and :HIGHLIGHTING-FUNCTION
+(define-output-recorder polygon-output-record draw-polygon (ink line-style)
+  :bounding-rectangle
+    (point-sequence-bounding-rectangle 
+      list-of-x-and-ys line-style))
+
+(defmethod make-design-from-output-record-1
+	   ((polygon polygon-output-record) x-offset y-offset)
+  (with-slots (list-of-xs-and-ys closed line-style ink) polygon
+    (let ((coords (copy-list list-of-xs-and-ys)))
+      (translate-point-sequence x-offset y-offset coords)
+      (compose-in
+	ink
+	(if (null line-style)
+	    (make-polygon* coords)
+            (make-polyline* coords :closed closed))))))
+
+(defmethod draw-design ((polygon standard-polygon) stream &rest args &key ink line-style)
+  (declare (dynamic-extent args)
+	   (ignore ink line-style))
+  (apply #'draw-polygon stream (polygon-points polygon) :closed t :filled t args))
+
+(defmethod draw-design ((polyline standard-polyline) stream &rest args &key ink line-style)
+  (declare (dynamic-extent args)
+	   (ignore ink line-style))
+  (with-slots (closed) polyline
+    (apply #'draw-polygon stream (polygon-points polyline) :closed closed :filled nil args)))
+
+(defun point-sequence-bounding-rectangle (list-of-x-and-ys line-style)
+  (let* ((minx (car list-of-x-and-ys))
+	 (miny (second list-of-x-and-ys))
+	 (maxx minx)
+	 (maxy miny))
+    (map-point-sequence
+      #'(lambda (x y)
+	  (minf minx x)
+	  (minf miny y)
+	  (maxf maxx x)
+	  (maxf maxy y))
+      list-of-x-and-ys)
+    (with-half-thickness (lthickness rthickness) line-style
+      (values (- minx lthickness)
+	      (- miny lthickness)
+	      (+ maxx rthickness)
+	      (+ maxy rthickness)))))
+
+(defun map-point-sequence (fn list-of-x-and-ys)
+  (do ((p list-of-x-and-ys (cddr p)))
+      ((null p))
+    (funcall fn (car p) (cadr p))))
+
+
+(define-output-recorder ellipse-output-record draw-ellipse (ink line-style)
+  :bounding-rectangle
+    (multiple-value-bind (left top right bottom)
+	(elliptical-arc-box
+	  center-x center-y 
+	  radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+	  start-angle end-angle
+	  (line-style-thickness (medium-line-style medium)))
+      ;;--- Make this a bit too big because most hosts rasterize
+      ;;--- ellipses to be a shade too big on the right
+      (values left top (1+ right) (1+ bottom)))
+  :highlighting-test
+    ((x y)
+     (with-slots (center-x center-y
+		  radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+		  start-angle end-angle ink line-style) record
+       (and (or (null start-angle)
+		;; NYI - check for within the proper angle
+		t)
+	    (if (null line-style)
+		(point-inside-ellipse-p (- x center-x) (- y center-y)
+					radius-1-dx radius-1-dy radius-2-dx radius-2-dy)
+		(point-on-thick-ellipse-p (- x center-x) (- y center-y)
+					  radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+					  (ceiling (line-style-thickness line-style) 2))))))
+  :highlighting-function
+    ((stream state)
+     (declare (ignore state))
+     (multiple-value-bind (xoff yoff)
+	 (convert-from-relative-to-absolute-coordinates
+	   stream (output-record-parent record))
+       (with-slots (center-x center-y
+		    radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+		    start-angle end-angle ink line-style) record
+	 (let ((delta 2)
+	       (radius-1 (sqrt (+ (* radius-1-dx radius-1-dx) (* radius-1-dy radius-1-dy))))
+	       (radius-2 (sqrt (+ (* radius-2-dx radius-2-dx) (* radius-2-dy radius-2-dy)))))
+	   (when line-style
+	     (incf delta (ceiling (line-style-thickness line-style) 2)))
+	   (let ((delta-1-dx (round (* delta radius-1-dx) radius-1))
+		 (delta-1-dy (round (* delta radius-1-dy) radius-1))
+		 (delta-2-dx (round (* delta radius-2-dx) radius-2))
+		 (delta-2-dy (round (* delta radius-2-dy) radius-2)))
+	     (with-output-recording-options (stream :record nil)
+	       (draw-ellipse-internal
+		 stream xoff yoff
+		 center-x center-y
+		 (+ radius-1-dx delta-1-dx) (+ radius-1-dy delta-1-dy)
+		 (+ radius-2-dx delta-2-dx) (+ radius-2-dy delta-2-dy)
+		 start-angle end-angle
+		 +flipping-ink+ +highlighting-line-style+))))))))
+
+(defmethod make-design-from-output-record-1
+	   ((ellipse ellipse-output-record) x-offset y-offset)
+  (with-slots (center-x center-y radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+	       start-angle end-angle line-style ink) ellipse
+    (compose-in
+      ink
+      (if (null line-style)
+	  (make-ellipse* (+ center-x x-offset) (+ center-y y-offset)
+			 radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+			 :start-angle start-angle :end-angle end-angle)
+          (make-elliptical-arc* (+ center-x x-offset) (+ center-y y-offset)
+				radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+				:start-angle start-angle :end-angle end-angle)))))
+
+(defmethod draw-design ((ellipse standard-ellipse) stream &rest args &key ink line-style)
+  (declare (dynamic-extent args)
+	   (ignore ink line-style))
+  (multiple-value-bind (center-x center-y)
+      (ellipse-center-point* ellipse)
+    (multiple-value-bind (radius-1-dx radius-1-dy radius-2-dx radius-2-dy)
+	(ellipse-radii ellipse)
+      (apply #'draw-ellipse* stream center-x center-y
+			     radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+			     :start-angle (ellipse-start-angle ellipse)
+			     :end-angle (ellipse-end-angle ellipse)
+			     :filled t args))))
+
+(defmethod draw-design ((ellipse standard-elliptical-arc) stream &rest args &key ink line-style)
+  (declare (dynamic-extent args)
+	   (ignore ink line-style))
+  (multiple-value-bind (center-x center-y)
+      (ellipse-center-point* ellipse)
+    (multiple-value-bind (radius-1-dx radius-1-dy radius-2-dx radius-2-dy)
+	(ellipse-radii ellipse)
+      (apply #'draw-ellipse* stream center-x center-y
+			     radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+			     :start-angle (ellipse-start-angle ellipse)
+			     :end-angle (ellipse-end-angle ellipse)
+			     :filled nil args))))
+
+
+;;--- Where is DRAW-TEXT?  and/or DRAW-STRING and DRAW-CHARACTER?
+
+
+;;--- Does anyone use this?
+(defun adjust-point-sequence (list-of-x-and-ys dx dy)
+  (let (r)
+    (map-point-sequence
+     #'(lambda (x y)
+	 (push (- x dx) r)
+	 (push (- y dy) r))
+     list-of-x-and-ys)
+    (nreverse r)))
+
+
+       
diff --git a/clim/lucid-after.lisp b/clim/lucid-after.lisp
new file mode 100644
index 00000000..77a976d1
--- /dev/null
+++ b/clim/lucid-after.lisp
@@ -0,0 +1,52 @@
+;;; -*- Mode: LISP; Syntax: Common-Lisp; Package: LUCID; Base: 10 -*-
+;;;
+;;;; Lucid-after-patches, Module CLIM
+;;;
+;;; ***************************************************************************
+;;;
+;;;        Copyright (c) 1991, 1992 by Lucid, Inc.  All Rights Reserved
+;;;
+;;; ***************************************************************************
+;;;
+;;; Lucid specific hacks which need to be loaded after CLIM gets loaded.
+;;;
+;;;
+;;; Edit-History:
+;;;
+;;; Created: PW  2-Nov-91
+;;;
+;;;
+;;; End-of-Edit-History
+
+
+(in-package :lucid)
+
+
+;;; $fiHeader$
+;;; Workaround for a disksave/hash bug.  
+;;;
+(defun rehash-ptypes ()
+  (dolist (ht (list clim-internals::*presentation-type-description-table*
+		    clim-internals::*presentation-type-history-table*
+		    clim-internals::*presentation-type-class-table*
+		    clim-internals::*presentation-type-inheritance-table*
+		    clim-internals::*presentation-type-parameters-table*
+		    clim-internals::*presentation-type-options-table*
+		    clim-internals::*presentation-type-abbreviation-table*
+		    clim-internals::*presentation-generic-function-table*))
+    (rehash ht)))
+
+;;; Do this when we load CLIM
+(rehash-ptypes)
+
+;;; Add this for disksaving
+(when (boundp '*restart-cleanup-functions*)
+  (pushnew 'rehash-ptypes *restart-cleanup-functions*))
+
+
+(eval-when (load)
+  (pushnew :clim-2-0 *features*)
+  (defparameter *clim-repacking-date* (universal-time-string (get-universal-time)))
+  ;;;(precompile-generic-functions)
+  ;;(clos-system:revalidate-all-mki-optimizations)
+  )
diff --git a/clim/recording-protocol.lisp b/clim/recording-protocol.lisp
new file mode 100644
index 00000000..2f29c7de
--- /dev/null
+++ b/clim/recording-protocol.lisp
@@ -0,0 +1,1416 @@
+;;; -*- Mode: Lisp; Syntax: ANSI-Common-Lisp; Package: CLIM-INTERNALS; Base: 10; Lowercase: Yes -*-
+
+;; $fiHeader: recording-protocol.lisp,v 1.6 92/01/31 16:22:15 cer Exp $
+
+(in-package :clim-internals)
+
+"Copyright (c) 1990, 1991, 1992 Symbolics, Inc.  All rights reserved.
+ Portions copyright (c) 1991, 1992 Franz, Inc.  All rights reserved.
+ Portions copyright (c) 1989, 1990 International Lisp Associates."
+
+;; The protocol class for an object that obeys the output record protocol,
+;; that is, can hold output record elements
+(define-protocol-class output-record (bounding-rectangle))
+
+;; The protocol class for output records that are leaves.
+(define-protocol-class displayed-output-record (bounding-rectangle))
+
+;; The protocol class for textual displayed output records.
+(define-protocol-class text-displayed-output-record (displayed-output-record))
+
+;; The protocol class for graphical displayed output records.
+(define-protocol-class graphics-displayed-output-record (displayed-output-record))
+
+
+;;; A mix-in for classes that can be stored by other output records
+;;; OUTPUT-RECORD-ELEMENT-MIXIN has slots for
+;;;     (bounding rectangle, parent, start-position, end-position, contents-ok)
+;;;     plus space to store old bounding rectangle and position for incremental redisplay
+;;;  graphics output records
+;;;  text output records
+;;;  OUTPUT-RECORD-MIXIN has slots for (generation-tick, old-children)
+;;;      both used for incremental redisplay.
+;;;   STANDARD-SEQUENCE-OUTPUT-RECORD
+;;;    table, row, column, cell, presentation
+;;;   STANDARD-TREE-OUTPUT-RECORD
+;;;   KD-TREE-OUTPUT-RECORD (someday)
+
+;;; The output-record-element "protocol"
+;;;   :x-position, :y-position, :parent init args.
+;;;   bounding rectangle protocol
+
+;;; The output record protocol:
+;;;  output-record-children: (record)
+;;;  add-output-record: (child record)
+;;;  delete-output-record: (child record)
+;;;  clear-output-record: (record)
+;;;  replay-output-record: (record stream &optional region (x-offset 0) (y-offset 0)
+;;;  recompute-extent: (record)
+;;;  recompute-extent-for-new-child (there's a default): (record child)
+;;;  recompute-extent-for-changed-child: (record child)
+;;;  map-over-output-records-overlapping-region:
+;;;   (function record region
+;;;    &optional (x-offset 0) (y-offset 0) &rest continuation-args)
+;;;  map-over-output-records-containing-point*:
+;;;   (function record x y
+;;;    &optional (x-offset 0) (y-offset 0) &rest continuation-args)
+
+;;; The incremental redisplay protocol:
+;;;  see file incremental-redisplay-protocol.text, and incremental-redisplay.lisp.
+;;;
+
+;; Bounding rectangle position and set-position are in relative coordinates, 
+;;   relative to (OUTPUT-RECORD-POSITION* (OUTPUT-RECORD-PARENT RECORD)).
+;; The bounding rectangle measures just the ink.
+;; (OUTPUT-RECORD-START-CURSOR-POSITION* RECORD) refers to the position of the
+;; cursor at the start of RECORD.  It is also the origin of the
+;; coordinate system for all children of RECORD.
+(defclass output-record-element-mixin (standard-bounding-rectangle)
+    ;; start position is relative to the parent's start-position
+    ;; start position is where the cursor was when the new
+    ;; output-record was started.
+    ((start-x :initform 0 :initarg :start-x)
+     (start-y :initform 0 :initarg :start-y)
+     ;; end position is relative to start position.
+     ;; end position is where the cursor was when we finished the
+     ;; output-record.
+     (end-x :initform 0 :initarg :end-x)
+     (end-y :initform 0 :initarg :end-y)
+     ;; old-start-position is relative to old-start-position of parent
+     (old-start-x :initform 0)
+     (old-start-y :initform 0)
+     ;; old bounding rectangle is relative to parents' old-start-position.
+     (old-bounding-rectangle :initform nil
+			     :accessor output-record-old-bounding-rectangle)
+     (contents-ok :initform nil :accessor output-record-contents-ok)
+     (parent :accessor output-record-parent :initarg :parent)
+     (stream :initform nil :accessor output-record-stream))
+  (:default-initargs :parent nil :left 0 :top 0 :right 0 :bottom 0))
+
+;;; Give initial rectangle of 0 size, it will get expanded as children are added.
+(defmethod initialize-instance :after ((record output-record-element-mixin)
+				       &key (x-position 0) (y-position 0))
+  (with-slots (left top right bottom) record
+    (setf left x-position
+	  top  y-position
+	  right  x-position
+	  bottom y-position)))
+
+;;; Shadow the method on RECTANGLE with this one that keeps the start-position and 
+;;; bounding rectangle in synch.
+(defmethod bounding-rectangle-set-position* ((record output-record-element-mixin) nx ny)
+  (declare (type coordinate nx ny))
+  (with-slots (left top right bottom start-x start-y parent) record
+    (declare (type coordinate left top right bottom start-x start-y))
+    ;; Move the start position by as much as we do the record.
+    (setq start-x (+ start-x (- nx left)))
+    (setq start-y (+ start-y (- ny top)))
+    (let ((width (- right left))
+	  (height (- bottom top)))
+      (setf left nx top ny)
+      (setf right  (+ nx width)
+	    bottom (+ ny height)))))
+
+#+ignore
+(defmethod bounding-rectangle-set-position* :around ((record output-record-element-mixin) nx ny)
+  (with-bounding-rectangle* (x1 y1 x2 y2) record
+    (call-next-method)
+    (note-output-record-moved record (- nx x1) (- ny y1) (- nx x2) (- ny y2))))
+
+#+ignore
+(defmethod bounding-rectangle-set-edges :around ((record output-record-element-mixin) 
+						 left top right bottom)
+  (with-bounding-rectangle* (x1 y1 x2 y2) record
+    (call-next-method)
+    (note-output-record-moved record (- left x1) (- top y1) (- right x2) (- bottom y2))))
+
+#+Silica
+(defmethod note-output-record-moved ((record output-record-element-mixin) dx1 dy1 dx2 dy2)
+  (declare (ignore dx1 dy1 dx2 dy2))
+  nil)
+
+(defun-inline output-record-position* (record)
+  (output-record-start-cursor-position* record))
+
+;; X and Y had better be fixnums
+;;--- Coerce to COORDINATE
+(defmethod output-record-set-position* ((record output-record-element-mixin) x y)
+  (declare (type coordinate x y))
+  (bounding-rectangle-set-position* record x y))
+
+(defmethod output-record-start-cursor-position ((record output-record-element-mixin))
+  (with-slots (start-x start-y) record
+    (make-point start-x start-y)))
+
+(defmethod output-record-start-cursor-position* ((record output-record-element-mixin))
+  (with-slots (start-x start-y) record
+    (values start-x start-y)))
+
+;;; Keep the start-position and bounding rectangle in synch
+(defmethod output-record-set-start-cursor-position*
+	   ((record output-record-element-mixin) nx ny)
+  (declare (type coordinate nx ny))
+  (with-slots (start-x start-y) record
+    (declare (type coordinate start-x start-y))
+    (with-bounding-rectangle* (left top right bottom) record
+      (let ((dx (- nx start-x))
+	    (dy (- ny start-y)))
+	(bounding-rectangle-set-edges 
+	  record
+	  (+ left dx) (+ top dy) (+ right dx) (+ bottom dy))
+	(setf start-x nx start-y ny)))))
+
+(defmethod output-record-end-cursor-position* ((record output-record-element-mixin))
+  (with-slots (end-x end-y) record
+    (values end-x end-y)))
+  
+(defmethod output-record-set-end-cursor-position* ((record output-record-element-mixin) nx ny)
+  (declare (type coordinate nx ny))
+  (with-slots (end-x end-y) record
+    (setf end-x nx)
+    (setf end-y ny)))
+
+(defmethod output-record-old-start-cursor-position ((record output-record-element-mixin))
+  (with-slots (old-start-x old-start-y) record
+    (make-point old-start-x old-start-y)))
+
+(defmethod output-record-old-start-cursor-position* ((record output-record-element-mixin))
+  (with-slots (old-start-x old-start-y) record
+    (values old-start-x old-start-y)))
+
+(defmethod output-record-set-old-start-cursor-position*
+	   ((record output-record-element-mixin) nx ny)
+  (declare (type coordinate nx ny))
+  (with-slots (old-start-x old-start-y) record
+    (setf old-start-x nx)
+    (setf old-start-y ny)))
+
+#+CLIM-1-compatibility
+(progn
+(define-compatibility-function (output-record-start-position
+				output-record-start-cursor-position)
+			       (record)
+  (output-record-start-cursor-position record))
+
+(define-compatibility-function (output-record-start-position*
+				output-record-start-cursor-position*)
+			       (record)
+  (output-record-start-cursor-position* record))
+
+(define-compatibility-function (output-record-set-start-position*
+				output-record-set-start-cursor-position*)
+			       (record nx ny)
+  (output-record-set-start-cursor-position* record nx ny))
+
+(define-compatibility-function (output-record-end-position*
+				output-record-end-cursor-position*)
+			       (record)
+  (output-record-end-cursor-position* record))
+
+(define-compatibility-function (output-record-set-end-position*
+				output-record-set-end-cursor-position*)
+			       (record nx ny)
+  (output-record-set-end-cursor-position* record nx ny))
+)	;#+CLIM-1-compatibility
+
+
+(defmethod output-record-children ((record output-record-element-mixin))
+  nil)
+
+;;; For specialization by PRESENTATIONs, for example
+(defmethod output-record-refined-sensitivity-test ((record output-record-element-mixin) x y)
+  (declare (ignore x y))
+  T)
+
+(defun compute-output-record-offsets (record)
+  (let ((parent (output-record-parent record)))
+    (if (null parent)
+	(values 0 0)
+      (multiple-value-bind (x y)
+	  (compute-output-record-offsets parent)
+	(declare (type coordinate x y))
+	(multiple-value-bind (our-x our-y) (output-record-position* record)
+	  (declare (type coordinate our-x our-y))
+	  (values (+ our-x x) (+ our-y y)))))))
+
+(defmethod region-equal
+	   ((record1 output-record-element-mixin) (record2 output-record-element-mixin))
+  (with-bounding-rectangle* (left1 top1 right1 bottom1) record1
+    (with-bounding-rectangle* (left2 top2 right2 bottom2) record2
+      (if (eq (output-record-parent record1) (output-record-parent record2))
+	  (ltrb-equals-ltrb-p left1 top1 right1 bottom1
+			      left2 top2 right2 bottom2)
+	(multiple-value-bind (xoff1 yoff1) (compute-output-record-offsets record1)
+	  (declare (type coordinate xoff1 yoff1))
+	  (multiple-value-bind (xoff2 yoff2) (compute-output-record-offsets record2)
+	    (declare (type coordinate xoff2 yoff2))
+	    (translate-fixnum-positions xoff1 yoff1 left1 top1 right1 bottom1)
+	    (translate-fixnum-positions xoff2 yoff2 left2 top2 right2 bottom2)
+	    (ltrb-equals-ltrb-p left1 top1 right1 bottom1
+				left2 top2 right2 bottom2)))))))
+
+(defmethod region-contains-point*-p
+	   ((record output-record-element-mixin) x y)
+  (with-bounding-rectangle* (left top right bottom) record
+    (multiple-value-bind (xoff yoff) (compute-output-record-offsets record)
+      (declare (type coordinate xoff yoff))
+      (ltrb-contains-point*-p left top right bottom
+			      (+ x xoff) (+ y yoff)))))
+
+(defmethod region-contains-region-p
+	   ((record1 output-record-element-mixin) (record2 output-record-element-mixin))
+  (with-bounding-rectangle* (left1 top1 right1 bottom1) record1
+    (with-bounding-rectangle* (left2 top2 right2 bottom2) record2
+      (if (eq (output-record-parent record1) (output-record-parent record2))
+	  (ltrb-contains-ltrb-p left1 top1 right1 bottom1
+				left2 top2 right2 bottom2)
+	(multiple-value-bind (xoff1 yoff1) (compute-output-record-offsets record1)
+	  (declare (type coordinate xoff1 yoff1))
+	  (multiple-value-bind (xoff2 yoff2) (compute-output-record-offsets record2)
+	    (declare (type coordinate xoff2 yoff2))
+	    (translate-fixnum-positions xoff1 yoff1 left1 top1 right1 bottom1)
+	    (translate-fixnum-positions xoff2 yoff2 left2 top2 right2 bottom2)
+	    (ltrb-contains-ltrb-p left1 top1 right1 bottom1
+				  left2 top2 right2 bottom2)))))))
+
+(defmethod region-intersects-region-p
+	   ((record1 output-record-element-mixin) (record2 output-record-element-mixin))
+  (with-bounding-rectangle* (left1 top1 right1 bottom1) record1
+    (with-bounding-rectangle* (left2 top2 right2 bottom2) record2
+      (if (eq (output-record-parent record1) (output-record-parent record2))
+	  (ltrb-overlaps-ltrb-p left1 top1 right1 bottom1
+				left2 top2 right2 bottom2)
+	(multiple-value-bind (xoff1 yoff1) (compute-output-record-offsets record1)
+	  (declare (type coordinate xoff1 yoff1))
+	  (multiple-value-bind (xoff2 yoff2) (compute-output-record-offsets record2)
+	    (declare (type coordinate xoff2 yoff2))
+	    (translate-fixnum-positions xoff1 yoff1 left1 top1 right1 bottom1)
+	    (translate-fixnum-positions xoff2 yoff2 left2 top2 right2 bottom2)
+	    (ltrb-overlaps-ltrb-p left1 top1 right1 bottom1
+				  left2 top2 right2 bottom2)))))))
+
+(defun region-contains-offset-region-p (region1 region2 xoff yoff)
+  (declare (type coordinate xoff yoff))
+  (with-bounding-rectangle* (left1 top1 right1 bottom1) region1
+    (with-bounding-rectangle* (left2 top2 right2 bottom2) region2
+      (ltrb-contains-ltrb-p left1 top1 right1 bottom1
+			    (+ left2 xoff) (+ top2 yoff) (+ right2 xoff) (+ bottom2 yoff)))))
+
+(defun region-intersects-offset-region-p (region1 region2 xoff yoff)
+  (declare (type coordinate xoff yoff))
+  (with-bounding-rectangle* (left1 top1 right1 bottom1) region1
+    (with-bounding-rectangle* (left2 top2 right2 bottom2) region2
+      (ltrb-overlaps-ltrb-p left1 top1 right1 bottom1
+			    (+ left2 xoff) (+ top2 yoff) (+ right2 xoff) (+ bottom2 yoff)))))
+
+(defun offset-region-contains-point*-p (region xoff yoff x y)
+  (declare (type coordinate xoff yoff x y))
+   (with-bounding-rectangle* (left top right bottom) region
+     (ltrb-contains-point*-p (+ left xoff) (+ top yoff) (+ right xoff) (+ bottom yoff)
+			     x y)))
+
+;;; This maps over all of the children of the record
+#+Genera (zwei:defindentation (map-over-output-records 1 1))
+(defun map-over-output-records (function record
+				&optional (x-offset 0) (y-offset 0)
+				&rest continuation-args)
+  (declare (dynamic-extent function continuation-args))
+  (apply #'map-over-output-records-overlapping-region
+	 function record nil x-offset y-offset continuation-args))
+
+#+CLIM-1-compatibility
+(define-compatibility-function (map-over-output-record-elements
+				map-over-output-records)
+			       (record function
+				&optional x-offset y-offset &rest continuation-args)
+  (declare (dynamic-extent function continuation-args))
+  (apply #'map-over-output-records
+	 function record x-offset y-offset continuation-args))
+
+;;; This must map over the children in such a way that, when it maps over
+;;; overlapping children, the topmost (most recently inserted) child is
+;;; hit last.  This is because this function is used for things such as
+;;; replaying, where the most recently drawn thing must come out on top
+;;; (i.e., must be drawn last).  If the region is NIL, then this maps over
+;;; all of the children in the output record.
+#+Genera (zwei:defindentation (map-over-output-records-overlapping-region 2 1))
+(defgeneric map-over-output-records-overlapping-region
+	    (function record region
+	     &optional x-offset y-offset &rest continuation-args)
+  (declare (dynamic-extent function continuation-args)))
+
+#+CLIM-1-compatibility
+(define-compatibility-function (map-over-output-record-elements-overlapping-region
+				map-over-output-records-overlapping-region)
+			       (record region function
+				&optional x-offset y-offset &rest continuation-args)
+  (declare (dynamic-extent function continuation-args))
+  (apply #'map-over-output-records-overlapping-region
+	 function record region x-offset y-offset continuation-args))
+
+;;; This must map over the children in such a way that, when it maps over
+;;; overlapping children, the topmost (most recently inserted) child is
+;;; hit first, that is, the opposite order of MAP-...-OVERLAPPING-REGION.
+;;; This is because this function is used for things like locating the
+;;; presentation under the pointer, where the topmost thing wants to be
+;;; located first.
+#+Genera (zwei:defindentation (map-over-output-records-containing-point* 3 1))
+(defgeneric map-over-output-records-containing-point*
+	    (function record x y
+	     &optional x-offset y-offset &rest continuation-args)
+  (declare (dynamic-extent function continuation-args)))
+
+#+CLIM-1-compatibility
+(define-compatibility-function (map-over-output-record-elements-containing-point*
+				map-over-output-records-containing-point*)
+			       (record x y function
+				&optional x-offset y-offset &rest continuation-args)
+  (declare (dynamic-extent function continuation-args))
+  (apply #'map-over-output-records-containing-point*
+	 function record x y x-offset y-offset continuation-args))
+
+;;; X-offset and Y-offset represent the accumulated offset between the
+;;; regions's native coordinates and "our" coordinates and must be added
+;;; to our local coordinates (or subtracted from the region, if
+;;; possible) in order to validly compare them.
+;;; 
+;;; In the absence of x- and y- offsets, region should be in the
+;;; coordinate system of the record - i.e. relative to 
+;;;  (OUTPUT-RECORD-POSITION* RECORD).
+;;; This is the same coordinate system as the output record children
+;;; we are mapping over.
+(defmethod map-over-output-records-overlapping-region
+	   (function (record output-record-element-mixin) region
+	    &optional (x-offset 0) (y-offset 0) &rest continuation-args)
+  (declare (ignore region function x-offset y-offset continuation-args)
+	   (dynamic-extent function continuation-args))
+  nil)
+
+(defmethod map-over-output-records-containing-point*
+	   (function (record output-record-element-mixin) x y
+	    &optional (x-offset 0) (y-offset 0) &rest continuation-args)
+  (declare (ignore x y function x-offset y-offset continuation-args)
+	   (dynamic-extent function continuation-args))
+  nil)
+
+(defmethod map-over-output-records-containing-point*
+	   (function (record t) x y
+	    &optional (x-offset 0) (y-offset 0) &rest continuation-args)
+  (declare (dynamic-extent function continuation-args))
+  (apply #'map-over-output-records-overlapping-region
+	 function record (make-point x y)
+	 x-offset y-offset continuation-args))
+
+
+;; A mix-in for classes that can store other output records
+(defclass output-record-mixin ()
+     ;; OLD-CHILDREN is the list of >unmatched< output records from last
+     ;; redisplay pass.  if you implement your own FIND-INFERIOR-OUTPUT-RECORD,
+     ;; and iff you match from OLD-CHILDREN, you are required to remove the
+     ;; match from OLD-CHILDREN, probably by using DECACHE-INFERIOR-OUTPUT-RECORD.
+     ((old-children :initform nil :accessor output-record-old-children)
+      (generation-tick :initform 0 :initarg :generation-tick
+		       :accessor output-record-generation-tick)))
+
+(defmethod inferiors-never-overlap-p ((record output-record-mixin)) nil)
+
+#+Silica
+(defmethod note-output-record-moved :after ((record output-record-mixin) dx1 dy1 dx2 dy2)
+  (unless (= 0 dx1 dy1 dx2 dy2)
+    (map-over-output-records
+     #'(lambda (child)
+	 (note-output-record-moved child dx1 dy1 dx2 dy2))
+     record)))
+
+#+Silica
+(defmethod bounding-rectangle-set-position* :around ((record output-record-mixin) nx ny)
+  (multiple-value-bind (ox oy)
+      (output-record-position* record)
+    (call-next-method)
+    (when (or (/= ox nx) (/= oy ny))
+      (note-output-record-moved record 1 1 1 1))))
+
+#+Silica
+(defmethod bounding-rectangle-set-edges :around ((record output-record-mixin) 
+						 left top right bottom)
+  (declare (ignore  left top right bottom))
+  (multiple-value-bind (ox oy)
+      (output-record-position* record)
+    (call-next-method)
+    (multiple-value-bind (nx ny)
+	(output-record-position* record)
+      (when (or (/= ox nx) (/= oy ny))
+	(note-output-record-moved record 1 1 1 1)))))
+
+
+;; If some coordinate is relative to a given output-record, then
+;; CONVERT-FROM-RELATIVE-TO-ABSOLUTE-COORDINATES returns an x,y offset
+;; to be ADDED to any coordinates relative to OUTPUT-RECORD to give you
+;; absolute coordinates.
+(defun convert-from-relative-to-absolute-coordinates (stream output-record)
+  (declare (values x-offset y-offset))
+  (cond ((null output-record)
+	 (values 0 0)) ;;---------------------------- Why?
+	((and stream
+	      (eql output-record (stream-current-output-record stream)))
+	 (let ((position (stream-output-history-position stream)))
+	   (values (point-x position) (point-y position))))
+	((null (output-record-parent output-record))
+	 (values 0 0))
+	(t
+	 (multiple-value-bind (x y)
+	     (convert-from-relative-to-absolute-coordinates
+	       stream (output-record-parent output-record))
+	   (declare (type coordinate x y))
+	   (multiple-value-bind (our-x our-y) (output-record-position* output-record)
+	     (declare (type coordinate our-x our-y))
+	     (values (+ our-x x) (+ our-y y)))))))
+
+;; If some coordinate is in absolute coordinates, then
+;; CONVERT-FROM-ABSOLUTE-TO-RELATIVE-COORDINATES returns an x,y offset
+;; to be ADDED to any absolute coordinates to give you coordinates
+;; relative to OUTPUT-RECORD.
+(defun convert-from-absolute-to-relative-coordinates (stream output-record)
+  (declare (values x-offset y-offset))
+  (cond ((eql output-record (stream-current-output-record stream))
+	 (let ((position (stream-output-history-position stream)))
+	   (values (- (point-x position)) (- (point-y position)))))
+	((null (output-record-parent output-record))
+	 (values 0 0))
+	(t
+	 (multiple-value-bind (x y)
+	     (convert-from-absolute-to-relative-coordinates
+	       stream (output-record-parent output-record))
+	   (declare (type coordinate x y))
+	   (multiple-value-bind (our-x our-y) (output-record-position* output-record)
+	     (declare (type coordinate our-x our-y))
+	     (values (- x our-x) (- y our-y)))))))
+
+;; if ANCESTOR is an output-record with DESCENDANT as a descendant
+;; output-record (member of the transitive closure of all children of
+;; ancestor) then:  CONVERT-FROM-ANCESTOR-TO-DESCENDANT-COORDINATES
+;; returns an x,y offset pair that can be ADDED to any coordinates
+;; relative to ANCESTOR in order to get coordinates relative to
+;; DESCENDANT.
+(defun convert-from-ancestor-to-descendant-coordinates (ancestor descendant)
+  (declare (values x-offset y-offset))
+  (cond ((eql descendant ancestor)
+	 (values 0 0))
+	((null descendant)
+	 (error "~S was not an ancestor of ~S" ancestor descendant))
+	(t
+	 (multiple-value-bind (x y)
+	     (convert-from-ancestor-to-descendant-coordinates
+	       ancestor (output-record-parent descendant))
+	   (declare (type coordinate x y))
+	   (multiple-value-bind (our-x our-y) (output-record-position* descendant)
+	     (declare (type coordinate our-x our-y))
+	     (values (- x our-x) (- y our-y)))))))
+
+;; if ANCESTOR is an output-record with DESCENDANT as a descendant
+;; output-record (member of the transitive closure of all children of
+;; ancestor) then:  CONVERT-FROM-DESCENDANT-TO-ANCESTOR-COORDINATES
+;; returns an x,y offset pair that can be ADDED to any coordinates
+;; relative to DESCENDANT in order to get coordinates relative to
+;; ANCESTOR.
+(defun convert-from-descendant-to-ancestor-coordinates (descendant ancestor)
+  (declare (values x-offset y-offset))
+  (cond ((eql descendant ancestor)
+	 (values 0 0))
+	((null descendant)
+	 (error "~s was not an ancestor of ~s" ancestor descendant))
+	(t
+	 (multiple-value-bind (x y)
+	     (convert-from-descendant-to-ancestor-coordinates
+	       (output-record-parent descendant) ancestor)
+	   (declare (type coordinate x y))
+	   (multiple-value-bind (our-x our-y) (output-record-position* descendant)
+	     (declare (type coordinate our-x our-y))
+	     (values (+ our-x x) (+ our-y y)))))))
+
+
+(defun with-output-record-1 (continuation stream record &optional abs-x abs-y)
+  ;; Close the text record before and after, 
+  (stream-close-text-output-record stream)
+  (let ((current-output-position
+	  (stream-output-history-position stream)))
+    (unless abs-y
+      (multiple-value-setq (abs-x abs-y)
+	(stream-cursor-position* stream)))
+    (letf-globally (((point-x current-output-position) abs-x)
+		    ((point-y current-output-position) abs-y)
+		    ((stream-current-output-record stream) record))
+      (funcall continuation record)
+      (multiple-value-bind (end-x end-y)
+	  (stream-cursor-position* stream)
+	(declare (type coordinate end-x end-y))
+	(output-record-set-end-cursor-position*
+	  record (- end-x abs-x) (- end-y abs-y)))
+      (stream-close-text-output-record stream))))
+
+;;; Rest of stuff started in clim-defs...
+(defun construct-output-record-1 (type &rest init-args)
+  (declare (dynamic-extent init-args))
+  (let ((constructor (gethash type *output-record-constructor-cache*)))
+    (if constructor
+	(apply constructor init-args)
+	(apply #'make-instance type init-args))))
+
+#||
+;;; A hash table associating vectors holding free output records.
+;;; The idea is to not cons on allocate/free, but be fast.
+(defvar *record-resource-table* (make-hash-table))
+(defvar *use-record-resources* nil)
+
+(defun allocate-record (type)
+  (when *use-record-resources*
+    (multiple-value-bind (record-vector found-p)
+	(gethash type *record-resource-table*)
+      (unless found-p
+	(setq record-vector
+	      (setf (gethash type *record-resource-table*)
+		    (make-array 20 :fill-pointer 0))))
+      (vector-pop record-vector))))
+
+(defun free-record (record)
+  (when *use-record-resources*
+    (let ((type (class-name (class-of record))))
+      (multiple-value-bind (record-vector found-p)
+	  (gethash type *record-resource-table*)
+	(unless found-p
+	  (setq record-vector
+		(setf (gethash type *record-resource-table*)
+		      (make-array 20 :fill-pointer 0))))
+	(setf (output-record-parent record) nil)
+	(vector-push-extend record record-vector)))))
+||#
+
+(defun invoke-with-new-output-record (stream continuation record-type constructor
+				      &rest init-args &key parent &allow-other-keys)
+  (declare (dynamic-extent init-args))
+  (with-keywords-removed (init-args init-args '(:parent))
+    (let* ((current-output-record (stream-current-output-record stream))
+	   (new-output-record (and (stream-redisplaying-p stream)
+				   current-output-record
+				   (apply #'find-inferior-output-record-1
+					  current-output-record record-type init-args))))
+      (multiple-value-bind (cursor-x cursor-y)
+	  (stream-cursor-position* stream)
+	(declare (type coordinate cursor-x cursor-y))
+	(multiple-value-bind (x y)
+	    (multiple-value-bind (px py)
+		(point-position*
+		  (stream-output-history-position stream))
+	      (declare (type coordinate px py))
+	      (position-difference* cursor-x cursor-y px py))
+	  (declare (type coordinate x y))
+	  (if new-output-record
+	      (copy-display-state new-output-record nil)
+	      (setq new-output-record
+		    ;;--- Used to call ALLOCATE-RECORD, then initialize by
+		    ;;--- setting the edges (or INITIALIZE-INSTANCE)
+		    (if constructor
+			(apply constructor
+			       :x-position x :y-position y init-args)
+			(apply #'construct-output-record-1 record-type
+			       :x-position x :y-position y init-args))))
+	  (output-record-set-start-cursor-position* new-output-record x y)
+	  (with-output-record-1 continuation 
+				stream new-output-record cursor-x cursor-y)
+	  (when (stream-redisplaying-p stream)
+	    (recompute-contents-ok new-output-record))
+	  ;; We set the parent after doing everything else so that calls
+	  ;; to RECOMPUTE-CONTENTS-OK inside the dynamic extent of the
+	  ;; continuation won't take forever.
+	  (let ((parent (or parent
+			    current-output-record
+			    (stream-output-history stream))))
+	    (when parent 
+	      (add-output-record new-output-record parent)))
+	  new-output-record)))))
+
+(defun invoke-with-room-for-graphics (stream continuation record-type move-cursor &key height)
+  (let ((record
+	  (with-output-recording-options (stream :draw nil :record t)
+	    (with-first-quadrant-coordinates (stream)
+	      (with-new-output-record (stream record-type)
+		(funcall continuation stream))))))
+    (multiple-value-bind (x y) (output-record-position* record)
+      (declare (type coordinate x y))
+      ;;--- Hey, there is something wierd going on here.  The problem is that
+      ;;--- OUTPUT-RECORD-POSITION* and OUTPUT-RECORD-SET-POSITION* seem to obey
+      ;;--- different coordinate system conventions.  Geez.
+      (when height
+	(incf y (- height (bounding-rectangle-height record))))
+      (output-record-set-position* record x y))
+    (tree-recompute-extent record)
+    (replay record stream)
+    (when move-cursor
+      (move-cursor-beyond-output-record stream record))
+    record))
+
+(defun replay (record stream &optional region)
+  (when (stream-drawing-p stream)
+    (multiple-value-bind (x-offset y-offset)
+	(convert-from-relative-to-absolute-coordinates stream (output-record-parent record))
+      ;; Output recording should be off, but let's be forgiving...
+      (letf-globally (((stream-recording-p stream) nil))
+	(replay-output-record record stream region x-offset y-offset)))))
+
+;; Replay all the the inferiors of RECORD that overlap REGION.
+(defmethod replay-output-record ((record output-record-mixin) stream
+				 &optional region (x-offset 0) (y-offset 0))
+  (declare (type coordinate x-offset y-offset))
+  ;;--- Doing things this way bypasses any REPLAY-OUTPUT-RECORD methods supplied on 
+  ;;--- non-standard classes that satisfy the output record protocol.
+  ;;--- Too bad, this relative coordinates stuff is a disaster anyway.
+  (labels ((replay-1 (record x-offset y-offset)
+	     (declare (type coordinate x-offset y-offset))
+	     (if (output-record-p record)
+		 (multiple-value-bind (xoff yoff) (output-record-position* record)
+		   (map-over-output-records-overlapping-region 
+		     #'replay-1 record region 
+		     (- x-offset) (- y-offset)
+		     (+ x-offset xoff) (+ y-offset yoff)))
+		 (replay-output-record record stream region x-offset y-offset))))
+    (declare (dynamic-extent #'replay-1))
+    (replay-1 record x-offset y-offset)))
+
+(defun move-cursor-beyond-output-record (stream record)
+  (multiple-value-bind (x-offset y-offset)
+      (convert-from-relative-to-absolute-coordinates
+	stream (output-record-parent record))
+    (declare (type coordinate x-offset y-offset))
+    (with-bounding-rectangle* (left top right bottom) record
+      (declare (ignore left top))
+      (with-end-of-page-action (stream :allow)
+	(stream-set-cursor-position*
+	  stream
+	  (+ right x-offset) (- (+ bottom y-offset) (stream-line-height stream)))))))
+
+
+(defmethod recompute-extent-for-changed-child ((record output-record-mixin) child
+					       old-left old-top old-right old-bottom)
+  (declare (type coordinate old-top old-right old-bottom))
+  ;; old edges are passed in parent's coordinate system because
+  ;; their reference point may have changed.
+  ;; (assert (child-completely-contained-within-extent-of record child))
+  (with-slots (parent) record
+    (with-bounding-rectangle* (left top right bottom) record
+      ;; We must recompute the extent if the child is not completely contained
+      ;; or if it used to "define" one of the old edges.
+      ;; A picture would help, but we're not going to draw it here. (:-)
+      (multiple-value-bind (xoff yoff)
+	  (convert-from-descendant-to-ancestor-coordinates record parent)
+	(when (or (not (region-contains-offset-region-p record child xoff yoff))
+		  (= old-left left)
+		  (= old-top top)
+		  (= old-right right)
+		  (= old-bottom bottom))
+	  (recompute-extent record))))))
+
+(defmethod recompute-extent ((record output-record-mixin))
+  (with-slots (parent) record
+    (with-bounding-rectangle* (old-left old-top old-right old-bottom) record
+      (let ((once nil)
+	    (min-x 0) (min-y 0) (max-x 0) (max-y 0))
+	(declare (type coordinate min-x min-y max-x max-y))
+	(flet ((recompute-extent-of-child (child)
+		 (with-bounding-rectangle* (left top right bottom) child
+		   (cond (once
+			  (minf min-x left)
+			  (minf min-y top)
+			  (maxf max-x right)
+			  (maxf max-y bottom))
+			 (t
+			  (setq min-x left
+				min-y top
+				max-x right
+				max-y bottom
+				once  t))))))
+	  (declare (dynamic-extent #'recompute-extent-of-child))
+	  (map-over-output-records #'recompute-extent-of-child record))
+	(multiple-value-bind (xoff yoff)
+	    (convert-from-descendant-to-ancestor-coordinates record parent)
+	  (declare (type coordinate xoff yoff))
+	  (if once
+	      (progn (assert (ltrb-well-formed-p min-x min-y max-x max-y))
+		     (bounding-rectangle-set-edges
+		       record
+		       (+ min-x xoff) (+ min-y yoff)
+		       (+ max-x xoff) (+ max-y yoff)))
+	      ;; No children
+	      (bounding-rectangle-set-edges record 0 0 0 0))
+	  ;; Pass these coordinates in parent's coordinate system (I think)
+	  (translate-fixnum-positions xoff yoff
+	    old-left old-top old-right old-bottom))
+	(when parent
+	  (recompute-extent-for-changed-child
+	    parent record old-left old-top old-right old-bottom))))))
+
+(defmethod recompute-extent-for-new-child ((record output-record-mixin) child)
+  (with-slots (parent) record
+    (with-bounding-rectangle* (left top right bottom) record
+      (let ((old-left left)
+	    (old-top top)
+	    (old-right right)
+	    (old-bottom bottom))
+	(with-bounding-rectangle* (eleft etop eright ebottom) child
+	  (multiple-value-bind (xoff yoff)
+	      (convert-from-descendant-to-ancestor-coordinates record parent)
+	    (translate-fixnum-positions xoff yoff
+	      eleft etop eright ebottom
+	      ;; pass these coordinates in parent's coordinate system.
+	      old-left old-top old-right old-bottom))
+	  (cond ((= (output-record-count record) 1)
+		 (bounding-rectangle-set-edges record eleft etop eright ebottom))
+		(t (bounding-rectangle-set-edges record
+						 (min left eleft) (min top etop)
+						 (max right eright) (max bottom ebottom)))))
+	(when parent
+	  (recompute-extent-for-changed-child
+	    parent record old-left old-top old-right old-bottom))))))
+
+;;; This is for adjusting extents after a bunch of leaves have been moved.
+(defmethod tree-recompute-extent ((record output-record-element-mixin))
+  (with-bounding-rectangle* (old-left old-top old-right old-bottom) record
+    (let ((parent (output-record-parent record)))
+      (multiple-value-bind (xoff yoff)
+	  (convert-from-descendant-to-ancestor-coordinates record parent)
+	(declare (type coordinate xoff yoff))
+	;; we must pass the old coordinates in the parent's coordinate system
+	;; because tree-recompute-extent-1 may adjust the reference point.
+	(translate-fixnum-positions xoff yoff old-left old-top old-right old-bottom))
+      (tree-recompute-extent-1 record)
+      (when parent
+	(recompute-extent-for-changed-child
+	  parent record old-left old-top old-right old-bottom)))))
+
+#+CLIM-1-compatibility
+(progn
+(define-compatibility-function (add-output-record-element add-output-record)
+			       (record child)
+  (add-output-record child record))
+
+(define-compatibility-function (delete-output-record-element delete-output-record)
+			       (record child &optional (errorp t))
+  (delete-output-record child record errorp))
+
+(define-compatibility-function (output-record-elements output-record-children)
+			       (record)
+  (output-record-children record))
+
+(define-compatibility-function (output-record-element-count output-record-count)n
+			       (record)
+  (output-record-count record))
+)	;#+CLIM-1-compatibility
+
+
+;;; Common to all implementations.
+;;; ADD-OUTPUT-RECORD assumes that CHILD's start-position and bounding 
+;;; rectangle have already been normalized to RECORD's coordinate system.
+(defmethod add-output-record :after (child (record output-record-mixin)) ;was :around
+  (setf (output-record-parent child) record)
+  (recompute-extent-for-new-child record child)
+  (when (output-record-stream record)
+    (note-output-record-attached child (output-record-stream record))))
+
+(defmethod note-output-record-attached ((record output-record-element-mixin) stream)
+  (setf (output-record-stream record) stream))
+
+(defmethod note-output-record-attached :after ((record output-record-mixin) stream)
+  (map-over-output-records
+   #'(lambda (rec)
+       (note-output-record-attached rec stream))
+   record))
+
+;;; Ditto.
+(defmethod delete-output-record :after
+	   (child (record output-record-mixin) &optional (errorp t))
+  (declare (ignore errorp))
+  (with-bounding-rectangle* (left top right bottom) child
+    (multiple-value-bind (xoff yoff)
+	(convert-from-descendant-to-ancestor-coordinates child record)
+      (declare (type coordinate xoff yoff))
+      (translate-fixnum-positions xoff yoff left top right bottom)
+      (recompute-extent-for-changed-child record child left top right bottom)))
+  (setf (output-record-parent child) nil))	;in case other things are still pointing to it.
+
+(defmethod delete-output-record :around (child (record output-record-mixin) &optional errorp)
+  (declare (ignore errorp))
+  (let ((stream (output-record-stream child)))
+    (multiple-value-prog1
+	(call-next-method)
+      (when stream
+	(note-output-record-detached child)))))
+
+
+(defmethod note-output-record-detached ((record output-record-element-mixin))
+  (setf (output-record-stream record) nil))
+
+(defmethod note-output-record-detached :after ((record output-record-mixin))
+  (map-over-output-records
+   #'note-output-record-detached
+   record))
+
+;;; Recurse down all inferiors returning them to the "resource" table.
+#+++ignore
+(defmethod clear-output-record :before ((record output-record-mixin))
+	   (free-output-record record))
+
+;;; Invoked by CLEAR-OUTPUT-RECORD.
+#+++ignore
+(defmethod free-output-record ((record output-record-element-mixin))
+  (free-record record)
+  (map-over-output-records #'free-output-record record))
+
+(defmethod clear-output-record :after ((record output-record-mixin))
+  (bounding-rectangle-set-edges record 0 0 0 0))
+
+(defmethod clear-output-record :around ((record output-record-mixin))
+  (when (output-record-stream record)
+    (map-over-output-records
+     #'note-output-record-detached
+     record))
+  (call-next-method))
+
+
+;;; Sequence output records store their children in a vector
+(defclass standard-sequence-output-record
+	  (output-record-mixin output-record-element-mixin output-record)
+    ((elements :initform nil)
+     (fill-pointer :initform 0 :type fixnum)))
+
+(define-output-record-constructor standard-sequence-output-record
+				  (&key x-position y-position (size 5))
+  :x-position x-position :y-position y-position :size size)
+
+(defmethod initialize-instance :after ((record standard-sequence-output-record) 
+				       &key (size 5))
+  ;; probably want to save size away somewhere so that the
+  ;; guy who actually makes the array can reference it...
+  (declare (ignore size))
+  ;; size defaults to very small to save space
+  ;; most dependent classes will have supplied default-initargs with better
+  ;; chosen default.
+  (with-slots (elements fill-pointer) record
+    ;; We run initialize-instance to re-initialize the record, so don't re-alloc the array
+    (etypecase elements
+      ((or null output-record displayed-output-record) (setf elements nil))
+      (array (setf fill-pointer 0)))))
+
+;;; For debugging.
+(defmethod output-record-children ((record standard-sequence-output-record))
+  (with-slots (elements fill-pointer) record
+    (typecase elements
+      (null nil)
+      (array
+	(let ((result (make-list fill-pointer)))
+	  (replace result elements :end1 fill-pointer :end2 fill-pointer)
+	  result))
+      ;; It must be an OUTPUT-RECORD or a DISPLAYED-OUTPUT-RECORD
+      (otherwise (list elements)))))
+
+(defmethod output-record-element ((record standard-sequence-output-record) index)
+  (with-slots (elements) record
+    (svref elements index)))
+
+(defmethod output-record-count ((record standard-sequence-output-record))
+  (with-slots (elements fill-pointer) record
+    (typecase elements
+      (null 0)
+      (array fill-pointer)
+      ;; It must be an OUTPUT-RECORD or a DISPLAYED-OUTPUT-RECORD
+      (otherwise 1))))
+
+(defmethod clear-output-record ((record standard-sequence-output-record))
+  (with-slots (elements fill-pointer) record
+    (typecase elements
+      (null nil)
+      (array (setf fill-pointer 0))
+      ;; It must be an OUTPUT-RECORD or a DISPLAYED-OUTPUT-RECORD
+      (otherwise (setf elements nil)))))
+
+(defmethod add-output-record (child (record standard-sequence-output-record))
+  (with-slots (elements fill-pointer) record
+    (typecase elements
+      (null
+	(setf elements child))
+      (array
+	(multiple-value-setq (elements fill-pointer)
+	  (simple-vector-push-extend child elements fill-pointer)))
+      ;; It must be an OUTPUT-RECORD or a DISPLAYED-OUTPUT-RECORD
+      (otherwise
+	(let ((first elements))
+	  (setf elements (make-array 5))
+	  (setf fill-pointer 2)
+	  (setf (svref elements 0) first)
+	  (setf (svref elements 1) child))))))
+
+(defmethod delete-output-record 
+	   (child (record standard-sequence-output-record) &optional (errorp t))
+  (with-slots (elements fill-pointer) record
+    (typecase elements
+      (null (error "The output record ~S was not found in ~S" child record))
+      (array
+	(let ((index (position child elements :end fill-pointer)))
+	  (cond (index
+		 (let ((new-fp (the fixnum (1- fill-pointer)))
+		       (vector elements))
+		   (declare (type simple-vector vector) (fixnum new-fp)
+			    #+Genera (sys:array-register vector))
+		   (unless (= (the fixnum index) new-fp)
+		     ;; Shift the whole vector downward
+		     (do ((i (the fixnum index) (1+ i)))
+			 ((= i new-fp))
+		       (declare (fixnum i) (optimize (speed 3) (safety 0)))
+		       (setf (svref vector i) (svref vector (1+ i)))))
+		   (setf fill-pointer new-fp)))
+		(errorp
+		 (error "The output record ~S was not found in ~S" child record)))))
+      ;; It must be an OUTPUT-RECORD or a DISPLAYED-OUTPUT-RECORD
+      (otherwise
+	(unless (eql elements child)
+	  (error "The output record ~S was not found in ~S" child record))
+	(setf elements nil))))
+  t)
+
+(defmethod map-over-output-records-overlapping-region
+	   (function (record standard-sequence-output-record) region  
+	    &optional (x-offset 0) (y-offset 0) &rest continuation-args)
+  (declare (dynamic-extent function continuation-args))
+  (declare (type coordinate x-offset y-offset))
+  (declare (optimize (safety 0)))
+  (with-slots (elements fill-pointer) record
+    (typecase elements
+      (null nil)
+      (array
+	(if (or (null region) (eql region +everywhere+))
+	    (dovector (child elements :start 0 :end fill-pointer :simple-p t)
+	      (apply function child continuation-args))
+	  (with-bounding-rectangle* (left1 top1 right1 bottom1) region
+	    (translate-fixnum-positions x-offset y-offset left1 top1 right1 bottom1)
+	    ;; Subtract out the record offset from the region, to make comparison fair
+	    (multiple-value-bind (xoff yoff)
+		(output-record-position* record)
+	      (translate-fixnum-positions (- xoff) (- yoff) left1 top1 right1 bottom1))
+	    (dovector (child elements :start 0 :end fill-pointer :simple-p t)
+	      (with-bounding-rectangle* (left2 top2 right2 bottom2) child
+		(when (ltrb-overlaps-ltrb-p left1 top1 right1 bottom1
+					    left2 top2 right2 bottom2)
+		  (apply function child continuation-args)))))))
+      (otherwise
+	(if (or (null region) (eql region +everywhere+))
+	    (apply function elements continuation-args)
+	  (multiple-value-bind (xoff yoff)
+	      (output-record-position* record)
+	    (declare (type coordinate xoff yoff))
+	    (when (region-intersects-offset-region-p
+		    elements region (- x-offset xoff) (- y-offset yoff))
+	      (apply function elements continuation-args)))))))
+  nil)
+
+(defmethod map-over-output-records-containing-point*
+	   (function (record standard-sequence-output-record) x y 
+	    &optional (x-offset 0) (y-offset 0) &rest continuation-args)
+  (declare (dynamic-extent function continuation-args))
+  (declare (type coordinate x y x-offset y-offset))
+  (declare (optimize (safety 0)))
+  (translate-fixnum-positions x-offset y-offset x y)
+  (with-slots (elements fill-pointer) record
+    (typecase elements
+      (null nil)
+      (array
+	(multiple-value-bind (xoff yoff)
+	    (output-record-position* record)
+	  (translate-fixnum-positions (- xoff) (- yoff) x y))
+	(dovector (child elements :start 0 :end fill-pointer :from-end t :simple-p t)
+	  (with-bounding-rectangle* (left top right bottom) child
+	    (when (ltrb-contains-point*-p left top right bottom x y)
+	      (apply function child continuation-args)))))
+      (otherwise
+	(multiple-value-bind (xoff yoff) (output-record-position* record)
+	  (when (offset-region-contains-point*-p elements xoff yoff x y)
+	    (apply function elements continuation-args))))))
+  nil)
+
+
+;;; Mix this in for top-level output histories
+(defclass stream-output-history-mixin () ((stream)))
+
+(defmethod bounding-rectangle-set-edges ((record stream-output-history-mixin)
+					 left top right bottom)
+  (declare (type coordinate left top right bottom))
+  #+ignore (assert (<= left right))
+  #+ignore (assert (<= top bottom))
+  (with-slots ((bl left) (bt top) (br right) (bb bottom) parent stream) record
+    ;; Top-level output records must not have their upper left corner any
+    ;; "later" than (0,0), or else scroll bars and scrolling will not do
+    ;; the right thing.
+    (let ((old-left bl)
+	  (old-top bt)
+	  (old-right br)
+	  (old-bottom bb))
+      (declare (type coordinate old-left old-top old-right old-bottom))
+      (setq bl (min left 0)
+	    bt (min top 0)
+	    br right
+	    bb bottom)))
+  record)
+
+#+Silica
+(defmethod bounding-rectangle-set-edges :around ((r stream-output-history-mixin) 
+						 nminx nminy nmaxx nmaxy)
+  (multiple-value-bind
+      (minx miny maxx maxy)
+      (bounding-rectangle* r)
+    (call-next-method)
+    (unless (and (= minx nminx)
+		 (= miny nminy)
+		 (= maxx nmaxx)
+		 (= maxy nmaxy))
+      ;; This should update the scrollbars etc 
+      (let* ((stream (output-record-stream r))
+	     (vp (pane-viewport stream)))
+	(when vp
+	  (update-scrollbars vp))
+	(update-region stream (- nmaxx nminx) (- nmaxy nminy))))))
+
+;;; Defclass of OUTPUT-RECORDING-MIXIN, etc. is in STREAM-CLASS-DEFS
+(defmethod initialize-instance :after ((stream output-recording-mixin) &rest args)
+  (declare (ignore args))
+  (with-slots (output-record) stream
+    ;;--- Our OUTPUT-RECORDING-MIXIN expects extended output...
+    (multiple-value-bind (x y) (stream-cursor-position* stream)
+      ;; I don't understand why the output record's initial position was set to
+      ;; some untransformed "viewport" coordinate.  The cursor position is the
+      ;; right place, no?
+      (output-record-set-position* output-record x y))
+    (setf (slot-value output-record 'stream) stream)))
+
+(defmethod clear-output-history ((stream output-recording-mixin))
+  (when (stream-output-history stream)
+    (clear-output-record (stream-output-history stream)))
+  (setf (stream-text-output-record stream) nil)
+  (setf (stream-highlighted-presentation stream) nil))
+
+(defmethod stream-add-output-record ((stream output-recording-mixin) record)
+  (with-slots (output-record current-output-record-stack) stream
+    (let ((the-output-record (or current-output-record-stack output-record)))
+     (add-output-record record the-output-record)
+     #+Silica
+     (let ((width (bounding-rectangle-width stream))
+	   (height (bounding-rectangle-height stream)))
+       (declare (type coordinate width height))
+       (with-bounding-rectangle* (rl rt rr rb) the-output-record
+	 (when (or (< rl 0) (< width rr)
+		   (< rt 0) (< height rb))
+	   (update-region stream (- rr rl) (- rb rt))))))))
+
+(defmethod stream-replay ((stream output-recording-mixin) &optional region)
+  (when (stream-drawing-p stream)
+    (with-slots (output-record text-output-record record-p) stream
+      (when (or output-record text-output-record)
+	(letf-globally ((record-p nil))
+	  (when output-record
+	    (replay-output-record output-record stream region 0 0))
+	  (when text-output-record
+	    (replay-output-record text-output-record stream region 0 0)))))))
+
+(defun erase-output-record (output-record stream)	;--- specialize on stream?
+  (multiple-value-bind (xoff yoff)
+      (convert-from-relative-to-absolute-coordinates 
+	;; --- I'm certainly going to forget to use the PARENT at some point!
+	stream (output-record-parent output-record))
+    (with-bounding-rectangle* (left top right bottom) output-record
+      (with-output-recording-options (stream :record nil)
+	(if (or (= left right) (= top bottom))
+	    ;; Handle specially, for a line is wider than a rectangle of zero width or height
+	    (draw-line-internal stream xoff yoff
+				left top right bottom
+				+background-ink+ nil)
+	    (draw-rectangle-internal stream xoff yoff
+				     left top right bottom
+				     +background-ink+ nil)))))
+  (when (output-record-parent output-record)
+    (delete-output-record output-record (output-record-parent output-record)))
+  ;; Use the output record itself as the replay region, and replay
+  ;; the stuff that might have been obscured by the erased output
+  (frame-replay *application-frame* stream output-record))
+
+(defmethod invoke-with-output-recording-options ((stream output-recording-mixin)
+						 continuation record draw)
+  (letf-globally (((stream-recording-p stream) record)
+		  ((stream-drawing-p stream) draw))
+    (funcall continuation)))
+
+;;; The following two are only called when STREAM-RECORDING-P is true and the
+;;; characters are printable (see CHARACTER-DRAWING.LISP).
+(defmethod stream-add-string-output ((stream output-recording-mixin) string
+				     start end text-style width height baseline)
+  (declare (fixnum start end))
+  (when (< start end)
+    (let ((record (get-text-output-record stream text-style)))
+      (add-string-output-to-text-record record string start end text-style
+					width height baseline))))
+
+(defmethod stream-add-character-output ((stream output-recording-mixin) character
+					text-style width height baseline)
+  (let ((record (get-text-output-record stream text-style)))
+    (add-character-output-to-text-record record character text-style
+					 width height baseline)))
+
+(defmethod get-text-output-record ((stream output-recording-mixin) style)
+  (let ((default-style (medium-default-text-style stream)))
+    (let ((record (stream-text-output-record stream)))
+      (when record
+	;; If we're changing styles mid-stream, need to convert this
+	;; text record to the more expensive form
+	(when (and (not (eq style default-style))
+		   (not (typep record 'styled-text-output-record)))
+	  (setq record (stylize-text-output-record record default-style stream)))
+	(return-from get-text-output-record record)))
+    (let* ((string (make-array 16 :element-type 'extended-char	;--- 16?
+				  :fill-pointer 0 :adjustable t))
+	   (record (if (not (eq style default-style))
+		       (make-styled-text-output-record (medium-ink stream) string)
+		       (make-standard-text-output-record (medium-ink stream) string))))
+      (setf (stream-text-output-record stream) record)
+      (multiple-value-bind (abs-x abs-y)
+	  (point-position*
+	    (stream-output-history-position stream))
+	(declare (type coordinate abs-x abs-y))
+	(multiple-value-bind (cx cy) (stream-cursor-position* stream)
+	  (declare (type coordinate cx cy))
+	  (output-record-set-start-cursor-position*
+	    record (- cx abs-x) (- cy abs-y))))
+      ;; Moved to STREAM-CLOSE-TEXT-OUTPUT-RECORD, since we don't need this thing
+      ;; in the history until then.  This should save an extra recompute-extent call
+      ;; (one in here, one when the string is added).
+      ;; (stream-add-output-record stream record)
+      record)))
+
+(defmethod stream-close-text-output-record ((stream output-recording-mixin)
+					    &optional wrapped)
+  ;; It's faster to access the slot directly instead of going through 
+  ;; STREAM-TEXT-OUTPUT-RECORD
+  (let ((text-record (slot-value stream 'text-output-record)))
+    (when text-record
+      (when wrapped
+	(setf (slot-value text-record 'wrapped-p) t))
+      (stream-add-output-record stream text-record)
+      (when (stream-redisplaying-p stream)
+	(recompute-contents-ok text-record))
+      (setf (slot-value stream 'text-output-record) nil))))
+
+(defmethod stream-force-output :after ((stream output-recording-mixin))
+  (stream-close-text-output-record stream))
+
+(defmethod stream-finish-output :after ((stream output-recording-mixin))
+  (stream-close-text-output-record stream))
+
+;; When setting cursor position, have to dump old text record.
+;; This is necessary in order to capture the correct cursor position in
+;; text output records.  If we did not close the current text record,
+;; a sequence such as WRITE-STRING/SET-CURSORPOS/WRITE-STRING would
+;; create only a single output record, and intervening whitespace would
+;; be lost if the two WRITE-STRINGs took place on the same line.
+(defmethod stream-set-cursor-position* :before ((stream output-recording-mixin) x y)
+  (declare (ignore x y))
+  (stream-close-text-output-record stream))
+
+;; This gets used to reposition the cursor when drawing text.  We need to
+;; close the text output record when there was a line wrap, but not when
+;; we are simply incrementing the cursor beyond the just-written glyph.
+(defmethod stream-set-cursor-position*-internal :before ((stream output-recording-mixin) x y)
+  (declare (ignore x))
+  (multiple-value-bind (old-x old-y) (stream-cursor-position* stream)
+    (declare (ignore old-x))
+    (unless (eql y old-y)
+      (stream-close-text-output-record stream))))
+
+;; Copy just the text from the window to the stream.  If REGION is supplied,
+;; only the text overlapping that region is copied.
+;; This loses information about text styles, presentations, and graphics, and
+;; doesn't deal perfectly with tab characters and changing baselines.
+(defun copy-textual-output-history (window stream &optional region)
+  (let* ((char-width (stream-character-width window #\space))
+	 (line-height (stream-line-height window))
+	 (history (stream-output-history window))
+	 (array (make-array (ceiling (bounding-rectangle-height history) line-height)
+			    :fill-pointer 0 :adjustable t :initial-element nil)))
+    (labels ((collect (record x-offset y-offset)
+	       (multiple-value-bind (start-x start-y)
+		   (output-record-start-cursor-position* record)
+		 (translate-positions x-offset y-offset start-x start-y)
+		 (when (typep record 'standard-text-output-record)
+		   (vector-push-extend (list* start-y start-x (slot-value record 'string))
+				       array))
+		 (map-over-output-records-overlapping-region
+		   #'collect record region 
+		   (- x-offset) (- y-offset) start-x start-y))))
+      (declare (dynamic-extent #'collect))
+      (collect history 0 0))
+    (sort array #'(lambda (r1 r2)
+		    (or (< (first r1) (first r2))
+			(and (= (first r1) (first r2))
+			     (< (second r1) (second r2))))))
+    (let ((current-x 0)
+	  (current-y (first (aref array 0))))
+      (dotimes (i (fill-pointer array))
+	(let* ((item (aref array i))
+	       (y (pop item))
+	       (x (pop item)))
+	  (unless (= y current-y)
+	    (dotimes (j (round (- y current-y) line-height))
+	      #-(or Allegro Minima) (declare (ignore j))
+	      (terpri stream)
+	      (setq current-x 0))
+	    (setq current-y y))
+	  (unless (= x current-x)
+	    (dotimes (j (round (- x current-x) char-width))
+	      #-(or Allegro Minima) (declare (ignore j))
+	      (write-char #\space stream))
+	    (setq current-x x))
+	  (write-string item stream)
+	  (incf current-x (stream-string-width window item)))))))
+
+;;; This method should cover a multitude of sins.
+#+Silica
+(defmethod repaint-sheet :after ((stream output-recording-mixin) region)
+  ;;--- Who should establish the clipping region?
+  ;; Who should clear the region?
+  (with-sheet-medium (medium stream)
+    (multiple-value-call #'draw-rectangle*
+      medium
+      (bounding-rectangle* (region-intersection
+			    region 
+			    (or (pane-viewport-region stream)
+				(bounding-rectangle stream))))
+      :ink +background-ink+))
+  (stream-replay stream region))
+
+
+
+;;; For Silica
+;;;--- Consider these old methods on a case-by-case basis to see if the
+;;; general handle-repaint method subsumes them.
+
+;;; --- should merge our process-update-region with handle-repaint
+;;; Do we use it anywhere where Silica isn't generating handle-repaint?
+
+;;; Mix in window-output-recording when you have mixed together
+;;; something supporting the window protocol and something supporting
+;;; the output recording protocol.
+#-Silica
+(progn
+
+(defmethod window-process-update-region :around ((stream window-output-recording))
+  (let ((update-region (slot-value stream 'update-region)))
+    (when update-region
+      (with-output-recording-options (stream :draw t :record nil)
+	(let ((highlighted-presentation (slot-value stream 'highlighted-presentation)))
+	  (when highlighted-presentation
+	    (highlight-output-record stream highlighted-presentation :unhighlight))
+	  (call-next-method)
+	  (dolist (region update-region)
+	    (with-clipping-region (stream region)
+	      (frame-replay *application-frame* stream region)))
+	  (when highlighted-presentation
+	    (highlight-output-record stream highlighted-presentation :highlight))))
+      (window-flush-update-region stream))))
+
+;;;--- We need some version of this code to do the area copying.
+(defmethod window-set-viewport-position* :around ((stream window-output-recording)
+						  new-x new-y)
+  (declare (ignore new-x new-y))
+  (with-bounding-rectangle* (left top right bottom) (window-viewport stream)
+    (call-next-method)
+    ;; now replay
+    (with-bounding-rectangle* (nl nt nr nb) (window-viewport stream)
+      (cond
+	;; if some of the stuff that was previously on display is still on display
+	;; bitblt it into the proper place and redraw the rest.
+	((ltrb-overlaps-ltrb-p left top right bottom
+			       nl nt nr nb)
+	 ;; move the old stuff to the new position
+	 (window-shift-visible-region stream left top right bottom
+				      nl nt nr nb)
+	 (window-process-update-region stream))
+	;; otherwise, just redraw the whole visible viewport
+	;; Adjust for the left and top margins by hand so clear-area doesn't erase
+	;; the margin components.
+	(t (multiple-value-bind (ml mt) (window-margins stream)
+	     ;;--- Will these be coords or fixnums?
+	     (declare (type coordinate ml mt))
+	     (multiple-value-bind (vw vh) (window-inside-size stream)
+	       (declare (type coordinate vw vh))
+	       (window-clear-area stream
+				  ml mt (+ ml vw) (+ mt vh))))
+	   (frame-replay *application-frame* stream (window-viewport stream)))))))
+
+(defmethod window-refresh :after ((stream window-output-recording))
+  ;; don't bother me, it takes too long and is useless since
+  ;; we'll refresh this again when it eventually becomes visible
+  (when (window-drawing-possible stream)
+    (frame-replay *application-frame* stream (window-viewport stream))
+    (let ((text-record (stream-text-output-record stream)))
+      (when text-record (replay text-record stream)))
+    (redisplay-decorations stream)))
+
+;;; I don't think that this is needed.
+(defmethod window-note-size-or-position-change :after ((stream window-output-recording)
+						       left top right bottom)
+  (declare (ignore left top right bottom))
+  #+Ignore
+  (when (window-visibility stream)
+    (window-refresh stream)))
+
+;;; --- Define Silica version of this.
+(defmethod window-clear :before ((stream window-output-recording))
+  (clear-output-history stream))
+
+) ; end of #-Silica PROGN
+
+
+;;; Genera compatibility
+
+#+Genera
+(defmethod stream-compatible-output-as-presentation
+	   ((stream output-recording-mixin)
+	    continuation xstream
+	    &key (object nil) (type t) single-box &allow-other-keys)
+  (dw:with-type-decoded (type-name nil pr-args) type
+    (if (or (null type)
+	    (and (eq type-name 'sys:expression)
+		 (not (getf pr-args :escape *print-escape*))
+		 (stringp object)))
+	(funcall continuation xstream)
+        (multiple-value-bind (object clim-type changed-p)
+	    (dw-type-to-clim-type object type)
+	  (if changed-p
+	      (with-output-as-presentation (xstream object clim-type
+					    :single-box single-box)
+		(funcall continuation xstream))
+	      (funcall continuation xstream))))))
+
+#+Genera
+(defmethod stream-compatible-output-as-presentation-1
+	   ((stream output-recording-mixin)
+	    continuation continuation-args
+	    &key (object nil) (type t) single-box &allow-other-keys)
+  (dw:with-type-decoded (type-name nil pr-args) type
+    (if (or (null type)
+	    (and (eq type-name 'sys:expression)
+		 (not (getf pr-args :escape *print-escape*))
+		 (stringp object)))
+	(apply continuation continuation-args)
+        (multiple-value-bind (object clim-type changed-p)
+	    (dw-type-to-clim-type object type)
+	  (if changed-p
+	      (with-output-as-presentation (stream object clim-type
+					    :single-box single-box)
+		(apply continuation continuation-args))
+	      (apply continuation continuation-args))))))
+
+
diff --git a/clim/text-recording.lisp b/clim/text-recording.lisp
new file mode 100644
index 00000000..8b3c6ee2
--- /dev/null
+++ b/clim/text-recording.lisp
@@ -0,0 +1,447 @@
+;;; -*- Mode: Lisp; Syntax: ANSI-Common-Lisp; Package: CLIM-INTERNALS; Base: 10; Lowercase: Yes -*-
+
+;; $fiHeader: text-recording.lisp,v 1.1 92/01/31 16:22:15 cer Exp $
+
+(in-package :clim-internals)
+
+"Copyright (c) 1990, 1991, 1992 Symbolics, Inc.  All rights reserved.
+ Portions copyright (c) 1989, 1990 International Lisp Associates."
+
+;;; Text line output recording.  A stream which does text output creates one of
+;;; these per line of text.  Lines are delimited by either #\RETURNs or by
+;;; wrapping.  Line boundaries are not recalculated when window size is changed; a
+;;; higher-level kind of output record is required for that (protocol not yet
+;;; defined, but should be obvious).
+
+;;; The string is a vector of those characters which were output on the current
+;;; line.  The initial-text-style is the very first style which
+;;; appeared on the line.  The current-text-style is the style of
+;;; the last character which appeared on the line.  The baseline is used to
+;;; determine where to draw the glyphs.
+
+;;; The text-style-changes is an NCONCed list of conses of the form
+;;; (style . position).  The characters between the beginning of the record
+;;; and the first change are in the initial-text-style.  Unfortunately,
+;;; you can't just use STREAM-WRITE-STRING-1 on the substring involved
+;;; because that function returns in the middle when it encounters a character it
+;;; can't deal with, such as tabs and non-graphic characters.  There should never
+;;; be a #\Return character in a STANDARD-TEXT-OUTPUT-RECORD.
+
+(defclass standard-text-output-record
+	  (output-record-element-mixin text-displayed-output-record)
+    ((string :initarg :string)
+     (wrapped-p :initform nil :initarg :wrapped-p)
+     (ink :initarg :ink)))
+
+(defclass styled-text-output-record
+	  (standard-text-output-record text-displayed-output-record)
+    ((initial-text-style :initform nil :initarg :initial-style)
+     (text-style-changes :initform nil)
+     (current-text-style :initform nil :initarg :current-style)
+     (baseline :initform 0 :initarg :baseline)))
+
+(define-constructor make-standard-text-output-record
+		    standard-text-output-record (ink string)
+		    :ink ink :string string)
+
+(define-constructor make-styled-text-output-record
+		    styled-text-output-record (ink string)
+		    :ink ink :string string)
+
+(define-constructor make-styled-text-output-record-1
+		    styled-text-output-record (ink string wrapped-p style baseline)
+  :ink ink :string string :wrapped-p wrapped-p
+  :initial-style style :current-style style :baseline baseline)
+
+(defmethod print-object ((object standard-text-output-record) stream)
+  (print-unreadable-object (object stream :type t :identity t)
+    (format stream "~S /x ~A:~A y ~A:~A/"
+	    (safe-slot-value object 'string)
+	    (safe-slot-value object 'left)
+	    (safe-slot-value object 'right)
+	    (safe-slot-value object 'top)
+	    (safe-slot-value object 'bottom))))
+
+(defmethod output-record-unique-id ((text standard-text-output-record))
+  (slot-value text 'string))
+
+(defmethod replay-output-record ((record standard-text-output-record) stream
+				 &optional region (x-offset 0) (y-offset 0))
+  (declare (type coordinate x-offset y-offset))
+  (declare (ignore region))
+  (let* ((string (slot-value record 'string))
+	 (start 0)
+	 (end (length string))
+	 (text-style (medium-default-text-style stream))
+	 #+Silica (port (sheet-port stream))
+	 (baseline (- (text-style-height text-style #-Silica stream #+Silica port)
+		      (text-style-descent text-style #-Silica stream #+Silica port)))
+	 (glyph-buffer (stream-output-glyph-buffer stream))
+	 (color (slot-value record 'ink)))
+    (declare (fixnum start end))
+    (#-Silica progn
+     #+Silica with-sheet-medium #+Silica (medium stream)
+     (macrolet
+      ((do-it (end-position)
+	 `(loop
+	    (when (>= start ,end-position) (return))
+	    (multiple-value-bind (write-char next-char-index
+				  new-cursor-x new-baseline new-height font)
+		(stream-scan-string-for-writing stream #+Silica medium
+						string start ,end-position text-style
+						cursor-x
+						;;--- MOST-POSITIVE-FIXNUM loses
+						most-positive-fixnum 
+						glyph-buffer)
+	      ;; GLYPH-BUFFER NIL => pass the string to the port-specific code.
+	      #-Silica
+	      (if glyph-buffer
+		  (stream-write-string-1
+		    stream glyph-buffer 0 (the fixnum (- next-char-index start))
+		    font color
+		    cursor-x (+ cursor-y (- baseline new-baseline)))
+		  (stream-write-string-1
+		    stream string start next-char-index
+		    font color
+		    cursor-x (+ cursor-y (- baseline new-baseline))))
+	      #+Silica
+	      (with-identity-transformation (medium)
+		(draw-text* medium string
+			    cursor-x (+ cursor-y (- baseline new-baseline))
+			    :start start :end next-char-index 
+			    :align-y :top
+			    :text-style text-style :ink color))
+	      (setf cursor-x new-cursor-x start next-char-index)
+	      (when write-char
+		(cond ((eql write-char #\Tab)	;Only non-lozenged exception char?
+		       (setf cursor-x (stream-next-tab-column stream cursor-x text-style)))
+		      (t 
+		       (multiple-value-bind (new-cursor-x new-cursor-y)
+			   (stream-draw-lozenged-character
+			     stream write-char cursor-x cursor-y new-baseline new-height
+			     ;;--- MOST-POSITIVE-FIXNUM loses
+			     text-style most-positive-fixnum nil t)
+			 (setf cursor-x new-cursor-x
+			       cursor-y new-cursor-y))))
+		(incf start))))))
+      (multiple-value-bind (cursor-x cursor-y) 
+	  (output-record-start-cursor-position* record)
+	(declare (type coordinate cursor-x cursor-y))
+	(translate-fixnum-positions x-offset y-offset cursor-x cursor-y)
+	(do-it end)
+	#-Silica
+	(when (slot-value record 'wrapped-p)
+	  (draw-character-wrap-indicator
+	    stream cursor-y (bounding-rectangle-height record) (stream-text-margin stream) nil)))))))
+
+(defmethod replay-output-record ((record styled-text-output-record) stream
+				 &optional region (x-offset 0) (y-offset 0))
+  (declare (type coordinate x-offset y-offset))
+  (declare (ignore region))
+  (let* ((string (slot-value record 'string))
+	 (start 0)
+	 (end (length string))
+	 (text-style (slot-value record 'initial-text-style))
+	 (baseline (slot-value record 'baseline))
+	 (glyph-buffer (stream-output-glyph-buffer stream))
+	 (color (slot-value record 'ink)))
+    (declare (fixnum start end))
+    (#-Silica progn
+     #+Silica with-sheet-medium #+Silica (medium stream)
+     (macrolet
+      ((do-it (end-position)
+	 `(loop
+	    (when (>= start ,end-position) (return))
+	    (multiple-value-bind (write-char next-char-index
+				  new-cursor-x new-baseline new-height font)
+		(stream-scan-string-for-writing stream #+Silica medium
+						string start ,end-position text-style
+						cursor-x
+						;;--- LOSES
+						most-positive-fixnum 
+						glyph-buffer)
+	      #-Silica
+	      (if glyph-buffer
+		  (stream-write-string-1
+		    stream glyph-buffer 0 (the fixnum (- next-char-index start))
+		    font color
+		    cursor-x (+ cursor-y (- baseline new-baseline)))
+		  (stream-write-string-1
+		    stream string start next-char-index
+		    font color
+		    cursor-x (+ cursor-y (- baseline new-baseline))))
+	      #+Silica
+	      (with-identity-transformation (medium)
+		(draw-text* medium string
+			    cursor-x (+ cursor-y (- baseline new-baseline))
+			    :start start :end next-char-index 
+			    :align-y :top
+			    :text-style text-style :ink color))
+	      (setf cursor-x new-cursor-x start next-char-index)
+	      (when write-char
+		(cond ((eql write-char #\Tab)	;Only non-lozenged exception char?
+		       (setf cursor-x (stream-next-tab-column stream cursor-x text-style)))
+		      (t 
+		       (multiple-value-bind (new-cursor-x new-cursor-y)
+			   (stream-draw-lozenged-character
+			     stream write-char cursor-x cursor-y new-baseline new-height
+			     ;;--- LOSES
+			     text-style most-positive-fixnum nil t)
+			 (setf cursor-x new-cursor-x
+			       cursor-y new-cursor-y))))
+		(incf start))))))
+      (multiple-value-bind (cursor-x cursor-y) 
+	  (output-record-start-cursor-position* record)
+	(declare (type coordinate cursor-x cursor-y))
+	(translate-fixnum-positions x-offset y-offset cursor-x cursor-y)
+	(dolist (text-style-change (slot-value record 'text-style-changes))
+	  (let ((new-text-style (car text-style-change))
+		(change-position (cdr text-style-change)))
+	    (do-it change-position)
+	    (setf text-style new-text-style
+		  start change-position)))
+	(do-it end)
+	#-Silica
+	(when (slot-value record 'wrapped-p)
+	  (draw-character-wrap-indicator
+	    stream cursor-y (bounding-rectangle-height record) 
+	    (stream-text-margin stream) nil)))))))
+
+(defmethod bounding-rectangle-set-edges :around
+	   ((record standard-text-output-record) new-left new-top new-right new-bottom)
+  (declare (ignore new-left new-top new-right new-bottom))
+  (let ((parent (output-record-parent record)))
+    (if (not (null parent))
+	(with-bounding-rectangle* (old-left old-top old-right old-bottom) record
+	  (multiple-value-bind (xoff yoff)
+	      (convert-from-descendant-to-ancestor-coordinates record parent)
+	    (declare (type coordinate xoff yoff))
+	    (translate-fixnum-positions xoff yoff old-left old-top old-right old-bottom)
+	    (call-next-method)
+	    (recompute-extent-for-changed-child parent record
+						old-left old-top old-right old-bottom)))
+	(call-next-method))))
+
+(defmethod add-string-output-to-text-record ((record standard-text-output-record)
+					     text-string start end text-style
+					     new-width new-height new-baseline)
+  (declare (ignore text-style new-baseline))
+  (declare (fixnum start end))
+  (when (>= start end)
+    (return-from add-string-output-to-text-record))
+  (let* ((count (the fixnum (- end start)))
+	 (string (prepare-text-record-for-appending record count nil))
+	 (fill-pointer (fill-pointer string)))
+    (multiple-value-bind (width height) (bounding-rectangle-size record)
+      (declare (type coordinate width height))
+      (setf (fill-pointer string) (the fixnum (+ fill-pointer count)))
+      (replace string text-string :start1 fill-pointer :start2 start :end2 end)
+      (incf width new-width)
+      (maxf height new-height)
+      (bounding-rectangle-set-size record width height))))
+
+(defmethod add-string-output-to-text-record ((record styled-text-output-record)
+					     text-string start end text-style
+					     new-width new-height new-baseline)
+  (declare (fixnum start end))
+  (when (>= start end)
+    (return-from add-string-output-to-text-record))
+  (let* ((count (the fixnum (- end start)))
+	 (string (prepare-text-record-for-appending record count text-style))
+	 (fill-pointer (fill-pointer string)))
+    (multiple-value-bind (width height) (bounding-rectangle-size record)
+      (declare (type coordinate width height))
+      (setf (fill-pointer string) (the fixnum (+ fill-pointer count)))
+      (replace string text-string :start1 fill-pointer :start2 start :end2 end)
+      (incf width new-width)
+      (maxf height new-height)
+      (maxf (slot-value record 'baseline) new-baseline)
+      (bounding-rectangle-set-size record width height))))
+
+(defmethod add-character-output-to-text-record ((record standard-text-output-record)
+						character text-style
+						new-width new-height new-baseline)
+  (declare (ignore text-style new-baseline))
+  (let* ((string (prepare-text-record-for-appending record 1 nil))
+	 (fill-pointer (fill-pointer string)))
+    (multiple-value-bind (width height) (bounding-rectangle-size record)
+      (declare (type coordinate width height))
+      (setf (fill-pointer string) (1+ fill-pointer)
+	    (aref string fill-pointer) character)
+      (incf width new-width)
+      (maxf height new-height)
+      (bounding-rectangle-set-size record width height))))
+
+(defmethod add-character-output-to-text-record ((record styled-text-output-record)
+						character text-style
+						new-width new-height new-baseline)
+  (let* ((string (prepare-text-record-for-appending record 1 text-style))
+	 (fill-pointer (fill-pointer string)))
+    (multiple-value-bind (width height) (bounding-rectangle-size record)
+      (declare (type coordinate width height))
+      (setf (fill-pointer string) (1+ fill-pointer)
+	    (aref string fill-pointer) character)
+      (incf width new-width)
+      (maxf height new-height)
+      (maxf (slot-value record 'baseline) new-baseline)
+      (bounding-rectangle-set-size record width height))))
+
+(defmethod prepare-text-record-for-appending
+    ((record standard-text-output-record) space-needed style)
+  (declare (fixnum space-needed))
+  (declare (ignore style))
+  (let* ((string (slot-value record 'string))
+	 (fill-pointer (fill-pointer string)))
+    (declare (fixnum fill-pointer))
+    (when (> (the fixnum (+ fill-pointer space-needed)) (array-dimension string 0))
+      (setf string (adjust-array string (the fixnum (+ fill-pointer space-needed 16))))
+      (setf (slot-value record 'string) string))
+    string))
+
+(defmethod prepare-text-record-for-appending
+    ((record styled-text-output-record) space-needed style)
+  (declare (fixnum space-needed))
+  (with-slots (initial-text-style current-text-style
+	       text-style-changes baseline) record
+    (let* ((string (slot-value record 'string))
+	   (fill-pointer (fill-pointer string)))
+      (unless (eql style current-text-style)
+	(if (null initial-text-style)
+	    (setf initial-text-style style)
+	    (let ((change-record (cons style fill-pointer)))
+	      (setf text-style-changes 
+		    (nconc text-style-changes (list change-record)))))
+	(setf current-text-style style))
+      (when (> (the fixnum (+ fill-pointer space-needed)) (array-dimension string 0))
+	(setf string (adjust-array string (the fixnum (+ fill-pointer space-needed 16))))
+	(setf (slot-value record 'string) string))
+      string)))
+
+(defun text-recompute-contents-id-test (id1 id2)
+  (or (eql id1 id2)
+      (and (stringp id2)
+	   (string= id1 id2))))
+
+;; We don't do a INVOKE-WITH-NEW-OUTPUT-RECORD for STANDARD-TEXT-OUTPUT-RECORDs.
+;; However, STREAM-CLOSE-TEXT-OUTPUT-RECORD does a RECOMPUTE-CONTENTS-OK, too.
+(defmethod recompute-contents-ok ((text standard-text-output-record))
+  (with-slots (string wrapped-p) text
+    (let* ((output-record (output-record-parent text))
+	   (match (and output-record
+		       (find-inferior-output-record
+			 output-record t 'standard-text-output-record
+			 :unique-id string :id-test #'text-recompute-contents-id-test))))
+      (when match
+	;; The old extent is a copy of MATCH's bounding rectangle
+	(setf (output-record-old-bounding-rectangle text) (bounding-rectangle match))
+	(when (and (bounding-rectangle-size-equal match text)
+		   (eql wrapped-p (slot-value match 'wrapped-p))
+		   (eql (class-of text) (class-of match)))
+	  (setf (output-record-contents-ok text) t)
+	  ;; make sure that old bounding-rect is the same relative position from
+	  ;; old-start-position as the bounding-rect is from start-position
+	  (multiple-value-bind (delta-x delta-y)
+	      (multiple-value-bind (ex ey) (bounding-rectangle-position* text)
+		(declare (type coordinate ex ey))
+		(multiple-value-bind (sx sy) 
+		    (output-record-start-cursor-position* text)
+		  (declare (type coordinate sx sy))
+		  (position-difference* ex ey sx sy)))
+	    (declare (type coordinate delta-x delta-y))
+	    (multiple-value-bind (old-start-x old-start-y)
+		(multiple-value-bind (px py) (bounding-rectangle-position* match)
+		  (declare (type coordinate px py))
+		  (position-difference* px py delta-x delta-y))
+	      (output-record-set-old-start-cursor-position*
+		text old-start-x old-start-y))))))))
+
+(defmethod recompute-contents-ok ((text styled-text-output-record))
+  (with-slots (string wrapped-p initial-text-style current-text-style text-style-changes)
+	      text
+    (let* ((output-record (output-record-parent text))
+	   (match (and output-record
+		       (find-inferior-output-record
+			 output-record t 'styled-text-output-record
+			 :unique-id string :id-test #'text-recompute-contents-id-test))))
+      (when match
+	;; The old extent is a copy of MATCH's bounding rectangle
+	(setf (output-record-old-bounding-rectangle text) (bounding-rectangle match))
+	;; --- maybe make a method out of this to get efficient slot access?
+	(when (and (bounding-rectangle-size-equal match text)
+		   (eql wrapped-p (slot-value match 'wrapped-p))
+		   (eql (class-of text) (class-of match))
+		   (eql initial-text-style
+			(slot-value match 'initial-text-style))
+		   (eql current-text-style
+			(slot-value match 'current-text-style))
+		   (equal text-style-changes
+			  (slot-value match 'text-style-changes)))
+	  (setf (output-record-contents-ok text) t)
+	  ;; make sure that old bounding-rect is the same relative position from
+	  ;; old-start-position as the bounding-rect is from start-position
+	  (multiple-value-bind (delta-x delta-y)
+	      (multiple-value-bind (ex ey) (bounding-rectangle-position* text)
+		(declare (type coordinate ex ey))
+		(multiple-value-bind (sx sy) 
+		    (output-record-start-cursor-position* text)
+		  (declare (type coordinate sx sy))
+		  (position-difference* ex ey sx sy)))
+	    (declare (type coordinate delta-x delta-y))
+	    (multiple-value-bind (old-start-x old-start-y)
+		(multiple-value-bind (px py) (bounding-rectangle-position* match)
+		  (declare (type coordinate px py))
+		  (position-difference* px py delta-x delta-y))
+	      (output-record-set-old-start-cursor-position*
+		text old-start-x old-start-y))))))))
+
+(defun find-text-baseline (record stream)
+  ;; This finds the lowest baseline of the text in RECORD, which will be slower than, say,
+  ;; the first baseline but more likely to look good with misaligned things.
+  (let ((baseline 0)
+	(style (medium-default-text-style stream))
+	#+Silica (port (sheet-port stream)))
+    (declare (type coordinate baseline))
+    (labels ((find-or-recurse (record y-offset)
+	       (declare (type coordinate y-offset))
+	       (typecase record
+		 (styled-text-output-record
+		   (maxf baseline (+ y-offset (slot-value record 'baseline))))
+		 (standard-text-output-record
+		   (maxf baseline
+			 (+ y-offset 
+			    (- (text-style-height style #-Silica stream #+Silica port)
+			       (text-style-descent style #-Silica stream #+Silica port)))))
+		 (t
+		   (multiple-value-bind (xoff yoff) (output-record-position* record)
+		     (declare (type coordinate yoff))
+		     (declare (ignore xoff))
+		     (map-over-output-records #'find-or-recurse record
+					      0 0 (+ yoff y-offset)))))))
+      (declare (dynamic-extent #'find-or-recurse))
+      (find-or-recurse record 0))
+    baseline)) 
+
+;; The cost of stylizing an existing record is actually fairly low, and we
+;; don't do it very often, because of the optimization in GET-TEXT-OUTPUT-RECORD
+;; that creates a stylized record as early as possible.
+(defmethod stylize-text-output-record ((record standard-text-output-record) style stream)
+  (with-slots (ink string wrapped-p left top right bottom
+	       start-x start-y end-x end-y) record
+    (let* (#+Silica (port (sheet-port stream))
+	   (new-record (make-styled-text-output-record-1
+			 ink string wrapped-p
+			 style (- (text-style-height style #-Silica stream #+Silica port)
+				  (text-style-descent style #-Silica stream #+Silica port)))))
+      (with-slots ((new-left left) (new-top top) (new-right right) (new-bottom bottom)
+		   (new-sx start-x) (new-sy start-y) (new-ex end-x) (new-ey end-y)
+		   (new-wrapped-p wrapped-p)) new-record
+	(setq new-left left
+	      new-top top
+	      new-right right
+	      new-bottom bottom
+	      new-sx start-x
+	      new-sy start-y
+	      new-ex end-x
+	      new-ey end-y))
+      (setf (stream-text-output-record stream) new-record)
+      new-record)))
diff --git a/silica/db-border.lisp b/silica/db-border.lisp
new file mode 100644
index 00000000..9fd82742
--- /dev/null
+++ b/silica/db-border.lisp
@@ -0,0 +1,58 @@
+;;; -*- Mode: Lisp; Syntax: ANSI-Common-Lisp; Package: SILICA; Base: 10; Lowercase: Yes -*-
+
+"Copyright (c) 1989, 1990 by Xerox Corporation.  All rights reserved.
+ Portions copyright (c) 1991, 1992 by Symbolics, Inc.  All rights reserved."
+
+(in-package :silica)
+
+
+;;; Border Panes
+(defclass border-pane (layout-pane)
+    ((thickness :initform 1 :initarg :thickness)))
+
+(defmethod initialize-instance :after ((pane border-pane) &key contents)
+  (sheet-adopt-child pane contents))
+
+(defmethod compose-space ((pane border-pane) &key width height)
+  (with-slots (thickness) pane
+    (let ((child (sheet-child pane)))
+      (space-requirement+
+	(compose-space child :width width :height height)
+	(make-space-requirement 
+	  :width (* 2 thickness)
+	  :height (* 2 thickness))))))
+
+(defmethod allocate-space ((pane border-pane) width height)
+  (with-slots (thickness) pane
+    (move-and-resize-sheet* (sheet-child pane)
+			    thickness thickness
+			    (- width (* 2 thickness))
+			    (- height (* 2 thickness)))))
+  
+
+(defclass outlined-pane (border-pane)
+  ((background :initform +black+ :accessor pane-background)))
+
+(defmethod repaint-sheet ((pane border-pane) region)
+  (with-sheet-medium (medium pane)
+    (with-bounding-rectangle* (left top right bottom) (sheet-region pane)
+      (let ((thickness (slot-value pane 'thickness)))
+	(decf right (ceiling thickness 2))
+	(decf bottom (ceiling thickness 2))
+	(draw-rectangle* medium left top right bottom
+			 :line-thickness thickness :filled nil
+			 :ink (pane-background pane))))))
+
+(defmacro outlining (options &body contents)
+  `(realize-pane 'outlined-pane
+		 :contents ,@contents
+		 ,@options))
+
+
+(defclass spacing-pane (border-pane) ()
+  (:default-initargs :thickness 2))
+
+(defmacro spacing (options &body contents)
+  `(realize-pane 'spacing-pane
+		 :contents ,@contents
+		 ,@options))
diff --git a/utils/extended-regions.lisp b/utils/extended-regions.lisp
new file mode 100644
index 00000000..a3930749
--- /dev/null
+++ b/utils/extended-regions.lisp
@@ -0,0 +1,375 @@
+;;; -*- Mode: Lisp; Syntax: ANSI-Common-Lisp; Package: CLIM-UTILS; Base: 10; Lowercase: Yes -*-
+
+;; $fiHeader: extended-regions.lisp $
+
+(in-package :clim-utils)
+
+"Copyright (c) 1990, 1991, 1992 Symbolics, Inc.  All rights reserved."
+
+;;; Extended regions
+
+;;; Lines
+
+(defclass standard-line (line)
+    ((start-x :initarg :start-x :type real)
+     (start-y :initarg :start-y :type real)
+     (end-x :initarg :end-x :type real)
+     (end-y :initarg :end-y :type real)
+     (points :type simple-vector :initarg :points :reader polygon-points)))
+
+(define-constructor make-line-1 standard-line (start-x start-y end-x end-y points)
+		    :start-x start-x :start-y start-y :end-x end-x :end-y end-y :points points)
+
+(defun make-line (start-point end-point)
+  (make-line-1 (point-x start-point) (point-y start-point)
+	       (point-x end-point) (point-y end-point)
+	       (vector start-point end-point)))
+
+(define-constructor make-line*-1 standard-line (start-x start-y end-x end-y)
+		    :start-x start-x :start-y start-y :end-x end-x :end-y end-y)
+
+(defun make-line* (start-x start-y end-x end-y)
+  (make-line*-1 start-x start-y end-x end-y))
+
+(defmethod make-load-form ((line standard-line))
+  `(make-line ',(line-start-point line) ',(line-end-point line)))
+
+(defmethod line-start-point* ((line standard-line))
+  (with-slots (start-x start-y) line
+    (values start-x start-y)))
+
+(defmethod line-end-point* ((line standard-line))
+  (with-slots (end-x end-y) line
+    (values end-x end-y)))
+
+(defmethod slot-unbound (class (line standard-line) (slot (eql 'points)))
+  (declare (ignore class))
+  (with-slots (points start-x start-y end-x end-y) line
+    (setf points (vector (make-point start-x start-y) (make-point end-x end-y)))))
+
+(defmethod line-start-point ((line standard-line))
+  (with-slots (points) line
+    (svref points 0)))
+
+(defmethod line-end-point ((line standard-line))
+  (with-slots (points) line
+    (svref points 1)))
+
+(defmethod polyline-closed ((line standard-line))
+  nil)
+
+(defmethod map-over-polygon-coordinates (function (line standard-line))
+  (with-slots (start-x start-y end-x end-y) line
+    (funcall function start-x start-y)
+    (funcall function end-x end-y)
+    nil))
+
+(defmethod map-over-polygon-segments (function (line standard-line))
+  (with-slots (start-x start-y end-x end-y) line
+    (funcall function start-x start-y end-x end-y)
+    nil))
+
+(defmethod region-equal ((line1 standard-line) (line2 standard-line))
+  (with-slots ((sx1 start-x) (sy1 start-y) (ex1 end-x) (ey1 end-y)) line1
+    (with-slots ((sx2 start-x) (sy2 start-y) (ex2 end-x) (ey2 end-y)) line2
+      (or (and (= sx1 sx2) (= sy1 sy2) (= ex1 ex2) (= ey1 ey2))
+	  (and (= sx1 ex2) (= sy1 ey2) (= ex1 sx2) (= ey1 sy2))))))
+
+;; By using perpendicular-distance from line instead of slope and intercept
+;; we don't have to worry about divide by zero in slope and we're also more
+;; robust against roundoff error.
+(defmethod region-contains-point*-p ((line standard-line) x y)
+  (with-slots (start-x start-y end-x end-y) line
+    (let ((x1 start-x) (y1 start-y) (x2 end-x) (y2 end-y))
+      (when (or (<= x1 x x2)
+		(>= x1 x x2))
+	(= (+ (* (- y2 y1) x)
+	      (* (- x1 x2) y))
+	   (- (* x1 y2) (* x2 y1)))))))
+
+(defmethod region-contains-region-p ((line1 standard-line) (line2 standard-line))
+  (with-slots (start-x start-y end-x end-y) line2
+    (and (region-contains-point*-p line1 start-x start-y)
+	 (region-contains-point*-p line1 end-x end-y))))
+
+(defmethod region-intersects-region-p ((line1 standard-line) (line2 standard-line))
+  (with-slots ((sx1 start-x) (sy1 start-y) (ex1 end-x) (ey1 end-y)) line1
+    (with-slots ((sx2 start-x) (sy2 start-y) (ex2 end-x) (ey2 end-y)) line2
+      (let ((sx1 sx1) (sy1 sy1) (ex1 ex1) (ey1 ey1)
+	    (sx2 sx2) (sy2 sy2) (ex2 ex2) (ey2 ey2))
+	(and (>= (max sx2 ex2) (min sx1 ex1))
+	     (>= (max sx1 ex1) (min sx2 ex2))
+	     (let ((dx1 (- ex1 sx1)) (dy1 (- ey1 sy1))
+		   (dx2 (- ex2 sx2)) (dy2 (- ey2 sy2)))
+	       (and (= (* dx1 dy2) (* dx2 dy1)) ;slopes equal
+		    (= (* dx1 (- sy1 sy2)) (* dy1 (- sx1 sx2))))))))))
+
+(defmethod region-intersection ((line1 standard-line) (line2 standard-line))
+  (if (region-intersects-region-p line1 line2)
+      (with-slots ((sx1 start-x) (sy1 start-y) (ex1 end-x) (ey1 end-y)) line1
+	(with-slots ((sx2 start-x) (sy2 start-y) (ex2 end-x) (ey2 end-y)) line2
+	  (make-line* (max sx1 sx2) (max sy1 sy2) (min ex1 ex2) (min ey1 ey2))))
+      +nowhere+))
+
+(defmethod transform-region (transformation (line standard-line))
+  (with-slots (start-x start-y end-x end-y) line
+    (multiple-value-bind (sx sy)
+	(transform-point* transformation start-x start-y)
+      (multiple-value-bind (ex ey)
+	  (transform-point* transformation end-x end-y)
+	(make-line* sx sy ex ey)))))
+
+(defmethod bounding-rectangle* ((line standard-line))
+  (with-slots (start-x start-y end-x end-y) line
+    (fix-rectangle (min start-x end-x) (min start-y end-y)
+		   (max start-x end-x) (max start-y end-y))))
+
+
+;;; Polygons and polylines
+
+(defclass polygon-mixin ()
+    ((coords :type vector :initarg :coords)
+     (points :type vector :initarg :points :reader polygon-points)))
+
+(defmethod map-over-polygon-coordinates (function (polygon polygon-mixin))
+  (with-slots (coords points) polygon
+    (if (slot-boundp polygon 'coords)
+	(let ((ncoords (1- (length coords)))
+	      (i -1))
+	  (loop
+	    (funcall function (aref coords (incf i)) (aref coords (incf i)))
+	    (when (= i ncoords) (return)))
+	  nil)
+	(flet ((map-coordinates (point)
+		 (funcall function (point-x point) (point-y point))))
+	  (declare (dynamic-extent #'map-coordinates))
+	  (map nil #'map-coordinates points))))
+  nil)
+
+(defmethod map-over-polygon-segments (function (polygon polygon-mixin))
+  (with-slots (coords points) polygon
+    (if (slot-boundp polygon 'coords)
+	(let* ((ncoords (1- (length coords)))
+	       (x1 (aref coords 0))
+	       (y1 (aref coords 1))
+	       (x x1)
+	       (y y1)
+	       (i 1))
+	  (loop
+	    (funcall function x y
+		     (setf x (aref coords (incf i))) (setf x (aref coords (incf i))))
+	    (when (= i ncoords) (return)))
+	  (when (polyline-closed polygon)
+	    (funcall function x y x1 y1)))
+	(multiple-value-bind (x1 y1)
+	    (point-position* (aref points 0))
+	  (let ((x x1) (y y1))
+	    (dotimes (i (1- (length points)))
+	      (multiple-value-bind (nx ny)
+		  (point-position* (aref points (1+ i)))
+		(funcall function x y nx ny)
+		(psetf x nx y ny)))
+	    (when (polyline-closed polygon)
+	      (funcall function x y x1 y1)))))
+    nil))
+
+(defmethod bounding-rectangle* ((polygon polygon-mixin))
+  (let ((min-x nil) (min-y nil) (max-x nil) (max-y nil))
+    (flet ((add-coord (x y)
+	     (minf-or min-x x)
+	     (minf-or min-y y)
+	     (maxf-or max-x x)
+	     (maxf-or max-y y)))
+      (declare (dynamic-extent #'add-coord))
+      (map-over-polygon-coordinates #'add-coord polygon))
+    (fix-rectangle min-x min-y max-x max-y)))
+
+
+(defclass standard-polyline (polygon-mixin polyline)
+    ((closed :initarg :closed :reader polyline-closed)))
+
+(define-constructor make-polyline standard-polyline (point-seq &key closed)
+		    :points (coerce point-seq 'vector) :closed closed)
+
+(define-constructor make-polyline* standard-polyline (coord-seq &key closed)
+		    :coords (coerce coord-seq 'vector) :closed closed)
+
+(defmethod make-load-form ((polyline standard-polyline))
+  (with-slots (closed) polyline
+    `(make-polyline ',(polygon-points polyline) :closed ,closed)))
+
+(defmethod transform-region (transformation (polyline standard-polyline))
+  (let ((coords nil))
+    (flet ((transform-coord (x y)
+	     (multiple-value-bind (nx ny)
+		 (transform-point* transformation x y)
+	       (push ny coords)
+	       (push nx coords))))
+      (declare (dynamic-extent #'transform-coord))
+      (map-over-polygon-coordinates #'transform-coord polyline))
+    (make-polyline* (nreverse coords) :closed (slot-value polyline 'closed))))
+
+
+(defclass standard-polygon (polygon-mixin polygon) ())
+
+(define-constructor make-polygon standard-polygon (point-seq)
+		    :points (coerce point-seq 'vector))
+
+(define-constructor make-polygon* standard-polygon (coord-seq)
+		    :coords (coerce coord-seq 'vector))
+
+(defmethod make-load-form ((polygon standard-polygon))
+  `(make-polygon ',(polygon-points polygon)))
+
+(defmethod polyline-closed ((polygon standard-polygon))
+  t)
+
+(defmethod transform-region (transformation (polygon standard-polygon))
+  (let ((coords nil))
+    (flet ((transform-coord (x y)
+	     (multiple-value-bind (nx ny)
+		 (transform-point* transformation x y)
+	       (push ny coords)
+	       (push nx coords))))
+      (declare (dynamic-extent #'transform-coord))
+      (map-over-polygon-coordinates #'transform-coord polygon))
+    (make-polygon* (nreverse coords))))
+
+
+;;; Ellipses and elliptical arcs
+
+(defclass ellipse-mixin ()
+    ((center-point :type point :initarg :center-point :reader ellipse-center-point)
+     (center-x :initarg :center-x :type real)
+     (center-y :initarg :center-y :type real)
+     (radius-1-dx :initarg :radius-1-dx :type real)
+     (radius-1-dy :initarg :radius-1-dy :type real)
+     (radius-2-dx :initarg :radius-2-dx :type real)
+     (radius-2-dy :initarg :radius-2-dy :type real)
+     (start-angle :initarg :start-angle :reader ellipse-start-angle :type single-float)
+     (end-angle :initarg :end-angle :reader ellipse-end-angle :type single-float)))
+
+(defmethod slot-unbound (class (ellipse ellipse-mixin) (slot (eql 'ellipse-center-point)))
+  (declare (ignore class))
+  (with-slots (center-point center-x center-y) ellipse
+    (setf center-point (make-point center-x center-y))))
+
+(defmethod ellipse-center-point* ((ellipse ellipse-mixin))
+  (with-slots (center-x center-y) ellipse
+    (values center-x center-y)))
+
+(defmethod ellipse-radii ((ellipse ellipse-mixin))
+  (with-slots (radius-1-dx radius-1-dy radius-2-dx radius-2-dy) ellipse
+    (values radius-1-dx radius-1-dy radius-2-dx radius-2-dy)))
+
+
+(defclass standard-elliptical-arc (ellipse-mixin elliptical-arc) ())
+
+(define-constructor make-elliptical-arc standard-elliptical-arc
+  (center-point radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+		&key start-angle end-angle)
+  :center-point center-point :center-x (point-x center-point) :center-y (point-y center-point)
+  :radius-1-dx radius-1-dx :radius-1-dy radius-1-dy
+  :radius-2-dx radius-2-dx :radius-2-dy radius-2-dy
+  :start-angle (cond (start-angle (float start-angle 0f0))
+		     (end-angle 0f0)
+		     (t nil))
+  :end-angle (cond (end-angle (float end-angle 0f0))
+		   (start-angle (float (* 2 pi) 0f0))
+		   (t nil)))
+
+(define-constructor make-elliptical-arc* standard-elliptical-arc
+  (center-x center-y radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+	    &key start-angle end-angle)
+  :center-x center-x :center-y center-y
+  :radius-1-dx radius-1-dx :radius-1-dy radius-1-dy
+  :radius-2-dx radius-2-dx :radius-2-dy radius-2-dy
+  :start-angle (cond (start-angle (float start-angle 0f0))
+		     (end-angle 0f0)
+		     (t nil))
+  :end-angle (cond (end-angle (float end-angle 0f0))
+		   (start-angle (float (* 2 pi) 0f0))
+		   (t nil)))
+
+(defmethod make-load-form ((ellipse standard-elliptical-arc))
+  (with-slots (center-point radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+	       start-angle end-angle) ellipse
+    `(make-elliptical-arc ',center-point
+			  ,radius-1-dx ,radius-1-dy ,radius-2-dx ,radius-2-dy
+			  ,@(when start-angle `(:start-angle ,start-angle))
+			  ,@(when end-angle `(:end-angle ,end-angle)))))
+
+(defmethod transform-region (transformation (ellipse standard-elliptical-arc))
+  (with-slots (center-x center-y radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+	       start-angle end-angle) ellipse
+    (multiple-value-bind (cx cy)
+	(transform-point* transformation center-x center-y)
+      (multiple-value-bind (r1-dx r1-dy)
+	  (transform-distance transformation radius-1-dx radius-1-dy)
+	(multiple-value-bind (r2-dx r2-dy)
+	    (transform-distance transformation radius-2-dx radius-2-dy)
+	  (make-elliptical-arc* cx cy r1-dx r1-dy r2-dx r2-dy
+				;;--- How to transform start and end angles?
+				:start-angle start-angle :end-angle end-angle))))))
+
+(defmethod bounding-rectangle* ((ellipse standard-elliptical-arc))
+  (with-slots (center-x center-y radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+	       start-angle end-angle) ellipse
+    (elliptical-arc-box center-x center-y radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+			start-angle end-angle 0)))
+
+
+(defclass standard-ellipse (ellipse-mixin ellipse) ())
+
+(define-constructor make-ellipse standard-ellipse
+  (center-point radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+		&key start-angle end-angle)
+  :center-point center-point :center-x (point-x center-point) :center-y (point-y center-point)
+  :radius-1-dx radius-1-dx :radius-1-dy radius-1-dy
+  :radius-2-dx radius-2-dx :radius-2-dy radius-2-dy
+  :start-angle (cond (start-angle (float start-angle 0f0))
+		     (end-angle 0f0)
+		     (t nil))
+  :end-angle (cond (end-angle (float end-angle 0f0))
+		   (start-angle (float (* 2 pi) 0f0))
+		   (t nil)))
+
+(define-constructor make-ellipse* standard-ellipse
+  (center-x center-y radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+	    &key start-angle end-angle)
+  :center-x center-x :center-y center-y
+  :radius-1-dx radius-1-dx :radius-1-dy radius-1-dy
+  :radius-2-dx radius-2-dx :radius-2-dy radius-2-dy
+  :start-angle (cond (start-angle (float start-angle 0f0))
+		     (end-angle 0f0)
+		     (t nil))
+  :end-angle (cond (end-angle (float end-angle 0f0))
+		   (start-angle (float (* 2 pi) 0f0))
+		   (t nil)))
+
+(defmethod make-load-form ((ellipse standard-ellipse))
+  (with-slots (center-point radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+			    start-angle end-angle) ellipse
+    `(make-ellipse ',center-point
+		   ,radius-1-dx ,radius-1-dy ,radius-2-dx ,radius-2-dy
+		   ,@(when start-angle `(:start-angle ,start-angle))
+		   ,@(when end-angle `(:end-angle ,end-angle)))))
+
+(defmethod transform-region (transformation (ellipse standard-ellipse))
+  (with-slots (center-x center-y radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+	       start-angle end-angle) ellipse
+    (multiple-value-bind (cx cy)
+	(transform-point* transformation center-x center-y)
+      (multiple-value-bind (r1-dx r1-dy)
+	  (transform-distance transformation radius-1-dx radius-1-dy)
+	(multiple-value-bind (r2-dx r2-dy)
+	    (transform-distance transformation radius-2-dx radius-2-dy)
+	  (make-ellipse* cx cy r1-dx r1-dy r2-dx r2-dy
+			 ;;--- How to transform start and end angles?
+			 :start-angle start-angle :end-angle end-angle))))))
+
+(defmethod bounding-rectangle* ((ellipse standard-ellipse))
+  (with-slots (center-x center-y radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+	       start-angle end-angle) ellipse
+    (elliptical-arc-box center-x center-y radius-1-dx radius-1-dy radius-2-dx radius-2-dy
+			start-angle end-angle nil)))
diff --git a/utils/lucid-before.lisp b/utils/lucid-before.lisp
new file mode 100644
index 00000000..11466fa9
--- /dev/null
+++ b/utils/lucid-before.lisp
@@ -0,0 +1,54 @@
+;;; -*- Mode: LISP; Syntax: Common-Lisp; Package: LUCID; Base: 10 -*-
+;;;
+;;;; Lucid-before-patches, Module CLIM
+;;;
+;;; ***************************************************************************
+;;;
+;;;        Copyright (C) 1991 by Lucid, Inc.  All Rights Reserved
+;;;
+;;; ***************************************************************************
+;;;
+;;; Lucid specific hacks which need to be used by CLIM.
+;;;
+;;;
+;;; Edit-History:
+;;;
+;;; Created: PW  2-Nov-91
+;;;
+;;;
+;;; End-of-Edit-History
+
+
+(in-package :lucid)
+
+;;; kludge to check for the presence of NEWCHED
+#+ignore
+(when (boundp '*minimum-os-time-quantum*)
+  (defun %sleep (time)
+    (when (> time 0)
+      (let ((ms-time (round time (/ internal-time-units-per-second 1000))))
+	(if (< ms-time *minimum-os-time-quantum*) ; in msec's
+	    (process-allow-schedule)
+	    (process-wait "Sleep"
+	      #'(lambda (wakeup-time)
+		  (time> (get-ms-time) wakeup-time))
+	      (time-increment (get-ms-time) ms-time)))))))
+
+
+;;; load-time-value isn't until 4.1.  We have can't define this in :LCL because
+;;; CLOS gets it from :LUCID.
+
+(defmacro load-time-value (form &optional read-only-p)
+  (interpretive-load-time-value-expander form read-only-p))
+
+(defun interpretive-load-time-value-expander (form read-only-p)
+  (unless (or (eq read-only-p nil)
+	      (eq read-only-p t))
+    (check-type read-only-p (member nil t)))
+  (let ((cached-value-var (gentemp "LoadTimeValueCache" *clos-package*)))
+    (proclaim `(special ,cached-value-var))
+    `(if (boundp ',cached-value-var)
+	 ,cached-value-var
+	 (setq ,cached-value-var ,form))))
+
+(export '(load-time-value) :lucid)
diff --git a/utils/lucid-stream-functions.lisp b/utils/lucid-stream-functions.lisp
new file mode 100644
index 00000000..aa0b3bb0
--- /dev/null
+++ b/utils/lucid-stream-functions.lisp
@@ -0,0 +1,385 @@
+;;; -*- Mode: Lisp; Syntax: ANSI-Common-Lisp; Package: CLIM-UTILS; Base: 10; Lowercase: Yes -*-
+
+(in-package :clim-utils)
+
+"Copyright (c) 1990, 1991 Symbolics, Inc.  All rights reserved.
+ Portions copyright (c) 1989, 1990 International Lisp Associates."
+
+;;; All of this is taken from the STREAM-DEFINITION-BY-USER proposal to
+;;; the X3J13 committee, made by David Gray of TI on 22 March 1989.  No
+;;; Lisp implementation yet supports this proposal, so we implement it
+;;; here in this separate package.  This way we will be ready when some
+;;; Lisp implementation adopts it (or something like it).
+
+
+;;; just for development
+#+ignore
+(eval-when (compile load eval)
+  (defparameter sym-list '("PEEK-CHAR" "READ-BYTE" "READ-CHAR" "UNREAD-CHAR"
+			   "READ-CHAR-NO-HANG" "LISTEN" "READ-LINE" 
+			   "CLEAR-INPUT" "WRITE-BYTE" "WRITE-CHAR"
+			   "WRITE-STRING" "TERPRI" "FRESH-LINE" "FORCE-OUTPUT"
+			   "FINISH-OUTPUT" "CLEAR-OUTPUT" ))
+  (dolist (sym sym-list)
+    (unintern (find-symbol sym :clim-lisp) :clim-lisp)
+    (unintern (find-symbol sym :clim) :clim)))
+
+;;; Output functions
+
+(defmacro write-forwarding-lucid-output-stream-function (name args)
+  (let* ((cl-name (find-symbol (symbol-name name) (find-package 'lisp)))
+	 (method-name (intern (lisp:format nil "~A-~A" 'stream (symbol-name name))))
+	 (optional-args (or (member '&optional args) (member '&key args)))
+	 (required-args (ldiff args optional-args))
+	 (optional-parameters (mapcan #'(lambda (arg)
+					  (cond ((member arg lambda-list-keywords) nil)
+						((atom arg) (list arg))
+						(t (list (car arg)))))
+				      optional-args))
+	 (pass-args (append required-args optional-parameters))
+	 ;; optional-args are &optional in the method,
+	 ;; even if &key in the Common Lisp function
+	 (method-args (if (eq (first optional-args) '&key)
+			  (append required-args '(&optional) (cdr optional-args))
+			  args))
+	 (pass-keys (if (eq (first optional-args) '&key)
+			(mapcan #'(lambda (arg)
+				    (unless (atom arg)
+				      (setq arg (car arg)))
+				    (list (intern (string arg) :keyword) arg))
+				(cdr optional-args))
+			optional-parameters))
+	 )
+    (when (eq (first optional-args) '&optional)
+      (pop optional-args))
+    `(let ((orig-lucid-closure (or (getf (symbol-plist ',name) :original-lucid-closure)
+				(setf (getf (symbol-plist ',name) :original-lucid-closure)
+				      (symbol-function ',name)))))
+       
+       ;;(proclaim '(inline ,name))
+       (defun ,name (,@required-args &optional stream ,@optional-args)
+	 (cond ((null stream) (setq stream *standard-output*))
+	       ((eql stream t) (setq stream *terminal-io*)))
+	 (if (and (system:standard-object-p stream)
+		  (typep stream 'fundamental-stream))
+	     (,method-name stream ,@pass-args)
+	     (funcall orig-lucid-closure ,@required-args stream ,@pass-keys)))
+
+       ;; Define a default method for the generic function that calls back to the
+       ;; system stream implementation.  Call back via a message if there is one,
+       ;; otherwise via the Common Lisp function.
+       ;; Uses T as a parameter specializer name as a standin for cl:stream,
+       ;; which Genera doesn't support as a builtin class
+       (defmethod ,method-name ((stream t) ,@method-args)
+	 (,cl-name ,@required-args stream ,@pass-keys))
+       ;;(import ',name :clim-lisp)
+       ;;(export ',name :clim-lisp)
+       )))
+
+(write-forwarding-lucid-output-stream-function lisp:write-byte (integer))
+
+(write-forwarding-lucid-output-stream-function lisp:write-char (character))
+
+(write-forwarding-lucid-output-stream-function lisp:write-string (string &key (start 0) end))
+
+(write-forwarding-lucid-output-stream-function lisp:terpri ())
+
+(write-forwarding-lucid-output-stream-function lisp:fresh-line ())
+
+(write-forwarding-lucid-output-stream-function lisp:force-output ())
+
+(write-forwarding-lucid-output-stream-function lisp:finish-output ())
+
+(write-forwarding-lucid-output-stream-function lisp:clear-output ())
+
+
+;;; Input functions
+
+(defmacro write-forwarding-lucid-input-stream-function (name lambda-list
+							     &key eof 
+							     additional-arguments)
+  (let* ((cl-name (find-symbol (symbol-name name) (find-package 'lisp)))
+	 (method-name (intern (lisp:format nil "~A-~A" 'stream (symbol-name name))))
+	 (method-lambda-list (set-difference lambda-list '(stream peek-type)))
+	 (args (mapcar #'(lambda (var) (if (atom var) var (first var)))
+		       (remove-if #'(lambda (x) (member x lambda-list-keywords))
+				  lambda-list)))
+	 (method-calling-args (set-difference args '(stream peek-type)))
+	 (cleanup `(cond ((null stream) (setq stream *standard-input*))
+			 ((eql stream t) (setq stream *terminal-io*))))
+	 (call-method `(,method-name stream ,@method-calling-args))
+	 (calling-lambda-list (remove '&optional lambda-list)))
+    (when (member (first (last method-lambda-list)) lambda-list-keywords)
+      (setf method-lambda-list (butlast method-lambda-list)))
+    `(let ((orig-lucid-closure 
+	     (or (getf (symbol-plist ',name) :original-lucid-closure)
+		 (setf (getf (symbol-plist ',name) :original-lucid-closure)
+		       (symbol-function ',name)))))
+
+	   ;;(proclaim '(inline ,name))
+	   ,(if eof
+		(let ((args `(eof-error-p eof-value ,@(and (not (eq eof :no-recursive))
+							   '(recursive-p)))))
+		  `(defun ,name (,@lambda-list ,@args)
+		     ,cleanup
+		     (if (and (system:standard-object-p stream)
+			      (typep stream 'fundamental-stream))
+			 (let ((result ,call-method))
+			   (cond ((not (eq result :eof))
+				  result)
+				 (eof-error-p
+				  (signal-stream-eof stream ,@(and (not (eq eof :no-recursive))
+								   '(recursive-p))))
+				 (t
+				  eof-value)))
+			 (funcall orig-lucid-closure ,@calling-lambda-list ,@args))))
+		`(defun ,name ,lambda-list
+		   ,cleanup
+		   (if (and (system:standard-object-p stream)
+			    (typep stream 'fundamental-stream))
+		       ,call-method
+		       (funcall orig-lucid-closure ,@calling-lambda-list))))
+	   ;; Define a default method for the generic function that calls back to the
+	   ;; system stream implementation.  Call back via a message if there is one,
+	   ;; otherwise via the Common Lisp function.
+	   (defmethod ,method-name ((stream t) ,@method-lambda-list)
+	     (,cl-name ,@additional-arguments ,@(remove 'peek-type args)
+		       ,@(when eof `(nil :eof))))
+	   ;;(import ',name :clim-lisp)
+	   ;;(export ',name :clim-lisp)
+	   )))
+
+(write-forwarding-lucid-input-stream-function lisp:peek-char (&optional peek-type stream)
+					      :eof t 
+					      :additional-arguments (nil))
+
+(write-forwarding-lucid-input-stream-function lisp:read-byte (&optional stream)
+					      :eof :no-recursive)
+
+(write-forwarding-lucid-input-stream-function lisp:read-char (&optional stream) :eof t)
+
+(write-forwarding-lucid-input-stream-function lisp:unread-char (character
+								 &optional stream))
+
+(write-forwarding-lucid-input-stream-function lisp:read-char-no-hang (&optional stream)
+					      :eof t)
+
+(write-forwarding-lucid-input-stream-function lisp:listen (&optional stream))
+
+(write-forwarding-lucid-input-stream-function lisp:read-line (&optional stream) :eof t)
+
+(write-forwarding-lucid-input-stream-function lisp:clear-input (&optional stream))
+
+
+(defun signal-stream-eof (stream &optional recursive-p)
+  (declare (ignore recursive-p))
+  (error 'end-of-file :stream stream))
+
+
+;;; Make CLIM-LISP:FORMAT do something useful on CLIM windows.
+
+#|
+(defun format (stream format-control &rest format-args)
+  (when (null stream)
+    (return-from format
+      (apply #'lisp:format nil format-control format-args)))
+  (when (eq stream 't)
+    (setq stream *standard-output*))
+  (cond ((streamp stream)
+	 ;; this isn't going to quite work for ~&,
+	 ;; but it's better than nothing.
+	 (write-string (apply #'lisp:format nil format-control format-args) stream)
+	 nil)
+	(t
+	 (apply #'lisp:format stream format-control format-args))))|#
+
+
+
+;;; Higher level lisp printing functions.
+
+
+(eval-when (load)
+  (let ((original-lucid-closure
+	  (or (getf (symbol-plist 'lisp:format) :original-lucid-closure) 
+	      (setf (getf (symbol-plist 'lisp:format) :original-lucid-closure)
+		    (symbol-function 'lisp:format)))))
+    (defun format (stream format-control &rest format-args)
+      (when (eq stream 't)
+	(setq stream *standard-output*))
+      (cond ((null stream)
+	     (apply original-lucid-closure nil format-control format-args))
+	    ;; clim stream
+	    ((and (system:standard-object-p stream)
+		  (typep stream 'fundamental-stream))
+	     (write-string (apply original-lucid-closure nil format-control format-args)
+			   stream))
+	    ;; Lucid stream
+	    (t
+	     (apply original-lucid-closure stream format-control format-args))))))
+
+;;; Support for the IO functions with more varied argument templates and no
+;;; Grey stream equivalent.  Assumes there is an argument called "STREAM".
+
+(defmacro redefine-lucid-io-function (name lambda-list &body clim-body)
+  (let ((args (mapcar #'(lambda (var) (if (atom var) var (first var)))
+		      (remove-if #'(lambda (x) (member x lambda-list-keywords))
+				 lambda-list))))
+    `(let ((orig-lucid-closure 
+	     (or (getf (symbol-plist ',name) :original-lucid-closure)
+		 (setf (getf (symbol-plist ',name) :original-lucid-closure)
+		       (symbol-function ',name)))))
+	   (defun ,name ,lambda-list
+	     (if (and (system:standard-object-p stream)
+		      (typep stream 'fundamental-stream))
+		 ,@clim-body
+		 (funcall orig-lucid-closure ,@args))))))
+
+
+(defmacro %string-stream (stream &body body)
+  `(let (result
+	 (new-stream (cond ((typep ,stream 'clim-internals::accept-values-stream)
+			    (slot-value ,stream 'clim-internals::stream))
+			   ((typep ,stream 'fundamental-stream)
+			    ,stream)
+			   (t
+			    (let ((*standard-output* *terminal-io*))
+			      (error "Unknown stream type, ~S" ,stream))))))
+     (write-string
+       ;; execute the body using the STREAM locally rebound
+       ;; to an output stream object for I/O purposes:
+       (let ((,stream (make-string-output-stream)))
+	 ;; stream I/O stuff goes here
+	 (setq result ,@body				)
+	 ;; return the accumulated output string:
+	 (get-output-stream-string ,stream))
+       ;; use original output stream here ....
+       new-stream)
+     result))
+
+  
+(redefine-lucid-io-function lisp:streamp (stream) t)
+
+(redefine-lucid-io-function lcl:underlying-stream (stream &optional direction
+							  (recurse t)
+							  exact-same)
+			    (if (typep stream 'clim-internals::accept-values-stream)
+				(slot-value stream 'clim-internals::stream)
+				stream))
+
+(redefine-lucid-io-function lisp:prin1 (object &optional (stream *standard-output*))
+			      (%string-stream stream (lisp:prin1 object stream)))
+
+(redefine-lucid-io-function lisp:print (object &optional (stream *standard-output*))
+			      (%string-stream stream (lisp:print object stream)))
+
+(redefine-lucid-io-function lisp:princ (object &optional (stream *standard-output*))
+			      (%string-stream stream (lisp:princ object stream)))
+
+(redefine-lucid-io-function lisp:pprint (object &optional (stream *standard-output*))
+			      (%string-stream stream (lisp:pprint object stream)))
+
+(redefine-lucid-io-function lisp:write-line (string &optional (stream *standard-output*)
+						      &key (start 0) end)
+			      (%string-stream stream (lisp:write-line string stream :start start :end end)))
+
+
+;;; Easier to write this one out.
+;;;
+(let ((orig-lucid-closure (symbol-function 'lisp:write)))
+  (defun lisp:write (object
+		     &key
+		     ((:stream stream) *standard-output*)
+		     ((:escape escapep) *print-escape*)
+		     ((:radix *print-radix*) *print-radix*)
+		     ((:base new-print-base) *print-base* print-base-p)
+		     ((:circle *print-circle*) *print-circle*)
+		     ((:pretty *print-pretty*) *print-pretty*)
+		     ((:level *print-level*) *print-level*)
+		     ((:length *print-length*) *print-length*)
+		     ((:case new-print-case) *print-case* print-case-p)
+		     ((:array *print-array*) *print-array*)
+		     ((:gensym *print-gensym*) *print-gensym*)
+		     ((:structure lcl:*print-structure*) lcl:*print-structure*))
+    (if (and (system:standard-object-p stream)
+	     (typep stream 'fundamental-stream))
+	(%string-stream stream (lisp:write object :stream stream 
+					   :escape escapep
+					   :radix *print-radix*
+					   :base new-print-base :circle *print-circle*
+					   :pretty *print-pretty*
+					   :level *print-level* :length *print-length*
+					   :case new-print-case
+					   :array *print-array* :gensym *print-gensym*
+					   :structure lcl:*print-structure*))
+	(funcall orig-lucid-closure object :stream stream :escape escapep
+		 :radix *print-radix*
+		 :base new-print-base :circle *print-circle* :pretty *print-pretty*
+		 :level *print-level* :length *print-length* :case new-print-case
+		 :array *print-array* :gensym *print-gensym*
+		 :structure lcl:*print-structure*))))
+
+
+			    
+
+;;; Higher level lisp reading functions.
+
+;; this hack is necessary in order to allow (ACCEPT 'T ...) and
+;; (ACCEPT 'EXPRESSION ...) to function (sort of) correctly ....
+
+(defmethod MAKE-INSTANCE ((t-class (eql (find-class t))) &rest args)
+  (declare (ignore args) (dynamic-extent args))
+  t)
+
+
+(redefine-lucid-io-function lisp:read (&optional (stream *standard-input*)
+						 (eof-error-p t)
+						 (eof-value nil)
+						 (recursive-p nil))
+  ;; ACCEPT is only a rough equivalent of READ
+  (clim:accept 'clim:expression :stream stream))
+
+
+;;; Don't forget about this guys even if we don't implement them.
+
+;; READ-PRESERVING-WHITESPACE (&OPTIONAL (STREAM *STANDARD-INPUT*)
+;;					 (EOF-ERROR-P T)
+;;					 (EOF-VALUE NIL)
+;;					 (RECURSIVE-P NIL))
+
+;; READ-DELIMITED-LIST (CHAR &OPTIONAL (STREAM *STANDARD-INPUT*) (RECURSIVE-P NIL))
+
+
+;;; User Query Functions (interacts with the *QUERY-IO* stream):
+
+;;; Y-OR-N-P (&OPTIONAL FORMAT-STRING &REST FORMAT-ARGS)
+
+;;; NOTE: the built-in presentation type CLIM:BOOLEAN requires YES or NO -- not
+;;; Y or P -- as would normally be expected from Y-OR-N-P.
+
+(lcl:defadvice (lisp:y-or-n-p stream-wrapper) (&optional format-string &rest args)
+  (declare (dynamic-extent args))
+  (if (and (system:standard-object-p *QUERY-IO*)
+	   (typep *QUERY-IO* 'fundamental-stream))
+      (clim:accept 'clim:boolean :prompt (apply #'lisp::format nil format-string
+					   args))
+      (lcl:apply-advice-continue format-string args)))
+
+
+;;; YES-OR-NO-P (&OPTIONAL FORMAT-STRING &REST FORMAT-ARGS)
+;;;
+(lcl:defadvice (lisp:yes-or-no-p stream-wrapper) (&optional format-string &rest args)
+  (declare (dynamic-extent args))
+  (if (and (system:standard-object-p *query-io*)
+	   (typep *query-io* 'fundamental-stream))
+      (clim:accept 'clim:boolean :prompt (apply #'lisp:format nil format-string
+					   args))
+      (lcl:apply-advice-continue format-string args)))
+
+#+nope
+(lcl:defadvice (LISP:FORMAT stream-wrapper) (stream control-string &rest args)
+  (let ((stream (if (eq stream t) *standard-output* stream)))
+    (if (and (system:standard-object-p stream)
+	     (typep stream 'fundamental-stream))
+	(apply #'clim:format   stream control-string args)
+	(lcl:apply-advice-continue stream control-string args))))
+
-- 
GitLab