git-annex/Remote/Directory.hs

266 lines
9.1 KiB
Haskell
Raw Normal View History

{- A "remote" that is just a filesystem directory.
2011-03-30 13:18:46 -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.
-}
{-# LANGUAGE CPP #-}
2011-03-30 13:18:46 -04:00
module Remote.Directory (remote) where
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
import Types.Remote
import Types.Creds
import qualified Git
import Config.Cost
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
import Remote.Helper.Chunked
import qualified Remote.Helper.Chunked.Legacy as Legacy
import Crypto
import Annex.Content
import Annex.UUID
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
}
gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
gen r u c gc = do
cst <- remoteCost gc cheapRemoteCost
let chunkconfig = chunkConfig c
return $ Just $ encryptableRemote c
(storeEncrypted dir (getGpgEncParams (c,gc)) chunkconfig)
(retrieveEncrypted u dir chunkconfig)
2011-04-16 21:41:14 -04:00
Remote {
uuid = u,
cost = cst,
name = Git.repoDescribe r,
storeKey = store u dir chunkconfig,
retrieveKeyFile = retrieve u dir chunkconfig,
retrieveKeyFileCheap = retrieveCheap u dir chunkconfig,
removeKey = remove dir,
hasKey = checkPresent u dir chunkconfig,
2011-04-16 21:41:14 -04:00
hasKeyCheap = True,
whereisKey = Nothing,
remoteFsck = Nothing,
repairRepo = Nothing,
config = c,
repo = r,
gitconfig = gc,
2012-08-26 14:26:43 -04:00
localpath = Just dir,
readonly = False,
availability = LocallyAvailable,
remotetype = remote
2011-04-16 21:41:14 -04:00
}
where
dir = fromMaybe (error "missing directory") $ remoteAnnexDirectory gc
directorySetup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> Annex (RemoteConfig, UUID)
directorySetup mu _ c = do
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
absdir <- liftIO $ absPath dir
liftIO $ unlessM (doesDirectoryExist absdir) $
error $ "Directory does not exist: " ++ absdir
c' <- encryptionSetup c
2011-03-30 13:18:46 -04:00
-- The directory is stored in git config, not in this remote's
-- persistant state, so it can vary between hosts.
gitConfigSpecialRemote u c' "directory" absdir
return (M.delete "directory" c', u)
2011-03-30 13:18:46 -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. -}
locations :: FilePath -> Key -> [FilePath]
locations d k = map (d </>) (keyPaths k)
2011-03-30 13:18:46 -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
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
let chunkcount = f ++ Legacy.chunkCount
2012-11-11 00:51:07 -04:00
ifM (check chunkcount)
( do
chunks <- Legacy.listChunks f <$> readFile chunkcount
ifM (allM check chunks)
2012-11-11 00:51:07 -04:00
( a chunks , return False )
, do
chunks <- Legacy.probeChunks f check
if null chunks
then go fs
else a chunks
2012-11-11 00:51:07 -04:00
)
withCheckedFiles check u chunkconfig d k a =
go $ locations d k
where
go [] = return False
go (f:fs) = ifM (check f) ( a [f] , go fs )
withStoredFiles :: UUID -> ChunkConfig -> FilePath -> Key -> ([FilePath] -> IO Bool) -> IO Bool
withStoredFiles = withCheckedFiles doesFileExist
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 ->
case chunkconfig of
2014-07-24 15:08:07 -04:00
LegacyChunks chunksize ->
storeLegacyChunked meterupdate chunksize dests b
_ -> do
let dest = Prelude.head dests
meteredWriteFile meterupdate dest b
return [dest]
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]
{- Splits a ByteString into chunks and writes to dests, obeying configured
- 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]
storeLegacyChunked _ _ [] _ = error "bad storeLegacyChunked call"
storeLegacyChunked meterupdate chunksize alldests@(firstdest:_) b
| L.null b = do
-- always write at least one file, even for empty
L.writeFile firstdest b
return [firstdest]
| 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]
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 $
feed zeroBytesProcessed chunksize bs
storeLegacyChunked' meterupdate chunksize dests bs' (d:c)
2012-11-11 00:51:07 -04:00
where
feed _ _ [] _ = return []
feed bytes sz (l:ls) h = do
let len = S.length l
let s = fromIntegral len
if s <= sz || sz == chunksize
2012-11-11 00:51:07 -04:00
then do
S.hPut h l
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)
{- 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
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
let tmpf = tmpdir </> keyFile key
void $ storer [tmpf]
finalizer tmpdir destdir
return True
where
tmpdir = tmpDir d key
destdir = storeDir d key
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
-- may fail on some filesystems
void $ tryIO $ do
mapM_ preventWrite =<< dirContents dest
preventWrite dest
recorder f s = do
void $ tryIO $ allowWrite f
writeFile f s
void $ tryIO $ preventWrite f
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 ->
catchBoolIO $ do
meteredWriteFileChunks meterupdate f files L.readFile
return True
2011-04-16 21:41:14 -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 ->
catchBoolIO $ do
decrypt cipher (feeder files) $
readBytes $ meteredWriteFile meterupdate f
return True
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
retrieveCheap :: UUID -> FilePath -> ChunkConfig -> Key -> FilePath -> Annex Bool
-- no cheap retrieval for chunks
retrieveCheap _ _ (UnpaddedChunks _) _ _ = return False
retrieveCheap _ _ (LegacyChunks _) _ _ = return False
#ifndef mingw32_HOST_OS
retrieveCheap u d ck k f = liftIO $ withStoredFiles u ck d k go
2012-11-11 00:51:07 -04:00
where
go [file] = catchBoolIO $
createSymbolicLink file f >> return True
2012-11-11 00:51:07 -04:00
go _files = return False
#else
retrieveCheap _ _ _ _ _ = return False
#endif
remove :: FilePath -> Key -> Annex Bool
remove d k = liftIO $ do
void $ tryIO $ allowWrite dir
#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
catchBoolIO $ do
removeDirectoryRecursive dir
return True
2012-11-11 00:51:07 -04:00
where
dir = storeDir d k
2011-03-30 13:18:46 -04:00
checkPresent :: UUID -> FilePath -> ChunkConfig -> Key -> Annex (Either String Bool)
checkPresent u d chunkconfig k = liftIO $ catchMsgIO $ withStoredFiles u chunkconfig d k $
const $ return True -- withStoredFiles checked that it exists