help-smalltalk
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

[Help-smalltalk] [PATCH] resurrect MySQL driver and update to 4.1+ proto


From: Paolo Bonzini
Subject: [Help-smalltalk] [PATCH] resurrect MySQL driver and update to 4.1+ protocol
Date: Tue, 14 Aug 2007 12:42:29 +0200
User-agent: Thunderbird 2.0.0.6 (Macintosh/20070728)

This resurrects the MySQL driver from the shades of time. However, I'm pretty sure that there won't be anything like this in 3.0. There is somewhere a DBI-like interface for Postgres, and it makes sense to port the MySQL driver to it since it can't be worse than this. I'm only interested in converting it successfully (and hopefully Glorp too).

The MySQL package can be tested by configuring with --enable-mysql-tests; it requires MySQL to be running with a user called 'root' and whose password is, you guessed it, 'root'.

Paolo
* looking for address@hidden/smalltalk--devo--2.2--patch-520 to compare with
* comparing to address@hidden/smalltalk--devo--2.2--patch-520
M  tests/testsuite.at
M  tests/local.at
M  tests/testsuite
M  packages/mysql/package.xml
M  configure.ac
M  packages/mysql/MySQL.st
M  packages/mysql/MySQLTests.st
M  packages/mysql/mysql-test.st
M  tests/Makefile.am

* modified files

--- orig/configure.ac
+++ mod/configure.ac
@@ -295,7 +295,15 @@ GST_PACKAGE_ENABLE([Iconv], [iconv],
   [Makefile], [iconv.la])
 GST_PACKAGE_ENABLE([Java], [java])
 GST_PACKAGE_ENABLE([Digest], [digest], [], [], [Makefile], [digest.la])
+
 GST_PACKAGE_ENABLE([MySQL], [mysql])
+AC_MSG_CHECKING([whether to run MySQL tests])
+AC_ARG_ENABLE(mysql-tests,
+[  --enable-mysql-tests   test MySQL bindings, require user "root" with
+                          password "root", plus database "test"], ,
+[enable_mysql_tests=no])
+AC_SUBST(enable_mysql_tests)
+
 GST_PACKAGE_ENABLE([NCurses],
   [ncurses],
   [GST_HAVE_LIB(ncurses, initscr)],
@@ -400,6 +408,7 @@ dnl Scripts & data files
 AC_CONFIG_FILES(gnu-smalltalk.pc)
 AC_CONFIG_FILES(gst-config, chmod +x gst-config)
 AC_CONFIG_FILES(tests/gst, chmod +x tests/gst)
+AC_CONFIG_FILES(tests/atlocal)
 AC_CONFIG_FILES(libc.la)
 
 dnl Master Makefile


--- orig/packages/mysql/MySQL.st
+++ mod/packages/mysql/MySQL.st
@@ -73,14 +73,14 @@ Object subclass: #JdmMysqlCommand
 
 
 Jdm.JdmConnection subclass: #JdmConnection
-       instanceVariableNames: 'socket readStream writeStream hashesByProtocol 
responsePacket clientCapabilities '
+       instanceVariableNames: 'socket readStream writeStream hashesByProtocol 
responsePacket '
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Mysql-Driver'!
 
 
 Jdm.JdmServerInfo subclass: #JdmServerInfo
-       instanceVariableNames: 'protocol serverThread hashSeed options '
+       instanceVariableNames: 'protocol serverThread charset status hashSeed 
options '
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Mysql-Driver'!
@@ -113,7 +113,7 @@ Object subclass: #JdmTimestampWriter
        category: 'Mysql-Driver'!
 
 Jdm.JdmColumn subclass: #JdmColumn
-       instanceVariableNames: ''
+       instanceVariableNames: 'charset'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Mysql-Driver'!
@@ -159,7 +159,7 @@ nextPutAllNullTerminated: aCollection2 
 
 nextPutCommand: aCommand 
        self
-               nextPut: aCommand command asCharacter;
+               nextPut: (Character value: aCommand command);
                nextPutAllNullTerminated: aCommand message!
 
 outputPacket
@@ -300,9 +300,6 @@ initialize
 
 initializeConnection
     | messageText |
-    hashesByProtocol := self class dictionaryClass: Dictionary
-                                  from: self class protocolHashes.
-
     socket := TCP.Socket remote: connectionSpec host port: connectionSpec port.
     "socket := [ TCP Socket remote: connectionSpec host port: connectionSpec 
port ]
        on: Error
@@ -313,7 +310,7 @@ initializeConnection
     readStream := socket.
     writeStream := socket.
     serverInfo := JdmServerInfo on: self.
-    clientCapabilities := serverInfo protocol = 10 ifTrue: [1] ifFalse: [0]!
+!
 
 initializeDatabase
     (self requestPacket writeStream)
@@ -322,46 +319,53 @@ initializeDatabase
        flush.
     self responsePacket checkStatusOnError: #setDatabase!
 
+oldProtocolHashes
+    connectionSpec password isEmpty ifTrue: [ ^'' ].
+    ^{ self hash2: connectionSpec password seed: self serverInfo hashSeed }!
+
+newProtocolHashes
+    connectionSpec password isEmpty ifTrue: [ ^String new: 1 ].
+    ^{ self hashSHA1: connectionSpec password seed: self serverInfo hashSeed.
+       self hash2: connectionSpec password seed: self serverInfo hashSeed }!
+
 initializeUser
-    | replyStream password |
-    password := connectionSpec password isEmpty 
-       ifTrue: ['']
-       ifFalse: 
-           [self 
-                hash: connectionSpec password
-                seed: self serverInfo hashSeed
-                for: self serverInfo protocol].
-    
+    | replyStream hashes userSent longPassword |
     replyStream := self replyPacket writeStream.
