prev back next

Classic Smalltalk Bugs

Note

The biggest part of this document has been taken from the Prime time freeware collection (assuming it is freeware, and it can be included here) and reformatted for HTML.
If there are any legal reasons that prohibit the distribution of this paper with this documentation, please let me know..

Some of the material in this paper is ST-80 or ST-V specific, and I have added sections (between horizontal lines) where differences to ST/X or additional facts apply.

Claus (cg@ssw.de)

Contents



Classic Smalltalk Bugs


compiled by Ralph Johnson -- University of Illinois at Urbana-Champaign

Every programming system is prone to certain kinds of bugs. A good programmer learns these bugs, and how to avoid them. Smalltalk is no different. Smalltalk eliminates lots of bugs that are common in other languages, such as bugs in linear search algorithms. (Just use do:) However, it has its own set of classic bugs, which every new Smalltalk programmer runs into.

There are several reasons to collect classic bugs. The first is that it will help experienced programmers test and debug programs, and can help us design better programs in the first place. Second, if we teach these bugs up front then people should learn to be good programmers faster. Third, perhaps we can redesign the system to eliminate some of these bugs, or we can write checking tools to spot them automatically.

Bug 1: Variable-sized classes

Set, Dictionary, and OrderedCollection are variable-sized classes that grow. They grow by making a copy of themselves and "becoming" the copy. If you add new instance variables to a subclass then you have to make sure that these instance variables get copied, too, or else you will mysteriously lose the values of the instance variables at random points in time.

Smalltalk-80 R4.0 (and probably some earlier versions) has a copyEmpty: method in Collection that you are supposed to override if you make a subclass of Collection that adds instance varaibles. The solution to this bug is to write a version of copyEmpty: for your class.

It has been suggested that it would be easy to write a tool that checked that every new subclass of Collection that added instance variables also defined a method for copyEmpty:.


The same caution has to be taken in ST/X. In addition, many variable collections have been implemented as keeping the variable part in a separate array (instead of using the indexable vars). The reason is that the #become: operation can be quite expensive in direct pointer smalltalk implementations which ST/X is (you dont have to fully understand this :-). Therefore, all collections copy-methods should also copy their container-array, otherwise both the original and the copy might reference the same element-container - leading to much confusion later ...

Bug 2: "add:" returns its argument

For every collection that grows, add: returns its argument, not the receiver, and people usually assume that it returns its receiver. Thus, they write
    (c add: x) add: y
when they should really write
    c add: x; add: y
or else
    c add: x. c add: y
Note that this is one of the good uses for yourself, you can write
    (Set new 
	add: x; 
	add: y;
	...;
	yourself) 
to make sure that you have the new set.

Note that there are good reasons why add: returns its arguments, and even if there weren't, it is a very, very bad mistake to implement add: so that it returns the receiver, and so confuse every other Smalltalk programmer on the planet. Making add: return its argument often keeps you from resorting to temps, because you can create the argument to add: on the fly, and then do other things with it after the add:. If you want to access the collection, you can do it with yourself or cascaded messages, as described above.

Bug 3: Changing collection while iterating over it

You should never, never, never iterate over a collection which the iteration loop somehow modifies. Elements of the collection will be moved during the iteration, and elements might be missed or handled twice. Instead, make a copy of the collection you are iterating over, i.e.
    aCollection copy do: [:each | aCollection remove: each]
is a good program, but if you leave out the copy then it isn't.

Mario Wolczko suggested a solution that catches this problem the instant it occurs (at some performance penalty of course). The solution is to change the collection classes. Each iteration method enters that collection into a set of collections being iterated over (IteratedCollections), executes the block, then removes the collection from the set. Collections are usually (only?) modified using at:put: or basicAt:put:, so these are overriden to check that the collection is not in IteratedCollections. If it is, an error is signalled. You can either use this technique all the time, or you can just install these classes when you are testing and debugging your program. These changes are packaged in a file Iterator-check.st that is available on the Manchester and Illinois servers. On the Illinois server, it is in /pub/MANCHESTER/manchester/4.0/Iterator-check.st.

