[Haskell] Re: ANN: HDBC (Haskell Database Connectivity)

Keean Schupke k.schupke at imperial.ac.uk
Sun Jan 8 09:51:12 EST 2006


My solution to this when developing a database library for my own use 
was to define the API
in a bracket notation style, and only provide safe functions. The idea 
is that the function obtains the resource, calls a function passed as an 
argument, then frees the resource, so all resouces are guaranteed to be 
freed in the correct order... for example:

dbConnectWith ::  DbName -> (DbHandle -> IO Result) -> Result
dbConnectWith name workFn = do
    handle <- dbConnectTo name
    workFn handle `finally` dbDisconnect handle

In this way you avoid finalizers... and everthing is safe providing you 
only export the "with" style functions from the library... Here's an 
example from the library, the connect function:


safeConnect :: (SqlIO m,SqlIfIO m,MonadIO m,MonadPlus m) => SqlDbc -> 
OdbcConnection -> (SqlDbc -> m a) -> m a
safeConnect dbc connection doWith = ioBracket (
                ioBracket (ioNewCStringLen (odbcDsn connection)) 
(\(dsnS,_) -> ioFree dsnS) (\(dsnS,dsnL) ->
                ioBracket (ioNewCStringLen (odbcUid connection)) 
(\(uidS,_) -> ioFree uidS) (\(uidS,uidL) ->
                ioBracket (ioNewCStringLen (odbcAuth connection)) 
(\(authS,_) -> ioFree authS) (\(authS,authL) -> do
                        status <- ioSqlConnect dbc dsnS (fromIntegral 
dsnL) uidS (fromIntegral uidL) authS (fromIntegral authL)
                        ioIfFail status (\s -> fail ((showString " Bad 
status returned by sqlConnect (" . shows s) ")"))))))
                (\_ -> ioSqlDisconnect dbc) (\_ -> doWith dbc)


    Keean


Chris Kuklewicz wrote:

>Benjamin Franksen wrote:
>  
>
>>On Wednesday 04 January 2006 20:13, John Goerzen wrote:
>>
>>    
>>
>>>Well, yes and no.  It would be impossible to garbage collect (and
>>>thus finalize) any object for which references to it still exist. 
>>>Statement handles in HDBC maintain references to the database handle
>>>pointers, either directly or indirectly, so I can't see how it is
>>>possible for a database handle to be finalized before the statement
>>>handle in this situation.
>>>      
>>>
>>Hi John,
>>
>>I fear it /is/ possible. This is a very unfortunate situation and one I 
>>had quite some difficulties to understand, when Simon Marlow explained 
>>it to me.
>>
>>The problem is that finalization of the statement handle might be 
>>delayed indefinitely. The data dependencies between statement and 
>>connection handle only ensures that whenever the statement handle is 
>>alive, then too is the connection handle. But it does not say anything 
>>about what happens in which order after /both/ are dead (garbage). As 
>>soon as the connection handle to garbage, too, bothe handles can be 
>>finalized in /any/ order.
>>
>>As I pointed out before, this is a very bad thing, because it makes 
>>finalizers a whole lot less useful than they could be if an order 
>>between finalizations could be specified (directly or indirectly). The 
>>arguments against such a solution are mostly: (1) it is difficult to 
>>implement efficienty and (2) the programmer could accidentally cause 
>>finalizer deadlocks by specifying circular dependencies.
>>
>>Ben
>>    
>>
>
>This is also mentioned in the documentation:
>
>http://www.haskell.org/ghc/docs/6.4.1/html/libraries/base/Foreign-ForeignPtr.html#v%3AtouchForeignPtr
>
>  
>
>>touchForeignPtr :: ForeignPtr a -> IO ()
>>
>>This function ensures that the foreign object in question is alive at the given place in the sequence of IO actions. In particular withForeignPtr does a touchForeignPtr after it executes the user action.
>>
>>Note that this function should not be used to express liveness dependencies between ForeignPtrs. For example, if the finalizer for a ForeignPtr F1 calls touchForeignPtr on a second ForeignPtr F2, then the only guarantee is that the finalizer for F2 is never started before the finalizer for F1. They might be started together if for example both F1 and F2 are otherwise unreachable, and in that case the scheduler might end up running the finalizer for F2 first.
>>
>>In general, it is not recommended to use finalizers on separate objects with ordering constraints between them. To express the ordering robustly requires explicit synchronisation using MVars between the finalizers, but even then the runtime sometimes runs multiple finalizers sequentially in a single thread (for performance reasons), so synchronisation between finalizers could result in artificial deadlock. 
>>    
>>
>
>
>_______________________________________________
>Haskell mailing list
>Haskell at haskell.org
>http://www.haskell.org/mailman/listinfo/haskell
>  
>



More information about the Haskell mailing list