examples
authorClaus Gittinger <cg@exept.de>
Sat, 27 Apr 1996 20:23:13 +0200
changeset 161 5b6e284959a4
parent 160 61d95c5f5102
child 162 8b671f2e31ef
examples
2ColTxtV.st
ClrListEntry.st
ColoredListEntry.st
ImageEditView.st
ImageView.st
ImgEditV.st
MCLEntry.st
MultiColListEntry.st
Ruler.st
TabSpec.st
TabulatorSpecification.st
TwoColumnTextView.st
VRuler.st
VerticalRuler.st
--- a/2ColTxtV.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/2ColTxtV.st	Sat Apr 27 20:23:13 1996 +0200
@@ -62,21 +62,27 @@
      See more examples there.
      (you may find nice uses for it anyway ...)
 
+                                                                        [exBegin]
      TwoColumnTextView
         openOn:('smalltalk.rc' asFilename contentsOfEntireFile)
         and:('display.rc' asFilename contentsOfEntireFile)
+                                                                        [exEnd]
 
 
+                                                                        [exBegin]
      TwoColumnTextView
         openOn:('display.rc' asFilename contentsOfEntireFile)
         and:('smalltalk.rc' asFilename contentsOfEntireFile)
+                                                                        [exEnd]
 
 
+                                                                        [exBegin]
      TwoColumnTextView
         openOn:('smalltalk.rc' asFilename contentsOfEntireFile)
         label:'smalltalk.rc'
         and:('display.rc' asFilename contentsOfEntireFile)
         label:'display.rc'
+                                                                        [exEnd]
 "
 
     "Created: 20.11.1995 / 13:21:42 / cg"
@@ -164,4 +170,4 @@
 !TwoColumnTextView class methodsFor:'documentation'!
 
 version
-^ '$Header: /cvs/stx/stx/libwidg2/Attic/2ColTxtV.st,v 1.11 1996-04-25 17:32:19 cg Exp $'! !
+^ '$Header: /cvs/stx/stx/libwidg2/Attic/2ColTxtV.st,v 1.12 1996-04-27 18:23:13 cg Exp $'! !
--- a/ClrListEntry.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/ClrListEntry.st	Sat Apr 27 20:23:13 1996 +0200
@@ -46,6 +46,8 @@
 
     [see also:]
         ListView
+        ListEntry
+        String Color
 "
 !
 
@@ -53,41 +55,43 @@
 "
      putting colored entries into a SelectionInListView
      (instead of strings)'
+                                                                        [exBegin]
+        |v e myList tabs|
 
-	|v e myList tabs|
-
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	myList add:(ColoredListEntry string:'red' color:Color red).
-	myList add:(ColoredListEntry string:'green' color:Color green).
-	myList add:(ColoredListEntry string:'blue' color:Color blue).
-	myList add:(ColoredListEntry string:'white' color:Color white).
-	myList add:(ColoredListEntry string:'black' color:Color black).
-	myList add:(ColoredListEntry string:'yellow' color:Color yellow).
+        myList add:(ColoredListEntry string:'red' color:Color red).
+        myList add:(ColoredListEntry string:'green' color:Color green).
+        myList add:(ColoredListEntry string:'blue' color:Color blue).
+        myList add:(ColoredListEntry string:'white' color:Color white).
+        myList add:(ColoredListEntry string:'black' color:Color black).
+        myList add:(ColoredListEntry string:'yellow' color:Color yellow).
 
