DataSetColumn.st
changeset 1147 2d0b9fc2422c
parent 1133 619b0afc557a
child 1186 8da80b8ed338
equal deleted inserted replaced
1146:c15c713b9df6 1147:2d0b9fc2422c
    13 
    13 
    14 
    14 
    15 
    15 
    16 Object subclass:#DataSetColumn
    16 Object subclass:#DataSetColumn
    17 	instanceVariableNames:'columnNumber dataSet minWidth width description buttonExtent
    17 	instanceVariableNames:'columnNumber dataSet minWidth width description buttonExtent
    18 		drawableAction rendererType backgroundColor rowSeparatorSelector
    18 		drawableAction shownValue rendererType backgroundColor
    19 		showColSeparator showRowSeparator foregroundColor fgSelector
    19 		rowSeparatorSelector showColSeparator showRowSeparator
    20 		bgSelector columnAlignment label readSelector
    20 		foregroundColor fgSelector bgSelector columnAlignment label
    21 		numArgsToReadSelector columnAdaptor'
    21 		readSelector numArgsToReadSelector columnAdaptor'
    22 	classVariableNames:''
    22 	classVariableNames:''
    23 	poolDictionaries:''
    23 	poolDictionaries:''
    24 	category:'Views-DataSet'
    24 	category:'Views-DataSet'
    25 !
    25 !
    26 
    26 
   188 !
   188 !
   189 
   189 
   190 width
   190 width
   191     "returns the width in pixels
   191     "returns the width in pixels
   192     "
   192     "
   193     |end|
   193     |max w|
   194 
   194 
   195     width notNil ifTrue:[ ^ width ].                            "/ already computed
   195     width notNil ifTrue:[ ^ width ].                            "/ already computed
   196 
   196 
   197     (    (width := description width)    ~~ 0                   "/ fixed size
   197     (    (width := description width)    ~~ 0                   "/ fixed size
   198      or:[(width := description minWidth) ~~ 0]                  "/ start size
   198      or:[(width := description minWidth) ~~ 0]                  "/ start size
   199     ) ifFalse:[
   199     ) ifFalse:[
   200         self containsText ifTrue:[
   200         self containsText ifTrue:[
   201             "/ take maximum 10 entries to calculate the width;
   201             "/ take maximum 10 entries to calculate the width;
   202             "/ can be resized later if neccessary
   202             "/ can be resized later if neccessary
   203 
   203 
   204             end := 10 min:dataSet size.
   204             max := 10 min:dataSet size.
   205 
   205 
   206             1 to:end do:[:aRowNr||lbl|
   206             1 to:max do:[:i|
   207                 lbl := drawableAction value:(dataSet at:aRowNr).
   207                 w := self widthOfLabel:(shownValue value:(dataSet at:i)).
   208 
   208                 width := width max:w
   209                 (lbl respondsTo:#widthOn:) ifTrue:[
       
   210                     width := width max:(lbl widthOn:dataSet)
       
   211                 ] ifFalse:[
       
   212                     lbl notNil ifTrue:[
       
   213                         width := width max:(lbl displayString widthOn:dataSet)
       
   214                     ]
       
   215                 ]
       
   216             ].
   209             ].
   217             description editorType ~~ #None ifTrue:[
   210             description editorType ~~ #None ifTrue:[
   218                 width := width + (dataSet font widthOn:dataSet device)
   211                 width := width + (dataSet font widthOn:dataSet device)
   219             ].
   212             ].
   220         ].
   213         ].
   221         width := width + buttonExtent x.
   214         width := width + buttonExtent x.
   222 
   215         width := width max:(4 + (label preferredExtent x)).
   223         label notNil ifTrue:[
       
   224             width := width max:(4 + (label widthOn:dataSet))
       
   225         ]
       
   226     ].
   216     ].
   227     ^ width := minWidth := width + dataSet separatorSize + (2 * dataSet horizontalSpacing).
   217     ^ width := minWidth := width + dataSet separatorSize + (2 * dataSet horizontalSpacing).
   228 !
   218 !
   229 
   219 
   230 width:aWidth
   220 width:aWidth
   239     ].
   229     ].
   240 
   230 
   241 ! !
   231 ! !
   242 
   232 
   243 !DataSetColumn methodsFor:'drawing'!
   233 !DataSetColumn methodsFor:'drawing'!
       
   234 
       
   235 drawLabel:aLabel atX:xLeft y:yTop
       
   236     "redraw label
       
   237     "
       
   238     |x space|
       
   239 
       
   240     space := dataSet horizontalSpacing.
       
   241 
       
   242     columnAlignment == #left ifTrue:[
       
   243         x  := xLeft + space.
       
   244     ] ifFalse:[
       
   245         x := width - (aLabel widthOn:dataSet).
       
   246 
       
   247         columnAlignment == #right ifTrue:[x := x - space]
       
   248                                  ifFalse:[x := x // 2].
       
   249         x := (xLeft + x) max:0.
       
   250     ].
       
   251     aLabel isImageOrForm ifTrue:[
       
   252         aLabel displayOn:dataSet x:x y:yTop.
       
   253       ^ self
       
   254     ].
       
   255 
       
   256     aLabel displayOn:dataSet x:x y:(yTop + dataSet rowFontAscent)
       
   257 !
   244 
   258 
   245 drawLabelsAtX:xLeft y:yTop h:h from:start to:stop
   259 drawLabelsAtX:xLeft y:yTop h:h from:start to:stop
   246     "redraw labels from start to stop
   260     "redraw labels from start to stop
   247     "
   261     "
   248     |fg bg label row isSel
   262     |fg bg label row isSel
   249      y       "{ Class:SmallInteger }"
   263      y       "{ Class:SmallInteger }"
   250      yT      "{ Class:SmallInteger }"
   264      yT      "{ Class:SmallInteger }"
   251      x       "{ Class:SmallInteger }"
   265      x       "{ Class:SmallInteger }"
   252      hspace  "{ Class:SmallInteger }"
   266      hspace  "{ Class:SmallInteger }"
   253      ascent  "{ Class:SmallInteger }"
   267      ascent  "{ Class:SmallInteger }"
       
   268      lblHg   "{ Class:SmallInteger }"
   254     |
   269     |
   255     yT := yTop.
   270     yT := yTop.
   256     ascent := dataSet rowFontAscent.
   271     ascent := dataSet rowFontAscent.
   257     hspace := dataSet horizontalSpacing.
   272     hspace := dataSet horizontalSpacing.
   258 
   273 
   311                 x  := x + hspace.
   326                 x  := x + hspace.
   312             ] ifFalse:[
   327             ] ifFalse:[
   313                 label := nil
   328                 label := nil
   314             ]
   329             ]
   315         ] ifFalse:[
   330         ] ifFalse:[
   316             (label := drawableAction value:row) notNil ifTrue:[
   331             (isSel and:[dataSet hasOpenEditor]) ifTrue:[
   317                 columnAlignment == #left ifTrue:[
   332                 label := nil
   318                     x  := x + hspace.
   333             ]  ifFalse:[
   319                 ] ifFalse:[
   334                 label := shownValue value:row
   320                     x := width - (label widthOn:dataSet).
       
   321 
       
   322                     columnAlignment == #right ifTrue:[x := x - hspace]
       
   323                                              ifFalse:[x := x // 2].
       
   324                     x := (xLeft + x) max:0.
       
   325                 ]
       
   326             ]
   335             ]
   327         ].
   336         ].
   328         label notNil ifTrue:[
   337         label notNil ifTrue:[
   329             y := y + (h - (label heightOn:dataSet) // 2).
   338             lblHg := self heightOfLabel:label.
   330 
   339 
   331             label isImageOrForm ifFalse:[
   340             lblHg ~~ 0 ifTrue:[
   332                 y := y + ascent
   341                 y := y + (h - lblHg // 2).
   333             ].
   342                 dataSet paint:fg on:bg.
   334             dataSet paint:fg on:bg.
   343 
   335             label displayOn:dataSet x:x y:y
   344                 (label isSequenceable and:[label isString not]) ifFalse:[
       
   345                     self drawLabel:label atX:x y:y
       
   346                 ] ifTrue:[
       
   347                     label do:[:el|
       
   348                         el notNil ifTrue:[
       
   349                             self drawLabel:el atX:x y:y.
       
   350                             y := y + (el heightOn:dataSet).
       
   351                         ]
       
   352                     ]
       
   353                 ].
       
   354             ]
   336         ].
   355         ].
   337         yT := yT + h
   356         yT := yT + h
   338     ]
   357     ]
   339 
   358 
   340 
   359 
   417 
   436 
   418     showRowSeparator ifTrue:[
   437     showRowSeparator ifTrue:[
   419      "/ DRAW SEPARATORS AT TOP( LIGHT COLOR )
   438      "/ DRAW SEPARATORS AT TOP( LIGHT COLOR )
   420      "/ =====================================
   439      "/ =====================================
   421         yT := yTop.
   440         yT := yTop.
   422         xR := xR - 1.
       
   423 
   441 
   424         rowSeparatorSelector isNil ifTrue:[
   442         rowSeparatorSelector isNil ifTrue:[
   425             times timesRepeat:[
   443             times timesRepeat:[
   426                 dataSet displayLineFromX:xL y:yT toX:xR y:yT.
   444                 dataSet displayLineFromX:xL y:yT toX:xR y:yT.
   427                 yT := yT + h.
   445                 yT := yT + h.
   494 ! !
   512 ! !
   495 
   513 
   496 !DataSetColumn methodsFor:'editing'!
   514 !DataSetColumn methodsFor:'editing'!
   497 
   515 
   498 editorAt:aRowNr
   516 editorAt:aRowNr
   499     |val row|
   517     |val row index|
   500 
   518 
   501     row := (dataSet at:aRowNr).
   519     row := (dataSet at:aRowNr).
   502     val := self extractColFromRow:row.
   520     val := self extractColFromRow:row.
   503 
   521 
   504     val isText ifTrue:[val := val string].
   522     val isText ifTrue:[val := val string].
   505 
       
   506     ^ description editorOn:row value:val.
   523     ^ description editorOn:row value:val.
   507 ! !
   524 ! !
   508 
   525 
   509 !DataSetColumn methodsFor:'event handling'!
   526 !DataSetColumn methodsFor:'event handling'!
   510 
   527 
   547 
   564 
   548 ! !
   565 ! !
   549 
   566 
   550 !DataSetColumn methodsFor:'initialization'!
   567 !DataSetColumn methodsFor:'initialization'!
   551 
   568 
   552 on:aDSVColumnView description:aDescription columnNumber:aNumber
   569 on:aDSVColumnView description:aDescription columnNumber:aNumber label:aLabel
   553     "instance creation; set attributes dependent on the description
   570     "instance creation; set attributes dependent on the description
   554     "
   571     "
   555     |device selector format idx type oldFont newFont args|
   572     |device selector format idx type oldFont newFont args|
   556 
   573 
   557     columnNumber     := aNumber.
   574     columnNumber     := aNumber.
   558     dataSet          := aDSVColumnView.
   575     dataSet          := aDSVColumnView.
       
   576     label            := aLabel.
   559     description      := aDescription.
   577     description      := aDescription.
   560     rendererType     := description rendererType.
   578     rendererType     := description rendererType.
   561     width            := nil.
   579     width            := nil.
   562     device           := dataSet device.
   580     device           := dataSet device.
   563     drawableAction   := [:aRow| nil ].
   581     shownValue       := [:aRow| nil ].
   564     rowSeparatorSelector := description rowSeparatorSelector.
   582     rowSeparatorSelector := description rowSeparatorSelector.
   565     fgSelector       := description foregroundSelector.
   583     fgSelector       := description foregroundSelector.
   566     bgSelector       := description backgroundSelector.
   584     bgSelector       := description backgroundSelector.
   567     showColSeparator := description showColSeparator.
   585     showColSeparator := description showColSeparator.
   568     showRowSeparator := description showRowSeparator.
   586     showRowSeparator := description showRowSeparator.
   586         foregroundColor := dataSet foregroundColor
   604         foregroundColor := dataSet foregroundColor
   587     ] ifFalse:[
   605     ] ifFalse:[
   588         foregroundColor := foregroundColor on:dataSet device
   606         foregroundColor := foregroundColor on:dataSet device
   589     ].
   607     ].
   590 
   608 
   591     oldFont := nil.
       
   592     label   := self resolveLabelWithBuilder:(dataSet builder).
       
   593 
       
   594     (label respondsTo:#string) ifTrue:[
       
   595         "/
       
   596         "/ must set the font to accumulate the real extent of a string label
       
   597         "/
       
   598         (label isString and:[label isEmpty]) ifTrue:[
       
   599             label := nil
       
   600         ] ifFalse:[
       
   601             (newFont := description labelFont) notNil ifTrue:[
       
   602                 oldFont := dataSet font.
       
   603                 dataSet font:newFont.
       
   604             ]
       
   605         ]
       
   606     ].
       
   607 
       
   608     oldFont notNil ifTrue:[
       
   609         dataSet font:oldFont
       
   610     ].
       
   611 
       
   612     rendererType == #CheckToggle ifTrue:[
   609     rendererType == #CheckToggle ifTrue:[
   613         buttonExtent := dataSet checkToggleExtent.
   610         buttonExtent := dataSet checkToggleExtent.
   614       ^ self
   611       ^ self
   615     ].
   612     ].
   616 
   613 
   628     selector := description printSelector.
   625     selector := description printSelector.
   629 
   626 
   630     selector notNil ifTrue:[
   627     selector notNil ifTrue:[
   631         args := selector numArgs.
   628         args := selector numArgs.
   632         args == 0 ifTrue:[
   629         args == 0 ifTrue:[
   633             drawableAction := [:aRow| aRow perform:selector ]
   630             shownValue := [:aRow| aRow perform:selector ]
   634         ] ifFalse:[
   631         ] ifFalse:[
   635             args == 1 ifTrue:[
   632             args == 1 ifTrue:[
   636                 drawableAction := [:aRow| aRow perform:selector with:dataSet ]
   633                 shownValue := [:aRow| aRow perform:selector with:dataSet ]
   637             ] ifFalse:[
   634             ] ifFalse:[
   638                 drawableAction := [:aRow| aRow perform:selector with:dataSet with:columnNumber ]
   635                 shownValue := [:aRow| aRow perform:selector with:dataSet with:columnNumber ]
   639             ]
   636             ]
   640         ].
   637         ].
   641         ^ self
   638         ^ self
   642     ].
   639     ].
   643 
   640 
   649         (idx := format indexOf:$.) ~~ 0 ifTrue:[
   646         (idx := format indexOf:$.) ~~ 0 ifTrue:[
   650             idx := format size - idx
   647             idx := format size - idx
   651         ].
   648         ].
   652         format := '%0.', idx printString, 'f'.
   649         format := '%0.', idx printString, 'f'.
   653 
   650 
   654         drawableAction := [:aRow||n|
   651         shownValue := [:aRow||n|
   655             n := self extractColFromRow:aRow.
   652             n := self extractColFromRow:aRow.
   656             n isReal ifTrue:[n := n asFloat printfPrintString:format].
   653             n isReal ifTrue:[n := n asFloat printfPrintString:format].
   657             n
   654             n
   658         ]
   655         ]
   659     ] ifFalse:[         "/ default: no format string
   656     ] ifFalse:[         "/ default: no format string
   660         drawableAction := [:aRow| self extractColFromRow:aRow ]
   657         shownValue := [:aRow| self extractColFromRow:aRow ]
   661     ]
   658     ]
   662 
   659 
   663 
   660 
   664 !
       
   665 
       
   666 resolveLabelWithBuilder:aBuilder
       
   667     |label appl l2|
       
   668 
       
   669     aBuilder isNil ifTrue:[
       
   670         ^ description rawLabel        
       
   671     ].
       
   672 
       
   673     (label := description label) isString ifTrue:[
       
   674         description labelIsImage ifTrue:[
       
   675             aBuilder isEditing ifTrue:[
       
   676                 label := nil
       
   677             ] ifFalse:[
       
   678                 (label := aBuilder labelFor:(label asSymbol)) notNil ifTrue:[
       
   679                     ^ label
       
   680                 ]
       
   681             ].
       
   682             ^ description class defaultIcon
       
   683         ].
       
   684         description translateLabel == true ifTrue:[
       
   685             (appl := aBuilder application) notNil ifTrue:[
       
   686                 (l2 := appl resources string:label) notNil ifTrue:[^ l2]
       
   687             ]
       
   688         ]
       
   689     ].
       
   690     ^ label
       
   691 ! !
   661 ! !
   692 
   662 
   693 !DataSetColumn methodsFor:'private'!
   663 !DataSetColumn methodsFor:'private'!
   694 
   664 
   695 extractColFromRow:aRow
   665 extractColFromRow:aRow
   777         self containsText ifTrue:[
   747         self containsText ifTrue:[
   778             "/ search first none empty drawable object
   748             "/ search first none empty drawable object
   779             end := 10 min:dataSet size.
   749             end := 10 min:dataSet size.
   780 
   750 
   781             1 to:end do:[:aRowNr| |lbl|
   751             1 to:end do:[:aRowNr| |lbl|
   782                 lbl := drawableAction value:(dataSet at:aRowNr).
   752                 lbl  := shownValue value:(dataSet at:aRowNr).
   783 
   753                 hObj := self heightOfLabel:(shownValue value:(dataSet at:aRowNr)).
   784                 lbl notNil ifTrue:[
   754                 hMin := hMin max:hObj
   785                     (lbl respondsTo:#heightOn:) ifTrue:[
       
   786                         hObj := lbl heightOn:dataSet
       
   787                     ] ifFalse:[
       
   788                         hObj := lbl displayString heightOn:dataSet
       
   789                     ].
       
   790                     ^ hMin max:hObj
       
   791                 ]
       
   792             ]
   755             ]
   793         ]
   756         ]
   794     ].
   757     ].
   795     ^ hMin max:hObj.
   758     ^ hMin max:hObj.
       
   759 !
       
   760 
       
   761 heightOfLabel:aLabel
       
   762     "returns the height of the label
       
   763     "
       
   764     |h l|
       
   765 
       
   766     aLabel isNil ifTrue:[ ^ 0 ].
       
   767 
       
   768     (aLabel isSequenceable and:[aLabel isString not]) ifFalse:[
       
   769         (aLabel respondsTo:#heightOn:) ifTrue:[l := aLabel]
       
   770                                       ifFalse:[l := aLabel displayString].
       
   771         ^ l heightOn:dataSet
       
   772     ].
       
   773     h := 0.
       
   774 
       
   775     aLabel do:[:el|
       
   776         (el respondsTo:#heightOn:) ifTrue:[l := el]
       
   777                                   ifFalse:[l := el displayString].
       
   778         h := h + (el heightOn:dataSet)
       
   779     ].
       
   780     ^ h
       
   781 
       
   782 !
       
   783 
       
   784 heightOfLabelAt:aRowNr
       
   785     "returns the height of the label at a row in pixels
       
   786     "
       
   787     ^ self heightOfLabel:(shownValue value:(dataSet at:aRowNr)).
   796 !
   788 !
   797 
   789 
   798 showColSeparator
   790 showColSeparator
   799     "returns true if column separator is on
   791     "returns true if column separator is on
   800     "
   792     "
   803 
   795 
   804 showSelectionHighLighted
   796 showSelectionHighLighted
   805     "returns true if selection is highLighted
   797     "returns true if selection is highLighted
   806     "
   798     "
   807     ^ description showSelectionHighLighted ~~ false
   799     ^ description showSelectionHighLighted ~~ false
       
   800 !
       
   801 
       
   802 widthOfLabel:aLabel
       
   803     "returns the width of the label
       
   804     "
       
   805     |w l|
       
   806 
       
   807     aLabel isNil ifTrue:[ ^ 0 ].
       
   808 
       
   809     (aLabel isSequenceable and:[aLabel isString not]) ifFalse:[
       
   810         (aLabel respondsTo:#widthOn:) ifTrue:[l := aLabel]
       
   811                                      ifFalse:[l := aLabel displayString].
       
   812         ^ l widthOn:dataSet
       
   813     ].
       
   814     w := 0.
       
   815 
       
   816     aLabel do:[:el|
       
   817         (el respondsTo:#widthOn:) ifTrue:[l := el]
       
   818                                  ifFalse:[l := el displayString].
       
   819         w := w max:(el widthOn:dataSet)
       
   820     ].
       
   821     ^ w
   808 ! !
   822 ! !
   809 
   823 
   810 !DataSetColumn methodsFor:'searching'!
   824 !DataSetColumn methodsFor:'searching'!
   811 
   825 
   812 findRowNrStartingWithChar:aChar start:start stop:stop
   826 findRowNrStartingWithChar:aChar start:start stop:stop
   818 
   832 
   819     self containsText ifTrue:[
   833     self containsText ifTrue:[
   820         char  := aChar asLowercase.
   834         char  := aChar asLowercase.
   821 
   835 
   822         start to:stop do:[:aRowNr| |lbl|
   836         start to:stop do:[:aRowNr| |lbl|
   823             lbl := drawableAction value:(dataSet at:aRowNr).
   837             lbl := shownValue value:(dataSet at:aRowNr).
       
   838 
       
   839             (lbl isSequenceable and:[lbl isString not]) ifTrue:[
       
   840                 lbl := lbl at:1 ifAbsent:nil
       
   841             ].
   824 
   842 
   825             (lbl respondsTo:#string) ifTrue:[
   843             (lbl respondsTo:#string) ifTrue:[
   826                 lbl := lbl string.
   844                 lbl := lbl string.
   827                 (lbl size ~~ 0 and:[(lbl at:1) asLowercase == char]) ifTrue:[
   845                 (lbl size ~~ 0 and:[(lbl at:1) asLowercase == char]) ifTrue:[
   828                     ^ aRowNr
   846                     ^ aRowNr
   839 ! !
   857 ! !
   840 
   858 
   841 !DataSetColumn class methodsFor:'documentation'!
   859 !DataSetColumn class methodsFor:'documentation'!
   842 
   860 
   843 version
   861 version
   844     ^ '$Header: /cvs/stx/stx/libwidg2/DataSetColumn.st,v 1.36 1998-09-12 12:43:37 ca Exp $'
   862     ^ '$Header: /cvs/stx/stx/libwidg2/DataSetColumn.st,v 1.37 1998-09-25 15:01:16 cg Exp $'
   845 ! !
   863 ! !