caml-types:

- largest typed region is now dynamically recomputed.
 - changed binding to C-down-mouse-1 (allow other bindings).
 - allow scrolling when mouse is moved to bottom or top of window.
 - ignore key events, out of frame-motion, and wait for mouse release.


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5875 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Didier Rémy 2003-10-20 12:06:42 +00:00
parent 60b74b3c3c
commit 7cbb6ca64b
4 changed files with 159 additions and 64 deletions

View File

@ -5,10 +5,25 @@
(defalias 'caml-line-beginning-position 'line-beginning-position) (defalias 'caml-line-beginning-position 'line-beginning-position)
(defalias 'caml-read-event 'read-event)
(defalias 'caml-window-edges 'window-edges)
(defun caml-mouse-vertical-position ()
(cddr (mouse-position)))
(defalias 'caml-ignore-event-p 'integer-or-marker-p)
(defalias 'caml-mouse-movement-p 'mouse-movement-p)
(defalias 'caml-sit-for 'sit-for)
(defmacro caml-track-mouse (&rest body) (cons 'track-mouse body))
(defun caml-event-window (e) (posn-window (event-start e))) (defun caml-event-window (e) (posn-window (event-start e)))
(defun caml-event-point-start (e) (posn-point (event-start e))) (defun caml-event-point-start (e) (posn-point (event-start e)))
(defun caml-event-point-end (e) (posn-point (event-end e))) (defun caml-event-point-end (e) (posn-point (event-end e)))
(defalias 'caml-read-event 'read-event)
(defmacro caml-track-mouse (&rest body) (cons 'track-mouse body)) (defun caml-release-event-p (original event)
(and (equal (event-basic-type original) (event-basic-type event))
(let ((modifiers (event-modifiers event)))
(or (member 'drag modifiers)
(member 'click modifiers)))))
(provide 'caml-emacs) (provide 'caml-emacs)

View File

@ -153,7 +153,7 @@ See `caml-types-location-re' for annotation file format.
(not (window-live-p (get-buffer-window caml-types-buffer)))) (not (window-live-p (get-buffer-window caml-types-buffer))))
(display-buffer caml-types-buffer)) (display-buffer caml-types-buffer))
(unwind-protect (unwind-protect
(sit-for 60) (caml-sit-for 60)
(delete-overlay caml-types-expr-ovl) (delete-overlay caml-types-expr-ovl)
))) )))
@ -388,11 +388,23 @@ See `caml-types-location-re' for annotation file format.
(interactive "e") (interactive "e")
nil) nil)
(defun caml-types-time ()
(let ((time (current-time)))
(+ (* (mod (cadr time) 1000) 1000)
(/ (cadr (cdr time)) 1000))))
(defun caml-types-explore (event) (defun caml-types-explore (event)
"Explore type annotations by mouse dragging. "Explore type annotations by mouse dragging.
The expression under the mouse is highlighted The expression under the mouse is highlighted and its type is displayed
and its type is displayed in the minibuffer, until the move is released." in the minibuffer, until the move is released, much as `caml-types-show-type'.
The function uses two overlays.
. One overlay delimits the largest region whose all subnodes
are well-typed.
. Another overlay delimits the current node under the mouse (whose type
annotation is beeing displayed).
"
(interactive "e") (interactive "e")
(set-buffer (window-buffer (caml-event-window event))) (set-buffer (window-buffer (caml-event-window event)))
(let* ((target-buf (current-buffer)) (let* ((target-buf (current-buffer))
@ -403,8 +415,13 @@ and its type is displayed in the minibuffer, until the move is released."
target-pos target-pos
Left Right limits cnum node mes type Left Right limits cnum node mes type
region region
(window (caml-event-window event))
target-tree target-tree
(speed 100)
(last-time (caml-types-time))
(original-event event)
) )
(select-window window)
(unwind-protect (unwind-protect
(progn (progn
(caml-types-preprocess type-file) (caml-types-preprocess type-file)
@ -415,66 +432,111 @@ and its type is displayed in the minibuffer, until the move is released."
;; (message "Drag the mouse to explore types") ;; (message "Drag the mouse to explore types")
(unwind-protect (unwind-protect
(caml-track-mouse (caml-track-mouse
(setq region (while event
(caml-types-typed-make-overlay (message nil)
target-buf (caml-event-point-start event))) (message "%S" event)
(while (and event (cond
(integer-or-marker-p ;; In emacs eliminate
(setq cnum (caml-event-point-end event)))) ((caml-ignore-event-p event))
(if (and region (<= (car region) cnum) (< cnum (cdr region))) ((caml-release-event-p original-event event)
(if (and limits (setq event nil))
(>= cnum (car limits)) (< cnum (cdr limits))) ((and (caml-mouse-movement-p event)
(message mes) (not (and (equal window (caml-event-window event))
(setq target-bol (integer-or-marker-p
(save-excursion (caml-event-point-end event)))))
(goto-char cnum) (caml-line-beginning-position)) (let* ((win (caml-window-edges window))
target-line (1+ (count-lines (point-min) (top (nth 1 win))
target-bol)) (bottom (- (nth 3 win) 1))
target-pos mouse
(vector target-file target-line target-bol cnum)) time
(save-excursion )
(setq node (caml-types-find-location (while (and
target-pos () target-tree)) (caml-sit-for 0 (/ 500 speed))
(set-buffer caml-types-buffer) (setq time (caml-types-time))
(erase-buffer) (> (- time last-time) (/ 500 speed))
(cond (setq mouse (caml-mouse-vertical-position))
(node (or (< mouse top) (>= mouse bottom))
(setq Left )
(caml-types-get-pos target-buf (elt node 0)) (setq last-time time)
Right (cond
(caml-types-get-pos target-buf (elt node 1))) ((< mouse top)
(move-overlay (setq speed (- top mouse))
caml-types-expr-ovl Left Right target-buf) (condition-case nil
(setq limits (scroll-down 1)
(caml-types-find-interval target-buf (error (message "Beginning of buffer!"))))
target-pos node) ((>= mouse bottom)
type (elt node 2)) (setq speed (+ 1 (- mouse bottom)))
) (condition-case nil
(t (scroll-up 1)
(delete-overlay caml-types-expr-ovl) (error (message "End of buffer!"))))
(setq type "*no type information*") )
(setq limits (setq speed (* speed speed))
(caml-types-find-interval )))
target-buf target-pos target-tree)) ((or (caml-mouse-movement-p event)
)) (equal original-event event))
(message (setq mes (format "type: %s" type))) (setq cnum (caml-event-point-end event))
(insert type) (if (and region
))) (<= (car region) cnum) (< cnum (cdr region)))
(setq event (caml-read-event)) nil
(unless (mouse-movement-p event) (setq event nil)) (setq region
(caml-types-typed-make-overlay
target-buf (caml-event-point-start event))))
(if (and limits
(>= cnum (car limits)) (< cnum (cdr limits)))
(message mes)
(setq target-bol
(save-excursion
(goto-char cnum) (caml-line-beginning-position))
target-line (1+ (count-lines (point-min)
target-bol))
target-pos
(vector target-file target-line target-bol cnum))
(save-excursion
(setq node (caml-types-find-location
target-pos () target-tree))
(set-buffer caml-types-buffer)
(erase-buffer)
(cond
(node
(setq Left
(caml-types-get-pos target-buf (elt node 0))
Right
(caml-types-get-pos target-buf (elt node 1)))
(move-overlay
caml-types-expr-ovl Left Right target-buf)
(setq limits
(caml-types-find-interval target-buf
target-pos node)
type (elt node 2))
)
(t
(delete-overlay caml-types-expr-ovl)
(setq type "*no type information*")
(setq limits
(caml-types-find-interval
target-buf target-pos target-tree))
))
;; (message (setq mes (format "type: %s" type)))
(insert type)
))
)
)
(if event (setq event (caml-read-event)))
) )
) )
(delete-overlay caml-types-expr-ovl) (delete-overlay caml-types-expr-ovl)
(delete-overlay caml-types-typed-ovl) (delete-overlay caml-types-typed-ovl)
)) ))
;; the mouse is down. One should prevent against mouse release, ;; When an error occurs, the mouse release event has not been read.
;; which could do something undesirable. ;; We could wait for mouse release to prevent execution of
;; In most common cases, next event will be mouse release. ;; a binding of mouse release, such as cut or paste.
;; In most common cases, next event will be the mouse release.
;; However, it could also be a key stroke before mouse release. ;; However, it could also be a key stroke before mouse release.
;; Will then execute the action for mouse release (if bound).
;; Emacs does not allow to test whether mouse is up or down. ;; Emacs does not allow to test whether mouse is up or down.
;; Same problem may happen above while exploring ;; Not sure it is robust to loop for mouse release after an error
(if (and event (caml-read-event))) ;; occured, as is done for exploration.
;; So far, we just ignore next event. (Next line also be uncommenting.)
(if event (caml-read-event))
))) )))
(defun caml-types-typed-make-overlay (target-buf pos) (defun caml-types-typed-make-overlay (target-buf pos)

View File

@ -9,12 +9,31 @@
(defun caml-line-beginning-position () (defun caml-line-beginning-position ()
(save-excursion (beginning-of-line) (point))) (save-excursion (beginning-of-line) (point)))
(defun caml-event-window (e) (event-window e)) (defalias 'caml-read-event 'next-event)
(defalias 'caml-window-edges 'window-pixel-edges)
(defun caml-mouse-vertical-position ()
(let ((e (mouse-position-as-motion-event)))
(and e (event-y-pixel e))))
(defalias 'caml-mouse-movement-p 'motion-event-p)
(defun caml-event-window (e)
(and (mouse-event-p e) (event-window e)))
(defun caml-event-point-start (e) (event-closest-point e)) (defun caml-event-point-start (e) (event-closest-point e))
(defun caml-event-point-end (e) (event-closest-point e)) (defun caml-event-point-end (e) (event-closest-point e))
(defalias 'caml-read-event 'next-event) (defun caml-ignore-event-p (e)
(if (and (key-press-event-p e) (equal (key-binding e) 'keyboard-quit))
(keyboard-quit))
(not (mouse-event-p e)))
(defun caml-sit-for (sec &optional mili)
(sit-for (+ sec (if mili (* 0.001 mili)))))
(defmacro caml-track-mouse (&rest body) (cons 'progn body)) (defmacro caml-track-mouse (&rest body) (cons 'progn body))
(defun mouse-movement-p (e) (equal (event-type e) 'motion)) (defun caml-release-event-p (original event)
(and (button-release-event-p event)
(equal (event-button original) (event-button event))))
(provide 'caml-xemacs) (provide 'caml-xemacs)

View File

@ -283,9 +283,8 @@ have caml-electric-indent on, which see.")
;; caml-types ;; caml-types
(define-key caml-mode-map [?\C-c?\C-t] 'caml-types-show-type) (define-key caml-mode-map [?\C-c?\C-t] 'caml-types-show-type)
;; to prevent misbehavior in case of error during exploration. ;; must be a mouse-down event. Can be any button and any prefix
(define-key caml-mode-map [mouse-2] 'caml-types-mouse-ignore) (define-key caml-mode-map [?\C-c down-mouse-1] 'caml-types-explore)
(define-key caml-mode-map [down-mouse-2] 'caml-types-explore)
;; caml-help ;; caml-help
(define-key caml-mode-map [?\C-c?i] 'ocaml-add-path) (define-key caml-mode-map [?\C-c?i] 'ocaml-add-path)
(define-key caml-mode-map [?\C-c?]] 'ocaml-close-module) (define-key caml-mode-map [?\C-c?]] 'ocaml-close-module)