-	v := SelectionInListView new.
-	v setList:myList expandTabs:false.
-	v open
+        v := SelectionInListView new.
+        v setList:myList expandTabs:false.
+        v open
+                                                                        [exEnd]
 
 
      in a popUpList (sorry, Labels do not (yet) know how to display
      non-strings.
+                                                                        [exBegin]
+        |v e myList selList tabs|
 
-	|v e myList selList tabs|
-
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	myList add:(ColoredListEntry string:'red' color:Color red).
-	myList add:(ColoredListEntry string:'green' color:Color green).
-	myList add:(ColoredListEntry string:'blue' color:Color blue).
-	myList add:(ColoredListEntry string:'white' color:Color white).
-	myList add:(ColoredListEntry string:'black' color:Color black).
-	myList add:(ColoredListEntry string:'yellow' color:Color yellow).
+        myList add:(ColoredListEntry string:'red' color:Color red).
+        myList add:(ColoredListEntry string:'green' color:Color green).
+        myList add:(ColoredListEntry string:'blue' color:Color blue).
+        myList add:(ColoredListEntry string:'white' color:Color white).
+        myList add:(ColoredListEntry string:'black' color:Color black).
+        myList add:(ColoredListEntry string:'yellow' color:Color yellow).
 
-	selList := SelectionInList new list:myList.
+        selList := SelectionInList new list:myList.
 
-	v := PopUpList on:selList.
-	v open
+        v := PopUpList on:selList.
+        v open
+                                                                        [exEnd]
 "
 ! !
 
@@ -163,5 +167,5 @@
 !ColoredListEntry class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/ClrListEntry.st,v 1.10 1996-04-25 17:31:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/ClrListEntry.st,v 1.11 1996-04-27 18:22:28 cg Exp $'
 ! !
--- a/ColoredListEntry.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/ColoredListEntry.st	Sat Apr 27 20:23:13 1996 +0200
@@ -46,6 +46,8 @@
 
     [see also:]
         ListView
+        ListEntry
+        String Color
 "
 !
 
@@ -53,41 +55,43 @@
 "
      putting colored entries into a SelectionInListView
      (instead of strings)'
+                                                                        [exBegin]
+        |v e myList tabs|
 
-	|v e myList tabs|
-
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	myList add:(ColoredListEntry string:'red' color:Color red).
-	myList add:(ColoredListEntry string:'green' color:Color green).
-	myList add:(ColoredListEntry string:'blue' color:Color blue).
-	myList add:(ColoredListEntry string:'white' color:Color white).
-	myList add:(ColoredListEntry string:'black' color:Color black).
-	myList add:(ColoredListEntry string:'yellow' color:Color yellow).
+        myList add:(ColoredListEntry string:'red' color:Color red).
+        myList add:(ColoredListEntry string:'green' color:Color green).
+        myList add:(ColoredListEntry string:'blue' color:Color blue).
+        myList add:(ColoredListEntry string:'white' color:Color white).
+        myList add:(ColoredListEntry string:'black' color:Color black).
+        myList add:(ColoredListEntry string:'yellow' color:Color yellow).
 
-	v := SelectionInListView new.
-	v setList:myList expandTabs:false.
-	v open
+        v := SelectionInListView new.
+        v setList:myList expandTabs:false.
+        v open
+                                                                        [exEnd]
 
 
      in a popUpList (sorry, Labels do not (yet) know how to display
      non-strings.
+                                                                        [exBegin]
+        |v e myList selList tabs|
 
-	|v e myList selList tabs|
-
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	myList add:(ColoredListEntry string:'red' color:Color red).
-	myList add:(ColoredListEntry string:'green' color:Color green).
-	myList add:(ColoredListEntry string:'blue' color:Color blue).
-	myList add:(ColoredListEntry string:'white' color:Color white).
-	myList add:(ColoredListEntry string:'black' color:Color black).
-	myList add:(ColoredListEntry string:'yellow' color:Color yellow).
+        myList add:(ColoredListEntry string:'red' color:Color red).
+        myList add:(ColoredListEntry string:'green' color:Color green).
+        myList add:(ColoredListEntry string:'blue' color:Color blue).
+        myList add:(ColoredListEntry string:'white' color:Color white).
+        myList add:(ColoredListEntry string:'black' color:Color black).
+        myList add:(ColoredListEntry string:'yellow' color:Color yellow).
 
-	selList := SelectionInList new list:myList.
+        selList := SelectionInList new list:myList.
 
-	v := PopUpList on:selList.
-	v open
+        v := PopUpList on:selList.
+        v open
+                                                                        [exEnd]
 "
 ! !
 
@@ -163,5 +167,5 @@
 !ColoredListEntry class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/ColoredListEntry.st,v 1.10 1996-04-25 17:31:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/ColoredListEntry.st,v 1.11 1996-04-27 18:22:28 cg Exp $'
 ! !
--- a/ImageEditView.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/ImageEditView.st	Sat Apr 27 20:23:13 1996 +0200
@@ -11,11 +11,10 @@
 "
 
 ImageView subclass:#ImageEditView
-	 instanceVariableNames:'magnification colors magnifiedImage
-				colorPanel'
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Views-Misc'
+	instanceVariableNames:'magnification colors magnifiedImage colorPanel'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Views-Misc'
 !
 
 !ImageEditView class methodsFor:'documentation'!
@@ -39,26 +38,6 @@
     This View will eventually be able to edit bitmap images.
     For now, it is not.
 "
-!
-
-version
-    ^ '$Header: /cvs/stx/stx/libwidg2/ImageEditView.st,v 1.15 1995-11-11 16:29:05 cg Exp $'
-! !
-
-!ImageEditView methodsFor:'queries'!
-
-widthOfContents
-    "return the images width"
-
-    image isNil ifTrue:[^ 0].
-    ^ (image width * magnification x) rounded
-!
-
-heightOfContents
-    "return the images height"
-
-    image isNil ifTrue:[^ 0].
-    ^ (image height * magnification y) rounded
 ! !
 
 !ImageEditView methodsFor:'accessing'!
@@ -69,84 +48,6 @@
     super image:anImage
 ! !
 
-!ImageEditView methodsFor:'menu actions'!
-
-saveAs
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
-
-    |fileName|
-
-    fileName := Dialog
-		    requestFileName:'save image in:'
-		    default:''
-		    ok:'save'
-		    abort:'abort'
-		    pattern:'*.tiff'.
-
-    fileName notNil ifTrue:[
-	image saveOn:fileName
-    ].
-!
-
-showColors
-    colorPanel isNil ifTrue:[
-	colorPanel := ColorPanel new
-    ].
-    colorPanel shown ifFalse:[
-	colorPanel realize
-    ]
-!
-
-changeMagnification
-    |b|
-
-    b := EnterBox new.
-    b title:'magnification (magX @ magY)'.
-    b okText:'apply'.
-    b abortText:'abort'.
-    b action:[:string | self magnification:(Object readFromString:string)].
-    b initialText:(magnification printString).
-    b showAtPointer
-!
-
-magnification:aMagnificationPoint
-    |nPixel savedImage|
-
-    magnification ~= aMagnificationPoint ifTrue:[
-	"show wait cursor; although magnification is fast, dithering may take a while"
-	self cursor:Cursor wait.
-
-	(device visualType == #PseudoColor) ifTrue:[
-	    "keep colors - otherwise they might get collected & changed"
-	    colors := IdentitySet new.
-	].
-
-	magnification := aMagnificationPoint asPoint.
-
-	"use a magnified image, if its size wont be too big"
-	magnifiedImage := nil.
-
-	"avoid slow scroll"
-	savedImage := image.
-	image := nil.
-	self scrollToTopLeft.
-	image := savedImage.
-
-	magnification ~= (1@1) ifTrue:[
-	    nPixel := image width * image height * magnification x * magnification y.
-	    nPixel <= (device width * device height) ifTrue:[
-		Transcript showCr:'magnifying ..'; endEntry.
-		magnifiedImage := image magnifyBy:magnification
-	    ].
-	].
-
-	self contentsChanged.
-	self redraw.
-	self cursor:Cursor normal
-    ]
-! !
-
 !ImageEditView methodsFor:'drawing'!
 
 redraw
@@ -254,8 +155,73 @@
     ]
 ! !
 
+!ImageEditView methodsFor:'event handling'!
+
+buttonMotion:state x:x y:y
+    self showColorAtX:x y:y.
+!
+
+buttonPress:button x:x y:y
+    button == 1 ifTrue:[
+	self showColorAtX:x y:y.
+	^ self
+    ].
+    super buttonPress:button x:x y:y
+!
+
+showColorAtX:x y:y
+    |pi clr|
+
+    pi := (x @ y) - margin.
+    pi := pi // magnification.
+    ((0@0 corner:image extent) containsPoint:pi) ifTrue:[
+	clr := image at:pi.
+	colorPanel notNil ifTrue:[
+	    colorPanel setColor:clr.
+	] ifFalse:[
+	    Transcript showCr:clr displayString
+	]
+    ]
+! !
+
+!ImageEditView methodsFor:'image processing'!
+
+blurr
+    self performImageOperation:#blurr withArguments:nil
+!
+
+flipHorizontal
+    self performImageOperation:#flipHorizontal withArguments:nil
+!
+
+flipVertical
+    self performImageOperation:#flipVertical withArguments:nil
+!
+
+performImageOperation:operation withArguments:args
+    |oldMag|
+
+    windowGroup withCursor:Cursor wait do:[
+	oldMag := magnification.
+	magnifiedImage := nil.
+	magnification := 1@1.
+	image perform:operation withArguments:args.
+	(oldMag isNil or:[oldMag = magnification]) ifTrue:[
+	    self redraw
+	] ifFalse:[
+	    self magnification:oldMag.
+	]
+    ]
+! !
+
 !ImageEditView methodsFor:'initialization'!
 
+initialize
+    super initialize.
+    magnification := 1@1.
+    colors := nil
+!
+
 initializeMiddleButtonMenu
     |m|
 
@@ -303,71 +269,100 @@
      ImageEditView openOn:'bitmaps/SBrowser.xbm'
      ImageEditView openOn:'bitmaps/garfield.gif'
     "
-!
-
-initialize
-    super initialize.
-    magnification := 1@1.
-    colors := nil
 ! !
 
-!ImageEditView methodsFor:'event handling'!
+!ImageEditView methodsFor:'menu actions'!
+
+changeMagnification
+    |b|
 
-showColorAtX:x y:y
-    |pi clr|
+    b := EnterBox new.
+    b title:'magnification (magX @ magY)'.
+    b okText:'apply'.
+    b abortText:'abort'.
+    b action:[:string | self magnification:(Object readFromString:string)].
+    b initialText:(magnification printString).
+    b showAtPointer
+!
+
+magnification:aMagnificationPoint
+    |nPixel savedImage|
+
+    magnification ~= aMagnificationPoint ifTrue:[
+	"show wait cursor; although magnification is fast, dithering may take a while"
+	self cursor:Cursor wait.
 
-    pi := (x @ y) - margin.
-    pi := pi // magnification.
-    ((0@0 corner:image extent) containsPoint:pi) ifTrue:[
-	clr := image at:pi.
-	colorPanel notNil ifTrue:[
-	    colorPanel setColor:clr.
-	] ifFalse:[
-	    Transcript showCr:clr displayString
-	]
+	(device visualType == #PseudoColor) ifTrue:[
+	    "keep colors - otherwise they might get collected & changed"
+	    colors := IdentitySet new.
+	].
+
+	magnification := aMagnificationPoint asPoint.
+
+	"use a magnified image, if its size wont be too big"
+	magnifiedImage := nil.
+
+	"avoid slow scroll"
+	savedImage := image.
+	image := nil.
+	self scrollToTopLeft.
+	image := savedImage.
+
+	magnification ~= (1@1) ifTrue:[
+	    nPixel := image width * image height * magnification x * magnification y.
+	    nPixel <= (device width * device height) ifTrue:[
+		Transcript showCr:'magnifying ..'; endEntry.
+		magnifiedImage := image magnifyBy:magnification
+	    ].
+	].
+
+	self contentsChanged.
+	self redraw.
+	self cursor:Cursor normal
     ]
 !
 
-buttonMotion:state x:x y:y
-    self showColorAtX:x y:y.
+saveAs
+    "save contents into a file 
+     - ask user for filename using a fileSelectionBox."
+
+    |fileName|
+
+    fileName := Dialog
+		    requestFileName:'save image in:'
+		    default:''
+		    ok:'save'
+		    abort:'abort'
+		    pattern:'*.tiff'.
+
+    fileName notNil ifTrue:[
+	image saveOn:fileName
+    ].
 !
 
-buttonPress:button x:x y:y
-    button == 1 ifTrue:[
-	self showColorAtX:x y:y.
-	^ self
+showColors
+    colorPanel isNil ifTrue:[
+	colorPanel := ColorPanel new
     ].
-    super buttonPress:button x:x y:y
+    colorPanel shown ifFalse:[
+	colorPanel realize
+    ]
 ! !
 
-!ImageEditView methodsFor:'image processing'!
-
-performImageOperation:operation withArguments:args
-    |oldMag|
+!ImageEditView methodsFor:'queries'!
 
-    windowGroup withCursor:Cursor wait do:[
-	oldMag := magnification.
-	magnifiedImage := nil.
-	magnification := 1@1.
-	image perform:operation withArguments:args.
-	(oldMag isNil or:[oldMag = magnification]) ifTrue:[
-	    self redraw
-	] ifFalse:[
-	    self magnification:oldMag.
-	]
-    ]
+heightOfContents
+    "return the images height"
+
+    image isNil ifTrue:[^ 0].
+    ^ (image height * magnification y) rounded
 !
 
-flipVertical
-    self performImageOperation:#flipVertical withArguments:nil
-!
+widthOfContents
+    "return the images width"
 
-flipHorizontal
-    self performImageOperation:#flipHorizontal withArguments:nil
-!
-
-blurr
-    self performImageOperation:#blurr withArguments:nil
+    image isNil ifTrue:[^ 0].
+    ^ (image width * magnification x) rounded
 ! !
 
 !ImageEditView methodsFor:'release'!
@@ -381,3 +376,9 @@
     ].
     super destroy.
 ! !
+
+!ImageEditView class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libwidg2/ImageEditView.st,v 1.16 1996-04-27 18:21:55 cg Exp $'
+! !
--- a/ImageView.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/ImageView.st	Sat Apr 27 20:23:13 1996 +0200
@@ -11,10 +11,10 @@
 "
 
 SimpleView subclass:#ImageView
-	 instanceVariableNames:'image adjust'
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Views-Misc'
+	instanceVariableNames:'image adjust'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Views-Misc'
 !
 
 !ImageView class methodsFor:'documentation'!
@@ -53,10 +53,6 @@
 	ImageView openOnImage:(Image fromFile:'bitmaps/garfield.gif')
 	ImageView openOnImage:(Form fromFile:'SBrowser.xbm')
 "
-!
-
-version
-    ^ '$Header: /cvs/stx/stx/libwidg2/ImageView.st,v 1.18 1995-11-17 17:38:51 cg Exp $'
 ! !
 
 !ImageView class methodsFor:'startup'!
@@ -163,11 +159,42 @@
     "
 ! !
 
-!ImageView methodsFor:'release'!
+!ImageView methodsFor:'accessing'!
+
+adjust:layoutSymbol
+    "set the adjust (how the image is displayed);
+     currently, only support #topLeft and #center"
+
+    adjust := layoutSymbol
+!
+
+image
+    "return the image"
+
+    ^ image
+!
+
+image:anImage
+    "set the image - show a wait cursor, since image dithering may take a while"
 
-destroy
-    image := nil.
-    super destroy.
+    image := anImage.
+    anImage notNil ifTrue:[
+	self cursor:Cursor wait.
+	shown ifTrue:[
+	    self redraw
+	].
+	self contentsChanged.
+	self cursor:(Cursor normal).
+    ].
+
+    "
+     ImageView new realize image:(Image fromFile:'bitmaps/claus.gif')
+
+     |f|
+     f := Image fromFile:'bitmaps/SBrowser.xbm'.
+     f colorMap:(Array with:Color red with:Color yellow).
+     ImageView new realize image:f
+    "
 ! !
 
 !ImageView methodsFor:'drawing'!
@@ -198,56 +225,31 @@
     "Modified: 17.11.1995 / 15:44:14 / cg"
 ! !
 
-!ImageView methodsFor:'accessing'!
-
-image:anImage
-    "set the image - show a wait cursor, since image dithering may take a while"
-
-    image := anImage.
-    anImage notNil ifTrue:[
-	self cursor:Cursor wait.
-	shown ifTrue:[
-	    self redraw
-	].
-	self contentsChanged.
-	self cursor:(Cursor normal).
-    ].
-
-    "
-     ImageView new realize image:(Image fromFile:'bitmaps/claus.gif')
+!ImageView methodsFor:'queries'!
 
-     |f|
-     f := Image fromFile:'bitmaps/SBrowser.xbm'.
-     f colorMap:(Array with:Color red with:Color yellow).
-     ImageView new realize image:f
-    "
-!
-
-image
-    "return the image"
+heightOfContents
+    "return the images height - scrollbar needs this info"
 
-    ^ image
+    image isNil ifTrue:[^ 0].
+    ^ image height
 !
 
-adjust:layoutSymbol
-    "set the adjust (how the image is displayed);
-     currently, only support #topLeft and #center"
-
-    adjust := layoutSymbol
-! !
-
-!ImageView methodsFor:'queries'!
-
 widthOfContents
     "return the images width - scrollbar needs this info"
 
     image isNil ifTrue:[^ 0].
     ^ image width
-!
+! !
+
+!ImageView methodsFor:'release'!
 
-heightOfContents
-    "return the images height - scrollbar needs this info"
+destroy
+    image := nil.
+    super destroy.
+! !
 
-    image isNil ifTrue:[^ 0].
-    ^ image height
+!ImageView class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libwidg2/ImageView.st,v 1.19 1996-04-27 18:22:00 cg Exp $'
 ! !
--- a/ImgEditV.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/ImgEditV.st	Sat Apr 27 20:23:13 1996 +0200
@@ -11,11 +11,10 @@
 "
 
 ImageView subclass:#ImageEditView
-	 instanceVariableNames:'magnification colors magnifiedImage
-				colorPanel'
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Views-Misc'
+	instanceVariableNames:'magnification colors magnifiedImage colorPanel'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Views-Misc'
 !
 
 !ImageEditView class methodsFor:'documentation'!
@@ -39,26 +38,6 @@
     This View will eventually be able to edit bitmap images.
     For now, it is not.
 "
-!
-
-version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/ImgEditV.st,v 1.15 1995-11-11 16:29:05 cg Exp $'
-! !
-
-!ImageEditView methodsFor:'queries'!
-
-widthOfContents
-    "return the images width"
-
-    image isNil ifTrue:[^ 0].
-    ^ (image width * magnification x) rounded
-!
-
-heightOfContents
-    "return the images height"
-
-    image isNil ifTrue:[^ 0].
-    ^ (image height * magnification y) rounded
 ! !
 
 !ImageEditView methodsFor:'accessing'!
@@ -69,84 +48,6 @@
     super image:anImage
 ! !
 
-!ImageEditView methodsFor:'menu actions'!
-
-saveAs
-    "save contents into a file 
-     - ask user for filename using a fileSelectionBox."
-
-    |fileName|
-
-    fileName := Dialog
-		    requestFileName:'save image in:'
-		    default:''
-		    ok:'save'
-		    abort:'abort'
-		    pattern:'*.tiff'.
-
-    fileName notNil ifTrue:[
-	image saveOn:fileName
-    ].
-!
-
-showColors
-    colorPanel isNil ifTrue:[
-	colorPanel := ColorPanel new
-    ].
-    colorPanel shown ifFalse:[
-	colorPanel realize
-    ]
-!
-
-changeMagnification
-    |b|
-
-    b := EnterBox new.
-    b title:'magnification (magX @ magY)'.
-    b okText:'apply'.
-    b abortText:'abort'.
-    b action:[:string | self magnification:(Object readFromString:string)].
-    b initialText:(magnification printString).
-    b showAtPointer
-!
-
-magnification:aMagnificationPoint
-    |nPixel savedImage|
-
-    magnification ~= aMagnificationPoint ifTrue:[
-	"show wait cursor; although magnification is fast, dithering may take a while"
-	self cursor:Cursor wait.
-
-	(device visualType == #PseudoColor) ifTrue:[
-	    "keep colors - otherwise they might get collected & changed"
-	    colors := IdentitySet new.
-	].
-
-	magnification := aMagnificationPoint asPoint.
-
-	"use a magnified image, if its size wont be too big"
-	magnifiedImage := nil.
-
-	"avoid slow scroll"
-	savedImage := image.
-	image := nil.
-	self scrollToTopLeft.
-	image := savedImage.
-
-	magnification ~= (1@1) ifTrue:[
-	    nPixel := image width * image height * magnification x * magnification y.
-	    nPixel <= (device width * device height) ifTrue:[
-		Transcript showCr:'magnifying ..'; endEntry.
-		magnifiedImage := image magnifyBy:magnification
-	    ].
-	].
-
-	self contentsChanged.
-	self redraw.
-	self cursor:Cursor normal
-    ]
-! !
-
 !ImageEditView methodsFor:'drawing'!
 
 redraw
@@ -254,8 +155,73 @@
     ]
 ! !
 
+!ImageEditView methodsFor:'event handling'!
+
+buttonMotion:state x:x y:y
+    self showColorAtX:x y:y.
+!
+
+buttonPress:button x:x y:y
+    button == 1 ifTrue:[
+	self showColorAtX:x y:y.
+	^ self
+    ].
+    super buttonPress:button x:x y:y
+!
+
+showColorAtX:x y:y
+    |pi clr|
+
+    pi := (x @ y) - margin.
+    pi := pi // magnification.
+    ((0@0 corner:image extent) containsPoint:pi) ifTrue:[
+	clr := image at:pi.
+	colorPanel notNil ifTrue:[
+	    colorPanel setColor:clr.
+	] ifFalse:[
+	    Transcript showCr:clr displayString
+	]
+    ]
+! !
+
+!ImageEditView methodsFor:'image processing'!
+
+blurr
+    self performImageOperation:#blurr withArguments:nil
+!
+
+flipHorizontal
+    self performImageOperation:#flipHorizontal withArguments:nil
+!
+
+flipVertical
+    self performImageOperation:#flipVertical withArguments:nil
+!
+
+performImageOperation:operation withArguments:args
+    |oldMag|
+
+    windowGroup withCursor:Cursor wait do:[
+	oldMag := magnification.
+	magnifiedImage := nil.
+	magnification := 1@1.
+	image perform:operation withArguments:args.
+	(oldMag isNil or:[oldMag = magnification]) ifTrue:[
+	    self redraw
+	] ifFalse:[
+	    self magnification:oldMag.
+	]
+    ]
+! !
+
 !ImageEditView methodsFor:'initialization'!
 
+initialize
+    super initialize.
+    magnification := 1@1.
+    colors := nil
+!
+
 initializeMiddleButtonMenu
     |m|
 
@@ -303,71 +269,100 @@
      ImageEditView openOn:'bitmaps/SBrowser.xbm'
      ImageEditView openOn:'bitmaps/garfield.gif'
     "
-!
-
-initialize
-    super initialize.
-    magnification := 1@1.
-    colors := nil
 ! !
 
-!ImageEditView methodsFor:'event handling'!
+!ImageEditView methodsFor:'menu actions'!
+
+changeMagnification
+    |b|
 
-showColorAtX:x y:y
-    |pi clr|
+    b := EnterBox new.
+    b title:'magnification (magX @ magY)'.
+    b okText:'apply'.
+    b abortText:'abort'.
+    b action:[:string | self magnification:(Object readFromString:string)].
+    b initialText:(magnification printString).
+    b showAtPointer
+!
+
+magnification:aMagnificationPoint
+    |nPixel savedImage|
+
+    magnification ~= aMagnificationPoint ifTrue:[
+	"show wait cursor; although magnification is fast, dithering may take a while"
+	self cursor:Cursor wait.
 
-    pi := (x @ y) - margin.
-    pi := pi // magnification.
-    ((0@0 corner:image extent) containsPoint:pi) ifTrue:[
-	clr := image at:pi.
-	colorPanel notNil ifTrue:[
-	    colorPanel setColor:clr.
-	] ifFalse:[
-	    Transcript showCr:clr displayString
-	]
+	(device visualType == #PseudoColor) ifTrue:[
+	    "keep colors - otherwise they might get collected & changed"
+	    colors := IdentitySet new.
+	].
+
+	magnification := aMagnificationPoint asPoint.
+
+	"use a magnified image, if its size wont be too big"
+	magnifiedImage := nil.
+
+	"avoid slow scroll"
+	savedImage := image.
+	image := nil.
+	self scrollToTopLeft.
+	image := savedImage.
+
+	magnification ~= (1@1) ifTrue:[
+	    nPixel := image width * image height * magnification x * magnification y.
+	    nPixel <= (device width * device height) ifTrue:[
+		Transcript showCr:'magnifying ..'; endEntry.
+		magnifiedImage := image magnifyBy:magnification
+	    ].
+	].
+
+	self contentsChanged.
+	self redraw.
+	self cursor:Cursor normal
     ]
 !
 
-buttonMotion:state x:x y:y
-    self showColorAtX:x y:y.
+saveAs
+    "save contents into a file 
+     - ask user for filename using a fileSelectionBox."
+
+    |fileName|
+
+    fileName := Dialog
+		    requestFileName:'save image in:'
+		    default:''
+		    ok:'save'
+		    abort:'abort'
+		    pattern:'*.tiff'.
+
+    fileName notNil ifTrue:[
+	image saveOn:fileName
+    ].
 !
 
-buttonPress:button x:x y:y
-    button == 1 ifTrue:[
-	self showColorAtX:x y:y.
-	^ self
+showColors
+    colorPanel isNil ifTrue:[
+	colorPanel := ColorPanel new
     ].
-    super buttonPress:button x:x y:y
+    colorPanel shown ifFalse:[
+	colorPanel realize
+    ]
 ! !
 
-!ImageEditView methodsFor:'image processing'!
-
-performImageOperation:operation withArguments:args
-    |oldMag|
+!ImageEditView methodsFor:'queries'!
 
-    windowGroup withCursor:Cursor wait do:[
-	oldMag := magnification.
-	magnifiedImage := nil.
-	magnification := 1@1.
-	image perform:operation withArguments:args.
-	(oldMag isNil or:[oldMag = magnification]) ifTrue:[
-	    self redraw
-	] ifFalse:[
-	    self magnification:oldMag.
-	]
-    ]
+heightOfContents
+    "return the images height"
+
+    image isNil ifTrue:[^ 0].
+    ^ (image height * magnification y) rounded
 !
 
-flipVertical
-    self performImageOperation:#flipVertical withArguments:nil
-!
+widthOfContents
+    "return the images width"
 
-flipHorizontal
-    self performImageOperation:#flipHorizontal withArguments:nil
-!
-
-blurr
-    self performImageOperation:#blurr withArguments:nil
+    image isNil ifTrue:[^ 0].
+    ^ (image width * magnification x) rounded
 ! !
 
 !ImageEditView methodsFor:'release'!
@@ -381,3 +376,9 @@
     ].
     super destroy.
 ! !
+
+!ImageEditView class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/ImgEditV.st,v 1.16 1996-04-27 18:21:55 cg Exp $'
+! !
--- a/MCLEntry.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/MCLEntry.st	Sat Apr 27 20:23:13 1996 +0200
@@ -57,205 +57,212 @@
 "
      putting multiColListEntries into a ListView
      (instead of strings)'
-        
-	|v e myList tabs|
+                                                                        [exBegin]
+        |v e myList tabs|
 
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	tabs := TabulatorSpecification new.
-	tabs unit:#inch.
-	tabs positions:#(0 3 4).
-	tabs align:#(left #center #left).
+        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:'left centered left'.
+        e tabulatorSpecification:tabs.
+        myList add:e.
 
-	e := MultiColListEntry 
-		 fromString:'| | |'.
-	e tabulatorSpecification:tabs.
-	myList add:e.
-	myList add:''.
+        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:'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 
+                 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.
+        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
+        v := ListView new.
+        v setList:myList expandTabs:false.
+        v extent:500@100.
+        v open
+                                                                        [exEnd]
 
 
 
      many multiColListEntries in a scrollable ListView
+                                                                        [exBegin]
+        |v l e myList tabs|
 
-	|v l e myList tabs|
-
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	tabs := TabulatorSpecification new.
-	tabs unit:#cm.
-	tabs positions:#(1 3 5).
-	tabs align:#(#right #center #left).
+        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
+        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
+                                                                        [exEnd]
 
 
 
      like above, but uses nicer decimal alignments
+                                                                        [exBegin]
+        |v l e myList tabs|
 
-	|v l e myList tabs|
-
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
         
-	tabs := TabulatorSpecification new.
-	tabs unit:#cm.
-	tabs positions:#(1 3 6 9 12).
-	tabs align:#(#right #decimal #decimal #decimal #decimal).
+        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
+        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
+                                                                        [exEnd]
 
 
 
      specifying tabs in inches
-
-	|v l e myList tabs|
+                                                                        [exBegin]
+        |v l e myList tabs|
 
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	tabs := TabulatorSpecification new.
-	tabs unit:#inch.
-	tabs positions:#(0 2 3.5 4 6 8 10 12).
+        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.
+        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).
+        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
+        l := ListView new.
+        l setList:myList expandTabs:false.
+        v := HVScrollableView forView:l.
+        v extent:600@200.
+        v open
+                                                                        [exEnd]
 
 
      if you have the columns available as a collection, 
      setup can be done easier
-
-	|v l e myList tabs|
+                                                                        [exBegin]
+        |v l e myList tabs|
 
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	tabs := TabulatorSpecification new.
-	tabs unit:#inch.
-	tabs positions:#(0 2 3.5 4 6 8 10 12).
+        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.
+        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
+        l := ListView new.
+        l setList:myList expandTabs:false.
+        v := HVScrollableView forView:l.
+        v extent:600@200.
+        v open
+                                                                        [exEnd]
 
 
     concrete example, show /etc/passwd in a table:
-        
-	|v l s myList line e htabs tabs fingerEntry|
+                                                                        [exBegin]
+
+        |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).
+        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).
+        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.
+        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:''.
+        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.
+        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
+        l := ListView new.
+        l setList:myList expandTabs:false.
+        v := HVScrollableView forView:l.
+        v extent:600@200.
+        v open
+                                                                        [exEnd]
 "
 ! !
 
