-
Notifications
You must be signed in to change notification settings - Fork 2
/
Copy pathOOP4.st
302 lines (249 loc) · 9.75 KB
/
OOP4.st
1
Object subclass: #OOPObject instanceVariableNames: 'superclassInstances' classVariableNames: '' poolDictionaries: '' category: 'OOP4'!!OOPObject methodsFor: 'methods' stamp: '1 6/8/2019 17:06'!definingInstance: aSymbol |methodInheritType res| res := nil. methodInheritType := self class classifyInheritedMethod: aSymbol. ((methodInheritType = 'public') | (methodInheritType = 'protected') | (methodInheritType = 'private')) ifFalse: [^res]. "case inaccessible or ambiguous or undefined" self superclassInstances do: [:ins | (ins isKindOf: OOPObject) ifTrue:[ res := ins definingInstanceAux: aSymbol. (res = nil) ifFalse: [^res]. ] ifFalse:[ (ins respondsTo: aSymbol) ifTrue: [^ins]. ]. ]. ^nil.! !!OOPObject methodsFor: 'methods' stamp: 'ng 6/10/2019 14:39'!definingInstanceAux: aSymbol |res| "here only if is OOPObject" res := nil. (self class includesSelector: aSymbol) ifTrue: [^self.]. superclassInstances do: [:ins | (ins class isKindOf: OOPObject class) "if parent ins is not OOPObject can not call definingInstanceAux" ifTrue:[res := ins definingInstanceAux: aSymbol. (res ~= nil) ifTrue: [^res.]. ] ifFalse:[(ins respondsTo: aSymbol) ifTrue:[^ins] ].]. ^nil.! !!OOPObject methodsFor: 'methods' stamp: '1 6/8/2019 17:05'!doesNotUnderstand: aMessage |sender method methodInheritType aParent wayInheritType| method := aMessage asString asSymbol. sender := thisContext client class. methodInheritType := self class classifyInheritedMethod: method. ((methodInheritType='undefined') | (methodInheritType ='ambiguous') | (methodInheritType ='inaccessible')) ifFalse:[ aParent := self definingInstance: method. (methodInheritType = 'public') ifTrue: [^(aMessage sendTo: aParent)]. (methodInheritType = 'protected') & (sender superclass = OOPObject) ifTrue: [ wayInheritType := sender multInheritsFromType: self class. ((wayInheritType = 'public') | (wayInheritType = 'protected')) ifTrue: [^(aMessage sendTo: aParent)] ]. (self class = sender) ifTrue: [^(aMessage sendTo: aParent)]. ].OOPObject throwSender: (sender name) fails: (aMessage) inClass: ((self class) name) because: methodInheritType.! !!OOPObject methodsFor: 'methods' stamp: 'AL 5/26/2019 11:31'!initialize ^self initializeSupers postInitialize.! !!OOPObject methodsFor: 'methods' stamp: 'AL 6/8/2019 12:20'!initializeSupers superclassInstances := OrderedCollection new. "The class OrderedCollection is more general than Array; the size of an OrderedCollection grows on demand, and it has methods for addFirst: and addLast: as well as at: and at:put:." self class superclasses do: [:e| superclassInstances add: (e parentClass new)]! !!OOPObject methodsFor: 'methods' stamp: 'AL 5/26/2019 11:31'!postInitialize ^self.! !!OOPObject methodsFor: 'methods' stamp: 'ng 6/7/2019 09:32'!superclassInstances^superclassInstances.! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!OOPObject class instanceVariableNames: 'superclasses'!!OOPObject class methodsFor: 'methods' stamp: '1 6/8/2019 14:53'!classifyInheritedMethod: aSymbol |res resForP Punderstand| Punderstand := false. res := self classifyInheritedMethodAux: aSymbol Type: 'public'. (res ='ambiguous') ifTrue: [^'ambiguous'.]. self superclasses do: [:P | (P parentClass superclass == OOPObject) "this loop checks ONLY if the result is private or inaccessible." ifTrue: [ "it checks for each parent if he or his grandparents understand aSymbol" resForP := P parentClass classifyInheritedMethodAux: aSymbol Type: 'public'. "If that happens and inherType is private (self->p) we return private" (resForP ~= 'undefined') "otherwise, the private inheritance is up the tree so inaccessible" ifTrue: [Punderstand := true]. "case grandparents understands the symbol" (P parentClass includesSelector: aSymbol) ifTrue: [Punderstand := true.]. "case parent understands the symbol" (Punderstand) ifTrue: [ (P inheritanceType = 'private') ifTrue: [^'private']. "case inherit from parent is private" ]. ]. ]. (res='private') ifTrue: [^'inaccessible']. ^res. ! !!OOPObject class methodsFor: 'methods' stamp: '1 6/8/2019 17:07'!classifyInheritedMethodAux: aSymbol Type: inherType |foundAlready foundRec aParentfoundRec nextInherType retVal| foundRec := 'undefined'. retVal := 'undefined'. foundAlready :=false. self superclasses do: [:aParent | ((aParent parentClass) canUnderstand: aSymbol) ifTrue:["aParent understand" (foundAlready) ifTrue: [^'ambiguous']. foundAlready := true. retVal := self selectType: inherType secType: (aParent inheritanceType). "selectType determines the method (aSymbol)" "inheritance type by the inherType before and" (aParent parentClass superclass == OOPObject) "countinue to check for aSymbol in inheritance tree of aParent" ifTrue: [ aParentfoundRec := aParent parentClass classifyInheritedMethodAux: aSymbol Type: inherType. (aParentfoundRec = 'ambiguous') ifTrue: [^'ambiguous']. "don't care from other options here because the method has been overriden since aParent understands" ]. ] ifFalse: [ "parent doesnt understands the symbol, checking upper:" (aParent parentClass superclass == OOPObject) ifTrue: [ nextInherType := self selectType: inherType secType: (aParent inheritanceType). foundRec := aParent parentClass classifyInheritedMethodAux: aSymbol Type: nextInherType. "recursive call" (foundRec = 'ambiguous') ifTrue: [^'ambiguous']. (foundRec = 'undefined') ifFalse: [ "case YES defined" retVal := foundRec. (foundAlready) ifFalse: [foundAlready := true] ifTrue: [^'ambiguous']. ]. ]. ]. ]. ^retVal. ! !!OOPObject class methodsFor: 'methods' stamp: '1 6/8/2019 15:47'!multInheritsFrom: aClass superclasses do: [:e| (e parentClass == aClass) ifTrue: [^true]. "else" (e parentClass isKindOf: (OOPObject class)) ifTrue: [(e parentClass multInheritsFrom: aClass) "recursive call" ifTrue: [^true]] ifFalse:[(e parentClass isKindOf: (aClass class)) ifTrue:[^true]]. ]. ^false.! !!OOPObject class methodsFor: 'methods' stamp: '1 6/11/2019 16:29'!multInheritsFromType: aClass "returns the inherit type between classes. result can be: nil, private, protected, public." |tempInherType| superclasses do: [:e| (e parentClass == aClass) ifTrue: [^(e inheritanceType)]. "else" (e parentClass isKindOf: (OOPObject class)) ifTrue: [ tempInherType := e parentClass multInheritsFromType: aClass. "recursive call" (tempInherType ~= nil) ifTrue: [^(self selectType: (e inheritanceType) secType: tempInherType)] ] ifFalse:[(e parentClass isKindOf: (aClass class)) ifTrue:[^(e inheritanceType)]]. ]. ^nil.! !!OOPObject class methodsFor: 'methods' stamp: 'AL 6/8/2019 12:14'!selectType: Type1 secType: Type2 ((Type1 = 'private') | (Type2 = 'private')) ifTrue:[^'private']. ((Type1 = 'protected') | (Type2 = 'protected')) ifTrue:[^'protected']. ^'public'.! !!OOPObject class methodsFor: 'methods' stamp: '1 6/8/2019 14:12'!subclass: aSubclassName instanceVariableNames: instVarNames classVariableNames: classVarNames poolDictionaries: poolDictionaries category: aCategoryName ^(self subclass: aSubclassName parentClasses: (Array new) instanceVariableNames: instVarNames classVariableNames: classVarNames poolDictionaries: poolDictionaries category: aCategoryName)! !!OOPObject class methodsFor: 'methods' stamp: 'ng 6/11/2019 10:37'!subclass: aSubclassName parentClasses: anArray instanceVariableNames: instVarNames classVariableNames: classVarNames poolDictionaries: poolDictionaries category: aCategoryName |newClass newParent| "creating the new class" newClass := ClassBuilder new superclass: OOPObject subclass: aSubclassName instanceVariableNames: instVarNames classVariableNames: classVarNames poolDictionaries: poolDictionaries category: aCategoryName. "case operation is on OOPObject" (self == OOPObject) ifTrue: [newClass instVarNamed: #superclasses put: anArray. ^newClass]. "case operation is on another class, " newParent := OOPParent new parentClass: self. newParent inheritanceType: 'public'. "putting our new field" newClass instVarNamed: #superclasses put: {newParent}, anArray. "Appending an array with , sign" "returns" ^newClass.! !!OOPObject class methodsFor: 'methods' stamp: 'AL 5/26/2019 11:18'!superclasses ^superclasses.! !!OOPObject class methodsFor: 'methods' stamp: '1 6/8/2019 15:56'!throwSender: senderName fails: methodName inClass: receiverName because: reason |str| str := senderName,' cannot send ',methodName asString,' to ',receiverName,' because: ',reason. AssertionFailure signal: str. ! !Object subclass: #OOPParent instanceVariableNames: 'parentClass inheritanceType' classVariableNames: '' poolDictionaries: '' category: 'OOP4'!!OOPParent methodsFor: 'methods' stamp: 'AL 5/26/2019 09:13'!inheritanceType ^inheritanceType.! !!OOPParent methodsFor: 'methods' stamp: 'AL 5/26/2019 09:15'!inheritanceType: aString inheritanceType := aString.! !!OOPParent methodsFor: 'methods' stamp: 'ng 6/11/2019 12:16'!initialize parentClass:= Object new. inheritanceType:= 'public'.! !!OOPParent methodsFor: 'methods' stamp: 'AL 5/26/2019 09:11'!parentClass ^parentClass.! !!OOPParent methodsFor: 'methods' stamp: 'AL 5/27/2019 13:46'!parentClass: aClass parentClass := aClass.! !