back next

List of useful selectors

Introduction

The following is just a keyword list, to give you a hint what to search for. Use the SystemBrowser, to find implementors and/or senders of those messages.

Looking at the comments in the implementors will give you more information about what is done in those methods; looking at the senders code, you will learn more on how those messages are typically used.

Notice, that the browser supports wildcard searches - thus you can search for patterns such as "at*" or even "n*ut*".

A note to beginners:

what you see below is NOT smalltalk syntax, but a small fraction of messages understood by classes in the system; there is much more.

For smalltalk syntax and the basic classes/messages, see

Also, you will find demonstration code and examples for some concepts in the directory "doc/coding". A step-by-step introduction into the view classes is found in the document "viewintro", which is also available via the Launchers info & help / programming submenu.

In the list below, the characters '[' and ']' mean: optional; thus:

foo:[bar:]
means, that both methods for foo: and foo:bar: are provided.
(for beginners: this means that there are two methods in the system: foo: and foo:bar:)

This list is far from complete, currently there are more than 9000 methods in more than 500 classes to be found in the base system (not counting many goodies, demos and additional classes).

Happy browsing ...

copying objects


shallowCopy                     - shallow copy (the copy references the same objects)
deepCopy                        - deep copy (referenced objects are also deep-copied)
				  Handles recursive and self-referencing structures.
copy                            - usually defaults to a shallow copy

general queries


class                           - return an objects class
respondsTo:                     - ask if message is understood
isMemberOf:                     - ask if instance of a class (not recommended)
isKindOf:                       - ask if instance of a class or subclass (not recommeneded)
isNil                           - true, if object is nil
notNil                          - true, if object is not nil
isClass                         - true, if object is a class
isNumber                        - true, if object is a stream
isXXXX                          - some more of this
respondsToArithmetic            - true, if object understands arithmetic messages

allOwners                       - returns a collection of objects referencing the receiver
allInstances                    - returns a collection of a classes instances
allDerivedInstances             - returns a collection of a classes and subclasses insts

comparing


general

==                              - identical;  i.e. the same object
~~                              - not identical
=                               - equal; i.e. same structure and/or value(s) 
~=                              - not equal
hash                            - return a key for hashing
identityHash                    - return a key for hashing on identity

magnitudes

>                               - greater than
>=                              - greater or equal
<                               - less than
<=                              - less or equal

between:and:                    - test if in a range
min:                            - minimum
max:                            - maximum

arithmetic (numbers)


+                               - addition
-                               - difference
*                               - product
/                               - division - tends to convert to float
//                              - truncating division - returns integer
\\                              - modulu 

abs                             - absolute value
negated                         - negated value

rounded                         - round to nearest integer
truncated                       - truncate towards zero
ceiling                         - round toward positive infinity
floor                           - round toward negative infinity

asFloat                         - coerce to float
asInteger                       - coerce to integer (i.e. truncates)

log:                            - logarithm
sin                             - sine
cos                             - cosine
raiseTo:                        - raise to power
sqrt                            - square root

even                            - true if even
odd                             - true if odd
sign                            - signum (-1, 0, 1)
positive                        - true if positive
negative                        - true if negative

bitwise operations (integers)


bitAnd:                         - bitwise and
bitOr:                          - bitwise or
bitXor:                         - bitwise exclusive or
bitInvert                       - bitwise complement
bitShift:                       - shift

logical operations (booleans)


&                               - logical and
|                               - logical or
not                             - logical not

and:                            - non evaluating logical and
or:                             - non evaluating logical or

collections


sizing

size                            - number of elements
isEmpty / notEmpty              - true/false if collection is empty

adding

add:                            - add a new element
addAll:                         - add all elements of argument
at:put:                         - store element into collection
atAllPut:                       - fill
atAll:put:                      - fill parts
addFirst:                       - add at beginning
addLast:                        - add at end

removing

remove:[ifAbsent:]              - remove an element [with opt. error handler]
removeAll:                      - remove all
removeFirst                     - remove first element
removeLast                      - removeLast element
removeKey:                      - remove a key