@@ -450,5 +457,5 @@
 !MultiColListEntry class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/MCLEntry.st,v 1.15 1996-04-25 17:31:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/MCLEntry.st,v 1.16 1996-04-27 18:22:18 cg Exp $'
 ! !
--- a/MultiColListEntry.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/MultiColListEntry.st	Sat Apr 27 20:23:13 1996 +0200
@@ -57,205 +57,212 @@
 "
      putting multiColListEntries into a ListView
      (instead of strings)'
-        
-	|v e myList tabs|
+                                                                        [exBegin]
+        |v e myList tabs|
 
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	tabs := TabulatorSpecification new.
-	tabs unit:#inch.
-	tabs positions:#(0 3 4).
-	tabs align:#(left #center #left).
+        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:'left centered left'.
+        e tabulatorSpecification:tabs.
+        myList add:e.
 
-	e := MultiColListEntry 
-		 fromString:'| | |'.
-	e tabulatorSpecification:tabs.
-	myList add:e.
-	myList add:''.
+        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:'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 
+                 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.
+        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
+        v := ListView new.
+        v setList:myList expandTabs:false.
+        v extent:500@100.
+        v open
+                                                                        [exEnd]
 
 
 
      many multiColListEntries in a scrollable ListView
+                                                                        [exBegin]
+        |v l e myList tabs|
 
