MultiColListEntry.st
author claus
Wed, 17 May 1995 14:49:25 +0200
changeset 58 2bdd35f8aef0
parent 36 160b8f0dfd7d
child 62 378b60ba1200
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1994 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.
"

'From Smalltalk/X, Version:2.10.5 on 15-may-1995 at 9:15:44 am'!

ListEntry subclass:#MultiColListEntry
	 instanceVariableNames:'strings tabSpec'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Support'
!

!MultiColListEntry class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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.
"
!

version
"
$Header: /cvs/stx/stx/libwidg2/MultiColListEntry.st,v 1.5 1995-05-17 12:49:05 claus Exp $
"
!

documentation
"
    Instances of MultiColListEntry can be used in place of strings
    as entries of the list in a ListView or SelectionInListView.
    They allow data to be presented in table (or any other) form.
    See example here and in TabulatorSpecs documentation.
    Notice, that each entry can have its own tabulator specification;
    although, usually all share a single spec.
    Also, notice that each column may align different; making these
    perfect elements to present table data.

    MultiColListEntry and TabulatorSpec were originally created to
    support nice tabular display of file-lists in the FileBrowser;
    you may many other uses ...
"
!

examples
"
     putting multiColListEntries into a ListView
     (instead of strings)'
        
	|v e myList tabs|

	myList := OrderedCollection new.

	tabs := TabulatorSpecification new.
	tabs unit:#inch.
	tabs positions:#(0 3 4).
	tabs align:#(left #center #left).

	e := MultiColListEntry 
		 fromString:'left centered left'.
	e tabulatorSpecification:tabs.
	myList add:e.

	e := MultiColListEntry 
		 fromString:'| | |'.
	e tabulatorSpecification:tabs.
	myList add:e.
	myList add:''.

	e := MultiColListEntry 
		 fromString:'hello hallo salut'.
	e tabulatorSpecification:tabs.
	myList add:e.

	e := MultiColListEntry 
		 fromString:'good morning,guten Morgen,bon jour'
		 separatedBy:$,.
	e tabulatorSpecification:tabs.
	myList add:e.

	e := MultiColListEntry new.
	e colAt:1 put:'good bye'.
	e colAt:2 put:'auf Wiedersehen'.
	e colAt:3 put:'au revoir '.
	e tabulatorSpecification:tabs.
	myList add:e.

	v := ListView new.
	v setList:myList expandTabs:false.
	v extent:500@100.
	v open



     many multiColListEntries in a scrollable ListView

	|v l e myList tabs|

	myList := OrderedCollection new.

	tabs := TabulatorSpecification new.
	tabs unit:#cm.
	tabs positions:#(1 3 5).
	tabs align:#(#right #center #left).

	1 to:100 do:[:i|
	    e := MultiColListEntry new.
	    e colAt:1 put:i printString.
	    e colAt:2 put:i squared printString.
	    e colAt:3 put:i sqrt  printString.
	    e tabulatorSpecification:tabs.
	    myList add:e.
	].
	l := ListView new.
	l setList:myList expandTabs:false.
	v := ScrollableView forView:l.
	v extent:300@200.
	v open



     like above, but uses nicer decimal alignments

	|v l e myList tabs|

	myList := OrderedCollection new.
        
	tabs := TabulatorSpecification new.
	tabs unit:#cm.
	tabs positions:#(1 3 6 9 12).
	tabs align:#(#right #decimal #decimal #decimal #decimal).

	1 to:100 do:[:i|
	    e := MultiColListEntry new.
	    e colAt:1 put:i printString.
	    e colAt:2 put:i log printString.
	    e colAt:3 put:i sqrt  printString.
	    e colAt:4 put:i sin  printString.
	    e colAt:5 put:i cos  printString.
	    e tabulatorSpecification:tabs.
	    myList add:e.
	].
	l := ListView new.
	l setList:myList expandTabs:false.
	v := ScrollableView forView:l.
	v extent:600@200.
	v open



     specifying tabs in inches

	|v l e myList tabs|

	myList := OrderedCollection new.

	tabs := TabulatorSpecification new.
	tabs unit:#inch.
	tabs positions:#(0 2 3.5 4 6 8 10 12).

	e := MultiColListEntry new.
	e colAt:1 put:'2'.
	e colAt:2 put:'3.5'.
	e colAt:3 put:'4'.
	e colAt:4 put:'6'.
	e colAt:5 put:'8'.
	e colAt:6 put:'10'.
	e colAt:7 put:'12'.
	e tabulatorSpecification:tabs.
	myList add:e.

	myList add:((MultiColListEntry fromString:'| | | | | | |')
			 tabulatorSpecification:tabs).
	myList add:((MultiColListEntry fromString:'xxx xxx xxx xxx xxx xxx xxx')
			 tabulatorSpecification:tabs).

	l := ListView new.
	l setList:myList expandTabs:false.
	v := HVScrollableView forView:l.
	v extent:600@200.
	v open


     if you have the columns available as a collection, 
     setup can be done easier

	|v l e myList tabs|

	myList := OrderedCollection new.

	tabs := TabulatorSpecification new.
	tabs unit:#inch.
	tabs positions:#(0 2 3.5 4 6 8 10 12).

	e := MultiColListEntry new.
	e strings:#('2' '3.5' '4' '6' '8' '10' '12').
	e tabulatorSpecification:tabs.
	myList add:e.

	l := ListView new.
	l setList:myList expandTabs:false.
	v := HVScrollableView forView:l.
	v extent:600@200.
	v open


    concrete example, show /etc/passwd in a table:
        
	|v l s myList line e htabs tabs fingerEntry|

	tabs := TabulatorSpecification new.
	tabs unit:#inch.
	tabs positions:#(0    2      3.5  4.5   5    8    11).
	tabs align:    #(left left right right left left left).

	htabs := TabulatorSpecification new.
	htabs unit:#inch.
	htabs positions:#(0    2      3.5      4.5    5    8    11).
	htabs align:    #(left center center center left left left).

	myList := OrderedCollection new.

	e := MultiColListEntry 
		    fromString:'login-name:password:uid:gid:finger-entry:home-dir:shell' 
		    separatedBy:$:.
	e tabulatorSpecification:htabs.
	myList add:e.
	myList add:''.

	s := '/etc/passwd' asFilename readStream.
	[s atEnd] whileFalse:[
	    line := s nextLine.
	    e := MultiColListEntry 
			fromString:line
			separatedBy:$:.
	    fingerEntry := e colAt:5.
	    e colAt:5 put:(fingerEntry asCollectionOfSubstringsSeparatedBy:$,) first.
	    e tabulatorSpecification:tabs.
	    myList add:e.
	].
	s close.
        
	l := ListView new.
	l setList:myList expandTabs:false.
	v := HVScrollableView forView:l.
	v extent:600@200.
	v open