Bug 4: Modifying copies of collections

It is common for an object to have an accessing method that returns a collection of objects that you can modify. However, sometimes an object will return a copy of this collection to keep you from modifying it. Instead, you are probably supposed to use messages that will change the collection for you. The problem is that this is often poorly documented, and a person who likes to modify collections directly will run into problems. See "ScheduledControllers scheduledControllers" for an example.

The solution is to either provide better documentation, to claim that nobody is allowed to modify copies of collections returned from other objects, or to have objects that don't want their collections modified to return immutable versions of the collections that will give an error if you try to modify them.

Bug 5: Missing ^ (return)

It is very easy to leave off a return caret (^) on an expression. If there is no return at the end of a method, Smalltalk returns the receiver of the method. It only takes one missing return to mess up a long chain of method invocations.

Bug 6: Class instance creation methods

Writing a correct instance create method is apparently non-trivial. The correct way to do it is to have something like
    new
      ^ super new initialize
where you redefine initialize in each class to initialize that class's instance variables. In turn, initialize is defined as an instance method
    initialize
      super initialize "to initialize inherited instance variables"

      "initialize variables that I define"
      ...
There are lots of ways to do this wrong. Perhaps the most common is to forget the return, i.e. to write
    initialize
       super new initialize
The result is that you have the class where you want the instance of the class. This is a special case of bug #5.

Another error is to make an infinite loop by writing

    initialize
      ^ self new initialize
If Smalltalk doesn't respond when you think it should, press ^C (that is Control-C) to get the debugger. If the debugger shows a stack of new messages then you know you made this mistake.

Finally, you should only define new once for each class hierarchy and let subclasses inherit the method. If you redefine it in each class then you will reinitialize the new object many times, wasting time and perhaps memory.

One way to keep this from happening is to make the new method in Object send init, and have the initialize method in Object do nothing. Of course, sometimes the version of initialize that you define has arguments, and this wouldn't help those cases. It is probably better to rely on education to eliminate this kind of error.

Bug 7: Assigning to classes

    OrderedCollection := 2
is perfectly legal Smalltalk, but does dreadful things to your image. This bug could be eliminated if the compiler gave a warning when you assigned to a global variable that contained a class.
In ST/X, the incremental compiler outputs a warning

Bug 8: "become:"