-	|v l e myList tabs|
-
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	tabs := TabulatorSpecification new.
-	tabs unit:#cm.
-	tabs positions:#(1 3 5).
-	tabs align:#(#right #center #left).
+        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
+        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
+                                                                        [exEnd]
 
 
 
      like above, but uses nicer decimal alignments
+                                                                        [exBegin]
+        |v l e myList tabs|
 
-	|v l e myList tabs|
-
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
         
-	tabs := TabulatorSpecification new.
-	tabs unit:#cm.
-	tabs positions:#(1 3 6 9 12).
-	tabs align:#(#right #decimal #decimal #decimal #decimal).
+        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
+        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
+                                                                        [exEnd]
 
 
 
      specifying tabs in inches
-
-	|v l e myList tabs|
+                                                                        [exBegin]
+        |v l e myList tabs|
 
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	tabs := TabulatorSpecification new.
-	tabs unit:#inch.
-	tabs positions:#(0 2 3.5 4 6 8 10 12).
+        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.
+        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).
+        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
+        l := ListView new.
+        l setList:myList expandTabs:false.
+        v := HVScrollableView forView:l.
+        v extent:600@200.
+        v open
+                                                                        [exEnd]
 
 
      if you have the columns available as a collection, 
      setup can be done easier
-
-	|v l e myList tabs|
+                                                                        [exBegin]
+        |v l e myList tabs|
 
