Object


Kernel-Objects

Comment:

I am the superclass of all classes. I provide default behavior common to all objects, such as class access, copying and printing.

Hierarchy:

ProtoObject
Object

Summary:

class variables:

DependentsFields

methods:

instance class
accessing
  • addInstanceVarNamed:withValue:
  • at:
  • at:modify:
  • at:put:
  • basicAt:
  • basicAt:put:
  • basicSize
  • bindWithTemp:
  • environment
  • in:
  • readFromString:
  • size
  • starts:
  • yourself
associating
  • ->
binding
  • bindingOf:
casing
  • caseOf:
  • caseOf:otherwise:
class membership
  • class
  • isKindOf:
  • isKindOf:orOf:
  • isMemberOf:
  • respondsTo:
  • xxxClass
comparing
  • =
  • closeTo:
  • hash
  • hashMappedBy:
  • identityHashMappedBy:
  • identityHashPrintString
  • ~=
converting
  • adaptToFloat:andSend:
  • adaptToFraction:andSend:
  • adaptToInteger:andSend:
  • as:
  • asOrderedCollection
  • asString
  • withoutListWrapper
copying
  • clone
  • copy
  • copyAddedStateFrom:
  • copyFrom:
  • copySameFrom:
  • copyTwoLevel
  • deepCopy
  • initialDeepCopierSize
  • shallowCopy
  • veryDeepCopy
  • veryDeepCopyWith:
  • veryDeepFixupWith:
  • veryDeepInner:
dependents access
  • addDependent:
  • breakDependents
  • canDiscardEdits
  • dependents
  • evaluate:wheneverChangeIn:
  • hasUnacceptedEdits
  • release
  • removeDependent:
error handling
  • cannotInterpret:
  • caseError
  • confirm:
  • confirm:orCancel:
  • doesNotUnderstand:
  • error:
  • halt
  • halt:
  • handles:
  • notify:
  • notify:at:
  • primitiveFailed
  • shouldNotImplement
  • subclassResponsibility
  • tryToDefineVariableAccess:
filter streaming
  • byteEncode:
  • drawOnCanvas:
  • elementSeparator
  • encodePostscriptOn:
  • flattenOnStream:
  • fullDrawPostscriptOn:
  • printOnStream:
  • putOn:
  • storeOnStream:
  • writeOnFilterStream:
finalization
  • actAsExecutor
  • executor
  • finalize
  • retryWithGC:until:
flagging
  • flag:
  • isThisEverCalled
  • isThisEverCalled:
  • logEntry
  • logExecution
  • logExit
indicating macpal
  • codeStrippedOut:
  • contentsChanged
  • currentEvent
  • currentHand
  • currentWorld
  • flash
  • ifKindOf:thenDo:
  • instanceVariableValues
  • playSoundNamed:
  • scriptPerformer
message handling
  • perform:
  • perform:orSendTo:
  • perform:with:
  • perform:with:with:
  • perform:with:with:with:
  • perform:withArguments:
  • perform:withArguments:inSuperclass:
objects from disk
  • comeFullyUpOnReload:
  • objectForDataStream:
  • readDataFrom:size:
  • saveOnFile
  • storeDataOn:
printing
  • fullPrintString
  • isLiteral
  • longPrintOn:
  • longPrintString
  • printOn:
  • printString
  • printStringLimitedTo:
  • propertyList
  • storeOn:
  • storeString
  • stringForReadout
  • stringRepresentation
private
  • errorImproperStore
  • errorNonIntegerIndex
  • errorNotIndexable
  • errorSubscriptBounds:
  • mustBeBoolean
  • primitiveError:
  • species
  • storeAt:inTempFrame:
querying system primitives
  • asOop
  • becomeForward:
  • instVarAt:
  • instVarAt:put:
  • instVarNamed:
  • instVarNamed:put:
  • rootStubInImageSegment:
  • someObject
  • tryPrimitive:withArgs:
testing
  • basicType
  • conformsTo:
  • ends:
  • haltIfNil
  • isBehavior
  • isClass
  • isCollection
  • isColor
  • isFloat
  • isFraction
  • isInteger
  • isInterface
  • isMorph
  • isNumber
  • isPoint
  • isPseudoContext
  • isStream
  • isText
  • isTransparent
  • isTypeOf:
  • isWebBrowser
  • knownName
  • name
  • notNil
  • stepAt:in:
  • stepIn:
  • stepTime
  • stepTimeIn:
  • wantsSteps
  • wantsStepsIn:
translation support
  • asIf:var:
  • asIf:var:asValue:
  • asIf:var:put:
  • asOop:
  • asSmallIntegerObj
  • asValue:
  • cCode:
  • cCode:inSmalltalk:
  • cCoerce:to:
  • export:
  • inline:
  • primitive:parameters:receiver:
  • returnTypeC:
  • sharedCodeNamed:inCase:
  • suppressFailureGuards:
  • var:declareC:
updating
  • changed
  • changed:
  • handledListVerification
  • noteSelectionIndex:for:
  • okToChange
  • update:
  • updateListsAndCodeIn:
  • windowIsClosing
user interface
  • addModelItemsToWindowMenu:
  • addModelMenuItemsTo:forMorph:hand:
  • asExplorerString
  • basicInspect
  • beep
  • defaultBackgroundColor
  • defaultLabelForInspector
  • explore
  • fullScreenSize
  • hasContentsInExplorer
  • inform:
  • initialExtent
  • inspect
  • inspectWithLabel:
  • modelSleep
  • modelWakeUp
  • modelWakeUpIn:
  • mouseUpBalk:
  • newTileMorphRepresentative
  • notYetImplemented
  • smartInspect
  • windowActiveOnFirstClick
  • windowReqNewLabel:
documentation
  • howToModifyPrimitives
  • whatIsAPrimitive
instance creation
  • categoryForUniclasses
  • chooseUniqueClassName
  • copyMethodDictionaryFrom:
  • initialInstance
  • instanceOfUniqueClass
  • instanceOfUniqueClassWithInstVarString:andClassInstVarString:
  • isUniClass
  • newFrom:
  • newUniqueClassInstVars:classInstVars:
  • newUserInstance
  • readCarefullyFrom:
  • readFrom:
objects from disk
  • createFrom:size:version:
plugin generation
  • ccg:emitLoadFor:from:on:
  • ccg:generateCoerceToOopFrom:on:
  • ccg:generateCoerceToValueFrom:on:
  • ccg:prolog:expr:index:
  • ccgCanConvertFrom:
  • ccgDeclareCForVar:
private
  • initializeDependentsFields

Detail:

class variables:

DependentsFields
InitialValue:
IdentityDictionary (a CautiousModel->(a ColorSystemView ) a MVCWiWPasteUpMorph('Try ''turn gridding on''...' 193)->(a MorphWorldView ) an InfiniteForm->(a FormView ) an InfiniteForm->(a FormView ) a CautiousModel->(a ColorSystemView ) an InfiniteForm->(a FormView ) a CautiousModel->(a ColorSystemView ) a CautiousModel->(a ColorSystemView ) a MVCWiWPasteUpMorph('Page-scrolling works now, too...' 3445)->(a MorphWorldView ) a MVCWiWPasteUpMorph(830)->(a MorphWorldView ) an InfiniteForm->(a FormView ) an InfiniteForm->(a FormView ) ChangeSet->(a RepertoireHome ) an InfiniteForm->(a FormView ) an InfiniteForm->(a FormView ) an InfiniteForm->(a FormView ) a MVCWiWPasteUpMorph(2589)->(a MorphWorldView ) )
inferredType:
IdentityDictionary

instance methods:

accessing
environment


	^self class environment
starts: aSequenceableCollection

	"Answer whether the first element of aSequenceableCollection is equal to the receiver."

	^aSequenceableCollection first = self

indicating
needsFurtherWork

	"Marks code that needs further work.
	It is assumed to be left 'in the middle' of developement."
shouldImplementFor: anInterface
 
	"This method is used to mark a method as one generated (and stubbed) for an interface."

	^anInterface implementorsResponsibility
subclassesShouldOverride

	"Unlike #subclassResponsibility, this is a recommendation only."

querying
types

	"Which are all the types which I embody?
	Definition: Type = (Class | Interface)"

	^self class allSuperclasses 
		addAll: self class understoodInterfaces;
		yourself

testing
conformsTo: anInterface

	"Can I respond to any message in <anInterface> repertoire?"

	^self class understands: anInterface
ends: aSequenceableCollection

	"Answer whether the last element of aSequenceableCollection is equal to the receiver."

	^aSequenceableCollection last = self
isClass

	"Answer whether the receiver is a class."

	^false
isInterface


	^false
isTypeOf: aClassOrInterface


	^aClassOrInterface isEmbodiedIn: self

class methods:

^top


- made by Dandelion -