2015-02-16 19:08:29 +00:00
|
|
|
{- Persistent sqlite database handles.
|
|
|
|
-
|
|
|
|
- Copyright 2015 Joey Hess <id@joeyh.name>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
{-# LANGUAGE BangPatterns #-}
|
|
|
|
|
2015-02-16 19:08:29 +00:00
|
|
|
module Database.Handle (
|
|
|
|
DbHandle,
|
2015-02-18 19:54:24 +00:00
|
|
|
initDb,
|
2015-02-16 19:08:29 +00:00
|
|
|
openDb,
|
2015-02-18 18:11:27 +00:00
|
|
|
queryDb,
|
2015-02-16 20:04:23 +00:00
|
|
|
closeDb,
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
Size,
|
|
|
|
queueDb,
|
|
|
|
flushQueueDb,
|
2015-02-18 18:11:27 +00:00
|
|
|
commitDb,
|
2015-02-16 19:08:29 +00:00
|
|
|
) where
|
|
|
|
|
|
|
|
import Utility.Exception
|
2015-02-17 17:03:57 +00:00
|
|
|
import Messages
|
2015-02-16 19:08:29 +00:00
|
|
|
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
import Database.Persist.Sqlite
|
2015-02-18 19:54:24 +00:00
|
|
|
import qualified Database.Sqlite as Sqlite
|
2015-02-16 20:48:19 +00:00
|
|
|
import Control.Monad
|
2015-02-16 19:08:29 +00:00
|
|
|
import Control.Monad.IO.Class (liftIO)
|
|
|
|
import Control.Concurrent
|
|
|
|
import Control.Concurrent.Async
|
|
|
|
import Control.Exception (throwIO)
|
|
|
|
import qualified Data.Text as T
|
2015-02-22 18:08:26 +00:00
|
|
|
import Control.Monad.Trans.Resource (runResourceT)
|
|
|
|
import Control.Monad.Logger (runNoLoggingT)
|
|
|
|
import Data.List
|
2015-02-16 19:08:29 +00:00
|
|
|
|
|
|
|
{- A DbHandle is a reference to a worker thread that communicates with
|
|
|
|
- the database. It has a MVar which Jobs are submitted to. -}
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
data DbHandle = DbHandle (Async ()) (MVar Job) (MVar DbQueue)
|
2015-02-16 19:08:29 +00:00
|
|
|
|
2015-02-18 19:54:24 +00:00
|
|
|
{- Ensures that the database is initialized. Pass the migration action for
|
|
|
|
- the database.
|
|
|
|
-
|
|
|
|
- The database is put into WAL mode, to prevent readers from blocking
|
|
|
|
- writers, and prevent a writer from blocking readers.
|
|
|
|
-}
|
2015-02-22 18:08:26 +00:00
|
|
|
initDb :: FilePath -> SqlPersistM () -> IO ()
|
|
|
|
initDb f migration = do
|
|
|
|
let db = T.pack f
|
2015-02-18 19:54:24 +00:00
|
|
|
enableWAL db
|
2015-02-22 18:08:26 +00:00
|
|
|
runSqlite db migration
|
|
|
|
|
|
|
|
enableWAL :: T.Text -> IO ()
|
2015-02-18 19:54:24 +00:00
|
|
|
enableWAL db = do
|
2015-02-22 18:08:26 +00:00
|
|
|
conn <- Sqlite.open db
|
2015-02-18 19:54:24 +00:00
|
|
|
stmt <- Sqlite.prepare conn (T.pack "PRAGMA journal_mode=WAL;")
|
|
|
|
void $ Sqlite.step stmt
|
|
|
|
void $ Sqlite.finalize stmt
|
|
|
|
Sqlite.close conn
|
|
|
|
|
|
|
|
{- Opens the database, but does not perform any migrations. Only use
|
|
|
|
- if the database is known to exist and have the right tables. -}
|
2015-02-22 18:08:26 +00:00
|
|
|
openDb :: FilePath -> TableName -> IO DbHandle
|
|
|
|
openDb db tablename = do
|
2015-02-16 19:08:29 +00:00
|
|
|
jobs <- newEmptyMVar
|
2015-02-22 18:08:26 +00:00
|
|
|
worker <- async (workerThread (T.pack db) tablename jobs)
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
q <- newMVar emptyDbQueue
|
|
|
|
return $ DbHandle worker jobs q
|
2015-02-16 19:08:29 +00:00
|
|
|
|
2015-02-18 18:11:27 +00:00
|
|
|
data Job
|
|
|
|
= QueryJob (SqlPersistM ())
|
|
|
|
| ChangeJob ((SqlPersistM () -> IO ()) -> IO ())
|
|
|
|
| CloseJob
|
|
|
|
|
2015-02-22 18:08:26 +00:00
|
|
|
type TableName = String
|
|
|
|
|
|
|
|
workerThread :: T.Text -> TableName -> MVar Job -> IO ()
|
2015-02-22 18:21:39 +00:00
|
|
|
workerThread db tablename jobs = catchNonAsync (run loop) showerr
|
2015-02-16 19:08:29 +00:00
|
|
|
where
|
2015-02-18 18:11:27 +00:00
|
|
|
showerr e = liftIO $ warningIO $
|
|
|
|
"sqlite worker thread crashed: " ++ show e
|
2015-02-22 18:08:26 +00:00
|
|
|
|
2015-02-18 18:11:27 +00:00
|
|
|
loop = do
|
2015-02-22 18:21:39 +00:00
|
|
|
job <- liftIO $ takeMVar jobs
|
|
|
|
case job of
|
|
|
|
QueryJob a -> a >> loop
|
2015-02-18 18:11:27 +00:00
|
|
|
-- change is run in a separate database connection
|
|
|
|
-- since sqlite only supports a single writer at a
|
|
|
|
-- time, and it may crash the database connection
|
2015-02-22 18:21:39 +00:00
|
|
|
ChangeJob a -> liftIO (a run) >> loop
|
2015-02-16 20:04:23 +00:00
|
|
|
CloseJob -> return ()
|
2015-02-22 18:08:26 +00:00
|
|
|
|
|
|
|
-- like runSqlite, but calls settle on the raw sql Connection.
|
|
|
|
run a = do
|
|
|
|
conn <- Sqlite.open db
|
|
|
|
settle conn
|
|
|
|
runResourceT $ runNoLoggingT $
|
|
|
|
withSqlConn (wrapConnection conn) $
|
|
|
|
runSqlConn a
|
|
|
|
|
|
|
|
-- Work around a bug in sqlite: New database connections can
|
|
|
|
-- sometimes take a while to become usable; select statements will
|
|
|
|
-- fail with ErrorBusy for some time. So, loop until a select
|
|
|
|
-- succeeds; once one succeeds the connection will stay usable.
|
|
|
|
-- <http://thread.gmane.org/gmane.comp.db.sqlite.general/93116>
|
|
|
|
settle conn = do
|
|
|
|
r <- tryNonAsync $ do
|
|
|
|
stmt <- Sqlite.prepare conn nullselect
|
|
|
|
void $ Sqlite.step stmt
|
|
|
|
void $ Sqlite.finalize stmt
|
|
|
|
case r of
|
|
|
|
Right _ -> return ()
|
|
|
|
Left e -> do
|
|
|
|
if "ErrorBusy" `isInfixOf` show e
|
|
|
|
then do
|
|
|
|
threadDelay 1000 -- 1/1000th second
|
|
|
|
settle conn
|
|
|
|
else throwIO e
|
|
|
|
|
|
|
|
-- This should succeed for any table.
|
|
|
|
nullselect = T.pack $ "SELECT null from " ++ tablename ++ " limit 1"
|
2015-02-16 19:08:29 +00:00
|
|
|
|
2015-02-18 18:11:27 +00:00
|
|
|
{- Makes a query using the DbHandle. This should not be used to make
|
|
|
|
- changes to the database!
|
2015-02-16 19:08:29 +00:00
|
|
|
-
|
|
|
|
- Note that the action is not run by the calling thread, but by a
|
|
|
|
- worker thread. Exceptions are propigated to the calling thread.
|
|
|
|
-
|
2015-02-16 20:48:19 +00:00
|
|
|
- Only one action can be run at a time against a given DbHandle.
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
- If called concurrently in the same process, this will block until
|
|
|
|
- it is able to run.
|
2015-02-16 19:08:29 +00:00
|
|
|
-}
|
2015-02-22 18:08:26 +00:00
|
|
|
queryDb :: DbHandle -> SqlPersistM a -> IO a
|
|
|
|
queryDb (DbHandle _ jobs _) a = do
|
|
|
|
res <- newEmptyMVar
|
|
|
|
putMVar jobs $ QueryJob $
|
|
|
|
liftIO . putMVar res =<< tryNonAsync a
|
|
|
|
either throwIO return =<< takeMVar res
|
2015-02-16 20:04:23 +00:00
|
|
|
|
|
|
|
closeDb :: DbHandle -> IO ()
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
closeDb h@(DbHandle worker jobs _) = do
|
|
|
|
flushQueueDb h
|
2015-02-16 20:04:23 +00:00
|
|
|
putMVar jobs CloseJob
|
|
|
|
wait worker
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
|
|
|
|
type Size = Int
|
|
|
|
|
|
|
|
{- A queue of actions to perform, with a count of the number of actions
|
|
|
|
- queued. -}
|
|
|
|
data DbQueue = DbQueue Size (SqlPersistM ())
|
|
|
|
|
|
|
|
emptyDbQueue :: DbQueue
|
|
|
|
emptyDbQueue = DbQueue 0 (return ())
|
|
|
|
|
2015-02-18 18:11:27 +00:00
|
|
|
{- Queues a change to be made to the database. It will be buffered
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
- to be committed later, unless the queue gets larger than the specified
|
|
|
|
- size.
|
|
|
|
-
|
2015-02-18 18:11:27 +00:00
|
|
|
- (Be sure to call closeDb or flushQueueDb to ensure the change
|
|
|
|
- gets committed.)
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
-
|
|
|
|
- Transactions built up by queueDb are sent to sqlite all at once.
|
|
|
|
- If sqlite fails due to another change being made concurrently by another
|
|
|
|
- process, the transaction is put back in the queue. This solves
|
|
|
|
- the sqlite multiple writer problem.
|
|
|
|
-}
|
|
|
|
queueDb :: DbHandle -> Size -> SqlPersistM () -> IO ()
|
|
|
|
queueDb h@(DbHandle _ _ qvar) maxsz a = do
|
|
|
|
DbQueue sz qa <- takeMVar qvar
|
|
|
|
let !sz' = sz + 1
|
|
|
|
let qa' = qa >> a
|
2015-02-18 18:11:27 +00:00
|
|
|
let enqueue newsz = putMVar qvar (DbQueue newsz qa')
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
if sz' > maxsz
|
|
|
|
then do
|
2015-02-18 18:11:27 +00:00
|
|
|
r <- commitDb h qa'
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
case r of
|
2015-02-22 18:08:26 +00:00
|
|
|
Left _ -> enqueue 0
|
2015-02-18 19:54:24 +00:00
|
|
|
Right _ -> putMVar qvar emptyDbQueue
|
2015-02-18 18:11:27 +00:00
|
|
|
else enqueue sz'
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
|
|
|
|
{- If flushing the queue fails, this could be because there is another
|
|
|
|
- writer to the database. Retry repeatedly for up to 10 seconds. -}
|
|
|
|
flushQueueDb :: DbHandle -> IO ()
|
|
|
|
flushQueueDb h@(DbHandle _ _ qvar) = do
|
|
|
|
DbQueue sz qa <- takeMVar qvar
|
|
|
|
when (sz > 0) $
|
2015-02-18 18:11:27 +00:00
|
|
|
robustly Nothing 100 (commitDb h qa)
|
allow for concurrent incremental fsck processes again (sorta)
Sqlite doesn't support multiple concurrent writers
at all. One of them will fail to write. It's not even possible to have two
processes building up separate transactions at the same time. Before using
sqlite, incremental fsck could work perfectly well with multiple fsck
processes running concurrently. I'd like to keep that working.
My partial solution, so far, is to make git-annex buffer writes, and every
so often send them all to sqlite at once, in a transaction. So most of the
time, nothing is writing to the database. (And if it gets unlucky and
a write fails due to a collision with another writer, it can just wait and
retry the write later.) This lets multiple processes write to the database
successfully.
But, for the purposes of concurrent, incremental fsck, it's not ideal.
Each process doesn't immediately learn of files that another process has
checked. So they'll tend to do redundant work.
Only way I can see to improve this is to use some other mechanism for
short-term IPC between the fsck processes. Not yet done.
----
Also, make addDb check if an item is in the database already, and not try
to re-add it. That fixes an intermittent crash with
"SQLite3 returned ErrorConstraint while attempting to perform step."
I am not 100% sure why; it only started happening when I moved write
buffering into the queue. It seemed to generally happen on the same file
each time, so could just be due to multiple files having the same key.
However, I doubt my sound repo has many duplicate keys, and I suspect
something else is going on.
----
Updated benchmark, with the 1000 item queue: 6m33.808s
2015-02-17 20:39:35 +00:00
|
|
|
where
|
2015-02-18 18:11:27 +00:00
|
|
|
robustly :: Maybe SomeException -> Int -> IO (Either SomeException ()) -> IO ()
|
|
|
|
robustly e 0 _ = error $ "failed to commit changes to sqlite database: " ++ show e
|
|
|
|
robustly _ n a = do
|
|
|
|
r <- a
|
|
|
|
case r of
|
|
|
|
Right _ -> return ()
|
|
|
|
Left e -> do
|
|
|
|
threadDelay 100000 -- 1/10th second
|
|
|
|
robustly (Just e) (n-1) a
|
|
|
|
|
|
|
|
commitDb :: DbHandle -> SqlPersistM () -> IO (Either SomeException ())
|
|
|
|
commitDb (DbHandle _ jobs _) a = do
|
|
|
|
res <- newEmptyMVar
|
|
|
|
putMVar jobs $ ChangeJob $ \runner ->
|
|
|
|
liftIO $ putMVar res =<< tryNonAsync (runner a)
|
|
|
|
takeMVar res
|