-
-    replyStream 
-       nextPutAll: (self class integerAsByteArray: (self clientCapabilities) 
length: 2) asByteString;
-       nextPutAll: (self class integerAsByteArray: 65536 length: 3) 
asByteString;
-       nextPutAllNullTerminated: connectionSpec user;
-       nextPutAllNullTerminated: password.
-    replyStream flush.
+    serverInfo hashSeed size = 8
+       ifTrue: [
+           hashes := self oldProtocolHashes.
+           replyStream
+               nextPutAll: (self class integerAsByteArray: 1 length: 2) 
asByteString;
+               nextPutAll: (self class integerAsByteArray: 65536 length: 3) 
asByteString;
+               nextPutAllNullTerminated: connectionSpec user;
+               nextPutAllNullTerminated: hashes first;
+               flush ]
+       ifFalse: [
+           hashes := self newProtocolHashes.
+           replyStream
+               nextPutAll: (self class integerAsByteArray: 41477 length: 4) 
asByteString;
+               nextPutAll: (self class integerAsByteArray: 65536 length: 4) 
asByteString;
+               nextPut: 8 asCharacter;
+               next: 23 put: 0 asCharacter;
+               nextPutAllNullTerminated: connectionSpec user;
+               nextPut: hashes first size asCharacter;
+               nextPutAll: hashes first;
+               flush.
    
-    self responsePacket checkStatusOnError: #authenticate! !
+           (self responsePacket isStatus: 254 onError: #authenticate) ifTrue: [
+               replyStream := self replyPacket writeStream.
+               replyStream nextPutAll: hashes second; flush ] ]! !
 
 !JdmConnection methodsFor: 'hashing'!
 
-getHashFor: aProtocol 
-       ^hashesByProtocol at: aProtocol ifAbsent: [nil]!
-
-hash: aString seed: aSeed for: aProtocol 
-       | aHashMethod |
-       aHashMethod := self getHashFor: aProtocol.
-       aHashMethod isNil ifTrue: [^aString].
+hash: aString seed: aSeed for: hashMethod 
        ^self class 
-               perform: aHashMethod
+               perform: hashMethod
                with: aString
                with: aSeed! !
 
 !JdmConnection methodsFor: 'accessing'!
 
-clientCapabilities
-       ^clientCapabilities!
-
 replyPacket
        ^(JdmOutputPacket on: writeStream) 
                packetNumber: responsePacket packetNumber + 1!
@@ -378,42 +382,44 @@ JdmConnection class
        instanceVariableNames: ''!
 
 
-!JdmConnection class methodsFor: 'constants'!
-
-protocolHashes
-       ^#(9 #hash1:seed:
-          10 #hash2:seed:)! !
-
-!JdmConnection class methodsFor: 'hashing'!
+!JdmConnection methodsFor: 'hashing'!
 
-hash1: aString seed: aSeed 
-       "This algorithm is for protocol 9."
+hashSHA1: aString seed: aSeed 
+       "This algorithm is for MySQL 4.1+."
 
-       | hashedString maxValue array num1 num2 |
-       hashedString := String new: aSeed size.
-       array := self randomInit1: aString seed: aSeed.
-       maxValue := array at: 1.
-       num1 := array at: 2.
-       num2 := array at: 3.
-       1 to: hashedString size
-               do: 
-                       [:index | 
-                       | num3 |
-                       num1 := (num1 * 3 + num2) \\ maxValue.
-                       num2 := (num1 + num2 + 33) \\ maxValue.
-                       num3 := (num1 / maxValue * 31) truncated + 64.
-                       hashedString at: index put: num3 asCharacter].
-       ^hashedString!
+       | hashedString hashedStringSeeded result |
+       "Compute hash1 = SHA1(password), then hash2 = SHA1(hash1). The server
+        already knows this, as that is what is held in its password table
+        (preceded with a *)."
+
+       hashedString := SHA1 digestOf: aString.
+       hashedStringSeeded := SHA1 digestOf: hashedString.
+
+       "Append hash2 to the salt sent by the server and hash that."
+       hashedStringSeeded := SHA1 digestOf: aSeed, hashedStringSeeded.
+
+       "Finally, XOR the result with SHA1(password).  The server takes this,
+        computes SHA1(salt.`SHA1 stored in DB`), uses the latter result to
+        undo the XOR, computes again SHA1, and compares that with the SHA1
+        stored in the DB."
+
+       result := String new: 20.
+       1 to: 20 do: [ :i |
+           result at: i put: (Character value:
+               ((hashedString at: i) bitXor: (hashedStringSeeded at: i))) ].
+       ^result!
 
-hash2: aString seed: aSeed 
-       "This algorithm is for clientProtocol 10."
+hash2: aString seed: longSeed 
+       "This algorithm is for MySQL 3.22+."
 
-       | hashedString maxValue result num1 num2 num3 |
+       | hashedString maxValue result num1 num2 num3 aSeed |
+       "Reserve a final byte for NULL termination"
+       aSeed := longSeed copyFrom: 1 to: 8.
        hashedString := String new: aSeed size.
        result := self randomInit2: aString seed: aSeed.
-       maxValue := result at: 1.
-       num1 := result at: 2.
-       num2 := result at: 3.
+       maxValue := 16r3FFFFFFF.
+       num1 := result at: 1.
+       num2 := result at: 2.
        1 to: hashedString size
                do: 
                        [:index | 
@@ -424,11 +430,10 @@ hash2: aString seed: aSeed 
        num1 := (num1 * 3 + num2) \\ maxValue.
        num2 := (num1 + num2 + 33) \\ maxValue.
        num3 := (num1 / maxValue * 31) truncated.
-       hashedString inject: 1
-               into: 
-                       [:index :character | 
-                       hashedString at: index put: (character asInteger 
bitXor: num3) asCharacter.
-                       index + 1].
+       hashedString keysAndValuesDo: [:index :character | 
+               hashedString
+                       at: index
+                       put: (character asInteger bitXor: num3) asCharacter].
        ^hashedString!
 
 hash: aString 
@@ -450,24 +455,13 @@ hash: aString 
                                        num3 := num3 + charValue]].
        ^Array with: (num1 bitAnd: 2147483647) with: (num2 bitAnd: 2147483647)!
 
-randomInit1: aString seed: aSeed 
-       | result array1 array2 |
-       result := Array new: 3.
-       array1 := self hash: aString.
-       array2 := self hash: aSeed.
-       result at: 1 put: 16r01FFFFFF.
-       result at: 2 put: ((array1 at: 1) bitXor: (array2 at: 1)) \\ (result 
at: 1).
-       result at: 3 put: (result at: 2) // 2.
-       ^result!
-
 randomInit2: aString seed: aSeed 
        | result array1 array2 |
-       result := Array new: 3.
+       result := Array new: 2.
        array1 := self hash: aString.
        array2 := self hash: aSeed.
