fix kevent symlink creation
This commit is contained in:
parent
4ab9449cee
commit
57cf65eb6d
6 changed files with 83 additions and 57 deletions
|
@ -46,6 +46,7 @@ module Assistant where
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Assistant.ThreadedMonad
|
import Assistant.ThreadedMonad
|
||||||
import Assistant.DaemonStatus
|
import Assistant.DaemonStatus
|
||||||
|
import Assistant.Changes
|
||||||
import Assistant.Watcher
|
import Assistant.Watcher
|
||||||
import Assistant.Committer
|
import Assistant.Committer
|
||||||
import Assistant.SanityChecker
|
import Assistant.SanityChecker
|
||||||
|
|
59
Assistant/Changes.hs
Normal file
59
Assistant/Changes.hs
Normal file
|
@ -0,0 +1,59 @@
|
||||||
|
{- git-annex assistant change tracking
|
||||||
|
-
|
||||||
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
||||||
|
-}
|
||||||
|
|
||||||
|
module Assistant.Changes where
|
||||||
|
|
||||||
|
import Common.Annex
|
||||||
|
import qualified Annex.Queue
|
||||||
|
|
||||||
|
import Control.Concurrent.STM
|
||||||
|
import Data.Time.Clock
|
||||||
|
|
||||||
|
data ChangeType = PendingAddChange | LinkChange | RmChange | RmDirChange
|
||||||
|
deriving (Show, Eq)
|
||||||
|
|
||||||
|
type ChangeChan = TChan Change
|
||||||
|
|
||||||
|
data Change = Change
|
||||||
|
{ changeTime :: UTCTime
|
||||||
|
, changeFile :: FilePath
|
||||||
|
, changeType :: ChangeType
|
||||||
|
}
|
||||||
|
deriving (Show)
|
||||||
|
|
||||||
|
runChangeChan :: STM a -> IO a
|
||||||
|
runChangeChan = atomically
|
||||||
|
|
||||||
|
newChangeChan :: IO ChangeChan
|
||||||
|
newChangeChan = atomically newTChan
|
||||||
|
|
||||||
|
{- Handlers call this when they made a change that needs to get committed. -}
|
||||||
|
madeChange :: FilePath -> ChangeType -> Annex (Maybe Change)
|
||||||
|
madeChange f t = do
|
||||||
|
-- Just in case the commit thread is not flushing the queue fast enough.
|
||||||
|
when (t /= PendingAddChange) $
|
||||||
|
Annex.Queue.flushWhenFull
|
||||||
|
liftIO $ Just <$> (Change <$> getCurrentTime <*> pure f <*> pure t)
|
||||||
|
|
||||||
|
noChange :: Annex (Maybe Change)
|
||||||
|
noChange = return Nothing
|
||||||
|
|
||||||
|
{- Gets all unhandled changes.
|
||||||
|
- Blocks until at least one change is made. -}
|
||||||
|
getChanges :: ChangeChan -> IO [Change]
|
||||||
|
getChanges chan = runChangeChan $ do
|
||||||
|
c <- readTChan chan
|
||||||
|
go [c]
|
||||||
|
where
|
||||||
|
go l = do
|
||||||
|
v <- tryReadTChan chan
|
||||||
|
case v of
|
||||||
|
Nothing -> return l
|
||||||
|
Just c -> go (c:l)
|
||||||
|
|
||||||
|
{- Puts unhandled changes back into the channel.
|
||||||
|
- Note: Original order is not preserved. -}
|
||||||
|
refillChanges :: ChangeChan -> [Change] -> IO ()
|
||||||
|
refillChanges chan cs = runChangeChan $ mapM_ (writeTChan chan) cs
|
|
@ -1,4 +1,4 @@
|
||||||
{- git-annex assistant change tracking and committing
|
{- git-annex assistant commit thread
|
||||||
-
|
-
|
||||||
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
||||||
-}
|
-}
|
||||||
|
@ -6,67 +6,24 @@
|
||||||
module Assistant.Committer where
|
module Assistant.Committer where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
|
import Assistant.Changes
|
||||||
import Assistant.ThreadedMonad
|
import Assistant.ThreadedMonad
|
||||||
|
import Assistant.Watcher
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Annex.Queue
|
import qualified Annex.Queue
|
||||||
import qualified Git.Command
|
import qualified Git.Command
|
||||||
|
import qualified Git.HashObject
|
||||||
|
import Git.Types
|
||||||
import qualified Command.Add
|
import qualified Command.Add
|
||||||
import Utility.ThreadScheduler
|
import Utility.ThreadScheduler
|
||||||
import qualified Utility.Lsof as Lsof
|
import qualified Utility.Lsof as Lsof
|
||||||
|
import qualified Utility.DirWatcher as DirWatcher
|
||||||
import Types.Backend
|
import Types.Backend
|
||||||
|
|
||||||
import Control.Concurrent.STM
|
|
||||||
import Data.Time.Clock
|
import Data.Time.Clock
|
||||||
import Data.Tuple.Utils
|
import Data.Tuple.Utils
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
|
||||||
data ChangeType = PendingAddChange | LinkChange | RmChange | RmDirChange
|
|
||||||
deriving (Show, Eq)
|
|
||||||
|
|
||||||
type ChangeChan = TChan Change
|
|
||||||
|
|
||||||
data Change = Change
|
|
||||||
{ changeTime :: UTCTime
|
|
||||||
, changeFile :: FilePath
|
|
||||||
, changeType :: ChangeType
|
|
||||||
}
|
|
||||||
deriving (Show)
|
|
||||||
|
|
||||||
runChangeChan :: STM a -> IO a
|
|
||||||
runChangeChan = atomically
|
|
||||||
|
|
||||||
newChangeChan :: IO ChangeChan
|
|
||||||
newChangeChan = atomically newTChan
|
|
||||||
|
|
||||||
{- Handlers call this when they made a change that needs to get committed. -}
|
|
||||||
madeChange :: FilePath -> ChangeType -> Annex (Maybe Change)
|
|
||||||
madeChange f t = do
|
|
||||||
-- Just in case the commit thread is not flushing the queue fast enough.
|
|
||||||
when (t /= PendingAddChange) $
|
|
||||||
Annex.Queue.flushWhenFull
|
|
||||||
liftIO $ Just <$> (Change <$> getCurrentTime <*> pure f <*> pure t)
|
|
||||||
|
|
||||||
noChange :: Annex (Maybe Change)
|
|
||||||
noChange = return Nothing
|
|
||||||
|
|
||||||
{- Gets all unhandled changes.
|
|
||||||
- Blocks until at least one change is made. -}
|
|
||||||
getChanges :: ChangeChan -> IO [Change]
|
|
||||||
getChanges chan = runChangeChan $ do
|
|
||||||
c <- readTChan chan
|
|
||||||
go [c]
|
|
||||||
where
|
|
||||||
go l = do
|
|
||||||
v <- tryReadTChan chan
|
|
||||||
case v of
|
|
||||||
Nothing -> return l
|
|
||||||
Just c -> go (c:l)
|
|
||||||
|
|
||||||
{- Puts unhandled changes back into the channel.
|
|
||||||
- Note: Original order is not preserved. -}
|
|
||||||
refillChanges :: ChangeChan -> [Change] -> IO ()
|
|
||||||
refillChanges chan cs = runChangeChan $ mapM_ (writeTChan chan) cs
|
|
||||||
|
|
||||||
{- This thread makes git commits at appropriate times. -}
|
{- This thread makes git commits at appropriate times. -}
|
||||||
commitThread :: ThreadState -> ChangeChan -> IO ()
|
commitThread :: ThreadState -> ChangeChan -> IO ()
|
||||||
commitThread st changechan = runEvery (Seconds 1) $ do
|
commitThread st changechan = runEvery (Seconds 1) $ do
|
||||||
|
@ -122,7 +79,9 @@ shouldCommit now changes
|
||||||
-
|
-
|
||||||
- When a file is added, Inotify will notice the new symlink. So this waits
|
- When a file is added, Inotify will notice the new symlink. So this waits
|
||||||
- for additional Changes to arrive, so that the symlink has hopefully been
|
- for additional Changes to arrive, so that the symlink has hopefully been
|
||||||
- staged before returning, and will be committed.
|
- staged before returning, and will be committed immediately. OTOH, for
|
||||||
|
- kqueue, eventsCoalesce, so instead the symlink is directly created and
|
||||||
|
- staged.
|
||||||
-}
|
-}
|
||||||
handleAdds :: ThreadState -> ChangeChan -> [Change] -> IO ()
|
handleAdds :: ThreadState -> ChangeChan -> [Change] -> IO ()
|
||||||
handleAdds st changechan cs
|
handleAdds st changechan cs
|
||||||
|
@ -131,8 +90,9 @@ handleAdds st changechan cs
|
||||||
toadd' <- safeToAdd st toadd
|
toadd' <- safeToAdd st toadd
|
||||||
unless (null toadd') $ do
|
unless (null toadd') $ do
|
||||||
added <- filter id <$> forM toadd' add
|
added <- filter id <$> forM toadd' add
|
||||||
unless (null added) $
|
when (DirWatcher.eventsCoalesce && not (null added)) $
|
||||||
handleAdds st changechan =<< getChanges changechan
|
handleAdds st changechan
|
||||||
|
=<< getChanges changechan
|
||||||
where
|
where
|
||||||
toadd = map changeFile $ filter isPendingAdd cs
|
toadd = map changeFile $ filter isPendingAdd cs
|
||||||
|
|
||||||
|
@ -148,7 +108,11 @@ handleAdds st changechan cs
|
||||||
showEndFail
|
showEndFail
|
||||||
return False
|
return False
|
||||||
handle file (Just key) = do
|
handle file (Just key) = do
|
||||||
Command.Add.link file key True
|
link <- Command.Add.link file key True
|
||||||
|
when DirWatcher.eventsCoalesce $ do
|
||||||
|
sha <- inRepo $
|
||||||
|
Git.HashObject.hashObject BlobObject link
|
||||||
|
stageSymlink file sha
|
||||||
showEndOk
|
showEndOk
|
||||||
return True
|
return True
|
||||||
|
|
||||||
|
|
|
@ -11,7 +11,7 @@ import Common.Annex
|
||||||
import qualified Git.LsFiles
|
import qualified Git.LsFiles
|
||||||
import Assistant.DaemonStatus
|
import Assistant.DaemonStatus
|
||||||
import Assistant.ThreadedMonad
|
import Assistant.ThreadedMonad
|
||||||
import Assistant.Committer
|
import Assistant.Changes
|
||||||
import Utility.ThreadScheduler
|
import Utility.ThreadScheduler
|
||||||
import qualified Assistant.Watcher
|
import qualified Assistant.Watcher
|
||||||
|
|
||||||
|
|
|
@ -12,7 +12,7 @@ module Assistant.Watcher where
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Assistant.ThreadedMonad
|
import Assistant.ThreadedMonad
|
||||||
import Assistant.DaemonStatus
|
import Assistant.DaemonStatus
|
||||||
import Assistant.Committer
|
import Assistant.Changes
|
||||||
import Utility.DirWatcher
|
import Utility.DirWatcher
|
||||||
import Utility.Types.DirWatcher
|
import Utility.Types.DirWatcher
|
||||||
import qualified Annex.Queue
|
import qualified Annex.Queue
|
||||||
|
|
|
@ -97,8 +97,8 @@ undo file key e = do
|
||||||
src <- inRepo $ gitAnnexLocation key
|
src <- inRepo $ gitAnnexLocation key
|
||||||
liftIO $ moveFile src file
|
liftIO $ moveFile src file
|
||||||
|
|
||||||
{- Creates the symlink to the annexed content. -}
|
{- Creates the symlink to the annexed content, returns the link target. -}
|
||||||
link :: FilePath -> Key -> Bool -> Annex ()
|
link :: FilePath -> Key -> Bool -> Annex String
|
||||||
link file key hascontent = handle (undo file key) $ do
|
link file key hascontent = handle (undo file key) $ do
|
||||||
l <- calcGitLink file key
|
l <- calcGitLink file key
|
||||||
liftIO $ createSymbolicLink l file
|
liftIO $ createSymbolicLink l file
|
||||||
|
@ -112,6 +112,8 @@ link file key hascontent = handle (undo file key) $ do
|
||||||
mtime <- modificationTime <$> getFileStatus file
|
mtime <- modificationTime <$> getFileStatus file
|
||||||
touch file (TimeSpec mtime) False
|
touch file (TimeSpec mtime) False
|
||||||
|
|
||||||
|
return l
|
||||||
|
|
||||||
{- Note: Several other commands call this, and expect it to
|
{- Note: Several other commands call this, and expect it to
|
||||||
- create the symlink and add it. -}
|
- create the symlink and add it. -}
|
||||||
cleanup :: FilePath -> Key -> Bool -> CommandCleanup
|
cleanup :: FilePath -> Key -> Bool -> CommandCleanup
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue