[Seaside] ROE - VW 42 Port

Brett Taylor brett.taylor at healthauditors.com
Tue Apr 27 01:31:23 CEST 2004


I've just completed the ROE 42 port to VisualWorks.  I've published the
port on the Cincom Public Store as version 4.2 of the ROE bundle.

  The port was pretty straight forward, but did require some
modifications to the Squeak code in order to work in VW.  I've attached
a change set with the changes.  I've also added support for Oracle by
creating OracleRelation.   See the test class for  RATestOracleSemantics
for  examples. 

Some Notes: 
1) The differences between Smalltalk database access libraries (EXDI in
VisualWorks) in VW and Squeaks requires separate versions of the methods
RASQLRelation>>query: & RASQLRelation>>exec: for each dialect.   The
database library dictates how the DatabaseConnection is accessed.  So,
RAPostgresRelation must perform the query different depending upon the
database access library being used. This needs to be addressed through
refactoring the exec: and query: methods.  One option would be to create
a wrapper  class for the DB Access library with a standard protocol
across libraries.  

2) The problems remain with the way attribute names are compared by
different databases.  I've included some modifications to sort these
problems out by delegating attribute name comparisons to the
ConcreteRelation subclass.

Brett Taylor
-------------- next part --------------
"Changes in change set RoeVwPort"!
'From VisualWorks?, 7.2 of November 3, 2003 on April 26, 2004 at 4:24:27 pm'!


Smalltalk.Roe defineClass: #RAOracleRelation
	superclass: #{Roe.RASQLRelation}
	indexedType: #none
	private: false
	instanceVariableNames: ''
	classInstanceVariableNames: ''
	imports: ''
	category: 'ROE-Relations-Concrete'!

!Roe.RATuple methodsFor: 'as yet unclassified'!

hasAttributeNamed: aString 
	| concreteR |
	concreteR := self concreteRelation.
	^relation attributes 
		anySatisfy: [:ea | concreteR isAttributeName: ea name equalTo: aString]! !


!Roe.RARelation methodsFor: 'accessing'!

isAttributeName: firstName equalTo: secondName 
	^(self normalizeAttributeName: firstName) 
		= (self normalizeAttributeName: secondName)!

normalizeAttributeName: firstName 
	^firstName asString! !


!Roe.RARelation methodsFor: 'core operators'!

rename: oldName to: newName
	^ self renameAll: (Array with: oldName) to: (Array with: newName)!

renameAll: oldNameArray to: newNameArray
	^ RAAlias of: self from: (oldNameArray collect: [:e | e asString ] ) to: (newNameArray collect: [:e | e asString ] )! !

!Roe.RARelation methodsFor: 'accessing'!

attributeNamed: aString ifAbsent: errorBlock 
	| attribute |
	self attributes do: 
			[:ea | 
			(self concreteRelation isAttributeName: ea name equalTo: aString) 
				ifTrue: 
					[attribute ifNil: [attribute := ea]
						ifNotNil: [self ambiguousAttributeError: aString]]].
	^attribute ifNotNil: [attribute] ifNil: errorBlock! !


!Roe.RAOracleRelation methodsFor: 'private'!

basicExec: aString
	| result |
	result := connection execute: aString.
	^ result!

basicQuery: aString
	| result |
	result := self basicExec: aString.
	^ result upToEnd!

discoverAttributes
	^(self query: self sqlDiscoverAttributes) 
		collect: [ :each | RASimpleAttribute named: each first relation: self ]! !

!Roe.RAOracleRelation methodsFor: 'accessing'!

normalizeAttributeName: firstName
 
	^firstName asString asUppercase! !


!Roe.RAOracleRelation methodsFor: 'visiting'!

acceptRoeVisitor: aVisitor
	^ aVisitor visitOracleRelation: self! !

!Roe.RAOracleRelation methodsFor: 'updating'!

