[Haskell-cafe] Freeing dependent resources

Alexey Uimanov s9gf4ult at gmail.com
Wed Aug 14 07:17:26 CEST 2013


Hello, Haskellers.

I am working on HDBI and I faced with the problem.

There is an error when I close SQlite database, "unable to close due to
unfinalized statements or unfinished backups".
This problems occurs when there is some not finalized statements related to
this database.

So, I must protect the user from this error and garantee the finalisation
of all the statements BEFORE the disconnection from
the database.

There is naive implementation of weak child list inherited from HDBC

https://github.com/s9gf4ult/hdbi/blob/master/Database/HDBI/DriverUtils.hs

Here you can see that ChildList is just MVar to list of weak pointers.
Every time when the statement is created the new weak pointer prepended to
this list.
Every time when statement becomes not reachable the weak pointer becomes
empty and it's finalizer is scheduled to execute in parralel thread.
The finalizer finishes the statement, so if finalizer is executed the
statement is finished.
Before the actual call of disconnection the 'disconnect' method performs
'closeAllChildren'.
Call of 'closeAllChildren' performs finishing of just not empty weak
pointers, because the finishing of not reachable statements is imposible.

You can see the implementation here

https://github.com/s9gf4ult/hdbi-sqlite/blob/master/Database/HDBI/SQlite/Implementation.hs#L80
https://github.com/s9gf4ult/hdbi-sqlite/blob/master/Database/HDBI/SQlite/Implementation.hs#L117

and here is the simplest code which cause an error

{-# LANGUAGE
  OverloadedStrings
  #-}

module Main where

import System.Mem
import Database.HDBI.SQlite
import Database.HDBI

perf c = do
  runRaw c "create table integers (val)"
  s <- prepare c "select * from integers"
  return ()

main = do
  c <- connectSqlite3 ":memory:"
  perf c
  performGC
  disconnect c

If you remove 'performGC' error not occurs, because the weak pointer in
ChildList is still not empty and
'finish' is performed in 'closeAllChildren'.

The problem occures when the statement becomes not reachable and weak
pointer becomes empty,
but finalizer is not performed yet, because the finalizer performed in
parralel thread according to
https://www.google.ru/url?sa=t&rct=j&q=&esrc=s&source=web&cd=1&cad=rja&ved=0CC8QFjAA&url=http%3A%2F%2Fcommunity.haskell.org%2F~simonmar%2Fpapers%2Fweak.pdf&ei=vRALUvrELaaS4ASH_oCQCw&usg=AFQjCNEWQtRfh5ei7J_Qd-VDVMq0ied0KQ&sig2=nsvzz4FXB_4dWp75CU6gzg

The naive solution is to make 'closeAllChildren' to wait until all
finalizers is completely performed. But how ?
Maybe you have the better solution to garantee that all statements are
finished before the database disconnecting ?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130814/3571cbf4/attachment.htm>


More information about the Haskell-Cafe mailing list