*** empty log message ***
authorclaus
Mon, 10 Oct 1994 04:13:51 +0100
changeset 24 6704fad5eb7d
parent 23 1e6bf473d863
child 25 e07adf47d209
*** empty log message ***
2ColTxtV.st
FNmEdtFld.st
FilenameEditField.st
HSlider.st
HorizontalSlider.st
ImageView.st
LEnterFld.st
LabelledEnterField.st
Make.proto
Ruler.st
Slider.st
TwoColumnTextView.st
--- a/2ColTxtV.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/2ColTxtV.st	Mon Oct 10 04:13:51 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -11,17 +11,17 @@
 "
 
 View subclass:#TwoColumnTextView
-         instanceVariableNames:'textView1 textView2'
-         classVariableNames:''
-         poolDictionaries:''
-         category:'Views-Text'
+	 instanceVariableNames:'textView1 textView2'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Views-Text'
 !
 
 TwoColumnTextView comment:'
 COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg2/Attic/2ColTxtV.st,v 1.2 1994-08-07 13:26:26 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/Attic/2ColTxtV.st,v 1.3 1994-10-10 03:13:07 claus Exp $
 '!
 
 !TwoColumnTextView class methodsFor:'documentation'!
@@ -34,19 +34,26 @@
     code-versions, or other one-by-one vievable texts.
 
     Usually, it does not make much sense, to put totally different
-    or different-sized texts into this kind of view.
+    or unrelated texts into this kind of view.
+
+    See subclass DiffTextView for a real class;
+    see ChangesBrowsers compare operation for a real application
+    of this kind of views.
 "
 ! !
 
 !TwoColumnTextView class methodsFor:'instance creation'!
 
 openOn:firstText and:secondText
-    "open up a view showing firstText and secondText"
+    "open up a view showing firstText and secondText side-by-side"
 
      |top v|
 
      top := StandardSystemView label:'differences'.
-     v := HVScrollableView for:self in:top.
+     v := HVScrollableView 
+		for:self 
+		miniScrollerH:true miniScrollerV:false
+		in:top.
      v origin:0.0 @ 0.0 corner:1.0 @ 1.0.
      v scrolledView text1:firstText text2:secondText.
      ^ top open
@@ -141,15 +148,15 @@
     super initialize.
 
     textView1 := TextView origin:0.0 @ 0.0
-                          corner:0.5 @ 1.0
-                              in:self.
+			  corner:0.5 @ 1.0
+			      in:self.
 
     textView1 borderWidth:1.
     textView1 level:0. 
 
     textView2 := TextView origin:0.5 @ 0.0
-                          corner:1.0 @ 1.0
-                              in:self.
+			  corner:1.0 @ 1.0
+			      in:self.
 
     textView2 borderWidth:1.
     textView2 level:0. 
@@ -159,7 +166,7 @@
 
      v := HVScrollableView for:TwoColumnTextView.
      v scrolledView text1:('smalltalk.rc' asFilename readStream contents)
-                    text2:('smalltalk_r.rc' asFilename readStream contents).
+		    text2:('smalltalk_r.rc' asFilename readStream contents).
      v open
     "
 ! !
--- a/FNmEdtFld.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/FNmEdtFld.st	Mon Oct 10 04:13:51 1994 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1994 by Claus Gittinger
               All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg2/Attic/FNmEdtFld.st,v 1.3 1994-08-11 23:48:51 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/Attic/FNmEdtFld.st,v 1.4 1994-10-10 03:13:10 claus Exp $
 '!
 
 !FilenameEditField class methodsFor:'documentation'!
@@ -42,14 +42,14 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg2/Attic/FNmEdtFld.st,v 1.3 1994-08-11 23:48:51 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/Attic/FNmEdtFld.st,v 1.4 1994-10-10 03:13:10 claus Exp $
 "
 !
 
 documentation
 "
-    like a normal editField, but does filename-completion when TAB is
-    pressed.
+    like a normal editField, but does filename-completion on the last word of
+    the contents, when TAB is pressed.
 "
 ! !
 
@@ -58,27 +58,49 @@
 keyPress:key x:x y:y
     "handle tab for filename completion"
 