-	myList := OrderedCollection new.
+        myList := OrderedCollection new.
 
-	tabs := TabulatorSpecification new.
-	tabs unit:#inch.
-	tabs positions:#(0 2 3.5 4 6 8 10 12).
+        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.
+        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
+        l := ListView new.
+        l setList:myList expandTabs:false.
+        v := HVScrollableView forView:l.
+        v extent:600@200.
+        v open
+                                                                        [exEnd]
 
 
     concrete example, show /etc/passwd in a table:
-        
-	|v l s myList line e htabs tabs fingerEntry|
+                                                                        [exBegin]
+
+        |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).
+        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).
+        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.
+        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:''.
+        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.
+        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
+        l := ListView new.
+        l setList:myList expandTabs:false.
+        v := HVScrollableView forView:l.
+        v extent:600@200.
+        v open
+                                                                        [exEnd]
 "
 ! !
 
@@ -450,5 +457,5 @@
 !MultiColListEntry class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/MultiColListEntry.st,v 1.15 1996-04-25 17:31:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/MultiColListEntry.st,v 1.16 1996-04-27 18:22:18 cg Exp $'
 ! !
--- a/Ruler.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/Ruler.st	Sat Apr 27 20:23:13 1996 +0200
@@ -51,35 +51,39 @@
 
 examples
 "
