2011-03-30 18:56:31 +00:00
|
|
|
|
{- A "remote" that is just a filesystem directory.
|
2011-03-30 17:18:46 +00:00
|
|
|
|
-
|
2012-03-03 22:05:55 +00:00
|
|
|
|
- Copyright 2011-2012 Joey Hess <joey@kitenet.net>
|
2011-03-30 17:18:46 +00:00
|
|
|
|
-
|
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
|
-}
|
|
|
|
|
|
|
|
|
|
module Remote.Directory (remote) where
|
|
|
|
|
|
2011-04-16 22:22:52 +00:00
|
|
|
|
import qualified Data.ByteString.Lazy.Char8 as L
|
2012-03-04 07:17:03 +00:00
|
|
|
|
import qualified Data.ByteString.Char8 as S
|
2011-03-30 17:18:46 +00:00
|
|
|
|
import qualified Data.Map as M
|
2012-04-20 20:24:44 +00:00
|
|
|
|
import qualified Control.Exception as E
|
2011-03-30 17:18:46 +00:00
|
|
|
|
|
2011-10-05 20:02:51 +00:00
|
|
|
|
import Common.Annex
|
2011-06-02 01:56:04 +00:00
|
|
|
|
import Types.Remote
|
2011-06-30 17:16:57 +00:00
|
|
|
|
import qualified Git
|
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
|
|
|
|
|
import Remote.Helper.Encryptable
|
2011-04-16 22:22:52 +00:00
|
|
|
|
import Crypto
|
2012-03-03 22:05:55 +00:00
|
|
|
|
import Utility.DataUnits
|
|
|
|
|
import Data.Int
|
2012-04-20 20:24:44 +00:00
|
|
|
|
import Annex.Content
|
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
|
|
|
|
}
|
|
|
|
|
|
2011-12-31 08:11:39 +00:00
|
|
|
|
gen :: Git.Repo -> UUID -> Maybe RemoteConfig -> Annex Remote
|
2011-04-16 22:22:52 +00:00
|
|
|
|
gen r u c = do
|
2012-03-22 03:41:01 +00:00
|
|
|
|
dir <- getRemoteConfig r "directory" (error "missing directory")
|
2011-03-30 19:15:46 +00:00
|
|
|
|
cst <- remoteCost r cheapRemoteCost
|
2012-03-03 22:05:55 +00:00
|
|
|
|
let chunksize = chunkSize c
|
2011-04-17 04:40:23 +00:00
|
|
|
|
return $ encryptableRemote c
|
2012-03-03 22:05:55 +00:00
|
|
|
|
(storeEncrypted dir chunksize)
|
|
|
|
|
(retrieveEncrypted dir chunksize)
|
2011-04-17 01:41:14 +00:00
|
|
|
|
Remote {
|
|
|
|
|
uuid = u,
|
|
|
|
|
cost = cst,
|
|
|
|
|
name = Git.repoDescribe r,
|
2012-03-03 22:05:55 +00:00
|
|
|
|
storeKey = store dir chunksize,
|
|
|
|
|
retrieveKeyFile = retrieve dir chunksize,
|
|
|
|
|
retrieveKeyFileCheap = retrieveCheap dir chunksize,
|
|
|
|
|
removeKey = remove dir chunksize,
|
|
|
|
|
hasKey = checkPresent dir chunksize,
|
2011-04-17 01:41:14 +00:00
|
|
|
|
hasKeyCheap = True,
|
2012-02-14 07:49:48 +00:00
|
|
|
|
whereisKey = Nothing,
|
2011-09-19 00:11:39 +00:00
|
|
|
|
config = Nothing,
|
2011-12-31 07:27:37 +00:00
|
|
|
|
repo = r,
|
|
|
|
|
remotetype = remote
|
2011-04-17 01:41:14 +00:00
|
|
|
|
}
|
2012-03-03 22:05:55 +00:00
|
|
|
|
where
|
|
|
|
|
|
|
|
|
|
type ChunkSize = Maybe Int64
|
|
|
|
|
|
|
|
|
|
chunkSize :: Maybe RemoteConfig -> ChunkSize
|
|
|
|
|
chunkSize Nothing = Nothing
|
|
|
|
|
chunkSize (Just m) =
|
|
|
|
|
case M.lookup "chunksize" m of
|
|
|
|
|
Nothing -> Nothing
|
|
|
|
|
Just v -> case readSize dataUnits v of
|
|
|
|
|
Nothing -> error "bad chunksize"
|
|
|
|
|
Just size
|
|
|
|
|
| size <= 0 -> error "bad chunksize"
|
|
|
|
|
| otherwise -> Just $ fromInteger size
|
2011-03-30 17:18:46 +00:00
|
|
|
|
|
2011-04-15 19:09:36 +00:00
|
|
|
|
directorySetup :: UUID -> RemoteConfig -> Annex RemoteConfig
|
2011-03-30 18:00:54 +00:00
|
|
|
|
directorySetup u c = do
|
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
|
2012-01-24 19:28:13 +00:00
|
|
|
|
liftIO $ unlessM (doesDirectoryExist dir) $
|
|
|
|
|
error $ "Directory does not exist: " ++ dir
|
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.
|
2011-04-16 20:29:28 +00:00
|
|
|
|
gitConfigSpecialRemote u c' "directory" dir
|
|
|
|
|
return $ M.delete "directory" c'
|
2011-03-30 17:18:46 +00:00
|
|
|
|
|
2011-11-29 03:20:31 +00:00
|
|
|
|
{- Locations to try to access a given Key in the Directory. -}
|
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
|
|
|
|
|
2012-03-03 22:05:55 +00:00
|
|
|
|
{- An infinite stream of chunks to use for a given file. -}
|
|
|
|
|
chunkStream :: FilePath -> [FilePath]
|
2012-03-04 00:02:48 +00:00
|
|
|
|
chunkStream f = map (\n -> f ++ ".chunk" ++ show n) [1 :: Integer ..]
|
2012-03-03 22:05:55 +00:00
|
|
|
|
|
|
|
|
|
{- A file that records the number of chunks used. -}
|
|
|
|
|
chunkCount :: FilePath -> FilePath
|
|
|
|
|
chunkCount f = f ++ ".chunkcount"
|
|
|
|
|
|
|
|
|
|
withCheckedFiles :: (FilePath -> IO Bool) -> ChunkSize -> FilePath -> Key -> ([FilePath] -> IO Bool) -> IO Bool
|
|
|
|
|
withCheckedFiles _ _ [] _ _ = return False
|
|
|
|
|
withCheckedFiles check Nothing d k a = go $ locations d k
|
2011-11-22 22:20:55 +00:00
|
|
|
|
where
|
|
|
|
|
go [] = return False
|
2012-03-16 00:39:25 +00:00
|
|
|
|
go (f:fs) = ifM (check f) ( a [f] , go fs )
|
2012-03-03 22:05:55 +00:00
|
|
|
|
withCheckedFiles check (Just _) d k a = go $ locations d k
|
|
|
|
|
where
|
|
|
|
|
go [] = return False
|
|
|
|
|
go (f:fs) = do
|
|
|
|
|
let chunkcount = chunkCount f
|
|
|
|
|
use <- check chunkcount
|
|
|
|
|
if use
|
|
|
|
|
then do
|
|
|
|
|
count <- readcount chunkcount
|
|
|
|
|
let chunks = take count $ chunkStream f
|
2012-03-16 00:39:25 +00:00
|
|
|
|
ifM (all id <$> mapM check chunks)
|
|
|
|
|
( a chunks , return False )
|
2012-03-03 22:05:55 +00:00
|
|
|
|
else go fs
|
|
|
|
|
readcount f = fromMaybe (error $ "cannot parse " ++ f)
|
|
|
|
|
. (readish :: String -> Maybe Int)
|
|
|
|
|
<$> readFile f
|
2011-11-22 22:20:55 +00:00
|
|
|
|
|
2012-03-03 22:05:55 +00:00
|
|
|
|
withStoredFiles :: ChunkSize -> FilePath -> Key -> ([FilePath] -> IO Bool) -> IO Bool
|
|
|
|
|
withStoredFiles = withCheckedFiles doesFileExist
|
2011-11-22 22:20:55 +00:00
|
|
|
|
|
2012-03-03 22:05:55 +00:00
|
|
|
|
store :: FilePath -> ChunkSize -> Key -> Annex Bool
|
|
|
|
|
store d chunksize k = do
|
2011-11-29 02:43:51 +00:00
|
|
|
|
src <- inRepo $ gitAnnexLocation k
|
2012-03-04 07:17:03 +00:00
|
|
|
|
metered k $ \meterupdate ->
|
2012-04-20 20:24:44 +00:00
|
|
|
|
storeHelper d chunksize k $ \dests ->
|
2012-03-03 22:05:55 +00:00
|
|
|
|
case chunksize of
|
|
|
|
|
Nothing -> do
|
|
|
|
|
let dest = Prelude.head dests
|
2012-03-04 07:17:03 +00:00
|
|
|
|
meteredWriteFile meterupdate dest
|
|
|
|
|
=<< L.readFile src
|
2012-03-03 22:05:55 +00:00
|
|
|
|
return [dest]
|
2012-03-04 07:17:03 +00:00
|
|
|
|
Just _ ->
|
|
|
|
|
storeSplit meterupdate chunksize dests
|
|
|
|
|
=<< L.readFile src
|
2012-03-03 22:05:55 +00:00
|
|
|
|
|
2012-03-04 07:17:03 +00:00
|
|
|
|
storeEncrypted :: FilePath -> ChunkSize -> (Cipher, Key) -> Key -> Annex Bool
|
|
|
|
|
storeEncrypted d chunksize (cipher, enck) k = do
|
|
|
|
|
src <- inRepo $ gitAnnexLocation k
|
|
|
|
|
metered k $ \meterupdate ->
|
2012-04-20 20:24:44 +00:00
|
|
|
|
storeHelper d chunksize enck $ \dests ->
|
2012-03-04 07:17:03 +00:00
|
|
|
|
withEncryptedContent cipher (L.readFile src) $ \s ->
|
|
|
|
|
case chunksize of
|
|
|
|
|
Nothing -> do
|
|
|
|
|
let dest = Prelude.head dests
|
|
|
|
|
meteredWriteFile meterupdate dest s
|
|
|
|
|
return [dest]
|
|
|
|
|
Just _ -> storeSplit meterupdate chunksize dests s
|
|
|
|
|
|
|
|
|
|
{- Splits a ByteString into chunks and writes to dests, obeying configured
|
|
|
|
|
- chunk size (not to be confused with the L.ByteString chunk size).
|
2012-03-03 22:05:55 +00:00
|
|
|
|
- Note: Must always write at least one file, even for empty ByteString. -}
|
2012-03-04 07:17:03 +00:00
|
|
|
|
storeSplit :: MeterUpdate -> ChunkSize -> [FilePath] -> L.ByteString -> IO [FilePath]
|
|
|
|
|
storeSplit _ Nothing _ _ = error "bad storeSplit call"
|
|
|
|
|
storeSplit _ _ [] _ = error "bad storeSplit call"
|
|
|
|
|
storeSplit meterupdate (Just chunksize) alldests@(firstdest:_) b
|
|
|
|
|
| L.null b = do
|
2012-03-03 22:05:55 +00:00
|
|
|
|
-- must always write at least one file, even for empty
|
2012-03-04 07:17:03 +00:00
|
|
|
|
L.writeFile firstdest b
|
2012-03-03 22:05:55 +00:00
|
|
|
|
return [firstdest]
|
2012-03-04 07:17:03 +00:00
|
|
|
|
| otherwise = storeSplit' meterupdate chunksize alldests (L.toChunks b) []
|
|
|
|
|
storeSplit' :: MeterUpdate -> Int64 -> [FilePath] -> [S.ByteString] -> [FilePath] -> IO [FilePath]
|
|
|
|
|
storeSplit' _ _ [] _ _ = error "ran out of dests"
|
|
|
|
|
storeSplit' _ _ _ [] c = return $ reverse c
|
|
|
|
|
storeSplit' meterupdate chunksize (d:dests) bs c = do
|
2012-04-20 20:24:44 +00:00
|
|
|
|
bs' <- E.bracket (openFile d WriteMode) hClose (feed chunksize bs)
|
2012-03-04 07:17:03 +00:00
|
|
|
|
storeSplit' meterupdate chunksize dests bs' (d:c)
|
|
|
|
|
where
|
|
|
|
|
feed _ [] _ = return []
|
|
|
|
|
feed sz (l:ls) h = do
|
|
|
|
|
let s = fromIntegral $ S.length l
|
|
|
|
|
if s <= sz
|
|
|
|
|
then do
|
|
|
|
|
S.hPut h l
|
|
|
|
|
meterupdate $ toInteger s
|
|
|
|
|
feed (sz - s) ls h
|
|
|
|
|
else return (l:ls)
|
|
|
|
|
|
|
|
|
|
{- Write a L.ByteString to a file, updating a progress meter
|
|
|
|
|
- after each chunk of the L.ByteString, typically every 64 kb or so. -}
|
|
|
|
|
meteredWriteFile :: MeterUpdate -> FilePath -> L.ByteString -> IO ()
|
|
|
|
|
meteredWriteFile meterupdate dest b =
|
2012-03-04 15:48:23 +00:00
|
|
|
|
meteredWriteFile' meterupdate dest (L.toChunks b) feeder
|
2012-03-04 07:17:03 +00:00
|
|
|
|
where
|
2012-03-04 15:48:23 +00:00
|
|
|
|
feeder chunks = return ([], chunks)
|
|
|
|
|
|
|
|
|
|
{- Writes a series of S.ByteString chunks to a file, updating a progress
|
|
|
|
|
- meter after each chunk. The feeder is called to get more chunks. -}
|
|
|
|
|
meteredWriteFile' :: MeterUpdate -> FilePath -> s -> (s -> IO (s, [S.ByteString])) -> IO ()
|
|
|
|
|
meteredWriteFile' meterupdate dest startstate feeder =
|
2012-04-20 20:24:44 +00:00
|
|
|
|
E.bracket (openFile dest WriteMode) hClose (feed startstate [])
|
2012-03-04 15:48:23 +00:00
|
|
|
|
where
|
|
|
|
|
feed state [] h = do
|
|
|
|
|
(state', cs) <- feeder state
|
2012-04-22 03:32:33 +00:00
|
|
|
|
unless (null cs) $
|
|
|
|
|
feed state' cs h
|
2012-03-04 15:48:23 +00:00
|
|
|
|
feed state (c:cs) h = do
|
|
|
|
|
S.hPut h c
|
|
|
|
|
meterupdate $ toInteger $ S.length c
|
|
|
|
|
feed state cs h
|
2012-03-03 22:05:55 +00:00
|
|
|
|
|
|
|
|
|
{- Generates a list of destinations to write to in order to store a key.
|
|
|
|
|
- When chunksize is specified, this list will be a list of chunks.
|
|
|
|
|
- The action should store the file, and return a list of the destinations
|
|
|
|
|
- it stored it to, or [] on error.
|
|
|
|
|
- The stored files are only put into their final place once storage is
|
|
|
|
|
- complete.
|
|
|
|
|
-}
|
2012-04-20 20:24:44 +00:00
|
|
|
|
storeHelper :: FilePath -> ChunkSize -> Key -> ([FilePath] -> IO [FilePath]) -> Annex Bool
|
|
|
|
|
storeHelper d chunksize key a = prep <&&> check <&&> go
|
2012-03-03 22:05:55 +00:00
|
|
|
|
where
|
|
|
|
|
desttemplate = Prelude.head $ locations d key
|
2012-04-20 20:24:44 +00:00
|
|
|
|
dir = parentDir desttemplate
|
2012-03-03 22:05:55 +00:00
|
|
|
|
tmpdests = case chunksize of
|
|
|
|
|
Nothing -> [desttemplate ++ tmpprefix]
|
|
|
|
|
Just _ -> map (++ tmpprefix) (chunkStream desttemplate)
|
|
|
|
|
tmpprefix = ".tmp"
|
|
|
|
|
detmpprefix f = take (length f - tmpprefixlen) f
|
|
|
|
|
tmpprefixlen = length tmpprefix
|
2012-04-20 20:24:44 +00:00
|
|
|
|
prep = liftIO $ catchBoolIO $ do
|
|
|
|
|
createDirectoryIfMissing True dir
|
|
|
|
|
allowWrite dir
|
|
|
|
|
return True
|
|
|
|
|
{- The size is not exactly known when encrypting the key;
|
|
|
|
|
- this assumes that at least the size of the key is
|
|
|
|
|
- needed as free space. -}
|
|
|
|
|
check = checkDiskSpace (Just dir) key 0
|
|
|
|
|
go = liftIO $ catchBoolIO $ do
|
|
|
|
|
stored <- a tmpdests
|
|
|
|
|
forM_ stored $ \f -> do
|
|
|
|
|
let dest = detmpprefix f
|
|
|
|
|
renameFile f dest
|
|
|
|
|
preventWrite dest
|
|
|
|
|
when (chunksize /= Nothing) $ do
|
|
|
|
|
let chunkcount = chunkCount desttemplate
|
|
|
|
|
_ <- tryIO $ allowWrite chunkcount
|
|
|
|
|
writeFile chunkcount (show $ length stored)
|
|
|
|
|
preventWrite chunkcount
|
|
|
|
|
preventWrite dir
|
|
|
|
|
return (not $ null stored)
|
2012-03-03 22:05:55 +00:00
|
|
|
|
|
|
|
|
|
retrieve :: FilePath -> ChunkSize -> Key -> FilePath -> Annex Bool
|
2012-03-04 07:25:41 +00:00
|
|
|
|
retrieve d chunksize k f = metered k $ \meterupdate ->
|
|
|
|
|
liftIO $ withStoredFiles chunksize d k $ \files ->
|
|
|
|
|
catchBoolIO $ do
|
2012-03-04 15:48:23 +00:00
|
|
|
|
meteredWriteFile' meterupdate f files feeder
|
2012-03-03 22:05:55 +00:00
|
|
|
|
return True
|
2012-03-04 15:48:23 +00:00
|
|
|
|
where
|
|
|
|
|
feeder [] = return ([], [])
|
|
|
|
|
feeder (x:xs) = do
|
|
|
|
|
chunks <- L.toChunks <$> L.readFile x
|
|
|
|
|
return (xs, chunks)
|
2011-04-17 01:41:14 +00:00
|
|
|
|
|
2012-03-04 07:36:39 +00:00
|
|
|
|
retrieveEncrypted :: FilePath -> ChunkSize -> (Cipher, Key) -> Key -> FilePath -> Annex Bool
|
|
|
|
|
retrieveEncrypted d chunksize (cipher, enck) k f = metered k $ \meterupdate ->
|
|
|
|
|
liftIO $ withStoredFiles chunksize d enck $ \files ->
|
|
|
|
|
catchBoolIO $ do
|
|
|
|
|
withDecryptedContent cipher (L.concat <$> mapM L.readFile files) $
|
|
|
|
|
meteredWriteFile meterupdate f
|
|
|
|
|
return True
|
2011-03-30 17:18:46 +00:00
|
|
|
|
|
2012-03-03 22:05:55 +00:00
|
|
|
|
retrieveCheap :: FilePath -> ChunkSize -> Key -> FilePath -> Annex Bool
|
|
|
|
|
retrieveCheap _ (Just _) _ _ = return False -- no cheap retrieval for chunks
|
|
|
|
|
retrieveCheap d _ k f = liftIO $ withStoredFiles Nothing d k go
|
|
|
|
|
where
|
|
|
|
|
go [file] = catchBoolIO $ createSymbolicLink file f >> return True
|
|
|
|
|
go _files = return False
|
|
|
|
|
|
|
|
|
|
remove :: FilePath -> ChunkSize -> Key -> Annex Bool
|
|
|
|
|
remove d chunksize k = liftIO $ withStoredFiles chunksize d k go
|
|
|
|
|
where
|
|
|
|
|
go files = all id <$> mapM removefile files
|
|
|
|
|
removefile file = catchBoolIO $ do
|
|
|
|
|
let dir = parentDir file
|
|
|
|
|
allowWrite dir
|
|
|
|
|
removeFile file
|
|
|
|
|
_ <- tryIO $ removeDirectory dir
|
|
|
|
|
return True
|
2011-03-30 17:18:46 +00:00
|
|
|
|
|
2012-03-03 22:05:55 +00:00
|
|
|
|
checkPresent :: FilePath -> ChunkSize -> Key -> Annex (Either String Bool)
|
|
|
|
|
checkPresent d chunksize k = liftIO $ catchMsgIO $ withStoredFiles chunksize d k $
|
|
|
|
|
const $ return True -- withStoredFiles checked that it exists
|