|
|
6.121 RootNamespace
- Defined in namespace Smalltalk
- Category: Language-Implementation
- I am a special form of dictionary. I provide special ways to access my
keys, which typically begin with an uppercase letter. Classes hold on
an instance of me; it is called their `environment').
My keys are (expected to be) symbols, so I use == to match searched keys
to those in the dictionary -- this is done expecting that it brings a bit
more speed.
6.121.1 RootNamespace class: instance creation
- new
- Disabled - use #new to create instances
- new: spaceName
- Create a new root namespace with the given name, and add to Smalltalk a key that references it.
- primNew: parent name: spaceName
- Private - Create a new namespace with the given name and parent, and add to the parent a key that references it.
6.121.2 RootNamespace: accessing
- allAssociations
- Answer a Dictionary with all of the associations in the receiver and each of its superspaces (duplicate keys are associated to the associations that are deeper in the namespace hierarchy)
- allBehaviorsDo: aBlock
- Evaluate aBlock once for each class and metaclass in the namespace.
- allClassesDo: aBlock
- Evaluate aBlock once for each class in the namespace.
- allClassObjectsDo: aBlock
- Evaluate aBlock once for each class and metaclass in the namespace.
- allMetaclassesDo: aBlock
- Evaluate aBlock once for each metaclass in the namespace.
- classAt: aKey
- Answer the value corrisponding to aKey if it is a class. Fail if either aKey is not found or it is associated to something different from a class.
- classAt: aKey ifAbsent: aBlock
- Answer the value corrisponding to aKey if it is a class. Evaluate aBlock and answer its result if either aKey is not found or it is associated to something different from a class.
- define: aSymbol
- Define aSymbol as equal to nil inside the receiver. Fail if such a variable already exists (use #at:put: if you don't want to fail)
- doesNotUnderstand: aMessage
- Try to map unary selectors to read accesses to the Namespace, and one-argument keyword selectors to write accesses. Note that: a) this works only if the selector has an uppercase first letter; and b) `aNamespace Variable: value' is the same as `aNamespace set: #Variable to: value', not the same as `aNamespace at: #Variable put: value' -- the latter always refers to the current namespace, while the former won't define a new variable, instead searching in superspaces (and raising an error if the variable cannot be found).
- import: aSymbol from: aNamespace
- Add to the receiver the symbol aSymbol, associated to the same value as in aNamespace. Fail if aNamespace does not contain the given key.
6.121.3 RootNamespace: basic & copying
- = arg
- Answer whether the receiver is equal to arg. The equality test is by default the same as that for equal objects. = must not fail; answer false if the receiver cannot be compared to arg
- identityHash
- Answer an hash value for the receiver. This is the same as the object's #identityHash.
6.121.4 RootNamespace: copying
- copy
- Answer the receiver.
- deepCopy
- Answer the receiver.
- shallowCopy
- Answer the receiver.
6.121.5 RootNamespace: forward declarations
- at: key put: value
- Store value as associated to the given key. If any, recycle Associations temporarily stored by the compiler inside the `Undeclared' dictionary.
6.121.6 RootNamespace: namespace hierarchy
- addSubspace: aSymbol
- Add aNamespace to the set of the receiver's subspaces
- allSubassociationsDo: aBlock
- Invokes aBlock once for every association in each of the receiver's subspaces.
- allSubspaces
- Answer the direct and indirect subspaces of the receiver in a Set
- allSubspacesDo: aBlock
- Invokes aBlock for all subspaces, both direct and indirect.
- allSuperspaces
- Answer all the receiver's superspaces in a collection
- allSuperspacesDo: aBlock
- Evaluate aBlock once for each of the receiver's superspaces
- includesClassNamed: aString
- Answer whether the receiver or any of its superspaces include the given class -- note that this method (unlike #includesKey:) does not require aString to be interned and (unlike #includesGlobalNamed:) only returns true if the global is a class object.
- includesGlobalNamed: aString
- Answer whether the receiver or any of its superspaces include the given key -- note that this method (unlike #includesKey:) does not require aString to be interned but (unlike #includesClassNamed:) returns true even if the global is not a class object.
- inheritsFrom: aNamespace
- Answer whether aNamespace is one of the receiver's direct and indirect superspaces
- selectSubspaces: aBlock
- Return a Set of subspaces of the receiver satisfying aBlock.
- selectSuperspaces: aBlock
- Return a Set of superspaces of the receiver satisfying aBlock.
- siblings
- Answer all the other root namespaces
- siblingsDo: aBlock
- Evaluate aBlock once for each of the other root namespaces, passing the namespace as a parameter.
- subspaces
- Answer the receiver's direct subspaces
- subspacesDo: aBlock
- Invokes aBlock for all direct subspaces.
- superspace
- Send #at:ifAbsent: to super because our implementation of #at:ifAbsent: sends this message (chicken and egg!)
- superspace: aNamespace
- Set the superspace of the receiver to be 'aNamespace'. Also adds the receiver as a subspace of it.
- withAllSubspaces
- Answer a Set containing the receiver together with its direct and indirect subspaces
- withAllSubspacesDo: aBlock
- Invokes aBlock for the receiver and all subclasses, both direct and indirect.
- withAllSuperspaces
- Answer the receiver and all of its superspaces in a collection
- withAllSuperspacesDo: aBlock
- Invokes aBlock for the receiver and all superspaces, both direct and indirect.
6.121.7 RootNamespace: overrides for superspaces
- definedKeys
- Answer a kind of Set containing the keys of the receiver
- definesKey: key
- Answer whether the receiver defines the given key. `Defines' means that the receiver's superspaces, if any, are not considered.
- hereAt: key
- Return the value associated to the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be brought on in superspaces and the method will fail.
- hereAt: key ifAbsent: aBlock
- Return the value associated to the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be brought on in superspaces and aBlock will be immediately evaluated.
- inheritedKeys
- Answer a Set of all the keys in the receiver and its superspaces
- set: key to: newValue
- Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and raising an error if the variable cannot be found in any of the superspaces. Answer newValue.
- set: key to: newValue ifAbsent: aBlock
- Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue.
- values
- Answer a Bag containing the values of the receiver
6.121.8 RootNamespace: printing
- defaultName
- Private - Answer the name to be used if the receiver is not attached to an association in the superspace
- name
- Answer the receiver's name
- nameIn: aNamespace
- Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace
- printOn: aStream
- Print a representation of the receiver
- storeOn: aStream
- Store Smalltalk code compiling to the receiver
6.121.9 RootNamespace: testing
- isNamespace
- Answer `true'.
- isSmalltalk
- Answer `false'.
- species
- Answer `IdentityDictionary'.
|