accessing

at:                             - retrieve at index/key
at:ifAbsent:                    - retrieve, with handler if index is absent
first                           - retrieve first element
last                            - retrieve last element

testing

includes:                       - true, if element is in the collection
includesAny:                    - true, if any is in the collection
includesAll:                    - true, if all are in the collection
occurrencesOf:                  - return number of occurrences of an element
includesKey:                    - return true, if key is valid
indexOf:[ifAbsent:]             - search and return position using = (indexable collections)
identityIndexOf:[ifAbsent:]     - search and return position using == (indexable collections)

iterating

do:                             - enumerate collection elements
keysAndValuesDo:                - same, but pass keys and values to block
reverseDo:                      - in reverse order
collect:                        - enumerate elements, collect results
select:[ifNone:]                - enumerate elements, collect some elements
reject:                         - enumerate elements, collect some elements
inject:into:                    - enumerate and accumulate some result
findFirst:                      - find first/last element for which a check returns true 
findLast:
with:do:                        - enumerate two collections in one loop
with:collect:

converting

asArray                         - return an array with same elements
asOrderedCollection             - return an orderedCollection with same elements
asSortedCollection              - return a sortedCollection with same elements
asSet                           - return a set with same elements
asBag                           - return a bag with same elements
readStream                      - return a stream to read elements
writeStream                     - return a stream to write into collection

sorting

sort[:]                         - inplace sort [with optional sort criteria]
topologicalSort[:]              - full search (slow) [with optional sort block]
reverse                         - reverse elements order

copy (copy & replace - non destructive)

copyFrom:                                       - copy to the end
copyTo:                                         - copy from beginning
copyFrom:to:                                    - copy part
copyWith:                                       - copy and append
copyWithout:                                    - copy and remove
copyWithoutIndex:                               - copy and remove (indexable collections)

copyReplaceFrom:[to:][with:][startingAt:]       - copy and replace in the copy

copy                                            - copy all
deepCopy
shallowCopy

replacing (destructive)

replaceFrom:[to:][with:][startingAt:]           - replace elements
replaceAll:by:                                  - search & replace

string specials

,                                       - concatenation
paddedTo:[with:]                        - padding [with optional fill character]
leftPaddedTo:[with:]

asUppercase                             - copy and make copy uppercase
asLowercase                             - copy and make copy lowercase

asNumber                                - read number from string
asFileName

match:                                  - (simple) regular expression match
startsWith:                             - query for prefix
endsWith:                               - query for suffix
findString:[startingAt:[ifAbsent:]]     - substring search
spellAgainst                            - spelling difference

sameAs:                                 - compare ignoring case

countWords                              - simple scanning
asCollectionOfWords                     - separate into individual words
asCollectionOfLines                     - separate at line boundaries
withoutSpaces                           - copy & remove leading & trailing spaces
withoutSeparators                       - copy & remove leading & trailing whitespace

indexOfSeparator[StartingAt:]           - search for any whitespace
indexOfNonSeparator                     - search for non whitespace

asStringWith:from:to:compressTabs:final:- concatenate many strings

printing & storing


printing

printOn:                        - basic low level object printing
				  Does NOT output quotes around strings, so it
				  can be used directly to print into a file.

print                           - print receiver on standard output (Stdout)
printNewline                    - same, with a newline
printNL                         - same for short

errorPrint                      - print receiver on standard error (Stderr)
errorPrintNewline               - same, with a newline
errorPrintNL                    - same for short

