Recent Changes - Search:

OtherPlaces

PmWiki

pmwiki.org

edit SideBar

SandstoneDb

On the Pharocasts, there are two presentations, one on building a GUI using Polymorph (Contact Manager) and another on using SandstoneDb, to create persistent external records. See http://www.pharocasts.com/2011/02/pharo-gui-with-polymorph.html and http://www.pharocasts.com/2010/04/sandstonedb-simple-activerecord-style.html

I developed some code that uses SandstoneDb for the ContactManager program. This is not a full-fledged system, any more than the original Pharocast. The purpose is to give you an example of how to use SandstoneDb, so you have something to model from. Here's the code. You can also download it at http://dougedmunds.com/pub/Pharo. Get the file ContactManagerSSDb.zip

Object subclass: #ContactEditor
  instanceVariableNames: 'contact onOKAction'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'ContactManagerSSDb'!
!ContactEditor commentStamp: 'estelle 2/3/2011 08:06' prior: 0!
Dialog to edit a Contact. For example:

ContactEditor new
  contact: (Contact new firstName: 'Miles'; lastName:'Davis');
  openModal.!


!ContactEditor methodsFor: 'accessing' stamp: 'LaurentLaffont 1/23/2011 10:08'!
contact: aContact 
  contact := aContact! !


!ContactEditor methodsFor: 'ok actions' stamp: 'LaurentLaffont 1/23/2011 13:50'!
doOnOK
  ^ self onOK value! !

!ContactEditor methodsFor: 'ok actions' stamp: 'LaurentLaffont 1/23/2011 13:50'!
onOK
  ^ onOKAction ifNil: [onOKAction := []].! !

!ContactEditor methodsFor: 'ok actions' stamp: 'LaurentLaffont 1/23/2011 13:50'!
onOK: aBlock
  onOKAction := aBlock! !


!ContactEditor methodsFor: 'open/close' stamp: 'LaurentLaffont 1/25/2011 21:15'!
openModal
  |builder dialog content firstName|

  builder := UITheme builder.
  content := (builder newLabelGroup: {
        'First name' -> (firstName := (builder
                        newTextEntryFor: contact 
                      getText: #firstName 
                      setText: #firstName: 
                      help: 'Enter the first name of the contact')
                      acceptOnCR: false;
                      minWidth: 200).
        'Last name' -> ((builder
                newTextEntryFor: contact 
              getText: #lastName 
              setText: #lastName: 
              help: 'Enter the last name of the contact')
              acceptOnCR: false;
              minWidth: 200) 
  }).

  dialog := builder newPluggableDialogWindow:'Edit contact' for: content.
  dialog rememberKeyboardFocus: firstName.
  builder openModal: dialog.

  dialog cancelled ifFalse: [self doOnOK].! !


SDActiveRecord subclass: #Contact
  instanceVariableNames: 'firstName lastName'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'ContactManagerSSDb'!
!Contact commentStamp: 'estelle 2/3/2011 08:08' prior: 0!
I have informations about people. I can store created instances.

|someone|
someone := Contact new firstName: 'Miles'; lastName:'Davis'.
Contact database add: someone.

self assert: Contact database last firstName = 'Miles'.
self assert: Contact database last lastName = 'Davis'.!


!Contact methodsFor: 'accessing' stamp: 'LaurentLaffont 1/23/2011 10:20'!
firstName
  ^ firstName ifNil: [firstName := 'unknown']! !

!Contact methodsFor: 'accessing' stamp: 'LaurentLaffont 1/22/2011 18:11'!
firstName: anObject
  firstName := anObject! !

!Contact methodsFor: 'accessing' stamp: 'LaurentLaffont 1/23/2011 10:19'!
lastName
  ^ lastName ifNil: [lastName := 'unknown']! !

!Contact methodsFor: 'accessing' stamp: 'LaurentLaffont 1/22/2011 18:11'!
lastName: anObject
  lastName := anObject! !


!Contact methodsFor: 'printing' stamp: 'LaurentLaffont 1/22/2011 18:15'!
printOn: aStream
  aStream
    nextPutAll: self className;
    nextPutAll: '(';
    nextPutAll: self firstName;
    nextPutAll: ' ';
    nextPutAll: self lastName;
    nextPutAll: ')'.! !

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

Contact class
  instanceVariableNames: ''!

!Contact class methodsFor: 'accessing' stamp: 'DougEdmunds 5/3/2011 12:38'!
database
  |db|
  db := Contact findAll asOrderedCollection.  
  ^ db! !


