UIGalleryView.st
author ca
Fri, 17 Jan 2003 15:50:44 +0100
changeset 1671 493e0430518e
parent 1582 912fdf2e44a8
child 1673 5ec4b63a862a
permissions -rw-r--r--
no longer use InputView

"
 COPYRIGHT (c) 1997 by Claus Gittinger / eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"



"{ Package: 'stx:libtool2' }"

NoteBookView subclass:#UIGalleryView
	instanceVariableNames:'majorKey minorKeys minorKeysHolder'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

View subclass:#Canvas
	instanceVariableNames:'lockSema dragMode clientSpecHolder selection specification
		lastClickPoint menuSelector uiBuilder buttonPressed'
	classVariableNames:''
	poolDictionaries:''
	privateIn:UIGalleryView
!

DropObject subclass:#DropSpec
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:UIGalleryView::Canvas
!

!UIGalleryView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by Claus Gittinger / eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


!

documentation
"
    implements a selection panel, keeping widgets which could be placed
    into other components by drag & drop or copy @ paste. The objects
    which are draged/droped must be kind of UISpecification's.
    The UISelectionPanel used by the UIPainter is implemented in this way.

    [author:]
	Claus Gittinger
	Claus Atzkern

    [see also:]
	UIPainter
	UISelectionPanel
"

!

examples
"
    opens a gallery

									[exBegin]
    |top sel|

    top := StandardSystemView new label:'gallery'; extent:500@300.
    sel := UIGalleryView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.

    sel labels:#(    'Buttons'
		     'Panels'
		     'Text'
		   ).

    sel minorKeys:#( #standardButtonToggle
		     #standardPanels
		     #standardText
		   ).

    sel majorKey:UISelectionPanel.
    top open.
									[exEnd]
"
! !

!UIGalleryView methodsFor:'accessing'!

builder
    "get the builder used to setup a window from a specification (or nil in case
     of using a new builder)
    "
  ^ canvas builder
!

builder:aBuilderOrNil
    "set the builder used to setup a window from a specification (or nil in case
     of using a new builder)
    "
    canvas builder:aBuilderOrNil
!

canvas:aCanvas
    ^ self

!

labels:listOfLabels minorKeys:listOfMinorKeys majorKey:aMajorKey
    "setup for labels, selectors and class provider
    "
    self labels:listOfLabels.
    minorKeys := listOfMinorKeys.
    majorKey  := aMajorKey.
!

majorKey
    "get the class providing the window specifications
    "
  ^ majorKey
!

majorKey:aKey
    "get the class providing the window specifications
    "
    |appl|

    appl := self application.

    appl notNil ifTrue:[
	majorKey := appl resolveName:aKey
    ] ifFalse:[
	majorKey := Smalltalk resolveName:aKey inClass:self class
    ].
    self selection:nil
!

minorKeys
    "get the list of selector keys
    "
  ^ minorKeys
!

minorKeys:aListOfSelectors
    "set the list of selectors
    "
    minorKeys := aListOfSelectors.
    self selection:nil.
! !

!UIGalleryView methodsFor:'accessing-holders'!

clientSpecHolder
    "get the holder which keeps the current selection or in case of
     no selection the specification under the cursor
    "
  ^ canvas clientSpecHolder
!

clientSpecHolder:aHolder
    "set the holder which keeps the current selection or in case of
     no selection the specification under the cursor
    "
    canvas clientSpecHolder:aHolder
!

menuSelector
    ^ canvas menuSelector
!

menuSelector:aSelector
    ^ canvas menuSelector:aSelector
!

minorKeysHolder
    "get the holder keeping the minor keys; the selectors to access
     specifications from a class associated with the majorKey.
    "
  ^ minorKeysHolder
!

minorKeysHolder:aValueHolder
    "set the holder keeping the minor keys; the selectors to access
     specifications from a class associated with the majorKey.
    "
    minorKeysHolder notNil ifTrue:[
	minorKeysHolder removeDependent:self. 
    ].

    (minorKeysHolder := aValueHolder) notNil ifTrue:[
	minorKeysHolder addDependent:self.
    ].
    self minorKeys:(minorKeysHolder value)
! !

!UIGalleryView methodsFor:'change & update'!