-    |f matchSet name|
+    |s f matchSet name words|
 
     enabled ifTrue:[
         key == #Tab ifTrue:[
-"/            |f matchSet|
-
-            f := self contents asFilename.
+            s := self contents.
+            "
+             find the last word ...
+            "
+            words := s asCollectionOfWords.
+            f := words last asFilename.
             matchSet := f filenameCompletion.
             matchSet size ~~ 1 ifTrue:[
+                "
+                 more than one possible completion -
+                "
                 self changed:#directory with:f directoryName.
                 device beep
             ].
+            "
+             even with more than one possible completion,
+             f's name is now common prefix
+            "
             name := f asString.
             matchSet size == 1 ifTrue:[
+                "
+                 exactly one possible completion -
+                "
                 f isDirectory ifTrue:[
                     (name endsWith:(Filename separator)) ifFalse:[
                         name := (f construct:'') asString
                     ].
-                ]
+                ].
             ].
-            self contents:name.
+            "
+             construct new contents, by taking
+             last words completion
+            "
+            s := ''.
+            1 to:(words size - 1) do:[:idx |
+                s := s , (words at:idx) , ' '
+            ].
+            s := s , name.
+            self contents:s.
             self cursorToEndOfLine.
             ^ self
         ].
--- a/FilenameEditField.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/FilenameEditField.st	Mon Oct 10 04:13:51 1994 +0100
@@ -21,7 +21,7 @@
 COPYRIGHT (c) 1994 by Claus Gittinger
               All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg2/FilenameEditField.st,v 1.3 1994-08-11 23:48:51 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/FilenameEditField.st,v 1.4 1994-10-10 03:13:10 claus Exp $
 '!
 
 !FilenameEditField class methodsFor:'documentation'!
@@ -42,14 +42,14 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg2/FilenameEditField.st,v 1.3 1994-08-11 23:48:51 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/FilenameEditField.st,v 1.4 1994-10-10 03:13:10 claus Exp $
 "
 !
 
 documentation
 "
-    like a normal editField, but does filename-completion when TAB is
-    pressed.
+    like a normal editField, but does filename-completion on the last word of
+    the contents, when TAB is pressed.
 "
 ! !
 
@@ -58,27 +58,49 @@
 keyPress:key x:x y:y
     "handle tab for filename completion"
 
-    |f matchSet name|
+    |s f matchSet name words|
 
     enabled ifTrue:[
         key == #Tab ifTrue:[
-"/            |f matchSet|
-
-            f := self contents asFilename.
+            s := self contents.
+            "
+             find the last word ...
+            "
+            words := s asCollectionOfWords.
+            f := words last asFilename.
             matchSet := f filenameCompletion.
             matchSet size ~~ 1 ifTrue:[
+                "
+                 more than one possible completion -
+                "
                 self changed:#directory with:f directoryName.
                 device beep
             ].
+            "
+             even with more than one possible completion,
+             f's name is now common prefix
+            "
             name := f asString.
             matchSet size == 1 ifTrue:[
+                "
+                 exactly one possible completion -
+                "
                 f isDirectory ifTrue:[
                     (name endsWith:(Filename separator)) ifFalse:[
                         name := (f construct:'') asString
                     ].
-                ]
+                ].
             ].
-            self contents:name.
+            "
+             construct new contents, by taking
+             last words completion
+            "
+            s := ''.
+            1 to:(words size - 1) do:[:idx |
+                s := s , (words at:idx) , ' '
+            ].
+            s := s , name.
+            self contents:s.
             self cursorToEndOfLine.
             ^ self
         ].
--- a/HSlider.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/HSlider.st	Mon Oct 10 04:13:51 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -19,9 +19,9 @@
 
 HorizontalSlider comment:'
 COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg2/Attic/HSlider.st,v 1.1 1994-08-11 23:53:54 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/Attic/HSlider.st,v 1.2 1994-10-10 03:13:15 claus Exp $
 '!
 
 !HorizontalSlider class methodsFor:'documentation'!
@@ -29,7 +29,7 @@
 copyright
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg2/Attic/HSlider.st,v 1.1 1994-08-11 23:53:54 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/Attic/HSlider.st,v 1.2 1994-10-10 03:13:15 claus Exp $
 "
 !
 
@@ -62,12 +62,8 @@
 
 initStyle
     super initStyle.