become: is a very powerful operation. It is easy to destroy your image with it. Its main use is in growing collections (see bug #1), since it can make every reference to the old version of a collection become a reference to the new, larger version. It has slightly different semantics in Smalltalk/V and Smalltalk-80, since
    x become: y
causes every reference to x and y to be interchanged in Smalltalk-80, but does not change any of the references to y in Smalltalk/V.

Suppose that you want to eliminate all references to an object x. Saying:

    x become: nil
works fine in Smalltalk/V, but will cause every reference to nil to become a reference to x in Smalltalk-80. This is a sure calamity. You want x to become a new object with no references, such as in
    x become: String new

The semantic of become: in ST/X is the same as in Smalltalk-80. However, ST/X provides another method (becomeNil) to clear references. Using nil, smallIntegers or living contexts as either receiver or argument to become: is not allowed in ST/X.

BTW: become: is a very time consuming operation in ST/X (and maybe other smalltalk implementations). Please avoid the use of it.


Bug 9: Recompiling bugs in Smalltalk/V

It is easy to have references to obsolete objects in Smalltalk/V if you change code without cleaning things up carefully. For example, the associations whose keys are the referenced names in the Pool Dictionary are stored in the CompiledMethods at compile time. If you create a new version of the Pool Dictionary and install it by simple assignment then the compiled methods still refer to the old associations.

If you substitute a new instance of Dictionary or replace, rather than update an association in a pool dictionary, you have to recompile all methods using variables scoped to that Pool.

This is is also annoying when using ENVY, where the methods are under strict control. Perhaps Pool Dictionaries should be be first-class versioned pre-requisites of Classes, just like the class definition.

BTW we are using/VPM 1.4 with ENVY 1.3

1. If you prune & graft a subtree of your class structure you have to make sure that all referencing methods are recompiled. Otherwise you will run (or your customer, because this is only detected at run time) into an Deleted class error message. Thomas Muhr posted a "Bite" a while ago to handle this problem for Smalltalk/V 286.


In ST/X, deleted classes are kept as anonymous classes (i.e. they are no longer anchored in the Smalltalk dictionary). This means, that existing instances can still live and operate properly, but the SystemBrowser will not be able to show and/or modify any code.
The class will of course be physically deleted by the garbage collector, once the instance is no longer referenced.

The same is true, if a classes instance layout changes (for example, when adding an instance variable). Existing instances will remain to exist as instances of the (now obsolete) old class.

You can find removed classes with the MemoryUsageView; look for entries marked as "removed" or "obsolete" (of course, you can also enumerate all behaviors and filter them manually).


Bug 10: Opening windows

Smalltalk-V and the older versions of Smalltalk-80 do not return to the sender when a new window is opened. Thus, any code after a message to open a window will never be executed. This is the cause of much frustration. For example, if you try to open two windows at once, i.e.
    TextPane new open.
    TextPane new open
in Smalltalk-V and
    aScheduledWindow1 open.
    aScheduledWindow2 open
in Smalltalk-80, then you will get only one open window, and one forgotten piece of code. This problem has been fixed in Objectworks/Smalltalk R 4.1, so the above code will create two windows as you would expect.

The fix for earlier versions of Smalltalk-80 is to use the openNoTerminate method to open the window, which does not transfer control to it. A useful trick is to store the new window in a global variable so you can test it.

Aad Nales says that the fix for Smalltalk/VV is to fork the creation of the new window.

    [Textpane open] fork.
If this is not what the programmer wants then it is probably necessary to hack the dispatcher code and remove the dropSenderChain message, which is the ultimate cause of the problem.
This does not apply to ST/X.
In ST/X, open always returns immediately (and actually forks a new process for the new view, if its a topview), while openModal does not return until the new view is closed.

Bug 11: Blocks

Blocks are very powerful, and it isn't hard for programmers to get into trouble trying to be too tricky. To compound problems, the two versions of Smalltalk have slightly different semantics for blocks, and one of them often leads to problems.

Originally blocks did not have truly local variables. The block parameters were really local variables in the enclosing method. Thus,

    | x y |

    x := 0.
    (1 to: 100) do: [:z | x := x + z]
actually had three temporaries, x, y, and z. This leads to bugs like the following
    someMethod
	| a b  |

	a := #(4 3 2 1).
	b := SortedCollection sortBlock: [:a :b | a someOperation: b].
	b addAll: a.
	Transcript show: a.
When elements are added to b, the sortBlock is used to tell where to put them, but this will change a and b. addAll: is OK, but the a that gets displayed on the transcript will be an integer, not an array.

Early versions of Smalltalk-80 (2.4 and before?) implemented blocks like this, and Smalltalk/V still does. However, in current PPS implementations, blocks are close to being closures. You can declare variables local to a block, and the names of the block parameters are local to the block. Most people agree that this is a much better definition of blocks than the original one. Nevertheless, people planning to use Smalltalk/V should realise that it has a different semantics for blocks.

This difference can lead to some amusing problems. For example, here is some code written by someone who had obviously learned Scheme.

    | anotherArray aBlockArray |

    aBlockArray := Array new: 4.
    anotherArray := #(1 2 4 8).

    1 to: 4 do: [ :anIndex |
	aBlockArray at: anIndex put: [ (anotherArray at: anIndex) * 2 ]].
The programmer expected that each block would be stored in the array along with its own value of anIndex. If anIndex were just a local variable of the method then this will not work. It assumes that each execution of the block gets its own version of anIndex, and Smalltalk/V and old Smalltalk-80 actually make each execution share the same version.

So, if you are using Smalltalk/V then be careful not to reuse the names of arguments of blocks unless you know that the blocks are not going to have their lives overlap. Thus,

    aCollect do: [:i | ...].
    bCollect do: [:i | ...].
is probably OK because do: does not store its argument, so the blocks will be garbage by the time the method is finished. However, if the first block were stored in a variable somewhere and evaluated during the execution of the second block then problems would probably occur.
ST/X's block semantics is much like ST-80 R4 blocks.

Bug 12: Cached Menus

Menus are often defined in a class method, where they are created and stored in a class variable or a class instance variable. The method will look something like this
    initializeMenu
     ...
Note that accepting the method does *not* change the menu. You have to execute the method to change the class variable or class instance variable. Often the initializeMenu method is invoked by the class method initialize. This can lead to the strange effect that you can initialize the menu by deleting the class and filing it in again, but otherwise you don't seem to be able to change the menu (because you haven't figured out that you should really be executing the initializeMenu method).

