Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
SMFileDatabase
Last updated at 1:38 pm UTC on 9 May 2018
Excerpt from
By Ramon Leon - 14 January 2008
http://onsmalltalk.com/simple-image-based-persistence-in-squeak

Many business applications and prototypes are built to replace manual processes using Email, Word, and Excel. Word and Excel by the way, aren't ACID compliant, don't support transactions, and manage to successfully run most small businesses.

...
No object relational mapping layer (not even Rails and ActiveRecord) can match the simplicity, performance, and speed of development one can get just using plain old objects that are kept in memory all the time. Most small office apps with no more than a handful of users can easily fit everything into memory, this is the idea behind Prevayler.

...
The basic idea is to use a command pattern to apply changes to your model, you can then log the commands, snapshot the model, and replay the log in case of a crash to bring the last snapshot up to date. Nice idea, if you're OK creating commands for every state changing action in your application and being careful with how you use timestamps so replaying the logs works properly. I'm not OK with that, it introduces a level of complexity that is overkill for many apps and is likely the reason more people don't use a Prevayler like approach.

..
Using a ReferenceStream to serialize objects to disk Prevayler style, but ignoring the command pattern part and just treating it more like crash proof image persistence is a viable option if your app won't ever have that much data. Rather than trying to minimize writes with commands, you just snapshot the entire model on every change.


If you're going to have a lot of data, clearly this is a bad approach, but if you're already thinking about how to use the image for simple persistence because you know your data will fit in ram, here's how I do it.

It only takes a few lines of code in a single abstract class that you can subclass for each project to make a Squeak image fairly robust and crash proof and more than capable enough to allow you just use the image, no database necessary. We'll start with a class...

Object subclass: #SMFileDatabase
    instanceVariableNames: ''
    classVariableNames: ''
    poolDictionaries: ''
    category: 'SimpleFileDb'

SMFileDatabase class
    instanceVariableNames: 'lock'

...
So on shutdown, if the image is actually going down, just save the current data to disk.

 shutDown: isGoingDown 
     isGoingDown ifTrue: [ self saveRepository ]

And on startup we can #restoreLastBackup.

 startUp: isComingUp 
    isComingUp ifTrue: [ self restoreLastBackup ]




The full code
'From Squeak3.9 of 7 November 2006 [latest update: #7067] on 14 January 2008 at 9:55:46 pm'!
Object subclass: #SMFileDatabase
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SentorsaMagritte-Domain'!

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

SMFileDatabase class
	instanceVariableNames: 'lock'!

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/4/2007 17:57'!
backupDirectory
	^ (FileDirectory default directoryNamed: self name) assureExistence.
! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/9/2007 12:47'!
defaultHistoryCount
	^ 50! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/4/2007 18:15'!
enablePersistence
	Smalltalk addToStartUpList: self.
	Smalltalk addToShutDownList: self! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 1/14/2008 08:50'!
lastBackup
	| lastBackup |
	lastBackup := self lastBackupFile.
	lastBackup ifNil: [ ^ nil ].
	^ ReferenceStream 
		readOnlyFileNamed: (self backupDirectory fullNameFor: lastBackup)
		do: [ : f | f next ]! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/4/2007 18:28'!
lastBackupFile
	^ self backupDirectory fileNames 
		detectMax: [:each | each name asInteger]! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/4/2007 18:04'!
repositories
	self subclassResponsibility! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/11/2007 12:17'!
restoreLastBackup
	self lastBackup ifNotNilDo: [ : backup | self restoreRepositories: backup ]! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/4/2007 17:59'!
restoreRepositories: someRepositories
	self subclassResponsibility! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 1/14/2008 08:52'!
saveRepository
	| version |
	lock ifNil: [ lock := Semaphore forMutualExclusion ].
	lock critical: 
		[ self trimBackups.
		version := self lastBackupFile 
			ifNil: [ 1 ]
			ifNotNil: [ self lastBackupFile name asInteger + 1 ].
		ReferenceStream 
			newFileNamed: (self backupDirectory fullPathFor: self name) , '.' , version asString
			do: 
				[ : f | 
				f
					nextPut: self repositories ;
					flush ] ]! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/4/2007 18:19'!
shutDown: isGoingDown 
	isGoingDown ifTrue: [ self saveRepository ]! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/4/2007 18:24'!
startUp: isComingUp 
	isComingUp ifTrue: [ self restoreLastBackup ]! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/9/2007 12:24'!
takeSnapshot
	[self saveRepository] forkAt: Processor userBackgroundPriority
		named: 'snapshot: ' , self class name! !

!SMFileDatabase class methodsFor: 'database' stamp: 'rjl 12/11/2007 12:19'!
trimBackups
	| entries versionsToKeep |
	versionsToKeep := self defaultHistoryCount.
	entries := self backupDirectory entries.
	entries size < versionsToKeep ifTrue: [ ^ self ].
	((entries sortBy: [ : a : b | a first asInteger < b first asInteger ]) allButLast: versionsToKeep) 
		do: [ : entry | self backupDirectory deleteFileNamed: entry first ]! !