"
! !

!MultiColListEntry class methodsFor:'instance creation'!

fromString:aString
    ^ self fromString:aString separatedBy:Character space
!

fromString:aString separatedBy:separatorCharacter
     |subStrings e|

    e := self new.
    subStrings := aString asCollectionOfSubstringsSeparatedBy:separatorCharacter.
    subStrings keysAndValuesDo:[:i :sub |
	e colAt:i put:sub.
    ].
    ^ e
! !

!MultiColListEntry methodsFor:'drawing'!

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

    |xPos subString tabPos w prevString|

    xPos := x.
    prevString := ''.
    strings keysAndValuesDo:[:index :subString |
	subString notNil ifTrue:[
	    "
	     find next tab
	    "
	    tabPos := tabSpec positionOfTab:index forString:subString on:aGC.
	    tabPos isNil ifTrue:[
		"
		 no tab - just continue where we are ...
		"
		xPos := xPos + (aGC font widthOf:prevString).
	    ] ifFalse:[
		xPos := tabPos + x.
	    ].
	    aGC displayString:subString x:xPos y:y.
	    prevString := subString.
	]
    ].
! !

!MultiColListEntry methodsFor:'accessing'!

colAt:index put:aString
    "replace the substring at column index"

    strings isNil ifTrue:[
	strings := OrderedCollection new:index
    ].
    index > strings size ifTrue:[strings grow:index].
    strings at:index put:aString
!

tabulatorSpecification:aTabSpec
    "set the tabulator spec"

    tabSpec := aTabSpec
!

strings:aCollectionOfStrings
    "replace all substrings"

    strings := OrderedCollection withAll:aCollectionOfStrings. 
!

colAt:index
    "return the substring at column index"

    index > strings size ifTrue:[^ nil].
    ^ strings at:index
! !

!MultiColListEntry methodsFor:'queries'!

widthIn:aGC
    "return the width of the receiver when displayed in aGC"

    |xPos xMax subString tabPos w prevLen|

    "just to make certain:
     do not assume, that the last col is the rightmost one ...
    "
    xPos := 0.
    xMax := 0.
    prevLen := 0.
    strings keysAndValuesDo:[:index :subString |
	subString notNil ifTrue:[
	    "
	     find next tab
	    "
	    tabPos := tabSpec positionOfTab:index forString:subString on:aGC.
	    tabPos isNil ifTrue:[
		"
		 no tab - just continue where we are ...
		"
		xPos := xPos + prevLen.
	    ] ifFalse:[
		xPos := tabPos.
	    ].
	    w := prevLen := aGC font widthOf:subString.
	    xMax := xMax max:(xPos + w).
	]
    ].
    ^ xMax
! !

!MultiColListEntry methodsFor:'converting'!

asString
    "return the receiver as a string with embedded tabs"

    |s sub tab 
     nSub "{ Class: SmallInteger }"|

    s := ''.
    tab := Character tab asString.
    nSub := strings size.
    1 to:nSub do:[:subStringIndex |
	sub := strings at:subStringIndex.
	sub notNil ifTrue:[
	    s := s , sub.
	].
	subStringIndex == strings size ifFalse:[
	    s := s , tab
	]
    ].

    ^ s
! !