wire up scan and transfer to newly added removable drive

remote setup still todo
This commit is contained in:
Joey Hess 2012-08-04 21:18:57 -04:00
parent e125ce74b8
commit 3add2cd3ba
6 changed files with 49 additions and 57 deletions

View file

@ -155,7 +155,7 @@ startAssistant assistant daemonize webappwaiter = do
mapM_ startthread mapM_ startthread
[ watch $ commitThread st changechan commitchan transferqueue dstatus [ watch $ commitThread st changechan commitchan transferqueue dstatus
#ifdef WITH_WEBAPP #ifdef WITH_WEBAPP
, assist $ webAppThread (Just st) dstatus transferqueue Nothing webappwaiter , assist $ webAppThread (Just st) dstatus scanremotes transferqueue Nothing webappwaiter
#endif #endif
, assist $ pushThread st dstatus commitchan pushmap , assist $ pushThread st dstatus commitchan pushmap
, assist $ pushRetryThread st dstatus pushmap , assist $ pushRetryThread st dstatus pushmap

View file

@ -154,13 +154,14 @@ pollingThread st dstatus scanremotes = go =<< currentMountPoints
go nowmounted go nowmounted
handleMounts :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> MountPoints -> MountPoints -> IO () handleMounts :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> MountPoints -> MountPoints -> IO ()
handleMounts st dstatus scanremotes wasmounted nowmounted = mapM_ (handleMount st dstatus scanremotes) $ handleMounts st dstatus scanremotes wasmounted nowmounted =
S.toList $ newMountPoints wasmounted nowmounted mapM_ (handleMount st dstatus scanremotes . mnt_dir) $
S.toList $ newMountPoints wasmounted nowmounted
handleMount :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> Mntent -> IO () handleMount :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> FilePath -> IO ()
handleMount st dstatus scanremotes mntent = do handleMount st dstatus scanremotes dir = do
debug thisThread ["detected mount of", dir] debug thisThread ["detected mount of", dir]
rs <- remotesUnder st dstatus mntent rs <- remotesUnder st dstatus dir
unless (null rs) $ do unless (null rs) $ do
branch <- runThreadState st $ Command.Sync.currentBranch branch <- runThreadState st $ Command.Sync.currentBranch
let nonspecial = filter (Git.repoIsLocal . Remote.repo) rs let nonspecial = filter (Git.repoIsLocal . Remote.repo) rs
@ -171,8 +172,6 @@ handleMount st dstatus scanremotes mntent = do
now <- getCurrentTime now <- getCurrentTime
pushToRemotes thisThread now st Nothing nonspecial pushToRemotes thisThread now st Nothing nonspecial
addScanRemotes scanremotes rs addScanRemotes scanremotes rs
where
dir = mnt_dir mntent
{- Finds remotes located underneath the mount point. {- Finds remotes located underneath the mount point.
- -
@ -182,8 +181,8 @@ handleMount st dstatus scanremotes mntent = do
- at startup time, or may have changed (it could even be a different - at startup time, or may have changed (it could even be a different
- repository at the same remote location..) - repository at the same remote location..)
-} -}
remotesUnder :: ThreadState -> DaemonStatusHandle -> Mntent -> IO [Remote] remotesUnder :: ThreadState -> DaemonStatusHandle -> FilePath -> IO [Remote]
remotesUnder st dstatus mntent = runThreadState st $ do remotesUnder st dstatus dir = runThreadState st $ do
repotop <- fromRepo Git.repoPath repotop <- fromRepo Git.repoPath
rs <- remoteList rs <- remoteList
pairs <- mapM (checkremote repotop) rs pairs <- mapM (checkremote repotop) rs
@ -194,7 +193,7 @@ remotesUnder st dstatus mntent = runThreadState st $ do
return $ map snd $ filter fst pairs return $ map snd $ filter fst pairs
where where
checkremote repotop r = case Remote.path r of checkremote repotop r = case Remote.path r of
Just p | under mntent (absPathFrom repotop p) -> Just p | dirContains dir (absPathFrom repotop p) ->
(,) <$> pure True <*> updateremote r (,) <$> pure True <*> updateremote r
_ -> return (False, r) _ -> return (False, r)
updateremote r = do updateremote r = do
@ -214,7 +213,3 @@ currentMountPoints = S.fromList <$> getMounts
newMountPoints :: MountPoints -> MountPoints -> MountPoints newMountPoints :: MountPoints -> MountPoints -> MountPoints
newMountPoints old new = S.difference new old newMountPoints old new = S.difference new old
{- Checks if a mount point contains a path. The path must be absolute. -}
under :: Mntent -> FilePath -> Bool
under = dirContains . mnt_dir

View file

@ -19,6 +19,7 @@ import Assistant.WebApp.Configurators
import Assistant.WebApp.Documentation import Assistant.WebApp.Documentation
import Assistant.ThreadedMonad import Assistant.ThreadedMonad
import Assistant.DaemonStatus import Assistant.DaemonStatus
import Assistant.ScanRemotes
import Assistant.TransferQueue import Assistant.TransferQueue
import Utility.WebApp import Utility.WebApp
import Utility.FileMode import Utility.FileMode
@ -40,14 +41,16 @@ type Url = String
webAppThread webAppThread
:: (Maybe ThreadState) :: (Maybe ThreadState)
-> DaemonStatusHandle -> DaemonStatusHandle
-> ScanRemoteMap
-> TransferQueue -> TransferQueue
-> Maybe (IO String) -> Maybe (IO String)
-> Maybe (Url -> FilePath -> IO ()) -> Maybe (Url -> FilePath -> IO ())
-> IO () -> IO ()
webAppThread mst dstatus transferqueue postfirstrun onstartup = do webAppThread mst dstatus scanremotes transferqueue postfirstrun onstartup = do
webapp <- WebApp webapp <- WebApp
<$> pure mst <$> pure mst
<*> pure dstatus <*> pure dstatus
<*> pure scanremotes
<*> pure transferqueue <*> pure transferqueue
<*> (pack <$> genRandomToken) <*> (pack <$> genRandomToken)
<*> getreldir mst <*> getreldir mst

View file

@ -13,6 +13,7 @@ module Assistant.WebApp where
import Assistant.Common import Assistant.Common
import Assistant.ThreadedMonad import Assistant.ThreadedMonad
import Assistant.DaemonStatus import Assistant.DaemonStatus
import Assistant.ScanRemotes
import Assistant.TransferQueue import Assistant.TransferQueue
import Assistant.Alert hiding (Widget) import Assistant.Alert hiding (Widget)
import Utility.NotificationBroadcaster import Utility.NotificationBroadcaster
@ -32,6 +33,7 @@ mkYesodData "WebApp" $(parseRoutesFile "Assistant/WebApp/routes")
data WebApp = WebApp data WebApp = WebApp
{ threadState :: Maybe ThreadState { threadState :: Maybe ThreadState
, daemonStatus :: DaemonStatusHandle , daemonStatus :: DaemonStatusHandle
, scanRemotes :: ScanRemoteMap
, transferQueue :: TransferQueue , transferQueue :: TransferQueue
, secretToken :: Text , secretToken :: Text
, relDir :: Maybe FilePath , relDir :: Maybe FilePath

View file

@ -12,6 +12,7 @@ module Assistant.WebApp.Configurators where
import Assistant.Common import Assistant.Common
import Assistant.WebApp import Assistant.WebApp
import Assistant.WebApp.SideBar import Assistant.WebApp.SideBar
import Assistant.Threads.MountWatcher (handleMount)
import Utility.Yesod import Utility.Yesod
import qualified Remote import qualified Remote
import Logs.Web (webUUID) import Logs.Web (webUUID)
@ -32,7 +33,6 @@ import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import Data.Char import Data.Char
import System.Posix.Directory import System.Posix.Directory
import System.Posix.User
import qualified Control.Exception as E import qualified Control.Exception as E
{- The main configuration screen. -} {- The main configuration screen. -}
@ -199,7 +199,7 @@ selectDriveForm drives def = renderBootstrap $ RemovableDrive
, "free)" , "free)"
] ]
{- Making the first repository, when starting the webapp for the first time. -} {- Adding a removable drive. -}
getAddDriveR :: Handler RepHtml getAddDriveR :: Handler RepHtml
getAddDriveR = bootstrap (Just Config) $ do getAddDriveR = bootstrap (Just Config) $ do
sideBarDisplay sideBarDisplay
@ -211,50 +211,38 @@ getAddDriveR = bootstrap (Just Config) $ do
selectDriveForm (sort writabledrives) Nothing selectDriveForm (sort writabledrives) Nothing
case res of case res of
FormSuccess (RemovableDrive { mountPoint = d }) -> lift $ do FormSuccess (RemovableDrive { mountPoint = d }) -> lift $ do
liftIO $ go $ T.unpack d </> "annex" webapp <- getYesod
liftIO $ go webapp $ T.unpack d </> "annex"
setMessage $ toHtml $ T.unwords ["Added", d] setMessage $ toHtml $ T.unwords ["Added", d]
redirect ListRepositoriesR redirect ListRepositoriesR
_ -> do _ -> do
let authtoken = webAppFormAuthToken let authtoken = webAppFormAuthToken
$(widgetFile "configurators/adddrive") $(widgetFile "configurators/adddrive")
where where
{- There may already be a git-annex repo on the drive. go webapp dir = do
- If so, avoid re-initualizing it; this will be the
- case if a user is adding the same removable drive
- to several computers.
-
- Some drives will have FAT or another horrible filesystem
- that does not support symlinks; make a bare repo on those.
-
- Use the basename of the mount point, along with the
- username (but without the hostname as this repo
- travels!), as the repo description, and use the basename
- of the mount point as the git remote name.
-}
go dir = do
r <- E.try getannex :: IO (Either E.SomeException Annex.AnnexState) r <- E.try getannex :: IO (Either E.SomeException Annex.AnnexState)
state <- case r of case r of
Right state -> return state Right _ -> noop
Left _e -> do Left _e -> do
createDirectoryIfMissing True dir createDirectoryIfMissing True dir
bare <- not <$> canMakeSymlink dir bare <- not <$> canMakeSymlink dir
makeRepo dir bare makeRepo dir bare
getannex initRepo dir $ Just remotename
desc <- getdesc
Annex.eval state $ -- TODO setup up git remotes
unlessM isInitialized $ -- TODO add it to Annex.remotes
initialize $ Just desc
{- Now synthesize a mount event of the new
- git repository. This will sync it, and queue
- file transfers. -}
handleMount
(fromJust $ threadState webapp)
(daemonStatus webapp)
(scanRemotes webapp)
dir
where where
getannex = Annex.new =<< Git.Construct.fromAbsPath dir getannex = Annex.new =<< Git.Construct.fromAbsPath dir
remotename = takeFileName dir remotename = takeFileName dir
getdesc = do
username <- userName <$>
(getUserEntryForID =<< getEffectiveUserID)
return $ concat
[ username
, ":"
, remotename
]
{- List of removable drives. -} {- List of removable drives. -}
driveList :: IO [RemovableDrive] driveList :: IO [RemovableDrive]
@ -265,12 +253,12 @@ driveList = mapM (gen . mnt_dir) =<< filter sane <$> getMounts
<*> pure (T.pack dir) <*> pure (T.pack dir)
-- filter out some things that are surely not removable drives -- filter out some things that are surely not removable drives
sane Mntent { mnt_dir = dir, mnt_fsname = dev } sane Mntent { mnt_dir = dir, mnt_fsname = dev }
-- We want real disks like /dev/foo, not {- We want real disks like /dev/foo, not
-- dummy mount points like proc or tmpfs or - dummy mount points like proc or tmpfs or
-- gvfs-fuse-daemon - gvfs-fuse-daemon. -}
| not ('/' `elem` dev) = False | not ('/' `elem` dev) = False
-- Just in case: These mount points are surely not {- Just in case: These mount points are surely not
-- removable disks. - removable disks. -}
| dir == "/" = False | dir == "/" = False
| dir == "/tmp" = False | dir == "/tmp" = False
| dir == "/run/shm" = False | dir == "/run/shm" = False
@ -305,9 +293,10 @@ makeRepo path bare = do
{- Initializes a git-annex repository in a directory with a description. -} {- Initializes a git-annex repository in a directory with a description. -}
initRepo :: FilePath -> Maybe String -> IO () initRepo :: FilePath -> Maybe String -> IO ()
initRepo path desc = do initRepo path desc = do
g <- Git.Config.read =<< Git.Construct.fromPath path state <- Annex.new =<< Git.Config.read =<< Git.Construct.fromPath path
state <- Annex.new g Annex.eval state $
Annex.eval state $ initialize desc unlessM isInitialized $
initialize desc
{- Adds a directory to the autostart file. -} {- Adds a directory to the autostart file. -}
addAutoStart :: FilePath -> IO () addAutoStart :: FilePath -> IO ()

View file

@ -11,6 +11,7 @@ import Common.Annex
import Command import Command
import Assistant import Assistant
import Assistant.DaemonStatus import Assistant.DaemonStatus
import Assistant.ScanRemotes
import Assistant.TransferQueue import Assistant.TransferQueue
import Assistant.Threads.WebApp import Assistant.Threads.WebApp
import Utility.WebApp import Utility.WebApp
@ -83,10 +84,12 @@ autoStart autostartfile = do
firstRun :: IO () firstRun :: IO ()
firstRun = do firstRun = do
dstatus <- atomically . newTMVar =<< newDaemonStatus dstatus <- atomically . newTMVar =<< newDaemonStatus
scanremotes <- newScanRemoteMap
transferqueue <- newTransferQueue transferqueue <- newTransferQueue
v <- newEmptyMVar v <- newEmptyMVar
let callback a = Just $ a v let callback a = Just $ a v
webAppThread Nothing dstatus transferqueue (callback signaler) (callback mainthread) webAppThread Nothing dstatus scanremotes transferqueue
(callback signaler) (callback mainthread)
where where
signaler v = do signaler v = do
putMVar v "" putMVar v ""