-       result at: 1 put: 16r3FFFFFFF.
-       result at: 2 put: ((array1 at: 1) bitXor: (array2 at: 1)) \\ (result 
at: 1).
-       result at: 3 put: ((array1 at: 2) bitXor: (array2 at: 2)) \\ (result 
at: 1).
+       result at: 1 put: ((array1 at: 1) bitXor: (array2 at: 1)) \\ 
16r3FFFFFFF.
+       result at: 2 put: ((array1 at: 2) bitXor: (array2 at: 2)) \\ 
16r3FFFFFFF.
        ^result! !
 
 !JdmConnection class methodsFor: 'misc'!
@@ -505,7 +499,7 @@ byteArrayAsByteString: ba
     size := ba size.
     s := String new: size.
     1 to: size do: [:index |
-       s at: index put: ((ba at: index) asCharacter).
+       s at: index put: (Character value: (ba at: index)).
        ].
     ^s! !
 
@@ -573,6 +567,9 @@ initialize
 
 !JdmInputPacket methodsFor: 'reading'!
 
+isStatus: anInteger onError: aSymbol
+       ^(self readStatusOnError: aSymbol) = anInteger!
+
 checkForStatus: anInteger onError: aSymbol
        (self readStatusOnError: aSymbol) = anInteger ifFalse: [self 
handleError: aSymbol]!
 
@@ -647,8 +644,7 @@ flush
        s := JdmConnection byteArrayAsByteString: ba.
        aString replaceFrom: 1 to: self class sizeSize with: s startingAt: 1.
 
-       aString at: self class sizeSize + 1 put: self packetNumber asCharacter.
-       
+       aString at: self class sizeSize + 1 put: (Character value: self 
packetNumber).
        (self stream) nextPutAll: aString; flush
 ! !
 
@@ -761,6 +757,18 @@ initialize
 
 !JdmServerInfo methodsFor: 'accessing'!
 
+charset
+       ^charset!
+
+charset: anObject
+       charset := anObject!
+
+status
+       ^status!
+
+status: anObject
+       status := anObject!
+
 hashSeed
        ^hashSeed!
 
@@ -794,11 +802,26 @@ readFrom: aResponsePacket
                readServerVersionFrom: aResponsePacket;
                readServerThreadFrom: aResponsePacket;
                readHashSeedFrom: aResponsePacket;
-               readOptionsFrom: aResponsePacket!
+               readOptionsFrom: aResponsePacket.
+       aResponsePacket readStream atEnd ifFalse: [
+               self
+                       readCharsetFrom: aResponsePacket;
+                       readStatusFrom: aResponsePacket;
+                       readMoreSeedFrom: aResponsePacket ]!
+
+readStatusFrom: aResponsePacket
+       status := (aResponsePacket readStream next: 2) asByteArray asInteger.
+       aResponsePacket readStream next: 13!
+
+readCharsetFrom: aResponsePacket
+       charset := aResponsePacket readStream next value!
 
 readHashSeedFrom: aResponsePacket
        hashSeed := aResponsePacket readStream readNullTerminatedString!
 
+readMoreSeedFrom: aResponsePacket
+       hashSeed := hashSeed, aResponsePacket readStream 
readNullTerminatedString!
+
 readOptionsFrom: aResponsePacket 
        options := (aResponsePacket readStream next: 2) asByteArray asInteger!
 
@@ -809,7 +832,9 @@ readServerThreadFrom: aResponsePacket
        serverThread := (aResponsePacket readStream next: 4) asByteArray 
asInteger!
 
 readServerVersionFrom: aResponsePacket 
-       serverVersion := JdmServerVersion readFrom: aResponsePacket readStream! 
!
+       serverVersion := JdmServerVersion
+           readFrom: aResponsePacket readStream readNullTerminatedString 
readStream.
+! !
 
 !JdmServerInfo methodsFor: 'validation'!
 
@@ -848,7 +873,7 @@ readFrom: aStream
        release := Integer readFrom: aStream.
        aStream next.
        version := Integer readFrom: aStream.
-       aStream readNullTerminatedString! !
+! !
 
 !JdmServerVersion class methodsFor: 'instance creation'!
 
@@ -929,12 +954,17 @@ readMysqlTimeFrom: aStream 
        ^Time fromSeconds: 60 * (60 * hour + minute) + second!
 
 readMysqlTimestampFrom: aStream 
-       | year month day hour minute second |
+       | year month day hour minute second separators |
        year := self readIntegerFrom: aStream next: 4.
+       separators := aStream peekFor: $-.
        month := self readIntegerFrom: aStream next: 2.
+       separators ifTrue: [ aStream next ].
        day := self readIntegerFrom: aStream next: 2.
+       separators ifTrue: [ aStream next ].
        hour := self readIntegerFrom: aStream next: 2.
+       separators ifTrue: [ aStream next ].
        minute := self readIntegerFrom: aStream next: 2.
+       separators ifTrue: [ aStream next ].
        second := self readIntegerFrom: aStream next: 2.
        ^JdmDateTime
                fromDate: (Date newDay: day monthIndex: month year: year)
@@ -982,37 +1012,62 @@ print: anInteger on: aStream next: n 
 
 !JdmColumn methodsFor: 'reading'!
 
+charset
+       ^charset
+! !
+
+!JdmColumn methodsFor: 'reading'!
+
 readDecimalPlaces: aReadStream
        decimalPlaces := aReadStream next asInteger!
 
 readFlags: aReadStream 
-       "Currently the size of both the flags field and decimalPlaces field is 
specified as a sum of the two.
-        I am guessing that the size of the flags is more likely to change than 
that of the decimalPlaces.
-        Right now I assume that the flags are all bytes but the last and that 
the last is the decimalPlaces"
-
-       flags := (aReadStream next: aReadStream next asInteger - 1) asByteArray 
-                               asInteger!
+       flags := (aReadStream next: 2) asByteArray asInteger!
 
 readFrom: aReadStream 