sqlInsert: attributeNames values: anArray 
	^String streamContents: 
			[:stream | 
			stream
				nextPutAll: 'INSERT INTO ';
				nextPutAll: self name;
				nextPutAll: ' ('.
			attributeNames do: [:each | stream nextPutAll: each]
				separatedBy: [stream nextPutAll: ', '].
			stream nextPutAll: ') VALUES ('.
			anArray do: 
					[:each | 
					each isString 
						ifTrue: 
							[stream
								nextPut: $';
								nextPutAll: each asEscapedSql;
								nextPut: $']
						ifFalse: [stream nextPutAll: each asString printString]]
				separatedBy: [stream nextPutAll: ', '].
			stream nextPutAll: ')']! !

!Roe.RAOracleRelation methodsFor: 'accessing'!

nameForString: aString
	^aString asUppercase asSymbol!

sqlDiscoverAttributes
	^'SELECT column_name FROM user_tab_columns where table_name = ' 
		, self name printString asUppercase!

sqlPrinterClass
	^RAOracleSqlPrinter! !


Roe.RAOracleRelation reorganizeFromString: '(''visiting'' #acceptRoeVisitor:)
(''updating'' #sqlInsert:values:)
(''private'' #basicExec: #basicQuery: #discoverAttributes)
(''accessing'' #nameForString: #normalizeAttributeName: #sqlDiscoverAttributes #sqlPrinterClass)
'!

!Roe.RATestSemantics methodsFor: 'private'!

assertQueryUnordered: aRelation gives: anArray
	| relationValues expectedResultSet |
 
	relationValues := (aRelation collect: [:ea | ea values asArray]) asSet.
	expectedResultSet :=anArray asSet.
	self assert: relationValues size = expectedResultSet size.
	self assert: (relationValues - expectedResultSet) isEmpty! !


#{Roe.RADatabaseRelation} removeFromSystem!

CodeComponent type: #package named:  'ROE-Visitors' classNamed: 'Root.Smalltalk.Roe.RAPrinter' meta: false selector: #visitBinaryNode: change: #added!

CodeComponent type: #package named:  'ROE-Visitors' classNamed: 'Root.Smalltalk.Roe.RAPrinter' meta: false selector: #printOperator: change: #added!

CodeComponent type: #package named:  'ROE-Visitors' classNamed: 'Root.Smalltalk.Roe.RASingleTableSqlPrinter' meta: false selector: #printOperator: change: #added!

CodeComponent type: #package named:  'ROE-Visitors' classNamed: 'Root.Smalltalk.Roe.RASqlPrinter' meta: false selector: #printOperator: change: #added!

CodeComponent type: #package named:  'ROE-Relations-Core' classNamed: 'Root.Smalltalk.Roe.RAAlias' meta: false selector: #setRelation:attributes:newNames: change: #added!

CodeComponent type: #package named:  'ROE-Relations-Core' classNamed: 'Root.Smalltalk.Roe.RAGrouping' meta: false selector: #setSource:groupAttributes: change: #added!

CodeComponent type: #package named:  'ROE-Relations-Core' classNamed: 'Root.Smalltalk.Roe.RAOrdering' meta: false selector: #setSource:orderAttributes:ascending: change: #added!

CodeComponent type: #package named:  'ROE-Relations-Core' classNamed: 'Root.Smalltalk.Roe.RAProjection' meta: false selector: #setRelation:attributes: change: #added!

CodeComponent type: #package named:  'ROE-Relations-Core' classNamed: 'Root.Smalltalk.Roe.RARelation' meta: false selector: #attributeNamed:ifAbsent: change: #added!

CodeComponent type: #package named:  'ROE-Conditions' classNamed: 'Root.Smalltalk.Roe.RABinaryNode' meta: false selector: #sqlOperator change: #added!

CodeComponent type: #package named:  'ROE-Tuples' classNamed: 'Root.Smalltalk.Roe.RATuple' meta: false selector: #at: change: #added!

CodeComponent type: #package named:  'ROE-Tuples' classNamed: 'Root.Smalltalk.Roe.RATuple' meta: false selector: #doesNotUnderstand: change: #added!

CodeComponent type: #package named:  'ROE-Tuples' classNamed: 'Root.Smalltalk.Roe.RATuple' meta: false selector: #hasAttributeNamed: change: #added!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestPostgresSemantics' meta: false selector: #setUp change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RAAlias' meta: false selector: #setRelation:attributes:newNames: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RABinaryNode' meta: false selector: #sqlOperator change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RAGrouping' meta: false selector: #setSource:groupAttributes: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RAMockCourse' meta: false selector: #initializeWithValues: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RAMockStudent' meta: false selector: #initializeWithValues: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RAOrdering' meta: false selector: #setSource:orderAttributes:ascending: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RAPrinter' meta: false selector: #visitBinaryNode: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RAPrinter' meta: false selector: #printOperator: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RAProjection' meta: false selector: #setRelation:attributes: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RARelation' meta: false selector: #attributeNamed:ifAbsent: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RASingleTableSqlPrinter' meta: false selector: #printOperator: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RASqlPrinter' meta: false selector: #printOperator: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestPostgresSemanticsWithNils' meta: false selector: #dropNilColumnFromRelation: change: #removed!

CodeComponent type: #package named: 'ROE-Attributes' ownerNamed: 'Root.Smalltalk.Roe.RATestPostgresSemantics' static: #ConnectionArgs change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #setUp change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #testStudentIndex change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #testOrderStudents change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #testFindClassmates change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #addAllValues:to: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #assertQueryOrdered:gives: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #assertQueryUnordered:gives: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATestSyntax' meta: false selector: #setUp change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATuple' meta: false selector: #at: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATuple' meta: false selector: #doesNotUnderstand: change: #removed!

CodeComponent type: #package named:  'ROE-Attributes' classNamed: 'Root.Smalltalk.Roe.RATuple' meta: false selector: #hasAttributeNamed: change: #removed!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestPostgresSemantics' meta: false selector: #setUp change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RAMockCourse' meta: false selector: #initializeWithValues: change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RAMockStudent' meta: false selector: #initializeWithValues: change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestPostgresSemanticsWithNils' meta: false selector: #dropNilColumnFromRelation: change: #added!

CodeComponent type: #package named: 'ROE-Tests' ownerNamed: 'Root.Smalltalk.Roe.RATestPostgresSemantics' static: #ConnectionArgs change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #setUp change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #testStudentIndex change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #testOrderStudents change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #testFindClassmates change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #addAllValues:to: change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #assertQueryOrdered:gives: change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestSemantics' meta: false selector: #assertQueryUnordered:gives: change: #added!

CodeComponent type: #package named:  'ROE-Tests' classNamed: 'Root.Smalltalk.Roe.RATestSyntax' meta: false selector: #setUp change: #added!



More information about the Seaside mailing list