DrawAdaptor.st
author Stefan Vogel <sv@exept.de>
Tue, 22 Jul 2008 20:49:37 +0200
changeset 2523 497ef51ffbe6
parent 2502 50d27de32abd
child 2524 166a10a040c1
permissions -rw-r--r--
documentation

"
 COPYRIGHT (c) 2008 by 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:libview2' }"

Object subclass:#DrawAdaptor
	instanceVariableNames:'value drawValue'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Support'
!

!DrawAdaptor class methodsFor:'documentation'!

copyright 
"
 COPYRIGHT (c) 2008 by 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
"
    DrawAdaptor constains to values:
        - any Object
        - a replacement Object to be used only for draw operations.

    Use this class whenever you want to show something different for a given object -
    e.g. to show some language specific text instead of a symbol or any object in ComboBoxes/PopUpLists.

    [author:]
        Stefan Vogel (stefan@zwerg)

    [instance variables:]
        value       Object      the original object
        drawValue   Object      the replacement object used for draw operations

    [class variables:]

    [see also:]

"
!

examples
"
                                                                                    [exBegin]
    |labelList top comboList|

    labelList := DrawAdaptor collection:#(File Classes System Windows)
                             withResources:Launcher classResources.

     top := StandardSystemView new.
     top extent:(300 @ 200).

     comboList := ComboListView in:top.
     comboList origin:(0.0 @ 0.0) corner:(1.0 @ 0.0).
     comboList bottomInset:(comboList preferredExtent y negated).

     comboList list:labelList.
     comboList contents:labelList first.
     comboList action:[:selected | Transcript showCR:selected realValue].
     top open.
                                                                                     [exEnd]

"
! !

!DrawAdaptor class methodsFor:'instance creation'!

collection:aCollectionOfObjects withResources:resourcePack
    "create a collection of DrawAdaptors from aCollectionOfObjects (usually strings or symbols).
     Use resourcePack to do the translation"

    ^ aCollectionOfObjects collect:[:each|
            self value:each withResources:resourcePack
        ].


    "
      self collection:#(a File c) withResources:Launcher classResources
    "
!

value:value drawValue:drawValue 
    ^ self new value:value drawValue:drawValue 
!

value:anObject withResources:resourcePack
    "Create a DrawAdaptor for anObject,
     Resolved via the translations in resourcePack"

    ^ self new value:anObject drawValue:(resourcePack string:anObject)

    "
      self value:#Hello withResources:Launcher classResources
    "
! !

!DrawAdaptor methodsFor:'accessing'!

asString
    ^ drawValue
!

drawValue
    ^ drawValue
!

drawValue:something
    drawValue := something.
!

realValue
    ^ value
!

string
    ^ drawValue
!

value:something
    value := something.
!

value:valueArg drawValue:drawValueArg 
    value := valueArg.
    drawValue := drawValueArg.
! !

!DrawAdaptor methodsFor:'comparing'!

= anObject
    "two TranslatedSymbols are equal, if they have the same symbol"

    self species == anObject species ifTrue:[
        ^ value = anObject value.
    ].
    ^ value = anObject.

    "
        (self value:#hash drawValue:'x') = #hash
        (self value:#hash drawValue:'x') = 1
        (self value:#hash drawValue:'x') = (self value:#hash drawValue:'y')
    "
!

hash
    "equal, if they have the same realObject"

    ^ value hash
! !

!DrawAdaptor methodsFor:'delegation drawing'!

ascentOn:aGc
    ^ drawValue ascentOn:aGc
!

displayOn:aGCOrStream
    (aGCOrStream isStream or:[aGCOrStream == Transcript]) ifTrue:[
        aGCOrStream
            nextPutAll:self className;
            nextPut:$(.
        value printOn:aGCOrStream.
        aGCOrStream nextPutAll:'->'.
        drawValue printOn:aGCOrStream.
        aGCOrStream nextPut:$).
    ] ifFalse:[
        drawValue displayOn:aGCOrStream x:0 y:0.
    ].
!

displayOn:aGc x:x y:y opaque:opaque
    "copied from object, but do the ascent handling here"

    drawValue displayOn:aGc x:x y:y opaque:opaque.
!

heightOn:aGC
    "return the height of the receiver, if it is to be displayed on aGC"

    ^ drawValue heightOn:aGC
!

printString
    "this hast to be redefined to allow access from ComboLists via pressing the first character key"

    ^ drawValue printString
!

widthFrom:startIndex to:endIndex on:aGC
    "return the width of the receiver, if it is to be displayed on aGC"

    ^ drawValue widthFrom:startIndex to:endIndex on:aGC
!

widthOn:aGc
    ^ drawValue widthOn:aGc
! !

!DrawAdaptor class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/DrawAdaptor.st,v 1.2 2008-07-22 18:49:37 stefan Exp $'
! !