I hope this one runs
authortz
Sat, 17 Jan 1998 16:02:05 +0100
changeset 419 34cc530118c6
parent 418 f47e99ae91bc
child 420 7fd01e47c912
I hope this one runs
DataSetBuilder.st
--- a/DataSetBuilder.st	Sat Jan 17 13:43:56 1998 +0100
+++ b/DataSetBuilder.st	Sat Jan 17 16:02:05 1998 +0100
@@ -815,76 +815,76 @@
   ^ super helpSpec addPairsFrom:#(
 
 #backgroundColor
-'set the background color of the column if the color-checkBox is turned on. Otherwise, the column uses its default background color (which is specified in the styleSheet).'
+'Sets the background color of the column if the color-checkBox is turned on. Otherwise, the column uses its default background color (which is specified in the styleSheet).'
 
 #backgroundSelector
-'selector which returns the background color for a cell (optional). If the selector is nil or returns nil, the default background color is set.'
+'Selector which returns the background color for a cell (optional). If the selector is nil or returns nil, the default background color is set.'
 
 #canSelect
-'if true, each cell in the column can be selected. In case of having a menu, the menu can be opened by selecting the cell and pressing down the right or middle button of the mouse. if false, the whole line is selected. The menu opened derives from the DataSetView, which is specified in the window specification (Basics).'
+'If true, each cell in the column can be selected. In case of having a menu, the menu can be opened by selecting the cell and pressing down the right or middle button of the mouse. if false, the whole line is selected. The menu opened derives from the DataSetView, which is specified in the window specification (Basics).'
 
 #choices
-'selector to get the collection of choices for a column which is selectable and its editor is kind of a ComboBox or ComboList. If a cell in the column is selected, the visual editor is opened and in case of having choices, the choices are assigned to the widget.'
+'Selector to get the collection of choices for a column which is selectable and its editor is kind of a ComboBox or ComboList. If a cell in the column is selected, the visual editor is opened and in case of having choices, the choices are assigned to the widget.'
+
+#doubleClickedSelector
+'Selector evaluated without arguments on selected column.'
 
 #editorField
-'type of visual editor (using default editors) or a selector, which will return an visual editor. If the cell is selected, a visual editor is opened in in the cell. In case of an unsupported selector (user defined editor), the row object is asked for the visual editor by performing the selector on the row. A widget instance must be returned which is opened in the cell.'
-
-#doubleClickedSelector
-'selector evaluated without arguments on selected column'
+'Type of visual editor (using default editors) or a selector, which will return an visual editor. If the cell is selected, a visual editor is opened in in the cell. In case of an unsupported selector (user defined editor), the row object is asked for the visual editor by performing the selector on the row. A widget instance must be returned which is opened in the cell.'
 
 #foregroundColor
-'set the foreground color of the column  if the color-checkBox is turned on. Otherwise, the column uses its default foreground color (which is specified in the styleSheet).'
+'Sets the foreground color of the column  if the color-checkBox is turned on. Otherwise, the column uses its default foreground color (which is specified in the styleSheet).'
 
 #foregroundSelector
-'selector which returns the foreground color for a cell (optional). If the selector is nil or returns nil, the default foreground color is set.'
+'Selector which returns the foreground color for a cell (optional). If the selector is nil or returns nil, the default foreground color is set.'
 
 #formatString
-'format string, which specifies the output format of a text in a cell. \ At the moment only numbers are supported. \ \ for example: 0.0000'
+'Format string, which specifies the output format of a text in a cell. At the moment  only numbers are supported  (for example: 0.0000).'
 
 #height
-'preferred height (optional)'
+'Preferred height (optional).'
 
 #label
-'the label of the column. If ''label is image'' is off, this is the label string. Otherwise, it specifies the applications selector, which returns the label - either a string or a bitmap image.'
+'The label of the column. If ''label is image'' is off, this is the label string. Otherwise, it specifies the applications selector, which returns the label - either a string or a bitmap image.'
 
 #labelIsImage
-'if ''label is image'' is off (the default), the columns label is the string as entered in the label aspect. Otherwise, its the name of the message sent to the application - this should return a string or bitmap image, which is used as logo in the column.'
+'If ''label is image'' is off (the default), the columns label is the string as entered in the label aspect. Otherwise, its the name of the message sent to the application - this should return a string or bitmap image, which is used as logo in the column.'
 
 #menuSelector
-'a selector to access the middleButton menu or nil. If a cell is selected. The menu will be opened by selecting the cell and pressing down the right or middle button of the mouse.'
+'A selector to access the middleButton menu or nil. If a cell is selected. The menu will be opened by selecting the cell and pressing down the right or middle button of the mouse.'
 
 #minWidth
-'makes sense if the width is set to 0 or nil. This is the minimum size required; no computation dependent on the contents. When resizing the view the column may grow or shrink to the minimum width.'
+'Makes sense if the width is set to 0 or nil. This is the minimum size required; no computation dependent on the contents. When resizing the view the column may grow or shrink to the minimum width.'
 
 #printSelector
-'a selector with one argument, the DataSetView. Used to access a drawable display object. In case of nil, the value derived from the readSelector is shown in the unselected cell.\ \ Using bitmaps, the DataSetView offers three important methods:\ \ #registerImage:anImage key:aSymbol\ register an image with an unique symbol. This symbol can be used by the row object to access the image, using #registeredImageAt:. The image will be associated to the device.\ \ #registeredImageAt:aSymbol\ returns an image assigned to the symbol or nil. The image returned is associated to the device.\ \ #releaseAllRegisteredImages\ relaese all registered images'
+'A selector with one argument, the DataSetView. Used to access a drawable display object. In case of nil, the value derived from the readSelector is shown in the unselected cell.\ \ Using bitmaps, the DataSetView offers three important methods:\ \ #registerImage:anImage key:aSymbol\ register an image with an unique symbol. This symbol can be used by the row object to access the image, using #registeredImageAt:. The image will be associated to the device.\ \ #registeredImageAt:aSymbol\ returns an image assigned to the symbol or nil. The image returned is associated to the device.\ \ #releaseAllRegisteredImages\ relaese all registered images.'
 
 #readSelector