To make matters worse, it is possible that each instance of the controller, or model, or whatever has the menu, stores its own copy of the menu in an instance variable. If that is the case then it is not enough to execute initializeMenu, you also must cause each object to reinitialize its own copy of the menu. It is often easier to just delete the objects and recreate them.

Often a class will have a #flushMenus method to clear out all menus. Typically the method that fetches the menu will check to see if it is nil and invoke initializeMenu if it is. So, flushMenus will just nil out the variable holding the menu. The best way to figure out what is happening is to look at all uses of the variable. Smalltalk experts rarely have problems with this bug, but it often confuses novices.

Caching is a very common technique in Smalltalk for making programs more efficient in both time and space. Caching of menus is one of the simplest uses of caches, and other uses can create more subtle bugs.

Bug 13: Smalltalk/V class library

Thomas Muhr makes these comments about bugs in the Smalltalk/V class library that you should know if you want to keep your programs fast and correct.

  1. Never use symbols to label objects if you are dealing with many objects. This will slow down your system to an almost dead halt. Use strings instead.

  2. Never use Sets when you can otherwise assure the uniqueness. Look at the implementation of add: for Sets and you'll know what I mean: on every add: the new element is compared to all others resulting into a nonlinear time for adding to Sets.

  3. Do not think that if you collect: something from a SortedCollection, that your result will be sorted as the origin, unless you use the default sortBlock. This is one of the bugs provided by the language vendor


These bugs are not known in ST/X's or Smalltalk-80.


Many thanks to the many people who contributed bugs or solutions to bugs to the list. These include
 muhr@opal.cs.tu-berlin.de (Thomas Muhr)
 steinman@is.morgan.com (Jan Steinman)
 knight@mrco.carleton.ca (Alan Knight)
 mario@cs.man.ac.uk (Mario Wolczko)
 peterg@netcom.com (Peter Goodall)
 Aad Nales 
 scrl@otter.hpl.hp.com (Simon Lewis)
 msmith@volcano.ma30.bull.com (Mike Smith)
 dai@mrco.carleton.ca (Naci Dai)
 dcr0@speedy.enet.dec.com (Dave Robbins)
 randy@tigercat.den.mmc.com (Randy Stafford)
 Hubert.Baumeister@mpi-sb.mpg.de (Hubert Baumeister)
 eliot@dcs.qmw.ac.uk (Eliot Miranda)
 dmm@aristotle.ils.nwu.edu (donald)
 amir@is.morgan.com (Amir Bakhtiar)
 Kurt Piersol 
 sullivan@ticipa.ti.com (Michael Sullivan)
 terry@zoe.network23.com (Terry)
 brent@uwovax.uwo.ca (Brent Sterner)
 frerk@informatik.uni-kl.de
 nicted@toz.buffalo.ny.us (Nicole Tedesco)
 riks@ogicse.ogi.edu (Rik Fischer Smoody)
 marten@feki.toppoint.de (Marten Feldtmann) 
 mst@vexpert.dbai.tuwien.ac.at (Markus Stumptner)