selectionHasChanged
    "selection changed
    "
    |specification selector selection application|

    selection := self listIndexOf:(self selection).

    minorKeysHolder notNil ifTrue:[
        minorKeys := minorKeysHolder value.
    ].
    (selection notNil and:[minorKeys size >= selection]) ifTrue:[
        selector := minorKeys at:selection.

        (majorKey respondsTo:selector) ifTrue:[
            specification := majorKey perform:selector
        ] ifFalse:[
            (application := self application) notNil ifTrue:[
                MessageNotUnderstood handle:[:ex|
                    (application class respondsTo:selector) ifTrue:[
                        specification := application class perform:selector
                    ]
                ] do:[
                    specification := application aspectFor:selector
                ]
            ]
        ]
    ].
    self withWaitCursorDo:[
        canvas specification:specification.
    ]
!

update
    self selectionHasChanged.
!

update:something with:aParameter from:changedObject
    "one of my models changed its value
    "
    changedObject == minorKeysHolder ifTrue:[
        ^ self minorKeys:( minorKeysHolder value)
    ].
    super update:something with:aParameter from:changedObject.

! !

!UIGalleryView methodsFor:'initialization & release'!

initialize
    "setup default attributes
    "
    canvas := Canvas.

    super initialize.

    self action:[:something| self selectionHasChanged ].

!

release
    minorKeysHolder notNil ifTrue:[
        minorKeysHolder removeDependent:self. 
        minorKeysHolder := nil.
    ].
    super release.
! !

!UIGalleryView::Canvas methodsFor:'accessing'!

builder
    "get the builder used to setup a window from a specification (or nil in case
     of using a new builder)
    "
  ^ uiBuilder
!

builder:something
    "set the builder used to setup a window from a specification (or nil in case
     of using a new builder)
    "
    uiBuilder := something.
!

clientSpecHolder
    "get the holder which keeps the current selection or in case of
     no selection the specification under the cursor
    "
    ^ clientSpecHolder
!

clientSpecHolder:aHolder
    "set the holder which keeps the current selection or in case of
     no selection the specification under the cursor
    "
    (clientSpecHolder := aHolder) notNil ifTrue:[
	clientSpecHolder value:selection
    ].
!

menuSelector
    "return the value of the instance variable 'menuSelector' (automatically generated)"

    ^ menuSelector
!

menuSelector:something
    "set the value of the instance variable 'menuSelector' (automatically generated)"

    menuSelector := something.
!

specification
    "get current specification
    "
   ^ specification


!

specification:aSpecOrSpecArray
    "set a new specification
    "
    |builder|

    self selection:nil.

    subViews size ~~ 0 ifTrue:[
        subViews copy do:[:aSubView| aSubView destroy ].
    ].

    aSpecOrSpecArray notNil ifTrue:[
        specification := UISpecification from:aSpecOrSpecArray.

        (specification respondsTo:#buildViewFor:in:) ifFalse:[
            specification := nil.
            ^ self
        ].
        (builder := uiBuilder) isNil ifTrue:[
            builder := UIBuilder new isEditing:true.
            builder showDefaults:true.
        ].

        specification buildViewFor:builder in:self.

        subViews do:[:v|
            (self findSpecFor:v) notNil ifTrue:[
                v borderWidth:1.
            ]
        ].
        self shown ifTrue:[
            self realizeAllSubViews.
        ]
    ] ifFalse:[
        specification := nil
    ]
! !

!UIGalleryView::Canvas methodsFor:'building'!

buildSpecFrom:aSpec
    "build spec out of spec
    "
    |spec comp coll|

    (aSpec notNil and:[aSpec canUIDrag]) ifFalse:[
	^ nil
    ].

    spec := aSpec copy.

    (aSpec class supportsSubComponents and:[aSpec component notNil]) ifFalse:[
	^ spec
    ].
    comp := aSpec component.
    spec component:nil.

    comp canUIDrag ifFalse:[
      ^ spec
    ].
    coll := OrderedCollection new.

    comp do:[:anEntry||spc|
	(spc := self buildSpecFrom:anEntry) notNil ifTrue:[
	    coll add:spc
	]
    ].
    coll isEmpty ifTrue:[
      ^ spec
    ].
    comp := comp copy.
    comp collection:coll.
    spec component:comp.
  ^ spec




! !

!UIGalleryView::Canvas methodsFor:'drag & drop'!