Object subclass: #ContactListEditor
  instanceVariableNames: 'selectedContactIndex mainWindow'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'ContactManagerSSDb'!
!ContactListEditor commentStamp: 'DougEdmunds 5/3/2011 12:37' prior: 0!
Window to add / remove / edit a list of Contact.

Open with 
"ContactListEditor open."!


!ContactListEditor methodsFor: 'callback' stamp: 'DougEdmunds 5/3/2011 11:11'!
addButtonClick
  |newContact|
  newContact := Contact new.

  ContactEditor new
    contact: newContact;
    onOK: [ newContact save.  
        selectedContactIndex := Contact database size.
        self 
          changed: #contacts;
          changed: #hasSelectedContact];
    openModal.

  ! !

!ContactListEditor methodsFor: 'callback' stamp: 'LaurentLaffont 1/25/2011 21:17'!
contactSelectedIndex: aSmallInteger 
  selectedContactIndex := aSmallInteger.
  self 
    changed: #contactSelectedIndex;
      changed: #hasSelectedContact! !

!ContactListEditor methodsFor: 'callback' stamp: 'DougEdmunds 5/3/2011 11:56'!
editButtonClick
  |thisContact|
  ContactEditor new
    contact: (thisContact := Contact database at: selectedContactIndex);
    onOK: [ thisContact save.
        selectedContactIndex := Contact database size.
        Transcript cr; show: selectedContactIndex.
        self
          changed: #contacts;
          changed: #hasSelectedContact];
    openModal.

  self changed: #contacts.! !

!ContactListEditor methodsFor: 'callback' stamp: 'DougEdmunds 5/3/2011 11:18'!
removeButtonClick

  (Contact database at: selectedContactIndex) delete.

  self
      contactSelectedIndex: (self contactSelectedIndex min: Contact database size);
      changed: #contacts  ! !


!ContactListEditor methodsFor: 'accessing' stamp: 'LaurentLaffont 1/25/2011 21:17'!
contactSelectedIndex
  ^ selectedContactIndex ifNil: [selectedContactIndex := 0]! !

!ContactListEditor methodsFor: 'accessing' stamp: 'DougEdmunds 5/3/2011 11:38'!
contacts
  ^ (Contact database) collect: [:aContact| 
    ', ' join: {aContact lastName.  aContact firstName}
  ].! !

!ContactListEditor methodsFor: 'accessing' stamp: 'LaurentLaffont 1/25/2011 21:18'!
hasSelectedContact
  ^selectedContactIndex > 0! !


!ContactListEditor methodsFor: 'open/close' stamp: 'DougEdmunds 5/3/2011 11:41'!
open
|builder content|
builder := UITheme builder.

content := builder newColumn: {   
  builder 
    newListFor: self   
    list: #contacts
    selected: #contactSelectedIndex
    changeSelected: #contactSelectedIndex:
    help: 'contacts'.
  builder newRow: {
    builder newButtonFor: self 
                action: #addButtonClick 
                label: 'Add' 
                help: 'Create a new contact'.
    builder newButtonFor: self 
                action: #removeButtonClick 
                getEnabled: #hasSelectedContact 
                label: 'Remove' 
                help: 'Remove selected contact'.
    builder newButtonFor: self 
                action: #editButtonClick 
                getEnabled: #hasSelectedContact 
                label: 'Edit' 
                help: 'Edit selected contact'.
    builder newButtonFor: self 
                action: #closeButtonClick
                label: 'Close' 
                help: 'Close' .                       

                  }}.

mainWindow := (content openInWindowLabeled: 'Contacts') extent: 400@300.! !


!ContactListEditor methodsFor: 'as yet unclassified' stamp: 'DougEdmunds 5/3/2011 11:12'!
closeButtonClick

  mainWindow delete.! !

!ContactListEditor methodsFor: 'as yet unclassified' stamp: 'DougEdmunds 5/3/2011 12:44'!
initialize

  SDCheckPointer startUp: true.
  Contact warmUp.! !

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

ContactListEditor class
  instanceVariableNames: ''!

!ContactListEditor class methodsFor: 'menu' stamp: 'LaurentLaffont 1/28/2011 21:38'!
menuCommandOn: aBuilder 
  <worldMenu> 
  (aBuilder item: #'Manage contacts')
      action:[ self open].! !


!ContactListEditor class methodsFor: 'instance creation' stamp: 'LaurentLaffont 1/23/2011 11:10'!
open
  ^ self new open.! !

Edit - History - Print - Recent Changes - Search
Page last modified on May 05, 2011, at 01:06 PM