2017-09-04 17:52:22 +00:00
|
|
|
{- Sqlite database used for exports to special remotes.
|
|
|
|
-
|
|
|
|
- Copyright 2017 Joey Hess <id@joeyh.name>
|
|
|
|
-:
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings, GADTs, FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE MultiParamTypeClasses, GeneralizedNewtypeDeriving #-}
|
|
|
|
{-# LANGUAGE RankNTypes #-}
|
2017-09-25 13:57:41 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
2017-09-04 17:52:22 +00:00
|
|
|
|
|
|
|
module Database.Export (
|
|
|
|
ExportHandle,
|
|
|
|
openDb,
|
|
|
|
closeDb,
|
2017-09-04 18:33:09 +00:00
|
|
|
flushDbQueue,
|
2017-09-18 17:57:25 +00:00
|
|
|
addExportedLocation,
|
|
|
|
removeExportedLocation,
|
|
|
|
getExportedLocation,
|
2017-09-15 18:33:07 +00:00
|
|
|
isExportDirectoryEmpty,
|
2017-09-18 22:40:16 +00:00
|
|
|
getExportTreeCurrent,
|
|
|
|
recordExportTreeCurrent,
|
2017-09-18 17:57:25 +00:00
|
|
|
getExportTree,
|
2017-09-18 18:24:42 +00:00
|
|
|
addExportTree,
|
|
|
|
removeExportTree,
|
2017-09-18 17:57:25 +00:00
|
|
|
updateExportTree,
|
2017-09-18 18:24:42 +00:00
|
|
|
updateExportTree',
|
2017-09-20 20:22:32 +00:00
|
|
|
updateExportTreeFromLog,
|
2017-09-04 17:52:22 +00:00
|
|
|
ExportedId,
|
2017-09-15 18:33:07 +00:00
|
|
|
ExportedDirectoryId,
|
2017-09-18 22:40:16 +00:00
|
|
|
ExportTreeId,
|
|
|
|
ExportTreeCurrentId,
|
2017-09-04 17:52:22 +00:00
|
|
|
) where
|
|
|
|
|
|
|
|
import Database.Types
|
|
|
|
import qualified Database.Queue as H
|
|
|
|
import Database.Init
|
|
|
|
import Annex.Locations
|
|
|
|
import Annex.Common hiding (delete)
|
2017-09-15 20:34:45 +00:00
|
|
|
import Types.Export
|
2017-09-18 17:57:25 +00:00
|
|
|
import Annex.Export
|
2017-09-20 20:22:32 +00:00
|
|
|
import qualified Logs.Export as Log
|
|
|
|
import Annex.LockFile
|
2017-09-18 17:57:25 +00:00
|
|
|
import Git.Types
|
|
|
|
import Git.Sha
|
|
|
|
import Git.FilePath
|
|
|
|
import qualified Git.DiffTree
|
2017-09-04 17:52:22 +00:00
|
|
|
|
|
|
|
import Database.Persist.TH
|
|
|
|
import Database.Esqueleto hiding (Key)
|
|
|
|
|
2017-09-20 20:22:32 +00:00
|
|
|
data ExportHandle = ExportHandle H.DbQueue UUID
|
2017-09-04 17:52:22 +00:00
|
|
|
|
|
|
|
share [mkPersist sqlSettings, mkMigrate "migrateExport"] [persistLowerCase|
|
2017-09-18 22:40:16 +00:00
|
|
|
-- Files that have been exported to the remote and are present on it.
|
2017-09-04 17:52:22 +00:00
|
|
|
Exported
|
|
|
|
key IKey
|
|
|
|
file SFilePath
|
2017-09-18 17:57:25 +00:00
|
|
|
ExportedIndex key file
|
|
|
|
-- Directories that exist on the remote, and the files that are in them.
|
2017-09-15 18:33:07 +00:00
|
|
|
ExportedDirectory
|
|
|
|
subdir SFilePath
|
|
|
|
file SFilePath
|
2017-09-18 17:57:25 +00:00
|
|
|
ExportedDirectoryIndex subdir file
|
2017-09-18 22:40:16 +00:00
|
|
|
-- The content of the tree that has been exported to the remote.
|
|
|
|
-- Not all of these files are necessarily present on the remote yet.
|
|
|
|
ExportTree
|
|
|
|
key IKey
|
|
|
|
file SFilePath
|
|
|
|
ExportTreeIndex key file
|
|
|
|
-- The tree stored in ExportTree
|
|
|
|
ExportTreeCurrent
|
2017-09-18 17:57:25 +00:00
|
|
|
tree SRef
|
|
|
|
UniqueTree tree
|
2017-09-04 17:52:22 +00:00
|
|
|
|]
|
|
|
|
|
2017-09-18 22:40:16 +00:00
|
|
|
{- Opens the database, creating it if it doesn't exist yet.
|
|
|
|
-
|
|
|
|
- Only a single process should write to the export at a time, so guard
|
|
|
|
- any writes with the gitAnnexExportLock.
|
|
|
|
-}
|
2017-09-04 17:52:22 +00:00
|
|
|
openDb :: UUID -> Annex ExportHandle
|
|
|
|
openDb u = do
|
|
|
|
dbdir <- fromRepo (gitAnnexExportDbDir u)
|
|
|
|
let db = dbdir </> "db"
|
|
|
|
unlessM (liftIO $ doesFileExist db) $ do
|
|
|
|
initDb db $ void $
|
|
|
|
runMigrationSilent migrateExport
|
2017-09-06 21:07:49 +00:00
|
|
|
h <- liftIO $ H.openDbQueue H.SingleWriter db "exported"
|
2017-09-20 20:22:32 +00:00
|
|
|
return $ ExportHandle h u
|
2017-09-04 17:52:22 +00:00
|
|
|
|
|
|
|
closeDb :: ExportHandle -> Annex ()
|
2017-09-20 20:22:32 +00:00
|
|
|
closeDb (ExportHandle h _) = liftIO $ H.closeDbQueue h
|
2017-09-04 17:52:22 +00:00
|
|
|
|
|
|
|
queueDb :: ExportHandle -> SqlPersistM () -> IO ()
|
2017-09-20 20:22:32 +00:00
|
|
|
queueDb (ExportHandle h _) = H.queueDb h checkcommit
|
2017-09-04 17:52:22 +00:00
|
|
|
where
|
|
|
|
-- commit queue after 1000 changes
|
|
|
|
checkcommit sz _lastcommittime
|
|
|
|
| sz > 1000 = return True
|
|
|
|
| otherwise = return False
|
|
|
|
|
2017-09-18 17:57:25 +00:00
|
|
|
flushDbQueue :: ExportHandle -> IO ()
|
2017-09-20 20:22:32 +00:00
|
|
|
flushDbQueue (ExportHandle h _) = H.flushDbQueue h
|
2017-09-18 17:57:25 +00:00
|
|
|
|
2017-09-18 22:40:16 +00:00
|
|
|
recordExportTreeCurrent :: ExportHandle -> Sha -> IO ()
|
|
|
|
recordExportTreeCurrent h s = queueDb h $ do
|
2017-09-18 17:57:25 +00:00
|
|
|
delete $ from $ \r -> do
|
2017-09-18 22:40:16 +00:00
|
|
|
where_ (r ^. ExportTreeCurrentTree ==. r ^. ExportTreeCurrentTree)
|
|
|
|
void $ insertUnique $ ExportTreeCurrent $ toSRef s
|
2017-09-18 17:57:25 +00:00
|
|
|
|
2017-09-18 22:40:16 +00:00
|
|
|
getExportTreeCurrent :: ExportHandle -> IO (Maybe Sha)
|
2017-09-20 20:22:32 +00:00
|
|
|
getExportTreeCurrent (ExportHandle h _) = H.queryDbQueue h $ do
|
2017-09-18 17:57:25 +00:00
|
|
|
l <- select $ from $ \r -> do
|
2017-09-18 22:40:16 +00:00
|
|
|
where_ (r ^. ExportTreeCurrentTree ==. r ^. ExportTreeCurrentTree)
|
|
|
|
return (r ^. ExportTreeCurrentTree)
|
2017-09-18 17:57:25 +00:00
|
|
|
case l of
|
2017-09-18 22:40:16 +00:00
|
|
|
(s:[]) -> return $ Just $ fromSRef $ unValue s
|
2017-09-18 17:57:25 +00:00
|
|
|
_ -> return Nothing
|
|
|
|
|
|
|
|
addExportedLocation :: ExportHandle -> Key -> ExportLocation -> IO ()
|
|
|
|
addExportedLocation h k el = queueDb h $ do
|
2017-09-15 18:33:07 +00:00
|
|
|
void $ insertUnique $ Exported ik ef
|
2017-09-25 13:57:41 +00:00
|
|
|
let edirs = map
|
2017-09-18 17:57:25 +00:00
|
|
|
(\ed -> ExportedDirectory (toSFilePath (fromExportDirectory ed)) ef)
|
2017-09-15 20:34:45 +00:00
|
|
|
(exportDirectories el)
|
2017-09-25 13:57:41 +00:00
|
|
|
#if MIN_VERSION_persistent(2,1,0)
|
|
|
|
insertMany_ edirs
|
|
|
|
#else
|
|
|
|
void $ insertMany edirs
|
|
|
|
#endif
|
2017-09-15 18:33:07 +00:00
|
|
|
where
|
|
|
|
ik = toIKey k
|
2017-09-18 17:57:25 +00:00
|
|
|
ef = toSFilePath (fromExportLocation el)
|
2017-09-04 17:52:22 +00:00
|
|
|
|
2017-09-18 17:57:25 +00:00
|
|
|
removeExportedLocation :: ExportHandle -> Key -> ExportLocation -> IO ()
|
|
|
|
removeExportedLocation h k el = queueDb h $ do
|
2017-09-04 17:52:22 +00:00
|
|
|
delete $ from $ \r -> do
|
|
|
|
where_ (r ^. ExportedKey ==. val ik &&. r ^. ExportedFile ==. val ef)
|
2017-09-18 17:57:25 +00:00
|
|
|
let subdirs = map (toSFilePath . fromExportDirectory)
|
2017-09-15 20:34:45 +00:00
|
|
|
(exportDirectories el)
|
2017-09-15 18:33:07 +00:00
|
|
|
delete $ from $ \r -> do
|
|
|
|
where_ (r ^. ExportedDirectoryFile ==. val ef
|
|
|
|
&&. r ^. ExportedDirectorySubdir `in_` valList subdirs)
|
2017-09-04 17:52:22 +00:00
|
|
|
where
|
|
|
|
ik = toIKey k
|
2017-09-18 17:57:25 +00:00
|
|
|
ef = toSFilePath (fromExportLocation el)
|
2017-09-04 18:33:09 +00:00
|
|
|
|
|
|
|
{- Note that this does not see recently queued changes. -}
|
2017-09-18 17:57:25 +00:00
|
|
|
getExportedLocation :: ExportHandle -> Key -> IO [ExportLocation]
|
2017-09-20 20:22:32 +00:00
|
|
|
getExportedLocation (ExportHandle h _) k = H.queryDbQueue h $ do
|
2017-09-04 17:52:22 +00:00
|
|
|
l <- select $ from $ \r -> do
|
|
|
|
where_ (r ^. ExportedKey ==. val ik)
|
|
|
|
return (r ^. ExportedFile)
|
2017-09-18 17:57:25 +00:00
|
|
|
return $ map (mkExportLocation . fromSFilePath . unValue) l
|
2017-09-04 17:52:22 +00:00
|
|
|
where
|
|
|
|
ik = toIKey k
|
2017-09-15 18:33:07 +00:00
|
|
|
|
|
|
|
{- Note that this does not see recently queued changes. -}
|
|
|
|
isExportDirectoryEmpty :: ExportHandle -> ExportDirectory -> IO Bool
|
2017-09-20 20:22:32 +00:00
|
|
|
isExportDirectoryEmpty (ExportHandle h _) d = H.queryDbQueue h $ do
|
2017-09-15 18:33:07 +00:00
|
|
|
l <- select $ from $ \r -> do
|
|
|
|
where_ (r ^. ExportedDirectorySubdir ==. val ed)
|
|
|
|
return (r ^. ExportedDirectoryFile)
|
|
|
|
return $ null l
|
|
|
|
where
|
2017-09-18 17:57:25 +00:00
|
|
|
ed = toSFilePath $ fromExportDirectory d
|
|
|
|
|
|
|
|
{- Get locations in the export that might contain a key. -}
|
|
|
|
getExportTree :: ExportHandle -> Key -> IO [ExportLocation]
|
2017-09-20 20:22:32 +00:00
|
|
|
getExportTree (ExportHandle h _) k = H.queryDbQueue h $ do
|
2017-09-18 17:57:25 +00:00
|
|
|
l <- select $ from $ \r -> do
|
|
|
|
where_ (r ^. ExportTreeKey ==. val ik)
|
|
|
|
return (r ^. ExportTreeFile)
|
|
|
|
return $ map (mkExportLocation . fromSFilePath . unValue) l
|
|
|
|
where
|
|
|
|
ik = toIKey k
|
|
|
|
|
|
|
|
addExportTree :: ExportHandle -> Key -> ExportLocation -> IO ()
|
|
|
|
addExportTree h k loc = queueDb h $
|
2017-09-18 22:40:16 +00:00
|
|
|
void $ insertUnique $ ExportTree ik ef
|
2017-09-18 17:57:25 +00:00
|
|
|
where
|
|
|
|
ik = toIKey k
|
|
|
|
ef = toSFilePath (fromExportLocation loc)
|
|
|
|
|
|
|
|
removeExportTree :: ExportHandle -> Key -> ExportLocation -> IO ()
|
|
|
|
removeExportTree h k loc = queueDb h $
|
|
|
|
delete $ from $ \r ->
|
|
|
|
where_ (r ^. ExportTreeKey ==. val ik &&. r ^. ExportTreeFile ==. val ef)
|
|
|
|
where
|
|
|
|
ik = toIKey k
|
|
|
|
ef = toSFilePath (fromExportLocation loc)
|
|
|
|
|
|
|
|
{- Diff from the old to the new tree and update the ExportTree table. -}
|
|
|
|
updateExportTree :: ExportHandle -> Sha -> Sha -> Annex ()
|
|
|
|
updateExportTree h old new = do
|
|
|
|
(diff, cleanup) <- inRepo $
|
|
|
|
Git.DiffTree.diffTreeRecursive old new
|
|
|
|
forM_ diff $ \i -> do
|
|
|
|
srcek <- getek (Git.DiffTree.srcsha i)
|
|
|
|
dstek <- getek (Git.DiffTree.dstsha i)
|
2017-09-18 18:24:42 +00:00
|
|
|
updateExportTree' h srcek dstek i
|
2017-09-18 17:57:25 +00:00
|
|
|
void $ liftIO cleanup
|
|
|
|
where
|
|
|
|
getek sha
|
|
|
|
| sha == nullSha = return Nothing
|
|
|
|
| otherwise = Just <$> exportKey sha
|
2017-09-18 18:24:42 +00:00
|
|
|
|
|
|
|
updateExportTree' :: ExportHandle -> Maybe ExportKey -> Maybe ExportKey -> Git.DiffTree.DiffTreeItem-> Annex ()
|
|
|
|
updateExportTree' h srcek dstek i = do
|
|
|
|
case srcek of
|
|
|
|
Nothing -> return ()
|
|
|
|
Just k -> liftIO $ removeExportTree h (asKey k) loc
|
|
|
|
case dstek of
|
|
|
|
Nothing -> return ()
|
|
|
|
Just k -> liftIO $ addExportTree h (asKey k) loc
|
|
|
|
where
|
|
|
|
loc = mkExportLocation $ getTopFilePath $ Git.DiffTree.file i
|
2017-09-20 20:22:32 +00:00
|
|
|
|
|
|
|
updateExportTreeFromLog :: ExportHandle -> Annex ()
|
|
|
|
updateExportTreeFromLog db@(ExportHandle _ u) =
|
|
|
|
withExclusiveLock (gitAnnexExportLock u) $ do
|
|
|
|
old <- liftIO $ fromMaybe emptyTree
|
|
|
|
<$> getExportTreeCurrent db
|
|
|
|
l <- Log.getExport u
|
|
|
|
case map Log.exportedTreeish l of
|
|
|
|
(new:[]) | new /= old -> do
|
|
|
|
updateExportTree db old new
|
|
|
|
liftIO $ recordExportTreeCurrent db new
|
|
|
|
liftIO $ flushDbQueue db
|
|
|
|
_ -> return ()
|