-    tallyMarks := 1.
-    style == #iris ifTrue:[
-        tallyLevel := 1.
-    ] ifFalse:[
-        tallyLevel := -1.
-    ]
+    tallyMarks := StyleSheet at:'sliderNTallyMarks' default:1.
+    tallyLevel := StyleSheet at:'sliderTallyLevel' default:-1.    
 ! !
 
 !HorizontalSlider methodsFor:'accessing'!
@@ -111,13 +107,13 @@
      do not create new Rectangle if its the same anyway
     "
     thumbFrame notNil ifTrue:[
-        (ny == thumbFrame top) ifTrue:[
-          (nx == thumbFrame left) ifTrue:[
-            (nh == thumbFrame height) ifTrue:[
-              (nw == thumbFrame width) ifTrue:[ ^ self]
-            ]
-          ]
-        ]
+	(ny == thumbFrame top) ifTrue:[
+	  (nx == thumbFrame left) ifTrue:[
+	    (nh == thumbFrame height) ifTrue:[
+	      (nw == thumbFrame width) ifTrue:[ ^ self]
+	    ]
+	  ]
+	]
     ].
     thumbFrame := Rectangle left:nx top:ny width:nw height:nh
 ! !
--- a/HorizontalSlider.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/HorizontalSlider.st	Mon Oct 10 04:13:51 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -19,9 +19,9 @@
 
 HorizontalSlider comment:'
 COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg2/HorizontalSlider.st,v 1.1 1994-08-11 23:53:54 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/HorizontalSlider.st,v 1.2 1994-10-10 03:13:15 claus Exp $
 '!
 
 !HorizontalSlider class methodsFor:'documentation'!
@@ -29,7 +29,7 @@
 copyright
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg2/HorizontalSlider.st,v 1.1 1994-08-11 23:53:54 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/HorizontalSlider.st,v 1.2 1994-10-10 03:13:15 claus Exp $
 "
 !
 
@@ -62,12 +62,8 @@
 
 initStyle
     super initStyle.
-    tallyMarks := 1.
-    style == #iris ifTrue:[
-        tallyLevel := 1.
-    ] ifFalse:[
-        tallyLevel := -1.
-    ]
+    tallyMarks := StyleSheet at:'sliderNTallyMarks' default:1.
+    tallyLevel := StyleSheet at:'sliderTallyLevel' default:-1.    
 ! !
 
 !HorizontalSlider methodsFor:'accessing'!
@@ -111,13 +107,13 @@
      do not create new Rectangle if its the same anyway
     "
     thumbFrame notNil ifTrue:[
-        (ny == thumbFrame top) ifTrue:[
-          (nx == thumbFrame left) ifTrue:[
-            (nh == thumbFrame height) ifTrue:[
-              (nw == thumbFrame width) ifTrue:[ ^ self]
-            ]
-          ]
-        ]
+	(ny == thumbFrame top) ifTrue:[
+	  (nx == thumbFrame left) ifTrue:[
+	    (nh == thumbFrame height) ifTrue:[
+	      (nw == thumbFrame width) ifTrue:[ ^ self]
+	    ]
+	  ]
+	]
     ].
     thumbFrame := Rectangle left:nx top:ny width:nw height:nh
 ! !
--- a/ImageView.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/ImageView.st	Mon Oct 10 04:13:51 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -11,17 +11,17 @@
 "
 
 View subclass:#ImageView
-         instanceVariableNames:'image'
-         classVariableNames:''
-         poolDictionaries:''
-         category:'Views-Misc'
+	 instanceVariableNames:'image'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Views-Misc'
 !
 
 ImageView comment:'
 COPYRIGHT (c) 1993 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg2/ImageView.st,v 1.4 1994-08-05 01:23:58 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/ImageView.st,v 1.5 1994-10-10 03:13:21 claus Exp $
 '!
 
 !ImageView class methodsFor:'startup'!
