View source with raw comments or as raw
    1/*  Part of XPCE --- The SWI-Prolog GUI toolkit
    2
    3    Author:        Jan Wielemaker and Anjo Anjewierden
    4    E-mail:        jan@swi.psy.uva.nl
    5    WWW:           http://www.swi.psy.uva.nl/projects/xpce/
    6    Copyright (c)  2003-2011, University of Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(pce_unclip, []).   36:- use_module(library(pce)).   37
   38
   39/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   40This library deals with showing graphicals   that  are partly clipped by
   41the window on which  they  are  displayed.   It  is  used  by  the class
   42toc_image from library(pce_toc) to  show   nodes  that  (typically) have
   43their right-side clipped and provides a  convient mechanism to deal with
   44a few long labels in a relatively small window.
   45
   46It is upto the clipped graphical to  detect the mouse is positioned over
   47it   and   part   of   the   graphical     is    clipped.   The   method
   48`graphical->clipped_by_window' can be used to   detect  the graphical is
   49(partly) obscured.
   50
   51For an example, please start  the   SWI-Prolog  manual  browser using ?-
   52help.   The   source-code   that   attaches     this   library   is   in
   53`toc_image->entered'.
   54- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
   55
   56:- pce_extend_class(graphical).
   57
   58clipped_by_window(Gr) :->
   59    "Test if graphical is clipped by window border"::
   60    get(Gr, window, Window),
   61    get(Window, visible, Visible),
   62    get(Gr, absolute_position, Window, point(X,Y)),
   63    get(Gr, area, area(_,_,W,H)),
   64    \+ send(Visible, inside, area(X,Y,W,H)).
   65
   66:- pce_end_class(graphical).
   67
   68
   69                 /*******************************
   70                 *           INVISIBLE          *
   71                 *******************************/
   72
   73:- pce_global(@unclip_window, new(pce_unclip_window)).
   74
   75:- pce_begin_class(pce_unclip_window, window).
   76
   77variable(handler, handler, get, "Handler used to fetch all events").
   78variable(busy,    bool := @off, none, "Handling attach/detach?").
   79
   80class_variable(background, colour, azure).
   81
   82initialise(W) :->
   83    send_super(W, initialise),
   84    get(W, frame, Fr),
   85    send(Fr, kind, popup),
   86    send(Fr, sensitive, @off),
   87    send(W, pen, 0),
   88    send(Fr, border, 1),
   89    send(Fr?tile, border, 0),
   90    send(W, slot, handler,
   91         handler(any, message(W, unclipped_event, @event))).
   92
   93attach(W, To:graphical) :->
   94    "Attach to graphical"::
   95    (   get(W, slot, busy, @off)
   96    ->  send(W, slot, busy, @on),
   97        call_cleanup(attach(W, To),
   98                     send(W, slot, busy, @off))
   99    ;   true
  100    ).
  101
  102attach(W, To) :-
  103    get(To, window, ToWindow),
  104    (   get(W, hypered, mirroring, Old)
  105    ->  send(W, delete_hypers, mirroring),
  106        (   get(Old, window, ToWindow)
  107        ->  true
  108        ;   send(Old, grab_pointer, @off),
  109            send(ToWindow, grab_pointer, @on)
  110        )
  111    ;   get(W, handler, H),
  112        send(ToWindow, grab_pointer, @on),
  113        send(@display?inspect_handlers, prepend, H)
  114    ),
  115    new(_, hyper(To, W, mirror, mirroring)),
  116    send(W, update),
  117    get(To, display_position, point(X,Y)),
  118    (   get(@pce, window_system, windows)
  119    ->  Border = 0                  % TBD: Fix inside kernel
  120    ;   get(W, border, Border)
  121    ),
  122    send(W, open, point(X-Border,Y-Border)),
  123    send(W, expose).
  124
  125update(W) :->
  126    "Update for changed receiver"::
  127    send(W, clear),
  128    (   get(W, hypered, mirroring, Gr)
  129    ->  get(Gr, clone, Clone),
  130        (   get(@pce, window_system, windows)
  131        ->  get(Clone, size, size(W0, H0)),
  132            send(W, size, size(W0+1, H0+1))
  133        ;   get(Clone, size, Size),
  134            send(W, size, Size)
  135        ),
  136        send(Clone, set, 0, 0),
  137        send(W, display, Clone)
  138    ;   true
  139    ).
  140
  141
  142detach(W) :->
  143    "Detach and hide"::
  144    (   get(W, slot, busy, @off)
  145    ->  send(W, slot, busy, @on),
  146        call_cleanup(detach(W),
  147                     send(W, slot, busy, @off))
  148    ;   true
  149    ).
  150
  151detach(W) :-
  152    (   get(W, hypered, mirroring, Gr)
  153    ->  send(W, delete_hypers, mirroring),
  154        send(W, clear),
  155        send(W, show, @off),
  156        get(W, handler, H),
  157        send(Gr?window, grab_pointer, @off),
  158        send(@display?inspect_handlers, delete, H)
  159    ;   true
  160    ).
  161
  162
  163unclipped_event(W, Ev:event) :->
  164    (   send(Ev, is_a, loc_move),
  165        (   \+ send(Ev, inside, W)
  166        ;   get(W, hypered, mirroring, Gr),
  167            \+ send(Ev, inside, Gr?window)
  168        )
  169    ->  send(W, detach)
  170    ;   (   send(Ev, is_a, button)
  171        ;   send(Ev, is_a, keyboard)
  172        ;   send(Ev, is_a, wheel)
  173        )
  174    ->  send(W, detach),
  175        fail                        % normal event-processing
  176    ).
  177
  178:- pce_end_class(pce_unclip_window)