Login

Making a Connection Pool for Glorp in Seaside

First let me say.... Glorp rocks! Kudos to Alan Knight for this framework. I'm really liking it, having written two home brew O/R frameworks in the past (mostly to learn how, and in less capable languages than Smalltalk), I can appreciate the flexibility of its design. This is going on my list of programs to read thoroughly from time to time. It's a very well written and very nice example of a well written OO system that anyone could learn a lot from. I'd add both Seaside and Magritte to that list as well. Reading great code is a lost art too few programmers do these days.

Glorp really gives me that object oriented feel and allows me to at least pretend I'm working with an object database, while keeping all the benefits of a relational database like constraints, indexing, and random queries. It's far more capable than I thought it'd be and totally pluggable if you need to add any capabilities. It'll do things Rails couldn't dream of as far as mapping and querying goes, and it does it in native Smalltalk syntax.

OK, enough of the Glorp envy. I've been working to get Glorp, Seaside, and Magritte all tied together so I can have a full stack framework to work with that allows me to work in Smalltalk at every level. I've used many languages and nothing comes close to the productivity I feel in Smalltalk, so naturally, I'm looking forward to finally using it from top to bottom, html, biz objects, and sql queries, all in Smalltalk.

While working on an implementation of a sort of ActiveRecord, but using Magritte for the meta data instead of the database, I quickly found I needed to mary one Glorp session to one Seaside session to keep everything simple and intuitive. It's a good match, however, I don't want to keep a connection to PostgreSQL, they're too valuable a resource to keep sitting idle and unused for 10 minutes while a session times out.

I played around a bit and found, at least so far, that within Glorp, the Squeak and Postgres adapters don't really maintain any state and can be swapped in and out of an existing GlorpSession. I decided that I'd write a connection pool for Glorp's SqueakDatabaseAccessor allowing me to tie a PostgreSQL connection to a request allowing much more scalability in the web scenario without risking running out of connections during peak loads. So, after a bit of playing around, I came up with a class called MGConnectionPool. I'm using the class side for all this code, taking advantage of the simple fact that in Smalltalk a class "is" a singleton ensuring there's only one instance of the pool in the image.

MGConnectionPool class>>initialize
    lock := Monitor new.
    connections := Dictionary new.

MGConnectionPool class>>poolTimeout
    ^30 seconds

MGConnectionPool class>>withUser: aUser password: aPassword 
    server: aServer database: aDatabase in: aBlock

    | connection result expired |
    "Grab a connection from the pool util you find one that
    isn't expired, logout the expired ones"
    expired := true.
    [expired]
        whileTrue: [connection := self
                        getConnectionUser: aUser
                        password: aPassword
                        server: aServer
                        database: aDatabase.
            expired := DateAndTime now - connection value > self poolTimeout.
            expired ifTrue: [connection key logout]].

    "pass the connection through the block, which will be the page
    request, and ensure it's returned to the pool when done"
    [result := aBlock value: connection key]
        ensure: [self
                returnConnection: connection
                forKey: (self
                        makeKeyUser: aUser
                        password: aPassword
                        server: aServer
                        database: aDatabase)].
    ^result

MGConnectionPool class>>getConnectionUser: aUser password: aPassword 
    server: aServer database: aDatabase 

    | key matchingConnections |
    ^ lock
        critical: [key := self
                        makeKeyUser: aUser
                        password: aPassword
                        server: aServer
                        database: aDatabase.
            matchingConnections := connections
                        at: key
                        ifAbsentPut: [OrderedCollection new].
            matchingConnections
                ifEmpty: [matchingConnections add: (self
                            newLoginForUser: aUser
                            password: aPassword
                            server: aServer
                            database: aDatabase)
                            -> DateAndTime now].
            matchingConnections removeFirst]

MGConnectionPool class>>makeKeyUser: aUser password: aPassword 
    server: aServer database: aDatabase 

    ^aUser , '~' , aPassword , '~' , aServer , '~' , aDatabase

MGConnectionPool class>>newLoginForUser: aUser password: aPassword 
    server: aServer database: aDatabase 

    ^ (SqueakDatabaseAccessor forLogin: 
        (Login new database: PostgreSQLPlatform new;
             username: aUser;
             password: aPassword;
             connectString: aServer , '_' , aDatabase)) 
         login; 
         yourself