-'a selector, which is used to get or set (if the write selector is undefined) the value of a cell. The value returned by the method can be a string object or a bitmap. The set operation only is performed if the column is selectable.'
+'A selector, which is used to get or set (if the write selector is undefined) the value of a cell. The value returned by the method can be a string object or a bitmap. The set operation only is performed if the column is selectable.'
 
 #rendererType
 'This type specifies, how the text of an unselected cell should be shown. As Text, CheckToggle, ComboBox, ComboList or as a RowSelector.'
 
 #selectSelector
-'an optional selector, which is used to test whether the cell in the column is selectable; the ''Is Selectable'' flag must be enabled.'
+'An optional selector, which is used to test whether the cell in the column is selectable; the ''Is Selectable'' flag must be enabled.'
 
 #showColumnSeparator
-'show or hide the column separator (right vertical separator).'
+'Shows or hide the column separator (right vertical separator).'
 
 #showRowSeparator
-'show or hide the row separator (bottom horizontal separator)'
+'Shows or hide the row separator (bottom horizontal separator).'
 
 #size
-'max size of an InputField, ComboBox or ComboList. 0 or nil means unlimited.'
+'Max size of an InputField, ComboBox or ComboList. 0 or nil means unlimited.'
 
 #type
-'a type converter symbol used by the input field'
+'A type converter symbol used by the input field.'
 
 #width
-'the width of a fixed column; in case of nil or 0 the column width will be computed dependent on the contents.'
+'The width of a fixed column; in case of nil or 0 the column width will be computed dependent on the contents.'
 
 #writeSelector
-'a selector, which is used to set the value of a cell. If the selector is not defined, the selector derives from the printSelector.'
+'A selector, which is used to set the value of a cell. If the selector is not defined, the selector derives from the printSelector.'
 
 )
 ! !
@@ -1019,11 +1019,11 @@
           #'window:' 
            #(#WindowSpec
               #'name:' 'Data Set Builder'
-              #'layout:' #(#LayoutFrame 277 0 356 0 763 0 715 0)
+              #'layout:' #(#LayoutFrame 246 0 169 0 732 0 528 0)
               #'label:' 'Data Set Builder'
               #'min:' #(#Point 10 10)
               #'max:' #(#Point 1152 900)
-              #'bounds:' #(#Rectangle 277 356 764 716)
+              #'bounds:' #(#Rectangle 246 169 733 529)
               #'menu:' #menu
               #'usePreferredExtent:' false
           )
@@ -1033,12 +1033,12 @@
                #(
                  #(#MenuPanelSpec
                     #'name:' 'menuToolbarView'
-                    #'layout:' #(#LayoutFrame 0 0.0 0 0.0 0 1.0 34 0)
+                    #'layout:' #(#LayoutFrame 0 0.0 0 0.0 0 1.0 32 0)
                     #'menu:' #menuToolbar
                 )
                  #(#VariableHorizontalPanelSpec
                     #'name:' 'VariablePanel'
-                    #'layout:' #(#LayoutFrame 0 0.0 36 0.0 0 1.0 -22 1.0)
+                    #'layout:' #(#LayoutFrame 0 0.0 34 0.0 0 1.0 -22 1.0)
                     #'component:' 
                      #(#SpecCollection
                         #'collection:' 
@@ -1243,6 +1243,7 @@
              #(#MenuItem
                 #'label:' 'Create Column'
                 #'value:' #doCreateColumn
+                #'enabled:' #columnIsNotEditing
                 #'labelImage:' #(#ResourceRetriever nil #newColumnIcon 'Create Column')
             )
              #(#MenuItem
@@ -1289,6 +1290,7 @@
                 #'label:' 'Create Column'
                 #'isButton:' true
                 #'value:' #doCreateColumn
+                #'enabled:' #columnIsNotEditing
                 #'labelImage:' #(#ResourceRetriever nil #newColumnIcon)
             )
              #(#MenuItem
@@ -1321,19 +1323,19 @@
     "ImageEditor openOnClass:self andSelector:#newColumnIcon"
 
     <resource: #image>