printString                     - a string for printing (uses #printOn:)
displayString                   - same as printString, but used when 
				  is to be shown in a view (such as an inspector).
				  Different from printString in some classes.

printStringRadix:               - (integers) print in different radix

Number displayRadix:            - set the radix used in displayString

formatted printing:

printOn:paddedTo:[with:]        - print and pad output on the right
				  [with optional fill character]
printOn:leftPaddedTo:[with:]    - print and pad output on the left
printStringPaddedTo:[with:]     - return a right padded printstring  
printStringLeftPaddedTo:[with:] - return a left padded printstring  

storing:

storeOn:                        - store a textual representation.
				  Warning: this is slow, creates huge files and
					   does not handle self references.
readFrom:                       - retrieve an object stored with 'storeOn:'

storeBinaryOn:                  - stores  in a binary representation
				  (handles recursive and self referencing objects)
readBinaryFrom:                 - retrieves an object stored with 'binaryStoreOn:'

object dependencies:


addDependent:                   - make another object be a dependent
removeDependent:                - remove a dependent
dependents                      - get dependents
changed:[with:]                 - notify dependents of a change
broadcast:[with:]               - broadcast a message
update:[with:][from:]           - sent to dependents

debugging:


alerts:

warn:                           - pops up a warning box
notify:                         - pops up a notifier
information:                    - pops up an information box
confirm:                        - asks yes/no questions

debugging:

halt                            - raise halt signal - usually ends in debugger
halt:                           - halt with message
error                           - raise error signal - usually ends in debugger
error:                          - error with message

inspect                         - to have a deeper look into any object
basicInspect                     

advanced debugging:

MessageTracer trace:selector:     - to trace sends of a selector to an object
MessageTracer trap:selector:      - to trape send of a selector to an object
MessageTracer untrap:[selector:]  - remove trace or trap

MessageTally spyOn:               - execution profile

special object manipulations


instSize                        - returns number of named instance variables
instVarAt:                      - returns a named instance variable (do not use)
instVarAt:put:                  - set a named instance variable (never use)

become:                         - become another object - and vice versa
becomeNil                       - effectively destroy an object

changeClassTo:                  - for dynamic inheritance

handling errors:


handle:do:                      - define a signal handler for an evaluation
				  handler does #return, #returnWith:, #restart or #resume
				  (see Exception)
catch:                          - catch signals while evaluating (i.e. ignore)
handlerBlock:                   - defines a handler block for a signal

ex return[:]                    - return from an exception [with optional value]
ex restart                      - restart execution after an exeption
ex proceed[With:]               - continue execution from an exception [with optional value]

signal raise                    - raise an exception

Object doesNotUnderstandSignal  - some common signals
Number divisionByZeroSignal
Float domainErrorSignal 
PipeStream brokenPipeSignal 
Socket brokenConnectionSignal
Object abortSignal

Object noHandlerSignal          - raised for unhandled signals

Object errorSignal              - parent of all signals handling this one als handles all others
Number arithmeticSignal         - parent of all arithmetic signals

program control:


basic control:

ifTrue:[ifFalse:]               - simple if
ifFalse:[ifTrue:]

whileTrue:                      - loop test at entry
whileFalse:

whileTrue                       - condition only
whileFalse

doUntil:                        - loop test at end
doWhile:

loop                            - loop forever
loopWithExit                    - and with exit

timesRepeat:                    - counted loop

to:[by:]do:                     - loop with index

evaluating blocks:

value                           - evaluate without
value:[value:[value:]]          - evaluate with arguments (up to 4)
valueWithArguments:             - evaluate with arguments from an array
valueWithExit                   - evaluate with exit possibility
valueOnUnwindDo:                - with cleanup actions on unwind
valueNowOrOnUnwindDo:           - with cleanup in any case
valueUninterruptably            - evaluate with interrupts blocked

message sending / method evaluation:

perform:[with:[with:]]          - perform; for non-constant selector sends
perform:withArguments:          - with arguments from an array
perform:ifNotUnderstood:        - save perform with handler 
perform:inClass:withArguments:  - perform, with class for lookup (super-send)

processes (also called lightweight processes or threads)


creation:

fork                            - create a process to execute in parallel
forkAt:prio                     - with any priority
newProcess                      - create, but dont run

Processor activeProcess         - get the current process
Processor activePriority        - get the current priority

control:

suspend                         - suspend a process
resume                          - resume a process
terminate                       - terminate a process
terminateNoSignal               - quick terminate a process
priority[:]                     - get/set priority

interruptWith:                  - interrupt a process

semaphores, sharedQueues and delays:

wait[WithTimeout:]              - suspend process to wait on semaphore [with optional timeout]
signal                          - wakeup processes waiting on semaphore
signalIf                        - wakeup but only if being waited upon
critical:                       - critical regions (mutual exclusion)

next                            - controlled access to sharedQueues
nextPut:

Delay forSeconds:               - create a Delay object
Delay forMilliseconds:

wait                            - suspend process to wait on delay
resume                          - premature wakeup of a delay

calling context chain:

thisContext                     - the context of the current method
				  (this is not a message, but a pseudo variable)
return[:]                       - return a context (with value)
restart                         - restart a context
resume                          - continue execution in a context
unwind[:]                       - return with cleanup actions

files


asFilename                      - convert string to filename

exists                          - check existance of a file
copyTo:                         - copy a file
renameTo:                       - rename a file

file and stream i/o


FileStream oldFileNamed:        - open an existing file
FileStream readonlyFileNamed:   - open for readonly
FileStream newFileNamed:        - open/create for writing

aFilename readStream            - stream on a file (given the name) for reading
aFilename writeStream           - for writing

collection readStream           - stream on a collection for reading
collection writeStream          - for writing

binary                          - read bytes (as opposed to characters)

atEnd                           - check for end-of-stream

reading:

next[:]                         - read next (n) element(s)

peek                            - look ahead
nextPeek                        - read and look ahead
peekFor:                        - look ahead and compare

upTo:                           - read up-to some element
upToEnd                         - read till end is reached

skip:                           - skip
skipFor:                        - skip up-to
skipThrough:                    - skip up-to and including
skipAny:                        - skip all from a collection
skipToAll:                      - skip until arg matches (string search)

writing:

nextPut:                        - append an element
next:put:                       - append an element repeated
nextPutAll:[startingAt:to:]     - append (part of) a collection

file stream specials:

readWait[WithTimeout:]          - wait for data to become available for reading
writeWait[WithTimeout:]         - wait till write is possible without blocking

canReadWithoutBlocking          - check for data being available for reading
canWriteWithoutBlocking         - check for write possible

ioctl:[with:]                   - perform ioctl
blocking:                       - turn on/off blocking I/O
buffered:                       - turn on/off buffered I/O

reading/writing character streams:

nextLine                        - read a line (external streams)
nextWord                        - read a word (external streams)
nextChunk                       - read a chunk in fileIn format (external streams)

nextPutLine:                    - append a line plus newline character

peekForLineStartingWith:        - search for & return next matching line
peekForLineStartingWithAny:     - same, but match any of a collection

upToSeparator                   - read up-to next whitspace (character streams)

skipSpaces                      - skip all spaces (character streams)
skipSeparators                  - skip whitespace (character streams)
skipSeparatorsExceptCR          - skip whitespace, stop at line end (character streams)
skipLine                        - skip one line (i.e. up to newline)

reading/writing binary data:

nextByte                        - read a byte
nextShortMSB:                   - read a signed short (2 bytes) specifying msb or lsb
nextUnsignedShortMSB:           - read an unsigned short (2 bytes) specifying msb or lsb
nextLongMSB:                    - read a signed long (4 bytes) specifying msb or lsb
nextUnsignedLongMSB:            - read an unsigned long (4 bytes) specifying msb or lsb
nextBytes:into:                 - read some bytes

nextPutByte:                    - write a byte
nextPutShort:MSB:               - write a signed short (2 bytes), specifying msb or lsb
nextPutLong:MSB:                - write a signed long (4 bytes), specifying msb or lsb
nextPutBytes:from:              - write some bytes

List of interesting globals

Smalltalk                       - contains all globals (name<->object associations)

Transcript                      - to output messages

Stdout                          - standard output stream (i.e. xterm)
Stderr                          - standard error stream (i.e. xterm)
Stdin                           - standard input stream (i.e. xterm)

Display                         - your display Workstation

Arguments                       - array with command-line arguments 
				  (i.e. argv in C-world)

Processor                       - for process scheduling


Copyright © Claus Gittinger Development & Consulting, all rights reserved

(cg@ssw.de)