-       self
-               readTable: aReadStream;
-               readName: aReadStream;
-               readSize: aReadStream;
-               readType: aReadStream;
-               readFlags: aReadStream;
-               readDecimalPlaces: aReadStream!
+       | length fields |
+       "can be catalogue, db, table, org table, field (and org field follows)
+        or table, field, length, type, flags+decimal"
+       fields := (1 to: 5) collect: [ :i |
+               aReadStream next: aReadStream next asInteger ].
+       aReadStream atEnd ifFalse: [
+               table := fields at: 3.
+               name := fields at: 5.
+               "org field"
+               aReadStream next: aReadStream next asInteger.
+               length := aReadStream next asInteger - 10.
+               self
+                       readCharset: aReadStream;
+                       readSize: aReadStream;
+                       readType: aReadStream;
+                       readFlags: aReadStream;
+                       readDecimalPlaces: aReadStream.
+               aReadStream next: length.
+               ^self ].
+
+       "MySQL 3.x format."
+       table := fields at: 1.
+       name := fields at: 2.
+       size := (fields at: 3) asByteArray asInteger.
+       type := (fields at: 4) first asInteger.
+       self readFlags: (fields at: 5) readStream.
+       decimalPlaces := (fields at: 5) last asInteger!
+
+
+readCharset: aReadStream
+       charset := (aReadStream next: 2) asByteArray asInteger!
 
 readName: aReadStream
        name := (aReadStream next: aReadStream next asInteger)!
 
 readSize: aReadStream
-       size := (aReadStream next: aReadStream next asInteger) asByteArray 
asInteger!
+       size := (aReadStream next: 4) asByteArray asInteger!
 
 readTable: aReadStream
        table := (aReadStream next: aReadStream next asInteger)!
 
 readType: aReadStream
-       type := (aReadStream next: aReadStream next asInteger) asByteArray 
asInteger! !
+       type := aReadStream next asInteger! !
 "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
 
 JdmColumn class
@@ -1030,8 +1085,11 @@ datetimeType
 dateType
        ^10!
 
+oldDecimalType
+       ^246!
+
 decimalType
-       ^0!
+       ^246!
 
 doubleType
        ^5!
@@ -1135,23 +1193,20 @@ readFrom: aReadStream
 checkForEndOrNull: aReadStream 
        "This is a bit unclean...the value 254 has been overloaded in the 
protocol.  When it is the only
         value in the stream, it indicates there are no more rows.  It also 
indicates that the following
-        4 bytes contain the size of the field value.  The problem is that 
there is another condition that
+        8 bytes contain the size of the field value.  The problem is that 
there is another condition that
         produces a single value on the stream...a row with one column whose 
value is NULL."
 
        | endOrNull |
-       aReadStream size = 1 ifFalse: [^false].
-       endOrNull := aReadStream next asInteger.
-       endOrNull = 254 
-               ifTrue: 
-                       [isEmpty := true.
-                       ^true].
-       endOrNull = 251 
-               ifTrue: 
-                       [^true].
-       "Unexpected Value"
-       JdmErrorTable throwException: #invalidQuery
-               message: 'Unexpected value ' , endOrNull printString.
-       ^true!
+       aReadStream size = 1 ifTrue: [
+               endOrNull := aReadStream next asInteger.
+               isEmpty := endOrNull = 254.
+               ^true ].
+       (aReadStream size < 9 and: [ aReadStream peekFor: (Character value: 
254) ])
+               ifTrue: [
+                       aReadStream next: aReadStream size - 1.
+                       isEmpty := true.
+                       ^true ].
+       ^false !
 
 readFrom: aReadStream 
        (self checkForEndOrNull: aReadStream) ifTrue: [^self].
@@ -1170,7 +1225,9 @@ readSizeFrom: aReadStream 
        aSize := aReadStream next asInteger.
        aSize < 251 ifTrue: [^aSize].
        aSize = 251 ifTrue: [^-1].
-       ^(aReadStream next: (aSize bitAnd: 3) + 2) asByteArray asInteger! !
+       aSize = 252 ifTrue: [^(aReadStream next: 2) asByteArray asInteger].
+       aSize = 253 ifTrue: [^(aReadStream next: 3) asByteArray asInteger].
+       aSize = 254 ifTrue: [^(aReadStream next: 8) asByteArray asInteger]! !
 
 !JdmRow methodsFor: 'initialize-release'!
 
@@ -1369,6 +1426,7 @@ buildTypeMap
                at: JdmColumn longlongType put: #toInteger:column:;
                at: JdmColumn floatType put: #toFloat:column:;
                at: JdmColumn doubleType put: #toDouble:column:;
+               at: JdmColumn oldDecimalType put: #toDouble:column:;
                at: JdmColumn decimalType put: #toDouble:column:;
                at: JdmColumn dateType put: #toDate:column:;
                at: JdmColumn datetimeType put: #toDateTime:column:;
@@ -1413,7 +1471,7 @@ asByteString
     | stream | 
     stream := WriteStream on: String new.
     1 to: self size do: [ :x |
-       stream nextPut: (self basicAt: x) asCharacter].
+       stream nextPut: (Character value: (self basicAt: x))].
     ^stream contents
 ! !
 


--- orig/packages/mysql/MySQLTests.st
+++ mod/packages/mysql/MySQLTests.st
@@ -29,9 +29,6 @@
 |
  ======================================================================"
 
-Jdm addSubspace: #MySQL!
-Namespace current: Jdm.MySQL!
-
 TestCase subclass: #JdmMysqlBaseTestCase
        instanceVariableNames: 'connection testSupport testProgress '
        classVariableNames: ''
@@ -127,17 +124,25 @@ createTable
        Transcript show: 'Creating table: ', testSupport class tableName, '...'.
        result := connection createStatement 
                                executeQuery: testSupport createTable.