-    ^(Depth4Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(#[17 17 16 0 0 0 0 0 0 17 17 17 17 16 17 17 17 17 17 32 17 17 17 17 16 18 34 34 34 34 48 17 17 17 17 16 18 32 2 32 34 48 17 17 17 17 16 18 2 34 2 2 48 17 17 17 17 16 18 2 34 2 2 48 17 17 17 17 16 18 32 2 32 34 48 17 17 16 17 16 18 34 34 34 34 48 17 17 17 17 16 18 2 34 2 2 48 17 17 17 17 16 18 2 34 2 2 48 17 17 17 17 16 18 2 34 2 2 48 17 17 17 17 16 18 0 2 0 2 48 17 17 17 17 16 18 34 34 34 34 48 17 17 17 17 16 18 34 34 34 34 48 17 17 17 17 16 18 2 2 2 2 48 17 17 17 17 16 18 0 2 0 2 48 17 17 17 17 16 18 2 2 0 2 48 17 17 17 17 16 18 2 2 2 2 48 17 17 17 17 16 18 34 34 34 34 48 17 17 17 17 16 18 34 34 34 34 48 17 17 17 17 16 35 51 51 51 51 48 17 17 17 17 16 0 0 0 0 0 0 17 17]) ; colorMap:((OrderedCollection new add:(Color black); add:(Color white); add:(Color grey:66.9978); add:(Color grey:49.9962); add:(Color red:100.0 green:0.0 blue:0.0); add:(Color red:0.0 green:100.0 blue:0.0); add:(Color red:0.0 green:0.0 blue:100.0); add:(Color red:0.0 green:100.0 blue:100.0); add:(Color red:100.0 green:100.0 blue:0.0); add:(Color red:100.0 green:0.0 blue:100.0); add:(Color red:49.9992 green:0.0 blue:0.0); add:(Color red:0.0 green:49.9992 blue:0.0); add:(Color red:0.0 green:0.0 blue:49.9992); add:(Color red:0.0 green:49.9992 blue:49.9992); add:(Color red:49.9992 green:49.9992 blue:0.0); add:(Color red:49.9992 green:0.0 blue:49.9992); yourself)); mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(#[7 255 192 7 255 192 7 255 192 7 255 192 7 255 192 7 255 192 7 255 192 7 255 192 7 255 195 7 255 192 7 255 192 7 255 192 7 255 192 7 255 195 7 255 193 7 255 192 7 255 195 7 255 192 7 255 195 7 255 192 7 255 192 7 255 193]) ; yourself); yourself! !
+    ^(Depth2Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(#[85 64 0 0 5 80 85 69 85 85 133 80 85 70 170 170 197 80 85 70 130 138 197 80 85 70 42 34 197 89 85 70 42 34 197 80 85 70 130 138 197 80 69 70 170 170 197 80 85 70 42 34 197 80 85 70 42 34 197 80 85 70 42 34 197 80 85 70 2 2 197 80 85 70 170 170 197 80 85 70 170 170 197 80 85 70 34 34 197 89 85 70 2 2 197 80 85 70 34 2 197 80 85 70 34 34 197 80 85 70 170 170 197 80 85 70 170 170 197 80 85 75 255 255 197 80 85 64 0 0 5 80]) ; colorMap:(((Array new:4) at:1 put:((Color black)); at:2 put:((Color white)); at:3 put:((Color grey:66.9978)); at:4 put:((Color grey:49.9962)); yourself)); mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(#[7 255 192 7 255 192 7 255 192 7 255 192 7 255 192 7 255 192 7 255 192 7 255 192 7 255 195 7 255 192 7 255 192 7 255 192 7 255 192 7 255 195 7 255 193 7 255 192 7 255 195 7 255 192 7 255 195 7 255 192 7 255 192 7 255 193]) ; yourself); yourself! !
 
 !DataSetBuilder methodsFor:'accessing'!
 
 columns
-    "returns list of columns
-    "
-    ^ columns
+    "returns list of columns"
+
+    ^columns
 !
 
 columns:aListOfColumns fromView:aColumnView
-    "setup columns from a column view
-    "
+    "setup columns from a column view"
+
     |list|
 
     columnView := aColumnView.
@@ -1343,375 +1345,83 @@
 
     list removeAll.
 
-    aListOfColumns size ~~ 0 ifTrue:[
-        aListOfColumns do:[:aCol|
-            columns add:(aCol copy).
-            aCol rendererType == #rowSelector ifFalse:[list add:(aCol label)]
-                                               ifTrue:[list add:'Row Selector'].
+    aListOfColumns size ~~ 0 
+    ifTrue:
+    [
+        aListOfColumns do:
+        [:aColumn|
+            columns add: aColumn copy.
+            aColumn rendererType == #rowSelector 
+                ifFalse:[list add: aColumn label]
+                ifTrue: [list add:'Row Selector']
         ]
-    ].
+    ]
 !
 
 rowClassName
-    ^ (Smalltalk resolveName:className inClass:self class) notNil ifTrue:[className] ifFalse:[nil]
+
+    ^(Smalltalk resolveName:className inClass:self class) notNil ifTrue:[className] ifFalse:[nil]
 !
 
 rowClassName:aClassName
+
     |cls|
 
     superclassName := nil.
 
-    (className := aClassName) notNil ifTrue:[
-        (cls := self resolveClassNamed) notNil ifTrue:[
-            superclassName := cls superclass name asString.
-        ] ifFalse:[
-            superclassName := 'Object'
-        ]
+    (className := aClassName) notNil 
+    ifTrue:
+    [
+        (cls := self resolveClassNamed) notNil 
+            ifTrue: [superclassName := cls superclass name asString] 
+            ifFalse:[superclassName := 'Object']
     ]
 
 ! !
 
-!DataSetBuilder methodsFor:'accessing menu'!
+!DataSetBuilder methodsFor:'aspects'!
 
-columnMenu
-    "this window spec was automatically generated by the UI Builder"
+aspectFor:aKey
+    "returns aspect for a key or nil"
 
-    ^ self class columnMenu
+    ^aspects at:aKey ifAbsent:[super aspectFor:aKey]
 
 
 !
 
-doBrowseClass
-    |cls|
+columnIsNotEditing
+    "returns a boolean value holder which is set to true if column is not editing"
 
-    (cls := self resolveClassNamed) notNil ifTrue:[
-        SystemBrowser openInClass:cls
-    ] ifFalse:[
-        self information:'No class defined!!'
-    ]
+    ^builder valueAspectFor:#columnIsNotEditing initialValue: true
 
 
 
 !
 
-doCopyColumn
-    "copy selected column to the clipboard"
-
-    |idx|
-
-    (idx := selectedColumnIndex) ~~ 0 ifTrue:[
-        self clipboard: (columns at: idx) deepCopy.
-    ].
-!
-
-doCreateColumn
-    "create a new column after selected column or at left (nothing selected)
-    "
-    |label list|
-
-    list := self seqList.
-    label := 'Column ', list size printString.
-    columns add:(DataSetColumnSpec label:label selector:nil) afterIndex:selectedColumnIndex.
-    self seqList add:label afterIndex:selectedColumnIndex.
-    hasChanged := true.
-
-    self modified ifFalse:[
-        self selectedColumnModel value:(selectedColumnIndex + 1)
-    ].
-    self updateColumnView.
-
-!
-
-doCutColumn
-    "remove selected column and put it to the clipboard"
-
-    |idx|
-
-    (idx := selectedColumnIndex) ~~ 0 ifTrue:[
-        self selectedColumnModel value:0.
-        self clipboard: (columns at: idx).
-        columns removeIndex:idx.
-        self seqList removeIndex:idx.
-        self updateColumnView.
-        columns isEmpty ifTrue: [self isColumnSelected value: false].
-        hasChanged := true
-    ].
-!
-
-doDefineClass
-    "launch a dialog to define class and superclass
-    "
-    |aspects cls oldClass oldSuper|
-
-    aspects  := IdentityDictionary new.
-    oldClass := className.
-    oldSuper := superclassName.
-
-    [true] whileTrue:[
-        className notNil ifTrue:[
-            (cls := self resolveClassNamed) notNil ifTrue:[
-                superclassName := cls superclass name asString.
-            ].
-            aspects at:#classNameChannel put:className asValue
-        ] ifFalse:[
-            aspects at:#classNameChannel put:'DSVRow' asValue
-        ].
-
-        superclassName notNil ifTrue:[
-            aspects at:#superclassNameChannel put:superclassName asValue
-        ] ifFalse:[
-            aspects at:#superclassNameChannel put:'Object' asValue
-        ].
-
-        (self openDialogInterface:#defineClassNameSpec withBindings:aspects) ifFalse:[
-            className := oldClass.
-            superclassName := oldSuper.
-          ^ self
-        ].
-        className      := ((aspects at:#classNameChannel) value)      withoutSeparators.
-        superclassName := ((aspects at:#superclassNameChannel) value) withoutSeparators.
-
-        className size == 0 ifTrue:[
-            className := nil.
-            self information:'no valid className'.
-        ] ifFalse:[
-            cls := self resolveClassNamed.
-
-            cls notNil ifTrue:[
-                cls := cls superclass name asString
-            ].
-
-            superclassName size == 0 ifTrue:[        
-                cls notNil ifTrue:[
-                    superclassName := cls
-                ] ifFalse:[
-                    superclassName := 'Object'
-                ].
-                self information:( 'set superclassName' ).
-            ] ifFalse:[
-                (cls isNil or:[superclassName = cls]) ifTrue:[
-                    hasChanged := true.
-                    ^ self
-                ].
-                self information:('a global named ' , className , ' exists,\' ,
-                                  'but is not a subclass of ' , superclassName, '.\\' ,
-                                  'Check and try again if that is not what you want.') withCRs.
-
-                superclassName := cls.
-            ]
-        ]
-    ]
-!
-
-doGenerateCode
-    |cls superclass|
-
-    className isNil ifTrue:[
-        ^ self information:'No class defined!!'
-    ].
-    cls := self resolveClassNamed.
-
-    cls isNil ifTrue:[
-        superclass := Smalltalk resolveName:superclassName inClass:self class.
-
-        superclass isNil ifTrue:[
-            ^ self information:'no superclass defined'
-        ].
-        (self confirm:'create ' , className , ' ?') ifFalse:[
-            ^ self
-        ].
-        cls := superclass subclass:(className asSymbol)
-                     instanceVariableNames:''
-                     classVariableNames:''
-                     poolDictionaries:''
-                     category:'Applications'.
-    ].
-
-    self generateChoicesIn:cls.
-    self generateMenuIn:cls.
-    self generatePrintSelectorIn:cls.
-    self generateReadSelectorIn:cls.
-    self generateBackgroundSelectorIn:cls.
-    self generateForegroundSelectorIn:cls.
-    self generateSelectSelectorIn:cls.
-    self generateWriteSelectorIn:cls.
-    self generateDoubleClickSelectorIn:cls.
-!
-
-doMoveColumn:upOrDown
-    "move selected column up or down
-    "
-    |idx list label col size|
+editorTypeList
+    "generate list of supported editor types"
 
-    (idx := selectedColumnIndex) == 0 ifTrue:[
-        ^ self
-    ].
-    list := self seqList.
-    size := list size.
-
-    size == 1 ifTrue:[
-        ^ self
-    ].
-    hasChanged := true.
-    selectedColumnIndex := 0.
-    label := list at:idx.
-    col   := columns at:idx.
-    list    removeIndex:idx.
-    columns removeIndex:idx.
-
-    upOrDown == #up ifTrue:[
-        idx == 1 ifTrue:[idx := size]
-                ifFalse:[idx := idx - 1]
-    ] ifFalse:[
-        idx == size ifTrue:[idx := 1]
-                   ifFalse:[idx := idx + 1]
-    ].
-    columns add:col   beforeIndex:idx.
-    list    add:label beforeIndex:idx.
-    self selectedColumnModel value:idx.
-    self updateColumnView.
-!
-
-doPasteColumn
-    "paste clipboard copy column after selected column or at left (nothing selected)
-    "
-    |label list|
-
-    list := self seqList.
-    label := self class clipboard label.
-    columns add: self class clipboard deepCopy afterIndex:selectedColumnIndex.
-    self seqList add: label afterIndex:selectedColumnIndex.
-    hasChanged := true.
-
-    self modified ifFalse:[
-        self selectedColumnModel value:(selectedColumnIndex + 1)
-    ].
-    self updateColumnView.
-
-!
-
-mainMenu
-    "this window spec was automatically generated by the UI Builder"
-
-    ^ self class mainMenu
-
-
-!
-
-menu
-    "this window spec was automatically generated by the UI Builder"
-
-    ^ self class menu
-
-
-!
-
-menuEdit
-    "this window spec was automatically generated by the UI Builder"
-
-    ^ self class menuEdit
-
-
-!
-
-menuToolbar
-    "this window spec was automatically generated by the UI Builder"
-
-    ^ self class menuToolbar
-
-
-!
-
-subMenu
-    "this window spec was automatically generated by the UI Builder"
-
-    ^ self class subMenu
-
-
-! !
-
-!DataSetBuilder methodsFor:'actions'!
-
-accept
-    "accept changes made
-    "
-    |column type|
-
-    self modifiedChannel value == false ifTrue:[
-        ^ self
-    ].
-    isModified := true.
-
-    (column := self selectedColumn) isNil ifTrue:[
-        ^ self cancel
-    ].
-
-    type := (aspects at:#rendererType) value.
-
-    type == #rowSelector ifTrue:[
-        #( label width minWidth editorType choices readSelector writeSelector printSelector
-           formatString type size height canSelect selectSelector
-         ) do:[:aKey| (aspects at:aKey) value:nil ].
-    ].
-        
-    aspects keysAndValuesDo:[:aKey :aModel|
-        column perform:(aKey , ':') asSymbol with:(aModel value).
-    ].
-    self seqList at:selectedColumnIndex put:((aspects at:#label) value).
-    self updateColumnView.
-    self cancel
-!
-
-cancel
-    "remove all changes and reload selected column
-    "
-    |column|
-
-    isModified := true.
-    (column := self selectedColumn) isNil ifTrue:[
-        self tabModel value:0.
-    ] ifFalse:[
-        aspects keysAndValuesDo:[:aKey :aModel|
-            aModel value:(column perform:aKey)
-        ].
-        tabSelectionIndex == 0 ifTrue:[self tabModel value:1].
-    ].
-    self modifiedChannel value:false.
-    isModified := false.
-! !
-
-!DataSetBuilder methodsFor:'aspects'!
-
-aspectFor:aKey
-    "returns aspect for a key or nil
-    "
-  ^ aspects at:aKey ifAbsent:[ super aspectFor:aKey ]
-
-
-!
-
-editorTypeList
-    "generate list of supported editor types
-    "
     |list|
 
-    (list := builder bindingAt:#editorTypeList) isNil ifTrue:[
+    (list := builder bindingAt:#editorTypeList) isNil 
+    ifTrue:
+    [
         list := OrderedCollection new.
-        DataSetColumnSpec slices do:[:aSlice||type|
+        DataSetColumnSpec slices do:
+        [:aSlice||type|
             type := aSlice at:1.
-            (list includes:type) ifFalse:[list add:type].
+            (list includes:type) ifFalse:[list add:type]
         ].
-        builder aspectAt:#editorTypeList put:list.
-
+        builder aspectAt:#editorTypeList put:list
     ].
-    ^ list
+    ^list
 !
 
 isColumnSelected
     "returns a boolean value holder which is set to true if something is modified
-     and not accepted
-    "
-    ^ builder valueAspectFor:#isColumnSelected initialValue: false
+     and not accepted"
+
+    ^builder valueAspectFor:#isColumnSelected initialValue: false
 
 
 
@@ -1719,33 +1429,35 @@
 
 modifiedChannel
     "returns a boolean value holder which is set to true if something is modified
-     and not accepted
-    "
-    ^ builder booleanValueAspectFor:#modifiedChannel
+     and not accepted"
+
+    ^builder booleanValueAspectFor:#modifiedChannel
 
 
 
 !
 
 rendererTypeList
-    "generate list of supported renderer types
-    "
+    "generate list of supported renderer types"
+
     |list|
 
-    (list := builder bindingAt:#rendererTypeList) isNil ifTrue:[
+    (list := builder bindingAt:#rendererTypeList) isNil 
+    ifTrue:
+    [
         list := OrderedCollection new.
-        DataSetColumnSpec slices do:[:aSlice||type|
+        DataSetColumnSpec slices do:
+        [:aSlice||type|
             type := aSlice at:2.
-            (list includes:type) ifFalse:[list add:type].
+            (list includes:type) ifFalse:[list add:type]
         ].
-        builder aspectAt:#rendererTypeList put:list.
-
+        builder aspectAt:#rendererTypeList put:list
     ].
-    ^ list
+    ^list
 !
 
 selectedColumnModel
-    "automatically generated by UIPainter ..."
+    "returns a value holder which keeps selected column"
 
     |holder|
 
@@ -1757,7 +1469,6 @@
 !
 
 seqList
-    "automatically generated by UIPainter ..."
 
     |list|
 
@@ -1768,7 +1479,6 @@
 !
 
 specChannel
-    "automatically generated by UIPainter ..."
 
     |holder|
 
@@ -1779,19 +1489,19 @@
 !
 
 style
-    ^ self aspectFor:#labelFont
+
+    ^self aspectFor:#labelFont
 !
 
 tabList
-    "automatically generated by UIPainter ..."
 
-    ^ self class slices collect:[:aSlice| aSlice first ]
+    ^self class slices collect:[:aSlice|aSlice first]
 
 !
 
 tabModel
-    "returns a value holder which keeps the index of the current selected tab or 0
-    "
+    "returns a value holder which keeps the index of the current selected tab or 0"
+
     |holder|
 
     (holder := builder bindingAt:#tabModel) isNil ifTrue:[
@@ -1804,27 +1514,28 @@
 !DataSetBuilder methodsFor:'change & update'!
 
 update:something with:aParameter from:someObject
-    "one of my aspects has changed; update modified channel
-    " 
+    "one of my aspects has changed; update modified channel"
 
-    isModified ifFalse:[
+    isModified 
+    ifFalse:
+    [
         isModified := hasChanged := true.
-        self modifiedChannel value:true.
-        "self isNotModified   value:false. "
+        self modifiedChannel value: true.
+        self columnIsNotEditing value: false
     ]
 ! !
 
 !DataSetBuilder methodsFor:'code generation'!
 
 compile:aCode forClass:aClass inCategory:aCategory
-    "compile method for class in a category
-    "
+    "compile method for class in a category"
+
     ByteCodeCompiler compile:aCode withCRs forClass:aClass inCategory:aCategory
 !
 
 generateBackgroundSelectorIn:aClass
-    "generate code for #backgroundSelector
-    "
+    "generate code for #backgroundSelector"
+
     |sel catg code bCode|
 
     catg := 'accessing look' asSymbol.
@@ -1835,9 +1546,12 @@
             , '\'
             .
 
-    columns do:[:aCol|
-        ((sel := aCol backgroundSelector) notNil and:[(aClass implements:sel) not]) ifTrue:[
-            bCode := sel asString, code, '    ^ nil'.
+    columns do:
+    [:aColumn|
+        ((sel := aColumn backgroundSelector) notNil and:[(aClass implements:sel) not]) 
+        ifTrue:
+        [
+            bCode := sel asString, code, '    ^nil'.
             self compile:bCode forClass:aClass inCategory:catg
         ]
     ]
@@ -1846,8 +1560,8 @@
 !
 
 generateChoicesIn:aClass
-    "generate code for #choices
-    "
+    "generate code for #choices"
+
     |sel catg code|
 
     catg := 'accessing menu' asSymbol.
@@ -1856,23 +1570,25 @@
             , '\'
             , '    "get choices for visual editor; (a list of labels)\'
             , '\'
-            , '    ^ nil'
+            , '    ^nil'
             .
 
-    columns do:[:aColumn|
-        (     aColumn canSelect
-         and:[aColumn rendererType ~~ #rowSelector
-         and:[(sel := aColumn choices) notNil
-         and:[(aClass implements:sel) not]]]
-        ) ifTrue:[
+    columns do:
+    [:aColumn|
+        (aColumn canSelect
+        and:[aColumn rendererType ~~ #rowSelector
+        and:[(sel := aColumn choices) notNil
+        and:[(aClass implements:sel) not]]]) 
+        ifTrue:
+        [
             self compile:(sel asString, code) forClass:aClass inCategory:catg
         ]
     ]
 !
 
 generateDoubleClickSelectorIn:aClass
-    "generate code for #foregroundSelector
-    "
+    "generate code for #foregroundSelector"
+
     |sel catg code bCode|
 
     catg := 'accessing action' asSymbol.
@@ -1883,8 +1599,12 @@
             , '\'
             .
 
-    columns do:[:aCol|
-        ((sel := aCol doubleClickedSelector) notNil and:[(aClass implements:sel) not]) ifTrue:[
+    columns do:
+    [:aColumn|
+        ((sel := aColumn doubleClickedSelector) notNil 
+        and:[(aClass implements:sel) not]) 
+        ifTrue:
+        [
             bCode := sel asString, code.
             self compile:bCode forClass:aClass inCategory:catg
         ]
@@ -1906,9 +1626,13 @@
             , '\'
             .
 
-    columns do:[:aCol|
-        ((sel := aCol foregroundSelector) notNil and:[(aClass implements:sel) not]) ifTrue:[
-            bCode := sel asString, code, '    ^ nil'.
+    columns do:
+    [:aColumn|
+        ((sel := aColumn foregroundSelector) notNil 
+        and:[(aClass implements:sel) not]) 
+        ifTrue:
+        [
+            bCode := sel asString, code, '    ^nil'.
             self compile:bCode forClass:aClass inCategory:catg
         ]
     ]
@@ -1917,8 +1641,8 @@
 !
 
 generateMenuIn:aClass
-    "generate code for #menu
-    "
+    "generate code for #menu"
+
     |sel catg code|
 
     catg := 'accessing menu' asSymbol.
@@ -1927,22 +1651,24 @@
             , '\'
             , '    "get middleButton menu for selected cell in column"\'
             , '\'
-            , '    ^ nil'
+            , '    ^nil'
             .
 
-    columns do:[:aColumn|
-        (     aColumn canSelect
-         and:[(sel := aColumn menu) notNil
-         and:[(aClass implements:sel) not]]
-        ) ifTrue:[
+    columns do:
+    [:aColumn|
+        (aColumn canSelect
+        and:[(sel := aColumn menu) notNil
+        and:[(aClass implements:sel) not]]) 
+        ifTrue:
+        [
             self compile:(sel asString, code) forClass:aClass inCategory:catg
         ]
     ]
 !
 
 generatePrintSelectorIn:aClass
-    "generate code for #printSelector
-    "
+    "generate code for #printSelector"
+
     |sel catg code|
 
     catg := 'accessing' asSymbol.
@@ -1951,22 +1677,24 @@
             , '\'
             , '    "get drawable image or text on a gc"\'
             , '\'
-            , '    ^ nil'
+            , '    ^nil'
             .
 
-    columns do:[:aColumn|
-        (     aColumn rendererType ~~ #rowSelector
-         and:[(sel := aColumn printSelector) notNil
-         and:[(aClass implements:sel) not]]
-        ) ifTrue:[
+    columns do:
+    [:aColumn|
+        (aColumn rendererType ~~ #rowSelector
+        and:[(sel := aColumn printSelector) notNil
+        and:[(aClass implements:sel) not]]) 
+        ifTrue:
+        [
             self compile:(sel asString, code) forClass:aClass inCategory:catg
         ]
     ]
 !
 
 generateReadSelectorIn:aClass
-    "generate code for #readSelector
-    "
+    "generate code for #readSelector"
+
     |sel catg code bCode|
 
     catg := 'accessing' asSymbol.
@@ -1977,22 +1705,22 @@
             , '\'
             .
 
-    columns do:[:aColumn|
-        (     aColumn rendererType ~~ #rowSelector 
-         and:[(sel := aColumn readSelector) notNil
-         and:[(aClass implements:sel) not]]
-        ) ifTrue:[
-            (aColumn printSelector isNil or:[aColumn canSelect]) ifTrue:[
-                sel numArgs == 0 ifTrue:[
-                    bCode := sel asString, code
-                ] ifFalse:[
-                    bCode := sel asString, 'anIndex\', code
-                ].
-                aColumn rendererType == #CheckToggle ifFalse:[
-                    bCode := bCode, '    ^ nil'
-                ] ifTrue:[
-                    bCode := bCode, '    ^ true'
-                ]. 
+    columns do:
+    [:aColumn|
+        (aColumn rendererType ~~ #rowSelector 
+        and:[(sel := aColumn readSelector) notNil
+        and:[(aClass implements:sel) not]]) 
+        ifTrue:
+        [
+            (aColumn printSelector isNil or:[aColumn canSelect]) 
+            ifTrue:
+            [
+                sel numArgs == 0 
+                    ifTrue: [bCode := sel asString, code] 
+                    ifFalse:[bCode := sel asString, 'anIndex\', code].
+                aColumn rendererType == #CheckToggle 
+                    ifFalse:[bCode := bCode, '    ^nil'] 
+                    ifTrue: [bCode := bCode, '    ^true']. 
                 self compile:bCode forClass:aClass inCategory:catg
             ]
         ]
@@ -2012,13 +1740,17 @@
             , '\'
             .
 
-    columns do:[:aColumn|
-        (     aColumn rendererType ~~ #rowSelector 
+    columns do:
+    [:aColumn|
+        (aColumn rendererType ~~ #rowSelector 
          and:[(sel := aColumn selectSelector) notNil
-         and:[(aClass implements:sel) not]]
-        ) ifTrue:[
-            aColumn canSelect ifTrue:[
-                bCode := sel asString, code, '    ^ true'.
+         and:[(aClass implements:sel) not]]) 
+         ifTrue:
+         [
+            aColumn canSelect 
+            ifTrue:
+            [
+                bCode := sel asString, code, '    ^true'.
                 self compile:bCode forClass:aClass inCategory:catg
             ]
         ]
@@ -2026,8 +1758,8 @@
 !
 
 generateWriteSelectorIn:aClass
-    "generate code for #writeSelector
-    "
+    "generate code for #writeSelector"
+
     |sel catg code bCode sz|
 
     catg := 'accessing' asSymbol.
@@ -2037,17 +1769,23 @@
             , '    "set value"\'
             .
 
-    columns do:[:aColumn|
-        (    (sel := aColumn writeSelector) notNil
-         and:[(aColumn canSelect)
-         and:[(aClass implements:sel) not]]
-        ) ifTrue:[
-            sel numArgs == 1 ifTrue:[
+    columns do:
+    [:aColumn|
+        ((sel := aColumn writeSelector) notNil
+         and:[aColumn canSelect
+         and:[(aClass implements:sel) not]]) 
+        ifTrue:
+        [
+            sel numArgs == 1 
+            ifTrue:
+            [
                 bCode := sel asString
-            ] ifFalse:[
+            ] 
+            ifFalse:
+            [
                 sz := sel indexOf:$:.
                 bCode := sel copyTo:sz.
-                bCode := bCode, 'anIndex ', (sel copyFrom:(sz + 1)).
+                bCode := bCode, 'anIndex ', (sel copyFrom:sz + 1)
             ].
             self compile:(bCode, code) forClass:aClass inCategory:catg
         ]
@@ -2057,8 +1795,8 @@
 !DataSetBuilder methodsFor:'initialization'!
 
 initialize
-    "setup aspects used by column description specifications
-    "
+    "setup aspects used by column description specifications"
+
     |holder|
 
     super initialize.
@@ -2102,8 +1840,8 @@
         labelAlignment
      ) do:[:aKey|
         aspects at:aKey put:(holder := ValueHolder new).
-        holder addDependent:self.
-    ].
+        holder addDependent:self
+    ]
 
 ! !
 
@@ -2127,81 +1865,93 @@
 !
 
 resolveClassNamed
-    "returns current class or nil
-    "
-    ^ Smalltalk resolveName:className inClass:self class.
+    "returns current class or nil"
+
+    ^Smalltalk resolveName:className inClass:self class.
 
 !
 
 updateColumnView
-    "update column view from column descriptions
-    "
-    columnView notNil ifTrue:[
-        columnView columnDescriptors:columns.
-    ].
+    "update column view from column descriptions"
+
+    columnView notNil ifTrue:[columnView columnDescriptors:columns]
+!
+
+updateInputFields
+    "reload item value into input fields"
+
+    |column|
+
+    (column := self selectedColumn) isNil 
+    ifTrue:
+    [
+        self tabModel value:0.
+    ] 
+    ifFalse:
+    [
+        aspects keysAndValuesDo:[:aKey :aModel|aModel value:(column perform:aKey)].
+        tabSelectionIndex == 0 ifTrue:[self tabModel value:1]
+    ]
 ! !
 
 !DataSetBuilder methodsFor:'queries'!
 
 hasChanged
-    "returns true if changes are done to the original column description
-    "
-    ^ hasChanged
-!
+    "returns true if changes are done to the original column description"
 
-modified
-    "returns true if current specification is modified
-    "
-    ^ self modifiedChannel value
+    ^hasChanged
 ! !
 
 !DataSetBuilder methodsFor:'selection'!
 
 selectedColumn
-    "returns selected column or nil
-    "
-    ^ selectedColumnIndex == 0 ifFalse:[columns at:selectedColumnIndex]
-                                ifTrue:[nil]
+    "returns selected column or nil"
+
+    ^selectedColumnIndex == 0 
+        ifFalse:[columns at:selectedColumnIndex]
+        ifTrue: [nil]
 !
 
 selectedColumnIndex
-    "returns selected column index or 0
-    "
-    ^ selectedColumnIndex
+    "returns selected column index or 0"
+
+    ^selectedColumnIndex
 !
 
 selectedColumnIndex:something
-    "change selected column and update specifications
-    "
-    something == selectedColumnIndex ifFalse:[
+    "change selected column and update specifications"
+
+    something == selectedColumnIndex 
+    ifFalse:
+    [
         selectedColumnIndex := something ? 0.
-        self cancel.
         self isColumnSelected value: true
-    ].
+    ]
 
 !
 
 tabSelectionIndex
-    "returns selected tab index or 0
-    "
-    ^ tabSelectionIndex
+    "returns selected tab index or 0"
+
+    ^tabSelectionIndex
 !
 
 tabSelectionIndex:something
-    "change selected tab and set corresponding specification
-    "
+    "change selected tab and set corresponding specification"
+
     |specSelector|
 
-    something == tabSelectionIndex ifTrue:[
-        ^ self
-    ].
-    self selectedColumn isNil ifTrue:[
-        tabSelectionIndex == 0 ifTrue:[^ self ].
+    something == tabSelectionIndex ifTrue:[^self].
+    self selectedColumn isNil 
+    ifTrue:
+    [
+        tabSelectionIndex == 0 ifTrue:[^self].
         tabSelectionIndex := 0
-    ] ifFalse:[
-        (tabSelectionIndex := something) ~~ 0 ifTrue:[
-            specSelector := (self class slices at:tabSelectionIndex) last.
-        ]
+    ] 
+    ifFalse:
+    [
+        (tabSelectionIndex := something) ~~ 0 
+            ifTrue: [specSelector := (self class slices at:tabSelectionIndex) last]
     ].
     self specChannel value:specSelector
 
@@ -2211,8 +1961,8 @@
 !DataSetBuilder methodsFor:'startup / release'!
 
 closeRequest
-    "close request
-    "
+    "close request"
+
     self checkMenuItemModified ifTrue: [super closeRequest]
 !
 
@@ -2222,12 +1972,268 @@
 
     (builder componentAt: #columnView) 
         selectConditionBlock: [:i|self checkMenuItemModified];
+        action: [:i|self cancel];
         selection: 1
 
 
 
 ! !
 
+!DataSetBuilder methodsFor:'user actions'!
+
+accept
+    "accept changes made"
+
+    |column type|
+
+    self modifiedChannel value == false ifTrue: [^self].
+    isModified := true.
+
+    (column := self selectedColumn) isNil ifTrue: [^self cancel].
+
+    type := (aspects at:#rendererType) value.
+
+    type == #rowSelector 
+    ifTrue:
+    [
+        #(label width minWidth editorType choices readSelector writeSelector printSelector
+          formatString type size height canSelect selectSelector) do:[:aKey|(aspects at:aKey) value:nil]
+    ].
+        
+    aspects keysAndValuesDo:[:aKey :aModel| column perform:(aKey , ':') asSymbol with: aModel value].
+    self seqList at:selectedColumnIndex put: (aspects at:#label) value.
+    self updateColumnView.
+    self cancel
+!
+
+cancel
+    "remove all changes and reload selected column values"
+
+    |column|
+
+    self updateInputFields.
+    self modifiedChannel value:false.
+    self columnIsNotEditing value: true.
+    isModified := false
+!
+
+doBrowseClass
+    "browse class of columns spec"
+
+    |cls|
+
+    (cls := self resolveClassNamed) notNil 
+        ifTrue: [SystemBrowser openInClass:cls] 
+        ifFalse:[self information:'No class defined!!']
+
+
+
+!
+
+doCopyColumn
+    "copy selected column to the clipboard"
+
+    |idx|
+
+    (idx := selectedColumnIndex) ~~ 0 
+    ifTrue:
+    [
+        self clipboard: (columns at: idx) deepCopy
+    ]
+!
+
+doCreateColumn
+    "create a new column after selected column or at left (nothing selected)"
+
+    |label list|
+
+    list := self seqList.
+    label := 'Column ', list size printString.
+    columns add:(DataSetColumnSpec label:label selector:nil) afterIndex:selectedColumnIndex.
+    self seqList add:label afterIndex:selectedColumnIndex.
+    hasChanged := true.
+    self modifiedChannel value ifFalse:[self selectedColumnModel value:selectedColumnIndex + 1].
+    self cancel
+
+!
+
+doCutColumn
+    "remove selected column and put it to the clipboard"
+
+    |idx|
+
+    ((idx := selectedColumnIndex) ~~ 0 and: [self checkMenuItemModified]) 
+    ifTrue:
+    [
+        self selectedColumnModel value:0.
+        self clipboard: (columns at: idx).
+        columns removeIndex:idx.
+        self seqList removeIndex:idx.
+        self updateColumnView.
+        columns isEmpty ifTrue: [self isColumnSelected value: false].
+        hasChanged := true
+    ]
+!
+
+doDefineClass
+    "launch a dialog to define class and superclass"
+
+    |aspects cls oldClass oldSuper|
+
+    aspects  := IdentityDictionary new.
+    oldClass := className.
+    oldSuper := superclassName.
+
+    [true] 
+    whileTrue:
+    [
+        className notNil 
+        ifTrue:
+        [
+            (cls := self resolveClassNamed) notNil 
+            ifTrue:
+            [
+                superclassName := cls superclass name asString
+            ].
+            aspects at:#classNameChannel put:className asValue
+        ] 
+        ifFalse:
+        [
+            aspects at:#classNameChannel put:'DSVRow' asValue
+        ].
+
+        superclassName notNil 
+            ifTrue: [aspects at:#superclassNameChannel put:superclassName asValue] 
+            ifFalse:[aspects at:#superclassNameChannel put:'Object' asValue].
+
+        (self openDialogInterface:#defineClassNameSpec withBindings:aspects) 
+        ifFalse:
+        [
+            className := oldClass.
+            superclassName := oldSuper.
+            ^self
+        ].
+        className      := ((aspects at:#classNameChannel) value)      withoutSeparators.
+        superclassName := ((aspects at:#superclassNameChannel) value) withoutSeparators.
+
+        className size == 0 
+        ifTrue:
+        [
+            className := nil.
+            self information:'no valid className'
+        ] 
+        ifFalse: 
+        [
+            cls := self resolveClassNamed.
+
+            cls notNil ifTrue:[cls := cls superclass name asString].
+
+            superclassName size == 0 
+            ifTrue:
+            [        
+                cls notNil ifTrue:[
+                    superclassName := cls
+                ] ifFalse:[
+                    superclassName := 'Object'
+                ].
+                self information: 'set superclassName'
+            ] 
+            ifFalse:
+            [
+                (cls isNil or:[superclassName = cls]) ifTrue:[hasChanged := true. ^self].
+                self information:('A global named ' , className , ' exists,\' ,
+                                  'but is not a subclass of ' , superclassName, '.\\' ,
+                                  'Check and try again if that is not what you want.') withCRs.
+
+                superclassName := cls
+            ]
+        ]
+    ]
+!
+
+doGenerateCode
+    "generate code for column values"
+
+    |cls superclass|
+
+    className isNil ifTrue:[^self information:'No class defined!!'].
+    cls := self resolveClassNamed.
+
+    cls isNil 
+    ifTrue:
+    [
+        superclass := Smalltalk resolveName:superclassName inClass:self class.
+
+        superclass isNil ifTrue:[^self information:'No superclass defined!!'].
+        (self confirm:'create ' , className , ' ?') ifFalse:[^self].
+        cls := superclass subclass:className asSymbol
+                     instanceVariableNames:''
+                     classVariableNames:''
+                     poolDictionaries:''
+                     category:'Applications'.
+    ].
+
+    self generateChoicesIn:cls.
+    self generateMenuIn:cls.
+    self generatePrintSelectorIn:cls.
+    self generateReadSelectorIn:cls.
+    self generateBackgroundSelectorIn:cls.
+    self generateForegroundSelectorIn:cls.
+    self generateSelectSelectorIn:cls.
+    self generateWriteSelectorIn:cls.
+    self generateDoubleClickSelectorIn:cls.
+!
+
+doMoveColumn:upOrDown
+    "move selected column up or down"
+
+    |idx list label col size|
+
+    (idx := selectedColumnIndex) == 0 ifTrue:[^self].
+    list := self seqList.
+    size := list size.
+
+    size == 1 ifTrue:[^self].
+    hasChanged := true.
+    selectedColumnIndex := 0.
+    label := list at:idx.
+    col   := columns at:idx.
+    list    removeIndex:idx.
+    columns removeIndex:idx.
+
+    upOrDown == #up 
+    ifTrue:
+    [
+        idx == 1 ifTrue:[idx := size]
+                ifFalse:[idx := idx - 1]
+    ] 
+    ifFalse:
+    [
+        idx == size ifTrue:[idx := 1]
+                   ifFalse:[idx := idx + 1]
+    ].
+    columns add:col   beforeIndex:idx.
+    list    add:label beforeIndex:idx.  
+    self selectedColumnModel value:idx.
+    self updateColumnView.
+!
+
+doPasteColumn
+    "paste clipboard copy column after selected column or at left (nothing selected)"
+
+    |label list|
+
+    list := self seqList.
+    label := self class clipboard label.
+    columns add: self class clipboard deepCopy afterIndex:selectedColumnIndex.
+    self seqList add: label afterIndex:selectedColumnIndex.
+    hasChanged := true.
+
+    self modifiedChannel value ifFalse:[self selectedColumnModel value:selectedColumnIndex + 1].
+    self updateColumnView.
+
+! !
+
 !DataSetBuilder class methodsFor:'documentation'!
 
 version