InterfaceConfiguration


SmallInterfaces

Comment:



Hierarchy:

ProtoObject
Object
InterfaceConfiguration

Summary:

instance variables:

defaultInterfaceClassCategory enforceNonEmptyInterfaces removeOnlyStubbedImplementations selectorForClassInterfaces selectorForInterfaceInheritance

class instance variables:

singleton

methods:

instance class
accessing class initialization instance creation

Detail:

instance variables:

defaultInterfaceClassCategory
InitialValue:
Interfaces
inferredType:
String
enforceNonEmptyInterfaces
InitialValue:
true
inferredType:
True
removeOnlyStubbedImplementations
InitialValue:
true
inferredType:
True
selectorForClassInterfaces
InitialValue:
#understoodInterfacesMinimalSet
inferredType:
Symbol
selectorForInterfaceInheritance
InitialValue:
#parents
inferredType:
Symbol

class instance variables:

singleton
InitialValue:
an InterfaceConfiguration
inferredType:
InterfaceConfiguration

instance methods:

accessing
defaultInterfaceClassCategory

	"SmallInterfaces: ##added for Squeak -M.U. 6/23/1999 23:35"
	^defaultInterfaceClassCategory ifNil: [defaultInterfaceClassCategory := 'Interfaces']
defaultInterfaceClassCategory: aString

	"SmallInterfaces: ##added for Squeak -M.U. 6/23/1999 23:35"
	defaultInterfaceClassCategory := aString
enforceNonEmptyInterfaces


	^enforceNonEmptyInterfaces ifNil: [enforceNonEmptyInterfaces := true]
enforceNonEmptyInterfaces: aBoolean


	enforceNonEmptyInterfaces := aBoolean
removeOnlyStubbedImplementations


	^removeOnlyStubbedImplementations ifNil: [removeOnlyStubbedImplementations := true]
removeOnlyStubbedImplementations: aBoolean


	removeOnlyStubbedImplementations := aBoolean
selectorForClassInterfaces


	^selectorForClassInterfaces ifNil: [selectorForClassInterfaces := #understoodInterfacesMinimalSet]
selectorForClassInterfaces: selectorSymbol


	| permittedSelectors |
	permittedSelectors := Class selectorsInCategory: #'interfaces'.
	(permittedSelectors includes: selectorSymbol) 
		ifTrue:  [selectorForClassInterfaces := selectorSymbol]
		ifFalse: [self error: 'selector must be one of: ',  permittedSelectors asArray printString]
selectorForInterfaceInheritance


	^selectorForInterfaceInheritance ifNil: [selectorForInterfaceInheritance := #parents]
selectorForInterfaceInheritance: selectorSymbol


	| permittedSelectors |
	permittedSelectors := Interface class selectorsInCategory: #'accessing-extended'.
	(permittedSelectors includes: selectorSymbol)
		ifTrue:  [selectorForInterfaceInheritance := selectorSymbol]
		ifFalse: [self error: 'selector must be one of: ',  permittedSelectors asArray printString]

class methods:

class initialization
initialize

	"InterfaceConfiguration initialize."
	"SmallInterfaces: ##modified for Squeak -M.U. 6/23/1999 23:35"

obsolete

	"SmallInterfaces: ##modified for Squeak -M.U. 6/23/1999 23:35"
	self nuke.

instance creation
current


	^singleton ifNil: [singleton := super new]
new


	^self current
nuke


	singleton := nil

^top


- made by Dandelion -