2011-03-30 18:56:31 +00:00
|
|
|
{- A "remote" that is just a filesystem directory.
|
2011-03-30 17:18:46 +00:00
|
|
|
-
|
2014-07-27 00:19:24 +00:00
|
|
|
- Copyright 2011-2014 Joey Hess <joey@kitenet.net>
|
2011-03-30 17:18:46 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-05-11 20:03:00 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2014-08-04 13:35:57 +00:00
|
|
|
module Remote.Directory (
|
|
|
|
remote,
|
|
|
|
finalizeStoreGeneric,
|
|
|
|
removeDirGeneric,
|
|
|
|
) where
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2012-06-20 17:13:40 +00:00
|
|
|
import qualified Data.ByteString.Lazy as L
|
2011-03-30 17:18:46 +00:00
|
|
|
import qualified Data.Map as M
|
|
|
|
|
2011-10-05 20:02:51 +00:00
|
|
|
import Common.Annex
|
2011-06-02 01:56:04 +00:00
|
|
|
import Types.Remote
|
2014-02-11 18:06:50 +00:00
|
|
|
import Types.Creds
|
2011-06-30 17:16:57 +00:00
|
|
|
import qualified Git
|
2013-03-13 20:16:01 +00:00
|
|
|
import Config.Cost
|
2011-03-30 18:32:08 +00:00
|
|
|
import Config
|
2011-09-23 22:13:24 +00:00
|
|
|
import Utility.FileMode
|
2011-08-17 00:49:54 +00:00
|
|
|
import Remote.Helper.Special
|
2014-07-27 00:19:24 +00:00
|
|
|
import qualified Remote.Directory.LegacyChunked as Legacy
|
2012-04-20 20:24:44 +00:00
|
|
|
import Annex.Content
|
2013-09-07 22:38:00 +00:00
|
|
|
import Annex.UUID
|
2013-03-28 21:03:04 +00:00
|
|
|
import Utility.Metered
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2011-12-31 08:11:39 +00:00
|
|
|
remote :: RemoteType
|
2011-03-30 17:18:46 +00:00
|
|
|
remote = RemoteType {
|
|
|
|
typename = "directory",
|
2011-03-30 18:00:54 +00:00
|
|
|
enumerate = findSpecialRemotes "directory",
|
2011-03-30 17:18:46 +00:00
|
|
|
generate = gen,
|
2011-03-30 18:00:54 +00:00
|
|
|
setup = directorySetup
|
2011-03-30 17:18:46 +00:00
|
|
|
}
|
|
|
|
|
2013-09-12 19:54:35 +00:00
|
|
|
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
|
2013-01-01 17:52:47 +00:00
|
|
|
gen r u c gc = do
|
|
|
|
cst <- remoteCost gc cheapRemoteCost
|
2014-08-03 19:35:23 +00:00
|
|
|
let chunkconfig = getChunkConfig c
|
|
|
|
return $ Just $ specialRemote c
|
2014-07-27 00:19:24 +00:00
|
|
|
(prepareStore dir chunkconfig)
|
|
|
|
(retrieve dir chunkconfig)
|
2011-04-17 01:41:14 +00:00
|
|
|
Remote {
|
|
|
|
uuid = u,
|
|
|
|
cost = cst,
|
|
|
|
name = Git.repoDescribe r,
|
2014-07-27 00:19:24 +00:00
|
|
|
storeKey = storeKeyDummy,
|
|
|
|
retrieveKeyFile = retreiveKeyFileDummy,
|
|
|
|
retrieveKeyFileCheap = retrieveCheap dir chunkconfig,
|
2012-11-19 17:18:23 +00:00
|
|
|
removeKey = remove dir,
|
2014-07-27 00:19:24 +00:00
|
|
|
hasKey = checkPresent dir chunkconfig,
|
2011-04-17 01:41:14 +00:00
|
|
|
hasKeyCheap = True,
|
2012-02-14 07:49:48 +00:00
|
|
|
whereisKey = Nothing,
|
2013-10-11 20:03:18 +00:00
|
|
|
remoteFsck = Nothing,
|
2013-10-27 19:38:59 +00:00
|
|
|
repairRepo = Nothing,
|
2013-11-02 20:37:28 +00:00
|
|
|
config = c,
|
2011-12-31 07:27:37 +00:00
|
|
|
repo = r,
|
2013-01-01 17:52:47 +00:00
|
|
|
gitconfig = gc,
|
2012-08-26 18:26:43 +00:00
|
|
|
localpath = Just dir,
|
2012-08-26 19:39:02 +00:00
|
|
|
readonly = False,
|
2014-01-13 18:41:10 +00:00
|
|
|
availability = LocallyAvailable,
|
2011-12-31 07:27:37 +00:00
|
|
|
remotetype = remote
|
2011-04-17 01:41:14 +00:00
|
|
|
}
|
2013-01-01 17:52:47 +00:00
|
|
|
where
|
|
|
|
dir = fromMaybe (error "missing directory") $ remoteAnnexDirectory gc
|
2012-03-03 22:05:55 +00:00
|
|
|
|
2014-02-11 18:06:50 +00:00
|
|
|
directorySetup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> Annex (RemoteConfig, UUID)
|
|
|
|
directorySetup mu _ c = do
|
2013-09-07 22:38:00 +00:00
|
|
|
u <- maybe (liftIO genUUID) return mu
|
2011-03-30 17:18:46 +00:00
|
|
|
-- verify configuration is sane
|
2011-07-15 16:47:14 +00:00
|
|
|
let dir = fromMaybe (error "Specify directory=") $
|
2011-05-15 06:49:43 +00:00
|
|
|
M.lookup "directory" c
|
2013-05-06 21:15:36 +00:00
|
|
|
absdir <- liftIO $ absPath dir
|
|
|
|
liftIO $ unlessM (doesDirectoryExist absdir) $
|
|
|
|
error $ "Directory does not exist: " ++ absdir
|
2011-04-16 20:29:28 +00:00
|
|
|
c' <- encryptionSetup c
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2011-03-30 18:32:08 +00:00
|
|
|
-- The directory is stored in git config, not in this remote's
|
|
|
|
-- persistant state, so it can vary between hosts.
|
2013-05-06 21:15:36 +00:00
|
|
|
gitConfigSpecialRemote u c' "directory" absdir
|
2013-09-07 22:38:00 +00:00
|
|
|
return (M.delete "directory" c', u)
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2014-07-27 00:19:24 +00:00
|
|
|
{- Locations to try to access a given Key in the directory.
|
|
|
|
- We try more than one since we used to write to different hash
|
|
|
|
- directories. -}
|
2011-11-22 22:20:55 +00:00
|
|
|
locations :: FilePath -> Key -> [FilePath]
|
2011-12-02 18:56:48 +00:00
|
|
|
locations d k = map (d </>) (keyPaths k)
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2014-07-27 00:19:24 +00:00
|
|
|
{- Returns the location off a Key in the directory. If the key is
|
|
|
|
- present, returns the location that is actually used, otherwise
|
|
|
|
- returns the first, default location. -}
|
|
|
|
getLocation :: FilePath -> Key -> IO FilePath
|
|
|
|
getLocation d k = do
|
|
|
|
let locs = locations d k
|
|
|
|
fromMaybe (Prelude.head locs) <$> firstM doesFileExist locs
|
|
|
|
|
2012-11-19 17:18:23 +00:00
|
|
|
{- Directory where the file(s) for a key are stored. -}
|
|
|
|
storeDir :: FilePath -> Key -> FilePath
|
|
|
|
storeDir d k = addTrailingPathSeparator $ d </> hashDirLower k </> keyFile k
|
|
|
|
|
2014-07-27 00:19:24 +00:00
|
|
|
{- Where we store temporary data for a key, in the directory, as it's being
|
|
|
|
- written. -}
|
2012-11-19 17:18:23 +00:00
|
|
|
tmpDir :: FilePath -> Key -> FilePath
|
|
|
|
tmpDir d k = addTrailingPathSeparator $ d </> "tmp" </> keyFile k
|
|
|
|
|
2014-07-27 00:19:24 +00:00
|
|
|
{- Check if there is enough free disk space in the remote's directory to
|
|
|
|
- store the key. Note that the unencrypted key size is checked. -}
|
2014-07-27 04:30:04 +00:00
|
|
|
prepareStore :: FilePath -> ChunkConfig -> Preparer Storer
|
|
|
|
prepareStore d chunkconfig = checkPrepare
|
|
|
|
(\k -> checkDiskSpace (Just d) k 0)
|
2014-07-29 18:53:17 +00:00
|
|
|
(byteStorer $ store d chunkconfig)
|
2014-07-24 18:49:22 +00:00
|
|
|
|
2014-07-29 20:22:19 +00:00
|
|
|
store :: FilePath -> ChunkConfig -> Key -> L.ByteString -> MeterUpdate -> Annex Bool
|
|
|
|
store d chunkconfig k b p = liftIO $ do
|
2014-07-27 03:01:44 +00:00
|
|
|
void $ tryIO $ createDirectoryIfMissing True tmpdir
|
2014-07-25 20:21:01 +00:00
|
|
|
case chunkconfig of
|
2014-08-04 13:35:57 +00:00
|
|
|
LegacyChunks chunksize -> Legacy.store chunksize finalizeStoreGeneric k b p tmpdir destdir
|
2014-07-27 03:26:10 +00:00
|
|
|
_ -> do
|
2014-07-27 00:19:24 +00:00
|
|
|
let tmpf = tmpdir </> keyFile k
|
|
|
|
meteredWriteFile p tmpf b
|
2014-08-04 13:35:57 +00:00
|
|
|
finalizeStoreGeneric tmpdir destdir
|
2014-07-24 18:49:22 +00:00
|
|
|
return True
|
2014-07-25 20:21:01 +00:00
|
|
|
where
|
2014-07-27 00:19:24 +00:00
|
|
|
tmpdir = tmpDir d k
|
|
|
|
destdir = storeDir d k
|
2014-08-04 13:35:57 +00:00
|
|
|
|
|
|
|
{- Passed a temp directory that contains the files that should be placed
|
|
|
|
- in the dest directory, moves it into place. Anything already existing
|
|
|
|
- in the dest directory will be deleted. File permissions will be locked
|
|
|
|
- down. -}
|
|
|
|
finalizeStoreGeneric :: FilePath -> FilePath -> IO ()
|
|
|
|
finalizeStoreGeneric tmp dest = do
|
|
|
|
void $ tryIO $ allowWrite dest -- may already exist
|
|
|
|
void $ tryIO $ removeDirectoryRecursive dest -- or not exist
|
|
|
|
createDirectoryIfMissing True (parentDir dest)
|
|
|
|
renameDirectory tmp dest
|
|
|
|
-- may fail on some filesystems
|
|
|
|
void $ tryIO $ do
|
|
|
|
mapM_ preventWrite =<< dirContents dest
|
|
|
|
preventWrite dest
|
2012-03-03 22:05:55 +00:00
|
|
|
|
2014-07-27 04:30:04 +00:00
|
|
|
retrieve :: FilePath -> ChunkConfig -> Preparer Retriever
|
|
|
|
retrieve d (LegacyChunks _) = Legacy.retrieve locations d
|
2014-08-03 05:12:24 +00:00
|
|
|
retrieve d _ = simplyPrepare $ byteRetriever $ \k sink ->
|
|
|
|
sink =<< liftIO (L.readFile =<< getLocation d k)
|
2011-04-17 01:41:14 +00:00
|
|
|
|
2014-07-27 00:19:24 +00:00
|
|
|
retrieveCheap :: FilePath -> ChunkConfig -> Key -> FilePath -> Annex Bool
|
|
|
|
-- no cheap retrieval possible for chunks
|
|
|
|
retrieveCheap _ (UnpaddedChunks _) _ _ = return False
|
|
|
|
retrieveCheap _ (LegacyChunks _) _ _ = return False
|
2013-08-02 16:27:32 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2014-07-27 00:19:24 +00:00
|
|
|
retrieveCheap d NoChunks k f = liftIO $ catchBoolIO $ do
|
|
|
|
file <- getLocation d k
|
|
|
|
createSymbolicLink file f
|
|
|
|
return True
|
2013-05-11 20:03:00 +00:00
|
|
|
#else
|
2014-07-27 00:19:24 +00:00
|
|
|
retrieveCheap _ _ _ _ = return False
|
2013-05-11 20:03:00 +00:00
|
|
|
#endif
|
2012-03-03 22:05:55 +00:00
|
|
|
|
2012-11-19 17:18:23 +00:00
|
|
|
remove :: FilePath -> Key -> Annex Bool
|
2014-08-04 13:00:57 +00:00
|
|
|
remove d k = liftIO $ removeDirGeneric d (storeDir d k)
|
|
|
|
|
|
|
|
{- Removes the directory, which must be located under the topdir.
|
|
|
|
-
|
|
|
|
- Succeeds even on directories and contents that do not have write
|
|
|
|
- permission.
|
|
|
|
-
|
|
|
|
- If the directory does not exist, succeeds as long as the topdir does
|
|
|
|
- exist. If the topdir does not exist, fails, because in this case the
|
|
|
|
- remote is not currently accessible and probably still has the content
|
|
|
|
- we were supposed to remove from it.
|
|
|
|
-}
|
|
|
|
removeDirGeneric :: FilePath -> FilePath -> IO Bool
|
|
|
|
removeDirGeneric topdir dir = do
|
2013-02-14 18:10:36 +00:00
|
|
|
void $ tryIO $ allowWrite dir
|
2013-08-04 17:39:31 +00:00
|
|
|
#ifdef mingw32_HOST_OS
|
|
|
|
{- Windows needs the files inside the directory to be writable
|
|
|
|
- before it can delete them. -}
|
|
|
|
void $ tryIO $ mapM_ allowWrite =<< dirContents dir
|
|
|
|
#endif
|
2014-07-28 18:14:01 +00:00
|
|
|
ok <- catchBoolIO $ do
|
2013-02-14 18:10:36 +00:00
|
|
|
removeDirectoryRecursive dir
|
|
|
|
return True
|
2014-07-28 18:14:01 +00:00
|
|
|
if ok
|
|
|
|
then return ok
|
2014-08-04 13:00:57 +00:00
|
|
|
else doesDirectoryExist topdir <&&> (not <$> doesDirectoryExist dir)
|
2011-03-30 17:18:46 +00:00
|
|
|
|
2014-07-27 00:19:24 +00:00
|
|
|
checkPresent :: FilePath -> ChunkConfig -> Key -> Annex (Either String Bool)
|
|
|
|
checkPresent d (LegacyChunks _) k = Legacy.checkPresent d locations k
|
2014-07-27 02:52:47 +00:00
|
|
|
checkPresent d _ k = liftIO $ do
|
|
|
|
v <- catchMsgIO $ anyM doesFileExist (locations d k)
|
|
|
|
case v of
|
|
|
|
Right False -> ifM (doesDirectoryExist d)
|
|
|
|
( return v
|
|
|
|
, return $ Left $ "directory " ++ d ++ " is not accessible"
|
|
|
|
)
|
|
|
|
_ -> return v
|