-       Transcript show: ' Done'.
+       Transcript show: ' Done'; nl.
        self should: [result type = #update and: [result value = 0]]! !
 
 !JdmMysqlDropTableTestCase methodsFor: 'tests'!
 
+dropTableIfExists
+       | result |
+       Transcript show: 'Dropping table: ', testSupport class tableName, '...'.
+       result := connection createStatement 
+                               executeQuery: 'drop table if exists ' , 
testSupport class tableName.
+       Transcript show: ' Done'; nl.
+       self should: [result type = #update and: [result value = 0]]!
+
 dropTable
        | result |
        Transcript show: 'Dropping table: ', testSupport class tableName, '...'.
        result := connection createStatement 
                                executeQuery: 'drop table ' , testSupport class 
tableName.
-       Transcript show: ' Done'.
+       Transcript show: ' Done'; nl.
        self should: [result type = #update and: [result value = 0]]! !
 
 !JdmMysqlDeleteTestCase methodsFor: 'tests'!
@@ -148,8 +153,9 @@ deleteRows
                show: 'Deleting ' , testSupport class numRowsToInsert 
printString , ' rows...'.
        result := connection createStatement 
                                executeQuery: 'delete from ' , testSupport 
class tableName.
-       Transcript show: ' Done'.
-       self should: [result type = #update and: [result value = 0]]! !
+       Transcript show: ' Done'; nl.
+       "Value is either 0 or numRowsToInsert, depending on the version"
+       self should: [result type = #update]! !
 
 !JdmMysqlInsertTestCase methodsFor: 'tests'!
 
@@ -169,7 +175,7 @@ insertRows
        ok := true.
        testSupport class numRowsToInsert timesRepeat: [
                result := self insertRow.
-               ok := ok and: [result type = #update and: [result value = 1]].
+               ok := ok and: [result type = #update "and: [result value = 1]"].
        ].
        self should: [ ok ]! !
 
@@ -246,7 +252,7 @@ writeFieldDefinitionFor: aType on: aWrit
 connectionSpec
        ^JdmConnectionSpec new
                initialize;
-               user: 'utente'; password: '';
+               user: 'root'; password: 'root';
                host: 'localhost'; database: 'test';
                port: 3306; yourself!
 
@@ -498,7 +504,7 @@ resetMysqlTestSupport
 !JdmMysqlTestSupport class methodsFor: 'constants'!
 
 numRowsToInsert
-       ^500!
+       ^40!
 
 tableName
        ^'JdmMysqlTestTable'! !
@@ -587,7 +593,7 @@ checkSteps
        totalSteps = numSteps 
                ifTrue: 
                        [Transcript
-                               show: ' Done']! !
+                               show: ' Done'; nl]! !
 
 !JdmTestProgress methodsFor: 'accessing'!
 
@@ -636,6 +642,7 @@ defaultResolution
 initialize
 "      super initialize."
        self name: 'JdmMysql-Test'.
+       self addTest: (JdmMysqlDropTableTestCase selector: #dropTableIfExists).
        self addTest: (JdmMysqlCreateTableTestCase selector: #createTable).
        self addTest: (JdmMysqlInsertTestCase selector: #insertRows).
        self addTest: (JdmMysqlSelectTestCase selector: #selectRows).
@@ -645,7 +652,7 @@ initialize
 
 !JdmMysqlTestSuite class methodsFor: 'instance creation'!
 
-new
+suite
        ^super new initialize! !
 
 !JdmMysqlTestSupport methodsFor: 'private'!
@@ -941,11 +948,8 @@ resetMysqlTestSupport
 !JdmMysqlTestSupport class methodsFor: 'constants'!
 
 numRowsToInsert
-       ^500!
+       ^40!
 
 tableName
        ^'JdmMysqlTestTable'! !
 
-Namespace current: Smalltalk!
-
-


--- orig/packages/mysql/mysql-test.st
+++ mod/packages/mysql/mysql-test.st
@@ -5,11 +5,12 @@
 |
  ======================================================================"
 
-| value resultSet statement spec connection |
+PackageLoader fileInPackage: #MySQL!
 
+| value resultSet statement spec connection |
 spec :=    (Jdm.JdmConnectionSpec new initialize
-        user: 'root'; password: '';
-        host: 'philo';
+        user: 'root'; password: 'root';
+        host: 'localhost';
         database: 'mysql';
         port: 3306).
 


--- orig/packages/mysql/package.xml
+++ mod/packages/mysql/package.xml
@@ -4,8 +4,13 @@
   <prereq>DB</prereq>
   <prereq>TCP</prereq>
   <prereq>SUnit</prereq>
+  <prereq>Digest</prereq>
   <filein>MySQL.st</filein>
-  <filein>MySQLTests.st</filein>
+
+  <test>
+    <sunit>Jdm.MySQL.JdmMysqlTestSuite</sunit>
+    <filein>MySQLTests.st</filein>
+  </test>
 
   <file>MySQL.st</file>
   <file>MySQLTests.st</file>


--- orig/tests/Makefile.am
+++ mod/tests/Makefile.am
@@ -4,7 +4,7 @@ AUTOTEST = $(AUTOM4TE) --language=autote
 TESTSUITE = $(srcdir)/testsuite
 
 dist_noinst_DATA = \
-local.at testsuite.at $(TESTSUITE) package.m4 \
+atlocal.in local.at testsuite.at $(TESTSUITE) package.m4 \
 ackermann.ok ackermann.st arrays.ok arrays.st ary3.ok ary3.st blocks.ok \
 blocks.st chars.ok chars.st classes.ok classes.st cobjects.ok cobjects.st \
 compiler.ok compiler.st dates.ok dates.st delays.ok delays.st except.ok \
@@ -45,13 +45,13 @@ $(srcdir)/package.m4: $(top_srcdir)/conf
            echo 'm4_define([AT_PACKAGE_BUGREPORT], address@hidden@])'; \
          } >'$(srcdir)/package.m4'
 
-check-local: gst atconfig $(TESTSUITE)
+check-local: gst atlocal atconfig $(TESTSUITE)
        $(SHELL) '$(TESTSUITE)' $(TESTSUITEFLAGS)
 
 clean-local:
        -$(SHELL) '$(TESTSUITE)' --clean
 
-installcheck-local: atconfig $(TESTSUITE)
+installcheck-local: atlocal atconfig $(TESTSUITE)
        if test -z "$(DESTDIR)"; then \
          $(SHELL) '$(TESTSUITE)' $(TESTSUITEFLAGS) AUTOTEST_PATH=$(bindir); \
        fi


--- orig/tests/local.at
+++ mod/tests/local.at
@@ -40,24 +40,26 @@ m4_define([AT_DIFF_TEST], [
   AT_CLEANUP
 ])
 
-dnl AT_PACKAGE_TEST([PACKAGE], [XFAILS])
-dnl ------------------------------------
+dnl AT_PACKAGE_TEST([PACKAGE], [XFAILS], [CLASSES], [CONDITION])
+dnl ------------------------------------------------------------
 m4_define([AT_PACKAGE_TEST], [
   AT_SETUP([$1])
   AT_KEYWORDS([m4_if([$1], [SUnit], [], [$1 ])SUnit])
   $2
-  AT_CHECK_GST([-f $abs_top_srcdir/scripts/Test.st --verbose -p $1], [], [], 
[ignore])
+  m4_ifval([$4], [AT_CHECK([$4 || exit 77])])
+  AT_CHECK_GST([-f $abs_top_srcdir/scripts/Test.st --verbose -p $1 $3], [], 
[], [ignore])
   AT_CLEANUP
 ])
 
-dnl AT_OPTIONAL_PACKAGE_TEST([PACKAGE], [XFAILS])
-dnl ---------------------------------------------
+dnl AT_OPTIONAL_PACKAGE_TEST([PACKAGE], [XFAILS], [CLASSES], [CONDITION])
+dnl ---------------------------------------------------------------------
 dnl Returns exit code 77 (skip) if the package cannot be loaded.
 m4_define([AT_OPTIONAL_PACKAGE_TEST], [
   AT_SETUP([$1])
   AT_KEYWORDS([$1 SUnit])
   $2
-  AT_CHECK_GST([-f $abs_top_srcdir/scripts/Test.st --verbose -p $1
+  m4_ifval([$4], [AT_CHECK([$4 || exit 77])])
+  AT_CHECK_GST([-f $abs_top_srcdir/scripts/Test.st --verbose -p $1 $3
     ret=$?
     case $ret in
       2) exit 77 ;;


--- orig/tests/testsuite
+++ mod/tests/testsuite
@@ -620,7 +620,7 @@ at_times_file=$at_suite_dir/at-times
 # List of the tested programs.
 at_tested='gst'
 # List of the all the test groups.
-at_groups_all=' banner-1 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 
22 banner-2 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 banner-3 41 
42 banner-4 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 
65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 
91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 banner-5 108 109 110 
111 112 113 114 115'
+at_groups_all=' banner-1 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 
22 banner-2 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 banner-3 41 
42 banner-4 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 
65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 
91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 banner-5 108 109 110 
111 112 113 114 115 116'
 # As many question marks as there are digits in the last test group number.
 # Used to normalize the test group numbers so that `ls' lists them in
 # numerical order.
@@ -740,7 +740,8 @@ at_help_all="1;testsuite.at:27;arrays.st
 112;testsuite.at:146;Digest;Digest SUnit;
 113;testsuite.at:147;GDBM;GDBM SUnit;
 114;testsuite.at:148;Iconv;Iconv SUnit;
-115;testsuite.at:149;ZLib;ZLib SUnit;
+115;testsuite.at:149;MySQL;MySQL SUnit;
+116;testsuite.at:150;ZLib;ZLib SUnit;
 "
 
 at_prev=
@@ -4076,19 +4077,20 @@ _ATEOF
 
 
 
+
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
     *) image_path="" ;;
   esac
 
-  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p SUnit); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode"
+  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p SUnit ); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode"
   $at_traceoff
-echo "$at_srcdir/testsuite.at:71: { (cd \$abs_top_builddir && gst \$image_path 
-f \$abs_top_srcdir/scripts/Test.st --verbose -p SUnit); echo exit \$? > 
retcode; } | tr -d '\\r' | tee stdout; . retcode"
+echo "$at_srcdir/testsuite.at:71: { (cd \$abs_top_builddir && gst \$image_path 
-f \$abs_top_srcdir/scripts/Test.st --verbose -p SUnit ); echo exit \$? > 
retcode; } | tr -d '\\r' | tee stdout; . retcode"
 echo testsuite.at:71 >"$at_check_line_file"
 
 at_trace_this=
 if test -n "$at_traceon"; then
-    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p SUnit); echo exit $? > retcode; } 
| tr -d '\\r' | tee stdout; . retcode" in
+    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p SUnit ); echo exit $? > retcode; } 
| tr -d '\\r' | tee stdout; . retcode" in
         *'
 '*) echo 'Not enabling shell tracing (command contains an embedded newline)' ;;
  *) at_trace_this=yes ;;
@@ -4096,12 +4098,12 @@ if test -n "$at_traceon"; then
 fi
 
 if test -n "$at_trace_this"; then
-    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p SUnit); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
+    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p SUnit ); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
     at_status=$?
     grep '^ *+' "$at_stder1" >&2
     grep -v '^ *+' "$at_stder1" >"$at_stderr"
 else