+                                                                        [exBegin]
     |top ruler|
 
     top := StandardSystemView new.
     ruler := Ruler origin:0.0@0.0 corner:1.0@30 in:top.
     top open
+                                                                        [exEnd]
 
 
   defining paperWidth:
-
+                                                                        [exBegin]
     |top ruler|
 
     top := StandardSystemView new.
     ruler := Ruler origin:0.0@0.0 corner:1.0@30 in:top.
     ruler paperWidthInch:5.   
     top open
+                                                                        [exEnd]
 
 
   hide unit string:
-
+                                                                        [exBegin]
     |top ruler|
 
     top := StandardSystemView new.
     ruler := Ruler origin:0.0@0.0 corner:1.0@30 in:top.
     ruler showUnit:false.
     top open
+                                                                        [exEnd]
 
 
   both horizontal and vertical rulers (as in DrawTool):
-
+                                                                        [exBegin]
     |top hRuler vRuler|
 
     top := StandardSystemView new.
@@ -87,10 +91,11 @@
     vRuler := VerticalRuler origin:0.0@30 corner:30@1.0 in:top.
     vRuler showUnit:false.
     top open
+                                                                        [exEnd]
 
 
   with some 3D effects:
-
+                                                                        [exBegin]
     |top hRuler vRuler|
 
     top := StandardSystemView new.
