2011-03-30 14:56:31 -04:00
|
|
|
|
{- A "remote" that is just a filesystem directory.
|
2011-03-30 13:18:46 -04:00
|
|
|
|
-
|
2012-03-03 18:05:55 -04:00
|
|
|
|
- Copyright 2011-2012 Joey Hess <joey@kitenet.net>
|
2011-03-30 13:18:46 -04:00
|
|
|
|
-
|
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
|
-}
|
|
|
|
|
|
2013-05-11 15:03:00 -05:00
|
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
|
2011-03-30 13:18:46 -04:00
|
|
|
|
module Remote.Directory (remote) where
|
|
|
|
|
|
2012-06-20 13:13:40 -04:00
|
|
|
|
import qualified Data.ByteString.Lazy as L
|
|
|
|
|
import qualified Data.ByteString as S
|
2011-03-30 13:18:46 -04:00
|
|
|
|
import qualified Data.Map as M
|
|
|
|
|
|
2011-10-05 16:02:51 -04:00
|
|
|
|
import Common.Annex
|
2011-06-01 21:56:04 -04:00
|
|
|
|
import Types.Remote
|
2014-02-11 14:06:50 -04:00
|
|
|
|
import Types.Creds
|
2011-06-30 13:16:57 -04:00
|
|
|
|
import qualified Git
|
2013-03-13 16:16:01 -04:00
|
|
|
|
import Config.Cost
|
2011-03-30 14:32:08 -04:00
|
|
|
|
import Config
|
2011-09-23 18:13:24 -04:00
|
|
|
|
import Utility.FileMode
|
2011-08-16 20:49:54 -04:00
|
|
|
|
import Remote.Helper.Special
|
|
|
|
|
import Remote.Helper.Encryptable
|
2012-11-16 17:58:08 -04:00
|
|
|
|
import Remote.Helper.Chunked
|
2014-07-24 14:49:22 -04:00
|
|
|
|
import qualified Remote.Helper.Chunked.Legacy as Legacy
|
2011-04-16 18:22:52 -04:00
|
|
|
|
import Crypto
|
2012-04-20 16:24:44 -04:00
|
|
|
|
import Annex.Content
|
2013-09-07 18:38:00 -04:00
|
|
|
|
import Annex.UUID
|
2013-03-28 17:03:04 -04:00
|
|
|
|
import Utility.Metered
|
2011-03-30 13:18:46 -04:00
|
|
|
|
|
2011-12-31 04:11:39 -04:00
|
|
|
|
remote :: RemoteType
|
2011-03-30 13:18:46 -04:00
|
|
|
|
remote = RemoteType {
|
|
|
|
|
typename = "directory",
|
2011-03-30 14:00:54 -04:00
|
|
|
|
enumerate = findSpecialRemotes "directory",
|
2011-03-30 13:18:46 -04:00
|
|
|
|
generate = gen,
|
2011-03-30 14:00:54 -04:00
|
|
|
|
setup = directorySetup
|
2011-03-30 13:18:46 -04:00
|
|
|
|
}
|
|
|
|
|
|
2013-09-12 15:54:35 -04:00
|
|
|
|
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
|
2013-01-01 13:52:47 -04:00
|
|
|
|
gen r u c gc = do
|
|
|
|
|
cst <- remoteCost gc cheapRemoteCost
|
2014-07-24 14:49:22 -04:00
|
|
|
|
let chunkconfig = chunkConfig c
|
2013-09-12 15:54:35 -04:00
|
|
|
|
return $ Just $ encryptableRemote c
|
2014-07-24 14:49:22 -04:00
|
|
|
|
(storeEncrypted dir (getGpgEncParams (c,gc)) chunkconfig)
|
2014-07-25 16:21:01 -04:00
|
|
|
|
(retrieveEncrypted u dir chunkconfig)
|
2011-04-16 21:41:14 -04:00
|
|
|
|
Remote {
|
|
|
|
|
uuid = u,
|
|
|
|
|
cost = cst,
|
|
|
|
|
name = Git.repoDescribe r,
|
2014-07-25 16:21:01 -04:00
|
|
|
|
storeKey = store u dir chunkconfig,
|
|
|
|
|
retrieveKeyFile = retrieve u dir chunkconfig,
|
|
|
|
|
retrieveKeyFileCheap = retrieveCheap u dir chunkconfig,
|
2012-11-19 13:18:23 -04:00
|
|
|
|
removeKey = remove dir,
|
2014-07-25 16:21:01 -04:00
|
|
|
|
hasKey = checkPresent u dir chunkconfig,
|
2011-04-16 21:41:14 -04:00
|
|
|
|
hasKeyCheap = True,
|
2012-02-14 03:49:48 -04:00
|
|
|
|
whereisKey = Nothing,
|
2013-10-11 16:03:18 -04:00
|
|
|
|
remoteFsck = Nothing,
|
2013-10-27 15:38:59 -04:00
|
|
|
|
repairRepo = Nothing,
|
2013-11-02 16:37:28 -04:00
|
|
|
|
config = c,
|
2011-12-31 03:27:37 -04:00
|
|
|
|
repo = r,
|
2013-01-01 13:52:47 -04:00
|
|
|
|
gitconfig = gc,
|
2012-08-26 14:26:43 -04:00
|
|
|
|
localpath = Just dir,
|
2012-08-26 15:39:02 -04:00
|
|
|
|
readonly = False,
|
2014-01-13 14:41:10 -04:00
|
|
|
|
availability = LocallyAvailable,
|
2011-12-31 03:27:37 -04:00
|
|
|
|
remotetype = remote
|
2011-04-16 21:41:14 -04:00
|
|
|
|
}
|
2013-01-01 13:52:47 -04:00
|
|
|
|
where
|
|
|
|
|
dir = fromMaybe (error "missing directory") $ remoteAnnexDirectory gc
|
2012-03-03 18:05:55 -04:00
|
|
|
|
|
2014-02-11 14:06:50 -04:00
|
|
|
|
directorySetup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> Annex (RemoteConfig, UUID)
|
|
|
|
|
directorySetup mu _ c = do
|
2013-09-07 18:38:00 -04:00
|
|
|
|
u <- maybe (liftIO genUUID) return mu
|
2011-03-30 13:18:46 -04:00
|
|
|
|
-- verify configuration is sane
|
2011-07-15 12:47:14 -04:00
|
|
|
|
let dir = fromMaybe (error "Specify directory=") $
|
2011-05-15 02:49:43 -04:00
|
|
|
|
M.lookup "directory" c
|
2013-05-06 17:15:36 -04:00
|
|
|
|
absdir <- liftIO $ absPath dir
|
|
|
|
|
liftIO $ unlessM (doesDirectoryExist absdir) $
|
|
|
|
|
error $ "Directory does not exist: " ++ absdir
|
2011-04-16 16:29:28 -04:00
|
|
|
|
c' <- encryptionSetup c
|
2011-03-30 13:18:46 -04:00
|
|
|
|
|
2011-03-30 14:32:08 -04:00
|
|
|
|
-- The directory is stored in git config, not in this remote's
|
|
|
|
|
-- persistant state, so it can vary between hosts.
|
2013-05-06 17:15:36 -04:00
|
|
|
|
gitConfigSpecialRemote u c' "directory" absdir
|
2013-09-07 18:38:00 -04:00
|
|
|
|
return (M.delete "directory" c', u)
|
2011-03-30 13:18:46 -04:00
|
|
|
|
|
2012-11-19 13:18:23 -04:00
|
|
|
|
{- Locations to try to access a given Key in the Directory.
|
|
|
|
|
- We try more than since we used to write to different hash directories. -}
|
2011-11-22 18:20:55 -04:00
|
|
|
|
locations :: FilePath -> Key -> [FilePath]
|
2011-12-02 14:56:48 -04:00
|
|
|
|
locations d k = map (d </>) (keyPaths k)
|
2011-03-30 13:18:46 -04:00
|
|
|
|
|
2012-11-19 13:18:23 -04:00
|
|
|
|
{- Directory where the file(s) for a key are stored. -}
|
|
|
|
|
storeDir :: FilePath -> Key -> FilePath
|
|
|
|
|
storeDir d k = addTrailingPathSeparator $ d </> hashDirLower k </> keyFile k
|
|
|
|
|
|
|
|
|
|
{- Where we store temporary data for a key as it's being uploaded. -}
|
|
|
|
|
tmpDir :: FilePath -> Key -> FilePath
|
|
|
|
|
tmpDir d k = addTrailingPathSeparator $ d </> "tmp" </> keyFile k
|
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
withCheckedFiles :: (FilePath -> IO Bool) -> UUID -> ChunkConfig -> FilePath -> Key -> ([FilePath] -> IO Bool) -> IO Bool
|
|
|
|
|
withCheckedFiles _ _ _ [] _ _ = return False
|
|
|
|
|
withCheckedFiles check _ (LegacyChunks _) d k a = go $ locations d k
|
2012-11-11 00:51:07 -04:00
|
|
|
|
where
|
|
|
|
|
go [] = return False
|
|
|
|
|
go (f:fs) = do
|
2014-07-24 14:49:22 -04:00
|
|
|
|
let chunkcount = f ++ Legacy.chunkCount
|
2012-11-11 00:51:07 -04:00
|
|
|
|
ifM (check chunkcount)
|
|
|
|
|
( do
|
2014-07-24 14:49:22 -04:00
|
|
|
|
chunks <- Legacy.listChunks f <$> readFile chunkcount
|
2013-10-26 15:03:12 -04:00
|
|
|
|
ifM (allM check chunks)
|
2012-11-11 00:51:07 -04:00
|
|
|
|
( a chunks , return False )
|
2013-10-26 15:03:12 -04:00
|
|
|
|
, do
|
2014-07-24 14:49:22 -04:00
|
|
|
|
chunks <- Legacy.probeChunks f check
|
2013-10-26 15:03:12 -04:00
|
|
|
|
if null chunks
|
|
|
|
|
then go fs
|
|
|
|
|
else a chunks
|
2012-11-11 00:51:07 -04:00
|
|
|
|
)
|
2014-07-25 16:21:01 -04:00
|
|
|
|
withCheckedFiles check u chunkconfig d k a =
|
|
|
|
|
go $ locations d k
|
2014-07-24 14:49:22 -04:00
|
|
|
|
where
|
|
|
|
|
go [] = return False
|
|
|
|
|
go (f:fs) = ifM (check f) ( a [f] , go fs )
|
2011-11-22 18:20:55 -04:00
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
withStoredFiles :: UUID -> ChunkConfig -> FilePath -> Key -> ([FilePath] -> IO Bool) -> IO Bool
|
2012-03-03 18:05:55 -04:00
|
|
|
|
withStoredFiles = withCheckedFiles doesFileExist
|
2011-11-22 18:20:55 -04:00
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
store :: UUID -> FilePath -> ChunkConfig -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool
|
|
|
|
|
store u d chunkconfig k _f p = whenDiskAvail d k $
|
|
|
|
|
sendAnnex k (void $ remove d k) $ \src ->
|
|
|
|
|
storeChunks u chunkconfig k src p $ \k' b meterupdate ->
|
|
|
|
|
storeHelper d chunkconfig k' $ \dests ->
|
2014-07-24 14:49:22 -04:00
|
|
|
|
case chunkconfig of
|
2014-07-24 15:08:07 -04:00
|
|
|
|
LegacyChunks chunksize ->
|
2014-07-24 14:49:22 -04:00
|
|
|
|
storeLegacyChunked meterupdate chunksize dests b
|
|
|
|
|
_ -> do
|
2012-03-04 03:17:03 -04:00
|
|
|
|
let dest = Prelude.head dests
|
2012-11-18 15:27:44 -04:00
|
|
|
|
meteredWriteFile meterupdate dest b
|
2012-03-04 03:17:03 -04:00
|
|
|
|
return [dest]
|
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
storeEncrypted :: FilePath -> [CommandParam] -> ChunkConfig -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool
|
|
|
|
|
storeEncrypted d gpgOpts chunkconfig (cipher, enck) k p = whenDiskAvail d k $
|
|
|
|
|
sendAnnex k (void $ remove d enck) $ \src ->
|
|
|
|
|
metered (Just p) k $ \meterupdate ->
|
|
|
|
|
storeHelper d chunkconfig enck $ \dests ->
|
|
|
|
|
encrypt gpgOpts cipher (feedFile src) $ readBytes $ \b ->
|
|
|
|
|
case chunkconfig of
|
|
|
|
|
LegacyChunks chunksize ->
|
|
|
|
|
storeLegacyChunked meterupdate chunksize dests b
|
|
|
|
|
_ -> do
|
|
|
|
|
let dest = Prelude.head dests
|
|
|
|
|
meteredWriteFile meterupdate dest b
|
|
|
|
|
return [dest]
|
|
|
|
|
|
2012-03-04 03:17:03 -04:00
|
|
|
|
{- Splits a ByteString into chunks and writes to dests, obeying configured
|
2014-07-25 16:21:01 -04:00
|
|
|
|
- chunk size (not to be confused with the L.ByteString chunk size). -}
|
2014-07-24 15:08:07 -04:00
|
|
|
|
storeLegacyChunked :: MeterUpdate -> ChunkSize -> [FilePath] -> L.ByteString -> IO [FilePath]
|
2014-07-24 14:49:22 -04:00
|
|
|
|
storeLegacyChunked _ _ [] _ = error "bad storeLegacyChunked call"
|
|
|
|
|
storeLegacyChunked meterupdate chunksize alldests@(firstdest:_) b
|
2012-03-04 03:17:03 -04:00
|
|
|
|
| L.null b = do
|
2014-07-25 16:21:01 -04:00
|
|
|
|
-- always write at least one file, even for empty
|
2012-03-04 03:17:03 -04:00
|
|
|
|
L.writeFile firstdest b
|
2012-03-03 18:05:55 -04:00
|
|
|
|
return [firstdest]
|
2014-07-24 14:49:22 -04:00
|
|
|
|
| otherwise = storeLegacyChunked' meterupdate chunksize alldests (L.toChunks b) []
|
2014-07-24 15:08:07 -04:00
|
|
|
|
storeLegacyChunked' :: MeterUpdate -> ChunkSize -> [FilePath] -> [S.ByteString] -> [FilePath] -> IO [FilePath]
|
2014-07-24 14:49:22 -04:00
|
|
|
|
storeLegacyChunked' _ _ [] _ _ = error "ran out of dests"
|
|
|
|
|
storeLegacyChunked' _ _ _ [] c = return $ reverse c
|
|
|
|
|
storeLegacyChunked' meterupdate chunksize (d:dests) bs c = do
|
2013-09-25 23:19:01 -04:00
|
|
|
|
bs' <- withFile d WriteMode $
|
2013-03-28 17:03:04 -04:00
|
|
|
|
feed zeroBytesProcessed chunksize bs
|
2014-07-24 14:49:22 -04:00
|
|
|
|
storeLegacyChunked' meterupdate chunksize dests bs' (d:c)
|
2012-11-11 00:51:07 -04:00
|
|
|
|
where
|
2013-03-28 17:03:04 -04:00
|
|
|
|
feed _ _ [] _ = return []
|
|
|
|
|
feed bytes sz (l:ls) h = do
|
|
|
|
|
let len = S.length l
|
|
|
|
|
let s = fromIntegral len
|
2012-11-19 13:30:58 -04:00
|
|
|
|
if s <= sz || sz == chunksize
|
2012-11-11 00:51:07 -04:00
|
|
|
|
then do
|
|
|
|
|
S.hPut h l
|
2013-03-28 17:03:04 -04:00
|
|
|
|
let bytes' = addBytesProcessed bytes len
|
|
|
|
|
meterupdate bytes'
|
|
|
|
|
feed bytes' (sz - s) ls h
|
2012-11-11 00:51:07 -04:00
|
|
|
|
else return (l:ls)
|
2012-03-04 03:17:03 -04:00
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
{- An encrypted key does not have a known size, so the unencrypted
|
|
|
|
|
- key should always be passed. -}
|
|
|
|
|
whenDiskAvail :: FilePath -> Key -> Annex Bool -> Annex Bool
|
|
|
|
|
whenDiskAvail d k a = checkDiskSpace (Just d) k 0 <&&> a
|
2014-07-24 14:49:22 -04:00
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
storeHelper :: FilePath -> ChunkConfig -> Key -> ([FilePath] -> IO [FilePath]) -> Annex Bool
|
|
|
|
|
storeHelper d chunkconfig key storer = liftIO $ do
|
|
|
|
|
void $ liftIO $ tryIO $ createDirectoryIfMissing True tmpdir
|
|
|
|
|
case chunkconfig of
|
|
|
|
|
LegacyChunks _ -> Legacy.storeChunks key tmpdir destdir storer recorder finalizer
|
|
|
|
|
_ -> flip catchNonAsync (\e -> print e >> return False) $ do
|
2014-07-24 14:49:22 -04:00
|
|
|
|
let tmpf = tmpdir </> keyFile key
|
|
|
|
|
void $ storer [tmpf]
|
|
|
|
|
finalizer tmpdir destdir
|
|
|
|
|
return True
|
2014-07-25 16:21:01 -04:00
|
|
|
|
where
|
|
|
|
|
tmpdir = tmpDir d key
|
|
|
|
|
destdir = storeDir d key
|
|
|
|
|
|
2012-11-19 13:18:23 -04:00
|
|
|
|
finalizer tmp dest = do
|
|
|
|
|
void $ tryIO $ allowWrite dest -- may already exist
|
|
|
|
|
void $ tryIO $ removeDirectoryRecursive dest -- or not exist
|
|
|
|
|
createDirectoryIfMissing True (parentDir dest)
|
|
|
|
|
renameDirectory tmp dest
|
2013-02-14 14:10:36 -04:00
|
|
|
|
-- may fail on some filesystems
|
|
|
|
|
void $ tryIO $ do
|
|
|
|
|
mapM_ preventWrite =<< dirContents dest
|
|
|
|
|
preventWrite dest
|
2014-07-24 14:49:22 -04:00
|
|
|
|
|
2012-11-16 17:58:08 -04:00
|
|
|
|
recorder f s = do
|
|
|
|
|
void $ tryIO $ allowWrite f
|
|
|
|
|
writeFile f s
|
2013-02-14 14:10:36 -04:00
|
|
|
|
void $ tryIO $ preventWrite f
|
2012-03-03 18:05:55 -04:00
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
retrieve :: UUID -> FilePath -> ChunkConfig -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
|
|
|
|
|
retrieve u d chunkconfig k _ f p = metered (Just p) k $ \meterupdate ->
|
|
|
|
|
liftIO $ withStoredFiles u chunkconfig d k $ \files ->
|
2012-03-04 03:25:41 -04:00
|
|
|
|
catchBoolIO $ do
|
2014-07-24 16:42:35 -04:00
|
|
|
|
meteredWriteFileChunks meterupdate f files L.readFile
|
2012-03-03 18:05:55 -04:00
|
|
|
|
return True
|
2011-04-16 21:41:14 -04:00
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
retrieveEncrypted :: UUID -> FilePath -> ChunkConfig -> (Cipher, Key) -> Key -> FilePath -> MeterUpdate -> Annex Bool
|
|
|
|
|
retrieveEncrypted u d chunkconfig (cipher, enck) k f p = metered (Just p) k $ \meterupdate ->
|
|
|
|
|
liftIO $ withStoredFiles u chunkconfig d enck $ \files ->
|
2012-03-04 03:36:39 -04:00
|
|
|
|
catchBoolIO $ do
|
2012-11-18 15:27:44 -04:00
|
|
|
|
decrypt cipher (feeder files) $
|
|
|
|
|
readBytes $ meteredWriteFile meterupdate f
|
2012-03-04 03:36:39 -04:00
|
|
|
|
return True
|
2012-11-18 15:27:44 -04:00
|
|
|
|
where
|
2013-09-25 23:19:01 -04:00
|
|
|
|
feeder files h = forM_ files $ L.hPut h <=< L.readFile
|
2011-03-30 13:18:46 -04:00
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
retrieveCheap :: UUID -> FilePath -> ChunkConfig -> Key -> FilePath -> Annex Bool
|
2014-07-24 14:49:22 -04:00
|
|
|
|
-- no cheap retrieval for chunks
|
2014-07-25 16:21:01 -04:00
|
|
|
|
retrieveCheap _ _ (UnpaddedChunks _) _ _ = return False
|
|
|
|
|
retrieveCheap _ _ (LegacyChunks _) _ _ = return False
|
2013-08-02 12:27:32 -04:00
|
|
|
|
#ifndef mingw32_HOST_OS
|
2014-07-25 16:21:01 -04:00
|
|
|
|
retrieveCheap u d ck k f = liftIO $ withStoredFiles u ck d k go
|
2012-11-11 00:51:07 -04:00
|
|
|
|
where
|
2014-07-25 16:21:01 -04:00
|
|
|
|
go [file] = catchBoolIO $
|
|
|
|
|
createSymbolicLink file f >> return True
|
2012-11-11 00:51:07 -04:00
|
|
|
|
go _files = return False
|
2013-05-11 15:03:00 -05:00
|
|
|
|
#else
|
2014-07-25 16:21:01 -04:00
|
|
|
|
retrieveCheap _ _ _ _ _ = return False
|
2013-05-11 15:03:00 -05:00
|
|
|
|
#endif
|
2012-03-03 18:05:55 -04:00
|
|
|
|
|
2012-11-19 13:18:23 -04:00
|
|
|
|
remove :: FilePath -> Key -> Annex Bool
|
2013-02-14 14:10:36 -04:00
|
|
|
|
remove d k = liftIO $ do
|
|
|
|
|
void $ tryIO $ allowWrite dir
|
2013-08-04 13:39:31 -04: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
|
2013-02-14 14:10:36 -04:00
|
|
|
|
catchBoolIO $ do
|
|
|
|
|
removeDirectoryRecursive dir
|
|
|
|
|
return True
|
2012-11-11 00:51:07 -04:00
|
|
|
|
where
|
2012-11-19 13:18:23 -04:00
|
|
|
|
dir = storeDir d k
|
2011-03-30 13:18:46 -04:00
|
|
|
|
|
2014-07-25 16:21:01 -04:00
|
|
|
|
checkPresent :: UUID -> FilePath -> ChunkConfig -> Key -> Annex (Either String Bool)
|
|
|
|
|
checkPresent u d chunkconfig k = liftIO $ catchMsgIO $ withStoredFiles u chunkconfig d k $
|
2012-03-03 18:05:55 -04:00
|
|
|
|
const $ return True -- withStoredFiles checked that it exists
|