-    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p SUnit); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
+    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p SUnit ); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
     at_status=$?
 fi
 
@@ -4143,19 +4145,20 @@ $at_traceon
 
 
 
+
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
     *) image_path="" ;;
   esac
 
-  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Parser); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode"
+  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Parser ); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode"
   $at_traceoff
-echo "$at_srcdir/testsuite.at:72: { (cd \$abs_top_builddir && gst \$image_path 
-f \$abs_top_srcdir/scripts/Test.st --verbose -p Parser); echo exit \$? > 
retcode; } | tr -d '\\r' | tee stdout; . retcode"
+echo "$at_srcdir/testsuite.at:72: { (cd \$abs_top_builddir && gst \$image_path 
-f \$abs_top_srcdir/scripts/Test.st --verbose -p Parser ); echo exit \$? > 
retcode; } | tr -d '\\r' | tee stdout; . retcode"
 echo testsuite.at:72 >"$at_check_line_file"
 
 at_trace_this=
 if test -n "$at_traceon"; then
-    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Parser); echo exit $? > retcode; } 
| tr -d '\\r' | tee stdout; . retcode" in
+    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Parser ); echo exit $? > retcode; 
} | tr -d '\\r' | tee stdout; . retcode" in
         *'
 '*) echo 'Not enabling shell tracing (command contains an embedded newline)' ;;
  *) at_trace_this=yes ;;
@@ -4163,12 +4166,12 @@ if test -n "$at_traceon"; then
 fi
 
 if test -n "$at_trace_this"; then
-    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Parser); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
+    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Parser ); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
     at_status=$?
     grep '^ *+' "$at_stder1" >&2
     grep -v '^ *+' "$at_stder1" >"$at_stderr"
 else
-    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Parser); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
+    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Parser ); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
     at_status=$?
 fi
 
@@ -8583,19 +8586,20 @@ _ATEOF
 
 
 
+
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
     *) image_path="" ;;
   esac
 
-  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Complex); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode"
+  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Complex ); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode"
   $at_traceoff
-echo "$at_srcdir/testsuite.at:142: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Complex); echo 
exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
+echo "$at_srcdir/testsuite.at:142: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Complex ); echo 
exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
 echo testsuite.at:142 >"$at_check_line_file"
 
 at_trace_this=
 if test -n "$at_traceon"; then
-    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Complex); echo exit $? > retcode; 
} | tr -d '\\r' | tee stdout; . retcode" in
+    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Complex ); echo exit $? > retcode; 
} | tr -d '\\r' | tee stdout; . retcode" in
         *'
 '*) echo 'Not enabling shell tracing (command contains an embedded newline)' ;;
  *) at_trace_this=yes ;;
