TabSpec.st
author claus
Mon, 21 Nov 1994 17:49:32 +0100
changeset 28 ca403f4c5b86
parent 25 e07adf47d209
child 36 160b8f0dfd7d
permissions -rw-r--r--
*** empty log message ***

'From Smalltalk/X, Version:2.10.3 on 12-aug-1994 at 10:44:09 pm'!

Object subclass:#TabulatorSpecification
	 instanceVariableNames:'tabUnit unitReference tabPositions tabTypes'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Support'
!

!TabulatorSpecification 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/Attic/TabSpec.st,v 1.3 1994-11-21 16:49:03 claus Exp $
"
!

documentation
"
    This is a helper class for table widgets and tabular data in
    lists.
    A tabulatorSpecification keeps track of where the tabs are,
    and how they align. They are to be used un conjunction with
    MultiColumnListEntry or the upcoming tableWidget.
"
!

examples 
"
    Example use (in a ListView):

	|listView tabSpec entry|

	listView := ListView new.

	tabSpec := TabulatorSpecification new.
	tabSpec unit:#inch.
	tabSpec positions:#(0     1     2.5    3.5    4       5        ).
	tabSpec align:    #(#left #left #right #right #center #decimal ).

	entry := MultiColListEntry new.
	entry tabulatorSpecification:tabSpec.
	entry colAt:1 put:'left';
	      colAt:2 put:'left';
	      colAt:3 put:'right';
	      colAt:4 put:'right';
	      colAt:5 put:'center';
	      colAt:6 put:'.decimal'.

	listView at:1 put:entry.

	entry := MultiColListEntry new.
	entry tabulatorSpecification:tabSpec.
	entry colAt:1 put:'col1';
	      colAt:2 put:'col2';
	      colAt:3 put:'col3';
	      colAt:4 put:'col4';
	      colAt:5 put:'col5';
	      colAt:6 put:'col6.decimal'.

	listView at:2 put:entry.

	entry := MultiColListEntry new.
	entry tabulatorSpecification:tabSpec.
	entry colAt:1 put:'foo';
	      colAt:2 put:'fooBar';
	      colAt:3 put:'bar';
	      colAt:4 put:'barFoo';
	      colAt:5 put:'baz';
	      colAt:6 put:'1234.56'.

	listView at:3 put:entry.
	listView open


    defining field positions in millimeter :

	|listView tabSpec entry|

	listView := ListView new.

	tabSpec := TabulatorSpecification new.
	tabSpec unit:#mm.
	tabSpec positions:#(0 10 20 40).
	tabSpec align:    #left.          

	entry := MultiColListEntry new.
	entry tabulatorSpecification:tabSpec.
	entry colAt:1 put:'1';
	      colAt:2 put:'2';
	      colAt:3 put:'3';
	      colAt:4 put:'4'.

	listView at:1 put:entry.

	entry := MultiColListEntry new.
	entry tabulatorSpecification:tabSpec.
	entry colAt:1 put:'aa';
	      colAt:2 put:'bb';
	      colAt:3 put:'cc';
	      colAt:4 put:'dd'.

	listView at:2 put:entry.

	listView open

    defining field widths in millimeter :

	|listView tabSpec entry|

	listView := ListView new.

	tabSpec := TabulatorSpecification new.
	tabSpec unit:#mm.
	tabSpec widths:#(10 10 20 10).
	tabSpec align:    #left.        

	entry := MultiColListEntry new.
	entry tabulatorSpecification:tabSpec.
	entry colAt:1 put:'1';
	      colAt:2 put:'2';
	      colAt:3 put:'3';
	      colAt:4 put:'4'.

	listView at:1 put:entry.

	entry := MultiColListEntry new.
	entry tabulatorSpecification:tabSpec.
	entry colAt:1 put:'aa';
	      colAt:2 put:'bb';
	      colAt:3 put:'cc';
	      colAt:4 put:'dd'.

	listView at:2 put:entry.

	listView open

    defining field widths in pixels :

	|listView tabSpec entry|

	listView := ListView new.

	tabSpec := TabulatorSpecification new.
	tabSpec unit:#pixel.
	tabSpec widths:#(50 30 30 50).
	tabSpec align:    #left.        

	entry := MultiColListEntry new.
	entry tabulatorSpecification:tabSpec.
	entry colAt:1 put:'1';
	      colAt:2 put:'2';
	      colAt:3 put:'3';
	      colAt:4 put:'4'.

	listView at:1 put:entry.

	entry := MultiColListEntry new.
	entry tabulatorSpecification:tabSpec.
	entry colAt:1 put:'aa';
	      colAt:2 put:'bb';
	      colAt:3 put:'cc';
	      colAt:4 put:'dd'.

	listView at:2 put:entry.

	listView open