@@ -40,60 +40,60 @@
 
     img := Image fromFile:aFileName.
     img notNil ifTrue:[
-        imageView image:img.
+	imageView image:img.
 
-        "define an icon view showing little version of image.
-         Since some window managers cannot handle this correctly (twm),
-         this is only done when running on an IRIS"
+	"define an icon view showing little version of image.
+	 Since some window managers cannot handle this correctly (twm),
+	 this is only done when running on an IRIS"
 
-        (true "(OperatingSystem getSystemType = 'iris')" and:[self defaultStyle == #iris]) ifTrue:[
-            icn := self new.
+	(true "(OperatingSystem getSystemType = 'iris')" and:[self defaultStyle == #iris]) ifTrue:[
+	    icn := self new.
 
-            "for now; should somehow get access to preferred iconview extent ..."
-            icnW := 86.
-            icnH := 68.
+	    "for now; should somehow get access to preferred iconview extent ..."
+	    icnW := 86.
+	    icnH := 68.
 
-            ((img width <= icnW) and:[img height <= icnH]) ifTrue:[
-                icn extent:(img width @ img height).
-                mag := 1 @ 1
-            ] ifFalse:[
-                magX := icnW / img width.
-                magY := icnH / img height.
+	    ((img width <= icnW) and:[img height <= icnH]) ifTrue:[
+		icn extent:(img width @ img height).
+		mag := 1 @ 1
+	    ] ifFalse:[
+		magX := icnW / img width.
+		magY := icnH / img height.
 
-                "scale image"
+		"scale image"
 "
-                mag := magX @ magY.
+		mag := magX @ magY.
 "
-                "preserve ratio"
+		"preserve ratio"
 " 
-                mag := (magX min:magY) asPoint.
+		mag := (magX min:magY) asPoint.
 " 
 " "
-                mag := (magX max:magY) asPoint.
+		mag := (magX max:magY) asPoint.
 " "
 
-                icn extent:((img width @ img height) * mag) rounded.
-            ].
-            "start icon as a low prio bg process -
-             so magnification and color allocation will not hurt us ..."
+		icn extent:((img width @ img height) * mag) rounded.
+	    ].
+	    "start icon as a low prio bg process -
+	     so magnification and color allocation will not hurt us ..."
 
-            ProcessorScheduler isPureEventDriven ifFalse:[
-                wg := WindowGroup new.
-                icn windowGroup:wg.
-                wg addTopView:icn.
-                wg startup.
-                wg process priority:4.
-            ].
-            top iconView:icn.
-        ].
+	    ProcessorScheduler isPureEventDriven ifFalse:[
+		wg := WindowGroup new.
+		icn windowGroup:wg.
+		wg addTopView:icn.
+		wg startup.
+		wg process priority:4.
+	    ].
+	    top iconView:icn.
+	].
     ].
 
     top open.
 
     icn notNil ifTrue:[
-        [ 
-            icn image:(img magnifyBy:mag).
-        ] forkAt:4
+	[ 
+	    icn image:(img magnifyBy:mag).
+	] forkAt:4
     ].
 
     "ImageView openOn:'bitmaps/garfield.gif'"
@@ -107,17 +107,17 @@
 
 You can display an image with:
 
-        (ImageView new image:anImage) realize
+	(ImageView new image:anImage) realize
 
-        i.e.
+	i.e.
 
-        (ImageView new image:(Image fromFile:''bitmaps/garfield.gif'')) realize
-        (ImageView new image:(Image fromFile:''bitmaps/dano.tiff'')) realize
-        (ImageView new image:(Form fromFile:''SBrowser.xbm'')) realize
+	(ImageView new image:(Image fromFile:''bitmaps/garfield.gif'')) realize
+	(ImageView new image:(Image fromFile:''bitmaps/dano.tiff'')) realize
+	(ImageView new image:(Form fromFile:''SBrowser.xbm'')) realize
 
-        or simply by:
+	or simply by:
 
-        ImageView startOn:''bitmaps/garfield.gif''
+	ImageView startOn:''bitmaps/garfield.gif''
 
 "
 ! !
@@ -135,17 +135,17 @@
     |clrMap|
 
     image notNil ifTrue:[
-        image := image on:device.
-        self clear.
-        self foreground:Black background:White.
-        (image depth == 1) ifTrue:[
-            clrMap := image colorMap.
-            clrMap notNil ifTrue:[
-                self paint:(clrMap at:2) on:(clrMap at:1).
-            ]
-        ].
-        self function:#copy.
-        self displayOpaqueForm:image x:(0 - viewOrigin x) y:(0 - viewOrigin y)
+	image := image on:device.
+	self clear.
+	(image depth == 1) ifTrue:[
+	    clrMap := image colorMap.
+	    clrMap notNil ifTrue:[
+		self paint:(clrMap at:2) on:(clrMap at:1).
+	    ] ifFalse:[
+		self paint:Color black on:Color white.
+	    ]
+	].
+	self displayOpaqueForm:image x:(0 - viewOrigin x) y:(0 - viewOrigin y)
     ]
 ! !
 
@@ -156,15 +156,22 @@
 
     image := anImage.
     anImage notNil ifTrue:[
-        self cursor:Cursor wait.
-        shown ifTrue:[
-            self redraw
-        ].
-        self contentsChanged.
-        self cursor:(Cursor normal).
+	self cursor:Cursor wait.
+	shown ifTrue:[
+	    self redraw
+	].
+	self contentsChanged.
+	self cursor:(Cursor normal).
     ].
 
-    "ImageView new realize image:(Image fromFile:'bitmaps/claus.gif')"
+    "
+     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
+    "
 !
 
 image
--- a/LEnterFld.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/LEnterFld.st	Mon Oct 10 04:13:51 1994 +0100
@@ -23,7 +23,7 @@
 
 An EnterField with a name.
 
-$Header: /cvs/stx/stx/libwidg2/Attic/LEnterFld.st,v 1.1 1994-08-05 01:24:02 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/Attic/LEnterFld.st,v 1.2 1994-10-10 03:13:24 claus Exp $
 written winter 91 by claus
 '!
 
@@ -49,10 +49,18 @@
 
 !LabelledEnterField methodsFor:'accessing'!
 
+disable
+   textField disable
+!
+
 label:aString
     labelField label:aString
 !
 
+contents
+    ^ textField contents
+!
+
 contents:aString
     textField contents:aString
 ! !
--- a/LabelledEnterField.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/LabelledEnterField.st	Mon Oct 10 04:13:51 1994 +0100
@@ -23,7 +23,7 @@
 
 An EnterField with a name.
 
-$Header: /cvs/stx/stx/libwidg2/LabelledEnterField.st,v 1.1 1994-08-05 01:24:02 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/LabelledEnterField.st,v 1.2 1994-10-10 03:13:24 claus Exp $
 written winter 91 by claus
 '!
 
@@ -49,10 +49,18 @@
 
 !LabelledEnterField methodsFor:'accessing'!
 
+disable
+   textField disable
+!
+
 label:aString
     labelField label:aString
 !
 
+contents
+    ^ textField contents
+!
+
 contents:aString
     textField contents:aString
 ! !
--- a/Make.proto	Mon Oct 10 04:13:44 1994 +0100
+++ b/Make.proto	Mon Oct 10 04:13:51 1994 +0100
@@ -19,7 +19,8 @@
 		ImageView.$(O)		\
 		ImgEditV.$(O)		\
 		FNmEntrBox.$(O)		\
-	        FNmEdtFld.$(O)
+	        FNmEdtFld.$(O)		\
+		TextBox.$(O)
 
 obsolete:				\
 		RetButton.$(O)          \
@@ -80,6 +81,9 @@
 Slider.$(O):            Slider.st $(I)/Scroller.H $(VIEW)
 HSlider.$(O):           HSlider.st $(I)/Slider.H $(I)/Scroller.H $(VIEW)
 
+StepSlider.$(O):        StepSlider.st $(I)/ScrollBar.H $(VIEW)
+StepHSlider.$(O):       StepHSlider.st $(I)/HScrBar.H $(VIEW)
+
 FormEdtView.$(O):       FormEdtView.st $(VIEW)
 LEnterFld.$(O):         LEnterFld.st $(VIEW)
 
@@ -87,7 +91,9 @@
 FNmEdtFld.$(O):		FNmEdtFld.st $(I)/EditField.H $(I)/ETxtView.H $(VIEW)
 
 ImageView.$(O):		ImageView.st $(VIEW)
-ImgEdtV.$(O):		ImgEdtV.st $(VIEW)
+ImgEdtV.$(O):		ImgEdtV.st $(I)/ImageView.H $(VIEW)
 
 MCLEntry.$(O):		$(OBJECT)
 TabSpec.$(O):		$(OBJECT)
+
+TextBox.$(O):           TextBox.st $(ENTERBOX)
--- a/Ruler.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/Ruler.st	Mon Oct 10 04:13:51 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -11,19 +11,19 @@
 "
 
 View subclass:#Ruler
-         instanceVariableNames:'fgColor metric paperWidth paperHeight'
-         classVariableNames:''
-         poolDictionaries:''
-         category:'Views-Interactors'
+	 instanceVariableNames:'fgColor metric paperWidth paperHeight'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Views-Interactors'
 !
 
 Ruler comment:'
 COPYRIGHT (c) 1991 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
 a Ruler for page layout.
 
-$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.6 1994-08-05 01:24:05 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.7 1994-10-10 03:13:35 claus Exp $
 
 written oct 91 by claus
 '!
@@ -31,11 +31,31 @@
 !Ruler methodsFor:'accessing'!
 
 metric:aSymbol
-    "set the metric"
+    "set the metric. The argument may be either #inch or #mm"
+
+    aSymbol ~~ metric ifTrue:[
+	metric := aSymbol.
+	shown ifTrue:[
+	    self redraw
+	]
+    ]
+!
+
+paperWidthInch:inches
+    "set the width of the document"
 
-    metric := aSymbol.
+    paperWidth := inches.
     shown ifTrue:[
-        self redraw
+	self redraw
+    ]
+!
+
+paperWidthMM:millis
+    "set the width of the document"
+
+    paperWidth := self millimeterToInch:millis.
+    shown ifTrue:[
+	self redraw
     ]
 ! !
 
@@ -47,18 +67,21 @@
     |x pixelPerMM pixelPerInch mod pos shortLen veryShortLen longLen charY
      top paperWidthMM paperWidthPixel xOrigin labelRight marg|
 
-    self fill:viewBackground.
+    shown ifFalse:[^ self].
+
+"/    self fill:viewBackground.
+    self clear.
 
     xOrigin := viewOrigin x.
 
     paperWidthPixel := (self inchToPixel:paperWidth) rounded.
     (xOrigin + width > paperWidthPixel) ifTrue:[
-        self paint:(Color darkGrey).
-        self fillRectangleX:paperWidthPixel - xOrigin y:0
-                      width:(width - (paperWidthPixel - xOrigin)) height:height.
-        self paint:fgColor.
-        self displayLineFromX:paperWidthPixel - xOrigin y:0
-                          toX:paperWidthPixel - xOrigin y:height
+	self paint:(Color darkGrey).
+	self fillRectangleX:paperWidthPixel - xOrigin y:0
+		      width:(width - (paperWidthPixel - xOrigin)) height:height.
+	self paint:fgColor.
+	self displayLineFromX:paperWidthPixel - xOrigin y:0
+			  toX:paperWidthPixel - xOrigin y:height
     ].
 
     self paint:fgColor.
@@ -71,66 +94,66 @@
     marg := 3. "character shift"
 
     (metric == #mm) ifTrue:[
-        "centimeter - long blibs every centimeter; short ones every half"
+	"centimeter - long blibs every centimeter; short ones every half"
 
-        paperWidthMM := self inchToMillimeter:paperWidth.
-        pixelPerMM := self millimeterToPixel:1.
-        pos := 5.
-        labelRight := marg + (font widthOf:'cm').
+	paperWidthMM := self inchToMillimeter:paperWidth.
+	pixelPerMM := self millimeterToPixel:1.
+	pos := 5.
+	labelRight := marg + (font widthOf:'cm').
 
-        x := (pixelPerMM * pos - xOrigin) rounded.
-        [(x < width) and:[pos <= paperWidthMM]] whileTrue:[
-            (mod == 1) ifTrue:[
-                self displayLineFromX:x y:top
-                                  toX:x y:(top + shortLen)
-            ] ifFalse:[
-                x < labelRight ifFalse:[
-                    self displayLineFromX:x y:top
-                                      toX:x y:(top + longLen).
-                    self displayString:(pos // 10) printString
-                                     x:(x + marg)
-                                     y:charY
-                ]
-            ].
-            mod := (mod + 1) \\ 2.
-            pos := pos + 5.
-            x := (pixelPerMM * pos - xOrigin) rounded 
-        ].
-        self displayString:'cm ' x:marg y:charY.
+	x := (pixelPerMM * pos - xOrigin) rounded.
+	[(x < width) and:[pos <= paperWidthMM]] whileTrue:[
+	    (mod == 1) ifTrue:[
+		self displayLineFromX:x y:top
+				  toX:x y:(top + shortLen)
+	    ] ifFalse:[
+		x < labelRight ifFalse:[
+		    self displayLineFromX:x y:top
+				      toX:x y:(top + longLen).
+		    self displayString:(pos // 10) printString
+				     x:(x + marg)
+				     y:charY
+		]
+	    ].
+	    mod := (mod + 1) \\ 2.
+	    pos := pos + 5.
+	    x := (pixelPerMM * pos - xOrigin) rounded 
+	].
+	self displayString:'cm ' x:marg y:charY.
     ].
     (metric == #inch) ifTrue:[
-        "inches - long blibs every inch; short ones every half; very
-         short ones every quarter"
+	"inches - long blibs every inch; short ones every half; very
+	 short ones every quarter"
 
-        pixelPerInch := self inchToPixel:1.
-        pos := 0.25.
-        labelRight := marg + (font widthOf:'inch').
+	pixelPerInch := self inchToPixel:1.
+	pos := 0.25.
+	labelRight := marg + (font widthOf:'inch').
 
-        x := (pixelPerInch * pos - xOrigin) rounded.
-        veryShortLen := longLen // 4.
-        [(x < width) and:[pos <= paperWidth]] whileTrue:[
-            (mod == 0) ifTrue:[
-                x < labelRight ifFalse:[
-                    self displayLineFromX:x y:top
-                                      toX:x y:(top + longLen).
-                    self displayString:pos asInteger printString
-                                     x:(x + marg)
-                                     y:charY
-                ]
-            ] ifFalse:[
-                (mod == 2) ifTrue:[
-                    self displayLineFromX:x y:top
-                                      toX:x y:(top + shortLen)
-                ] ifFalse:[
-                    self displayLineFromX:x y:top
-                                      toX:x y:(top + veryShortLen)
-                ]
-            ].
-            mod := (mod + 1) \\ 4.
-            pos := pos + 0.25.
-            x := (pixelPerInch * pos - xOrigin) rounded
-        ].
-        self displayString:'inch ' x:marg y:charY.
+	x := (pixelPerInch * pos - xOrigin) rounded.
+	veryShortLen := longLen // 4.
+	[(x < width) and:[pos <= paperWidth]] whileTrue:[
+	    (mod == 0) ifTrue:[
+		x < labelRight ifFalse:[
+		    self displayLineFromX:x y:top
+				      toX:x y:(top + longLen).
+		    self displayString:pos asInteger printString
+				     x:(x + marg)
+				     y:charY
+		]
+	    ] ifFalse:[
+		(mod == 2) ifTrue:[
+		    self displayLineFromX:x y:top
+				      toX:x y:(top + shortLen)
+		] ifFalse:[
+		    self displayLineFromX:x y:top
+				      toX:x y:(top + veryShortLen)
+		]
+	    ].
+	    mod := (mod + 1) \\ 4.
+	    pos := pos + 0.25.
+	    x := (pixelPerInch * pos - xOrigin) rounded
+	].
+	self displayString:'inch ' x:marg y:charY.
     ].
     self redrawEdges
 
@@ -144,14 +167,29 @@
     fgColor := Black.
     self height:(font height + font descent + font descent). 
     (Language == #english) ifTrue:[
-        metric := #inch
+	metric := #inch
     ] ifFalse:[
-        metric := #mm
+	metric := #mm
     ].
     paperWidth := 8.5.
-    paperHeight := 11
+    paperHeight := 11.
 
-    "Ruler new realize"
+    "
+     take a smaller font
+    "
+    font := (Font family:(font family)
+		    face:(font face)
+		   style:(font style)
+		    size:8) on:device.
+
+    "
+     Ruler new open
+    "
+!
+
+reinitialize
+    super reinitialize.
+    font := font on:device.
 ! !
 
 !Ruler methodsFor:'metric conversions'!
--- a/Slider.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/Slider.st	Mon Oct 10 04:13:51 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -19,9 +19,9 @@
 
 Slider comment:'
 COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg2/Slider.st,v 1.5 1994-08-05 01:24:08 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/Slider.st,v 1.6 1994-10-10 03:13:40 claus Exp $
 '!
 
 !Slider class methodsFor:'documentation'!
@@ -29,7 +29,7 @@
 copyright
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg2/Slider.st,v 1.5 1994-08-05 01:24:08 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/Slider.st,v 1.6 1994-10-10 03:13:40 claus Exp $
 "
 !
 
@@ -64,12 +64,9 @@
 
 initStyle
     super initStyle.
-    tallyMarks := 1.
-    style == #iris ifTrue:[
-        tallyLevel := 1.
-    ] ifFalse:[
-        tallyLevel := -1.
-    ]
+
+    tallyMarks := StyleSheet at:'sliderNTallyMarks' default:1.
+    tallyLevel := StyleSheet at:'sliderTallyLevel' default:-1.    
 ! !
 
 !Slider methodsFor:'accessing'!
@@ -113,13 +110,13 @@
      do not create new Rectangle if its the same anyway
     "
     thumbFrame notNil ifTrue:[
-        (ny == thumbFrame top) ifTrue:[
-          (nx == thumbFrame left) ifTrue:[
-            (nh == thumbFrame height) ifTrue:[
-              (nw == thumbFrame width) ifTrue:[ ^ self]
-            ]
-          ]
-        ]
+	(ny == thumbFrame top) ifTrue:[
+	  (nx == thumbFrame left) ifTrue:[
+	    (nh == thumbFrame height) ifTrue:[
+	      (nw == thumbFrame width) ifTrue:[ ^ self]
+	    ]
+	  ]
+	]
     ].
     thumbFrame := Rectangle left:nx top:ny width:nw height:nh
 ! !
--- a/TwoColumnTextView.st	Mon Oct 10 04:13:44 1994 +0100
+++ b/TwoColumnTextView.st	Mon Oct 10 04:13:51 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -11,17 +11,17 @@
 "
 
 View subclass:#TwoColumnTextView
-         instanceVariableNames:'textView1 textView2'
-         classVariableNames:''
-         poolDictionaries:''
-         category:'Views-Text'
+	 instanceVariableNames:'textView1 textView2'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Views-Text'
 !
 
 TwoColumnTextView comment:'
 COPYRIGHT (c) 1994 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg2/TwoColumnTextView.st,v 1.2 1994-08-07 13:26:26 claus Exp $
+$Header: /cvs/stx/stx/libwidg2/TwoColumnTextView.st,v 1.3 1994-10-10 03:13:07 claus Exp $
 '!
 
 !TwoColumnTextView class methodsFor:'documentation'!
@@ -34,19 +34,26 @@
     code-versions, or other one-by-one vievable texts.
 
     Usually, it does not make much sense, to put totally different
-    or different-sized texts into this kind of view.
+    or unrelated texts into this kind of view.
+
+    See subclass DiffTextView for a real class;
+    see ChangesBrowsers compare operation for a real application
+    of this kind of views.
 "
 ! !
 
 !TwoColumnTextView class methodsFor:'instance creation'!
 
 openOn:firstText and:secondText
-    "open up a view showing firstText and secondText"
+    "open up a view showing firstText and secondText side-by-side"
 
      |top v|
 
      top := StandardSystemView label:'differences'.
-     v := HVScrollableView for:self in:top.
+     v := HVScrollableView 
+		for:self 
+		miniScrollerH:true miniScrollerV:false
+		in:top.
      v origin:0.0 @ 0.0 corner:1.0 @ 1.0.
      v scrolledView text1:firstText text2:secondText.
      ^ top open
@@ -141,15 +148,15 @@
     super initialize.
 
     textView1 := TextView origin:0.0 @ 0.0
-                          corner:0.5 @ 1.0
-                              in:self.
+			  corner:0.5 @ 1.0
+			      in:self.
 
     textView1 borderWidth:1.
     textView1 level:0. 
 
     textView2 := TextView origin:0.5 @ 0.0
-                          corner:1.0 @ 1.0
-                              in:self.
+			  corner:1.0 @ 1.0
+			      in:self.
 
     textView2 borderWidth:1.
     textView2 level:0. 
@@ -159,7 +166,7 @@
 
      v := HVScrollableView for:TwoColumnTextView.
      v scrolledView text1:('smalltalk.rc' asFilename readStream contents)
-                    text2:('smalltalk_r.rc' asFilename readStream contents).
+		    text2:('smalltalk_r.rc' asFilename readStream contents).
      v open
     "
 ! !