Skip to content
Snippets Groups Projects
frames.lisp 43.8 KiB
Newer Older
cer's avatar
cer committed
;;; -*- Mode: Lisp; Syntax: ANSI-Common-Lisp; Package: CLIM-INTERNALS; Base: 10; Lowercase: Yes -*-

cer's avatar
cer committed
;; $fiHeader: frames.lisp,v 1.24 92/06/03 18:18:29 cer Exp Locker: cer $
cer's avatar
cer committed

(in-package :clim-internals)

cer's avatar
cer committed
"Copyright (c) 1990, 1991, 1992 Symbolics, Inc.  All rights reserved.
 Portions copyright (c) 1989, 1990 International Lisp Associates.
 Portions copyright (c) 1991, 1992 Franz, Inc.  All rights reserved."
cer's avatar
cer committed

cer's avatar
cer committed
(define-protocol-class application-frame ())
cer's avatar
cer committed

cer's avatar
cer committed
;;--- We should add an input event-queue to frames, so that other
;;--- processes can queue up requests.  This queue should be managed
;;--- like other event queues.  It can contains "command" events, too.
cer's avatar
cer committed
(defclass standard-application-frame (application-frame)
cer's avatar
cer committed
    ;;--- Is it right for these to be SHEET accessors??
    ((name :initarg :name :accessor frame-name)
     (pretty-name :initarg :pretty-name :accessor frame-pretty-name)
     (command-table :initarg :command-table 
		    :initform (find-command-table 'user-command-table)
		    :accessor frame-command-table)
     (disabled-commands :initarg :disabled-commands :initform nil)
     ;; One of  T, NIL, or a command-table; used by the menu-bar
     (menu-bar :initarg :menu-bar :initform nil)
     (histories :initform nil)
     (frame-manager :reader frame-manager)
     (calling-frame :reader frame-calling-frame :initarg :calling-frame)
     ;; PANES is the description of all of the named panes,
     ;; ALL-PANES is an alist that stores all of the named panes that
     ;; have actually been realized so far
     (panes :initarg :panes :accessor frame-panes)
     (all-panes :initform nil)
     (current-panes :initform nil :accessor frame-current-panes)
     (initialized-panes :initform nil)
     (pane-constructors :initarg :pane-constructors)
     (top-level-sheet :accessor frame-top-level-sheet :initform nil)
     (state :initform :disowned :accessor frame-state 
	    :type (member :disowned :disabled :enabled :shrunk))
     (top-level :initarg :top-level  :accessor frame-top-level)
     (current-layout :initarg :default-layout :initform nil
		     :reader frame-current-layout)
     (geometry :initform nil :initarg :geometry :reader frame-geometry)
     (icon :initform nil :initarg :icon :reader frame-icon)
     (shell :accessor frame-shell)
     (pointer-documentation-p :initarg :pointer-documentation
			      :reader frame-pointer-documentation-p)
     (pointer-documentation-pane :initform nil)
     (properties :initform nil :initarg :properties
		 :accessor frame-properties)
     (resizable :initarg :resize-frame
		:reader frame-resizable)
cer's avatar
cer committed
     (layout :initarg :layouts :reader frame-layouts))
cer's avatar
cer committed
  (:default-initargs :pointer-documentation nil
cer's avatar
cer committed
    :layouts nil
cer's avatar
cer committed
    :resize-frame nil
    :top-level 'default-frame-top-level))
cer's avatar
cer committed

(defmethod port ((frame standard-application-frame))
  (port (frame-manager frame)))

(defmethod graft ((frame standard-application-frame))
  (graft (frame-manager frame)))

cer's avatar
cer committed
#+CLIM-1-compatibility
(define-compatibility-function (frame-top-level-window frame-top-level-sheet)
			       (frame)
  (frame-top-level-sheet frame))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod initialize-instance :after ((frame standard-application-frame) 
cer's avatar
cer committed
				       &rest args
				       &key frame-manager
cer's avatar
cer committed
					    geometry icon
cer's avatar
cer committed
					    (parent frame-manager))
cer's avatar
cer committed
  (declare (ignore args))
cer's avatar
cer committed
  (destructuring-bind (&key x y width height) geometry
    (declare (ignore x y width height)))
cer's avatar
cer committed
  (destructuring-bind (&key name pixmap clipping-mask) icon
cer's avatar
cer committed
    (declare (ignore name pixmap clipping-mask)))
cer's avatar
cer committed
  (let ((frame-manager
cer's avatar
cer committed
	  (etypecase parent
	    (null (find-frame-manager))
	    (list (apply #'find-frame-manager parent))
	    (frame-manager parent)
	    (application-frame (frame-manager parent))
	    (port (find-frame-manager :port parent))
cer's avatar
cer committed
	    (graft (find-frame-manager :port (port parent)))
cer's avatar
cer committed
	    (sheet (frame-manager (pane-frame parent))))))
cer's avatar
cer committed
    (setf (slot-value frame 'frame-manager) frame-manager)
    (adopt-frame frame-manager frame)))
cer's avatar
cer committed

cer's avatar
cer committed
;; Default method does nothing
(defmethod generate-panes ((framem standard-frame-manager)
			   (frame standard-application-frame))
cer's avatar
cer committed
  (setf (frame-panes frame) nil))

cer's avatar
cer committed
(eval-when (eval compile load)
(defun define-application-frame-1 (name state-variables pane-descriptions
cer's avatar
cer committed
				   &key top-level layouts
cer's avatar
cer committed
					command-table disabled-commands)
  (let* ((command-table-name (first command-table)))
    ;; If we're going to be defining commands for this application frame,
    ;; make sure there's an command table lying around so that all other
    ;; code doesn't have to be defensive against its absence.
    (when command-table
      (apply #'define-command-table-1 command-table))))
)	;eval-when

cer's avatar
cer committed
(defmacro define-application-frame (name superclasses slots &rest options)
cer's avatar
cer committed
  #+Genera (declare (zwei:indentation 1 25 2 3 3 1))
  (with-warnings-for-definition name define-application-frame
cer's avatar
cer committed
    (let (pane panes layouts top-level menu-bar pointer-documentation
cer's avatar
cer committed
	  command-definer command-table disabled-commands
	  icon geometry default-initargs)
cer's avatar
cer committed
      (macrolet ((extract (name keyword default &optional (pair t))
		   `(let ((entry (assoc ',keyword options)))
		      (cond ((null entry)
			     (setq ,name ,default))
			    (t
			     ,@(if pair
				   `((assert (= (length entry) 2) (entry)
					     "The length of the option ~S must be 2" entry)
				     (setq ,name (second entry)
					   options (delete entry options)))
				   `((assert (listp (rest entry)) (entry)
					     "The remainder of ~S must be a list" entry)
				     (setq ,name (rest entry)
cer's avatar
cer committed
					   options (delete entry options)))))))))
cer's avatar
cer committed
	(extract pane :pane nil)
	(extract panes :panes nil nil)
cer's avatar
cer committed
	(extract layouts :layouts nil nil)
cer's avatar
cer committed
	(extract top-level :top-level '(default-frame-top-level))
	(extract menu-bar :menu-bar t)
cer's avatar
cer committed
	(extract pointer-documentation :pointer-documentation nil)
cer's avatar
cer committed
	(extract command-definer :command-definer t)
	(extract command-table :command-table t)
cer's avatar
cer committed
	(extract disabled-commands :disabled-commands nil)
	(extract default-initargs :default-initargs nil nil)
	(extract icon :icon nil nil)
	(extract geometry :geometry nil nil))
cer's avatar
cer committed
      (check-type name symbol)
      (check-type superclasses list)
      (check-type slots list)
      (check-type pane list)
      (check-type panes list)
cer's avatar
cer committed
      (check-type layouts list)
cer's avatar
cer committed
      (check-type top-level list)
      (check-type disabled-commands list)
      (when (and pane panes)
	(error "The ~S and ~S options cannot be used together" :pane :panes))
cer's avatar
cer committed
      (when (and pane layouts)
	(error "The ~S and ~S options cannot be used together" :pane :layouts))
      (when (or (and panes (null layouts))
cer's avatar
cer committed
		;; I thing you can have multiple :layouts that dont
		;; share any panes
		#+ignore
cer's avatar
cer committed
		(and layouts (null panes)))
	(error "The ~S and ~S options must be used together" :panes :layouts))
cer's avatar
cer committed
      (when (null superclasses)
	(setq superclasses '(standard-application-frame)))
      (when (eq command-definer 't)
	(setq command-definer (fintern "~A-~A-~A" 'define name 'command)))
      (check-type command-definer symbol)
      (cond ((null command-table))
	    ((symbolp command-table)
	     (setq command-table (list command-table)))
	    (t (warn-if-command-table-invalid name command-table)))
      (when (eq (first command-table) 't)
	(setq command-table (list* name (rest command-table))))
    #-Silica (warn-if-pane-descriptions-invalid name pane-descriptions)
cer's avatar
cer committed
    #-Silica (warn-if-layouts-invalid name layouts pane-descriptions)
cer's avatar
cer committed
    (let ((pane-constructors 
cer's avatar
cer committed
	    (cond (layouts
cer's avatar
cer committed
		   (compute-pane-constructor-code panes))
		  (pane
cer's avatar
cer committed
		   (compute-pane-constructor-code `((,name ,pane))))))
	  (layout-value
	   `(list ,@(mapcar
		     #'(lambda (layout)
			 (destructuring-bind
			     (name panes . sizes) layout
			   (if sizes
			       `(list ',name ',panes 
				      ,@(mapcar #'(lambda (pane-and-size)
						    `(list ',(car pane-and-size)
							   ,@(cdr pane-and-size)))
						sizes))
			     `',layout)))
		     layouts))))
cer's avatar
cer committed
      `(progn
	 (eval-when (compile)
	   (when ',command-table
	     (setf (compile-time-property ',(first command-table) 'command-table-name) t))
	   (define-application-frame-1 ',name ',slots ,pane-constructors
cer's avatar
cer committed
				       :layouts ,layout-value
cer's avatar
cer committed
				       :top-level ',top-level
				       :command-table ',command-table))
	 (define-group ,name define-application-frame
	   (defclass ,name ,superclasses ,slots
	     ,@options
	     (:default-initargs
cer's avatar
cer committed
		 :layouts ,layout-value
cer's avatar
cer committed
	       :menu-bar ',menu-bar
	       :pointer-documentation ',pointer-documentation
cer's avatar
cer committed
	       ,@(and command-table `(:command-table ',(car command-table)))
	       ,@(and top-level `(:top-level ',top-level))
cer's avatar
cer committed
	       ,@(and layouts `(:pane-constructors ,pane-constructors))
cer's avatar
cer committed
	       ,@(and layouts `(:default-layout ',(caar layouts)))
cer's avatar
cer committed
	       ,@(and icon `(:icon (list ,@icon)))
	       ,@(and geometry `(:geometry (list ,@geometry)))
	       ,@default-initargs))
cer's avatar
cer committed
	   ,@(when command-definer
	       `((defmacro ,command-definer (command-name arguments &body body)
		   #+Genera (declare (zwei:indentation 1 3 2 1))
		   `(define-frame-command ,',(first command-table)
					  ,command-name ,arguments ,@body))
		 #+Genera (scl:defprop ,command-definer
				       define-command
				       zwei:definition-function-spec-type)
		 #+Genera (scl:defprop ,command-definer
				       remove-command
				       zwei:kill-definition)
		 #+Genera (scl:defprop ,command-definer
				       zwei:defselect-function-spec-finder
				       zwei:definition-function-spec-finder)))
	   ;;--- Need to handle DISABLED-COMMANDS properly, 
	   ;;--- which entails doing a COPY-LIST
	   (define-application-frame-1 ',name ',slots ,pane-constructors
cer's avatar
cer committed
				       :layouts ',layout-value
cer's avatar
cer committed
				       :top-level ',top-level
				       :command-table ',command-table
				       :disabled-commands ',disabled-commands)
	   #+Cloe-Runtime
	   (cloe:define-program ,name ()
	     :main ,name
	     :debugger-hook cloe-debugger-hook)
cer's avatar
cer committed
	   ,@(compute-generate-panes-code name pane panes layouts)))))))
cer's avatar
cer committed

cer's avatar
cer committed
#+Genera
(scl:defprop define-application-frame "CLIM Application Frame" si:definition-type-name)

;; For now each application frame has its own command table named after the application
cer's avatar
cer committed
(defmacro define-frame-command (command-table-name name-and-options arguments &body body)
cer's avatar
cer committed
  #+Genera (declare (zwei:indentation 2 3 3 1))
cer's avatar
cer committed
  (multiple-value-bind (command-name command-options)
      (decode-name-and-options name-and-options command-table-name)
    `(define-command (,command-name :command-table ,command-table-name ,@command-options)
cer's avatar
cer committed
	 ,arguments
       ,@body)))

#+Genera
(scl::defprop define-frame-command define-command zwei:definition-function-spec-type)
#+Genera
(scl:defun (:property define-frame-command zwei:definition-function-spec-finder) (bp)
  (zwei:defselect-function-spec-finder (zwei:forward-sexp bp 1 t)))
cer's avatar
cer committed

cer's avatar
cer committed
#+CLIM-1-compatibility
(defmacro with-frame-state-variables
	  ((frame-name &optional (frame '*application-frame*)) &body body)
  ;; frame descriptor must be findable at compile-time
  (let* ((descriptor (find-frame-descriptor frame-name))
	 (state-variables (frame-descriptor-state-variable-names descriptor)))
    `(with-slots ,state-variables ,frame ,@body)))

(defun warn-if-command-table-invalid (frame-name command-table)
  (cond ((not (and (listp command-table)
		   (symbolp (first command-table))
		   (oddp (length command-table))))
	 (warn "The ~S option for frame ~S, ~S, is invalid.~@
		It is supposed to be a list of a command table name followed by ~
		keyword/value pairs."
	       :command-table frame-name command-table))
	(t
	 (do* ((options (cdr command-table) (cddr options))
	       (keyword (first options) (first options))
	       (value (second options) (second options)))
	      ((null options))
	   (case keyword
	     (:inherit-from
	       (if (listp value)
		   (dolist (item value)
		     (unless (typep item '(or symbol command-table))
		       (warn "The ~S keyword in the ~S option for frame ~S~@
			      is followed by a list containing ~S, which is not a ~
			      command table nor a command table name."
			     :inherit-from :command-table frame-name item)))
		   (warn "The ~S keyword in the ~S option for frame ~S~@
			  is followed by ~S, which is not a list of command tables ~
			  or command table names."
			 :inherit-from :command-table frame-name value)))
	     (:menu
	       (if (listp value)
		   (dolist (clause value)
		     (unless (and (listp clause)
				  (>= (length clause) 3)
				  (oddp (length clause))
				  (stringp (first clause))
				  (member (second clause)
					  '(:command :function :menu :divider)))
		       (warn "The ~S keyword in the ~S option for frame ~S~@
			      is followed by a list of menu clauses containing~@
			      an invalid clause ~S."
			     :menu :command-table frame-name clause)))
		   (warn "The ~S keyword in the ~S option for frame ~S~@
			  is followed by ~S, which is not a list of menu clauses."
			 :menu :command-table frame-name value)))
	     (otherwise
	       (warn "The keyword ~S in the ~S option for frame ~S is invalid.~@
		      The valid keywords are ~S and ~S."
		     keyword :command-table frame-name :inherit-from :menu))))))) 
cer's avatar
cer committed

cer's avatar
cer committed
(defun compute-generate-panes-code (name code panes layouts)
cer's avatar
cer committed
  (if layouts
cer's avatar
cer committed
      (compute-complex-generate-panes-code name panes layouts)
cer's avatar
cer committed
      (compute-simple-generate-panes-code name code)))
cer's avatar
cer committed

(defun compute-simple-generate-panes-code (name code)
cer's avatar
cer committed
  (and code
cer's avatar
cer committed
       (let ((frame '#:frame)
	     (framem '#:framem))
	 `((defmethod generate-panes ((,framem standard-frame-manager) (,frame ,name))
	     (let ((*application-frame* ,frame))
	       (setf (frame-panes ,frame)
		     (frame-wrapper ,framem ,frame
		       (with-look-and-feel-realization (,framem ,frame)
			 ,code)))))))))
cer's avatar
cer committed

cer's avatar
cer committed
(defun compute-complex-generate-panes-code (name panes layouts)
cer's avatar
cer committed
  (let ((frame '#:frame)
	(framem '#:framem))
    `((defmethod generate-panes ((,framem standard-frame-manager) (,frame ,name))
cer's avatar
cer committed
	(symbol-macrolet
cer's avatar
cer committed
	  ,(mapcar #'(lambda (pane-spec)
cer's avatar
cer committed
		       (destructuring-bind (name code &rest ignore) pane-spec
			 (declare (ignore code ignore))
cer's avatar
cer committed
			 `(,name (find-or-make-pane-named ,frame ',name))))
		   panes)
	  (let ((*application-frame* ,frame))
	    (setf (frame-panes ,frame)
		  (frame-wrapper ,framem ,frame
		    (with-look-and-feel-realization (,framem ,frame)
		      (ecase (frame-current-layout ,frame)
			,@(mapcar #'(lambda (layout-spec)
cer's avatar
cer committed
				      (destructuring-bind (name panes . ignore) layout-spec
					(declare (ignore ignore))
cer's avatar
cer committed
					`(,name ,panes)))
				  layouts)))))))))))
cer's avatar
cer committed

cer's avatar
cer committed
(defun compute-pane-constructor-code (panes)
  `(list ,@(mapcar #'(lambda (pane-spec)
cer's avatar
cer committed
		       (destructuring-bind (name code &rest options) pane-spec
			 (setq code (canonicalize-pane-spec name code options))
cer's avatar
cer committed
			 `(list ',name
				#'(lambda (frame framem)
				    (with-look-and-feel-realization (framem frame)
				      ,code)))))
		   panes)))
cer's avatar
cer committed
   
cer's avatar
cer committed
(defun canonicalize-pane-spec (name code rest)
  (cond ((symbolp code)
cer's avatar
cer committed
	 (unless (getf rest :name)
	   (setf (getf rest :name) `',name))
	 (apply #'find-pane-class-constructor code rest))
cer's avatar
cer committed
	((null rest) code)
cer's avatar
cer committed
	(t
	 (error "Invalid pane specification: ~S"
		(list* name code rest)))))

cer's avatar
cer committed
(defmethod find-pane-class-constructor ((type t) &rest options)
cer's avatar
cer committed
  (error "Unknown pane type ~S with options ~S" type options))

cer's avatar
cer committed
(defmacro define-pane-type (type lambda-list &body body)
  `(defmethod find-pane-class-constructor ((type (eql ',type)) ,@lambda-list)
     ,@body))

cer's avatar
cer committed
(define-pane-type :title (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'title-pane ,@options))

cer's avatar
cer committed
(define-pane-type :interactor (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-clim-interactor-pane ,@options))

(define-pane-type :application (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-clim-application-pane ,@options))

(define-pane-type :pointer-documentation (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'pointer-documentation-pane ,@options))

(define-pane-type :command-menu (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'command-menu-pane ,@options))

cer's avatar
cer committed
(define-pane-type scroll-bar (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'scroll-bar ,@options))

cer's avatar
cer committed
(define-pane-type slider (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'slider ,@options))

cer's avatar
cer committed
(define-pane-type push-button (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'push-button ,@options))

cer's avatar
cer committed
(define-pane-type label-pane (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'label-pane ,@options))

cer's avatar
cer committed
(define-pane-type text-field (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'text-field ,@options))

cer's avatar
cer committed
(define-pane-type text-editor (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'text-editor ,@options))
cer's avatar
cer committed

cer's avatar
cer committed
(define-pane-type toggle-button (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'toggle-button ,@options))

cer's avatar
cer committed
(define-pane-type radio-box (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'radio-box ,@options))

cer's avatar
cer committed
(define-pane-type menu-bar (&rest options)
cer's avatar
cer committed
  #-Allegro (declare (dynamic-extent options))
cer's avatar
cer committed
  `(make-pane 'menu-bar ,@options))
cer's avatar
cer committed

;;; 

cer's avatar
cer committed
(defmethod find-or-make-pane-named ((frame standard-application-frame) name)
  (with-slots (all-panes pane-constructors) frame
    (second (or (assoc name all-panes)
		(car (push (list name 
cer's avatar
cer committed
 				 (funcall (second (assoc name pane-constructors))
cer's avatar
cer committed
					  frame (frame-manager frame)))
			   all-panes))))))

(defmethod layout-frame ((frame standard-application-frame) &optional width height)
  (let ((panes (frame-panes frame)))
    (when panes
cer's avatar
cer committed
      (clear-space-requirement-caches-in-tree panes)
cer's avatar
cer committed
      (unless (and width height)
	(let ((sr (compose-space panes)))
	  (setq width  (space-requirement-width sr)
cer's avatar
cer committed
		height (space-requirement-height sr))
cer's avatar
cer committed
	  ;;--- This looks dubious  --SWM
	  (multiple-value-bind (gw gh)
	      (bounding-rectangle-size (graft frame))
cer's avatar
cer committed
	    (minf width (* 0.9 gw))
cer's avatar
cer committed
 	    (minf height (* 0.9 gh)))))
cer's avatar
cer committed
      ;;--- Don't bother with this if the size didn't change?
cer's avatar
cer committed
      (let ((top-sheet (or (frame-top-level-sheet frame) panes)))
	(if (and (sheet-enabled-p top-sheet)
cer's avatar
cer committed
		 (not (frame-resizable frame)))
cer's avatar
cer committed
	    (multiple-value-call #'allocate-space 
	      top-sheet (bounding-rectangle-size top-sheet))
cer's avatar
cer committed
	  (resize-sheet* 
cer's avatar
cer committed
	   top-sheet
cer's avatar
cer committed
	   width height))))))
cer's avatar
cer committed

cer's avatar
cer committed

(defmethod (setf frame-current-layout) (layout (frame standard-application-frame))
  (unless (eq (frame-current-layout frame) layout)
    (setf (slot-value frame 'current-layout) layout)
cer's avatar
cer committed
    ;; First disown all the children
    (dolist (name-and-pane (slot-value frame 'all-panes))
      (let ((sheet (second name-and-pane)))
	(when (sheet-parent sheet)
	  (sheet-disown-child (sheet-parent sheet) sheet))))
    (dolist (child (sheet-children (frame-top-level-sheet frame)))
      (sheet-disown-child (frame-top-level-sheet frame) child))
    ;; Now we want to give it some new ones
    (generate-panes (frame-manager frame) frame)
cer's avatar
cer committed

cer's avatar
cer committed
    (sheet-adopt-child (frame-top-level-sheet frame) (frame-panes frame))
cer's avatar
cer committed
    
    (let ((layout-space-requirements 
cer's avatar
cer committed
	   (cddr (assoc layout (frame-layouts frame)))))
cer's avatar
cer committed
      (changing-space-requirements (:layout nil)
cer's avatar
cer committed
	   (flet ((adjust-layout (sheet)
cer's avatar
cer committed
		    (silica::change-space-requirements-to-default sheet)
cer's avatar
cer committed
		    (let ((x (and (panep sheet)
				  (assoc (pane-name sheet) layout-space-requirements))))
		      (when x (apply #'change-space-requirements sheet (cdr x))))))
	     (declare (dynamic-extent #'adjust-layout))
	     (map-over-sheets #'adjust-layout (frame-top-level-sheet frame)))))
cer's avatar
cer committed
    (multiple-value-call #'layout-frame
      frame (bounding-rectangle-size (frame-top-level-sheet frame)))
    (throw 'layout-changed nil)))
cer's avatar
cer committed


;;-- Should be elsewhere.  

(defmethod change-pane-space-requirements-to-default ((pane t))
  nil)

(defmethod change-pane-space-requirements-to-default ((pane space-requirement-mixin))
  (silica::change-space-requirements-to pane (silica::pane-initial-space-requirements pane)))

cer's avatar
cer committed
#+CLIM-1-compatibility
(define-compatibility-function (set-frame-layout (setf frame-current-layout))
cer's avatar
cer committed
			       (frame layout)
  (setf (frame-current-layout frame) layout))
cer's avatar
cer committed

(defun make-application-frame (frame-name &rest options 
			       &key frame-class
				    enable pretty-name
cer's avatar
cer committed
			            x y width height
cer's avatar
cer committed
				    save-under
			       &allow-other-keys)
  (declare (dynamic-extent options))
  (check-type pretty-name (or null string))
  (when (null frame-class)
    (setq frame-class frame-name))
cer's avatar
cer committed
  (when (or x y width height)
    (when (getf options :geometry)
cer's avatar
cer committed
      (error "Cannot specify ~S and ~S, S, ~S, or ~S at the same time"
	     :geometry :x :y :width :height))
cer's avatar
cer committed
    (setf (getf options :geometry)
cer's avatar
cer committed
	  (append (and x `(:x ,x))
		  (and y `(:y ,y))
		  (and width `(:width ,width))
		  (and height `(:height ,height)))))
cer's avatar
cer committed
  (with-keywords-removed (options options 
			  '(:frame-class :pretty-name
cer's avatar
cer committed
			    :enable :x :y :width :height :save-under))
cer's avatar
cer committed
      (let ((frame (apply #'make-instance frame-class
			  :name frame-name
cer's avatar
cer committed
			  ;;--- Perhaps this should be a default-initarg?
cer's avatar
cer committed
			  :pretty-name (or pretty-name
					   (title-capitalize (string frame-name)))
			  :properties `(:save-under ,save-under)
			  options)))
	(when enable 
	  (enable-frame frame))
	frame)))

(defun title-capitalize (string)
  (let ((new-string (substitute #\Space #\- string)))
    (when (eq new-string string)
      (setq new-string (copy-seq new-string)))
    (nstring-capitalize new-string)))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod enable-frame ((frame standard-application-frame))
cer's avatar
cer committed
  (unless (frame-manager frame)
cer's avatar
cer committed
    (error "Cannot enabled a disowned frame ~S" frame))
  (destructuring-bind (&key width height &allow-other-keys)
      (frame-geometry frame)
cer's avatar
cer committed
    (ecase (frame-state frame)
      (:enabled)
      ((:disabled :disowned)
       (let ((old (frame-state frame)))
	 (setf (frame-state frame) :enabled)
cer's avatar
cer committed
	 ;; If this is a new frame then if the user specified a width
cer's avatar
cer committed
	 ;; then we should be using that
cer's avatar
cer committed
	 ;; If the frame already exists then we probably should be using
cer's avatar
cer committed
	 ;; the top level sheet size
cer's avatar
cer committed
	 (multiple-value-call #'layout-frame 
cer's avatar
cer committed
	   frame
	   (ecase old
	     (:disowned 
cer's avatar
cer committed
 	       (if (and width height)
cer's avatar
cer committed
		   (values width height)
cer's avatar
cer committed
		   (values)))
cer's avatar
cer committed
	     (:disabled
cer's avatar
cer committed
	       (bounding-rectangle-size
		 (frame-top-level-sheet frame)))))
cer's avatar
cer committed
	 (note-frame-enabled (frame-manager frame) frame))))))

cer's avatar
cer committed
(defmethod destroy-frame ((frame standard-application-frame))
  (when (eq (frame-state frame) :enabled)
    (disable-frame frame))
  (disown-frame (frame-manager frame) frame))

cer's avatar
cer committed
(defmethod disable-frame ((frame standard-application-frame))
cer's avatar
cer committed
  (ecase (frame-state frame)
cer's avatar
cer committed
    ((:disowned :disabled))
cer's avatar
cer committed
    ((:enabled :shrunk)
     (setf (frame-state frame) :disabled)
     (note-frame-disabled (frame-manager frame) frame))))

cer's avatar
cer committed
(defmethod reset-frame ((frame standard-application-frame) &rest ignore)
  (declare (ignore ignore))
  nil)
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod note-frame-enabled ((framem standard-frame-manager)
			       (frame standard-application-frame))
cer's avatar
cer committed
  )

cer's avatar
cer committed
(defmethod note-frame-disabled ((framem standard-frame-manager)
				(frame standard-application-frame))
  )
cer's avatar
cer committed

(defmethod run-frame-top-level :around ((frame standard-application-frame))
cer's avatar
cer committed
  (with-simple-restart (frame-exit "Exit ~A" (frame-pretty-name frame))
cer's avatar
cer committed
    (unwind-protect
cer's avatar
cer committed
	(let (;; Reset the state of the input editor and the presentation
cer's avatar
cer committed
	      ;; type system, etc., in case there is an entry into another
	      ;; application from inside the input editor, such as a Debugger
	      ;; written using CLIM.
	      ;;--- This should be done in a more modular way
	      ;;--- If you change this, change MENU-CHOOSE-FROM-DRAWER
	      (*original-stream* nil)
	      (*input-wait-test* nil)
	      (*input-wait-handler* nil)
	      (*pointer-button-press-handler* nil)
	      (*numeric-argument* nil)
	      (*delimiter-gestures* nil)
	      (*activation-gestures* nil)
	      (*accelerator-gestures* nil)
	      (*input-context* nil)
	      (*accept-help* nil)
	      (*assume-all-commands-enabled* nil)
	      (*command-parser* 'command-line-command-parser)
	      (*command-unparser* 'command-line-command-unparser)
	      (*partial-command-parser*
		'command-line-read-remaining-arguments-for-partial-command) 
	      (*application-frame* frame))
cer's avatar
cer committed
	  (with-frame-manager ((frame-manager frame))
	    (loop
	      (with-simple-restart (nil "~A top level" (frame-pretty-name frame))
		(loop
		  (catch 'layout-changed
		    (let ((*application-frame* frame)
			  (*pointer-documentation-output*
			   (frame-pointer-documentation-output frame)))
		      ;; We must return the values from CALL-NEXT-METHOD,
		      ;; or else ACCEPTING-VALUES will return NIL
		      #-CCL-2
		      (return-from run-frame-top-level (call-next-method))
		      ;; The (RETURN-FROM FOO (CALL-NEXT-METHOD)) form above
		      ;; doesn't work in Coral.  If the "top level" restart
		      ;; above is taken, the CALL-NEXT-METHOD form blows out
		      ;; the second time through this code, claiming that it
		      ;; can't find the next method.  Hoisting the
		      ;; CALL-NEXT-METHOD out of the RETURN-FROM form seems
		      ;; to fix it...  So it conses, big deal.
		      #+CCL-2
		      (let ((results (multiple-value-list (call-next-method))))
			(return-from run-frame-top-level (values-list results))))))))))
cer's avatar
cer committed
      (disable-frame frame))))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod run-frame-top-level ((frame standard-application-frame))
cer's avatar
cer committed
  (let ((top-level (frame-top-level frame)))
    (if (atom top-level)
	(funcall top-level frame)
        (apply (first top-level) frame (rest top-level)))))

(defmethod default-frame-top-level ((frame standard-application-frame)
				    &key command-parser command-unparser
					 partial-command-parser
cer's avatar
cer committed
					 (prompt "Command: "))
cer's avatar
cer committed
  (unless (eq (frame-state frame) :enabled)
    (enable-frame frame))
cer's avatar
cer committed
  (loop
    (catch 'layout-changed
cer's avatar
cer committed
      (let* ((*standard-output*
cer's avatar
cer committed
	       (or (frame-standard-output frame) *standard-output*))
cer's avatar
cer committed
	     (*standard-input* 
cer's avatar
cer committed
	       (or (frame-standard-input frame) *standard-output*))
cer's avatar
cer committed
	     (*query-io* 
cer's avatar
cer committed
	       (or (frame-query-io frame) *standard-input*))
cer's avatar
cer committed
	     (*error-output* 
cer's avatar
cer committed
	       (or (frame-error-output frame) *standard-output*))
cer's avatar
cer committed
	     (interactor
cer's avatar
cer committed
	       (not (null (find-frame-pane-of-type frame 'interactor-pane))))
cer's avatar
cer committed
	     (*command-parser*
cer's avatar
cer committed
	       (or command-parser
		   (if interactor
		       #'command-line-command-parser
		       #'menu-command-parser)))
cer's avatar
cer committed
	     (*command-unparser*
cer's avatar
cer committed
	       (or command-unparser 
		   #'command-line-command-unparser))
cer's avatar
cer committed
	     (*partial-command-parser* 
cer's avatar
cer committed
	       (or partial-command-parser
		   (if interactor
		       #'command-line-read-remaining-arguments-for-partial-command
		       #'menu-read-remaining-arguments-for-partial-command)))
cer's avatar
cer committed
	     (command-stream
cer's avatar
cer committed
	       ;;--- We have to ask the frame since we do not want to
	       ;;--- just pick up a stream from the dynamic environment
	       (let ((si (or (frame-standard-input frame)
			     (frame-standard-output frame))))
		 ;;--- I'm not really convinced that this is right  --SWM
		 (typecase si
		   (output-protocol-mixin si)
		   (t (frame-top-level-sheet frame))))))
cer's avatar
cer committed
	#+Allegro
cer's avatar
cer committed
	(unless (typep *standard-input* 'excl::bidirectional-terminal-stream)
cer's avatar
cer committed
	  (assert (port *standard-input*)))
cer's avatar
cer committed
	#+Allegro
cer's avatar
cer committed
	(unless (typep *standard-output* 'excl::bidirectional-terminal-stream)
cer's avatar
cer committed
	  (assert (port *standard-output*)))
cer's avatar
cer committed
	#+Allegro
cer's avatar
cer committed
	(unless (typep *query-io* 'excl::bidirectional-terminal-stream)
cer's avatar
cer committed
	  (assert (port *query-io*)))
cer's avatar
cer committed
	;; The read-eval-print loop for applications...
cer's avatar
cer committed
	(loop
cer's avatar
cer committed
	  ;; Redisplay all the panes
cer's avatar
cer committed
	  (catch-abort-gestures ("Return to ~A command level" (frame-pretty-name frame))
cer's avatar
cer committed
	    (redisplay-frame-panes frame)
	    (when interactor
	      (fresh-line *standard-input*)
	      (if (stringp prompt)
		  (write-string prompt *standard-input*)
cer's avatar
cer committed
		  (funcall prompt *standard-input* frame)))
cer's avatar
cer committed
	    (let ((command (read-frame-command frame :stream command-stream)))
cer's avatar
cer committed
	      (when interactor
		(terpri *standard-input*))
	      ;; Need this check in case the user aborted out of a command menu
	      (when command
		(execute-frame-command frame command)))))))))
cer's avatar
cer committed

cer's avatar
cer committed
;; Generic because someone might want :BEFORE or :AFTER
(defmethod frame-exit ((frame standard-application-frame))
  (invoke-restart 'frame-exit))

#-Silica
(defun display-title (frame stream)
  (multiple-value-bind (pane desc) (get-frame-pane frame stream)
    (when (and pane (eq pane stream))
      (let ((title (getf (pane-descriptor-options desc) :display-string)))
	(when (and (stringp title)
		   (not (string-equal title (frame-pretty-name frame))))
	  ;; On some hosts this will update the title bar 
	  (setf (frame-pretty-name frame) title))
	(when (and (eq stream pane) (not (dummy-pane-p pane)))
	  (multiple-value-bind (width height)
	      (window-inside-size stream)
	    (draw-string* stream (or title (frame-pretty-name frame))
			  (/ width 2) (/ height 2)
			  :align-x :center :align-y :center))
	  (force-output stream))
	(values)))))

cer's avatar
cer committed
;;--- Handle incremental redisplay...
cer's avatar
cer committed
(defun display-command-menu (frame stream &rest keys
			     &key command-table &allow-other-keys)
  (declare (dynamic-extent keys))
cer's avatar
cer committed
  (when (or (null command-table)
	    (eq command-table t))
    (setq command-table (frame-command-table frame)))
  (with-keywords-removed (keys keys '(:command-table))
    (apply #'display-command-table-menu command-table stream keys)))
cer's avatar
cer committed

;; The contract of GET-FRAME-PANE is to get a pane upon which we can do normal
;; I/O operations, that is, a CLIM stream pane
(defmethod get-frame-pane ((frame standard-application-frame) pane-name &key (errorp t))
  (with-slots (all-panes) frame
    (let ((pane (assoc pane-name all-panes)))
      (when pane
	(map-over-sheets #'(lambda (sheet)
			     (when (typep sheet 'clim-stream-pane)
			       (return-from get-frame-pane sheet)))
			 (second pane)))
      (when errorp
	(error "There is no pane named ~S in frame ~S" pane-name frame)))))

cer's avatar
cer committed
(defmethod redisplay-frame-panes (frame &key force-p)
  (map-over-sheets #'(lambda (sheet)
cer's avatar
cer committed
		       (when (typep sheet 'clim-stream-pane)
cer's avatar
cer committed
			 (redisplay-frame-pane frame sheet :force-p
					       force-p)))
		   (frame-top-level-sheet frame)))

cer's avatar
cer committed
;;--- What about CLIM 0.9's PANE-NEEDS-REDISPLAY, etc?
;;--- What about CLIM 1.0's :DISPLAY-AFTER-COMMANDS :NO-CLEAR?
cer's avatar
cer committed
(defun redisplay-frame-pane (frame pane &key force-p)
cer's avatar
cer committed
  (when (symbolp pane)
    (setq pane (get-frame-pane frame pane)))
cer's avatar
cer committed
  (cond ((pane-display-function pane)
	 (let* ((ir (slot-value pane 'incremental-redisplay-p))
		(redisplay-p (if (listp ir) (first ir) ir))
cer's avatar
cer committed
		(check-overlapping (or (atom ir)	;default is T
cer's avatar
cer committed
				       (getf (rest ir) :check-overlapping t))))
	   (with-simple-restart (nil "Skip redisplaying pane ~S" pane)
	     (loop
	       (with-simple-restart (nil "Retry displaying pane ~S" pane)
		 (return
		   (let ((redisplay-record
cer's avatar
cer committed
			   (and redisplay-p
				(let ((history (stream-output-history pane)))
				  (when history
				    #+compulsive-redisplay
				    (when (> (output-record-count history) 1)
				      (cerror "Clear the output history and proceed"
					      "There is more than one element in this redisplay pane")
				      (window-clear pane))
				    (unless (zerop (output-record-count history))
				      (output-record-element history 0)))))))
cer's avatar
cer committed
		     (cond ((and redisplay-p
				 (or force-p (null redisplay-record)))
			    (when force-p
			      (window-clear pane))
			    (invoke-pane-redisplay-function frame pane))
			   (redisplay-p
			    (redisplay redisplay-record pane 
				       :check-overlapping check-overlapping))
cer's avatar
cer committed
			   ((pane-needs-redisplay pane)
cer's avatar
cer committed
			    (invoke-pane-display-function frame pane))))))))))
cer's avatar
cer committed
	(force-p
	 ;;-- Is there anything else we need to do?
	 (stream-replay pane))))
cer's avatar
cer committed

(defun invoke-pane-redisplay-function (frame pane &rest args)
cer's avatar
cer committed
  (declare (dynamic-extent args))
  (updating-output (pane)
    (apply #'invoke-pane-display-function frame pane args)))

(defun invoke-pane-display-function (frame pane &rest args)
cer's avatar
cer committed
  (declare (dynamic-extent args))
  (let* ((df (pane-display-function pane))
	 (display-args (if (listp df) (rest df) nil))
	 (display-function (if (listp df) (first df) df)))
    ;; Cons as little as possible...
    (cond ((and (null args) (null display-args))
	   (funcall display-function frame pane))
	  ((null display-args)
	   (apply display-function frame pane args))
	  ((null args)
	   (apply display-function frame pane display-args))
	  (t
	   (apply display-function frame pane (append args display-args))))))
cer's avatar
cer committed
			 
cer's avatar
cer committed
(defmethod read-frame-command ((frame standard-application-frame) 
			       &key (stream *query-io*)		;frame-query-io?
			       ;; should the rest of the *command-parser*
			       ;; etc. variables be passed as keywords or bound?
			       )
  (read-command (frame-command-table frame) :stream stream))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod execute-frame-command ((frame standard-application-frame) command)
  (apply (command-name command) (command-arguments command)))
cer's avatar
cer committed

cer's avatar
cer committed
(defvar *click-outside-menu-handler* nil)

cer's avatar
cer committed
(defmethod command-enabled (command-name (frame standard-application-frame))
  (with-slots (disabled-commands) frame
    (or *assume-all-commands-enabled*
	(and (not (member command-name disabled-commands))
	     (command-accessible-in-command-table-p
	       command-name (frame-command-table frame))))))

(defmethod (setf command-enabled) (enabled command-name (frame standard-application-frame))
  (with-slots (disabled-commands) frame
    (cond (enabled
	   (setf disabled-commands (delete command-name disabled-commands))
	   (note-command-enabled (frame-manager frame) frame command-name))
	  (t
	   (push command-name disabled-commands)
	   (note-command-enabled (frame-manager frame) frame command-name)))))

cer's avatar
cer committed
#+CLIM-1-compatibility
(progn
(define-compatibility-function (command-enabled-p command-enabled)
			       (command-name frame)
  (command-enabled command-name frame))

(define-compatibility-function (enable-command (setf command-enabled))
			       (command-name frame)
  (setf (command-enabled command-name frame) t))

(define-compatibility-function (disable-command (setf command-enabled))
  (setf (command-enabled command-name frame) nil))
)	;#+CLIM-1-compatibility

(defmethod note-command-enabled ((framem standard-frame-manager)
				 (frame standard-application-frame) command)
cer's avatar
cer committed
  (declare (ignore command)))

cer's avatar
cer committed
(defmethod note-command-disabled ((framem standard-frame-manager)
				  (frame standard-application-frame) command)
cer's avatar
cer committed
  (declare (ignore command)))

;;; The contract of this is to replay the contents of STREAM within the region.
(defmethod frame-replay ((frame standard-application-frame) stream &optional region)
  (stream-replay stream region)
  (force-output stream))

;;; The contract of this is to find an "appropriate" presentation; i.e., one
;;; satisfying the input context specified by TYPE.  Everything that looks for a
;;; presentation goes through this so that applications can specialize it.
(defmethod frame-find-innermost-applicable-presentation
cer's avatar
cer committed
	   ((frame standard-application-frame) input-context stream x y &key event)
  (find-innermost-applicable-presentation
    input-context stream x y
    :frame frame
    :modifier-state (window-modifier-state stream) :event event))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod frame-input-context-button-press-handler
cer's avatar
cer committed
	   ((frame standard-application-frame) stream button-press-event)
cer's avatar
cer committed
  (declare (ignore stream))
  (let* ((window (event-sheet button-press-event))
	 (x (pointer-event-x button-press-event))
	 (y (pointer-event-y button-press-event))
	 (highlighted-presentation (highlighted-presentation window nil))
	 (input-context *input-context*))
cer's avatar
cer committed
    #+Allegro
cer's avatar
cer committed
    (when (and *click-outside-menu-handler*
		(output-recording-stream-p window)
cer's avatar
cer committed
		(not (region-contains-position-p (stream-output-history window) x y)))
cer's avatar
cer committed
      (funcall *click-outside-menu-handler*))
    (when highlighted-presentation
      ;; Unhighlight on the way out.
      ;; But only unhighlight the window that the click is from. 
      (unhighlight-highlighted-presentation window nil))
    (throw-highlighted-presentation 
      (or (and (output-recording-stream-p window)
	       (frame-find-innermost-applicable-presentation
cer's avatar
cer committed
		 frame input-context window x y
		 :event button-press-event))
cer's avatar
cer committed
	  *null-presentation*)
      input-context
      button-press-event)))

(defun find-frame-pane-of-type (frame type)
cer's avatar
cer committed
  (map-over-sheets #'(lambda (sheet)
cer's avatar
cer committed
		       (when (typep sheet type)
cer's avatar
cer committed
			 (return-from find-frame-pane-of-type sheet)))
		   (frame-top-level-sheet frame)))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod frame-standard-output ((frame standard-application-frame))
  (or (find-frame-pane-of-type frame 'application-pane)
      (find-frame-pane-of-type frame 'interactor-pane)))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod frame-standard-input ((frame standard-application-frame))
  (or (find-frame-pane-of-type frame 'interactor-pane)
      (frame-standard-output frame)))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod frame-query-io ((frame standard-application-frame))
cer's avatar
cer committed
  (or (frame-standard-input frame)
      (frame-standard-output frame)))

cer's avatar
cer committed
(defmethod frame-error-output ((frame standard-application-frame))
  (frame-standard-output frame))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod frame-pointer-documentation-output ((frame standard-application-frame))
  (with-slots (pointer-documentation-pane) frame
    pointer-documentation-pane))

cer's avatar
cer committed
;;--- This causes direct-manipulation and menu-driven applications not to
;;--- maintain histories.  Is there a better heuristic?
(defmethod frame-maintain-presentation-histories ((frame standard-application-frame))
  (not (null (find-frame-pane-of-type frame 'interactor-pane))))
cer's avatar
cer committed

cer's avatar
cer committed
(defmethod notify-user (frame message &rest options) 
cer's avatar
cer committed
  (declare (dynamic-extent options))
  (when frame
    (setf (getf options :frame) frame))
  (apply #'frame-manager-notify-user 
	 (if frame (frame-manager frame) (find-frame-manager)) message options))
cer's avatar
cer committed

(defmethod select-file (frame &rest options) 
cer's avatar
cer committed
  (declare (dynamic-extent options))
  (when frame
    (setf (getf options :frame) frame))
  (apply #'frame-manager-select-file
	 (if frame (frame-manager frame) (find-frame-manager)) options))
cer's avatar
cer committed

cer's avatar
cer committed

;;; Pointer documentation
cer's avatar
cer committed

cer's avatar
cer committed
(defvar *pointer-documentation-interval*
	(max (floor (* 1/10 internal-time-units-per-second)) 1))
(defvar *last-pointer-documentation-time* 0)
cer's avatar
cer committed

cer's avatar
cer committed
;;; Produce pointer documentation
(defmethod frame-document-highlighted-presentation
	   ((frame standard-application-frame) presentation input-context window x y stream)
cer's avatar
cer committed
  (frame-manager-display-pointer-documentation
    (frame-manager frame) frame presentation input-context window x y stream))

(defmethod frame-manager-display-pointer-documentation
	   ((framem standard-frame-manager)
	    frame presentation input-context window x y stream)
  (when stream
cer's avatar
cer committed
    ;; The documentation should never say anything if we're not over a presentation
    (when (null presentation) 
cer's avatar
cer committed
      (window-clear stream))
cer's avatar
cer committed
    ;; Cheap test to not do this work too often
    (let ((old-modifier-state *last-pointer-documentation-modifier-state*)
	  (modifier-state (window-modifier-state window))
	  (last-time *last-pointer-documentation-time*)
	  (time (get-internal-real-time)))
      (setq *last-pointer-documentation-modifier-state* modifier-state)
      (when (and (< time (+ last-time *pointer-documentation-interval*))
		 (= modifier-state old-modifier-state))
cer's avatar
cer committed
	(return-from frame-manager-display-pointer-documentation nil))
cer's avatar
cer committed
      (setq *last-pointer-documentation-time* time))
    (when presentation
      (with-output-recording-options (stream :record nil)
	(with-end-of-line-action (stream :allow)
	  (with-end-of-page-action (stream :allow)
	    (window-clear stream)
	    (when (null (frame-document-highlighted-presentation-1