Additional hints (from ST/X testers)

Storing into array literals

A very subtle and hard to debug bug is encountered, when a method returns or passes a literal array constant to someone else, which stores into this array using at:put: type messages.
Since array literals are kept and used from a methods literal table, the next call of the same method will return the same (now modified) array.

This bug is especially hard to find, since the methods sourcecode does not reflect that the array constant has changed - the browser will continue to show the original sourcecode.
For example:

Object subclass:#ArrayLiteralBugDemonstration
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Examples-Bugs'
!

!ArrayLiteralBugDemonstration methodsFor:'bug1'!

literalArray
    ^ #('hello' 'there')
!

buggy1
    "
     thats obvious ...
    "
    Transcript show:'literalArray initially returns: ';
	       showCr:(self literalArray) displayString.

    (self literalArray) at:2 put:'wrong'.

    Transcript show:'literalArray now returns: ';
	       showCr:(self literalArray) displayString.

    Transcript showCr:'but the source is still:'.
    Transcript cr.
    Transcript showCr:(self class compiledMethodAt:#literalArray) source.

    "
     ArrayLiteralBugDemonstration new buggy1
    "
!

buggy2
    "
     less obvious ... hard to track down
    "
    Transcript show:'literalArray initially returns: ';
	       showCr:(self literalArray) displayString.

    Transcript show:'literalArray modified: ';
	       showCr:(self literalArray replaceAll:'hello' by:'bug') displayString.

    Transcript show:'literalArray now returns: ';
	       showCr:(self literalArray) displayString.

    Transcript showCr:'but the source is still:'.
    Transcript cr.
    Transcript showCr:(self class compiledMethodAt:#literalArray) source.

    "
     ArrayLiteralBugDemonstration new buggy2
    "
! !

To help tracking down this bug, ST/X's incremental compiler can optionally create array literals as immutable (i.e. not to be allowed to be changed) objects.
This option is controlled by the classVariable ArraysAreImmutable in the Parser class. Setting this to true will turn array literals to immutable arrays, which raise an error when stored into.

Since this is incompatible to Smalltalk-80, the default is false. (Also, to the beginner, turning this on may create a bit of confusion if the array protocol is tried in a workspace/inspector).

The same mechanism will be implemented for literal strings and byteArrays in future versions, if this feature is appreciated by ST/X users.
Stc does not (currently) create immutable array literals; since this feature is of main use during development (in contrast to production code), there may be no need to ever implement it in stc.

Commenting comments

Sometimes, if you want to remove a piece of code by putting comments around, you reintroduce statements which used to be hidden in another comment by accident.
For example:
Original code:
	...
	some statement
	...
	"bad statement - disabled by a comment"
	...
	more statements
after you place your comment around the code, as in:
	...
"
	some statement
	...
	"bad statement - disabled by a comment"
	...
	more statements
"
and accept, you have really reintroduced the previously disabled "bad statement".

Also, comments in the original code may now be parsed as smalltalk code. Look at:

	...
	foo := foo squared.     "some stupid comment"
	...
and the commented version:
	...
"
	foo := foo squared.     "some stupid comment"
"
which now has the comment being compiled as smalltalk code.

This is really bad, because you often want to disable debug or print code (which was written during development), but keep that code around for future debugging or as hints for others.


To help getting around this problem, ST/X offers end-of-line comments, which do not nest, but instead treat everything (including comments) to the end of line as a comment. These comments are written as:
	"/  everything after this is a comment
This character sequence was choosen after code studies of existing programs; it was found to not create backward compatibility problems (however, there could be programs around, for which this is not true).

Of course, these comments are not defined in the smalltalk language standard; therefore you should be careful in using them, if you plan to port your code to other smalltalks.
The ST/X compilers output a warning, if such a non standard language extension is used.

(BTW: it is well known in the computer society, that comment syntax using the same characters as delimiters is a bad thing. Any upcoming ANSI standard should take care of this).


Redefined private methods

In some situations, methods assumed to be private get redefined, although they really should not (this happens especially when working in groups). How can I make certain that I reach my own method in a send.

There is no standard smalltalk solution to this problem.


Beside self- and super-sends, ST/X offers another one, called the here send. Using here as the receiver of a message send, will result in a method lookup which starts in the class in which the method was defined. Semantically, it is much like a super-send, with the exception, that a super-send starts the search in the superclass of the defining class.
Thus, you can use:
	here myPrivateMethod.
to get the local method - even if the receiver is an instance of a subclass, and the subclass redefined myPrivateMethod.

WARNING:

Keep in mind that here-sends limit the reusability of your classes, since methods using them will never get into any redefined subclass method.
Actually, here sends look much like normal function calls (except, that if no local target method is found, the search is continued in the superclass).
Both stc and the incremental compiler offer compilation flags to turn here sends into regular self sends. (of course, you will get a 'using nonstandard features' warning too).

Notice, that ST/X offers method privacy too. But these will lead to a signal raise at run time instead (if called). Also, method privacy is defined by the target method, while here sends are made up at the callers side.


Avoid the use of Array>>add

Although arrays support adding elements via the add: selector, you should try hard to avoid using it. It is very very slow. (For this reason, some other systems do not allow Array>>add:).

Since arrays are fixed size collections, changing the size implies a become: operation. Due to technical reasons, this operation may be very time consuming in ST/X. If your collection has to grow a lot, use orderedCollections instead of arrays. Another alternative is to use a WriteStream to generate the collection.
The above is also true for Strings, ByteArrays, FloatArrays and any other fix size collection.

For example:

	|a|

	a := Array new.
	1 to:10 do:[:i |
	    a add:i
	]
is up to 500 times slower than both:
	|t a|

	t := OrderedCollection new.
	1 to:10 do:[:i |
	    t add:i
	].
	a := t asArray
and:
	|s a|

	s := WriteStream on:(Array new).
	1 to:10 do:[:i |
	    s nextPut:i
	].
	a := s contents
Beside add:, watch out for other methods which may be based upon add:. For example: addAll:, addFirst:, addLast:.

Slow collection methods

You should be careful when constructing big collections using add-type methods. Some of these methods show a square time (and space) behavior, thus performing slow if applied to big collections.
For example, the copyWith: methods create a new collection, with one more element. If you use this in a loop, individually adding elements, you may wonder where your time goes.

Methods to be careful about in this respect are (among many others):

in general, all methods which copy or regrow collections are possible performance eaters.

In these cases, it is much better to preallocate the target collection, or work on a temporary container, which is tuned for this type of operation.

For example, Set, Dictionary, OrderedCollection and others allow you to specify an initial size, so that resizing is not needed later.
compare:

     |s|

     s := Set new.
     10000 timesRepeat:[
	s add:i asFloat
     ]  
to:
     |s|

     s := Set new:10000.
     10000 timesRepeat:[
	s add:i asFloat
     ]  
the second piece of code is about 10-20% faster. (Set is already tuned for resizing, therefore, the effect is not too dramatic.)
As an extreme example, compare:
     |a|

     a := Array new.
     1 to:10000 do:[:i |
	a := a copyWith:i
     ]  
to:
     |tmp a|

     tmp := OrderedCollection new.
     1 to:10000 do:[:i |
	tmp add:i
     ].
     a := tmp asArray
the second is about 5 to 7 times faster.

If you do not know the final size in advance, use a Stream. These are also tuned to handle this kind of growing.
compare:

     |s|

     s := ''.
     10000 timesRepeat:[
	s := s , 'more '
     ]  
to the (much faster):
     |s|

     s := WriteStream on:String new.
     10000 timesRepeat:[
	s nextPutAll:'more '
     ].
     s contents 
the second piece of code is about 5 to 10 times faster.

Wrong color drawing

When drawing in a view, be careful to keep a reference to the color used. Otherwise, the garbage collector could free the color, which implies freeing of the corresponding color index in the displays colormap. The next allocated color may reuse this index and therefore change the appearance (i.e. the color) of the previously displayed graph.
Example:
	...
	aGC paint:(Color red:15 green:15 blue:100).
	aGC displayLineFrom:(0@0) to:(100@100).
	...
	aGC paint:(Color red:50 green:50 blue:0).
	aGC displayLineFrom:(100@0) to:(0@100).
	...
is supposed to draw a cross, with different colors used. However, if a garbage collect occurs after drawing the first line, the first color may be reclaimed and the same colormap index be reused for the second color. The first line will therefore be shown in the same color on the screen.

Avoid this, by keeping references to all used colors somewhere in your view.

Of course, this reference must be kept as long as the view is visible; therefore a method local will usually not be the right place for it. Use an instance variable of an object which lives as long as the view is open.

Additional hints (from comp.lang.smalltalk)

These have still to be reformatted into HTML. More messages will be added here, as they arrive from the net.

From: jaeck@alc.com (William A. Jaeck)
Subject: Re: Classic Smalltalk bugs
Organization: Ascent Logic Corporation, San Jose, CA
Date: Fri, 14 Aug 1992 18:22:27 GMT

Here is a Smalltalk bug which bit me just this morning:

I had created a subclass of OrderedCollection with an instance
method called with:. This is supposed to do the same thing as
add:.

Then, I implemented a class method called with:with: as

   with: arg1 with: arg2

	 ^ self with: arg1; with: arg2

This ended up producing a result as if I had implemented it as

	^ self with: arg2

The correct implementation of with:with: is, of course

	^ (self with: arg1) with: arg2


From: riks@ogicse.cse.ogi.edu (Rik Fischer SmOOdy) Newsgroups: comp.lang.smalltalk Subject: Classes as a dirty trick to get globals. Ralph: here's one for the list. A common "dirty trick" is to use a class with class methods as an implementation for a "globally known" object which is expected to be unique. This class is never expected to be instantiated: instances would have no capabilities except those inherited by default from #Object. The trick usually works, but it qualifies as design by accident. A tyro might study the object as an example and be misled. (It is important to encourage re-use to keep the visible structure as comprehensible as we can) Future engineers might decide that there needs to be another "instance" of this globally known object. I have seen an example (identity of perpetrators withheld to protect the unconvicted) where the second instance was implmented as a sub-class, with numerous methods over-written to access a different class variable. On Smalltalk V/MAC, a quick scan found (Color MTrap Compiler and LCompiler ) Smalltalk80 V4 comes with DefineOpcodePool but that may have other redeeming social value. The most egregious examples have come with other installed packages. Mr. Manners instead approves of the way Smalltalk80 uses the globally published objects named Transcript, Undeclared, and even Smalltalk itself. Rik Fischer Smoody smOOdynamics Systems Made Outa Objects 2400 NE 25th, Suite 800 Portland, OR 97212 riks@cse.ogi.edu 503-249-8300 If the programming environment made it almost automatic to maintain distinguished SortedCollections in the "global" dictionary known as Smalltalk, we would see several examples of SortedCollections installed there, without having elements added to them. Their methodDictionary's would be used as Classes' are now. Naming is important, especially for us humans to get mnemonic value. I personally do not like contrived names that prepend the company of creation, the current author's name, the place in some hierarchy, nor short letters to grandmother. Naming is an art. Practice it well. Let's suppose that they implemented a class CheckBook. On the assumption that you only have ONE CheckBook, they put all the behavior in the class. It had class variables #Balance and #CheckNumber. Later, a second bank account was opened (or they got married?) and a second CheckBook was needed. A subclass CheckBookB was created, with class variables #BalanceB and #CheckNumberB. All methods that accessed either variable were over-written. I think there should have been a class CheckBook with an instance installed as #MyCheckBook (or something). The second instance could then simply be instantiated and installed as #MyCheckBookB. The extra maintainence hassle of installing the first one would have been repaid many times over with the second instantiation.
Newsgroups: comp.lang.smalltalk Date: Thu, 3 Nov 1994 15:57:53 +0100 Sender: SmallTalk programming language discussion From: Niklas Bjornerstedt Subject: Common bugs After seeing certain types of bug repeat themselves in many systems I got the idea of compiling a list of the most common ones. The bugs I am interested in are the ones that make it to the end user, not the ones that irritate the developer. To start everything off I'll present my favorites: 1. "self halt" left in the code. 2. delays left in the code. (A friend of mine "optmized" a routine in Object Pascal from 32 to 4 seconds by removing a delay he had forgotten during development.) 3. String handling code unable to handle TwoByteString (ParcPlace Smalltalk). Almost every major package I know of has had bugs in their handling of TwoByteString. 4. Forgetting to test against NULL in arguments and return-values. I could go on but I think this is enough to get things going. Now I invite others to add to this list. I will compile and repost the list if I get any responces. /Niklas ------------------------------------------------------------------------- Niklas Bjornerstedt Entra Data AB, Sweden tel: +46-8-80 97 00 Gustavslundsv. 151 G fax: +46-8-26 04 76 S-161 36 Bromma email: niklas.bjornerstedt@entra.se
From scrl Mon Jul 20 08:28:42 1992 Relay-Version: version Notes 2.8 87/9/11; site otter.hpl.hp.com From: scrl@otter.hpl.hp.com (Simon Lewis) Date: Mon, 20 Jul 1992 07:28:42 GMT Date-Received: Mon, 20 Jul 1992 07:28:42 GMT Subject: Re: Classic Smalltalk bugs Message-ID: <2610024@otter.hpl.hp.com> Organization: Hewlett-Packard Laboratories, Bristol, UK. Path: otter!scrl Newsgroups: comp.lang.smalltalk Posting-Version: version Notes 2.8 87/9/11; site otter.hpl.hp.com References: <1992Jul18.113941.30839@m.cs.uiuc.edu> Not so much a bug, but a common mistake I think :- (a < b) ifTrue: [a := a + 1]. "Works fine." (a < b) whileTrue: [a := a + 1]. "Is an error. Should be [a < b]." I've seen people do this, and take an awfully long time to figure out why the second one doesn't work, particularly if they *know* the system implements whileTrue:, but have a less than perfect understanding of *how* it works. Simon Lewis, HP Labs, Bristol, UK.
From johnson@m.cs.uiuc.edu Sat Jul 18 12:39:41 1992 Relay-Version: version Notes 2.8 87/9/11; site otter.hpl.hp.com From: johnson@m.cs.uiuc.edu (Ralph Johnson) Date: Sat, 18 Jul 1992 11:39:41 GMT Date-Received: Sat, 18 Jul 1992 12:06:01 GMT Subject: Classic Smalltalk bugs Message-ID: <1992Jul18.113941.30839@m.cs.uiuc.edu> Organization: University of Illinois, Dept. of Comp. Sci., Urbana, IL Path: otter!hpltoad!hpopd!hplextra!hpscdc!news.dtc.hp.com!hp-col!sdd.hp.com!ux1.cso.uiuc.edu!m.cs.uiuc.edu!johnson Newsgroups: comp.lang.smalltalk Lines: 27 We just saw one; if you add an instance variable to a variable-sized class then you have to make sure that if an instance grows then the variable gets copied. Another classic bug is that a class instance creation method leaves out the return statement, so it is super new init instead of ^super new init The result is that you have the class where you want the instance of the class. It seems to me that half the time I leave off a return, it is in an instance creation method. Ralph Johnson -- University of Illinois at Urbana-Champaign