summaryrefslogtreecommitdiff
path: root/Annex/LockFile.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2015-05-18 16:23:07 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2015-05-19 14:09:52 -0400
commitae5433c4caf0ee57e3338df6dcd625f20ece7101 (patch)
tree5bdab44419df36e7e5aab2e36cd6b221654de04e /Annex/LockFile.hs
parent94a3e606fb31150c969d63790ec1ef870f413cc1 (diff)
use lock pools throughout git-annex
The one exception is in Utility.Daemon. As long as a process only daemonizes once, which seems reasonable, and as long as it avoids calling checkDaemon once it's already running as a daemon, the fcntl locking gotchas won't be a problem there. Annex.LockFile has it's own separate lock pool layer, which has been renamed to LockCache. This is a persistent cache of locks that persist until closed. This is not quite done; lockContent stil needs to be converted.
Diffstat (limited to 'Annex/LockFile.hs')
-rw-r--r--Annex/LockFile.hs36
1 files changed, 18 insertions, 18 deletions
diff --git a/Annex/LockFile.hs b/Annex/LockFile.hs
index 62a101aa5..928b36ec5 100644
--- a/Annex/LockFile.hs
+++ b/Annex/LockFile.hs
@@ -8,26 +8,26 @@
{-# LANGUAGE CPP #-}
module Annex.LockFile (
- lockFileShared,
+ lockFileCached,
unlockFile,
- getLockPool,
+ getLockCache,
withExclusiveLock,
tryExclusiveLock,
) where
import Common.Annex
import Annex
-import Types.LockPool
+import Types.LockCache
import qualified Git
import Annex.Perms
-import Utility.LockFile
+import Utility.LockPool
import qualified Data.Map as M
{- Create a specified lock file, and takes a shared lock, which is retained
- - in the pool. -}
-lockFileShared :: FilePath -> Annex ()
-lockFileShared file = go =<< fromLockPool file
+ - in the cache. -}
+lockFileCached :: FilePath -> Annex ()
+lockFileCached file = go =<< fromLockCache file
where
go (Just _) = noop -- already locked
go Nothing = do
@@ -37,25 +37,25 @@ lockFileShared file = go =<< fromLockPool file
#else
lockhandle <- liftIO $ waitToLock $ lockShared file
#endif
- changeLockPool $ M.insert file lockhandle
+ changeLockCache $ M.insert file lockhandle
unlockFile :: FilePath -> Annex ()
-unlockFile file = maybe noop go =<< fromLockPool file
+unlockFile file = maybe noop go =<< fromLockCache file
where
go lockhandle = do
liftIO $ dropLock lockhandle
- changeLockPool $ M.delete file
+ changeLockCache $ M.delete file
-getLockPool :: Annex LockPool
-getLockPool = getState lockpool
+getLockCache :: Annex LockCache
+getLockCache = getState lockcache
-fromLockPool :: FilePath -> Annex (Maybe LockHandle)
-fromLockPool file = M.lookup file <$> getLockPool
+fromLockCache :: FilePath -> Annex (Maybe LockHandle)
+fromLockCache file = M.lookup file <$> getLockCache
-changeLockPool :: (LockPool -> LockPool) -> Annex ()
-changeLockPool a = do
- m <- getLockPool
- changeState $ \s -> s { lockpool = a m }
+changeLockCache :: (LockCache -> LockCache) -> Annex ()
+changeLockCache a = do
+ m <- getLockCache
+ changeState $ \s -> s { lockcache = a m }
{- Runs an action with an exclusive lock held. If the lock is already
- held, blocks until it becomes free. -}