@@ -8603,12 +8607,12 @@ if test -n "$at_traceon"; then
 fi
 
 if test -n "$at_trace_this"; then
-    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Complex); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
+    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Complex ); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
     at_status=$?
     grep '^ *+' "$at_stder1" >&2
     grep -v '^ *+' "$at_stder1" >"$at_stderr"
 else
-    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Complex); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
+    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Complex ); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
     at_status=$?
 fi
 
@@ -8650,19 +8654,20 @@ $at_traceon
 
 
 
+
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
     *) image_path="" ;;
   esac
 
-  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Continuations); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode"
+  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Continuations ); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode"
   $at_traceoff
-echo "$at_srcdir/testsuite.at:143: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Continuations); 
echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
+echo "$at_srcdir/testsuite.at:143: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Continuations ); 
echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
 echo testsuite.at:143 >"$at_check_line_file"
 
 at_trace_this=
 if test -n "$at_traceon"; then
-    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Continuations); echo exit $? > 
retcode; } | tr -d '\\r' | tee stdout; . retcode" in
+    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Continuations ); echo exit $? > 
retcode; } | tr -d '\\r' | tee stdout; . retcode" in
         *'
 '*) echo 'Not enabling shell tracing (command contains an embedded newline)' ;;
  *) at_trace_this=yes ;;
@@ -8670,12 +8675,12 @@ if test -n "$at_traceon"; then
 fi
 
 if test -n "$at_trace_this"; then
-    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Continuations); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
+    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Continuations ); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
     at_status=$?
     grep '^ *+' "$at_stder1" >&2
     grep -v '^ *+' "$at_stder1" >"$at_stderr"
 else
-    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Continuations); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
+    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Continuations ); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
     at_status=$?
 fi
 
@@ -8717,19 +8722,20 @@ $at_traceon
 
 
 
+
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
     *) image_path="" ;;
   esac
 
-  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode"
+  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools ); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode"
   $at_traceoff
-echo "$at_srcdir/testsuite.at:144: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools); echo 
exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
+echo "$at_srcdir/testsuite.at:144: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools ); 
echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
 echo testsuite.at:144 >"$at_check_line_file"
 
 at_trace_this=
 if test -n "$at_traceon"; then
-    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools); echo exit $? > 
retcode; } | tr -d '\\r' | tee stdout; . retcode" in
+    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools ); echo exit $? > 
retcode; } | tr -d '\\r' | tee stdout; . retcode" in
         *'
 '*) echo 'Not enabling shell tracing (command contains an embedded newline)' ;;
  *) at_trace_this=yes ;;
@@ -8737,12 +8743,12 @@ if test -n "$at_traceon"; then
 fi
 
 if test -n "$at_trace_this"; then
-    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
+    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools ); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
     at_status=$?
     grep '^ *+' "$at_stder1" >&2
     grep -v '^ *+' "$at_stder1" >"$at_stderr"
 else
-    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
+    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools ); echo exit $? > 
retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
     at_status=$?
 fi
 
@@ -8784,19 +8790,20 @@ $at_traceon
 
 
 
+
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
     *) image_path="" ;;
   esac
 
-  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods); echo exit $? 
> retcode; } | tr -d '\r' | tee stdout; . retcode"
+  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods ); echo exit 
$? > retcode; } | tr -d '\r' | tee stdout; . retcode"
   $at_traceoff
-echo "$at_srcdir/testsuite.at:145: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p 
DhbNumericalMethods); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . 
retcode"
+echo "$at_srcdir/testsuite.at:145: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p 
DhbNumericalMethods ); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . 
retcode"
 echo testsuite.at:145 >"$at_check_line_file"
 
 at_trace_this=
 if test -n "$at_traceon"; then
-    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods); echo exit $? 
> retcode; } | tr -d '\\r' | tee stdout; . retcode" in
+    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods ); echo exit 
$? > retcode; } | tr -d '\\r' | tee stdout; . retcode" in
         *'
 '*) echo 'Not enabling shell tracing (command contains an embedded newline)' ;;
  *) at_trace_this=yes ;;
@@ -8804,12 +8811,12 @@ if test -n "$at_traceon"; then
 fi
 
 if test -n "$at_trace_this"; then
-    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods); echo exit $? 
> retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
+    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods ); echo exit 
$? > retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 
2>"$at_stder1"
     at_status=$?
     grep '^ *+' "$at_stder1" >&2
     grep -v '^ *+' "$at_stder1" >"$at_stderr"
 else
-    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods); echo exit $? 
> retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
+    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods ); echo exit 
$? > retcode; } | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 
2>"$at_stderr"
     at_status=$?
 fi
 
@@ -8851,19 +8858,20 @@ $at_traceon
 
 
 
+
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
     *) image_path="" ;;
   esac
 
-  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Digest); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode"
+  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Digest ); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode"
   $at_traceoff
-echo "$at_srcdir/testsuite.at:146: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Digest); echo 
exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
+echo "$at_srcdir/testsuite.at:146: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Digest ); echo 
exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
 echo testsuite.at:146 >"$at_check_line_file"
 
 at_trace_this=
 if test -n "$at_traceon"; then
-    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Digest); echo exit $? > retcode; } 
| tr -d '\\r' | tee stdout; . retcode" in
+    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Digest ); echo exit $? > retcode; 
} | tr -d '\\r' | tee stdout; . retcode" in
         *'
 '*) echo 'Not enabling shell tracing (command contains an embedded newline)' ;;
  *) at_trace_this=yes ;;
@@ -8871,12 +8879,12 @@ if test -n "$at_traceon"; then
 fi
 
 if test -n "$at_trace_this"; then
-    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Digest); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
+    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Digest ); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
     at_status=$?
     grep '^ *+' "$at_stder1" >&2
     grep -v '^ *+' "$at_stder1" >"$at_stderr"
 else
-    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Digest); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
+    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p Digest ); echo exit $? > retcode; 
} | tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
     at_status=$?
 fi
 
@@ -8918,6 +8926,7 @@ $at_traceon
 
 
 
+
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
     *) image_path="" ;;
@@ -9001,6 +9010,7 @@ $at_traceon
 
 
 
+
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
     *) image_path="" ;;
@@ -9071,10 +9081,10 @@ $at_traceon
     at_status=`cat "$at_status_file"`
     ;;
 
-  115 ) # 115. testsuite.at:149: ZLib
+  115 ) # 115. testsuite.at:149: MySQL
     at_setup_line='testsuite.at:149'