@@ -100,6 +105,7 @@
     hRuler level:1.
     vRuler level:1.
     top open
+                                                                        [exEnd]
 
   see the DrawTool, for how to make it scroll in sync with some
   other view. 
@@ -409,5 +415,5 @@
 !Ruler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.21 1996-01-15 15:45:45 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.22 1996-04-27 18:22:09 cg Exp $'
 ! !
--- a/TabSpec.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/TabSpec.st	Sat Apr 27 20:23:13 1996 +0200
@@ -56,143 +56,147 @@
 examples 
 "
     Example use (in a ListView):
+                                                                        [exBegin]
+        |listView tabSpec entry|
 
-	|listView tabSpec entry|
-
-	listView := ListView new.
+        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 ).
+        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'.
+        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.
+        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'.
+        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.
+        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'.
+        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
+        listView at:3 put:entry.
+        listView open
+                                                                        [exEnd]
 
 
     defining field positions in millimeter :
+                                                                        [exBegin]
+        |listView tabSpec entry|
 
-	|listView tabSpec entry|
-
-	listView := ListView new.
+        listView := ListView new.
 
-	tabSpec := TabulatorSpecification new.
-	tabSpec unit:#mm.
-	tabSpec positions:#(0 10 20 40).
-	tabSpec align:    #left.          
+        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'.
+        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.
+        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'.
+        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 at:2 put:entry.
 
-	listView open
+        listView open
+                                                                        [exEnd]
 
     defining field widths in millimeter :
+                                                                        [exBegin]
+        |listView tabSpec entry|
 
-	|listView tabSpec entry|
-
-	listView := ListView new.
+        listView := ListView new.
 
-	tabSpec := TabulatorSpecification new.
-	tabSpec unit:#mm.
-	tabSpec widths:#(10 10 20 10).
-	tabSpec align:    #left.        
+        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'.
+        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.
+        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'.
+        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 at:2 put:entry.
 
-	listView open
+        listView open
+                                                                        [exEnd]
 
     defining field widths in pixels :
+                                                                        [exBegin]
+        |listView tabSpec entry|
 
-	|listView tabSpec entry|
-
-	listView := ListView new.
+        listView := ListView new.
 
-	tabSpec := TabulatorSpecification new.
-	tabSpec unit:#pixel.
-	tabSpec widths:#(50 30 30 50).
-	tabSpec align:    #left.        
+        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'.
+        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.
+        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'.
+        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 at:2 put:entry.
 
-	listView open
+        listView open
+                                                                        [exEnd]
 "
 ! !
 
@@ -396,5 +400,5 @@
 !TabulatorSpecification class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/TabSpec.st,v 1.10 1996-04-25 17:31:31 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/TabSpec.st,v 1.11 1996-04-27 18:22:36 cg Exp $'
 ! !
--- a/TabulatorSpecification.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/TabulatorSpecification.st	Sat Apr 27 20:23:13 1996 +0200
@@ -56,143 +56,147 @@
 examples 
 "
     Example use (in a ListView):
+                                                                        [exBegin]
+        |listView tabSpec entry|
 
-	|listView tabSpec entry|
-
-	listView := ListView new.
+        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 ).
+        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'.
+        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.
+        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'.
+        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.
+        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'.
+        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
+        listView at:3 put:entry.
+        listView open
+                                                                        [exEnd]
 
 
     defining field positions in millimeter :
+                                                                        [exBegin]
+        |listView tabSpec entry|
 
