Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Singleton
Last updated at 9:31 pm UTC on 5 May 2019
https://en.wikipedia.org/wiki/Singleton_pattern
In software engineering, the singleton pattern is a software design pattern that restricts the instantiation of a class to one object. This is useful when exactly one object is needed to coordinate actions across the system. The concept is sometimes generalized to systems that operate more efficiently when only one object exists, or that restrict the instantiation to a certain number of objects. The term comes from the mathematical concept of a singleton.

There are some who are critical of the singleton pattern and consider it to be an anti-pattern in that it is frequently used in scenarios where it is not beneficial, introduces unnecessary restrictions in situations where a sole instance of a class is not actually required, and introduces global state into an application


Sometimes a singleton is implemented with a class using class methods only as in FileServices and Flaps.
(Flaps allInstances size is 0)
A more regular implementation example is TheWorldMenuDockingBar.



Example implementation

'From Squeak 2.4b of April 23, 1999 on 30 April 1999 at 7:57:06 pm'!
"Change Set:		Singleton
Date:			30 April 1999
Author:			Chris Norton

Here's an implemenation of the generic class Singleton.

Subclasses of Singleton will only allow a single instance of themselves to be created.

To access the unique instance of Singleton, call it's 'current' class method.

e.g.  Singleton current"!

Object subclass: #Singleton
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Abstract-Singleton'!
Singleton class
	instanceVariableNames: 'Current '!

!Singleton commentStamp: 'ccn 4/30/1999 19:31' prior: 0!
Singleton implements the behavior for an object that has only one instance.

	!

!Singleton reorganize!
('initialization' initialize)
!


!Singleton methodsFor: 'initialization' stamp: 'ccn 4/30/1999 19:42'!
initialize
	"Put your special object initialization code in here..."! !


!Singleton class reorganize!
('public' current)
('private' new reset)
!


!Singleton class methodsFor: 'public' stamp: 'ccn 4/30/1999 19:41'!
current
	"Return the only instance of this class."

	Current isNil
		ifTrue: [Current _ self basicNew initialize].
	^Current! !

!Singleton class methodsFor: 'private' stamp: 'ccn 4/30/1999 19:49'!
new
	"There is only one of these, so don't let the user make a new one!!"

	^self error: 'Class ', self name, ' cannot create new instances.  Try ', self name, ' current'! !

!Singleton class methodsFor: 'private' stamp: 'ccn 4/30/1999 19:40'!
reset
	"Reset the only instance of this class."

	Current := nil! !


 "Postscript:

 Hope you enjoy this class!!
 
 —==> Chris"
 !