If you have any suggestions or additions on this theme, let me know about it.
version
and documentation
there.
version
methods comment consists of a single
version line - this is created automatically by the source code
control system (RCS or SCCS). In case of error reports, this string
should be used to identify the exact version of the class.
The documentation
methods comment describes the class, its uses
and (if of public interrest) its instance and classvariables.
In some classes, you will find an examples
method.
This will consist of a comment giving typical uses (ready to select & doIt).
These methods consist of comments only; they are not meant to be executed.
(actually, if evaluated, they will return the receiver; since empty methods
are semantically equivalent to a '^ self'
method).
The
SystemBrowser
automatically shows the documentation text
(found either in documentation
or in the class comment)
whenever a class is selected.
Thus, to be nice to other people browsing through the system,
you should add a short description of what your class is about in these
documentation methods.
Dont worry about memory usage when creating documentation methods - simple methods
which return self (as empty methods do) all share a common piece of code,
so there will NOT be thousands of empty methods filling
up your memory.
(to be exact: there is some little overhead per method created
by the method object itself - not by the methods code.
However, for production code, all documentation
methods can be easily
removed. Also, stc provides a command line argument, to skip
all methods in the documentation category;
to allow building more compact class libraries.)
If you dont like the above, use the classes comment string, which also does not eat up memory (it used to before release 2.10.3 of Smalltalk/X).
BTW: from the authors experience, you should not delay documentation too much. Write them down as soon as possible - otherwise you may not find the time to do so later - or you may simply forget to do it. Also, keep in mind that it may take more time to add those comments later, since you may have to reflect about what is going on. From our experience, the later the documentation is written in a project, the higher is its cost.
Please, use this type of comment, since ST/X provides special printout features, which allow you to create printed documentation automatically, based on these comments (see the SystemBrowsers printOut protocol functions).
select:aBlock
"return a new collection with all elements from the receiver, for which
the argument aBlock evaluates to true"
|newCollection|
newCollection := self species new.
self do:[:each |
(aBlock value:each) ifTrue:[newCollection add:each].
].
^ newCollection
"
#(1 2 3 4) select:[:e | e odd]
(1 to:10) select:[:e | e even]
"
By convention, global variables and class variables should start with an upper case character - other variables and selectors by a lower case chracter.
In many situations, a global can be eliminated by
by passing additional method arguments
(which may even be an advantage later,
offering more possibilities for reuse of a method).
Almost all globals can easily be
replaced by a private classVariable instead and access be provided to
other parts via class methods.
sum := sum + 1. "add one to sum"
is stupid and filling your methods with this kind of "information"
actually makes your code less readable.
However, if you use special tricks or uncommon constructs, you should add a comment describing what is going on - for yourself and for others.
foo
"this method performs some fooBar.
Sometimes even baz is done"
doingBar
ifTrue:[
self fooBar.
[doingBaz]
whileTrue:[
self baz].
self moreFooBar.
1 to:10 do:[:index |
1 to:10 do:[:index2 |
self doMore]]]
ifFalse:[
...
and so on]
This style of indentation is seen often in ST-80 code.
(the ST-80 formatter seems to automatically produce output in this format).
ifTrue:
and whileTrue:
right behing the receiver (as below).
foo
"this method performs some fooBar.
Sometimes even baz is done"
doingBar ifTrue:[
self fooBar.
[doingBaz] whileTrue:[
self baz
].
self moreFooBar.
1 to:10 do:[:index |
1 to:10 do:[:index2 |
self doMore
]
]
] ifFalse:[
...
and so on
]
Also, variations are possible; for example, the opening brackets of blocks
can be put onto a separate line, as in:
foo
"this method performs some fooBar.
Sometimes even baz is done"
doingBar ifTrue:
[
self fooBar
[doingBaz] whileTrue:
[
self baz
].
self moreFooBar.
1 to:10 do:
[:index |
1 to:10 do:
[:index2 |
self doMore
]
]
]
ifFalse:
[
...
and so on
]
However, this seems to spread the code for even small methods quite a bit.
To many programmers, this makes the readability worse.
Many other styles are possible, however, whichever you choose, follow these rules:
Copyright © Claus Gittinger Development & Consulting, all rights reserved
(cg@ssw.de)