-	|listView tabSpec entry|
-
-	listView := ListView new.
+        listView := ListView new.
 
-	tabSpec := TabulatorSpecification new.
-	tabSpec unit:#mm.
-	tabSpec positions:#(0 10 20 40).
-	tabSpec align:    #left.          
+        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'.
+        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.
+        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'.
+        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 at:2 put:entry.
 
-	listView open
+        listView open
+                                                                        [exEnd]
 
     defining field widths in millimeter :
+                                                                        [exBegin]
+        |listView tabSpec entry|
 
-	|listView tabSpec entry|
-
-	listView := ListView new.
+        listView := ListView new.
 
-	tabSpec := TabulatorSpecification new.
-	tabSpec unit:#mm.
-	tabSpec widths:#(10 10 20 10).
-	tabSpec align:    #left.        
+        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'.
+        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.
+        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'.
+        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 at:2 put:entry.
 
-	listView open
+        listView open
+                                                                        [exEnd]
 
     defining field widths in pixels :
+                                                                        [exBegin]
+        |listView tabSpec entry|
 
-	|listView tabSpec entry|
-
-	listView := ListView new.
+        listView := ListView new.
 
-	tabSpec := TabulatorSpecification new.
-	tabSpec unit:#pixel.
-	tabSpec widths:#(50 30 30 50).
-	tabSpec align:    #left.        
+        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'.
+        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.
+        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'.
+        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 at:2 put:entry.
 
-	listView open
+        listView open
+                                                                        [exEnd]
 "
 ! !
 
@@ -396,5 +400,5 @@
 !TabulatorSpecification class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/TabulatorSpecification.st,v 1.10 1996-04-25 17:31:31 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/TabulatorSpecification.st,v 1.11 1996-04-27 18:22:36 cg Exp $'
 ! !
--- a/TwoColumnTextView.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/TwoColumnTextView.st	Sat Apr 27 20:23:13 1996 +0200
@@ -62,21 +62,27 @@
      See more examples there.
      (you may find nice uses for it anyway ...)
 
+                                                                        [exBegin]
      TwoColumnTextView
         openOn:('smalltalk.rc' asFilename contentsOfEntireFile)
         and:('display.rc' asFilename contentsOfEntireFile)
+                                                                        [exEnd]
 
 
+                                                                        [exBegin]
      TwoColumnTextView
         openOn:('display.rc' asFilename contentsOfEntireFile)
         and:('smalltalk.rc' asFilename contentsOfEntireFile)
+                                                                        [exEnd]
 
 
+                                                                        [exBegin]
      TwoColumnTextView
         openOn:('smalltalk.rc' asFilename contentsOfEntireFile)
         label:'smalltalk.rc'
         and:('display.rc' asFilename contentsOfEntireFile)
         label:'display.rc'
+                                                                        [exEnd]
 "
 
     "Created: 20.11.1995 / 13:21:42 / cg"
@@ -164,4 +170,4 @@
 !TwoColumnTextView class methodsFor:'documentation'!
 
 version
-^ '$Header: /cvs/stx/stx/libwidg2/TwoColumnTextView.st,v 1.11 1996-04-25 17:32:19 cg Exp $'! !
+^ '$Header: /cvs/stx/stx/libwidg2/TwoColumnTextView.st,v 1.12 1996-04-27 18:23:13 cg Exp $'! !
--- a/VRuler.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/VRuler.st	Sat Apr 27 20:23:13 1996 +0200
@@ -11,10 +11,10 @@
 "
 
 Ruler subclass:#VerticalRuler
-	 instanceVariableNames:''
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Views-Misc'
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Views-Misc'
 !
 
 !VerticalRuler class methodsFor:'documentation'!
@@ -33,10 +33,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/VRuler.st,v 1.6 1995-11-11 16:29:35 cg Exp $'
-!
-
 documentation
 "
     like a Ruler, but vertical.
@@ -64,6 +60,18 @@
     ]
 ! !
 
+!VerticalRuler methodsFor:'initialization'!
+
+initialize
+    super initialize.
+
+    self width:(font widthOf:'inch').
+
+    "
+     VerticalRuler new open
+    "
+! !
+
 !VerticalRuler methodsFor:'redrawing'!
 
 redraw
@@ -179,15 +187,8 @@
     self redrawEdges
 ! !
 
-!VerticalRuler methodsFor:'initialization'!
-
-initialize
-    super initialize.
+!VerticalRuler class methodsFor:'documentation'!
 
-    self width:(font widthOf:'inch').
-
-    "
-     VerticalRuler new open
-    "
+version
+    ^ '$Header: /cvs/stx/stx/libwidg2/Attic/VRuler.st,v 1.7 1996-04-27 18:22:04 cg Exp $'
 ! !
-
--- a/VerticalRuler.st	Sat Apr 27 20:20:27 1996 +0200
+++ b/VerticalRuler.st	Sat Apr 27 20:23:13 1996 +0200
@@ -11,10 +11,10 @@
 "
 
 Ruler subclass:#VerticalRuler
-	 instanceVariableNames:''
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Views-Misc'
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Views-Misc'
 !
 
 !VerticalRuler class methodsFor:'documentation'!
@@ -33,10 +33,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libwidg2/VerticalRuler.st,v 1.6 1995-11-11 16:29:35 cg Exp $'
-!
-
 documentation
 "
     like a Ruler, but vertical.
@@ -64,6 +60,18 @@
     ]
 ! !
 
+!VerticalRuler methodsFor:'initialization'!
+
+initialize
+    super initialize.
+
+    self width:(font widthOf:'inch').
+
+    "
+     VerticalRuler new open
+    "
+! !
+
 !VerticalRuler methodsFor:'redrawing'!
 
 redraw
@@ -179,15 +187,8 @@
     self redrawEdges
 ! !
 
-!VerticalRuler methodsFor:'initialization'!
-
-initialize
-    super initialize.
+!VerticalRuler class methodsFor:'documentation'!
 
-    self width:(font widthOf:'inch').
-
-    "
-     VerticalRuler new open
-    "
+version
+    ^ '$Header: /cvs/stx/stx/libwidg2/VerticalRuler.st,v 1.7 1996-04-27 18:22:04 cg Exp $'
 ! !
-