-    at_desc="ZLib"
-    $at_quiet $ECHO_N "115: ZLib                                           
$ECHO_C"
+    at_desc="MySQL"
+    $at_quiet $ECHO_N "115: MySQL                                          
$ECHO_C"
     at_xfail=no
     echo "#                             -*- compilation -*-" >> "$at_group_log"
     (
@@ -9083,6 +9093,115 @@ $at_traceon
 
 
 
+  $at_traceoff
+echo "$at_srcdir/testsuite.at:149: test \"\$enable_mysql_tests\" = yes || exit 
77"
+echo testsuite.at:149 >"$at_check_line_file"
+
+at_trace_this=
+if test -n "$at_traceon"; then
+    case "test \"$enable_mysql_tests\" = yes || exit 77" in
+        *'
+'*) echo 'Not enabling shell tracing (command contains an embedded newline)' ;;
+ *) at_trace_this=yes ;;
+    esac
+fi
+
+if test -n "$at_trace_this"; then
+    ( $at_traceon; test "$enable_mysql_tests" = yes || exit 77 ) >"$at_stdout" 
2>"$at_stder1"
+    at_status=$?
+    grep '^ *+' "$at_stder1" >&2
+    grep -v '^ *+' "$at_stder1" >"$at_stderr"
+else
+    ( :; test "$enable_mysql_tests" = yes || exit 77 ) >"$at_stdout" 
2>"$at_stderr"
+    at_status=$?
+fi
+
+at_failed=false
+$at_diff "$at_devnull" "$at_stderr" || at_failed=:
+$at_diff "$at_devnull" "$at_stdout" || at_failed=:
+case $at_status in
+   77) echo 77 > "$at_status_file"; exit 77;;
+   0) ;;
+   *) echo "$at_srcdir/testsuite.at:149: exit code was $at_status, expected 0"
+      at_failed=:;;
+esac
+if $at_failed; then
+
+
+  echo 1 > "$at_status_file"
+  exit 1
+fi
+
+$at_traceon
+
+
+  case $AUTOTEST_PATH in
+    tests) image_path="-I $abs_top_builddir/gst.im" ;;
+    *) image_path="" ;;
+  esac
+
+  echo "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p MySQL ); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode"
+  $at_traceoff
+echo "$at_srcdir/testsuite.at:149: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p MySQL ); echo 
exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
+echo testsuite.at:149 >"$at_check_line_file"
+
+at_trace_this=
+if test -n "$at_traceon"; then
+    case "{ (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p MySQL ); echo exit $? > retcode; } 
| tr -d '\\r' | tee stdout; . retcode" in
+        *'
+'*) echo 'Not enabling shell tracing (command contains an embedded newline)' ;;
+ *) at_trace_this=yes ;;
+    esac
+fi
+
+if test -n "$at_trace_this"; then
+    ( $at_traceon; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p MySQL ); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stder1"
+    at_status=$?
+    grep '^ *+' "$at_stder1" >&2
+    grep -v '^ *+' "$at_stder1" >"$at_stderr"
+else
+    ( :; { (cd $abs_top_builddir && gst $image_path -f 
$abs_top_srcdir/scripts/Test.st --verbose -p MySQL ); echo exit $? > retcode; } 
| tr -d '\r' | tee stdout; . retcode ) >"$at_stdout" 2>"$at_stderr"
+    at_status=$?
+fi
+
+at_failed=false
+$at_diff "$at_devnull" "$at_stderr" || at_failed=:
+echo stdout:; cat "$at_stdout"
+case $at_status in
+   77) echo 77 > "$at_status_file"; exit 77;;
+   0) ;;
+   *) echo "$at_srcdir/testsuite.at:149: exit code was $at_status, expected 0"
+      at_failed=:;;
+esac
+if $at_failed; then
+
+
+  echo 1 > "$at_status_file"
+  exit 1
+fi
+
+$at_traceon
+
+
+        $at_traceoff
+      $at_times_p && times >"$at_times_file"
+    ) 5>&1 2>&1 | eval $at_tee_pipe
+    at_status=`cat "$at_status_file"`
+    ;;
+
+  116 ) # 116. testsuite.at:150: ZLib
+    at_setup_line='testsuite.at:150'
+    at_desc="ZLib"
+    $at_quiet $ECHO_N "116: ZLib                                           
$ECHO_C"
+    at_xfail=no
+    echo "#                             -*- compilation -*-" >> "$at_group_log"
+    (
+      echo "116. testsuite.at:150: testing ..."
+      $at_traceon
+
+
+
+
 
   case $AUTOTEST_PATH in
     tests) image_path="-I $abs_top_builddir/gst.im" ;;
@@ -9096,13 +9215,13 @@ $at_traceon
       0|1) exit $ret ;;
     esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . retcode"
   $at_traceoff
-echo "$at_srcdir/testsuite.at:149: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p ZLib
+echo "$at_srcdir/testsuite.at:150: { (cd \$abs_top_builddir && gst 
\$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p ZLib
     ret=\$?
     case \$ret in
       2) exit 77 ;;
       0|1) exit \$ret ;;
     esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . retcode"
-echo testsuite.at:149 >"$at_check_line_file"
+echo testsuite.at:150 >"$at_check_line_file"
 
 at_trace_this=
 if test -n "$at_traceon"; then
@@ -9135,7 +9254,7 @@ echo stdout:; cat "$at_stdout"
 case $at_status in
    77) echo 77 > "$at_status_file"; exit 77;;
    0) ;;
-   *) echo "$at_srcdir/testsuite.at:149: exit code was $at_status, expected 0"
+   *) echo "$at_srcdir/testsuite.at:150: exit code was $at_status, expected 0"
       at_failed=:;;
 esac
 if $at_failed; then


--- orig/tests/testsuite.at
+++ mod/tests/testsuite.at
@@ -146,4 +146,5 @@ AT_PACKAGE_TEST([DhbNumericalMethods])
 AT_PACKAGE_TEST([Digest])
 AT_OPTIONAL_PACKAGE_TEST([GDBM])
 AT_OPTIONAL_PACKAGE_TEST([Iconv])
+AT_PACKAGE_TEST([MySQL], [], [], [test "$enable_mysql_tests" = yes])
 AT_OPTIONAL_PACKAGE_TEST([ZLib])




reply via email to

[Prev in Thread] Current Thread [Next in Thread]