startDragFrom:aPoint
    "start drag at a point
    "
    |spec dragObj offset clickPos|

    clickPos := lastClickPoint.
    clickPos isNil ifTrue:[^ self].
    lastClickPoint := nil.

    self selection:(self findObjectAtX:(clickPos x) y:(clickPos y)).

    spec := self findSpecFor:selection.
    spec isNil ifTrue:[^ self].

    dragMode := true.
    spec := self buildSpecFrom:spec.
    spec name:(spec copy userFriendlyName, $1).

    dragObj := DropSpec for:selection specification:spec.
    offset  := clickPos - selection origin.

    dragMode ifTrue:[
        DragAndDropManager startDrag:dragObj from:self offset:offset.
    ].
! !

!UIGalleryView::Canvas methodsFor:'event handling'!

processEvent:anEvent
    |evView x y p|

    dragMode ifTrue:[
        anEvent isButtonReleaseEvent ifTrue:[
            dragMode := false.
            lastClickPoint := nil.
            self invalidateSelection.
        ].
        ^ false
    ].

    evView := anEvent view.
    evView isNil ifTrue:[ ^ false ].

    evView == self ifFalse:[
        (evView isComponentOf:self) ifFalse:[
            ^ false
        ].
    ].

    anEvent isInputEvent ifFalse:[
        anEvent isDamage ifTrue:[ self invalidateSelection ].
        ^ false
    ].

    anEvent isButtonReleaseEvent ifTrue:[
        lastClickPoint notNil ifTrue:[
            x := lastClickPoint x.
            y := lastClickPoint y.
            lastClickPoint := nil.
            self selection:(self findObjectAtX:x y:y).
        ].
        ^ true
    ].

    anEvent isButtonEvent ifFalse:[^ true].

    x := anEvent x.
    y := anEvent y.
    p := device translatePoint:(x@y) fromView:evView toView:self.

    anEvent isButtonPressEvent ifTrue:[ |button application|
        button := anEvent button.
        x := p x.
        y := p y.

        (button == 1 or:[button == #select]) ifTrue:[
            lastClickPoint := p.
        ] ifFalse:[
            lastClickPoint := nil.

            (menuSelector notNil and:[(application := self application) notNil]) ifTrue:[
                MessageNotUnderstood catch:[
                    application aspectFor:menuSelector
                ]
            ]
        ].
        ^ true
    ].

    anEvent isButtonMotionEvent ifTrue:[
        (lastClickPoint notNil and:[anEvent state ~~ 0]) ifTrue:[
            (lastClickPoint dist:(x@y)) > 10.0 ifTrue:[
                self startDragFrom:(x@y).
                "/ self startDragWithOffset:(x@y) - lastClickPoint.
                lastClickPoint := nil.
            ]
        ].
        ^ true
    ].

    ^ true
! !

!UIGalleryView::Canvas methodsFor:'initialization'!

initialize
    super initialize.

    lockSema      := RecursionLock new.
    dragMode      := false.
    buttonPressed := false.
!

realize
    super realize.
    self windowGroup addPreEventHook:self.
! !

!UIGalleryView::Canvas methodsFor:'private'!

redrawSelection
    "redraw all items selected
    "
    (buttonPressed or:[selection isNil or:[shown not]]) ifTrue:[
        ^ self
    ].

    (self sensor hasEvent:#redrawSelection for:self) ifTrue:[^ self].

    lockSema critical:[
        (buttonPressed or:[selection isNil ]) ifFalse:[
            self clippedByChildren:false.

            self handlesOf:selection do:[:aRectangle|
                self fillRectangle:aRectangle
            ].
            self clippedByChildren:true.
        ].
    ].
! !

!UIGalleryView::Canvas methodsFor:'searching'!

findObjectAtX:x y:y
    "find the origin/corner of the currentWidget
    "
    |point p|

    point := Point x:x y:y.

    subViews do:[:v|
        |pX pY|

        p := device translatePoint:point fromView:self toView:v.
        pX := p x.
        pY := p y.
        (     pX >= 0 and:[pX <= v width
         and:[pY >= 0 and:[pY <= v height
         and:[(self findSpecFor:v) notNil]]]]
        ) ifTrue:[
            ^ v
        ]
    ].
    ^ nil
!

findSpecFor:anObject
    "returns subspec assigned to instance or nil
    "
    |name|

    anObject notNil ifTrue:[
        name := anObject name.

        specification do:[:aSpec|
            aSpec notNil ifTrue:[
                aSpec name = name ifTrue:[
                    aSpec canUIDrag ifTrue:[^ aSpec]
                                   ifFalse:[^ nil]
                ]
            ]
        ]
    ].
    ^ nil

    "Modified: / 18.5.1999 / 14:47:25 / cg"
! !

!UIGalleryView::Canvas methodsFor:'selection'!

handlesOf:aComponent do:aOneArgBlock
    "evaluate the block on each handle; the argument to the block
     is a rectangle
    "
    aComponent notNil ifTrue:[
	aOneArgBlock value:(aComponent origin       - (2@2) extent:6@6).
	aOneArgBlock value:(aComponent corner       - (1@1) extent:6@6).
	aOneArgBlock value:(aComponent topRight     - (1@2) extent:6@6).
	aOneArgBlock value:(aComponent bottomLeft   - (2@1) extent:6@6).
	aOneArgBlock value:(aComponent leftCenter   - (2@0) extent:6@6).
	aOneArgBlock value:(aComponent rightCenter  - (1@0) extent:6@6).
	aOneArgBlock value:(aComponent topCenter    - (0@2) extent:6@6).
	aOneArgBlock value:(aComponent bottomCenter - (0@1) extent:6@6).
    ]


!

hideSelection
    "show unselected
    "
    |r currSel|

    (currSel := selection) isNil ifTrue:[
        ^ self
    ].
    shown ifFalse:[^ self].

    lockSema critical:[
        selection == currSel ifTrue:[
            selection := nil.

            self clippedByChildren:false.

            self handlesOf:currSel do:[:aRectangle|
                self clearRectangle:aRectangle
            ].
            self clippedByChildren:true.

            r := currSel bounds.

            subViews do:[:sv|
                |absOrg absFrame|

                (sv bounds intersects:r) ifTrue:[
                    sv borderColor:(Color white).           "/ to force a redraw
                    sv borderColor:(Color black).

                    sv withAllSubViewsDo:[:v|
                        v realized ifTrue:[
                            v fill:v viewBackground.
                            v exposeX:0 y:0 width:v width height:v height.
                        ]
                    ]
                ]
            ]
        ].
        selection := currSel.
    ].
!

invalidateSelection
    "show selected
    "
    (shown and:[selection notNil and:[buttonPressed not]]) ifTrue:[
        self sensor pushUserEvent:#redrawSelection for:self withArguments:nil.
    ].
!

selection:anObject
    "selection changed
    "
    |spec|

    selection == anObject ifTrue:[^ self].

    lockSema critical:[
        selection == anObject ifFalse:[
            self hideSelection.
            spec := self findSpecFor:anObject.

            spec notNil ifTrue:[ selection := anObject ]
                       ifFalse:[ selection := nil ].

            self invalidateSelection.    
            clientSpecHolder notNil ifTrue:[ clientSpecHolder value:spec ].
        ]
    ].
! !

!UIGalleryView::Canvas::DropSpec class methodsFor:'instance creation'!

for:aView specification:aSpec
    "create drop object for a view derived from a specification
    "
    |point extent rootView device inst displayObject|

    device   := aView device.
    rootView := device rootView.
    extent   := aView extent.
    point    := device translatePoint:0@0 fromView:aView toView:rootView.

    (point x > 0 and:[point y > 0]) ifTrue:[
        point := point + extent.
        (point x < rootView width and:[point y < rootView height]) ifTrue:[
            aView topView raise.
            device flush.
            aView invalidate.
            aView windowGroup processExposeEvents.
            displayObject := Image fromView:aView grab:false.
        ]
    ].
    displayObject isNil ifTrue:[
        displayObject := Form extent:extent depth:1.
        displayObject colorMap:(Array with:Color white with:Color black).
        displayObject fill:(Color colorId:0).
        displayObject paint:(Color colorId:1).
        displayObject displayRectangleX:0 y:0 width:aView extent x height:aView extent y.
    ].
    aSpec class == UISubSpecification ifTrue:[
        aSpec layout:(LayoutOrigin fromPoint:0@0)
    ].

    inst := self new.
    inst displayObject:displayObject.
    inst theObject:aSpec.
  ^ inst.

    "Modified: / 10.10.2001 / 14:03:00 / cg"
! !

!UIGalleryView class methodsFor:'documentation'!

version
    ^ '$Header$'
! !