MGConnectionPool class>>returnConnection: aConnection forKey: aKey 
    lock
        critical: [aConnection value: DateAndTime now.
            (connections at: aKey)
                add: aConnection]

This allows me to create a subclass of a Seaside session and glue Glorp and Seaside together like this.

MGGlorpSession>>commit: aBlock 
    ^database inUnitOfWorkDo: aBlock

MGGlorpSession>>execute: aQuery
    ^database execute: aQuery

MGGlorpSession>>register: anObject
    ^database register: anObject

MGGlorpSession>>ensureGlorpSessionOn: aDbAccessor 
    database
        ifNil: [database := GlorpSession new
                         system: (SBGlorpDescriptions 
                            forPlatform: aDbAccessor 
                                currentLogin database);
                         accessor: aDbAccessor;
                         yourself]

MGGlorpSession>>responseForRequest: aRequest 
    ^ MGConnectionPool
        withUser: (self application preferenceAt: #glorpUserName)
        password: (self application preferenceAt: #glorpPassword)
        server: (self application preferenceAt: #glorpServer)
        database: (self application preferenceAt: #glorpDatabase)
        in: [:dbAccessor | 
            self ensureGlorpSessionOn: dbAccessor.
            database accessor: dbAccessor.
            super responseForRequest: aRequest]

Reading in the authentication from the current application config. Now I can feel safe using Glorp from Seaside, and from within any Seaside component, run Glorp queries with ease in a scalable manner. The code is totally generic and can reused for every future application by simply subclassing. Programming is getting more fun by the day; it's going to be a good year for Seaside. All the necessary frameworks exist to build a truly awesome and "fully" object oriented web stack that doesn't drag you down into the request response cycle inherent to other frameworks, even Rails. Glorp + PostgreSQL + Seaside + Magritte + Scriptaculous + Albatross + a little glue == Slick totally object oriented full stack Ajax web framework of the future, today!

Comments (automatically disabled after 1 year)

cédrick] 6315 days ago

Thank you a lot Ramon for these excellent posts, I really enjoy reading them ! Glorp seems cool too , I'll definitively have a look at it soon !!!

Just a question, is Glorp only on squeakmap ?

See you

Cédrick]

Ramon Leon 6315 days ago

No problem, I'm not posting as often these days, but I'm trying to do quality posts on topics relevant to me, and hopefully to everyone else. As for Glorp, yea, as far as I know, I haven't seen it anywhere else.

Ronaldo 6315 days ago

One thing that always strikes me about Smalltalk code is how beautiful it is. Going back to .NET or something else is always hard to do after coding on it for a while. GLORP is really nice.

"It'll do things Rails couldn't dream of as far as mapping and querying goes, and it does it in native Smalltalk syntax."

That, however, is misleading and unqualified. It would be interesting to see at least one example of it, especially considering that Rails uses Ruby syntax in the same way Glorp uses Smalltalk syntax.

Ramon Leon 6315 days ago

Ronaldo, It may be unqualified, but it is a fact. Rails only works well when the database follows its assumptions, that's well known, but Glorp will map to anything. Glorp is a "full blown" OR Mapper, Rails is a "lite" OR mapper. Glorp is far more capable, but a bit heavier on configuration.

Nor does Rails use native Ruby syntax (I should have said "style") for its queries.

matches = 
    SomeClass.find(:all, 
        :limit => 15, 
        :conditions => "timestamp < now()", 
        : order => "timestamp desc")
That's not native, that's passing pieces of sql in strings as associations, not at all how you'd query a collection in memory using the each method and a block. Glorp actually uses native Smalltalk syntax, i.e. blocks, not sql in strings. In Glorp, I could write like this...
matches := session execute: 
    (SomeClass findAll 
        limit: 15;
        where:[:each | each timestamp < TimeStamp now];
        orderBy: [:each | each timestamp descending])

And in Glorp, queries are actually composable objects, so I can compose complicated queries, unions, joins, sub-queries, all in Smalltalk without dropping into sql, Rails makes you drop into sql.

Paul 6315 days ago

Cédrick,

>Just a question, is Glorp only on squeakmap ?

Alan Knight develops Glorp on Cincom VisualWorks and it will eventually (soon) become Cincom's official persistence framework. So if you install a current version of VisualWorks (for download of non commercial version see www.cincomsmalltalk.com) you will also get Glorp along with it. Additionally, the most up-to-date code for VisualWorks can be found on the Cincom Public Store Repository (for setting up access see also www.cincomsmalltalk.com).

Hope this helps, Paul]

Martin J. Laubach 6315 days ago

Doesn't that break object identity in Glorp? AFAIK, Glorp database objects are identical when they refer to the same underlying database object -- however, this identity is tied to the Glorp session.

So I think it's going to confuse Glorp a lot if you read object X from session A, modify it and write it on session B.

Also, you'll lose identity, the same object will be instanciated several times from different sessions, so what happens when you change instance 1 of object X but later on use instance 2?

Regards, mjl

Ramon Leon 6315 days ago

Look closer, I'm not pooling Glorp sessions, I'm pooling the database accessor on the Glorp session. Each Seaside session maintains one single Glorp session throughout its lifetime, but as far as I can tell, I can change the accessor for that session with no ill effect, it's just an adapter that contains a connection (which we want to pool) and translates to a specific sql dialect.

Ronaldo 6314 days ago

Nice example. I'd argue that using small pieces of SQL is not a deviation from the basic style of the language, but I see your point. The fact that Ruby doesn't accept more than one block as a parameter to a method without resorting to an unusual parameter passing strategy is a bummer. It's would certainly be possible to replicate the above syntax in Ruby, but not without using an extra keyword.

matches =
    SomeClass.find :all,
        :limit => 15,
        :conditions => proc { |each| each.timestamp  proc { |each| each.timestamp.descending }

Of course, Rails doesn't support that as of today (as far as I know), but It would be possible. In fact, part of the Rails validation protocol uses something similar for validation.

Ronaldo 6314 days ago

The code above is slightly incorrect (possibly due to a "less than" sign). It would be like this:

matches = SomeClass.find :all, :limit => 15, :conditions => proc { |each| each.timestamp != DateTime.now }, :order => proc { |each| each.timestamp.descending }

Ramon Leon 6314 days ago

Of course, I'm not concerned with what "could" be done in Rails, only what "is" done in Rails, and that's passing strings. Glorp does it better, that was my point.

Martin J. Laubach 6313 days ago

Oh, I see, indeed you are pooling the backend database connections. I still see a problem with this approach should one ever hold a transaction open - but in conjunction with Seaside, this is a bad thing to do anyway.

Thanks for the idea, I'll have a go at retrofitting some older applications of mine to see how that pooling interferes with unusual user interactions.

Also. it would be cool if you could join us on the glorp mailing list, I'm sure Alan would be more than interested in hearing from your experiences.

Regards, mjl

Ramon Leon 6313 days ago

One would never, in a web context, hold a transaction open between requests, so you're correct, this isn't an issue.

I've already been lurking on the Glorp mailing list for a while, even posted once or twice, and I'll post more about my experiences as I find time. Right now, I'm busy working on my own ActiveRecord derived from Magritte meta data. If I run into any serious problems, you can bet I'll post questions to the list.

Rick F. 6232 days ago

Ramon --

I'll have to give this a shot on VW and see what I might run into on that platform.. Obviously I've got a different Glorp backend to deal with (no SequakDatabaseAccessor -- it's a VWDatabaseAccessor IIRC) which I know has a different "look" to it.. I had a connection pool I got from someone else that was written for Squeak and gave up on getting it to work w/ Glorp on VW -- too much down in the bowels of Glorp and my infamiliarity with those bowels.. (8-

Ramon Leon 6232 days ago

I'm guessing mine will work fine with any version of Glorp, I'm not doing anything overly fancy, just swapping out the current database accessor on a Glorp session.

MK 6027 days ago

Perhaps you could use pgpool or sqlrelay for pooling, although I like your within-Smalltalk approach better.

Ramon Leon 6027 days ago

The within Smalltalk approach is necessary so that Glorp is always served up the same connection, otherwise transactions won't work.

about me|good books|popular posts|atom|rss