LabelAndIcon.st
author Claus Gittinger <cg@exept.de>
Sun, 12 May 1996 21:14:52 +0200
changeset 175 44a363de85f5
parent 172 c30e1ff9f9dd
child 176 ad0996413af4
permissions -rw-r--r--
examples

"
 COPYRIGHT (c) 1996 by Claus Gittinger
              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.
"


ListEntry subclass:#LabelAndIcon
	instanceVariableNames:'icon gap string'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Support'
!

!LabelAndIcon class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 by Claus Gittinger
              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
"
    an icon and a string, side by side.
    Usable as list entries in a fileList.

    This is an example class - currently not used by the system.

    [author:]
        Claus Gittinger

    [see also:]
        ListEntry Text String Icon
        ListView SelectionInListView
"

!

examples
"
  in a listView:
                                                                        [exBegin]
    |top slv wrapper l fileImage dirImage|

    fileImage := Image 
                   width:16 
                   height:16
                   depth:1
                   fromArray:#[2r00000000 2r00000000
                               2r00000000 2r00000000
                               2r00011111 2r11100000
                               2r00010000 2r00100000
                               2r00010000 2r00011000
                               2r00010000 2r00001000
                               2r00010000 2r00001000
                               2r00010000 2r00001000
                               2r00010000 2r00001000
                               2r00010000 2r00001000
                               2r00010000 2r00001000
                               2r00010000 2r00001000
                               2r00010000 2r00001000
                               2r00011111 2r11111000
                               2r00000000 2r00000000
                               2r00000000 2r00000000].
    fileImage photometric:#whiteIs0.

    dirImage := Image 
                   width:16 
                   height:16
                   depth:1
                   fromArray:#[2r00000000 2r00000000
                               2r00000000 2r00000000
                               2r00000000 2r00000000
                               2r01111111 2r11110000
                               2r01000000 2r00001000
                               2r01000000 2r00000100
                               2r01000000 2r00000010
                               2r01000000 2r00000010
                               2r01000000 2r00000010
                               2r01000000 2r00000010
                               2r01000000 2r00000010
                               2r01000000 2r00000010
                               2r01111111 2r11111110
                               2r00000000 2r00000000
                               2r00000000 2r00000000
                               2r00000000 2r00000000].
    dirImage photometric:#whiteIs0.


    l := OrderedCollection new.
    Filename currentDirectory directoryContents do:[:s |
        s asFilename isDirectory ifTrue:[
            l add:(LabelAndIcon icon:dirImage string:s)
        ] ifFalse:[
            l add:(LabelAndIcon icon:fileImage string:s)
        ]
    ].

    slv := SelectionInListView new.
    slv list:l.
    wrapper := HVScrollableView forView:slv miniScrollerH:true.

    top := StandardSystemView extent:150@200.
    top add:wrapper in:(0.0@0.0 corner:1.0@1.0).
    top open.
                                                                        [exEnd]
  in a selectionInListView:
                                                                        [exBegin]
    |top slv wrapper l fileImage dirImage|

    dirImage := Image fromFile:'DirObj.xbm'.
    fileImage := Image fromFile:'FileObj.xbm'.


    l := OrderedCollection new.
    Filename currentDirectory directoryContents do:[:s |
        s asFilename isDirectory ifTrue:[
            l add:(LabelAndIcon icon:dirImage string:s)
        ] ifFalse:[
            l add:(LabelAndIcon icon:fileImage string:s)
        ]
    ].

    slv := SelectionInListView new.
    slv list:l.
    wrapper := HVScrollableView forView:slv miniScrollerH:true.

    top := StandardSystemView extent:150@200.
    top add:wrapper in:(0.0@0.0 corner:1.0@1.0).
    top open.
                                                                        [exEnd]
  in a menu:
                                                                        [exBegin]
    |top l fileImage dirImage|

    dirImage := Image fromFile:'DirObj.xbm'.
    fileImage := Image fromFile:'FileObj.xbm'.


    l := OrderedCollection new.
    l add:(LabelAndIcon icon:dirImage string:'create directory').
    l add:(LabelAndIcon icon:fileImage string:'create file').

    top := View new.

    top middleButtonMenu:(PopUpMenu labels:l
                        selectors:#(foo bar)).

    top open.
                                                                        [exEnd]
"
! !

!LabelAndIcon class methodsFor:'instance creation'!

icon:anIcon string:aString
    ^ self new icon:anIcon string:aString

    "Created: 12.5.1996 / 20:00:58 / cg"
!

new
    ^ self basicNew initialize

    "Created: 12.5.1996 / 20:00:58 / cg"
! !

!LabelAndIcon methodsFor:'accessing'!

gap:pixels
    "set the spacing between the icon and the labelString.
     The default is 4."

    gap := pixels.

    "Created: 12.5.1996 / 20:00:52 / cg"
!

icon:anIcon
    "set the icon image"

    icon := anIcon.

    "Created: 12.5.1996 / 20:00:52 / cg"
!

icon:anIcon string:aString
    "set both iconImage and the labelString"

    icon := anIcon.
    string := aString

    "Created: 12.5.1996 / 20:00:52 / cg"
!

string
    ^ string
! !

!LabelAndIcon methodsFor:'displaying'!

displayOn:aGC x:x y:y opaque:opaque
    "display the receiver on a GC"

    |yOffs|

    icon displayOn:aGC
        x:x 
        y:y-aGC font ascent+(aGC font descent//2).
        
    (icon height > aGC font height) ifTrue:[
        yOffs := (icon height - aGC font height) // 2
    ] ifFalse:[
        yOffs := 0
    ].
    string 
        displayOn:aGC 
        x:x + icon width + gap
        y:y+yOffs.

    "Modified: 12.5.1996 / 20:36:43 / cg"
! !

!LabelAndIcon methodsFor:'initialization'!

initialize
    gap := 4
! !

!LabelAndIcon methodsFor:'queries'!

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

    ^ icon height + (aGC device pixelPerMillimeter x rounded) 
      max:(string heightOn:aGC)

    "Created: 12.5.1996 / 20:26:20 / cg"
    "Modified: 12.5.1996 / 20:34:23 / cg"
!

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

    ^ icon width + gap + (string widthOn:aGC)

    "Created: 12.5.1996 / 20:10:06 / cg"
    "Modified: 12.5.1996 / 20:13:49 / cg"
! !

!LabelAndIcon class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/LabelAndIcon.st,v 1.2 1996-05-12 19:14:52 cg Exp $'
! !