"
! !

!TabulatorSpecification methodsFor:'queries'!

pixelsPerUnitOn:aGC
    "
     return the number of device pixels one unit of my tabs
     takes on aGC
    "
    tabUnit isNil ifTrue:[
	tabUnit := #col
    ].
    tabUnit == #relative ifTrue:[
	^ unitReference width
    ].
    tabUnit == #col ifTrue:[
	^ aGC font width
    ].
    tabUnit == #inch ifTrue:[
	^ aGC device horizontalPixelPerInch
    ].
    tabUnit == #mm ifTrue:[
	^ aGC device horizontalPixelPerMillimeter
    ].
    tabUnit == #cm ifTrue:[
	^ aGC device horizontalPixelPerMillimeter * 10
    ].
    "
     assume pixels
    "
    ^ 1.
!

typeOfTab:index
    "return the type of the tab at position index."

    tabPositions isNil ifTrue:[^ #left].
    tabTypes notNil ifTrue:[
	(tabTypes isMemberOf:Symbol) ifTrue:[
	    ^ tabTypes
	].
	^ tabTypes at:index.
    ].
    "default is left"
    ^ #left
!

positionOfTab:index on:aGC
    "return the position (in device units) of the tab at index"

    |unit pos|

    tabPositions isNil ifTrue:[^ nil].

    unit := self pixelsPerUnitOn:aGC.
    pos := ((tabPositions at:index) * unit).
    ^ pos
!

positionOfTab:index forString:aString on:aGC
    "return the position (in device units) of the string to be drawn
     at position index."

    |pos type idx left|

    pos := self positionOfTab:index on:aGC.
    pos isNil ifTrue:[^ nil].

    type := self typeOfTab:index.

    type == #right ifTrue:[
	^ pos - (aGC font widthOf:aString).
    ].
    type == #center ifTrue:[
	^ pos - ((aGC font widthOf:aString) // 2).
    ].
    type == #decimal ifTrue:[
	idx := aString indexOf:$..
	idx == 0 ifTrue:[
	     ^ pos - (aGC font widthOf:aString).
	].
	left := aString copyTo:(idx-1).
	^ pos - (aGC font widthOf:left).
    ].
    "default is left"
    ^ pos
! !

!TabulatorSpecification methodsFor:'accessing'!

size
    "return the number of tabs in this spec"

    ^ tabPositions size
!

unit:aSymbol
    "set the unit.
     allowed are: #inch, #mm, #cm, #pixel and #col"

    tabUnit := aSymbol
!

unitRelativeTo:someObject
    "set for a relative unit. someObject should return its width
     and the tabs are set fraction-relative to this number (in pixel)."

    tabUnit := #relative.
    unitReference := someObject
!

unit
    "return the unit"

    ^ tabUnit
!

align:types
    "
     an array of tab-types; each one is
	#left
	#right
	#center
	#decimal
     or a symbol which gives align of all tabs

    "
    tabTypes := types
!

align
    "return the align-vector"

    ^ tabTypes
!

widths
    "return a width-vector"

    |prev|

    prev := 0.
    ^ tabPositions collect:[:p | |w| w := p - prev. prev := p. w].

    "
     |spec|

     spec := TabulatorSpecification new.
     spec unit:#inch.
     spec positions:#(0     1     2.5    3.5    4       5        ).
     spec align:    #(#left #left #right #right #center #decimal ).
     spec widths
    "
!

widths:fieldWidths
    "set the position-vector from a vector of field widths"

    |pos|

    pos := 0.
    tabPositions := fieldWidths collect:[:w | 
					    |p|

					    p := pos.
					    pos := pos + w.
					    p].
!

positions:tabs
    "set the position-vector"

    tabPositions := tabs
!

positions
    "return the position-vector"

    ^ tabPositions
! !