From b87dfe5ddfb3686ab0088c09e6e70bd7275a1f16 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sun, 3 Aug 2014 15:35:23 -0400 Subject: roll ChunkedEncryptable into Special and improve interface Allow disabling progress displays, for eg, rsync. --- Remote/Helper/Special.hs | 223 +++++++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 218 insertions(+), 5 deletions(-) (limited to 'Remote/Helper/Special.hs') diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs index 7fc421f46..2bcb7d530 100644 --- a/Remote/Helper/Special.hs +++ b/Remote/Helper/Special.hs @@ -1,20 +1,51 @@ -{- common functions for special remotes +{- helpers for special remotes - - - Copyright 2011 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} -module Remote.Helper.Special where - -import qualified Data.Map as M +module Remote.Helper.Special ( + findSpecialRemotes, + gitConfigSpecialRemote, + Preparer, + Storer, + Retriever, + simplyPrepare, + ContentSource, + checkPrepare, + resourcePrepare, + fileStorer, + byteStorer, + fileRetriever, + byteRetriever, + storeKeyDummy, + retreiveKeyFileDummy, + SpecialRemoteCfg(..), + specialRemoteCfg, + specialRemote, + specialRemote', + module X +) where import Common.Annex +import Types.StoreRetrieve import Types.Remote +import Crypto +import Config.Cost +import Utility.Metered +import Remote.Helper.Chunked as X +import Remote.Helper.Encryptable as X hiding (encryptableRemote) +import Annex.Content +import Annex.Exception import qualified Git import qualified Git.Command import qualified Git.Construct +import qualified Data.ByteString.Lazy as L +import Control.Exception (bracket) +import qualified Data.Map as M + {- Special remotes don't have a configured url, so Git.Repo does not - automatically generate remotes for them. This looks for a different - configuration key instead. @@ -38,3 +69,185 @@ gitConfigSpecialRemote u c k v = do [Param "config", Param (configsetting a), Param b] remotename = fromJust (M.lookup "name" c) configsetting s = "remote." ++ remotename ++ "." ++ s + +-- Use when nothing needs to be done to prepare a helper. +simplyPrepare :: helper -> Preparer helper +simplyPrepare helper _ a = a $ Just helper + +-- Use to run a check when preparing a helper. +checkPrepare :: (Key -> Annex Bool) -> helper -> Preparer helper +checkPrepare checker helper k a = ifM (checker k) + ( a (Just helper) + , a Nothing + ) + +-- Use to acquire a resource when preparing a helper. +resourcePrepare :: (Key -> (r -> Annex Bool) -> Annex Bool) -> (r -> helper) -> Preparer helper +resourcePrepare withr helper k a = withr k $ \r -> + a (Just (helper r)) + +-- A Storer that expects to be provided with a file containing +-- the content of the key to store. +fileStorer :: (Key -> FilePath -> MeterUpdate -> Annex Bool) -> Storer +fileStorer a k (FileContent f) m = a k f m +fileStorer a k (ByteContent b) m = withTmp k $ \f -> do + liftIO $ L.writeFile f b + a k f m + +-- A Storer that expects to be provided with a L.ByteString of +-- the content to store. +byteStorer :: (Key -> L.ByteString -> MeterUpdate -> Annex Bool) -> Storer +byteStorer a k c m = withBytes c $ \b -> a k b m + +-- A Retriever that writes the content of a Key to a provided file. +-- It is responsible for updating the progress meter as it retrieves data. +fileRetriever :: (FilePath -> Key -> MeterUpdate -> Annex ()) -> Retriever +fileRetriever a k m callback = do + f <- prepTmp k + a f k m + callback (FileContent f) + +-- A Retriever that generates a lazy ByteString containing the Key's +-- content, and passes it to a callback action which will fully consume it +-- before returning. +byteRetriever :: (Key -> (L.ByteString -> Annex Bool) -> Annex Bool) -> Retriever +byteRetriever a k _m callback = a k (callback . ByteContent) + +{- The base Remote that is provided to specialRemote needs to have + - storeKey and retreiveKeyFile methods, but they are never + - actually used (since specialRemote replaces them). + - Here are some dummy ones. + -} +storeKeyDummy :: Key -> AssociatedFile -> MeterUpdate -> Annex Bool +storeKeyDummy _ _ _ = return False +retreiveKeyFileDummy :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool +retreiveKeyFileDummy _ _ _ _ = return False + +type RemoteModifier = RemoteConfig -> Preparer Storer -> Preparer Retriever -> Remote -> Remote + +data SpecialRemoteCfg = SpecialRemoteCfg + { chunkConfig :: ChunkConfig + , displayProgress :: Bool + } + +specialRemoteCfg :: RemoteConfig -> SpecialRemoteCfg +specialRemoteCfg c = SpecialRemoteCfg (getChunkConfig c) True + +-- Modifies a base Remote to support both chunking and encryption, +-- which special remotes typically should support. +specialRemote :: RemoteModifier +specialRemote c = specialRemote' (specialRemoteCfg c) c + +specialRemote' :: SpecialRemoteCfg -> RemoteModifier +specialRemote' cfg c preparestorer prepareretriever baser = encr + where + encr = baser + { storeKey = \k _f p -> cip >>= storeKeyGen k p + , retrieveKeyFile = \k _f d p -> cip >>= retrieveKeyFileGen k d p + , retrieveKeyFileCheap = \k d -> cip >>= maybe + (retrieveKeyFileCheap baser k d) + (\_ -> return False) + , removeKey = \k -> cip >>= removeKeyGen k + , hasKey = \k -> cip >>= hasKeyGen k + , cost = maybe + (cost baser) + (const $ cost baser + encryptedRemoteCostAdj) + (extractCipher c) + } + cip = cipherKey c + gpgopts = getGpgEncParams encr + + safely a = catchNonAsyncAnnex a (\e -> warning (show e) >> return False) + + -- chunk, then encrypt, then feed to the storer + storeKeyGen k p enc = + safely $ preparestorer k $ safely . go + where + go (Just storer) = sendAnnex k rollback $ \src -> + displayprogress p k $ \p' -> + storeChunks (uuid baser) chunkconfig k src p' + (storechunk enc storer) + (hasKey baser) + go Nothing = return False + rollback = void $ removeKey encr k + + storechunk Nothing storer k content p = storer k content p + storechunk (Just (cipher, enck)) storer k content p = + withBytes content $ \b -> + encrypt gpgopts cipher (feedBytes b) $ + readBytes $ \encb -> + storer (enck k) (ByteContent encb) p + + -- call retriever to get chunks; decrypt them; stream to dest file + retrieveKeyFileGen k dest p enc = + safely $ prepareretriever k $ safely . go + where + go (Just retriever) = displayprogress p k $ \p' -> + retrieveChunks retriever (uuid baser) chunkconfig + enck k dest p' (sink dest enc) + go Nothing = return False + enck = maybe id snd enc + + removeKeyGen k enc = removeChunks remover (uuid baser) chunkconfig enck k + where + enck = maybe id snd enc + remover = removeKey baser + + hasKeyGen k enc = hasKeyChunks checker (uuid baser) chunkconfig enck k + where + enck = maybe id snd enc + checker = hasKey baser + + chunkconfig = chunkConfig cfg + + displayprogress p k a + | displayProgress cfg = metered (Just p) k a + | otherwise = a p + +{- Sink callback for retrieveChunks. Stores the file content into the + - provided Handle, decrypting it first if necessary. + - + - If the remote did not store the content using chunks, no Handle + - will be provided, and it's up to us to open the destination file. + - + - Note that when neither chunking nor encryption is used, and the remote + - provides FileContent, that file only needs to be renamed + - into place. (And it may even already be in the right place..) + -} +sink + :: FilePath + -> Maybe (Cipher, EncKey) + -> Maybe Handle + -> Maybe MeterUpdate + -> ContentSource + -> Annex Bool +sink dest enc mh mp content = do + case (enc, mh, content) of + (Nothing, Nothing, FileContent f) + | f == dest -> noop + | otherwise -> liftIO $ moveFile f dest + (Just (cipher, _), _, ByteContent b) -> + decrypt cipher (feedBytes b) $ + readBytes write + (Just (cipher, _), _, FileContent f) -> do + withBytes content $ \b -> + decrypt cipher (feedBytes b) $ + readBytes write + liftIO $ nukeFile f + (Nothing, _, FileContent f) -> do + withBytes content write + liftIO $ nukeFile f + (Nothing, _, ByteContent b) -> write b + return True + where + write b = case mh of + Just h -> liftIO $ b `streamto` h + Nothing -> liftIO $ bracket opendest hClose (b `streamto`) + streamto b h = case mp of + Just p -> meteredWrite p h b + Nothing -> L.hPut h b + opendest = openBinaryFile dest WriteMode + +withBytes :: ContentSource -> (L.ByteString -> Annex a) -> Annex a +withBytes (ByteContent b) a = a b +withBytes (FileContent f) a = a =<< liftIO (L.readFile f) -- cgit v1.2.3 From cc2606ce542e04c22cf229d536ad621f9e25c12d Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 6 Aug 2014 13:45:19 -0400 Subject: pushed checkPresent exception handling out of Remote implementations I tend to prefer moving toward explicit exception handling, not away from it, but in this case, I think there are good reasons to let checkPresent throw exceptions: 1. They can all be caught in one place (Remote.hasKey), and we know every possible exception is caught there now, which we didn't before. 2. It simplified the code of the Remotes. I think it makes sense for Remotes to be able to be implemented without needing to worry about catching exceptions inside them. (Mostly.) 3. Types.StoreRetrieve.Preparer can only work on things that return a Bool, which all the other relevant remote methods already did. I do not see a good way to generalize that type; my previous attempts failed miserably. --- Remote.hs | 8 +++++++ Remote/Bup.hs | 15 ++++++------- Remote/Ddar.hs | 15 +++++++------ Remote/Directory.hs | 21 ++++++++--------- Remote/Directory/LegacyChunked.hs | 9 ++++---- Remote/External.hs | 8 +++---- Remote/GCrypt.hs | 14 +++++------- Remote/Git.hs | 25 ++++++++------------- Remote/Glacier.hs | 28 ++++++++++------------- Remote/Helper/Chunked.hs | 47 ++++++++++++++++++++++----------------- Remote/Helper/Encryptable.hs | 6 ++--- Remote/Helper/Hooks.hs | 2 +- Remote/Helper/Messages.hs | 4 ++-- Remote/Helper/Special.hs | 8 +++---- Remote/Helper/Ssh.hs | 6 ++--- Remote/Hook.hs | 10 ++++----- Remote/Rsync.hs | 14 +++++------- Remote/S3.hs | 16 ++++++------- Remote/Tahoe.hs | 20 +++++++++-------- Remote/Web.hs | 10 ++++----- Remote/WebDAV.hs | 10 ++++----- Types/Remote.hs | 10 ++++----- Types/StoreRetrieve.hs | 8 +++++++ doc/design/assistant/chunks.mdwn | 16 ++++++------- 24 files changed, 167 insertions(+), 163 deletions(-) (limited to 'Remote/Helper/Special.hs') diff --git a/Remote.hs b/Remote.hs index 29097f77d..5ee75823f 100644 --- a/Remote.hs +++ b/Remote.hs @@ -56,6 +56,7 @@ import Data.Ord import Common.Annex import Types.Remote import qualified Annex +import Annex.Exception import Annex.UUID import Logs.UUID import Logs.Trust @@ -312,3 +313,10 @@ isXMPPRemote :: Remote -> Bool isXMPPRemote remote = Git.repoIsUrl r && "xmpp::" `isPrefixOf` Git.repoLocation r where r = repo remote + +hasKey :: Remote -> Key -> Annex (Either String Bool) +hasKey r k = either (Left . show) Right + <$> tryNonAsyncAnnex (checkPresent r k) + +hasKeyCheap :: Remote -> Bool +hasKeyCheap = checkPresentCheap diff --git a/Remote/Bup.hs b/Remote/Bup.hs index 6a04ad5f7..2e68f30ef 100644 --- a/Remote/Bup.hs +++ b/Remote/Bup.hs @@ -58,8 +58,8 @@ gen r u c gc = do , retrieveKeyFile = retreiveKeyFileDummy , retrieveKeyFileCheap = retrieveCheap buprepo , removeKey = remove buprepo - , hasKey = checkPresent r bupr' - , hasKeyCheap = bupLocal buprepo + , checkPresent = checkKey r bupr' + , checkPresentCheap = bupLocal buprepo , whereisKey = Nothing , remoteFsck = Nothing , repairRepo = Nothing @@ -163,14 +163,13 @@ remove buprepo k = do - in a bup repository. One way it to check if the git repository has - a branch matching the name (as created by bup split -n). -} -checkPresent :: Git.Repo -> Git.Repo -> Key -> Annex (Either String Bool) -checkPresent r bupr k +checkKey :: Git.Repo -> Git.Repo -> Key -> Annex Bool +checkKey r bupr k | Git.repoIsUrl bupr = do showChecking r - ok <- onBupRemote bupr boolSystem "git" params - return $ Right ok - | otherwise = liftIO $ catchMsgIO $ - boolSystem "git" $ Git.Command.gitCommandLine params bupr + onBupRemote bupr boolSystem "git" params + | otherwise = liftIO $ boolSystem "git" $ + Git.Command.gitCommandLine params bupr where params = [ Params "show-ref --quiet --verify" diff --git a/Remote/Ddar.hs b/Remote/Ddar.hs index b4c7ac1e6..1227b5275 100644 --- a/Remote/Ddar.hs +++ b/Remote/Ddar.hs @@ -54,8 +54,8 @@ gen r u c gc = do , retrieveKeyFile = retreiveKeyFileDummy , retrieveKeyFileCheap = retrieveCheap , removeKey = remove ddarrepo - , hasKey = checkPresent ddarrepo - , hasKeyCheap = ddarLocal ddarrepo + , checkPresent = checkKey ddarrepo + , checkPresentCheap = ddarLocal ddarrepo , whereisKey = Nothing , remoteFsck = Nothing , repairRepo = Nothing @@ -181,13 +181,14 @@ inDdarManifest ddarrepo k = do where k' = key2file k -checkPresent :: DdarRepo -> Key -> Annex (Either String Bool) -checkPresent ddarrepo key = do +checkKey :: DdarRepo -> Key -> Annex Bool +checkKey ddarrepo key = do directoryExists <- ddarDirectoryExists ddarrepo case directoryExists of - Left e -> return $ Left e - Right True -> inDdarManifest ddarrepo key - Right False -> return $ Right False + Left e -> error e + Right True -> either error return + =<< inDdarManifest ddarrepo key + Right False -> return False ddarLocal :: DdarRepo -> Bool ddarLocal = notElem ':' diff --git a/Remote/Directory.hs b/Remote/Directory.hs index 9b3c15695..0a2532aa5 100644 --- a/Remote/Directory.hs +++ b/Remote/Directory.hs @@ -52,8 +52,8 @@ gen r u c gc = do retrieveKeyFile = retreiveKeyFileDummy, retrieveKeyFileCheap = retrieveCheap dir chunkconfig, removeKey = remove dir, - hasKey = checkPresent dir chunkconfig, - hasKeyCheap = True, + checkPresent = checkKey dir chunkconfig, + checkPresentCheap = True, whereisKey = Nothing, remoteFsck = Nothing, repairRepo = Nothing, @@ -189,13 +189,10 @@ removeDirGeneric topdir dir = do then return ok else doesDirectoryExist topdir <&&> (not <$> doesDirectoryExist dir) -checkPresent :: FilePath -> ChunkConfig -> Key -> Annex (Either String Bool) -checkPresent d (LegacyChunks _) k = Legacy.checkPresent d locations k -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 +checkKey :: FilePath -> ChunkConfig -> Key -> Annex Bool +checkKey d (LegacyChunks _) k = Legacy.checkKey d locations k +checkKey d _ k = liftIO $ + ifM (anyM doesFileExist (locations d k)) + ( return True + , error $ "directory " ++ d ++ " is not accessible" + ) diff --git a/Remote/Directory/LegacyChunked.hs b/Remote/Directory/LegacyChunked.hs index 1be885db2..b2248c5f6 100644 --- a/Remote/Directory/LegacyChunked.hs +++ b/Remote/Directory/LegacyChunked.hs @@ -103,8 +103,7 @@ retrieve locations d basek a = do liftIO $ nukeFile tmp sink b -checkPresent :: FilePath -> (FilePath -> Key -> [FilePath]) -> Key -> Annex (Either String Bool) -checkPresent d locations k = liftIO $ catchMsgIO $ - withStoredFiles d locations k $ - -- withStoredFiles checked that it exists - const $ return True +checkKey :: FilePath -> (FilePath -> Key -> [FilePath]) -> Key -> Annex Bool +checkKey d locations k = liftIO $ withStoredFiles d locations k $ + -- withStoredFiles checked that it exists + const $ return True diff --git a/Remote/External.hs b/Remote/External.hs index c00093402..ffae94ec9 100644 --- a/Remote/External.hs +++ b/Remote/External.hs @@ -53,8 +53,8 @@ gen r u c gc = do retrieveKeyFile = retreiveKeyFileDummy, retrieveKeyFileCheap = \_ _ -> return False, removeKey = remove external, - hasKey = checkPresent external, - hasKeyCheap = False, + checkPresent = checkKey external, + checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, repairRepo = Nothing, @@ -121,8 +121,8 @@ remove external k = safely $ return False _ -> Nothing -checkPresent :: External -> Key -> Annex (Either String Bool) -checkPresent external k = either (Left . show) id <$> tryAnnex go +checkKey :: External -> Key -> Annex Bool +checkKey external k = either error id <$> go where go = handleRequest external (CHECKPRESENT k) Nothing $ \resp -> case resp of diff --git a/Remote/GCrypt.hs b/Remote/GCrypt.hs index d969e02f8..f971ff754 100644 --- a/Remote/GCrypt.hs +++ b/Remote/GCrypt.hs @@ -46,7 +46,6 @@ import Utility.Tmp import Logs.Remote import Logs.Transfer import Utility.Gpg -import Utility.FileMode remote :: RemoteType remote = RemoteType { @@ -109,8 +108,8 @@ gen' r u c gc = do , retrieveKeyFile = retreiveKeyFileDummy , retrieveKeyFileCheap = \_ _ -> return False , removeKey = remove this rsyncopts - , hasKey = checkPresent this rsyncopts - , hasKeyCheap = repoCheap r + , checkPresent = checkKey this rsyncopts + , checkPresentCheap = repoCheap r , whereisKey = Nothing , remoteFsck = Nothing , repairRepo = Nothing @@ -342,16 +341,15 @@ remove r rsyncopts k removersync = Remote.Rsync.remove rsyncopts k removeshell = Ssh.dropKey (repo r) k -checkPresent :: Remote -> Remote.Rsync.RsyncOpts -> Key -> Annex (Either String Bool) -checkPresent r rsyncopts k +checkKey :: Remote -> Remote.Rsync.RsyncOpts -> Key -> Annex Bool +checkKey r rsyncopts k | not $ Git.repoIsUrl (repo r) = guardUsable (repo r) (cantCheck $ repo r) $ - liftIO $ catchDefaultIO (cantCheck $ repo r) $ - Right <$> doesFileExist (gCryptLocation r k) + liftIO $ doesFileExist (gCryptLocation r k) | Git.repoIsSsh (repo r) = shellOrRsync r checkshell checkrsync | otherwise = unsupportedUrl where - checkrsync = Remote.Rsync.checkPresent (repo r) rsyncopts k + checkrsync = Remote.Rsync.checkKey (repo r) rsyncopts k checkshell = Ssh.inAnnex (repo r) k {- Annexed objects are hashed using lower-case directories for max diff --git a/Remote/Git.hs b/Remote/Git.hs index c35f9f32a..da5ca4c4a 100644 --- a/Remote/Git.hs +++ b/Remote/Git.hs @@ -141,8 +141,8 @@ gen r u c gc , retrieveKeyFile = copyFromRemote new , retrieveKeyFileCheap = copyFromRemoteCheap new , removeKey = dropKey new - , hasKey = inAnnex new - , hasKeyCheap = repoCheap r + , checkPresent = inAnnex new + , checkPresentCheap = repoCheap r , whereisKey = Nothing , remoteFsck = if Git.repoIsUrl r then Nothing @@ -284,11 +284,8 @@ tryGitConfigRead r void $ tryAnnex $ ensureInitialized Annex.getState Annex.repo -{- Checks if a given remote has the content for a key inAnnex. - - If the remote cannot be accessed, or if it cannot determine - - whether it has the content, returns a Left error message. - -} -inAnnex :: Remote -> Key -> Annex (Either String Bool) +{- Checks if a given remote has the content for a key in its annex. -} +inAnnex :: Remote -> Key -> Annex Bool inAnnex rmt key | Git.repoIsHttp r = checkhttp | Git.repoIsUrl r = checkremote @@ -298,17 +295,13 @@ inAnnex rmt key checkhttp = do showChecking r ifM (Url.withUrlOptions $ \uo -> anyM (\u -> Url.checkBoth u (keySize key) uo) (keyUrls rmt key)) - ( return $ Right True - , return $ Left "not found" + ( return True + , error "not found" ) checkremote = Ssh.inAnnex r key - checklocal = guardUsable r (cantCheck r) $ dispatch <$> check - where - check = either (Left . show) Right - <$> tryAnnex (onLocal rmt $ Annex.Content.inAnnexSafe key) - dispatch (Left e) = Left e - dispatch (Right (Just b)) = Right b - dispatch (Right Nothing) = cantCheck r + checklocal = guardUsable r (cantCheck r) $ + fromMaybe (cantCheck r) + <$> onLocal rmt (Annex.Content.inAnnexSafe key) keyUrls :: Remote -> Key -> [String] keyUrls r key = map tourl locs' diff --git a/Remote/Glacier.hs b/Remote/Glacier.hs index c5bfefa64..2ade37011 100644 --- a/Remote/Glacier.hs +++ b/Remote/Glacier.hs @@ -52,8 +52,8 @@ gen r u c gc = new <$> remoteCost gc veryExpensiveRemoteCost retrieveKeyFile = retreiveKeyFileDummy, retrieveKeyFileCheap = retrieveCheap this, removeKey = remove this, - hasKey = checkPresent this, - hasKeyCheap = False, + checkPresent = checkKey this, + checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, repairRepo = Nothing, @@ -164,25 +164,21 @@ remove r k = glacierAction r , Param $ archive r k ] -checkPresent :: Remote -> Key -> Annex (Either String Bool) -checkPresent r k = do +checkKey :: Remote -> Key -> Annex Bool +checkKey r k = do showAction $ "checking " ++ name r go =<< glacierEnv (config r) (uuid r) where - go Nothing = return $ Left "cannot check glacier" + go Nothing = error "cannot check glacier" go (Just e) = do {- glacier checkpresent outputs the archive name to stdout if - it's present. -} - v <- liftIO $ catchMsgIO $ - readProcessEnv "glacier" (toCommand params) (Just e) - case v of - Right s -> do - let probablypresent = key2file k `elem` lines s - if probablypresent - then ifM (Annex.getFlag "trustglacier") - ( return $ Right True, untrusted ) - else return $ Right False - Left err -> return $ Left err + s <- liftIO $ readProcessEnv "glacier" (toCommand params) (Just e) + let probablypresent = key2file k `elem` lines s + if probablypresent + then ifM (Annex.getFlag "trustglacier") + ( return True, error untrusted ) + else return False params = glacierParams (config r) [ Param "archive" @@ -192,7 +188,7 @@ checkPresent r k = do , Param $ archive r k ] - untrusted = return $ Left $ unlines + untrusted = unlines [ "Glacier's inventory says it has a copy." , "However, the inventory could be out of date, if it was recently removed." , "(Use --trust-glacier if you're sure it's still in Glacier.)" diff --git a/Remote/Helper/Chunked.hs b/Remote/Helper/Chunked.hs index 7ad790cb1..953c533b6 100644 --- a/Remote/Helper/Chunked.hs +++ b/Remote/Helper/Chunked.hs @@ -12,7 +12,7 @@ module Remote.Helper.Chunked ( storeChunks, removeChunks, retrieveChunks, - hasKeyChunks, + checkPresentChunks, ) where import Common.Annex @@ -94,8 +94,8 @@ storeChunks -> Key -> FilePath -> MeterUpdate - -> (Key -> ContentSource -> MeterUpdate -> Annex Bool) - -> (Key -> Annex (Either String Bool)) + -> Storer + -> CheckPresent -> Annex Bool storeChunks u chunkconfig k f p storer checker = case chunkconfig of @@ -158,7 +158,7 @@ storeChunks u chunkconfig k f p storer checker = seekResume :: Handle -> ChunkKeyStream - -> (Key -> Annex (Either String Bool)) + -> CheckPresent -> Annex (ChunkKeyStream, BytesProcessed) seekResume h chunkkeys checker = do sz <- liftIO (hFileSize h) @@ -172,7 +172,7 @@ seekResume h chunkkeys checker = do liftIO $ hSeek h AbsoluteSeek sz return (cks, toBytesProcessed sz) | otherwise = do - v <- checker k + v <- tryNonAsyncAnnex (checker k) case v of Right True -> check pos' cks' sz @@ -331,43 +331,48 @@ setupResume ls currsize = map dropunneeded ls {- Checks if a key is present in a remote. This requires any one - of the lists of options returned by chunkKeys to all check out - as being present using the checker action. + - + - Throws an exception if the remote is not accessible. -} -hasKeyChunks - :: (Key -> Annex (Either String Bool)) +checkPresentChunks + :: CheckPresent -> UUID -> ChunkConfig -> EncKey -> Key - -> Annex (Either String Bool) -hasKeyChunks checker u chunkconfig encryptor basek - | noChunks chunkconfig = + -> Annex Bool +checkPresentChunks checker u chunkconfig encryptor basek + | noChunks chunkconfig = do -- Optimisation: Try the unchunked key first, to avoid -- looking in the git-annex branch for chunk counts -- that are likely not there. - ifM ((Right True ==) <$> checker (encryptor basek)) - ( return (Right True) - , checklists Nothing =<< chunkKeysOnly u basek - ) + v <- check basek + case v of + Right True -> return True + _ -> checklists Nothing =<< chunkKeysOnly u basek | otherwise = checklists Nothing =<< chunkKeys u chunkconfig basek where - checklists Nothing [] = return (Right False) - checklists (Just deferrederror) [] = return (Left deferrederror) + checklists Nothing [] = return False + checklists (Just deferrederror) [] = error deferrederror checklists d (l:ls) | not (null l) = do v <- checkchunks l case v of Left e -> checklists (Just e) ls - Right True -> return (Right True) + Right True -> return True Right False -> checklists Nothing ls | otherwise = checklists d ls checkchunks :: [Key] -> Annex (Either String Bool) checkchunks [] = return (Right True) checkchunks (k:ks) = do - v <- checker (encryptor k) - if v == Right True - then checkchunks ks - else return v + v <- check k + case v of + Right True -> checkchunks ks + Right False -> return $ Right False + Left e -> return $ Left $ show e + + check = tryNonAsyncAnnex . checker . encryptor {- A key can be stored in a remote unchunked, or as a list of chunked keys. - This can be the case whether or not the remote is currently configured diff --git a/Remote/Helper/Encryptable.hs b/Remote/Helper/Encryptable.hs index 65a3ba284..c364a69e7 100644 --- a/Remote/Helper/Encryptable.hs +++ b/Remote/Helper/Encryptable.hs @@ -91,9 +91,9 @@ encryptableRemote c storeKeyEncrypted retrieveKeyFileEncrypted r = r , removeKey = \k -> cip k >>= maybe (removeKey r k) (\(_, enckey) -> removeKey r enckey) - , hasKey = \k -> cip k >>= maybe - (hasKey r k) - (\(_, enckey) -> hasKey r enckey) + , checkPresent = \k -> cip k >>= maybe + (checkPresent r k) + (\(_, enckey) -> checkPresent r enckey) , cost = maybe (cost r) (const $ cost r + encryptedRemoteCostAdj) diff --git a/Remote/Helper/Hooks.hs b/Remote/Helper/Hooks.hs index c3ff970c6..907400bd1 100644 --- a/Remote/Helper/Hooks.hs +++ b/Remote/Helper/Hooks.hs @@ -39,7 +39,7 @@ addHooks' r starthook stophook = r' , retrieveKeyFile = \k f d p -> wrapper $ retrieveKeyFile r k f d p , retrieveKeyFileCheap = \k f -> wrapper $ retrieveKeyFileCheap r k f , removeKey = wrapper . removeKey r - , hasKey = wrapper . hasKey r + , checkPresent = wrapper . checkPresent r } where wrapper = runHooks r' starthook stophook diff --git a/Remote/Helper/Messages.hs b/Remote/Helper/Messages.hs index c4b1966dc..3088a9ab2 100644 --- a/Remote/Helper/Messages.hs +++ b/Remote/Helper/Messages.hs @@ -13,5 +13,5 @@ import qualified Git showChecking :: Git.Repo -> Annex () showChecking r = showAction $ "checking " ++ Git.repoDescribe r -cantCheck :: Git.Repo -> Either String Bool -cantCheck r = Left $ "unable to check " ++ Git.repoDescribe r +cantCheck :: Git.Repo -> a +cantCheck r = error $ "unable to check " ++ Git.repoDescribe r diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs index 2bcb7d530..3c19f25eb 100644 --- a/Remote/Helper/Special.hs +++ b/Remote/Helper/Special.hs @@ -148,7 +148,7 @@ specialRemote' cfg c preparestorer prepareretriever baser = encr (retrieveKeyFileCheap baser k d) (\_ -> return False) , removeKey = \k -> cip >>= removeKeyGen k - , hasKey = \k -> cip >>= hasKeyGen k + , checkPresent = \k -> cip >>= checkPresentGen k , cost = maybe (cost baser) (const $ cost baser + encryptedRemoteCostAdj) @@ -167,7 +167,7 @@ specialRemote' cfg c preparestorer prepareretriever baser = encr displayprogress p k $ \p' -> storeChunks (uuid baser) chunkconfig k src p' (storechunk enc storer) - (hasKey baser) + (checkPresent baser) go Nothing = return False rollback = void $ removeKey encr k @@ -193,10 +193,10 @@ specialRemote' cfg c preparestorer prepareretriever baser = encr enck = maybe id snd enc remover = removeKey baser - hasKeyGen k enc = hasKeyChunks checker (uuid baser) chunkconfig enck k + checkPresentGen k enc = checkPresentChunks checker (uuid baser) chunkconfig enck k where enck = maybe id snd enc - checker = hasKey baser + checker = checkPresent baser chunkconfig = chunkConfig cfg diff --git a/Remote/Helper/Ssh.hs b/Remote/Helper/Ssh.hs index 05a98865f..42d77ea59 100644 --- a/Remote/Helper/Ssh.hs +++ b/Remote/Helper/Ssh.hs @@ -81,14 +81,14 @@ onRemote r (with, errorval) command params fields = do Nothing -> return errorval {- Checks if a remote contains a key. -} -inAnnex :: Git.Repo -> Key -> Annex (Either String Bool) +inAnnex :: Git.Repo -> Key -> Annex Bool inAnnex r k = do showChecking r onRemote r (check, cantCheck r) "inannex" [Param $ key2file k] [] where check c p = dispatch <$> safeSystem c p - dispatch ExitSuccess = Right True - dispatch (ExitFailure 1) = Right False + dispatch ExitSuccess = True + dispatch (ExitFailure 1) = False dispatch _ = cantCheck r {- Removes a key from a remote. -} diff --git a/Remote/Hook.hs b/Remote/Hook.hs index efbd9f8ba..037f71ced 100644 --- a/Remote/Hook.hs +++ b/Remote/Hook.hs @@ -45,8 +45,8 @@ gen r u c gc = do retrieveKeyFile = retreiveKeyFileDummy, retrieveKeyFileCheap = retrieveCheap hooktype, removeKey = remove hooktype, - hasKey = checkPresent r hooktype, - hasKeyCheap = False, + checkPresent = checkKey r hooktype, + checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, repairRepo = Nothing, @@ -128,11 +128,11 @@ retrieveCheap _ _ _ = return False remove :: HookName -> Key -> Annex Bool remove h k = runHook h "remove" k Nothing $ return True -checkPresent :: Git.Repo -> HookName -> Key -> Annex (Either String Bool) -checkPresent r h k = do +checkKey :: Git.Repo -> HookName -> Key -> Annex Bool +checkKey r h k = do showAction $ "checking " ++ Git.repoDescribe r v <- lookupHook h action - liftIO $ catchMsgIO $ check v + liftIO $ check v where action = "checkpresent" findkey s = key2file k `elem` lines s diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs index 421c451bd..91070fe84 100644 --- a/Remote/Rsync.hs +++ b/Remote/Rsync.hs @@ -12,7 +12,7 @@ module Remote.Rsync ( store, retrieve, remove, - checkPresent, + checkKey, withRsyncScratchDir, genRsyncOpts, RsyncOpts @@ -66,8 +66,8 @@ gen r u c gc = do , retrieveKeyFile = retreiveKeyFileDummy , retrieveKeyFileCheap = retrieveCheap o , removeKey = remove o - , hasKey = checkPresent r o - , hasKeyCheap = False + , checkPresent = checkKey r o + , checkPresentCheap = False , whereisKey = Nothing , remoteFsck = Nothing , repairRepo = Nothing @@ -214,14 +214,12 @@ remove o k = do , dir keyFile k "***" ] -checkPresent :: Git.Repo -> RsyncOpts -> Key -> Annex (Either String Bool) -checkPresent r o k = do +checkKey :: Git.Repo -> RsyncOpts -> Key -> Annex Bool +checkKey r o k = do showAction $ "checking " ++ Git.repoDescribe r -- note: Does not currently differentiate between rsync failing -- to connect, and the file not being present. - Right <$> check - where - check = untilTrue (rsyncUrls o k) $ \u -> + untilTrue (rsyncUrls o k) $ \u -> liftIO $ catchBoolIO $ do withQuietOutput createProcessSuccess $ proc "rsync" $ toCommand $ diff --git a/Remote/S3.hs b/Remote/S3.hs index 8603757eb..4c1f1ecfd 100644 --- a/Remote/S3.hs +++ b/Remote/S3.hs @@ -57,8 +57,8 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost retrieveKeyFile = retreiveKeyFileDummy, retrieveKeyFileCheap = retrieveCheap this, removeKey = remove this c, - hasKey = checkPresent this, - hasKeyCheap = False, + checkPresent = checkKey this, + checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, repairRepo = Nothing, @@ -167,16 +167,16 @@ remove' :: Remote -> Key -> Annex Bool remove' r k = s3Action r False $ \(conn, bucket) -> s3Bool =<< liftIO (deleteObject conn $ bucketKey r bucket k) -checkPresent :: Remote -> Key -> Annex (Either String Bool) -checkPresent r k = s3Action r noconn $ \(conn, bucket) -> do +checkKey :: Remote -> Key -> Annex Bool +checkKey r k = s3Action r noconn $ \(conn, bucket) -> do showAction $ "checking " ++ name r res <- liftIO $ getObjectInfo conn $ bucketKey r bucket k case res of - Right _ -> return $ Right True - Left (AWSError _ _) -> return $ Right False - Left e -> return $ Left (s3Error e) + Right _ -> return True + Left (AWSError _ _) -> return False + Left e -> s3Error e where - noconn = Left $ error "S3 not configured" + noconn = error "S3 not configured" s3Warning :: ReqError -> Annex Bool s3Warning e = do diff --git a/Remote/Tahoe.hs b/Remote/Tahoe.hs index d265d7ac1..6e52c0981 100644 --- a/Remote/Tahoe.hs +++ b/Remote/Tahoe.hs @@ -72,8 +72,8 @@ gen r u c gc = do retrieveKeyFile = retrieve u hdl, retrieveKeyFileCheap = \_ _ -> return False, removeKey = remove, - hasKey = checkPresent u hdl, - hasKeyCheap = False, + checkPresent = checkKey u hdl, + checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, repairRepo = Nothing, @@ -123,14 +123,16 @@ remove _k = do warning "content cannot be removed from tahoe remote" return False -checkPresent :: UUID -> TahoeHandle -> Key -> Annex (Either String Bool) -checkPresent u hdl k = go =<< getCapability u k +checkKey :: UUID -> TahoeHandle -> Key -> Annex Bool +checkKey u hdl k = go =<< getCapability u k where - go Nothing = return (Right False) - go (Just cap) = liftIO $ parseCheck <$> readTahoe hdl "check" - [ Param "--raw" - , Param cap - ] + go Nothing = return False + go (Just cap) = liftIO $ do + v <- parseCheck <$> readTahoe hdl "check" + [ Param "--raw" + , Param cap + ] + either error return v defaultTahoeConfigDir :: UUID -> IO TahoeConfigDir defaultTahoeConfigDir u = do diff --git a/Remote/Web.hs b/Remote/Web.hs index ddd1fc1cc..7bdd8d185 100644 --- a/Remote/Web.hs +++ b/Remote/Web.hs @@ -50,8 +50,8 @@ gen r _ c gc = retrieveKeyFile = downloadKey, retrieveKeyFileCheap = downloadKeyCheap, removeKey = dropKey, - hasKey = checkKey, - hasKeyCheap = False, + checkPresent = checkKey, + checkPresentCheap = False, whereisKey = Just getUrls, remoteFsck = Nothing, repairRepo = Nothing, @@ -98,12 +98,12 @@ dropKey k = do mapM_ (setUrlMissing k) =<< getUrls k return True -checkKey :: Key -> Annex (Either String Bool) +checkKey :: Key -> Annex Bool checkKey key = do us <- getUrls key if null us - then return $ Right False - else return =<< checkKey' key us + then return False + else either error return =<< checkKey' key us checkKey' :: Key -> [URLString] -> Annex (Either String Bool) checkKey' key us = firsthit us (Right False) $ \u -> do let (u', downloader) = getDownloader u diff --git a/Remote/WebDAV.hs b/Remote/WebDAV.hs index 0bdd38360..f0bcac10e 100644 --- a/Remote/WebDAV.hs +++ b/Remote/WebDAV.hs @@ -63,8 +63,8 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost retrieveKeyFile = retrieve this, retrieveKeyFileCheap = retrieveCheap this, removeKey = remove this, - hasKey = checkPresent this, - hasKeyCheap = False, + checkPresent = checkKey this, + checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, repairRepo = Nothing, @@ -170,10 +170,10 @@ remove r k = davAction r False $ \(baseurl, user, pass) -> liftIO $ do let url = davLocation baseurl k isJust . eitherToMaybe <$> tryNonAsync (deleteDAV url user pass) -checkPresent :: Remote -> Key -> Annex (Either String Bool) -checkPresent r k = davAction r noconn go +checkKey :: Remote -> Key -> Annex Bool +checkKey r k = davAction r noconn (either error id <$$> go) where - noconn = Left $ error $ name r ++ " not configured" + noconn = error $ name r ++ " not configured" go (baseurl, user, pass) = do showAction $ "checking " ++ name r diff --git a/Types/Remote.hs b/Types/Remote.hs index 805b98474..b657cfcdc 100644 --- a/Types/Remote.hs +++ b/Types/Remote.hs @@ -68,12 +68,12 @@ data RemoteA a = Remote { retrieveKeyFileCheap :: Key -> FilePath -> a Bool, -- removes a key's contents (succeeds if the contents are not present) removeKey :: Key -> a Bool, - -- Checks if a key is present in the remote; if the remote - -- cannot be accessed returns a Left error message. - hasKey :: Key -> a (Either String Bool), - -- Some remotes can check hasKey without an expensive network + -- Checks if a key is present in the remote. + -- Throws an exception if the remote cannot be accessed. + checkPresent :: Key -> a Bool, + -- Some remotes can checkPresent without an expensive network -- operation. - hasKeyCheap :: Bool, + checkPresentCheap :: Bool, -- Some remotes can provide additional details for whereis. whereisKey :: Maybe (Key -> a [String]), -- Some remotes can run a fsck operation on the remote, diff --git a/Types/StoreRetrieve.hs b/Types/StoreRetrieve.hs index 9fc0634c4..a21fa7866 100644 --- a/Types/StoreRetrieve.hs +++ b/Types/StoreRetrieve.hs @@ -33,3 +33,11 @@ type Storer = Key -> ContentSource -> MeterUpdate -> Annex Bool -- callback, which will fully consume the content before returning. -- Throws exception if key is not present, or remote is not accessible. type Retriever = Key -> MeterUpdate -> (ContentSource -> Annex Bool) -> Annex Bool + +-- Action that removes a Key's content from a remote. +-- Succeeds if key is already not present; never throws exceptions. +type Remover = Key -> Annex Bool + +-- Checks if a Key's content is present on a remote. +-- Throws an exception if the remote is not accessible. +type CheckPresent = Key -> Annex Bool diff --git a/doc/design/assistant/chunks.mdwn b/doc/design/assistant/chunks.mdwn index a9709a778..0aa389899 100644 --- a/doc/design/assistant/chunks.mdwn +++ b/doc/design/assistant/chunks.mdwn @@ -91,7 +91,7 @@ cannot tell when we've gotten the last chunk. (Also, we cannot strip padding.) Note that `addurl` sometimes generates keys w/o size info (particularly, it does so by design when using quvi). -Problem: Also, this makes `hasKey` hard to implement: How can it know if +Problem: Also, this makes `checkPresent` hard to implement: How can it know if all the chunks are present, if the key size is not known? Problem: Also, this makes it difficult to download encrypted keys, because @@ -111,7 +111,7 @@ So, SHA256-1048576-c1--xxxxxxx for the first chunk of 1 megabyte. Before any chunks are stored, write a chunkcount file, eg SHA256-s12345-c0--xxxxxxx. Note that this key is the same as the original object's key, except with chunk number set to 0. This file contains both -the number of chunks, and also the chunk size used. `hasKey` downloads this +the number of chunks, and also the chunk size used. `checkPresent` downloads this file, and then verifies that each chunk is present, looking for keys with the expected chunk numbers and chunk size. @@ -126,7 +126,7 @@ Note: This design lets an attacker with logs tell the (appoximate) size of objects, by finding the small files that contain a chunk count, and correlating when that is written/read and when other files are written/read. That could be solved by padding the chunkcount key up to the -size of the rest of the keys, but that's very innefficient; `hasKey` is not +size of the rest of the keys, but that's very innefficient; `checkPresent` is not designed to need to download large files. # design 3 @@ -139,7 +139,7 @@ This seems difficult; attacker could probably tell where the first encrypted part stops and the next encrypted part starts by looking for gpg headers, and so tell which files are the first chunks. -Also, `hasKey` would need to download some or all of the first file. +Also, `checkPresent` would need to download some or all of the first file. If all, that's a lot more expensive. If only some is downloaded, an attacker can guess that the file that was partially downloaded is the first chunk in a series, and wait for a time when it's fully downloaded to @@ -163,7 +163,7 @@ The location log does not record locations of individual chunk keys (too space-inneficient). Instead, look at a chunk log in the git-annex branch to get the chunk count and size for a key. -`hasKey` would check if any of the logged sets of chunks is +`checkPresent` would check if any of the logged sets of chunks is present on the remote. It would also check if the non-chunked key is present, as a fallback. @@ -225,7 +225,7 @@ Reasons: Note that this means that the chunks won't exactly match the configured chunk size. gpg does compression, which might make them a -lot smaller. Or gpg overhead could make them slightly larger. So `hasKey` +lot smaller. Or gpg overhead could make them slightly larger. So `checkPresent` cannot check exact file sizes. If padding is enabled, gpg compression should be disabled, to not leak @@ -250,10 +250,10 @@ and skip forward to the next needed chunk. Easy. Uploads: Check if the 1st chunk is present. If so, check the second chunk, etc. Once the first missing chunk is found, start uploading from there. -That adds one extra hasKey call per upload. Probably a win in most cases. +That adds one extra checkPresent call per upload. Probably a win in most cases. Can be improved by making special remotes open a persistent connection that is used for transferring all chunks, as well as for -checking hasKey. +checking checkPresent. Note that this is safe to do only as long as the Key being transferred cannot possibly have 2 different contents in different repos. Notably not -- cgit v1.2.3 From efe30b0e402200a017d275ea2c93e0ceb8e3ec42 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 6 Aug 2014 14:28:36 -0400 Subject: run Preparer to get Remover and CheckPresent actions This will allow special remotes to eg, open a http connection and reuse it, while checking if chunks are present, or removing chunks. S3 and WebDAV both need this to support chunks with reasonable speed. Note that a special remote might want to cache a http connection across multiple requests. A simple case of this is that CheckPresent is typically called before Store or Remove. A remote using this interface can certianly use a Preparer that eg, uses a MVar to cache a http connection. However, it's up to the remote to then deal with things like stale or stalled http connections when eg, doing a series of downloads from a remote and other places. There could be long delays between calls to a remote, which could lead to eg, http connection stalls; the machine might even move to a new network, etc. It might be nice to improve this interface later to allow the simple case without needing to handle the full complex case. One way to do it would be to have a `Transaction SpecialRemote cache`, where SpecialRemote contains methods for Storer, Retriever, Remover, and CheckPresent, that all expect to be passed a `cache`. --- Remote/Bup.hs | 10 ++++++---- Remote/Ddar.hs | 10 ++++++---- Remote/Directory.hs | 10 ++++++---- Remote/External.hs | 10 ++++++---- Remote/GCrypt.hs | 10 ++++++---- Remote/Glacier.hs | 10 ++++++---- Remote/Helper/Messages.hs | 14 ++++++++++++-- Remote/Helper/Special.hs | 40 +++++++++++++++++++++++++++++----------- Remote/Hook.hs | 10 ++++++---- Remote/Rsync.hs | 10 ++++++---- Remote/S3.hs | 16 +++++++++------- 11 files changed, 98 insertions(+), 52 deletions(-) (limited to 'Remote/Helper/Special.hs') diff --git a/Remote/Bup.hs b/Remote/Bup.hs index 2e68f30ef..80fffc056 100644 --- a/Remote/Bup.hs +++ b/Remote/Bup.hs @@ -57,8 +57,8 @@ gen r u c gc = do , storeKey = storeKeyDummy , retrieveKeyFile = retreiveKeyFileDummy , retrieveKeyFileCheap = retrieveCheap buprepo - , removeKey = remove buprepo - , checkPresent = checkKey r bupr' + , removeKey = removeKeyDummy + , checkPresent = checkPresentDummy , checkPresentCheap = bupLocal buprepo , whereisKey = Nothing , remoteFsck = Nothing @@ -76,6 +76,8 @@ gen r u c gc = do return $ Just $ specialRemote' specialcfg c (simplyPrepare $ store this buprepo) (simplyPrepare $ retrieve buprepo) + (simplyPrepare $ remove buprepo) + (simplyPrepare $ checkKey r bupr') this where buprepo = fromMaybe (error "missing buprepo") $ remoteAnnexBupRepo gc @@ -146,7 +148,7 @@ retrieveCheap _ _ _ = return False - - We can, however, remove the git branch that bup created for the key. -} -remove :: BupRepo -> Key -> Annex Bool +remove :: BupRepo -> Remover remove buprepo k = do go =<< liftIO (bup2GitRemote buprepo) warning "content cannot be completely removed from bup remote" @@ -163,7 +165,7 @@ remove buprepo k = do - in a bup repository. One way it to check if the git repository has - a branch matching the name (as created by bup split -n). -} -checkKey :: Git.Repo -> Git.Repo -> Key -> Annex Bool +checkKey :: Git.Repo -> Git.Repo -> CheckPresent checkKey r bupr k | Git.repoIsUrl bupr = do showChecking r diff --git a/Remote/Ddar.hs b/Remote/Ddar.hs index 1227b5275..fba05312b 100644 --- a/Remote/Ddar.hs +++ b/Remote/Ddar.hs @@ -44,6 +44,8 @@ gen r u c gc = do return $ Just $ specialRemote' specialcfg c (simplyPrepare $ store ddarrepo) (simplyPrepare $ retrieve ddarrepo) + (simplyPrepare $ remove ddarrepo) + (simplyPrepare $ checkKey ddarrepo) (this cst) where this cst = Remote @@ -53,8 +55,8 @@ gen r u c gc = do , storeKey = storeKeyDummy , retrieveKeyFile = retreiveKeyFileDummy , retrieveKeyFileCheap = retrieveCheap - , removeKey = remove ddarrepo - , checkPresent = checkKey ddarrepo + , removeKey = removeKeyDummy + , checkPresent = checkPresentDummy , checkPresentCheap = ddarLocal ddarrepo , whereisKey = Nothing , remoteFsck = Nothing @@ -140,7 +142,7 @@ retrieve ddarrepo = byteRetriever $ \k sink -> do retrieveCheap :: Key -> FilePath -> Annex Bool retrieveCheap _ _ = return False -remove :: DdarRepo -> Key -> Annex Bool +remove :: DdarRepo -> Remover remove ddarrepo key = do (cmd, params) <- ddarRemoteCall ddarrepo 'd' [Param $ key2file key] liftIO $ boolSystem cmd params @@ -181,7 +183,7 @@ inDdarManifest ddarrepo k = do where k' = key2file k -checkKey :: DdarRepo -> Key -> Annex Bool +checkKey :: DdarRepo -> CheckPresent checkKey ddarrepo key = do directoryExists <- ddarDirectoryExists ddarrepo case directoryExists of diff --git a/Remote/Directory.hs b/Remote/Directory.hs index 0a2532aa5..d9419757f 100644 --- a/Remote/Directory.hs +++ b/Remote/Directory.hs @@ -44,6 +44,8 @@ gen r u c gc = do return $ Just $ specialRemote c (prepareStore dir chunkconfig) (retrieve dir chunkconfig) + (simplyPrepare $ remove dir) + (simplyPrepare $ checkKey dir chunkconfig) Remote { uuid = u, cost = cst, @@ -51,8 +53,8 @@ gen r u c gc = do storeKey = storeKeyDummy, retrieveKeyFile = retreiveKeyFileDummy, retrieveKeyFileCheap = retrieveCheap dir chunkconfig, - removeKey = remove dir, - checkPresent = checkKey dir chunkconfig, + removeKey = removeKeyDummy, + checkPresent = checkPresentDummy, checkPresentCheap = True, whereisKey = Nothing, remoteFsck = Nothing, @@ -161,7 +163,7 @@ retrieveCheap d NoChunks k f = liftIO $ catchBoolIO $ do retrieveCheap _ _ _ _ = return False #endif -remove :: FilePath -> Key -> Annex Bool +remove :: FilePath -> Remover remove d k = liftIO $ removeDirGeneric d (storeDir d k) {- Removes the directory, which must be located under the topdir. @@ -189,7 +191,7 @@ removeDirGeneric topdir dir = do then return ok else doesDirectoryExist topdir <&&> (not <$> doesDirectoryExist dir) -checkKey :: FilePath -> ChunkConfig -> Key -> Annex Bool +checkKey :: FilePath -> ChunkConfig -> CheckPresent checkKey d (LegacyChunks _) k = Legacy.checkKey d locations k checkKey d _ k = liftIO $ ifM (anyM doesFileExist (locations d k)) diff --git a/Remote/External.hs b/Remote/External.hs index ffae94ec9..f326f26ba 100644 --- a/Remote/External.hs +++ b/Remote/External.hs @@ -45,6 +45,8 @@ gen r u c gc = do return $ Just $ specialRemote c (simplyPrepare $ store external) (simplyPrepare $ retrieve external) + (simplyPrepare $ remove external) + (simplyPrepare $ checkKey external) Remote { uuid = u, cost = cst, @@ -52,8 +54,8 @@ gen r u c gc = do storeKey = storeKeyDummy, retrieveKeyFile = retreiveKeyFileDummy, retrieveKeyFileCheap = \_ _ -> return False, - removeKey = remove external, - checkPresent = checkKey external, + removeKey = removeKeyDummy, + checkPresent = checkPresentDummy, checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, @@ -109,7 +111,7 @@ retrieve external = fileRetriever $ \d k p -> error errmsg _ -> Nothing -remove :: External -> Key -> Annex Bool +remove :: External -> Remover remove external k = safely $ handleRequest external (REMOVE k) Nothing $ \resp -> case resp of @@ -121,7 +123,7 @@ remove external k = safely $ return False _ -> Nothing -checkKey :: External -> Key -> Annex Bool +checkKey :: External -> CheckPresent checkKey external k = either error id <$> go where go = handleRequest external (CHECKPRESENT k) Nothing $ \resp -> diff --git a/Remote/GCrypt.hs b/Remote/GCrypt.hs index f971ff754..55a775811 100644 --- a/Remote/GCrypt.hs +++ b/Remote/GCrypt.hs @@ -107,8 +107,8 @@ gen' r u c gc = do , storeKey = storeKeyDummy , retrieveKeyFile = retreiveKeyFileDummy , retrieveKeyFileCheap = \_ _ -> return False - , removeKey = remove this rsyncopts - , checkPresent = checkKey this rsyncopts + , removeKey = removeKeyDummy + , checkPresent = checkPresentDummy , checkPresentCheap = repoCheap r , whereisKey = Nothing , remoteFsck = Nothing @@ -124,6 +124,8 @@ gen' r u c gc = do return $ Just $ specialRemote' specialcfg c (simplyPrepare $ store this rsyncopts) (simplyPrepare $ retrieve this rsyncopts) + (simplyPrepare $ remove this rsyncopts) + (simplyPrepare $ checkKey this rsyncopts) this where specialcfg @@ -331,7 +333,7 @@ retrieve r rsyncopts | otherwise = unsupportedUrl where -remove :: Remote -> Remote.Rsync.RsyncOpts -> Key -> Annex Bool +remove :: Remote -> Remote.Rsync.RsyncOpts -> Remover remove r rsyncopts k | not $ Git.repoIsUrl (repo r) = guardUsable (repo r) False $ liftIO $ Remote.Directory.removeDirGeneric (Git.repoLocation (repo r)) (parentDir (gCryptLocation r k)) @@ -341,7 +343,7 @@ remove r rsyncopts k removersync = Remote.Rsync.remove rsyncopts k removeshell = Ssh.dropKey (repo r) k -checkKey :: Remote -> Remote.Rsync.RsyncOpts -> Key -> Annex Bool +checkKey :: Remote -> Remote.Rsync.RsyncOpts -> CheckPresent checkKey r rsyncopts k | not $ Git.repoIsUrl (repo r) = guardUsable (repo r) (cantCheck $ repo r) $ diff --git a/Remote/Glacier.hs b/Remote/Glacier.hs index 2ade37011..dd28def63 100644 --- a/Remote/Glacier.hs +++ b/Remote/Glacier.hs @@ -42,6 +42,8 @@ gen r u c gc = new <$> remoteCost gc veryExpensiveRemoteCost new cst = Just $ specialRemote' specialcfg c (prepareStore this) (prepareRetrieve this) + (simplyPrepare $ remove this) + (simplyPrepare $ checkKey this) this where this = Remote { @@ -51,8 +53,8 @@ gen r u c gc = new <$> remoteCost gc veryExpensiveRemoteCost storeKey = storeKeyDummy, retrieveKeyFile = retreiveKeyFileDummy, retrieveKeyFileCheap = retrieveCheap this, - removeKey = remove this, - checkPresent = checkKey this, + removeKey = removeKeyDummy, + checkPresent = checkPresentDummy, checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, @@ -155,7 +157,7 @@ retrieve r k sink = go =<< glacierEnv c u retrieveCheap :: Remote -> Key -> FilePath -> Annex Bool retrieveCheap _ _ _ = return False -remove :: Remote -> Key -> Annex Bool +remove :: Remote -> Remover remove r k = glacierAction r [ Param "archive" @@ -164,7 +166,7 @@ remove r k = glacierAction r , Param $ archive r k ] -checkKey :: Remote -> Key -> Annex Bool +checkKey :: Remote -> CheckPresent checkKey r k = do showAction $ "checking " ++ name r go =<< glacierEnv (config r) (uuid r) diff --git a/Remote/Helper/Messages.hs b/Remote/Helper/Messages.hs index 3088a9ab2..774716ca1 100644 --- a/Remote/Helper/Messages.hs +++ b/Remote/Helper/Messages.hs @@ -9,9 +9,19 @@ module Remote.Helper.Messages where import Common.Annex import qualified Git +import qualified Types.Remote as Remote showChecking :: Git.Repo -> Annex () showChecking r = showAction $ "checking " ++ Git.repoDescribe r -cantCheck :: Git.Repo -> a -cantCheck r = error $ "unable to check " ++ Git.repoDescribe r +class Checkable a where + descCheckable :: a -> String + +instance Checkable Git.Repo where + descCheckable = Git.repoDescribe + +instance Checkable (Remote.RemoteA a) where + descCheckable = Remote.name + +cantCheck :: Checkable a => a -> e +cantCheck v = error $ "unable to check " ++ descCheckable v diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs index 3c19f25eb..f8428aff7 100644 --- a/Remote/Helper/Special.hs +++ b/Remote/Helper/Special.hs @@ -11,6 +11,8 @@ module Remote.Helper.Special ( Preparer, Storer, Retriever, + Remover, + CheckPresent, simplyPrepare, ContentSource, checkPrepare, @@ -21,6 +23,8 @@ module Remote.Helper.Special ( byteRetriever, storeKeyDummy, retreiveKeyFileDummy, + removeKeyDummy, + checkPresentDummy, SpecialRemoteCfg(..), specialRemoteCfg, specialRemote, @@ -36,6 +40,7 @@ import Config.Cost import Utility.Metered import Remote.Helper.Chunked as X import Remote.Helper.Encryptable as X hiding (encryptableRemote) +import Remote.Helper.Messages import Annex.Content import Annex.Exception import qualified Git @@ -114,16 +119,27 @@ byteRetriever :: (Key -> (L.ByteString -> Annex Bool) -> Annex Bool) -> Retrieve byteRetriever a k _m callback = a k (callback . ByteContent) {- The base Remote that is provided to specialRemote needs to have - - storeKey and retreiveKeyFile methods, but they are never - - actually used (since specialRemote replaces them). + - storeKey, retreiveKeyFile, removeKey, and checkPresent methods, + - but they are never actually used (since specialRemote replaces them). - Here are some dummy ones. -} storeKeyDummy :: Key -> AssociatedFile -> MeterUpdate -> Annex Bool storeKeyDummy _ _ _ = return False retreiveKeyFileDummy :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool retreiveKeyFileDummy _ _ _ _ = return False +removeKeyDummy :: Key -> Annex Bool +removeKeyDummy _ = return False +checkPresentDummy :: Key -> Annex Bool +checkPresentDummy _ = error "missing checkPresent implementation" -type RemoteModifier = RemoteConfig -> Preparer Storer -> Preparer Retriever -> Remote -> Remote +type RemoteModifier + = RemoteConfig + -> Preparer Storer + -> Preparer Retriever + -> Preparer Remover + -> Preparer CheckPresent + -> Remote + -> Remote data SpecialRemoteCfg = SpecialRemoteCfg { chunkConfig :: ChunkConfig @@ -139,13 +155,14 @@ specialRemote :: RemoteModifier specialRemote c = specialRemote' (specialRemoteCfg c) c specialRemote' :: SpecialRemoteCfg -> RemoteModifier -specialRemote' cfg c preparestorer prepareretriever baser = encr +specialRemote' cfg c preparestorer prepareretriever prepareremover preparecheckpresent baser = encr where encr = baser { storeKey = \k _f p -> cip >>= storeKeyGen k p , retrieveKeyFile = \k _f d p -> cip >>= retrieveKeyFileGen k d p , retrieveKeyFileCheap = \k d -> cip >>= maybe (retrieveKeyFileCheap baser k d) + -- retrieval of encrypted keys is never cheap (\_ -> return False) , removeKey = \k -> cip >>= removeKeyGen k , checkPresent = \k -> cip >>= checkPresentGen k @@ -160,8 +177,7 @@ specialRemote' cfg c preparestorer prepareretriever baser = encr safely a = catchNonAsyncAnnex a (\e -> warning (show e) >> return False) -- chunk, then encrypt, then feed to the storer - storeKeyGen k p enc = - safely $ preparestorer k $ safely . go + storeKeyGen k p enc = safely $ preparestorer k $ safely . go where go (Just storer) = sendAnnex k rollback $ \src -> displayprogress p k $ \p' -> @@ -178,7 +194,7 @@ specialRemote' cfg c preparestorer prepareretriever baser = encr readBytes $ \encb -> storer (enck k) (ByteContent encb) p - -- call retriever to get chunks; decrypt them; stream to dest file + -- call retrieve-r to get chunks; decrypt them; stream to dest file retrieveKeyFileGen k dest p enc = safely $ prepareretriever k $ safely . go where @@ -188,15 +204,17 @@ specialRemote' cfg c preparestorer prepareretriever baser = encr go Nothing = return False enck = maybe id snd enc - removeKeyGen k enc = removeChunks remover (uuid baser) chunkconfig enck k + removeKeyGen k enc = safely $ prepareremover k $ safely . go where + go (Just remover) = removeChunks remover (uuid baser) chunkconfig enck k + go Nothing = return False enck = maybe id snd enc - remover = removeKey baser - checkPresentGen k enc = checkPresentChunks checker (uuid baser) chunkconfig enck k + checkPresentGen k enc = preparecheckpresent k go where + go (Just checker) = checkPresentChunks checker (uuid baser) chunkconfig enck k + go Nothing = cantCheck baser enck = maybe id snd enc - checker = checkPresent baser chunkconfig = chunkConfig cfg diff --git a/Remote/Hook.hs b/Remote/Hook.hs index 037f71ced..a2d096ecd 100644 --- a/Remote/Hook.hs +++ b/Remote/Hook.hs @@ -37,6 +37,8 @@ gen r u c gc = do return $ Just $ specialRemote c (simplyPrepare $ store hooktype) (simplyPrepare $ retrieve hooktype) + (simplyPrepare $ remove hooktype) + (simplyPrepare $ checkKey r hooktype) Remote { uuid = u, cost = cst, @@ -44,8 +46,8 @@ gen r u c gc = do storeKey = storeKeyDummy, retrieveKeyFile = retreiveKeyFileDummy, retrieveKeyFileCheap = retrieveCheap hooktype, - removeKey = remove hooktype, - checkPresent = checkKey r hooktype, + removeKey = removeKeyDummy, + checkPresent = checkPresentDummy, checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, @@ -125,10 +127,10 @@ retrieve h = fileRetriever $ \d k _p -> retrieveCheap :: HookName -> Key -> FilePath -> Annex Bool retrieveCheap _ _ _ = return False -remove :: HookName -> Key -> Annex Bool +remove :: HookName -> Remover remove h k = runHook h "remove" k Nothing $ return True -checkKey :: Git.Repo -> HookName -> Key -> Annex Bool +checkKey :: Git.Repo -> HookName -> CheckPresent checkKey r h k = do showAction $ "checking " ++ Git.repoDescribe r v <- lookupHook h action diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs index 91070fe84..afd13abf0 100644 --- a/Remote/Rsync.hs +++ b/Remote/Rsync.hs @@ -58,6 +58,8 @@ gen r u c gc = do return $ Just $ specialRemote' specialcfg c (simplyPrepare $ fileStorer $ store o) (simplyPrepare $ fileRetriever $ retrieve o) + (simplyPrepare $ remove o) + (simplyPrepare $ checkKey r o) Remote { uuid = u , cost = cst @@ -65,8 +67,8 @@ gen r u c gc = do , storeKey = storeKeyDummy , retrieveKeyFile = retreiveKeyFileDummy , retrieveKeyFileCheap = retrieveCheap o - , removeKey = remove o - , checkPresent = checkKey r o + , removeKey = removeKeyDummy + , checkPresent = checkPresentDummy , checkPresentCheap = False , whereisKey = Nothing , remoteFsck = Nothing @@ -186,7 +188,7 @@ retrieve o f k p = retrieveCheap :: RsyncOpts -> Key -> FilePath -> Annex Bool retrieveCheap o k f = ifM (preseedTmp k f) ( rsyncRetrieve o k f Nothing , return False ) -remove :: RsyncOpts -> Key -> Annex Bool +remove :: RsyncOpts -> Remover remove o k = do ps <- sendParams withRsyncScratchDir $ \tmp -> liftIO $ do @@ -214,7 +216,7 @@ remove o k = do , dir keyFile k "***" ] -checkKey :: Git.Repo -> RsyncOpts -> Key -> Annex Bool +checkKey :: Git.Repo -> RsyncOpts -> CheckPresent checkKey r o k = do showAction $ "checking " ++ Git.repoDescribe r -- note: Does not currently differentiate between rsync failing diff --git a/Remote/S3.hs b/Remote/S3.hs index 4c1f1ecfd..1aba39245 100644 --- a/Remote/S3.hs +++ b/Remote/S3.hs @@ -47,6 +47,8 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost new cst = Just $ specialRemote c (prepareStore this) (prepareRetrieve this) + (simplyPrepare $ remove this c) + (simplyPrepare $ checkKey this) this where this = Remote { @@ -55,9 +57,9 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost name = Git.repoDescribe r, storeKey = storeKeyDummy, retrieveKeyFile = retreiveKeyFileDummy, - retrieveKeyFileCheap = retrieveCheap this, - removeKey = remove this c, - checkPresent = checkKey this, + retrieveKeyFileCheap = retrieveCheap, + removeKey = removeKeyDummy, + checkPresent = checkPresentDummy, checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, @@ -150,13 +152,13 @@ prepareRetrieve r = resourcePrepare (const $ s3Action r False) $ \(conn, bucket) liftIO (getObject conn $ bucketKey r bucket k) >>= either s3Error (sink . obj_data) -retrieveCheap :: Remote -> Key -> FilePath -> Annex Bool -retrieveCheap _ _ _ = return False +retrieveCheap :: Key -> FilePath -> Annex Bool +retrieveCheap _ _ = return False {- Internet Archive doesn't easily allow removing content. - While it may remove the file, there are generally other files - derived from it that it does not remove. -} -remove :: Remote -> RemoteConfig -> Key -> Annex Bool +remove :: Remote -> RemoteConfig -> Remover remove r c k | isIA c = do warning "Cannot remove content from the Internet Archive" @@ -167,7 +169,7 @@ remove' :: Remote -> Key -> Annex Bool remove' r k = s3Action r False $ \(conn, bucket) -> s3Bool =<< liftIO (deleteObject conn $ bucketKey r bucket k) -checkKey :: Remote -> Key -> Annex Bool +checkKey :: Remote -> CheckPresent checkKey r k = s3Action r noconn $ \(conn, bucket) -> do showAction $ "checking " ++ name r res <- liftIO $ getObjectInfo conn $ bucketKey r bucket k -- cgit v1.2.3 From 79e7ac8abc030637209486e09dc0ede60c74bb02 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 6 Aug 2014 16:55:32 -0400 Subject: convert WebDAV to new special remote interface, adding new-style chunking support Reusing http connection when operating on chunks is not done yet, I had to submit some patches to DAV to support that. However, this is no slower than old-style chunking was. Note that it's a fileRetriever and a fileStorer, despite DAV using bytestrings that would allow streaming. As a result, upload/download of encrypted files is made a bit more expensive, since it spools them to temp files. This was needed to get the progress meters to work. There are probably ways to avoid that.. But it turns out that the current DAV interface buffers the whole file content in memory, and I have sent in a patch to DAV to improve its interfaces. Using the new interfaces, it's certainly going to need to be a fileStorer, in order to read the file size from the file (getting the size of a bytestring would destroy laziness). It should be possible to use the new interface to make it be a byteRetriever, so I'll change that when I get to it. This commit was sponsored by Andreas Olsson. --- Remote/Helper/Encryptable.hs | 38 ------------ Remote/Helper/Special.hs | 4 +- Remote/WebDAV.hs | 130 ++++++++++++++++------------------------ debian/changelog | 2 +- doc/special_remotes/webdav.mdwn | 2 +- 5 files changed, 54 insertions(+), 122 deletions(-) (limited to 'Remote/Helper/Special.hs') diff --git a/Remote/Helper/Encryptable.hs b/Remote/Helper/Encryptable.hs index c364a69e7..dd032ce33 100644 --- a/Remote/Helper/Encryptable.hs +++ b/Remote/Helper/Encryptable.hs @@ -14,9 +14,7 @@ import Types.Remote import Crypto import Types.Crypto import qualified Annex -import Config.Cost import Utility.Base64 -import Utility.Metered {- Encryption setup for a remote. The user must specify whether to use - an encryption key, or not encrypt. An encrypted cipher is created, or is @@ -70,42 +68,6 @@ encryptionSetup c = maybe genCipher updateCipher $ extractCipher c -- remotes (while being backward-compatible). [ "keyid", "keyid+", "keyid-", "highRandomQuality" ] -{- Modifies a Remote to support encryption. -} --- TODO: deprecated -encryptableRemote - :: RemoteConfig - -> ((Cipher, Key) -> Key -> MeterUpdate -> Annex Bool) - -> ((Cipher, Key) -> Key -> FilePath -> MeterUpdate -> Annex Bool) - -> Remote - -> Remote -encryptableRemote c storeKeyEncrypted retrieveKeyFileEncrypted r = r - { storeKey = \k f p -> cip k >>= maybe - (storeKey r k f p) - (\v -> storeKeyEncrypted v k p) - , retrieveKeyFile = \k f d p -> cip k >>= maybe - (retrieveKeyFile r k f d p) - (\v -> retrieveKeyFileEncrypted v k d p) - , retrieveKeyFileCheap = \k d -> cip k >>= maybe - (retrieveKeyFileCheap r k d) - (\_ -> return False) - , removeKey = \k -> cip k >>= maybe - (removeKey r k) - (\(_, enckey) -> removeKey r enckey) - , checkPresent = \k -> cip k >>= maybe - (checkPresent r k) - (\(_, enckey) -> checkPresent r enckey) - , cost = maybe - (cost r) - (const $ cost r + encryptedRemoteCostAdj) - (extractCipher c) - } - where - cip k = do - v <- cipherKey c - return $ case v of - Nothing -> Nothing - Just (cipher, enck) -> Just (cipher, enck k) - {- Gets encryption Cipher. The decrypted Ciphers are cached in the Annex - state. -} remoteCipher :: RemoteConfig -> Annex (Maybe Cipher) diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs index f8428aff7..fc0e11d2f 100644 --- a/Remote/Helper/Special.hs +++ b/Remote/Helper/Special.hs @@ -39,7 +39,7 @@ import Crypto import Config.Cost import Utility.Metered import Remote.Helper.Chunked as X -import Remote.Helper.Encryptable as X hiding (encryptableRemote) +import Remote.Helper.Encryptable as X import Remote.Helper.Messages import Annex.Content import Annex.Exception @@ -119,7 +119,7 @@ byteRetriever :: (Key -> (L.ByteString -> Annex Bool) -> Annex Bool) -> Retrieve byteRetriever a k _m callback = a k (callback . ByteContent) {- The base Remote that is provided to specialRemote needs to have - - storeKey, retreiveKeyFile, removeKey, and checkPresent methods, + - storeKey, retrieveKeyFile, removeKey, and checkPresent methods, - but they are never actually used (since specialRemote replaces them). - Here are some dummy ones. -} diff --git a/Remote/WebDAV.hs b/Remote/WebDAV.hs index f0bcac10e..6679242e5 100644 --- a/Remote/WebDAV.hs +++ b/Remote/WebDAV.hs @@ -27,12 +27,9 @@ import qualified Git import Config import Config.Cost import Remote.Helper.Special -import Remote.Helper.Encryptable import qualified Remote.Helper.Chunked.Legacy as Legacy -import Crypto import Creds import Utility.Metered -import Annex.Content import Annex.UUID import Remote.WebDAV.DavUrl @@ -50,20 +47,22 @@ remote = RemoteType { gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote) gen r u c gc = new <$> remoteCost gc expensiveRemoteCost where - new cst = Just $ encryptableRemote c - (storeEncrypted this) - (retrieveEncrypted this) + new cst = Just $ specialRemote c + (prepareStore this chunkconfig) + (prepareRetrieve this chunkconfig) + (prepareRemove this) + (prepareCheckPresent this chunkconfig) this where this = Remote { uuid = u, cost = cst, name = Git.repoDescribe r, - storeKey = store this, - retrieveKeyFile = retrieve this, - retrieveKeyFileCheap = retrieveCheap this, - removeKey = remove this, - checkPresent = checkKey this, + storeKey = storeKeyDummy, + retrieveKeyFile = retreiveKeyFileDummy, + retrieveKeyFileCheap = retrieveCheap, + removeKey = removeKeyDummy, + checkPresent = checkPresentDummy, checkPresentCheap = False, whereisKey = Nothing, remoteFsck = Nothing, @@ -76,6 +75,7 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost availability = GloballyAvailable, remotetype = remote } + chunkconfig = getChunkConfig c webdavSetup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> Annex (RemoteConfig, UUID) webdavSetup mu mcreds c = do @@ -89,95 +89,67 @@ webdavSetup mu mcreds c = do c'' <- setRemoteCredPair c' (davCreds u) creds return (c'', u) -store :: Remote -> Key -> AssociatedFile -> MeterUpdate -> Annex Bool -store r k _f p = metered (Just p) k $ \meterupdate -> - davAction r False $ \(baseurl, user, pass) -> - sendAnnex k (void $ remove r k) $ \src -> - liftIO $ withMeteredFile src meterupdate $ - storeHelper r k baseurl user pass - -storeEncrypted :: Remote -> (Cipher, Key) -> Key -> MeterUpdate -> Annex Bool -storeEncrypted r (cipher, enck) k p = metered (Just p) k $ \meterupdate -> - davAction r False $ \(baseurl, user, pass) -> - sendAnnex k (void $ remove r enck) $ \src -> - liftIO $ encrypt (getGpgEncParams r) cipher - (streamMeteredFile src meterupdate) $ - readBytes $ storeHelper r enck baseurl user pass - -storeHelper :: Remote -> Key -> DavUrl -> DavUser -> DavPass -> L.ByteString -> IO Bool -storeHelper r k baseurl user pass b = catchBoolIO $ do +prepareStore :: Remote -> ChunkConfig -> Preparer Storer +prepareStore r chunkconfig = simplyPrepare $ fileStorer $ \k f p -> + davAction r False $ \(baseurl, user, pass) -> liftIO $ + withMeteredFile f p $ + storeHelper chunkconfig k baseurl user pass + +storeHelper :: ChunkConfig -> Key -> DavUrl -> DavUser -> DavPass -> L.ByteString -> IO Bool +storeHelper chunkconfig k baseurl user pass b = do mkdirRecursiveDAV tmpurl user pass case chunkconfig of - NoChunks -> flip catchNonAsync (\e -> warningIO (show e) >> return False) $ do - storehttp tmpurl b - finalizer tmpurl keyurl - return True - UnpaddedChunks _ -> error "TODO: storeHelper with UnpaddedChunks" LegacyChunks chunksize -> do let storer urls = Legacy.storeChunked chunksize urls storehttp b let recorder url s = storehttp url (L8.fromString s) Legacy.storeChunks k tmpurl keyurl storer recorder finalizer - + _ -> do + storehttp tmpurl b + finalizer tmpurl keyurl + return True where tmpurl = tmpLocation baseurl k keyurl = davLocation baseurl k - chunkconfig = getChunkConfig $ config r finalizer srcurl desturl = do void $ tryNonAsync (deleteDAV desturl user pass) mkdirRecursiveDAV (urlParent desturl) user pass moveDAV srcurl desturl user pass storehttp url = putDAV url user pass -retrieveCheap :: Remote -> Key -> FilePath -> Annex Bool -retrieveCheap _ _ _ = return False +retrieveCheap :: Key -> FilePath -> Annex Bool +retrieveCheap _ _ = return False -retrieve :: Remote -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool -retrieve r k _f d p = metered (Just p) k $ \meterupdate -> - davAction r False $ \(baseurl, user, pass) -> liftIO $ catchBoolIO $ - withStoredFiles r k baseurl user pass onerr $ \urls -> do - Legacy.meteredWriteFileChunks meterupdate d urls $ \url -> do +prepareRetrieve :: Remote -> ChunkConfig -> Preparer Retriever +prepareRetrieve r chunkconfig = simplyPrepare $ fileRetriever $ \d k p -> + davAction r onerr $ \(baseurl, user, pass) -> liftIO $ + withStoredFiles chunkconfig k baseurl user pass onerr $ \urls -> do + Legacy.meteredWriteFileChunks p d urls $ \url -> do mb <- getDAV url user pass case mb of - Nothing -> throwIO "download failed" + Nothing -> onerr Just b -> return b - return True - where - onerr _ = return False - -retrieveEncrypted :: Remote -> (Cipher, Key) -> Key -> FilePath -> MeterUpdate -> Annex Bool -retrieveEncrypted r (cipher, enck) k d p = metered (Just p) k $ \meterupdate -> - davAction r False $ \(baseurl, user, pass) -> liftIO $ catchBoolIO $ - withStoredFiles r enck baseurl user pass onerr $ \urls -> do - decrypt cipher (feeder user pass urls) $ - readBytes $ meteredWriteFile meterupdate d - return True where - onerr _ = return False - - feeder _ _ [] _ = noop - feeder user pass (url:urls) h = do - mb <- getDAV url user pass - case mb of - Nothing -> throwIO "download failed" - Just b -> do - L.hPut h b - feeder user pass urls h - -remove :: Remote -> Key -> Annex Bool -remove r k = davAction r False $ \(baseurl, user, pass) -> liftIO $ do - -- Delete the key's whole directory, including any chunked - -- files, etc, in a single action. - let url = davLocation baseurl k - isJust . eitherToMaybe <$> tryNonAsync (deleteDAV url user pass) - -checkKey :: Remote -> Key -> Annex Bool -checkKey r k = davAction r noconn (either error id <$$> go) + onerr = error "download failed" + +prepareRemove :: Remote -> Preparer Remover +prepareRemove r = simplyPrepare $ \k -> + davAction r False $ \(baseurl, user, pass) -> liftIO $ do + -- Delete the key's whole directory, including any + -- legacy chunked files, etc, in a single action. + let url = davLocation baseurl k + isJust . eitherToMaybe <$> tryNonAsync (deleteDAV url user pass) + +prepareCheckPresent :: Remote -> ChunkConfig -> Preparer CheckPresent +prepareCheckPresent r chunkconfig = simplyPrepare $ checkKey r chunkconfig + +checkKey :: Remote -> ChunkConfig -> Key -> Annex Bool +checkKey r chunkconfig k = davAction r noconn (either error id <$$> go) where noconn = error $ name r ++ " not configured" go (baseurl, user, pass) = do showAction $ "checking " ++ name r - liftIO $ withStoredFiles r k baseurl user pass onerr check + liftIO $ withStoredFiles chunkconfig k baseurl user pass onerr check where check [] = return $ Right True check (url:urls) = do @@ -196,7 +168,7 @@ checkKey r k = davAction r noconn (either error id <$$> go) else v withStoredFiles - :: Remote + :: ChunkConfig -> Key -> DavUrl -> DavUser @@ -204,9 +176,7 @@ withStoredFiles -> (DavUrl -> IO a) -> ([DavUrl] -> IO a) -> IO a -withStoredFiles r k baseurl user pass onerr a = case chunkconfig of - NoChunks -> a [keyurl] - UnpaddedChunks _ -> error "TODO: withStoredFiles with UnpaddedChunks" +withStoredFiles chunkconfig k baseurl user pass onerr a = case chunkconfig of LegacyChunks _ -> do let chunkcount = keyurl ++ Legacy.chunkCount v <- getDAV chunkcount user pass @@ -217,9 +187,9 @@ withStoredFiles r k baseurl user pass onerr a = case chunkconfig of if null chunks then onerr chunkcount else a chunks + _ -> a [keyurl] where keyurl = davLocation baseurl k ++ keyFile k - chunkconfig = getChunkConfig $ config r davAction :: Remote -> a -> ((DavUrl, DavUser, DavPass) -> Annex a) -> Annex a davAction r unconfigured action = do diff --git a/debian/changelog b/debian/changelog index 8da5b87bb..6d13c9637 100644 --- a/debian/changelog +++ b/debian/changelog @@ -1,7 +1,7 @@ git-annex (5.20140718) UNRELEASED; urgency=medium * New chunk= option to chunk files stored in special remotes. - Supported by: directory, S3, gcrypt, rsync, and all external + Supported by: directory, S3, webdav, gcrypt, rsync, and all external and hook special remotes. * Partially transferred files are automatically resumed when using chunked remotes! diff --git a/doc/special_remotes/webdav.mdwn b/doc/special_remotes/webdav.mdwn index 64eed5d0b..6b5f5b122 100644 --- a/doc/special_remotes/webdav.mdwn +++ b/doc/special_remotes/webdav.mdwn @@ -37,4 +37,4 @@ the webdav remote. Setup example: - # WEBDAV_USERNAME=joey@kitenet.net WEBDAV_PASSWORD=xxxxxxx git annex initremote box.com type=webdav url=https://dav.box.com/dav/git-annex chunksize=75mb keyid=joey@kitenet.net + # WEBDAV_USERNAME=joey@kitenet.net WEBDAV_PASSWORD=xxxxxxx git annex initremote box.com type=webdav url=https://dav.box.com/dav/git-annex chunk=10mb keyid=joey@kitenet.net -- cgit v1.2.3 From 69ef3f1025fb32a19f03517d072c1e64dcb326b7 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 7 Aug 2014 21:55:44 -0400 Subject: unify exception handling into Utility.Exception Removed old extensible-exceptions, only needed for very old ghc. Made webdav use Utility.Exception, to work after some changes in DAV's exception handling. Removed Annex.Exception. Mostly this was trivial, but note that tryAnnex is replaced with tryNonAsync and catchAnnex replaced with catchNonAsync. In theory that could be a behavior change, since the former caught all exceptions, and the latter don't catch async exceptions. However, in practice, nothing in the Annex monad uses async exceptions. Grepping for throwTo and killThread only find stuff in the assistant, which does not seem related. Command.Add.undo is changed to accept a SomeException, and things that use it for rollback now catch non-async exceptions, rather than only IOExceptions. --- Annex.hs | 6 ++-- Annex/Content.hs | 5 ++- Annex/Direct.hs | 3 +- Annex/Drop.hs | 3 +- Annex/Environment.hs | 3 +- Annex/Exception.hs | 63 -------------------------------------- Annex/Index.hs | 3 +- Annex/Journal.hs | 1 - Annex/LockFile.hs | 1 - Annex/Perms.hs | 5 ++- Annex/ReplaceFile.hs | 3 +- Annex/Transfer.hs | 3 +- Annex/View.hs | 6 ++-- Assistant/Pairing/Network.hs | 1 - Assistant/Threads/Committer.hs | 3 +- Assistant/Threads/Cronner.hs | 6 ++-- Assistant/Threads/SanityChecker.hs | 3 +- Assistant/Threads/Watcher.hs | 4 +-- Assistant/Threads/XMPPClient.hs | 18 +++++------ Assistant/XMPP/Client.hs | 7 ++--- Assistant/XMPP/Git.hs | 18 +++++------ CmdLine/Action.hs | 9 +++--- Command/Add.hs | 17 +++++----- Command/Direct.hs | 5 +-- Command/FuzzTest.hs | 3 +- Command/Indirect.hs | 7 ++--- Command/Map.hs | 3 +- Command/Move.hs | 10 +++--- Command/PreCommit.hs | 1 - Command/TestRemote.hs | 1 - Command/Vicfg.hs | 4 +-- Common.hs | 1 - Crypto.hs | 1 - Git/Config.hs | 1 - Git/UpdateIndex.hs | 2 -- Limit.hs | 8 ++--- Logs/Transfer.hs | 3 +- Messages.hs | 2 +- Remote.hs | 10 +++--- Remote/Ddar.hs | 1 - Remote/External.hs | 3 +- Remote/External/Types.hs | 1 - Remote/GCrypt.hs | 2 +- Remote/Git.hs | 4 +-- Remote/Helper/Chunked.hs | 15 +++++---- Remote/Helper/Special.hs | 4 +-- Remote/WebDAV.hs | 12 +++----- RemoteDaemon/Transport/Ssh.hs | 6 ++-- Test.hs | 3 +- Utility/Directory.hs | 3 +- Utility/Exception.hs | 28 ++++++++++++++--- Utility/FileMode.hs | 1 - Utility/Gpg.hs | 1 - Utility/Matcher.hs | 8 ++--- Utility/Parallel.hs | 1 - Utility/Tmp.hs | 15 +++++---- Utility/Url.hs | 8 ++--- Utility/WebApp.hs | 4 --- debian/control | 1 - git-annex.cabal | 5 ++- 60 files changed, 142 insertions(+), 237 deletions(-) delete mode 100644 Annex/Exception.hs (limited to 'Remote/Helper/Special.hs') diff --git a/Annex.hs b/Annex.hs index bb271c5e8..b915e852b 100644 --- a/Annex.hs +++ b/Annex.hs @@ -64,14 +64,16 @@ import Utility.Quvi (QuviVersion) import Utility.InodeCache import "mtl" Control.Monad.Reader -import Control.Monad.Catch import Control.Concurrent import qualified Data.Map as M import qualified Data.Set as S {- git-annex's monad is a ReaderT around an AnnexState stored in a MVar. - - This allows modifying the state in an exception-safe fashion. - The MVar is not exposed outside this module. + - + - Note that when an Annex action fails and the exception is caught, + - ny changes the action has made to the AnnexState are retained, + - due to the use of the MVar to store the state. -} newtype Annex a = Annex { runAnnex :: ReaderT (MVar AnnexState) IO a } deriving ( diff --git a/Annex/Content.hs b/Annex/Content.hs index eb84f2fe9..b51e15827 100644 --- a/Annex/Content.hs +++ b/Annex/Content.hs @@ -56,7 +56,6 @@ import Annex.Perms import Annex.Link import Annex.Content.Direct import Annex.ReplaceFile -import Annex.Exception #ifdef mingw32_HOST_OS import Utility.WinLock @@ -167,7 +166,7 @@ lockContent key a = do contentfile <- calcRepo $ gitAnnexLocation key lockfile <- contentLockFile key maybe noop setuplockfile lockfile - bracketAnnex (liftIO $ lock contentfile lockfile) (unlock lockfile) (const a) + bracket (liftIO $ lock contentfile lockfile) (unlock lockfile) (const a) where alreadylocked = error "content is locked" setuplockfile lockfile = modifyContent lockfile $ @@ -420,7 +419,7 @@ withObjectLoc key indirect direct = ifM isDirect cleanObjectLoc :: Key -> Annex () -> Annex () cleanObjectLoc key cleaner = do file <- calcRepo $ gitAnnexLocation key - void $ tryAnnexIO $ thawContentDir file + void $ tryIO $ thawContentDir file cleaner liftIO $ removeparents file (3 :: Int) where diff --git a/Annex/Direct.hs b/Annex/Direct.hs index e6b941e0f..374599369 100644 --- a/Annex/Direct.hs +++ b/Annex/Direct.hs @@ -32,7 +32,6 @@ import Utility.InodeCache import Utility.CopyFile import Annex.Perms import Annex.ReplaceFile -import Annex.Exception import Annex.VariantFile import Git.Index import Annex.Index @@ -252,7 +251,7 @@ mergeDirectCleanup d oldref = do go makeabs getsha getmode a araw (f, item) | getsha item == nullSha = noop | otherwise = void $ - tryAnnex . maybe (araw item makeabs f) (\k -> void $ a item makeabs k f) + tryNonAsync . maybe (araw item makeabs f) (\k -> void $ a item makeabs k f) =<< catKey (getsha item) (getmode item) moveout _ _ = removeDirect diff --git a/Annex/Drop.hs b/Annex/Drop.hs index 71263dc61..c5a3fbe5f 100644 --- a/Annex/Drop.hs +++ b/Annex/Drop.hs @@ -16,7 +16,6 @@ import qualified Remote import qualified Command.Drop import Command import Annex.Wanted -import Annex.Exception import Config import Annex.Content.Direct @@ -120,5 +119,5 @@ handleDropsFrom locs rs reason fromhere key afile knownpresentremote runner = do slocs = S.fromList locs - safely a = either (const False) id <$> tryAnnex a + safely a = either (const False) id <$> tryNonAsync a diff --git a/Annex/Environment.hs b/Annex/Environment.hs index 4b8d38464..bc97c17b7 100644 --- a/Annex/Environment.hs +++ b/Annex/Environment.hs @@ -13,7 +13,6 @@ import Common.Annex import Utility.UserInfo import qualified Git.Config import Config -import Annex.Exception #ifndef mingw32_HOST_OS import Utility.Env @@ -58,7 +57,7 @@ checkEnvironmentIO = {- Runs an action that commits to the repository, and if it fails, - sets user.email and user.name to a dummy value and tries the action again. -} ensureCommit :: Annex a -> Annex a -ensureCommit a = either retry return =<< tryAnnex a +ensureCommit a = either retry return =<< tryNonAsync a where retry _ = do name <- liftIO myUserName diff --git a/Annex/Exception.hs b/Annex/Exception.hs deleted file mode 100644 index 5ecbd28a0..000000000 --- a/Annex/Exception.hs +++ /dev/null @@ -1,63 +0,0 @@ -{- exception handling in the git-annex monad - - - - Note that when an Annex action fails and the exception is handled - - by these functions, any changes the action has made to the - - AnnexState are retained. This works because the Annex monad - - internally stores the AnnexState in a MVar. - - - - Copyright 2011-2014 Joey Hess - - - - Licensed under the GNU GPL version 3 or higher. - -} - -{-# LANGUAGE PackageImports #-} -{-# LANGUAGE ScopedTypeVariables #-} - -module Annex.Exception ( - bracketIO, - bracketAnnex, - tryAnnex, - tryAnnexIO, - throwAnnex, - catchAnnex, - catchNonAsyncAnnex, - tryNonAsyncAnnex, -) where - -import qualified Control.Monad.Catch as M -import Control.Exception - -import Common.Annex - -{- Runs an Annex action, with setup and cleanup both in the IO monad. -} -bracketIO :: IO v -> (v -> IO b) -> (v -> Annex a) -> Annex a -bracketIO setup cleanup = M.bracket (liftIO setup) (liftIO . cleanup) - -bracketAnnex :: Annex v -> (v -> Annex b) -> (v -> Annex a) -> Annex a -bracketAnnex = M.bracket - -{- try in the Annex monad -} -tryAnnex :: Annex a -> Annex (Either SomeException a) -tryAnnex = M.try - -{- try in the Annex monad, but only catching IO exceptions -} -tryAnnexIO :: Annex a -> Annex (Either IOException a) -tryAnnexIO = M.try - -{- throw in the Annex monad -} -throwAnnex :: Exception e => e -> Annex a -throwAnnex = M.throwM - -{- catch in the Annex monad -} -catchAnnex :: Exception e => Annex a -> (e -> Annex a) -> Annex a -catchAnnex = M.catch - -{- catchs all exceptions except for async exceptions -} -catchNonAsyncAnnex :: Annex a -> (SomeException -> Annex a) -> Annex a -catchNonAsyncAnnex a onerr = a `M.catches` - [ M.Handler (\ (e :: AsyncException) -> throwAnnex e) - , M.Handler (\ (e :: SomeException) -> onerr e) - ] - -tryNonAsyncAnnex :: Annex a -> Annex (Either SomeException a) -tryNonAsyncAnnex a = (Right <$> a) `catchNonAsyncAnnex` (return . Left) diff --git a/Annex/Index.hs b/Annex/Index.hs index af0cab45e..7757a412b 100644 --- a/Annex/Index.hs +++ b/Annex/Index.hs @@ -18,7 +18,6 @@ import Common.Annex import Git.Types import qualified Annex import Utility.Env -import Annex.Exception {- Runs an action using a different git index file. -} withIndexFile :: FilePath -> Annex a -> Annex a @@ -26,7 +25,7 @@ withIndexFile f a = do g <- gitRepo g' <- liftIO $ addGitEnv g "GIT_INDEX_FILE" f - r <- tryAnnex $ do + r <- tryNonAsync $ do Annex.changeState $ \s -> s { Annex.repo = g' } a Annex.changeState $ \s -> s { Annex.repo = (Annex.repo s) { gitEnv = gitEnv g} } diff --git a/Annex/Journal.hs b/Annex/Journal.hs index f34a7be1b..798bcba29 100644 --- a/Annex/Journal.hs +++ b/Annex/Journal.hs @@ -14,7 +14,6 @@ module Annex.Journal where import Common.Annex -import Annex.Exception import qualified Git import Annex.Perms import Annex.LockFile diff --git a/Annex/LockFile.hs b/Annex/LockFile.hs index 8114e94f2..dc4f82f98 100644 --- a/Annex/LockFile.hs +++ b/Annex/LockFile.hs @@ -18,7 +18,6 @@ import Common.Annex import Annex import Types.LockPool import qualified Git -import Annex.Exception import Annex.Perms import qualified Data.Map as M diff --git a/Annex/Perms.hs b/Annex/Perms.hs index e3a2fa65a..3430554c7 100644 --- a/Annex/Perms.hs +++ b/Annex/Perms.hs @@ -21,7 +21,6 @@ import Common.Annex import Utility.FileMode import Git.SharedRepository import qualified Annex -import Annex.Exception import Config import System.Posix.Types @@ -120,6 +119,6 @@ createContentDir dest = do modifyContent :: FilePath -> Annex a -> Annex a modifyContent f a = do createContentDir f -- also thaws it - v <- tryAnnex a + v <- tryNonAsync a freezeContentDir f - either throwAnnex return v + either throwM return v diff --git a/Annex/ReplaceFile.hs b/Annex/ReplaceFile.hs index e734c4d64..8776762e9 100644 --- a/Annex/ReplaceFile.hs +++ b/Annex/ReplaceFile.hs @@ -9,7 +9,6 @@ module Annex.ReplaceFile where import Common.Annex import Annex.Perms -import Annex.Exception {- Replaces a possibly already existing file with a new version, - atomically, by running an action. @@ -31,7 +30,7 @@ replaceFileOr :: FilePath -> (FilePath -> Annex ()) -> (FilePath -> Annex ()) -> replaceFileOr file action rollback = do tmpdir <- fromRepo gitAnnexTmpMiscDir void $ createAnnexDirectory tmpdir - bracketAnnex (liftIO $ setup tmpdir) rollback $ \tmpfile -> do + bracket (liftIO $ setup tmpdir) rollback $ \tmpfile -> do action tmpfile liftIO $ catchIO (rename tmpfile file) (fallback tmpfile) where diff --git a/Annex/Transfer.hs b/Annex/Transfer.hs index 001539adc..ebc8e8b89 100644 --- a/Annex/Transfer.hs +++ b/Annex/Transfer.hs @@ -20,7 +20,6 @@ import Common.Annex import Logs.Transfer as X import Annex.Notification as X import Annex.Perms -import Annex.Exception import Utility.Metered #ifdef mingw32_HOST_OS import Utility.WinLock @@ -103,7 +102,7 @@ runTransfer t file shouldretry a = do void $ tryIO $ removeFile $ transferLockFile tfile #endif retry oldinfo metervar run = do - v <- tryAnnex run + v <- tryNonAsync run case v of Right b -> return b Left e -> do diff --git a/Annex/View.hs b/Annex/View.hs index b96981612..a1d873f50 100644 --- a/Annex/View.hs +++ b/Annex/View.hs @@ -410,19 +410,19 @@ withViewChanges addmeta removemeta = do where handleremovals item | DiffTree.srcsha item /= nullSha = - handle item removemeta + handlechange item removemeta =<< catKey (DiffTree.srcsha item) (DiffTree.srcmode item) | otherwise = noop handleadds makeabs item | DiffTree.dstsha item /= nullSha = - handle item addmeta + handlechange item addmeta =<< ifM isDirect ( catKey (DiffTree.dstsha item) (DiffTree.dstmode item) -- optimisation , isAnnexLink $ makeabs $ DiffTree.file item ) | otherwise = noop - handle item a = maybe noop + handlechange item a = maybe noop (void . commandAction . a (getTopFilePath $ DiffTree.file item)) {- Generates a branch for a view. This is done using a different index diff --git a/Assistant/Pairing/Network.hs b/Assistant/Pairing/Network.hs index 6c625f881..4bb6088b1 100644 --- a/Assistant/Pairing/Network.hs +++ b/Assistant/Pairing/Network.hs @@ -20,7 +20,6 @@ import Utility.Verifiable import Network.Multicast import Network.Info import Network.Socket -import Control.Exception (bracket) import qualified Data.Map as M import Control.Concurrent diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index afe4aa144..4a47a9e2c 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -27,7 +27,6 @@ import qualified Utility.Lsof as Lsof import qualified Utility.DirWatcher as DirWatcher import Types.KeySource import Config -import Annex.Exception import Annex.Content import Annex.Link import Annex.CatFile @@ -217,7 +216,7 @@ commitStaged :: Annex Bool commitStaged = do {- This could fail if there's another commit being made by - something else. -} - v <- tryAnnex Annex.Queue.flush + v <- tryNonAsync Annex.Queue.flush case v of Left _ -> return False Right _ -> do diff --git a/Assistant/Threads/Cronner.hs b/Assistant/Threads/Cronner.hs index 55b3ca2f1..0fe7f58f4 100644 --- a/Assistant/Threads/Cronner.hs +++ b/Assistant/Threads/Cronner.hs @@ -191,10 +191,10 @@ runActivity' urlrenderer (ScheduledSelfFsck _ d) = do mapM_ reget =<< liftAnnex (dirKeys gitAnnexBadDir) where reget k = queueTransfers "fsck found bad file; redownloading" Next k Nothing Download -runActivity' urlrenderer (ScheduledRemoteFsck u s d) = handle =<< liftAnnex (remoteFromUUID u) +runActivity' urlrenderer (ScheduledRemoteFsck u s d) = dispatch =<< liftAnnex (remoteFromUUID u) where - handle Nothing = debug ["skipping remote fsck of uuid without a configured remote", fromUUID u, fromSchedule s] - handle (Just rmt) = void $ case Remote.remoteFsck rmt of + dispatch Nothing = debug ["skipping remote fsck of uuid without a configured remote", fromUUID u, fromSchedule s] + dispatch (Just rmt) = void $ case Remote.remoteFsck rmt of Nothing -> go rmt $ do program <- readProgramFile void $ batchCommand program $ diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index b62318382..dce2c2db7 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -40,7 +40,6 @@ import Logs.Transfer import Config.Files import Utility.DiskFree import qualified Annex -import Annex.Exception #ifdef WITH_WEBAPP import Assistant.WebApp.Types #endif @@ -85,7 +84,7 @@ sanityCheckerStartupThread startupdelay = namedThreadUnchecked "SanityCheckerSta liftIO $ fixUpSshRemotes {- Clean up old temp files. -} - void $ liftAnnex $ tryAnnex $ do + void $ liftAnnex $ tryNonAsync $ do cleanOldTmpMisc cleanReallyOldTmp diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 91e0fc619..fe9a95471 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -104,13 +104,13 @@ runWatcher = do , errHook = errhook } scanevents <- liftAnnex $ annexStartupScan <$> Annex.getGitConfig - handle <- liftIO $ watchDir "." ignored scanevents hooks startup + h <- liftIO $ watchDir "." ignored scanevents hooks startup debug [ "watching", "."] {- Let the DirWatcher thread run until signalled to pause it, - then wait for a resume signal, and restart. -} waitFor PauseWatcher $ do - liftIO $ stopWatchDir handle + liftIO $ stopWatchDir h waitFor ResumeWatcher runWatcher where hook a = Just <$> asIO2 (runHandler a) diff --git a/Assistant/Threads/XMPPClient.hs b/Assistant/Threads/XMPPClient.hs index 39b0459b7..2f70b508f 100644 --- a/Assistant/Threads/XMPPClient.hs +++ b/Assistant/Threads/XMPPClient.hs @@ -117,7 +117,7 @@ xmppClient urlrenderer d creds xmppuuid = void $ liftIO $ atomically . swapTMVar lasttraffic =<< getCurrentTime inAssistant $ debug ["received:", show $ map logXMPPEvent l] - mapM_ (handle selfjid) l + mapM_ (handlemsg selfjid) l sendpings selfjid lasttraffic = forever $ do putStanza pingstanza @@ -133,21 +133,21 @@ xmppClient urlrenderer d creds xmppuuid = - cause traffic, so good enough. -} pingstanza = xmppPing selfjid - handle selfjid (PresenceMessage p) = do + handlemsg selfjid (PresenceMessage p) = do void $ inAssistant $ updateBuddyList (updateBuddies p) <<~ buddyList resendImportantMessages selfjid p - handle _ (GotNetMessage QueryPresence) = putStanza gitAnnexSignature - handle _ (GotNetMessage (NotifyPush us)) = void $ inAssistant $ pull us - handle selfjid (GotNetMessage (PairingNotification stage c u)) = + handlemsg _ (GotNetMessage QueryPresence) = putStanza gitAnnexSignature + handlemsg _ (GotNetMessage (NotifyPush us)) = void $ inAssistant $ pull us + handlemsg selfjid (GotNetMessage (PairingNotification stage c u)) = maybe noop (inAssistant . pairMsgReceived urlrenderer stage u selfjid) (parseJID c) - handle _ (GotNetMessage m@(Pushing _ pushstage)) + handlemsg _ (GotNetMessage m@(Pushing _ pushstage)) | isPushNotice pushstage = inAssistant $ handlePushNotice m | isPushInitiation pushstage = inAssistant $ queuePushInitiation m | otherwise = inAssistant $ storeInbox m - handle _ (Ignorable _) = noop - handle _ (Unknown _) = noop - handle _ (ProtocolError _) = noop + handlemsg _ (Ignorable _) = noop + handlemsg _ (Unknown _) = noop + handlemsg _ (ProtocolError _) = noop resendImportantMessages selfjid (Presence { presenceFrom = Just jid }) = do let c = formatJID jid diff --git a/Assistant/XMPP/Client.hs b/Assistant/XMPP/Client.hs index 677bb2ff3..314ace64a 100644 --- a/Assistant/XMPP/Client.hs +++ b/Assistant/XMPP/Client.hs @@ -15,7 +15,6 @@ import Network.Protocol.XMPP import Network import Control.Concurrent import qualified Data.Text as T -import Control.Exception (SomeException) {- Everything we need to know to connect to an XMPP server. -} data XMPPCreds = XMPPCreds @@ -34,18 +33,18 @@ connectXMPP c a = case parseJID (xmppJID c) of {- Do a SRV lookup, but if it fails, fall back to the cached xmppHostname. -} connectXMPP' :: JID -> XMPPCreds -> (JID -> XMPP a) -> IO [(HostPort, Either SomeException ())] -connectXMPP' jid c a = reverse <$> (handle =<< lookupSRV srvrecord) +connectXMPP' jid c a = reverse <$> (handlesrv =<< lookupSRV srvrecord) where srvrecord = mkSRVTcp "xmpp-client" $ T.unpack $ strDomain $ jidDomain jid serverjid = JID Nothing (jidDomain jid) Nothing - handle [] = do + handlesrv [] = do let h = xmppHostname c let p = PortNumber $ fromIntegral $ xmppPort c r <- run h p $ a jid return [r] - handle srvs = go [] srvs + handlesrv srvs = go [] srvs go l [] = return l go l ((h,p):rest) = do diff --git a/Assistant/XMPP/Git.hs b/Assistant/XMPP/Git.hs index 301aa7185..19050c7d0 100644 --- a/Assistant/XMPP/Git.hs +++ b/Assistant/XMPP/Git.hs @@ -150,16 +150,16 @@ xmppPush cid gitpush = do SendPackOutput seqnum' b toxmpp seqnum' inh - fromxmpp outh controlh = withPushMessagesInSequence cid SendPack handle + fromxmpp outh controlh = withPushMessagesInSequence cid SendPack handlemsg where - handle (Just (Pushing _ (ReceivePackOutput _ b))) = + handlemsg (Just (Pushing _ (ReceivePackOutput _ b))) = liftIO $ writeChunk outh b - handle (Just (Pushing _ (ReceivePackDone exitcode))) = + handlemsg (Just (Pushing _ (ReceivePackDone exitcode))) = liftIO $ do hPrint controlh exitcode hFlush controlh - handle (Just _) = noop - handle Nothing = do + handlemsg (Just _) = noop + handlemsg Nothing = do debug ["timeout waiting for git receive-pack output via XMPP"] -- Send a synthetic exit code to git-annex -- xmppgit, which will exit and cause git push @@ -264,12 +264,12 @@ xmppReceivePack cid = do let seqnum' = succ seqnum sendNetMessage $ Pushing cid $ ReceivePackOutput seqnum' b relaytoxmpp seqnum' outh - relayfromxmpp inh = withPushMessagesInSequence cid ReceivePack handle + relayfromxmpp inh = withPushMessagesInSequence cid ReceivePack handlemsg where - handle (Just (Pushing _ (SendPackOutput _ b))) = + handlemsg (Just (Pushing _ (SendPackOutput _ b))) = liftIO $ writeChunk inh b - handle (Just _) = noop - handle Nothing = do + handlemsg (Just _) = noop + handlemsg Nothing = do debug ["timeout waiting for git send-pack output via XMPP"] -- closing the handle will make git receive-pack exit liftIO $ do diff --git a/CmdLine/Action.hs b/CmdLine/Action.hs index 247c658bc..db4f768ac 100644 --- a/CmdLine/Action.hs +++ b/CmdLine/Action.hs @@ -13,7 +13,6 @@ import Common.Annex import qualified Annex import Types.Command import qualified Annex.Queue -import Annex.Exception type CommandActionRunner = CommandStart -> CommandCleanup @@ -37,14 +36,14 @@ performCommandAction Command { cmdseek = seek, cmdcheck = c, cmdname = name } pa - - This should only be run in the seek stage. -} commandAction :: CommandActionRunner -commandAction a = handle =<< tryAnnexIO go +commandAction a = account =<< tryIO go where go = do Annex.Queue.flushWhenFull callCommandAction a - handle (Right True) = return True - handle (Right False) = incerr - handle (Left err) = do + account (Right True) = return True + account (Right False) = incerr + account (Left err) = do showErr err showEndFail incerr diff --git a/Command/Add.hs b/Command/Add.hs index ae895464e..5c7054543 100644 --- a/Command/Add.hs +++ b/Command/Add.hs @@ -10,7 +10,6 @@ module Command.Add where import Common.Annex -import Annex.Exception import Command import Types.KeySource import Backend @@ -33,6 +32,8 @@ import Annex.FileMatcher import Annex.ReplaceFile import Utility.Tmp +import Control.Exception (IOException) + def :: [Command] def = [notBareRepo $ withOptions [includeDotFilesOption] $ command "add" paramPaths seek SectionCommon @@ -103,7 +104,7 @@ lockDown = either (\e -> showErr e >> return Nothing) (return . Just) <=< lockDo lockDown' :: FilePath -> Annex (Either IOException KeySource) lockDown' file = ifM crippledFileSystem ( withTSDelta $ liftIO . tryIO . nohardlink - , tryAnnexIO $ do + , tryIO $ do tmp <- fromRepo gitAnnexTmpMiscDir createAnnexDirectory tmp go tmp @@ -167,7 +168,7 @@ ingest (Just source) = withTSDelta $ \delta -> do ) goindirect (Just (key, _)) mcache ms = do - catchAnnex (moveAnnex key $ contentLocation source) + catchNonAsync (moveAnnex key $ contentLocation source) (undo (keyFilename source) key) maybe noop (genMetaData key (keyFilename source)) ms liftIO $ nukeFile $ keyFilename source @@ -206,23 +207,23 @@ perform file = lockDown file >>= ingest >>= go {- On error, put the file back so it doesn't seem to have vanished. - This can be called before or after the symlink is in place. -} -undo :: FilePath -> Key -> IOException -> Annex a +undo :: FilePath -> Key -> SomeException -> Annex a undo file key e = do whenM (inAnnex key) $ do liftIO $ nukeFile file - catchAnnex (fromAnnex key file) tryharder + catchNonAsync (fromAnnex key file) tryharder logStatus key InfoMissing - throwAnnex e + throwM e where -- fromAnnex could fail if the file ownership is weird - tryharder :: IOException -> Annex () + tryharder :: SomeException -> Annex () tryharder _ = do src <- calcRepo $ gitAnnexLocation key liftIO $ moveFile src file {- Creates the symlink to the annexed content, returns the link target. -} link :: FilePath -> Key -> Maybe InodeCache -> Annex String -link file key mcache = flip catchAnnex (undo file key) $ do +link file key mcache = flip catchNonAsync (undo file key) $ do l <- inRepo $ gitAnnexLink file key replaceFile file $ makeAnnexLink l diff --git a/Command/Direct.hs b/Command/Direct.hs index a5165a4a2..c64ef6e56 100644 --- a/Command/Direct.hs +++ b/Command/Direct.hs @@ -7,8 +7,6 @@ module Command.Direct where -import Control.Exception.Extensible - import Common.Annex import Command import qualified Git @@ -16,7 +14,6 @@ import qualified Git.LsFiles import qualified Git.Branch import Config import Annex.Direct -import Annex.Exception def :: [Command] def = [notBareRepo $ noDaemonRunning $ @@ -52,7 +49,7 @@ perform = do Nothing -> noop Just a -> do showStart "direct" f - r' <- tryAnnex a + r' <- tryNonAsync a case r' of Left e -> warnlocked e Right _ -> showEndOk diff --git a/Command/FuzzTest.hs b/Command/FuzzTest.hs index d673541fb..7075aeddc 100644 --- a/Command/FuzzTest.hs +++ b/Command/FuzzTest.hs @@ -13,7 +13,6 @@ import Command import qualified Git.Config import Config import Utility.ThreadScheduler -import Annex.Exception import Utility.DiskFree import Data.Time.Clock @@ -56,7 +55,7 @@ fuzz :: Handle -> Annex () fuzz logh = do action <- genFuzzAction record logh $ flip Started action - result <- tryAnnex $ runFuzzAction action + result <- tryNonAsync $ runFuzzAction action record logh $ flip Finished $ either (const False) (const True) result diff --git a/Command/Indirect.hs b/Command/Indirect.hs index 4ce4c2c38..e146f13b7 100644 --- a/Command/Indirect.hs +++ b/Command/Indirect.hs @@ -7,8 +7,6 @@ module Command.Indirect where -import Control.Exception.Extensible - import Common.Annex import Command import qualified Git @@ -21,7 +19,6 @@ import Annex.Direct import Annex.Content import Annex.Content.Direct import Annex.CatFile -import Annex.Exception import Annex.Init import qualified Command.Add @@ -88,12 +85,12 @@ perform = do removeInodeCache k removeAssociatedFiles k whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do - v <-tryAnnexIO (moveAnnex k f) + v <- tryNonAsync (moveAnnex k f) case v of Right _ -> do l <- inRepo $ gitAnnexLink f k liftIO $ createSymbolicLink l f - Left e -> catchAnnex (Command.Add.undo f k e) + Left e -> catchNonAsync (Command.Add.undo f k e) warnlocked showEndOk diff --git a/Command/Map.hs b/Command/Map.hs index 5a32d7f52..a62c3e1ad 100644 --- a/Command/Map.hs +++ b/Command/Map.hs @@ -7,7 +7,6 @@ module Command.Map where -import Control.Exception.Extensible import qualified Data.Map as M import Common.Annex @@ -247,7 +246,7 @@ combineSame = map snd . nubBy sameuuid . map pair safely :: IO Git.Repo -> IO (Maybe Git.Repo) safely a = do - result <- try a :: IO (Either SomeException Git.Repo) + result <- tryNonAsync a case result of Left _ -> return Nothing Right r' -> return $ Just r' diff --git a/Command/Move.hs b/Command/Move.hs index 396ea4afc..3d9646dea 100644 --- a/Command/Move.hs +++ b/Command/Move.hs @@ -152,17 +152,17 @@ fromOk src key = go =<< Annex.getState Annex.force fromPerform :: Remote -> Bool -> Key -> AssociatedFile -> CommandPerform fromPerform src move key afile = moveLock move key $ ifM (inAnnex key) - ( handle move True - , handle move =<< go + ( dispatch move True + , dispatch move =<< go ) where go = notifyTransfer Download afile $ download (Remote.uuid src) key afile noRetry $ \p -> do showAction $ "from " ++ Remote.name src getViaTmp key $ \t -> Remote.retrieveKeyFile src key afile t p - handle _ False = stop -- failed - handle False True = next $ return True -- copy complete - handle True True = do -- finish moving + dispatch _ False = stop -- failed + dispatch False True = next $ return True -- copy complete + dispatch True True = do -- finish moving ok <- Remote.removeKey src key next $ Command.Drop.cleanupRemote key src ok diff --git a/Command/PreCommit.hs b/Command/PreCommit.hs index 412b9ae08..09ff042aa 100644 --- a/Command/PreCommit.hs +++ b/Command/PreCommit.hs @@ -19,7 +19,6 @@ import Annex.Hook import Annex.View import Annex.View.ViewedFile import Annex.Perms -import Annex.Exception import Logs.View import Logs.MetaData import Types.View diff --git a/Command/TestRemote.hs b/Command/TestRemote.hs index 463c4d359..cb36b66ba 100644 --- a/Command/TestRemote.hs +++ b/Command/TestRemote.hs @@ -31,7 +31,6 @@ import Locations import Test.Tasty import Test.Tasty.Runners import Test.Tasty.HUnit -import Control.Exception import "crypto-api" Crypto.Random import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as L diff --git a/Command/Vicfg.hs b/Command/Vicfg.hs index 5ec6bbf72..1f1695536 100644 --- a/Command/Vicfg.hs +++ b/Command/Vicfg.hs @@ -217,7 +217,7 @@ parseCfg curcfg = go [] curcfg . lines | null l = Right cfg | "#" `isPrefixOf` l = Right cfg | null setting || null f = Left "missing field" - | otherwise = handle cfg f setting value' + | otherwise = parsed cfg f setting value' where (setting, rest) = separate isSpace l (r, value) = separate (== '=') rest @@ -225,7 +225,7 @@ parseCfg curcfg = go [] curcfg . lines f = reverse $ trimspace $ reverse $ trimspace r trimspace = dropWhile isSpace - handle cfg f setting value + parsed cfg f setting value | setting == "trust" = case readTrustLevel value of Nothing -> badval "trust value" value Just t -> diff --git a/Common.hs b/Common.hs index 0f3dc71d0..76e8d5133 100644 --- a/Common.hs +++ b/Common.hs @@ -6,7 +6,6 @@ import Control.Monad as X import Control.Monad.IfElse as X import Control.Applicative as X import "mtl" Control.Monad.State.Strict as X (liftIO) -import Control.Exception.Extensible as X (IOException) import Data.Maybe as X import Data.List as X hiding (head, tail, init, last) diff --git a/Crypto.hs b/Crypto.hs index 10d6e5cef..8d4d4f04f 100644 --- a/Crypto.hs +++ b/Crypto.hs @@ -38,7 +38,6 @@ import Data.ByteString.Lazy.UTF8 (fromString) import Control.Applicative import qualified Data.Map as M import Control.Monad.IO.Class -import Control.Monad.Catch (MonadMask) import Common.Annex import qualified Utility.Gpg as Gpg diff --git a/Git/Config.hs b/Git/Config.hs index d998fd1e2..171c3e6c6 100644 --- a/Git/Config.hs +++ b/Git/Config.hs @@ -9,7 +9,6 @@ module Git.Config where import qualified Data.Map as M import Data.Char -import Control.Exception.Extensible import Common import Git diff --git a/Git/UpdateIndex.hs b/Git/UpdateIndex.hs index 7de2f1be3..ecd154aa0 100644 --- a/Git/UpdateIndex.hs +++ b/Git/UpdateIndex.hs @@ -29,8 +29,6 @@ import Git.Command import Git.FilePath import Git.Sha -import Control.Exception (bracket) - {- Streamers are passed a callback and should feed it lines in the form - read by update-index, and generated by ls-tree. -} type Streamer = (String -> IO ()) -> IO () diff --git a/Limit.hs b/Limit.hs index 9ac849bce..89dd9d33e 100644 --- a/Limit.hs +++ b/Limit.hs @@ -152,8 +152,8 @@ limitCopies want = case split ":" want of go num good = case readish num of Nothing -> Left "bad number for copies" Just n -> Right $ \notpresent -> checkKey $ - handle n good notpresent - handle n good notpresent key = do + go' n good notpresent + go' n good notpresent key = do us <- filter (`S.notMember` notpresent) <$> (filterM good =<< Remote.keyLocations key) return $ length us >= n @@ -170,10 +170,10 @@ addLackingCopies approx = addLimit . limitLackingCopies approx limitLackingCopies :: Bool -> MkLimit Annex limitLackingCopies approx want = case readish want of Just needed -> Right $ \notpresent mi -> flip checkKey mi $ - handle mi needed notpresent + go mi needed notpresent Nothing -> Left "bad value for number of lacking copies" where - handle mi needed notpresent key = do + go mi needed notpresent key = do NumCopies numcopies <- if approx then approxNumCopies else case mi of diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index c96d9cd1e..b6279ccba 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -11,7 +11,6 @@ module Logs.Transfer where import Common.Annex import Annex.Perms -import Annex.Exception import qualified Git import Types.Key import Utility.Metered @@ -94,7 +93,7 @@ percentComplete (Transfer { transferKey = key }) info = mkProgressUpdater :: Transfer -> TransferInfo -> Annex (MeterUpdate, FilePath, MVar Integer) mkProgressUpdater t info = do tfile <- fromRepo $ transferFile t - _ <- tryAnnex $ createAnnexDirectory $ takeDirectory tfile + _ <- tryNonAsync $ createAnnexDirectory $ takeDirectory tfile mvar <- liftIO $ newMVar 0 return (liftIO . updater tfile mvar, tfile, mvar) where diff --git a/Messages.hs b/Messages.hs index 9f473110a..f27755f3a 100644 --- a/Messages.hs +++ b/Messages.hs @@ -47,7 +47,7 @@ import System.Log.Handler (setFormatter, LogHandler) import System.Log.Handler.Simple import qualified Data.Set as S -import Common +import Common hiding (handle) import Types import Types.Messages import qualified Messages.JSON as JSON diff --git a/Remote.hs b/Remote.hs index 5ee75823f..8a8eb64df 100644 --- a/Remote.hs +++ b/Remote.hs @@ -56,7 +56,6 @@ import Data.Ord import Common.Annex import Types.Remote import qualified Annex -import Annex.Exception import Annex.UUID import Logs.UUID import Logs.Trust @@ -114,10 +113,10 @@ byNameWithUUID = checkuuid <=< byName byName' :: RemoteName -> Annex (Either String Remote) byName' "" = return $ Left "no remote specified" -byName' n = handle . filter matching <$> remoteList +byName' n = go . filter matching <$> remoteList where - handle [] = Left $ "there is no available git remote named \"" ++ n ++ "\"" - handle (match:_) = Right match + go [] = Left $ "there is no available git remote named \"" ++ n ++ "\"" + go (match:_) = Right match matching r = n == name r || toUUID n == uuid r {- Only matches remote name, not UUID -} @@ -315,8 +314,7 @@ isXMPPRemote remote = Git.repoIsUrl r && "xmpp::" `isPrefixOf` Git.repoLocation r = repo remote hasKey :: Remote -> Key -> Annex (Either String Bool) -hasKey r k = either (Left . show) Right - <$> tryNonAsyncAnnex (checkPresent r k) +hasKey r k = either (Left . show) Right <$> tryNonAsync (checkPresent r k) hasKeyCheap :: Remote -> Bool hasKeyCheap = checkPresentCheap diff --git a/Remote/Ddar.hs b/Remote/Ddar.hs index fba05312b..beeb4d7cc 100644 --- a/Remote/Ddar.hs +++ b/Remote/Ddar.hs @@ -8,7 +8,6 @@ module Remote.Ddar (remote) where -import Control.Exception import qualified Data.Map as M import qualified Data.ByteString.Lazy as L import System.IO.Error diff --git a/Remote/External.hs b/Remote/External.hs index f326f26ba..4fb760afd 100644 --- a/Remote/External.hs +++ b/Remote/External.hs @@ -21,7 +21,6 @@ import Logs.PreferredContent.Raw import Logs.RemoteState import Config.Cost import Annex.UUID -import Annex.Exception import Creds import Control.Concurrent.STM @@ -137,7 +136,7 @@ checkKey external k = either error id <$> go _ -> Nothing safely :: Annex Bool -> Annex Bool -safely a = go =<< tryAnnex a +safely a = go =<< tryNonAsync a where go (Right r) = return r go (Left e) = do diff --git a/Remote/External/Types.hs b/Remote/External/Types.hs index 983764f70..3a69ae9ea 100644 --- a/Remote/External/Types.hs +++ b/Remote/External/Types.hs @@ -32,7 +32,6 @@ module Remote.External.Types ( ) where import Common.Annex -import Annex.Exception import Types.Key (file2key, key2file) import Types.StandardGroups (PreferredContentExpression) import Utility.Metered (BytesProcessed(..)) diff --git a/Remote/GCrypt.hs b/Remote/GCrypt.hs index 55a775811..8891977f7 100644 --- a/Remote/GCrypt.hs +++ b/Remote/GCrypt.hs @@ -15,7 +15,7 @@ module Remote.GCrypt ( import qualified Data.Map as M import qualified Data.ByteString.Lazy as L -import Control.Exception.Extensible +import Control.Exception import Common.Annex import Types.Remote diff --git a/Remote/Git.hs b/Remote/Git.hs index da5ca4c4a..34c60d98f 100644 --- a/Remote/Git.hs +++ b/Remote/Git.hs @@ -27,7 +27,6 @@ import qualified Annex import Logs.Presence import Annex.Transfer import Annex.UUID -import Annex.Exception import qualified Annex.Content import qualified Annex.BranchState import qualified Annex.Branch @@ -56,7 +55,6 @@ import Creds import Control.Concurrent import Control.Concurrent.MSampleVar import qualified Data.Map as M -import Control.Exception.Extensible remote :: RemoteType remote = RemoteType { @@ -281,7 +279,7 @@ tryGitConfigRead r s <- Annex.new r Annex.eval s $ do Annex.BranchState.disableUpdate - void $ tryAnnex $ ensureInitialized + void $ tryNonAsync $ ensureInitialized Annex.getState Annex.repo {- Checks if a given remote has the content for a key in its annex. -} diff --git a/Remote/Helper/Chunked.hs b/Remote/Helper/Chunked.hs index 953c533b6..5e4ea111f 100644 --- a/Remote/Helper/Chunked.hs +++ b/Remote/Helper/Chunked.hs @@ -24,7 +24,6 @@ import Logs.Chunk import Utility.Metered import Crypto (EncKey) import Backend (isStableKey) -import Annex.Exception import qualified Data.ByteString.Lazy as L import qualified Data.Map as M @@ -172,7 +171,7 @@ seekResume h chunkkeys checker = do liftIO $ hSeek h AbsoluteSeek sz return (cks, toBytesProcessed sz) | otherwise = do - v <- tryNonAsyncAnnex (checker k) + v <- tryNonAsync (checker k) case v of Right True -> check pos' cks' sz @@ -231,7 +230,7 @@ retrieveChunks retriever u chunkconfig encryptor basek dest basep sink -- Optimisation: Try the unchunked key first, to avoid -- looking in the git-annex branch for chunk counts -- that are likely not there. - getunchunked `catchNonAsyncAnnex` + getunchunked `catchNonAsync` const (go =<< chunkKeysOnly u basek) | otherwise = go =<< chunkKeys u chunkconfig basek where @@ -241,7 +240,7 @@ retrieveChunks retriever u chunkconfig encryptor basek dest basep sink let ls' = maybe ls (setupResume ls) currsize if any null ls' then return True -- dest is already complete - else firstavail currsize ls' `catchNonAsyncAnnex` giveup + else firstavail currsize ls' `catchNonAsync` giveup giveup e = do warning (show e) @@ -251,20 +250,20 @@ retrieveChunks retriever u chunkconfig encryptor basek dest basep sink firstavail currsize ([]:ls) = firstavail currsize ls firstavail currsize ((k:ks):ls) | k == basek = getunchunked - `catchNonAsyncAnnex` (const $ firstavail currsize ls) + `catchNonAsync` (const $ firstavail currsize ls) | otherwise = do let offset = resumeOffset currsize k let p = maybe basep (offsetMeterUpdate basep . toBytesProcessed) offset - v <- tryNonAsyncAnnex $ + v <- tryNonAsync $ retriever (encryptor k) p $ \content -> bracketIO (maybe opennew openresume offset) hClose $ \h -> do void $ tosink (Just h) p content let sz = toBytesProcessed $ fromMaybe 0 $ keyChunkSize k getrest p h sz sz ks - `catchNonAsyncAnnex` giveup + `catchNonAsync` giveup case v of Left e | null ls -> giveup e @@ -372,7 +371,7 @@ checkPresentChunks checker u chunkconfig encryptor basek Right False -> return $ Right False Left e -> return $ Left $ show e - check = tryNonAsyncAnnex . checker . encryptor + check = tryNonAsync . checker . encryptor {- A key can be stored in a remote unchunked, or as a list of chunked keys. - This can be the case whether or not the remote is currently configured diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs index fc0e11d2f..ba9ff4fb4 100644 --- a/Remote/Helper/Special.hs +++ b/Remote/Helper/Special.hs @@ -42,13 +42,11 @@ import Remote.Helper.Chunked as X import Remote.Helper.Encryptable as X import Remote.Helper.Messages import Annex.Content -import Annex.Exception import qualified Git import qualified Git.Command import qualified Git.Construct import qualified Data.ByteString.Lazy as L -import Control.Exception (bracket) import qualified Data.Map as M {- Special remotes don't have a configured url, so Git.Repo does not @@ -174,7 +172,7 @@ specialRemote' cfg c preparestorer prepareretriever prepareremover preparecheckp cip = cipherKey c gpgopts = getGpgEncParams encr - safely a = catchNonAsyncAnnex a (\e -> warning (show e) >> return False) + safely a = catchNonAsync a (\e -> warning (show e) >> return False) -- chunk, then encrypt, then feed to the storer storeKeyGen k p enc = safely $ preparestorer k $ safely . go diff --git a/Remote/WebDAV.hs b/Remote/WebDAV.hs index b70001ddb..4caebaf21 100644 --- a/Remote/WebDAV.hs +++ b/Remote/WebDAV.hs @@ -14,10 +14,10 @@ import qualified Data.Map as M import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.UTF8 as B8 import qualified Data.ByteString.Lazy.UTF8 as L8 -import qualified Control.Exception.Lifted as EL import Network.HTTP.Client (HttpException(..)) import Network.HTTP.Types import System.IO.Error +import Control.Monad.Catch import Common.Annex import Types.Remote @@ -31,7 +31,6 @@ import Creds import Utility.Metered import Utility.Url (URLString) import Annex.UUID -import Annex.Exception import Remote.WebDAV.DavLocation remote :: RemoteType @@ -301,11 +300,11 @@ moveDAV baseurl src dest = inLocation src $ moveContentM newurl newurl = B8.fromString (locationUrl baseurl dest) existsDAV :: DavLocation -> DAVT IO (Either String Bool) -existsDAV l = inLocation l check `EL.catch` (\(e :: EL.SomeException) -> return (Left $ show e)) +existsDAV l = inLocation l check `catchNonAsync` (\e -> return (Left $ show e)) where check = do setDepth Nothing - EL.catchJust + catchJust (matchStatusCodeException notFound404) (getPropsM >> ispresent True) (const $ ispresent False) @@ -319,8 +318,7 @@ matchStatusCodeException _ _ = Nothing -- Ignores any exceptions when performing a DAV action. safely :: DAVT IO a -> DAVT IO (Maybe a) -safely a = (Just <$> a) - `EL.catch` (\(_ :: EL.SomeException) -> return Nothing) +safely = eitherToMaybe <$$> tryNonAsync choke :: IO (Either String a) -> IO a choke f = do @@ -336,7 +334,7 @@ withDAVHandle r a = do mcreds <- getCreds (config r) (uuid r) case (mcreds, configUrl r) of (Just (user, pass), Just baseurl) -> - bracketIO (mkDAVContext baseurl) closeDAVContext $ \ctx -> + withDAVContext baseurl $ \ctx -> a (Just (DavHandle ctx (toDavUser user) (toDavPass pass) baseurl)) _ -> a Nothing diff --git a/RemoteDaemon/Transport/Ssh.hs b/RemoteDaemon/Transport/Ssh.hs index 65c313852..db6b6127c 100644 --- a/RemoteDaemon/Transport/Ssh.hs +++ b/RemoteDaemon/Transport/Ssh.hs @@ -108,10 +108,10 @@ data Status = Stopping | ConnectionClosed {- Make connection robustly, with exponentioal backoff on failure. -} robustly :: Int -> IO Status -> IO () -robustly backoff a = handle =<< catchDefaultIO ConnectionClosed a +robustly backoff a = caught =<< catchDefaultIO ConnectionClosed a where - handle Stopping = return () - handle ConnectionClosed = do + caught Stopping = return () + caught ConnectionClosed = do threadDelaySeconds (Seconds backoff) robustly increasedbackoff a diff --git a/Test.hs b/Test.hs index 5032038ad..9a34835cc 100644 --- a/Test.hs +++ b/Test.hs @@ -20,7 +20,6 @@ import Options.Applicative hiding (command) #if MIN_VERSION_optparse_applicative(0,8,0) import qualified Options.Applicative.Types as Opt #endif -import Control.Exception.Extensible import qualified Data.Map as M import qualified Text.JSON @@ -1444,7 +1443,7 @@ indir testenv dir a = do (try a::IO (Either SomeException ())) case r of Right () -> return () - Left e -> throw e + Left e -> throwM e setuprepo :: TestEnv -> FilePath -> IO FilePath setuprepo testenv dir = do diff --git a/Utility/Directory.hs b/Utility/Directory.hs index ade5ef811..a4429d5b9 100644 --- a/Utility/Directory.hs +++ b/Utility/Directory.hs @@ -11,7 +11,6 @@ module Utility.Directory where import System.IO.Error import System.Directory -import Control.Exception (throw, bracket) import Control.Monad import Control.Monad.IfElse import System.FilePath @@ -114,7 +113,7 @@ moveFile src dest = tryIO (rename src dest) >>= onrename whenM (isdir dest) rethrow viaTmp mv dest undefined where - rethrow = throw e + rethrow = throwM e mv tmp _ = do ok <- boolSystem "mv" [Param "-f", Param src, Param tmp] unless ok $ do diff --git a/Utility/Exception.hs b/Utility/Exception.hs index 13c9d508a..802e9e24b 100644 --- a/Utility/Exception.hs +++ b/Utility/Exception.hs @@ -7,11 +7,25 @@ {-# LANGUAGE ScopedTypeVariables #-} -module Utility.Exception where +module Utility.Exception ( + module X, + catchBoolIO, + catchMaybeIO, + catchDefaultIO, + catchMsgIO, + catchIO, + tryIO, + bracketIO, + catchNonAsync, + tryNonAsync, + tryWhenExists, +) where +import Control.Monad.Catch as X hiding (Handler) +import qualified Control.Monad.Catch as M import Control.Exception (IOException, AsyncException) -import Control.Monad.Catch import Control.Monad +import Control.Monad.IO.Class (liftIO, MonadIO) import System.IO.Error (isDoesNotExistError) import Utility.Data @@ -44,14 +58,20 @@ catchIO = catch tryIO :: MonadCatch m => m a -> m (Either IOException a) tryIO = try +{- bracket with setup and cleanup actions lifted to IO. + - + - Note that unlike catchIO and tryIO, this catches all exceptions. -} +bracketIO :: (MonadMask m, MonadIO m) => IO v -> (v -> IO b) -> (v -> m a) -> m a +bracketIO setup cleanup = bracket (liftIO setup) (liftIO . cleanup) + {- Catches all exceptions except for async exceptions. - This is often better to use than catching them all, so that - ThreadKilled and UserInterrupt get through. -} catchNonAsync :: MonadCatch m => m a -> (SomeException -> m a) -> m a catchNonAsync a onerr = a `catches` - [ Handler (\ (e :: AsyncException) -> throwM e) - , Handler (\ (e :: SomeException) -> onerr e) + [ M.Handler (\ (e :: AsyncException) -> throwM e) + , M.Handler (\ (e :: SomeException) -> onerr e) ] tryNonAsync :: MonadCatch m => m a -> m (Either SomeException a) diff --git a/Utility/FileMode.hs b/Utility/FileMode.hs index c2ef683a8..832250bde 100644 --- a/Utility/FileMode.hs +++ b/Utility/FileMode.hs @@ -11,7 +11,6 @@ module Utility.FileMode where import System.IO import Control.Monad -import Control.Exception (bracket) import System.PosixCompat.Types import Utility.PosixFiles #ifndef mingw32_HOST_OS diff --git a/Utility/Gpg.hs b/Utility/Gpg.hs index 410259b11..dfca82778 100644 --- a/Utility/Gpg.hs +++ b/Utility/Gpg.hs @@ -13,7 +13,6 @@ import Control.Applicative import Control.Concurrent import Control.Monad.IO.Class import qualified Data.Map as M -import Control.Monad.Catch (bracket, MonadMask) import Common import qualified Build.SysConfig as SysConfig diff --git a/Utility/Matcher.hs b/Utility/Matcher.hs index 1ee224ffc..76f8903f5 100644 --- a/Utility/Matcher.hs +++ b/Utility/Matcher.hs @@ -102,13 +102,13 @@ findClose l = in (Group (reverse g), rest) where go c [] = (c, []) -- not picky about extra Close - go c (t:ts) = handle t + go c (t:ts) = dispatch t where - handle Close = (c, ts) - handle Open = + dispatch Close = (c, ts) + dispatch Open = let (c', ts') = go [] ts in go (Group (reverse c') : c) ts' - handle _ = go (One t:c) ts + dispatch _ = go (One t:c) ts {- Checks if a Matcher matches, using a supplied function to check - the value of Operations. -} diff --git a/Utility/Parallel.hs b/Utility/Parallel.hs index 239c81e7b..7966811ab 100644 --- a/Utility/Parallel.hs +++ b/Utility/Parallel.hs @@ -10,7 +10,6 @@ module Utility.Parallel where import Common import Control.Concurrent -import Control.Exception {- Runs an action in parallel with a set of values, in a set of threads. - In order for the actions to truely run in parallel, requires GHC's diff --git a/Utility/Tmp.hs b/Utility/Tmp.hs index 7da5cc284..edd82f5ac 100644 --- a/Utility/Tmp.hs +++ b/Utility/Tmp.hs @@ -14,7 +14,6 @@ import System.Directory import Control.Monad.IfElse import System.FilePath import Control.Monad.IO.Class -import Control.Monad.Catch (bracket, MonadMask) import Utility.Exception import Utility.FileSystemEncoding @@ -33,11 +32,11 @@ viaTmp a file content = bracket setup cleanup use setup = do createDirectoryIfMissing True dir openTempFile dir template - cleanup (tmpfile, handle) = do - _ <- tryIO $ hClose handle + cleanup (tmpfile, h) = do + _ <- tryIO $ hClose h tryIO $ removeFile tmpfile - use (tmpfile, handle) = do - hClose handle + use (tmpfile, h) = do + hClose h a tmpfile content rename tmpfile file @@ -54,10 +53,10 @@ withTmpFileIn :: (MonadIO m, MonadMask m) => FilePath -> Template -> (FilePath - withTmpFileIn tmpdir template a = bracket create remove use where create = liftIO $ openTempFile tmpdir template - remove (name, handle) = liftIO $ do - hClose handle + remove (name, h) = liftIO $ do + hClose h catchBoolIO (removeFile name >> return True) - use (name, handle) = a name handle + use (name, h) = a name h {- Runs an action with a tmp directory located within the system's tmp - directory (or within "." if there is none), then removes the tmp diff --git a/Utility/Url.hs b/Utility/Url.hs index bf2d3859c..4137a5d8b 100644 --- a/Utility/Url.hs +++ b/Utility/Url.hs @@ -51,11 +51,11 @@ checkBoth url expected_size uo = do v <- check url expected_size uo return (fst v && snd v) check :: URLString -> Maybe Integer -> UrlOptions -> IO (Bool, Bool) -check url expected_size = handle <$$> exists url +check url expected_size = go <$$> exists url where - handle (False, _) = (False, False) - handle (True, Nothing) = (True, True) - handle (True, s) = case expected_size of + go (False, _) = (False, False) + go (True, Nothing) = (True, True) + go (True, s) = case expected_size of Just _ -> (True, expected_size == s) Nothing -> (True, True) diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 0f3378a15..6bcfce919 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -38,10 +38,6 @@ import Data.Byteable #ifdef __ANDROID__ import Data.Endian #endif -#if defined(__ANDROID__) || defined (mingw32_HOST_OS) -#else -import Control.Exception (bracketOnError) -#endif localhost :: HostName localhost = "localhost" diff --git a/debian/control b/debian/control index 66d340e3c..821629297 100644 --- a/debian/control +++ b/debian/control @@ -26,7 +26,6 @@ Build-Depends: libghc-ifelse-dev, libghc-bloomfilter-dev, libghc-edit-distance-dev, - libghc-extensible-exceptions-dev, libghc-hinotify-dev [linux-any], libghc-stm-dev (>= 2.3), libghc-dbus-dev (>= 0.10.3) [linux-any], diff --git a/git-annex.cabal b/git-annex.cabal index 8f36bfe48..8dd42ee2f 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -96,8 +96,7 @@ Executable git-annex Main-Is: git-annex.hs Build-Depends: MissingH, hslogger, directory, filepath, containers, utf8-string, network (>= 2.0), mtl (>= 2), - bytestring, old-locale, time, HTTP, - extensible-exceptions, dataenc, SHA, process, json, + bytestring, old-locale, time, HTTP, dataenc, SHA, process, json, base (>= 4.5 && < 4.9), monad-control, exceptions (>= 0.5), IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process, SafeSemaphore, uuid, random, dlist, unix-compat, async, stm (>= 2.3), @@ -143,7 +142,7 @@ Executable git-annex if flag(WebDAV) Build-Depends: DAV (>= 0.8), - http-client, http-conduit, http-types, lifted-base, transformers + http-client, http-conduit, http-types CPP-Options: -DWITH_WEBDAV if flag(Assistant) && ! os(solaris) -- cgit v1.2.3 From a26b7127d4cc8b2a5e15ef662ab2793dbf9e7919 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 9 Oct 2014 14:53:13 -0400 Subject: fix some mixed space+tab indentation This fixes all instances of " \t" in the code base. Most common case seems to be after a "where" line; probably vim copied the two space layout of that line. Done as a background task while listening to episode 2 of the Type Theory podcast. --- Annex/Branch.hs | 6 +++--- Annex/CatFile.hs | 6 +++--- Annex/CheckIgnore.hs | 2 +- Annex/Content.hs | 4 ++-- Annex/Direct.hs | 2 +- Annex/Environment.hs | 4 ++-- Annex/FileMatcher.hs | 2 +- Annex/ReplaceFile.hs | 2 +- Annex/Ssh.hs | 4 ++-- Annex/Transfer.hs | 2 +- Annex/View.hs | 8 ++++---- Annex/View/ViewedFile.hs | 2 +- Assistant.hs | 2 +- Assistant/Alert.hs | 2 +- Assistant/Alert/Utility.hs | 2 +- Assistant/DaemonStatus.hs | 2 +- Assistant/DeleteRemote.hs | 2 +- Assistant/MakeRemote.hs | 2 +- Assistant/NetMessager.hs | 4 ++-- Assistant/Ssh.hs | 6 +++--- Assistant/Threads/Committer.hs | 6 +++--- Assistant/Threads/Cronner.hs | 8 ++++---- Assistant/Threads/SanityChecker.hs | 2 +- Assistant/Threads/UpgradeWatcher.hs | 4 ++-- Assistant/Threads/Upgrader.hs | 2 +- Assistant/Threads/Watcher.hs | 6 +++--- Assistant/Threads/WebApp.hs | 2 +- Assistant/Threads/XMPPClient.hs | 2 +- Assistant/Threads/XMPPPusher.hs | 4 ++-- Assistant/TransferQueue.hs | 2 +- Assistant/Types/NetMessager.hs | 2 +- Assistant/XMPP.hs | 2 +- Assistant/XMPP/Git.hs | 10 +++++----- Backend/Hash.hs | 2 +- Build/EvilLinker.hs | 10 +++++----- Build/EvilSplicer.hs | 22 +++++++++++----------- Build/NullSoftInstaller.hs | 2 +- Build/OSXMkLibs.hs | 2 +- Checks.hs | 2 +- CmdLine.hs | 2 +- CmdLine/GitAnnexShell.hs | 2 +- CmdLine/Seek.hs | 4 ++-- Command/Add.hs | 6 +++--- Command/AddUrl.hs | 8 ++++---- Command/ConfigList.hs | 2 +- Command/Copy.hs | 2 +- Command/EnableRemote.hs | 2 +- Command/Fsck.hs | 2 +- Command/FuzzTest.hs | 6 +++--- Command/Get.hs | 2 +- Command/Import.hs | 4 ++-- Command/ImportFeed.hs | 4 ++-- Command/Indirect.hs | 2 +- Command/Info.hs | 2 +- Command/Migrate.hs | 2 +- Command/RecvKey.hs | 4 ++-- Command/Schedule.hs | 2 +- Command/Sync.hs | 2 +- Command/TransferKeys.hs | 2 +- Command/Uninit.hs | 2 +- Command/Vicfg.hs | 4 ++-- Command/Wanted.hs | 2 +- Config/Cost.hs | 2 +- Config/Files.hs | 2 +- Git/CatFile.hs | 2 +- Git/Command.hs | 4 ++-- Git/Config.hs | 2 +- Git/GCrypt.hs | 6 +++--- Git/LsTree.hs | 2 +- Git/Remote.hs | 2 +- Git/Repair.hs | 4 ++-- Git/Version.hs | 2 +- Limit.hs | 4 ++-- Locations.hs | 4 ++-- Logs.hs | 8 ++++---- Logs/FsckResults.hs | 2 +- Logs/MetaData.hs | 2 +- Logs/Schedule.hs | 2 +- Logs/Transitions.hs | 6 +++--- Logs/Web.hs | 2 +- Remote.hs | 2 +- Remote/External.hs | 2 +- Remote/GCrypt.hs | 10 +++++----- Remote/Git.hs | 2 +- Remote/Helper/Chunked.hs | 6 +++--- Remote/Helper/Special.hs | 4 ++-- Remote/Hook.hs | 2 +- Remote/Rsync.hs | 2 +- Remote/Tahoe.hs | 4 ++-- Remote/Web.hs | 2 +- RemoteDaemon/Transport/Ssh.hs | 2 +- Test.hs | 6 +++--- Types/Key.hs | 2 +- Types/MetaData.hs | 2 +- Types/StandardGroups.hs | 2 +- Utility/Batch.hs | 2 +- Utility/CoProcess.hs | 4 ++-- Utility/CopyFile.hs | 4 ++-- Utility/Daemon.hs | 2 +- Utility/DataUnits.hs | 2 +- Utility/Directory.hs | 4 ++-- Utility/ExternalSHA.hs | 2 +- Utility/FileSystemEncoding.hs | 2 +- Utility/Format.hs | 2 +- Utility/Gpg.hs | 6 +++--- Utility/HumanTime.hs | 4 ++-- Utility/InodeCache.hs | 2 +- Utility/Matcher.hs | 4 ++-- Utility/Path.hs | 8 ++++---- Utility/Quvi.hs | 2 +- Utility/Rsync.hs | 2 +- Utility/SRV.hs | 2 +- Utility/Scheduled.hs | 18 +++++++++--------- Utility/SshConfig.hs | 6 +++--- Utility/TList.hs | 2 +- Utility/WebApp.hs | 2 +- doc/design/requests_routing/simroutes.hs | 6 +++--- 117 files changed, 212 insertions(+), 212 deletions(-) (limited to 'Remote/Helper/Special.hs') diff --git a/Annex/Branch.hs b/Annex/Branch.hs index a03d6ddf3..c567db554 100644 --- a/Annex/Branch.hs +++ b/Annex/Branch.hs @@ -454,7 +454,7 @@ handleTransitions jl localts refs = do ignoreRefs untransitionedrefs return True where - getreftransition ref = do + getreftransition ref = do ts <- parseTransitionsStrictly "remote" . decodeBS <$> catFile ref transitionsLog return (ref, ts) @@ -470,7 +470,7 @@ ignoreRefs rs = do getIgnoredRefs :: Annex (S.Set Git.Ref) getIgnoredRefs = S.fromList . mapMaybe Git.Sha.extractSha . lines <$> content where - content = do + content = do f <- fromRepo gitAnnexIgnoredRefs liftIO $ catchDefaultIO "" $ readFile f @@ -498,7 +498,7 @@ performTransitionsLocked jl ts neednewlocalbranch transitionedrefs = do ref <- getBranch commitIndex jl ref message (nub $ fullname:transitionedrefs) where - message + message | neednewlocalbranch && null transitionedrefs = "new branch for transition " ++ tdesc | otherwise = "continuing transition " ++ tdesc tdesc = show $ map describeTransition $ transitionList ts diff --git a/Annex/CatFile.hs b/Annex/CatFile.hs index 8b4d746e1..8a6f10def 100644 --- a/Annex/CatFile.hs +++ b/Annex/CatFile.hs @@ -100,10 +100,10 @@ catKey' modeguaranteed sha mode catLink :: Bool -> Sha -> Annex String catLink modeguaranteed sha = fromInternalGitPath . decodeBS <$> get where - -- If the mode is not guaranteed to be correct, avoid + -- If the mode is not guaranteed to be correct, avoid -- buffering the whole file content, which might be large. -- 8192 is enough if it really is a symlink. - get + get | modeguaranteed = catObject sha | otherwise = L.take 8192 <$> catObject sha @@ -120,7 +120,7 @@ catKeyChecked :: Bool -> Ref -> Annex (Maybe Key) catKeyChecked needhead ref@(Ref r) = catKey' False ref =<< findmode <$> catTree treeref where - pathparts = split "/" r + pathparts = split "/" r dir = intercalate "/" $ take (length pathparts - 1) pathparts file = fromMaybe "" $ lastMaybe pathparts treeref = Ref $ if needhead then "HEAD" ++ dir ++ "/" else dir ++ "/" diff --git a/Annex/CheckIgnore.hs b/Annex/CheckIgnore.hs index d45e652bc..f2ed93543 100644 --- a/Annex/CheckIgnore.hs +++ b/Annex/CheckIgnore.hs @@ -18,7 +18,7 @@ import qualified Annex checkIgnored :: FilePath -> Annex Bool checkIgnored file = go =<< checkIgnoreHandle where - go Nothing = return False + go Nothing = return False go (Just h) = liftIO $ Git.checkIgnored h file checkIgnoreHandle :: Annex (Maybe Git.CheckIgnoreHandle) diff --git a/Annex/Content.hs b/Annex/Content.hs index c0c79ae56..37090d3bb 100644 --- a/Annex/Content.hs +++ b/Annex/Content.hs @@ -456,7 +456,7 @@ removeAnnex (ContentLock key) = withObjectLoc key remove removedirect secureErase :: FilePath -> Annex () secureErase file = maybe noop go =<< annexSecureEraseCommand <$> Annex.getGitConfig where - go basecmd = void $ liftIO $ + go basecmd = void $ liftIO $ boolSystem "sh" [Param "-c", Param $ gencmd basecmd] gencmd = massReplace [ ("%file", shellEscape file) ] @@ -555,7 +555,7 @@ saveState nocommit = doSideAction $ do downloadUrl :: [Url.URLString] -> FilePath -> Annex Bool downloadUrl urls file = go =<< annexWebDownloadCommand <$> Annex.getGitConfig where - go Nothing = Url.withUrlOptions $ \uo -> + go Nothing = Url.withUrlOptions $ \uo -> anyM (\u -> Url.download u file uo) urls go (Just basecmd) = liftIO $ anyM (downloadcmd basecmd) urls downloadcmd basecmd url = diff --git a/Annex/Direct.hs b/Annex/Direct.hs index 76a6f27dc..9489b74f2 100644 --- a/Annex/Direct.hs +++ b/Annex/Direct.hs @@ -347,7 +347,7 @@ toDirectGen k f = do (dloc:_) -> return $ Just $ fromdirect dloc ) where - fromindirect loc = do + fromindirect loc = do {- Move content from annex to direct file. -} updateInodeCache k loc void $ addAssociatedFile k f diff --git a/Annex/Environment.hs b/Annex/Environment.hs index bc97c17b7..b1b5e96e9 100644 --- a/Annex/Environment.hs +++ b/Annex/Environment.hs @@ -45,7 +45,7 @@ checkEnvironmentIO = ensureEnv "GIT_COMMITTER_NAME" username where #ifndef __ANDROID__ - -- existing environment is not overwritten + -- existing environment is not overwritten ensureEnv var val = void $ setEnv var val False #else -- Environment setting is broken on Android, so this is dealt with @@ -59,7 +59,7 @@ checkEnvironmentIO = ensureCommit :: Annex a -> Annex a ensureCommit a = either retry return =<< tryNonAsync a where - retry _ = do + retry _ = do name <- liftIO myUserName setConfig (ConfigKey "user.name") name setConfig (ConfigKey "user.email") name diff --git a/Annex/FileMatcher.hs b/Annex/FileMatcher.hs index da6a5e0e9..856c68122 100644 --- a/Annex/FileMatcher.hs +++ b/Annex/FileMatcher.hs @@ -106,7 +106,7 @@ tokenizeMatcher = filter (not . null ) . concatMap splitparens . words largeFilesMatcher :: Annex (FileMatcher Annex) largeFilesMatcher = go =<< annexLargeFiles <$> Annex.getGitConfig where - go Nothing = return matchAll + go Nothing = return matchAll go (Just expr) = do gm <- groupMap rc <- readRemoteLog diff --git a/Annex/ReplaceFile.hs b/Annex/ReplaceFile.hs index 9700d4b60..0355ddd51 100644 --- a/Annex/ReplaceFile.hs +++ b/Annex/ReplaceFile.hs @@ -33,7 +33,7 @@ replaceFileOr file action rollback = do tmpfile <- liftIO $ setup tmpdir go tmpfile `catchNonAsync` (const $ rollback tmpfile) where - setup tmpdir = do + setup tmpdir = do (tmpfile, h) <- openTempFileWithDefaultPermissions tmpdir "tmp" hClose h return tmpfile diff --git a/Annex/Ssh.hs b/Annex/Ssh.hs index ad636b4aa..3b7bd7d69 100644 --- a/Annex/Ssh.hs +++ b/Annex/Ssh.hs @@ -78,10 +78,10 @@ bestSocketPath abssocketfile = do then Just socketfile else Nothing where - -- ssh appends a 16 char extension to the socket when setting it + -- ssh appends a 16 char extension to the socket when setting it -- up, which needs to be taken into account when checking -- that a valid socket was constructed. - sshgarbage = replicate (1+16) 'X' + sshgarbage = replicate (1+16) 'X' sshConnectionCachingParams :: FilePath -> [CommandParam] sshConnectionCachingParams socketfile = diff --git a/Annex/Transfer.hs b/Annex/Transfer.hs index d33d3073b..fb89869f8 100644 --- a/Annex/Transfer.hs +++ b/Annex/Transfer.hs @@ -69,7 +69,7 @@ runTransfer' ignorelock t file shouldretry a = do return False else do ok <- retry info metervar $ - bracketIO (return fd) (cleanup tfile) (const $ a meter) + bracketIO (return fd) (cleanup tfile) (const $ a meter) unless ok $ recordFailedTransfer t info return ok where diff --git a/Annex/View.hs b/Annex/View.hs index a1d873f50..4cbf274aa 100644 --- a/Annex/View.hs +++ b/Annex/View.hs @@ -102,7 +102,7 @@ refineView origview = checksize . calc Unchanged origview let (components', viewchanges) = runWriter $ mapM (\c -> updateViewComponent c field vf) (viewComponents view) viewchange = if field `elem` map viewField (viewComponents origview) - then maximum viewchanges + then maximum viewchanges else Narrowing in (view { viewComponents = components' }, viewchange) | otherwise = @@ -207,7 +207,7 @@ viewComponentMatcher :: ViewComponent -> (MetaData -> Maybe [MetaValue]) viewComponentMatcher viewcomponent = \metadata -> matcher (currentMetaDataValues metafield metadata) where - metafield = viewField viewcomponent + metafield = viewField viewcomponent matcher = case viewFilter viewcomponent of FilterValues s -> \values -> setmatches $ S.intersection s values @@ -236,8 +236,8 @@ toViewPath = concatMap escapeslash . fromMetaValue fromViewPath :: FilePath -> MetaValue fromViewPath = toMetaValue . deescapeslash [] where - deescapeslash s [] = reverse s - deescapeslash s (c:cs) + deescapeslash s [] = reverse s + deescapeslash s (c:cs) | c == pseudoSlash = case cs of (c':cs') | c' == pseudoSlash -> deescapeslash (pseudoSlash:s) cs' diff --git a/Annex/View/ViewedFile.hs b/Annex/View/ViewedFile.hs index 25ac16a34..ef901f700 100644 --- a/Annex/View/ViewedFile.hs +++ b/Annex/View/ViewedFile.hs @@ -58,7 +58,7 @@ viewedFileReuse = takeFileName dirFromViewedFile :: ViewedFile -> FilePath dirFromViewedFile = joinPath . drop 1 . sep [] "" where - sep l _ [] = reverse l + sep l _ [] = reverse l sep l curr (c:cs) | c == '%' = sep (reverse curr:l) "" cs | c == '\\' = case cs of diff --git a/Assistant.hs b/Assistant.hs index 82f157241..b7e2463fa 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -119,7 +119,7 @@ startDaemon assistant foreground startdelay cannotrun listenhost startbrowser = ) #endif where - desc + desc | assistant = "assistant" | otherwise = "watch" start daemonize webappwaiter = withThreadState $ \st -> do diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 745694f59..a41baa85f 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -145,7 +145,7 @@ syncResultAlert' succeeded failed = makeAlertFiller (not $ null succeeded) $ , alertHeader = Just $ tenseWords msg } where - msg + msg | null succeeded = ["Failed to sync with", showRemotes failed] | null failed = ["Synced with", showRemotes succeeded] | otherwise = diff --git a/Assistant/Alert/Utility.hs b/Assistant/Alert/Utility.hs index be631e999..ea1280dac 100644 --- a/Assistant/Alert/Utility.hs +++ b/Assistant/Alert/Utility.hs @@ -119,7 +119,7 @@ mergeAlert i al m = maybe updatePrune updateCombine (alertCombiner al) where bloat = M.size m' - maxAlerts pruneold l = - let (f, rest) = partition (\(_, a) -> isFiller a) l + let (f, rest) = partition (\(_, a) -> isFiller a) l in drop bloat f ++ rest updatePrune = pruneBloat $ M.filterWithKey pruneSame $ M.insertWith' const i al m diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 35f8fc856..3edc2c174 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -65,7 +65,7 @@ calcSyncRemotes = do , syncingToCloudRemote = any iscloud syncdata } where - iscloud r = not (Remote.readonly r) && Remote.availability r == Remote.GloballyAvailable + iscloud r = not (Remote.readonly r) && Remote.availability r == Remote.GloballyAvailable {- Updates the syncRemotes list from the list of all remotes in Annex state. -} updateSyncRemotes :: Assistant () diff --git a/Assistant/DeleteRemote.hs b/Assistant/DeleteRemote.hs index cc05786e4..a900753a7 100644 --- a/Assistant/DeleteRemote.hs +++ b/Assistant/DeleteRemote.hs @@ -62,7 +62,7 @@ removableRemote urlrenderer uuid = do <$> liftAnnex (Remote.remoteFromUUID uuid) mapM_ (queueremaining r) keys where - queueremaining r k = + queueremaining r k = queueTransferWhenSmall "remaining object in unwanted remote" Nothing (Transfer Download uuid k) r {- Scanning for keys can take a long time; do not tie up diff --git a/Assistant/MakeRemote.hs b/Assistant/MakeRemote.hs index 967a4d41d..d244a7729 100644 --- a/Assistant/MakeRemote.hs +++ b/Assistant/MakeRemote.hs @@ -48,7 +48,7 @@ makeRsyncRemote :: RemoteName -> String -> Annex String makeRsyncRemote name location = makeRemote name location $ const $ void $ go =<< Command.InitRemote.findExisting name where - go Nothing = setupSpecialRemote name Rsync.remote config Nothing + go Nothing = setupSpecialRemote name Rsync.remote config Nothing (Nothing, Command.InitRemote.newConfig name) go (Just (u, c)) = setupSpecialRemote name Rsync.remote config Nothing (Just u, c) diff --git a/Assistant/NetMessager.hs b/Assistant/NetMessager.hs index acb18b648..f042b4e4e 100644 --- a/Assistant/NetMessager.hs +++ b/Assistant/NetMessager.hs @@ -80,7 +80,7 @@ checkImportantNetMessages (storedclient, sentclient) = go <<~ netMessager queuePushInitiation :: NetMessage -> Assistant () queuePushInitiation msg@(Pushing clientid stage) = do tv <- getPushInitiationQueue side - liftIO $ atomically $ do + liftIO $ atomically $ do r <- tryTakeTMVar tv case r of Nothing -> putTMVar tv [msg] @@ -88,7 +88,7 @@ queuePushInitiation msg@(Pushing clientid stage) = do let !l' = msg : filter differentclient l putTMVar tv l' where - side = pushDestinationSide stage + side = pushDestinationSide stage differentclient (Pushing cid _) = cid /= clientid differentclient _ = True queuePushInitiation _ = noop diff --git a/Assistant/Ssh.hs b/Assistant/Ssh.hs index e1a78cd00..7b82f4624 100644 --- a/Assistant/Ssh.hs +++ b/Assistant/Ssh.hs @@ -92,7 +92,7 @@ parseSshUrl u , sshCapabilities = [] } where - (user, host) = if '@' `elem` userhost + (user, host) = if '@' `elem` userhost then separate (== '@') userhost else ("", userhost) fromrsync s @@ -260,7 +260,7 @@ setupSshKeyPair sshkeypair sshdata = do fixSshKeyPairIdentitiesOnly :: IO () fixSshKeyPairIdentitiesOnly = changeUserSshConfig $ unlines . go [] . lines where - go c [] = reverse c + go c [] = reverse c go c (l:[]) | all (`isInfixOf` l) indicators = go (fixedline l:l:c) [] | otherwise = go (l:c) [] @@ -268,7 +268,7 @@ fixSshKeyPairIdentitiesOnly = changeUserSshConfig $ unlines . go [] . lines | all (`isInfixOf` l) indicators && not ("IdentitiesOnly" `isInfixOf` next) = go (fixedline l:l:c) (next:rest) | otherwise = go (l:c) (next:rest) - indicators = ["IdentityFile", "key.git-annex"] + indicators = ["IdentityFile", "key.git-annex"] fixedline tmpl = takeWhile isSpace tmpl ++ "IdentitiesOnly yes" {- Add StrictHostKeyChecking to any ssh config stanzas that were written diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index 4a47a9e2c..47c2aa4aa 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -164,8 +164,8 @@ waitChangeTime a = waitchanges 0 -} aftermaxcommit oldchanges = loop (30 :: Int) where - loop 0 = continue oldchanges - loop n = do + loop 0 = continue oldchanges + loop n = do liftAnnex noop -- ensure Annex state is free liftIO $ threadDelaySeconds (Seconds 1) changes <- getAnyChanges @@ -301,7 +301,7 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do add change@(InProcessAddChange { keySource = ks }) = catchDefaultIO Nothing <~> doadd where - doadd = sanitycheck ks $ do + doadd = sanitycheck ks $ do (mkey, mcache) <- liftAnnex $ do showStart "add" $ keyFilename ks Command.Add.ingest $ Just ks diff --git a/Assistant/Threads/Cronner.hs b/Assistant/Threads/Cronner.hs index 0fe7f58f4..6dc6f4c6b 100644 --- a/Assistant/Threads/Cronner.hs +++ b/Assistant/Threads/Cronner.hs @@ -87,7 +87,7 @@ cronnerThread urlrenderer = namedThreadUnchecked "Cronner" $ do liftIO $ waitNotification h debug ["reloading changed activities"] go h amap' nmap' - startactivities as lastruntimes = forM as $ \activity -> + startactivities as lastruntimes = forM as $ \activity -> case connectActivityUUID activity of Nothing -> do runner <- asIO2 (sleepingActivityThread urlrenderer) @@ -108,8 +108,8 @@ cronnerThread urlrenderer = namedThreadUnchecked "Cronner" $ do sleepingActivityThread :: UrlRenderer -> ScheduledActivity -> Maybe LocalTime -> Assistant () sleepingActivityThread urlrenderer activity lasttime = go lasttime =<< getnexttime lasttime where - getnexttime = liftIO . nextTime schedule - go _ Nothing = debug ["no scheduled events left for", desc] + getnexttime = liftIO . nextTime schedule + go _ Nothing = debug ["no scheduled events left for", desc] go l (Just (NextTimeExactly t)) = waitrun l t Nothing go l (Just (NextTimeWindow windowstart windowend)) = waitrun l windowstart (Just windowend) @@ -129,7 +129,7 @@ sleepingActivityThread urlrenderer activity lasttime = go lasttime =<< getnextti go l =<< getnexttime l else run nowt where - tolate nowt tz = case mmaxt of + tolate nowt tz = case mmaxt of Just maxt -> nowt > maxt -- allow the job to start 10 minutes late Nothing ->diffUTCTime diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index 3371f212f..9fd963a69 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -258,7 +258,7 @@ checkOldUnused :: UrlRenderer -> Assistant () checkOldUnused urlrenderer = go =<< annexExpireUnused <$> liftAnnex Annex.getGitConfig where go (Just Nothing) = noop - go (Just (Just expireunused)) = expireUnused (Just expireunused) + go (Just (Just expireunused)) = expireUnused (Just expireunused) go Nothing = maybe noop prompt =<< describeUnusedWhenBig prompt msg = diff --git a/Assistant/Threads/UpgradeWatcher.hs b/Assistant/Threads/UpgradeWatcher.hs index ffad09d3d..431e6f339 100644 --- a/Assistant/Threads/UpgradeWatcher.hs +++ b/Assistant/Threads/UpgradeWatcher.hs @@ -51,9 +51,9 @@ upgradeWatcherThread urlrenderer = namedThread "UpgradeWatcher" $ do let depth = length (splitPath dir) + 1 let nosubdirs f = length (splitPath f) == depth void $ liftIO $ watchDir dir nosubdirs False hooks (startup mvar) - -- Ignore bogus events generated during the startup scan. + -- Ignore bogus events generated during the startup scan. -- We ask the watcher to not generate them, but just to be safe.. - startup mvar scanner = do + startup mvar scanner = do r <- scanner void $ swapMVar mvar Started return r diff --git a/Assistant/Threads/Upgrader.hs b/Assistant/Threads/Upgrader.hs index 637c82a7d..100c15414 100644 --- a/Assistant/Threads/Upgrader.hs +++ b/Assistant/Threads/Upgrader.hs @@ -39,7 +39,7 @@ upgraderThread urlrenderer = namedThread "Upgrader" $ h <- liftIO . newNotificationHandle False . networkConnectedNotifier =<< getDaemonStatus go h =<< liftIO getCurrentTime where - {- Wait for a network connection event. Then see if it's been + {- Wait for a network connection event. Then see if it's been - half a day since the last upgrade check. If so, proceed with - check. -} go h lastchecked = do diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index fe9a95471..8482de895 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -192,7 +192,7 @@ runHandler handler file filestatus = void $ do liftAnnex Annex.Queue.flushWhenFull recordChange change where - normalize f + normalize f | "./" `isPrefixOf` file = drop 2 f | otherwise = f @@ -246,7 +246,7 @@ onAddDirect symlinkssupported matcher file fs = do debug ["add direct", file] add matcher file where - {- On a filesystem without symlinks, we'll get changes for regular + {- On a filesystem without symlinks, we'll get changes for regular - files that git uses to stand-in for symlinks. Detect when - this happens, and stage the symlink, rather than annexing the - file. -} @@ -276,7 +276,7 @@ onAddSymlink isdirect file filestatus = unlessIgnored file $ do onAddSymlink' :: Maybe String -> Maybe Key -> Bool -> Handler onAddSymlink' linktarget mk isdirect file filestatus = go mk where - go (Just key) = do + go (Just key) = do when isdirect $ liftAnnex $ void $ addAssociatedFile key file link <- liftAnnex $ inRepo $ gitAnnexLink file key diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 416c07874..b22b54a8d 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -97,7 +97,7 @@ webAppThread assistantdata urlrenderer noannex cannotrun postfirstrun listenhost urlfile <- getAnnex' $ fromRepo gitAnnexUrlFile go tlssettings addr webapp htmlshim (Just urlfile) where - -- The webapp thread does not wait for the startupSanityCheckThread + -- The webapp thread does not wait for the startupSanityCheckThread -- to finish, so that the user interface remains responsive while -- that's going on. thread = namedThreadUnchecked "WebApp" diff --git a/Assistant/Threads/XMPPClient.hs b/Assistant/Threads/XMPPClient.hs index 2f70b508f..8ce99eac6 100644 --- a/Assistant/Threads/XMPPClient.hs +++ b/Assistant/Threads/XMPPClient.hs @@ -131,7 +131,7 @@ xmppClient urlrenderer d creds xmppuuid = {- XEP-0199 says that the server will respond with either - a ping response or an error message. Either will - cause traffic, so good enough. -} - pingstanza = xmppPing selfjid + pingstanza = xmppPing selfjid handlemsg selfjid (PresenceMessage p) = do void $ inAssistant $ diff --git a/Assistant/Threads/XMPPPusher.hs b/Assistant/Threads/XMPPPusher.hs index 30c91c7f0..35c76ebf1 100644 --- a/Assistant/Threads/XMPPPusher.hs +++ b/Assistant/Threads/XMPPPusher.hs @@ -34,7 +34,7 @@ xmppReceivePackThread = pusherThread "XMPPReceivePack" ReceivePack pusherThread :: String -> PushSide -> UrlRenderer -> NamedThread pusherThread threadname side urlrenderer = namedThread threadname $ go Nothing where - go lastpushedto = do + go lastpushedto = do msg <- waitPushInitiation side $ selectNextPush lastpushedto debug ["started running push", logNetMessage msg] @@ -78,4 +78,4 @@ selectNextPush lastpushedto l = go [] l (Pushing clientid _) | Just clientid /= lastpushedto -> (m, rejected ++ ms) _ -> go (m:rejected) ms - go [] [] = undefined + go [] [] = undefined diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 93c982224..d138e16ef 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -92,7 +92,7 @@ queueTransfersMatching matching reason schedule k f direction filterM (wantSend True (Just k) f . Remote.uuid) $ filter (\r -> not (inset s r || Remote.readonly r)) rs where - locs = S.fromList <$> Remote.keyLocations k + locs = S.fromList <$> Remote.keyLocations k inset s r = S.member (Remote.uuid r) s gentransfer r = Transfer { transferDirection = direction diff --git a/Assistant/Types/NetMessager.hs b/Assistant/Types/NetMessager.hs index 5ae987a61..f5ad85b4a 100644 --- a/Assistant/Types/NetMessager.hs +++ b/Assistant/Types/NetMessager.hs @@ -85,7 +85,7 @@ logNetMessage (Pushing c stage) = show $ Pushing (logClientID c) $ SendPackOutput n _ -> SendPackOutput n elided s -> s where - elided = T.encodeUtf8 $ T.pack "" + elided = T.encodeUtf8 $ T.pack "" logNetMessage (PairingNotification stage c uuid) = show $ PairingNotification stage (logClientID c) uuid logNetMessage m = show m diff --git a/Assistant/XMPP.hs b/Assistant/XMPP.hs index e74705021..cc0343abf 100644 --- a/Assistant/XMPP.hs +++ b/Assistant/XMPP.hs @@ -195,7 +195,7 @@ decodeMessage m = decode =<< gitAnnexTagInfo m <*> a i gen c i = c . toUUID <$> headMaybe (words (T.unpack (tagValue i))) seqgen c i = do - packet <- decodeTagContent $ tagElement i + packet <- decodeTagContent $ tagElement i let seqnum = fromMaybe 0 $ readish $ T.unpack $ tagValue i return $ c seqnum packet shasgen c i = do diff --git a/Assistant/XMPP/Git.hs b/Assistant/XMPP/Git.hs index 19050c7d0..868fe6609 100644 --- a/Assistant/XMPP/Git.hs +++ b/Assistant/XMPP/Git.hs @@ -152,7 +152,7 @@ xmppPush cid gitpush = do fromxmpp outh controlh = withPushMessagesInSequence cid SendPack handlemsg where - handlemsg (Just (Pushing _ (ReceivePackOutput _ b))) = + handlemsg (Just (Pushing _ (ReceivePackOutput _ b))) = liftIO $ writeChunk outh b handlemsg (Just (Pushing _ (ReceivePackDone exitcode))) = liftIO $ do @@ -266,7 +266,7 @@ xmppReceivePack cid = do relaytoxmpp seqnum' outh relayfromxmpp inh = withPushMessagesInSequence cid ReceivePack handlemsg where - handlemsg (Just (Pushing _ (SendPackOutput _ b))) = + handlemsg (Just (Pushing _ (SendPackOutput _ b))) = liftIO $ writeChunk inh b handlemsg (Just _) = noop handlemsg Nothing = do @@ -337,7 +337,7 @@ handlePushNotice (Pushing cid (CanPush theiruuid shas)) = , go ) where - go = do + go = do u <- liftAnnex getUUID sendNetMessage $ Pushing cid (PushRequest u) haveall l = liftAnnex $ not <$> anyM donthave l @@ -359,9 +359,9 @@ writeChunk h b = do withPushMessagesInSequence :: ClientID -> PushSide -> (Maybe NetMessage -> Assistant ()) -> Assistant () withPushMessagesInSequence cid side a = loop 0 where - loop seqnum = do + loop seqnum = do m <- timeout xmppTimeout <~> waitInbox cid side - let go s = a m >> loop s + let go s = a m >> loop s let next = seqnum + 1 case extractSequence =<< m of Just seqnum' diff --git a/Backend/Hash.hs b/Backend/Hash.hs index 62d0a0fca..7c47a4abc 100644 --- a/Backend/Hash.hs +++ b/Backend/Hash.hs @@ -144,7 +144,7 @@ trivialMigrate oldkey newbackend hashFile :: Hash -> FilePath -> Integer -> Annex String hashFile hash file filesize = liftIO $ go hash where - go (SHAHash hashsize) = case shaHasher hashsize filesize of + go (SHAHash hashsize) = case shaHasher hashsize filesize of Left sha -> sha <$> L.readFile file Right command -> either error return diff --git a/Build/EvilLinker.hs b/Build/EvilLinker.hs index cf0f771e5..e2921cc8c 100644 --- a/Build/EvilLinker.hs +++ b/Build/EvilLinker.hs @@ -58,13 +58,13 @@ parseGccLink = do collect2params <- restOfLine return $ CmdParams (path ++ collectcmd) (escapeDosPaths collect2params) cenv where - collectcmd = "collect2.exe" - collectgccenv = "COLLECT_GCC" + collectcmd = "collect2.exe" + collectgccenv = "COLLECT_GCC" collectltoenv = "COLLECT_LTO_WRAPPER" pathenv = "COMPILER_PATH" libpathenv = "LIBRARY_PATH" - optenv = "COLLECT_GCC_OPTIONS" - collectenv = do + optenv = "COLLECT_GCC_OPTIONS" + collectenv = do void $ many1 $ do notFollowedBy $ string collectgccenv restOfLine @@ -148,7 +148,7 @@ runAtFile p s f extraparams = do removeFile f return out where - c = case parse p "" s of + c = case parse p "" s of Left e -> error $ (show e) ++ "\n<<<\n" ++ s ++ "\n>>>" diff --git a/Build/EvilSplicer.hs b/Build/EvilSplicer.hs index 648d631b5..fc41c624f 100644 --- a/Build/EvilSplicer.hs +++ b/Build/EvilSplicer.hs @@ -86,7 +86,7 @@ number = read <$> many1 digit coordsParser :: Parser (Coord, Coord) coordsParser = (try singleline <|> try weird <|> multiline) "Coords" where - singleline = do + singleline = do line <- number void $ char ':' startcol <- number @@ -151,7 +151,7 @@ spliceParser = do (unlines codelines) splicetype where - tosplicetype "declarations" = SpliceDeclaration + tosplicetype "declarations" = SpliceDeclaration tosplicetype "expression" = SpliceExpression tosplicetype s = error $ "unknown splice type: " ++ s @@ -177,7 +177,7 @@ spliceParser = do splicesExtractor :: Parser [Splice] splicesExtractor = rights <$> many extract where - extract = try (Right <$> spliceParser) <|> (Left <$> compilerJunkLine) + extract = try (Right <$> spliceParser) <|> (Left <$> compilerJunkLine) compilerJunkLine = restOfLine {- Modifies the source file, expanding the splices, which all must @@ -214,8 +214,8 @@ applySplices destdir imports splices@(first:_) = do hPutStr h newcontent hClose h where - expand lls [] = lls - expand lls (s:rest) + expand lls [] = lls + expand lls (s:rest) | isExpressionSplice s = expand (expandExpressionSplice s lls) rest | otherwise = expand (expandDeclarationSplice s lls) rest @@ -291,12 +291,12 @@ expandExpressionSplice sp lls = concat [before, spliced:padding, end] -- ie: bar $(splice) | otherwise = s ++ " $ " where - s' = filter (not . isSpace) s + s' = filter (not . isSpace) s findindent = length . takeWhile isSpace addindent n = unlines . map (i ++) . lines where - i = take n $ repeat ' ' + i = take n $ repeat ' ' {- Tweaks code output by GHC in splices to actually build. Yipes. -} mangleCode :: String -> String @@ -315,7 +315,7 @@ mangleCode = flip_colon . remove_package_version . emptylambda where - {- Lambdas are often output without parens around them. + {- Lambdas are often output without parens around them. - This breaks when the lambda is immediately applied to a - parameter. - @@ -409,7 +409,7 @@ mangleCode = flip_colon restofline = manyTill (noneOf "\n") newline - {- For some reason, GHC sometimes doesn't like the multiline + {- For some reason, GHC sometimes doesn't like the multiline - strings it creates. It seems to get hung up on \{ at the - start of a new line sometimes, wanting it to not be escaped. - @@ -646,7 +646,7 @@ parsecAndReplace p s = case parse find "" s of Left _e -> s Right l -> concatMap (either return id) l where - find :: Parser [Either Char String] + find :: Parser [Either Char String] find = many $ try (Right <$> p) <|> (Left <$> anyChar) main :: IO () @@ -654,7 +654,7 @@ main = go =<< getArgs where go (destdir:log:header:[]) = run destdir log (Just header) go (destdir:log:[]) = run destdir log Nothing - go _ = error "usage: EvilSplicer destdir logfile [headerfile]" + go _ = error "usage: EvilSplicer destdir logfile [headerfile]" run destdir log mheader = do r <- parseFromFile splicesExtractor log diff --git a/Build/NullSoftInstaller.hs b/Build/NullSoftInstaller.hs index b8fc82605..22d3caf36 100644 --- a/Build/NullSoftInstaller.hs +++ b/Build/NullSoftInstaller.hs @@ -103,7 +103,7 @@ makeInstaller gitannex license extrabins launchers = nsis $ do name "git-annex" outFile $ str installer {- Installing into the same directory as git avoids needing to modify - - path myself, since the git installer already does it. -} + - path myself, since the git installer already does it. -} installDir gitInstallDir requestExecutionLevel Admin diff --git a/Build/OSXMkLibs.hs b/Build/OSXMkLibs.hs index 5640e4d36..ef668bb4a 100644 --- a/Build/OSXMkLibs.hs +++ b/Build/OSXMkLibs.hs @@ -112,7 +112,7 @@ expand_rpath libs replacement_libs cmd return $ map (replacem m) libs | otherwise = return libs where - probe c = "DYLD_PRINT_RPATHS=1 " ++ c ++ " --getting-rpath-dummy-option 2>&1 | grep RPATH" + probe c = "DYLD_PRINT_RPATHS=1 " ++ c ++ " --getting-rpath-dummy-option 2>&1 | grep RPATH" parse s = case words s of ("RPATH":"successful":"expansion":"of":old:"to:":new:[]) -> Just (old, new) diff --git a/Checks.hs b/Checks.hs index 7a9cd1e38..831c0a009 100644 --- a/Checks.hs +++ b/Checks.hs @@ -35,7 +35,7 @@ noDaemonRunning :: Command -> Command noDaemonRunning = addCheck $ whenM (isJust <$> daemonpid) $ error "You cannot run this command while git-annex watch or git-annex assistant is running." where - daemonpid = liftIO . checkDaemon =<< fromRepo gitAnnexPidFile + daemonpid = liftIO . checkDaemon =<< fromRepo gitAnnexPidFile dontCheck :: CommandCheck -> Command -> Command dontCheck check cmd = mutateCheck cmd $ \c -> filter (/= check) c diff --git a/CmdLine.hs b/CmdLine.hs index 606390130..7df310f69 100644 --- a/CmdLine.hs +++ b/CmdLine.hs @@ -58,7 +58,7 @@ dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do shutdown $ cmdnocommit cmd go _flags params (Left e) = do when fuzzy $ - autocorrect =<< Git.Config.global + autocorrect =<< Git.Config.global maybe (throw e) (\a -> a params) (cmdnorepo cmd) err msg = msg ++ "\n\n" ++ usage header allcmds cmd = Prelude.head cmds diff --git a/CmdLine/GitAnnexShell.hs b/CmdLine/GitAnnexShell.hs index 6c212b24d..91cfd3ede 100644 --- a/CmdLine/GitAnnexShell.hs +++ b/CmdLine/GitAnnexShell.hs @@ -66,7 +66,7 @@ options = commonOptions ++ check u = unexpectedUUID expected u checkGCryptUUID expected = check =<< getGCryptUUID True =<< gitRepo where - check (Just u) | u == toUUID expected = noop + check (Just u) | u == toUUID expected = noop check Nothing = unexpected expected "uninitialized repository" check (Just u) = unexpectedUUID expected u unexpectedUUID expected u = unexpected expected $ "UUID " ++ fromUUID u diff --git a/CmdLine/Seek.hs b/CmdLine/Seek.hs index 397a48118..238ed4291 100644 --- a/CmdLine/Seek.hs +++ b/CmdLine/Seek.hs @@ -107,7 +107,7 @@ withFilesUnlocked' :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> (F withFilesUnlocked' typechanged a params = seekActions $ prepFiltered a unlockedfiles where - check f = liftIO (notSymlink f) <&&> + check f = liftIO (notSymlink f) <&&> (isJust <$> catKeyFile f <||> isJust <$> catKeyFileHEAD f) unlockedfiles = filterM check =<< seekHelper typechanged params @@ -165,7 +165,7 @@ withKeyOptions keyop fallbackop params = do Just k -> go auto $ return [k] _ -> error "Can only specify one of file names, --all, --unused, or --key" where - go True _ = error "Cannot use --auto with --all or --unused or --key" + go True _ = error "Cannot use --auto with --all or --unused or --key" go False a = do matcher <- Limit.getMatcher seekActions $ map (process matcher) <$> a diff --git a/Command/Add.hs b/Command/Add.hs index e2b6d04fe..1bc20d819 100644 --- a/Command/Add.hs +++ b/Command/Add.hs @@ -125,7 +125,7 @@ lockDown' file = ifM crippledFileSystem - This is not done in direct mode, because files there need to - remain writable at all times. -} - go tmp = do + go tmp = do unlessM isDirect $ freezeContent file withTSDelta $ \delta -> liftIO $ do @@ -134,7 +134,7 @@ lockDown' file = ifM crippledFileSystem hClose h nukeFile tmpfile withhardlink delta tmpfile `catchIO` const (nohardlink delta) - nohardlink delta = do + nohardlink delta = do cache <- genInodeCache file delta return KeySource { keyFilename = file @@ -207,7 +207,7 @@ finishIngestDirect key source = do perform :: FilePath -> CommandPerform perform file = lockDown file >>= ingest >>= go where - go (Just key, cache) = next $ cleanup file key cache True + go (Just key, cache) = next $ cleanup file key cache True go (Nothing, _) = stop {- On error, put the file back so it doesn't seem to have vanished. diff --git a/Command/AddUrl.hs b/Command/AddUrl.hs index c21ce928f..87711663c 100644 --- a/Command/AddUrl.hs +++ b/Command/AddUrl.hs @@ -56,7 +56,7 @@ seek ps = do start :: Bool -> Maybe FilePath -> Maybe Int -> String -> CommandStart start relaxed optfile pathdepth s = go $ fromMaybe bad $ parseURI s where - (s', downloader) = getDownloader s + (s', downloader) = getDownloader s bad = fromMaybe (error $ "bad url " ++ s') $ parseURI $ escapeURIString isUnescapedInURI s' choosefile = flip fromMaybe optfile @@ -95,8 +95,8 @@ start relaxed optfile pathdepth s = go $ fromMaybe bad $ parseURI s performQuvi :: Bool -> URLString -> URLString -> FilePath -> CommandPerform performQuvi relaxed pageurl videourl file = ifAnnexed file addurl geturl where - quviurl = setDownloader pageurl QuviDownloader - addurl key = next $ cleanup quviurl file key Nothing + quviurl = setDownloader pageurl QuviDownloader + addurl key = next $ cleanup quviurl file key Nothing geturl = next $ isJust <$> addUrlFileQuvi relaxed quviurl videourl file #endif @@ -189,7 +189,7 @@ download url file = do , return Nothing ) where - runtransfer dummykey tmp = Transfer.notifyTransfer Transfer.Download (Just file) $ + runtransfer dummykey tmp = Transfer.notifyTransfer Transfer.Download (Just file) $ Transfer.download webUUID dummykey (Just file) Transfer.forwardRetry $ const $ do liftIO $ createDirectoryIfMissing True (parentDir tmp) downloadUrl [url] tmp diff --git a/Command/ConfigList.hs b/Command/ConfigList.hs index 219685c21..2aea29b22 100644 --- a/Command/ConfigList.hs +++ b/Command/ConfigList.hs @@ -29,7 +29,7 @@ start = do showConfig coreGCryptId =<< fromRepo (Git.Config.get coreGCryptId "") stop where - showConfig k v = liftIO $ putStrLn $ k ++ "=" ++ v + showConfig k v = liftIO $ putStrLn $ k ++ "=" ++ v {- The repository may not yet have a UUID; automatically initialize it - when there's a git-annex branch available. -} diff --git a/Command/Copy.hs b/Command/Copy.hs index ae254aae2..5acb722de 100644 --- a/Command/Copy.hs +++ b/Command/Copy.hs @@ -23,7 +23,7 @@ seek ps = do to <- getOptionField toOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID withKeyOptions - (Command.Move.startKey to from False) + (Command.Move.startKey to from False) (withFilesInGit $ whenAnnexed $ start to from) ps diff --git a/Command/EnableRemote.hs b/Command/EnableRemote.hs index 42ab43374..5e21a9dbd 100644 --- a/Command/EnableRemote.hs +++ b/Command/EnableRemote.hs @@ -29,7 +29,7 @@ start (name:ws) = go =<< InitRemote.findExisting name where config = Logs.Remote.keyValToConfig ws - go Nothing = unknownNameError "Unknown special remote name." + go Nothing = unknownNameError "Unknown special remote name." go (Just (u, c)) = do let fullconfig = config `M.union` c t <- InitRemote.findType fullconfig diff --git a/Command/Fsck.hs b/Command/Fsck.hs index a17662d62..f27f18e57 100644 --- a/Command/Fsck.hs +++ b/Command/Fsck.hs @@ -329,7 +329,7 @@ checkKeySizeOr bad key file = case Types.Key.keySize key of checkBackend :: Backend -> Key -> Maybe FilePath -> Annex Bool checkBackend backend key mfile = go =<< isDirect where - go False = do + go False = do content <- calcRepo $ gitAnnexLocation key checkBackendOr badContent backend key content go True = maybe nocheck checkdirect mfile diff --git a/Command/FuzzTest.hs b/Command/FuzzTest.hs index 7075aeddc..31f31be32 100644 --- a/Command/FuzzTest.hs +++ b/Command/FuzzTest.hs @@ -47,7 +47,7 @@ guardTest = unlessM (fromMaybe False . Git.Config.isTrue <$> getConfig key "") $ , "Refusing to run fuzz tests, since " ++ keyname ++ " is not set!" ] where - key = annexConfig "eat-my-repository" + key = annexConfig "eat-my-repository" (ConfigKey keyname) = key @@ -257,7 +257,7 @@ existingDir = do newFile :: IO (Maybe FuzzFile) newFile = go (100 :: Int) where - go 0 = return Nothing + go 0 = return Nothing go n = do f <- genFuzzFile ifM (doesnotexist (toFilePath f)) @@ -268,7 +268,7 @@ newFile = go (100 :: Int) newDir :: FilePath -> IO (Maybe FuzzDir) newDir parent = go (100 :: Int) where - go 0 = return Nothing + go 0 = return Nothing go n = do (FuzzDir d) <- genFuzzDir ifM (doesnotexist (parent d)) diff --git a/Command/Get.hs b/Command/Get.hs index d0be20018..a1db1f515 100644 --- a/Command/Get.hs +++ b/Command/Get.hs @@ -48,7 +48,7 @@ start' expensivecheck from key afile = stopUnless (not <$> inAnnex key) $ stopUnless (Command.Move.fromOk src key) $ go $ Command.Move.fromPerform src False key afile where - go a = do + go a = do showStart' "get" key afile next a diff --git a/Command/Import.hs b/Command/Import.hs index 97e3f7652..02f44a598 100644 --- a/Command/Import.hs +++ b/Command/Import.hs @@ -50,8 +50,8 @@ getDuplicateMode = gen <*> getflag cleanDuplicatesOption <*> getflag skipDuplicatesOption where - getflag = Annex.getFlag . optionName - gen False False False False = Default + getflag = Annex.getFlag . optionName + gen False False False False = Default gen True False False False = Duplicate gen False True False False = DeDuplicate gen False False True False = CleanDuplicates diff --git a/Command/ImportFeed.hs b/Command/ImportFeed.hs index 1fdba46a1..d11227cdf 100644 --- a/Command/ImportFeed.hs +++ b/Command/ImportFeed.hs @@ -153,7 +153,7 @@ performDownload relaxed cache todownload = case location todownload of rundownload videourl ("." ++ Quvi.linkSuffix link) $ addUrlFileQuvi relaxed quviurl videourl where - forced = Annex.getState Annex.force + forced = Annex.getState Annex.force {- Avoids downloading any urls that are already known to be - associated with a file in the annex, unless forced. -} @@ -192,7 +192,7 @@ performDownload relaxed cache todownload = case location todownload of , return $ Just f ) where - f = if n < 2 + f = if n < 2 then file else let (d, base) = splitFileName file diff --git a/Command/Indirect.hs b/Command/Indirect.hs index e146f13b7..97e6f5951 100644 --- a/Command/Indirect.hs +++ b/Command/Indirect.hs @@ -94,7 +94,7 @@ perform = do warnlocked showEndOk - warnlocked :: SomeException -> Annex () + warnlocked :: SomeException -> Annex () warnlocked e = do warning $ show e warning "leaving this file as-is; correct this problem and run git annex add on it" diff --git a/Command/Info.hs b/Command/Info.hs index 63bc92bbe..1bea17ab4 100644 --- a/Command/Info.hs +++ b/Command/Info.hs @@ -100,7 +100,7 @@ localInfo dir = showCustom (unwords ["info", dir]) $ do evalStateT (mapM_ showStat stats) =<< getLocalStatInfo dir return True where - tostats = map (\s -> s dir) + tostats = map (\s -> s dir) selStats :: [Stat] -> [Stat] -> Annex [Stat] selStats fast_stats slow_stats = do diff --git a/Command/Migrate.hs b/Command/Migrate.hs index cea9e9426..cab807d05 100644 --- a/Command/Migrate.hs +++ b/Command/Migrate.hs @@ -65,7 +65,7 @@ upgradableKey backend key = isNothing (Types.Key.keySize key) || backendupgradab perform :: FilePath -> Key -> Backend -> Backend -> CommandPerform perform file oldkey oldbackend newbackend = go =<< genkey where - go Nothing = stop + go Nothing = stop go (Just (newkey, knowngoodcontent)) | knowngoodcontent = finish newkey | otherwise = stopUnless checkcontent $ finish newkey diff --git a/Command/RecvKey.hs b/Command/RecvKey.hs index d5971d6cf..2ea03b055 100644 --- a/Command/RecvKey.hs +++ b/Command/RecvKey.hs @@ -63,7 +63,7 @@ start key = fieldTransfer Download key $ \_p -> Nothing -> return True Just size -> do size' <- fromIntegral . fileSize - <$> liftIO (getFileStatus tmp) + <$> liftIO (getFileStatus tmp) return $ size == size' if oksize then case Backend.maybeLookupBackendName (Types.Key.keyBackendName key) of @@ -76,7 +76,7 @@ start key = fieldTransfer Download key $ \_p -> warning "recvkey: received key with wrong size; discarding" return False where - runfsck check = ifM (check key tmp) + runfsck check = ifM (check key tmp) ( return True , do warning "recvkey: received key from direct mode repository seems to have changed as it was transferred; discarding" diff --git a/Command/Schedule.hs b/Command/Schedule.hs index a088dbef8..7b72990a7 100644 --- a/Command/Schedule.hs +++ b/Command/Schedule.hs @@ -27,7 +27,7 @@ seek = withWords start start :: [String] -> CommandStart start = parse where - parse (name:[]) = go name performGet + parse (name:[]) = go name performGet parse (name:expr:[]) = go name $ \uuid -> do showStart "schedile" name performSet expr uuid diff --git a/Command/Sync.hs b/Command/Sync.hs index 6a6a254b3..6819d25a0 100644 --- a/Command/Sync.hs +++ b/Command/Sync.hs @@ -356,7 +356,7 @@ syncFile rs f k = do handleDropsFrom locs' rs "unwanted" True k (Just f) Nothing callCommandAction where - wantget have = allM id + wantget have = allM id [ pure (not $ null have) , not <$> inAnnex k , wantGet True (Just k) (Just f) diff --git a/Command/TransferKeys.hs b/Command/TransferKeys.hs index fba0e6593..b9a8bf3be 100644 --- a/Command/TransferKeys.hs +++ b/Command/TransferKeys.hs @@ -57,7 +57,7 @@ runRequests readh writeh a = do fileEncoding writeh go =<< readrequests where - go (d:rn:k:f:rest) = do + go (d:rn:k:f:rest) = do case (deserialize d, deserialize rn, deserialize k, deserialize f) of (Just direction, Just remotename, Just key, Just file) -> do mremote <- Remote.byName' remotename diff --git a/Command/Uninit.hs b/Command/Uninit.hs index 3f57782fc..89ccc2102 100644 --- a/Command/Uninit.hs +++ b/Command/Uninit.hs @@ -100,7 +100,7 @@ prepareRemoveAnnexDir annexdir = removeUnannexed :: [Key] -> Annex [Key] removeUnannexed = go [] where - go c [] = return c + go c [] = return c go c (k:ks) = ifM (inAnnexCheck k $ liftIO . enoughlinks) ( do lockContent k removeAnnex diff --git a/Command/Vicfg.hs b/Command/Vicfg.hs index 1f1695536..26a75dab2 100644 --- a/Command/Vicfg.hs +++ b/Command/Vicfg.hs @@ -136,7 +136,7 @@ genCfg cfg descs = unlines $ intercalate [""] (\(s, u) -> line "group" u $ unwords $ S.toList s) (\u -> lcom $ line "group" u "") where - grouplist = unwords $ map fromStandardGroup [minBound..] + grouplist = unwords $ map fromStandardGroup [minBound..] preferredcontent = settings cfg descs cfgPreferredContentMap [ com "Repository preferred contents" @@ -157,7 +157,7 @@ genCfg cfg descs = unlines $ intercalate [""] (\(s, g) -> gline g s) (\g -> gline g "") where - gline g value = [ unwords ["groupwanted", g, "=", value] ] + gline g value = [ unwords ["groupwanted", g, "=", value] ] allgroups = S.unions $ stdgroups : M.elems (cfgGroupMap cfg) stdgroups = S.fromList $ map fromStandardGroup [minBound..maxBound] diff --git a/Command/Wanted.hs b/Command/Wanted.hs index bae450d26..9c3b0ff98 100644 --- a/Command/Wanted.hs +++ b/Command/Wanted.hs @@ -26,7 +26,7 @@ seek = withWords start start :: [String] -> CommandStart start = parse where - parse (name:[]) = go name performGet + parse (name:[]) = go name performGet parse (name:expr:[]) = go name $ \uuid -> do showStart "wanted" name performSet expr uuid diff --git a/Config/Cost.hs b/Config/Cost.hs index 2d94a6b15..44a26f064 100644 --- a/Config/Cost.hs +++ b/Config/Cost.hs @@ -52,7 +52,7 @@ insertCostAfter l pos | otherwise = firstsegment ++ [costBetween item nextitem ] ++ lastsegment where - nextpos = pos + 1 + nextpos = pos + 1 maxpos = length l - 1 item = l !! pos diff --git a/Config/Files.hs b/Config/Files.hs index 30ed0a3cf..8d5c1fd12 100644 --- a/Config/Files.hs +++ b/Config/Files.hs @@ -66,4 +66,4 @@ readProgramFile = do ) ) where - cmd = "git-annex" + cmd = "git-annex" diff --git a/Git/CatFile.hs b/Git/CatFile.hs index 8e64fc558..d0bcef4fb 100644 --- a/Git/CatFile.hs +++ b/Git/CatFile.hs @@ -94,7 +94,7 @@ catTree :: CatFileHandle -> Ref -> IO [(FilePath, FileMode)] catTree h treeref = go <$> catObjectDetails h treeref where go (Just (b, _, TreeObject)) = parsetree [] b - go _ = [] + go _ = [] parsetree c b = case L.break (== 0) b of (modefile, rest) diff --git a/Git/Command.hs b/Git/Command.hs index 30d2dcbf9..c61cc9fe8 100644 --- a/Git/Command.hs +++ b/Git/Command.hs @@ -79,7 +79,7 @@ pipeWriteRead params writer repo = assertLocal repo $ writeReadProcessEnv "git" (toCommand $ gitCommandLine params repo) (gitEnv repo) writer (Just adjusthandle) where - adjusthandle h = do + adjusthandle h = do fileEncoding h hSetNewlineMode h noNewlineTranslation @@ -117,7 +117,7 @@ gitCoProcessStart restartable params repo = CoProcess.start numrestarts "git" (toCommand $ gitCommandLine params repo) (gitEnv repo) where - {- If a long-running git command like cat-file --batch + {- If a long-running git command like cat-file --batch - crashes, it will likely start up again ok. If it keeps crashing - 10 times, something is badly wrong. -} numrestarts = if restartable then 10 else 0 diff --git a/Git/Config.hs b/Git/Config.hs index 171c3e6c6..32c0dd1cc 100644 --- a/Git/Config.hs +++ b/Git/Config.hs @@ -167,7 +167,7 @@ coreBare = "core.bare" fromPipe :: Repo -> String -> [CommandParam] -> IO (Either SomeException (Repo, String)) fromPipe r cmd params = try $ withHandle StdoutHandle createProcessSuccess p $ \h -> do - fileEncoding h + fileEncoding h val <- hGetContentsStrict h r' <- store val r return (r', val) diff --git a/Git/GCrypt.hs b/Git/GCrypt.hs index c2a5a98fe..db067e25c 100644 --- a/Git/GCrypt.hs +++ b/Git/GCrypt.hs @@ -38,12 +38,12 @@ isEncrypted _ = False encryptedRemote :: Repo -> Repo -> IO Repo encryptedRemote baserepo = go where - go Repo { location = Url url } + go Repo { location = Url url } | urlPrefix `isPrefixOf` u = fromRemoteLocation (drop plen u) baserepo | otherwise = notencrypted where - u = show url + u = show url plen = length urlPrefix go _ = notencrypted notencrypted = error "not a gcrypt encrypted repository" @@ -92,7 +92,7 @@ getParticiantList globalconfigrepo repo remotename = KeyIds $ parse $ firstJust ] where defaultkey = "gcrypt.participants" - parse (Just "simple") = [] + parse (Just "simple") = [] parse (Just l) = words l parse Nothing = [] diff --git a/Git/LsTree.hs b/Git/LsTree.hs index 6d3ca4813..ca5e323e0 100644 --- a/Git/LsTree.hs +++ b/Git/LsTree.hs @@ -44,7 +44,7 @@ lsTreeParams t = [ Params "ls-tree --full-tree -z -r --", File $ fromRef t ] lsTreeFiles :: Ref -> [FilePath] -> Repo -> IO [TreeItem] lsTreeFiles t fs repo = map parseLsTree <$> pipeNullSplitStrict ps repo where - ps = [Params "ls-tree --full-tree -z --", File $ fromRef t] ++ map File fs + ps = [Params "ls-tree --full-tree -z --", File $ fromRef t] ++ map File fs {- Parses a line of ls-tree output. - (The --long format is not currently supported.) -} diff --git a/Git/Remote.hs b/Git/Remote.hs index 7573c87ee..7e8e5f817 100644 --- a/Git/Remote.hs +++ b/Git/Remote.hs @@ -70,7 +70,7 @@ remoteLocationIsSshUrl _ = False parseRemoteLocation :: String -> Repo -> RemoteLocation parseRemoteLocation s repo = ret $ calcloc s where - ret v + ret v #ifdef mingw32_HOST_OS | dosstyle v = RemotePath (dospath v) #endif diff --git a/Git/Repair.hs b/Git/Repair.hs index 43f0a56fa..0769ecb30 100644 --- a/Git/Repair.hs +++ b/Git/Repair.hs @@ -222,7 +222,7 @@ badBranches missing r = filterM isbad =<< getAllRefs r getAllRefs :: Repo -> IO [Ref] getAllRefs r = map toref <$> dirContentsRecursive refdir where - refdir = localGitDir r "refs" + refdir = localGitDir r "refs" toref = Ref . relPathDirToFile (localGitDir r) explodePackedRefsFile :: Repo -> IO () @@ -411,7 +411,7 @@ displayList items header putStrLn header putStr $ unlines $ map (\i -> "\t" ++ i) truncateditems where - numitems = length items + numitems = length items truncateditems | numitems > 10 = take 10 items ++ ["(and " ++ show (numitems - 10) ++ " more)"] | otherwise = items diff --git a/Git/Version.hs b/Git/Version.hs index 5ad1d5959..5c61f859e 100644 --- a/Git/Version.hs +++ b/Git/Version.hs @@ -21,7 +21,7 @@ instance Show GitVersion where installed :: IO GitVersion installed = normalize . extract <$> readProcess "git" ["--version"] where - extract s = case lines s of + extract s = case lines s of [] -> "" (l:_) -> unwords $ drop 2 $ words l diff --git a/Limit.hs b/Limit.hs index 89dd9d33e..573bd57b6 100644 --- a/Limit.hs +++ b/Limit.hs @@ -234,7 +234,7 @@ limitSize vs s = case readSize dataUnits s of Nothing -> Left "bad size" Just sz -> Right $ go sz where - go sz _ (MatchingFile fi) = lookupFileKey fi >>= check fi sz + go sz _ (MatchingFile fi) = lookupFileKey fi >>= check fi sz go sz _ (MatchingKey key) = checkkey sz key checkkey sz key = return $ keySize key `vs` Just sz check _ sz (Just key) = checkkey sz key @@ -254,7 +254,7 @@ limitMetaData s = case parseMetaData s of let cglob = compileGlob (fromMetaValue v) CaseInsensative in Right $ const $ checkKey (check f cglob) where - check f cglob k = not . S.null + check f cglob k = not . S.null . S.filter (matchGlob cglob . fromMetaValue) . metaDataValues f <$> getCurrentMetaData k diff --git a/Locations.hs b/Locations.hs index 0369c7a1c..bcf793bda 100644 --- a/Locations.hs +++ b/Locations.hs @@ -148,7 +148,7 @@ gitAnnexLink file key r = do loc <- gitAnnexLocation' key r False return $ relPathDirToFile (parentDir absfile) loc where - whoops = error $ "unable to normalize " ++ file + whoops = error $ "unable to normalize " ++ file {- File used to lock a key's content. -} gitAnnexContentLock :: Key -> Git.Repo -> GitConfig -> IO FilePath @@ -356,7 +356,7 @@ isLinkToAnnex s = (pathSeparator:objectDir) `isInfixOf` s preSanitizeKeyName :: String -> String preSanitizeKeyName = concatMap escape where - escape c + escape c | isAsciiUpper c || isAsciiLower c || isDigit c = [c] | c `elem` ".-_ " = [c] -- common, assumed safe | c `elem` "/%:" = [c] -- handled by keyFile diff --git a/Logs.hs b/Logs.hs index ff7b7dcf0..1b7a61efe 100644 --- a/Logs.hs +++ b/Logs.hs @@ -117,7 +117,7 @@ urlLogFileKey path | ext == urlLogExt = fileKey base | otherwise = Nothing where - file = takeFileName path + file = takeFileName path (base, ext) = splitAt (length file - extlen) file extlen = length urlLogExt @@ -144,7 +144,7 @@ chunkLogFileKey path | ext == chunkLogExt = fileKey base | otherwise = Nothing where - file = takeFileName path + file = takeFileName path (base, ext) = splitAt (length file - extlen) file extlen = length chunkLogExt @@ -176,10 +176,10 @@ prop_logs_sane dummykey = and , expect gotOtherLog (getLogVariety $ numcopiesLog) ] where - expect = maybe False + expect = maybe False gotUUIDBasedLog UUIDBasedLog = True gotUUIDBasedLog _ = False - gotNewUUIDBasedLog NewUUIDBasedLog = True + gotNewUUIDBasedLog NewUUIDBasedLog = True gotNewUUIDBasedLog _ = False gotChunkLog (ChunkLog k) = k == dummykey gotChunkLog _ = False diff --git a/Logs/FsckResults.hs b/Logs/FsckResults.hs index 619dd586c..23367a3d3 100644 --- a/Logs/FsckResults.hs +++ b/Logs/FsckResults.hs @@ -28,7 +28,7 @@ writeFsckResults u fsckresults = do | S.null s -> nukeFile logfile | otherwise -> store s t logfile where - store s t logfile = do + store s t logfile = do createDirectoryIfMissing True (parentDir logfile) liftIO $ viaTmp writeFile logfile $ serialize s t serialize s t = diff --git a/Logs/MetaData.hs b/Logs/MetaData.hs index 250317090..d63a87470 100644 --- a/Logs/MetaData.hs +++ b/Logs/MetaData.hs @@ -67,7 +67,7 @@ getCurrentMetaData k = do return $ currentMetaData $ unionMetaData loggedmeta (lastchanged ls loggedmeta) where - lastchanged [] _ = emptyMetaData + lastchanged [] _ = emptyMetaData lastchanged ls (MetaData currentlyset) = let m = foldl' (flip M.union) M.empty (map genlastchanged ls) in MetaData $ diff --git a/Logs/Schedule.hs b/Logs/Schedule.hs index 1d78467bb..540667059 100644 --- a/Logs/Schedule.hs +++ b/Logs/Schedule.hs @@ -35,7 +35,7 @@ scheduleSet uuid@(UUID _) activities = do Annex.Branch.change scheduleLog $ showLog id . changeLog ts uuid val . parseLog Just where - val = fromScheduledActivities activities + val = fromScheduledActivities activities scheduleSet NoUUID _ = error "unknown UUID; cannot modify" scheduleMap :: Annex (M.Map UUID [ScheduledActivity]) diff --git a/Logs/Transitions.hs b/Logs/Transitions.hs index 64e9d3344..15ea32401 100644 --- a/Logs/Transitions.hs +++ b/Logs/Transitions.hs @@ -53,7 +53,7 @@ showTransitions = unlines . map showTransitionLine . S.elems parseTransitions :: String -> Maybe Transitions parseTransitions = check . map parseTransitionLine . lines where - check l + check l | all isJust l = Just $ S.fromList $ catMaybes l | otherwise = Nothing @@ -68,8 +68,8 @@ showTransitionLine (TransitionLine ts t) = unwords [show t, show ts] parseTransitionLine :: String -> Maybe TransitionLine parseTransitionLine s = TransitionLine <$> pdate ds <*> readish ts where - ws = words s - ts = Prelude.head ws + ws = words s + ts = Prelude.head ws ds = unwords $ Prelude.tail ws pdate = utcTimeToPOSIXSeconds <$$> parseTime defaultTimeLocale "%s%Qs" diff --git a/Logs/Web.hs b/Logs/Web.hs index ede600ec2..1d16e10b3 100644 --- a/Logs/Web.hs +++ b/Logs/Web.hs @@ -76,7 +76,7 @@ knownUrls = do return $ concat r where geturls Nothing = return [] - geturls (Just logsha) = getLog . L.unpack <$> catObject logsha + geturls (Just logsha) = getLog . L.unpack <$> catObject logsha data Downloader = DefaultDownloader | QuviDownloader diff --git a/Remote.hs b/Remote.hs index 8a8eb64df..0e725c215 100644 --- a/Remote.hs +++ b/Remote.hs @@ -101,7 +101,7 @@ byName (Just n) = either error Just <$> byName' n byNameWithUUID :: Maybe RemoteName -> Annex (Maybe Remote) byNameWithUUID = checkuuid <=< byName where - checkuuid Nothing = return Nothing + checkuuid Nothing = return Nothing checkuuid (Just r) | uuid r == NoUUID = if remoteAnnexIgnore (gitconfig r) diff --git a/Remote/External.hs b/Remote/External.hs index c3ea7e1db..d40972412 100644 --- a/Remote/External.hs +++ b/Remote/External.hs @@ -169,7 +169,7 @@ handleRequest' lck external req mp responsehandler go | otherwise = go where - go = do + go = do sendMessage lck external req loop loop = receiveMessage lck external responsehandler diff --git a/Remote/GCrypt.hs b/Remote/GCrypt.hs index f1d561d23..fc7718a2a 100644 --- a/Remote/GCrypt.hs +++ b/Remote/GCrypt.hs @@ -147,7 +147,7 @@ rsyncTransport r | ":" `isInfixOf` loc = sshtransport $ separate (== ':') loc | otherwise = othertransport where - loc = Git.repoLocation r + loc = Git.repoLocation r sshtransport (host, path) = do let rsyncpath = if "/~/" `isPrefixOf` path then drop 3 path @@ -166,7 +166,7 @@ gCryptSetup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> Annex (RemoteConf gCryptSetup mu _ c = go $ M.lookup "gitrepo" c where remotename = fromJust (M.lookup "name" c) - go Nothing = error "Specify gitrepo=" + go Nothing = error "Specify gitrepo=" go (Just gitrepo) = do (c', _encsetup) <- encryptionSetup c inRepo $ Git.Command.run @@ -234,7 +234,7 @@ setupRepo gcryptid r - create the objectDir on the remote, - which is needed for direct rsync of objects to work. -} - rsyncsetup = Remote.Rsync.withRsyncScratchDir $ \tmp -> do + rsyncsetup = Remote.Rsync.withRsyncScratchDir $ \tmp -> do liftIO $ createDirectoryIfMissing True $ tmp objectDir (rsynctransport, rsyncurl, _) <- rsyncTransport r let tmpconfig = tmp "config" @@ -266,7 +266,7 @@ isShell r = case method of AccessShell -> True _ -> False where - method = toAccessMethod $ fromMaybe "" $ + method = toAccessMethod $ fromMaybe "" $ remoteAnnexGCrypt $ gitconfig r shellOrRsync :: Remote -> Annex a -> Annex a -> Annex a @@ -352,7 +352,7 @@ checkKey r rsyncopts k | Git.repoIsSsh (repo r) = shellOrRsync r checkshell checkrsync | otherwise = unsupportedUrl where - checkrsync = Remote.Rsync.checkKey (repo r) rsyncopts k + checkrsync = Remote.Rsync.checkKey (repo r) rsyncopts k checkshell = Ssh.inAnnex (repo r) k {- Annexed objects are hashed using lower-case directories for max diff --git a/Remote/Git.hs b/Remote/Git.hs index 6397c1a2e..a249f43b2 100644 --- a/Remote/Git.hs +++ b/Remote/Git.hs @@ -305,7 +305,7 @@ inAnnex rmt key | Git.repoIsUrl r = checkremote | otherwise = checklocal where - r = repo rmt + r = repo rmt checkhttp = do showChecking r ifM (Url.withUrlOptions $ \uo -> anyM (\u -> Url.checkBoth u (keySize key) uo) (keyUrls rmt key)) diff --git a/Remote/Helper/Chunked.hs b/Remote/Helper/Chunked.hs index 271978658..eb5dbc793 100644 --- a/Remote/Helper/Chunked.hs +++ b/Remote/Helper/Chunked.hs @@ -123,7 +123,7 @@ storeChunks u chunkconfig k f p storer checker = loop bytesprocessed (chunk, bs) chunkkeys | L.null chunk && numchunks > 0 = do - -- Once all chunks are successfully + -- Once all chunks are successfully -- stored, update the chunk log. chunksStored u k (FixedSizeChunks chunksize) numchunks return True @@ -138,7 +138,7 @@ storeChunks u chunkconfig k f p storer checker = ) where numchunks = numChunks chunkkeys - {- The MeterUpdate that is passed to the action + {- The MeterUpdate that is passed to the action - storing a chunk is offset, so that it reflects - the total bytes that have already been stored - in previous chunks. -} @@ -290,7 +290,7 @@ retrieveChunks retriever u chunkconfig encryptor basek dest basep sink hSeek h AbsoluteSeek startpoint return h - {- Progress meter updating is a bit tricky: If the Retriever + {- Progress meter updating is a bit tricky: If the Retriever - populates a file, it is responsible for updating progress - as the file is being retrieved. - diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs index ba9ff4fb4..5b9db9b08 100644 --- a/Remote/Helper/Special.hs +++ b/Remote/Helper/Special.hs @@ -196,7 +196,7 @@ specialRemote' cfg c preparestorer prepareretriever prepareremover preparecheckp retrieveKeyFileGen k dest p enc = safely $ prepareretriever k $ safely . go where - go (Just retriever) = displayprogress p k $ \p' -> + go (Just retriever) = displayprogress p k $ \p' -> retrieveChunks retriever (uuid baser) chunkconfig enck k dest p' (sink dest enc) go Nothing = return False @@ -210,7 +210,7 @@ specialRemote' cfg c preparestorer prepareretriever prepareremover preparecheckp checkPresentGen k enc = preparecheckpresent k go where - go (Just checker) = checkPresentChunks checker (uuid baser) chunkconfig enck k + go (Just checker) = checkPresentChunks checker (uuid baser) chunkconfig enck k go Nothing = cantCheck baser enck = maybe id snd enc diff --git a/Remote/Hook.hs b/Remote/Hook.hs index 45a0ae742..707e2cb75 100644 --- a/Remote/Hook.hs +++ b/Remote/Hook.hs @@ -138,7 +138,7 @@ checkKey r h k = do v <- lookupHook h action liftIO $ check v where - action = "checkpresent" + action = "checkpresent" findkey s = key2file k `elem` lines s check Nothing = error $ action ++ " hook misconfigured" check (Just hook) = do diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs index 643411149..7a965aa9d 100644 --- a/Remote/Rsync.hs +++ b/Remote/Rsync.hs @@ -175,7 +175,7 @@ store o k src meterupdate = withRsyncScratchDir $ \tmp -> do ] else return False where - {- If the key being sent is encrypted or chunked, the file + {- If the key being sent is encrypted or chunked, the file - containing its content is a temp file, and so can be - renamed into place. Otherwise, the file is the annexed - object file, and has to be copied or hard linked into place. -} diff --git a/Remote/Tahoe.hs b/Remote/Tahoe.hs index bde8ee9d7..5c1729448 100644 --- a/Remote/Tahoe.hs +++ b/Remote/Tahoe.hs @@ -167,7 +167,7 @@ writeSharedConvergenceSecret configdir scs = getSharedConvergenceSecret :: TahoeConfigDir -> IO SharedConvergenceSecret getSharedConvergenceSecret configdir = go (60 :: Int) where - f = convergenceFile configdir + f = convergenceFile configdir go n | n == 0 = error $ "tahoe did not write " ++ f ++ " after 1 minute. Perhaps the daemon failed to start?" | otherwise = do @@ -190,7 +190,7 @@ startTahoeDaemon configdir = void $ boolTahoe configdir "start" [] withTahoeConfigDir :: TahoeHandle -> (TahoeConfigDir -> IO a) -> IO a withTahoeConfigDir (TahoeHandle configdir v) a = go =<< atomically needsstart where - go True = do + go True = do startTahoeDaemon configdir a configdir go False = a configdir diff --git a/Remote/Web.hs b/Remote/Web.hs index 04b453277..ef7d2b39a 100644 --- a/Remote/Web.hs +++ b/Remote/Web.hs @@ -120,7 +120,7 @@ checkKey' key us = firsthit us (Right False) $ \u -> do Url.withUrlOptions $ catchMsgIO . Url.checkBoth u' (keySize key) where - firsthit [] miss _ = return miss + firsthit [] miss _ = return miss firsthit (u:rest) _ a = do r <- a u case r of diff --git a/RemoteDaemon/Transport/Ssh.hs b/RemoteDaemon/Transport/Ssh.hs index db6b6127c..afedf559e 100644 --- a/RemoteDaemon/Transport/Ssh.hs +++ b/RemoteDaemon/Transport/Ssh.hs @@ -119,5 +119,5 @@ robustly backoff a = caught =<< catchDefaultIO ConnectionClosed a | b2 > maxbackoff = maxbackoff | otherwise = b2 where - b2 = backoff * 2 + b2 = backoff * 2 maxbackoff = 3600 -- one hour diff --git a/Test.hs b/Test.hs index 6348b0d6d..50d2f1d55 100644 --- a/Test.hs +++ b/Test.hs @@ -122,7 +122,7 @@ main ps = do #else handleParseResult $ execParserPure pprefs pinfo args #endif - progdesc = "git-annex test" + progdesc = "git-annex test" ingredients :: [Ingredient] ingredients = @@ -822,7 +822,7 @@ test_conflict_resolution_movein_regression testenv = withtmpclonerepo testenv Fa - be missing the content of the file that had - been put in it. -} forM_ [r1, r2] $ \r -> indir testenv r $ do - git_annex testenv "get" [] @? "unable to get all files after merge conflict resolution in " ++ rname r + git_annex testenv "get" [] @? "unable to get all files after merge conflict resolution in " ++ rname r {- Simple case of conflict resolution; 2 different versions of annexed - file. -} @@ -1404,7 +1404,7 @@ intmpclonerepoInDirect testenv a = intmpclonerepo testenv $ , a ) where - isdirect = annexeval $ do + isdirect = annexeval $ do Annex.Init.initialize Nothing Config.isDirect diff --git a/Types/Key.hs b/Types/Key.hs index 5bb41e15f..da9ff494a 100644 --- a/Types/Key.hs +++ b/Types/Key.hs @@ -133,7 +133,7 @@ prop_idempotent_key_decode f | normalfieldorder = maybe True (\k -> key2file k == f) (file2key f) | otherwise = True where - -- file2key will accept the fields in any order, so don't + -- file2key will accept the fields in any order, so don't -- try the test unless the fields are in the normal order normalfieldorder = fields `isPrefixOf` "smSC" fields = map (f !!) $ filter (< length f) $ map succ $ diff --git a/Types/MetaData.hs b/Types/MetaData.hs index 8df56734d..f19e0b439 100644 --- a/Types/MetaData.hs +++ b/Types/MetaData.hs @@ -290,4 +290,4 @@ prop_metadata_serialize f v m = and , deserialize (serialize m') == Just m' ] where - m' = removeEmptyFields m + m' = removeEmptyFields m diff --git a/Types/StandardGroups.hs b/Types/StandardGroups.hs index 37ba6e9c6..66c1dd5ef 100644 --- a/Types/StandardGroups.hs +++ b/Types/StandardGroups.hs @@ -96,7 +96,7 @@ standardPreferredContent UnwantedGroup = "exclude=*" notArchived :: String notArchived = "not (copies=archive:1 or copies=smallarchive:1)" - + {- Most repositories want any content that is only on untrusted - or dead repositories, or that otherwise does not have enough copies. - Does not look at .gitattributes since that is quite a lot slower. diff --git a/Utility/Batch.hs b/Utility/Batch.hs index d6dadae67..ff81318fb 100644 --- a/Utility/Batch.hs +++ b/Utility/Batch.hs @@ -32,7 +32,7 @@ batch :: IO a -> IO a #if defined(linux_HOST_OS) || defined(__ANDROID__) batch a = wait =<< batchthread where - batchthread = asyncBound $ do + batchthread = asyncBound $ do setProcessPriority 0 maxNice a #else diff --git a/Utility/CoProcess.hs b/Utility/CoProcess.hs index 332c09d49..97826ec1e 100644 --- a/Utility/CoProcess.hs +++ b/Utility/CoProcess.hs @@ -65,7 +65,7 @@ query ch send receive = do restartable s (receive $ coProcessFrom s) return where - restartable s a cont + restartable s a cont | coProcessNumRestarts (coProcessSpec s) > 0 = maybe restart cont =<< catchMaybeIO a | otherwise = cont =<< a @@ -87,7 +87,7 @@ rawMode ch = do raw $ coProcessTo s return ch where - raw h = do + raw h = do fileEncoding h #ifdef mingw32_HOST_OS hSetNewlineMode h noNewlineTranslation diff --git a/Utility/CopyFile.hs b/Utility/CopyFile.hs index 6601d0a80..503ab842a 100644 --- a/Utility/CopyFile.hs +++ b/Utility/CopyFile.hs @@ -47,10 +47,10 @@ createLinkOrCopy :: FilePath -> FilePath -> IO Bool #ifndef mingw32_HOST_OS createLinkOrCopy src dest = go `catchIO` const fallback where - go = do + go = do createLink src dest return True - fallback = copyFileExternal CopyAllMetaData src dest + fallback = copyFileExternal CopyAllMetaData src dest #else createLinkOrCopy = copyFileExternal CopyAllMetaData #endif diff --git a/Utility/Daemon.hs b/Utility/Daemon.hs index 2f0f84179..0615149e5 100644 --- a/Utility/Daemon.hs +++ b/Utility/Daemon.hs @@ -175,7 +175,7 @@ winLockFile pid pidfile = do cleanstale return $ prefix ++ show pid ++ suffix where - prefix = pidfile ++ "." + prefix = pidfile ++ "." suffix = ".lck" cleanstale = mapM_ (void . tryIO . removeFile) =<< (filter iswinlockfile <$> dirContents (parentDir pidfile)) diff --git a/Utility/DataUnits.hs b/Utility/DataUnits.hs index 7575af21f..e035b2f86 100644 --- a/Utility/DataUnits.hs +++ b/Utility/DataUnits.hs @@ -120,7 +120,7 @@ roughSize units short i showUnit x (Unit size abbrev name) = s ++ " " ++ unit where - v = (fromInteger x :: Double) / fromInteger size + v = (fromInteger x :: Double) / fromInteger size s = showImprecise 2 v unit | short = abbrev diff --git a/Utility/Directory.hs b/Utility/Directory.hs index a4429d5b9..e4e4b80a7 100644 --- a/Utility/Directory.hs +++ b/Utility/Directory.hs @@ -56,7 +56,7 @@ dirContentsRecursive = dirContentsRecursiveSkipping (const False) True dirContentsRecursiveSkipping :: (FilePath -> Bool) -> Bool -> FilePath -> IO [FilePath] dirContentsRecursiveSkipping skipdir followsubdirsymlinks topdir = go [topdir] where - go [] = return [] + go [] = return [] go (dir:dirs) | skipdir (takeFileName dir) = go dirs | otherwise = unsafeInterleaveIO $ do @@ -87,7 +87,7 @@ dirContentsRecursiveSkipping skipdir followsubdirsymlinks topdir = go [topdir] dirTreeRecursiveSkipping :: (FilePath -> Bool) -> FilePath -> IO [FilePath] dirTreeRecursiveSkipping skipdir topdir = go [] [topdir] where - go c [] = return c + go c [] = return c go c (dir:dirs) | skipdir (takeFileName dir) = go c dirs | otherwise = unsafeInterleaveIO $ do diff --git a/Utility/ExternalSHA.hs b/Utility/ExternalSHA.hs index 595acd8cf..858d04e6a 100644 --- a/Utility/ExternalSHA.hs +++ b/Utility/ExternalSHA.hs @@ -57,7 +57,7 @@ externalSHA command shasize file = do Left $ "Unexpected character in output of " ++ command ++ "\"" ++ sha ++ "\"" | otherwise = Right sha' where - sha' = map toLower sha + sha' = map toLower sha expectedSHALength :: Int -> Int expectedSHALength 1 = 40 diff --git a/Utility/FileSystemEncoding.hs b/Utility/FileSystemEncoding.hs index b81fdc532..fa4b39aa3 100644 --- a/Utility/FileSystemEncoding.hs +++ b/Utility/FileSystemEncoding.hs @@ -111,7 +111,7 @@ truncateFilePath :: Int -> FilePath -> FilePath #ifndef mingw32_HOST_OS truncateFilePath n = go . reverse where - go f = + go f = let bytes = decodeW8 f in if length bytes <= n then reverse f diff --git a/Utility/Format.hs b/Utility/Format.hs index 2a5ae5c34..78620f9b9 100644 --- a/Utility/Format.hs +++ b/Utility/Format.hs @@ -117,7 +117,7 @@ decode_c s = unescape ("", s) handle (x:'x':n1:n2:rest) | isescape x && allhex = (fromhex, rest) where - allhex = isHexDigit n1 && isHexDigit n2 + allhex = isHexDigit n1 && isHexDigit n2 fromhex = [chr $ readhex [n1, n2]] readhex h = Prelude.read $ "0x" ++ h :: Int handle (x:n1:n2:n3:rest) diff --git a/Utility/Gpg.hs b/Utility/Gpg.hs index f9b60f276..f880e55fa 100644 --- a/Utility/Gpg.hs +++ b/Utility/Gpg.hs @@ -166,7 +166,7 @@ secretKeys :: IO (M.Map KeyId UserId) secretKeys = catchDefaultIO M.empty makemap where makemap = M.fromList . parse . lines <$> readStrict params - params = [Params "--with-colons --list-secret-keys --fixed-list-mode"] + params = [Params "--with-colons --list-secret-keys --fixed-list-mode"] parse = extract [] Nothing . map (split ":") extract c (Just keyid) (("uid":_:_:_:_:_:_:_:_:userid:_):rest) = extract ((keyid, decode_c userid):c) Nothing rest @@ -196,7 +196,7 @@ genSecretKey keytype passphrase userid keysize = withHandle StdinHandle createProcessSuccess (proc gpgcmd params) feeder where params = ["--batch", "--gen-key"] - feeder h = do + feeder h = do hPutStr h $ unlines $ catMaybes [ Just $ "Key-Type: " ++ case keytype of @@ -232,7 +232,7 @@ genRandom highQuality size = checksize <$> readStrict randomquality :: Int randomquality = if highQuality then 2 else 1 - {- The size is the number of bytes of entropy desired; the data is + {- The size is the number of bytes of entropy desired; the data is - base64 encoded, so needs 8 bits to represent every 6 bytes of - entropy. -} expectedlength = size * 8 `div` 6 diff --git a/Utility/HumanTime.hs b/Utility/HumanTime.hs index 2aef1b09c..4214ea680 100644 --- a/Utility/HumanTime.hs +++ b/Utility/HumanTime.hs @@ -47,8 +47,8 @@ daysToDuration i = Duration $ i * dsecs parseDuration :: String -> Maybe Duration parseDuration = Duration <$$> go 0 where - go n [] = return n - go n s = do + go n [] = return n + go n s = do num <- readish s :: Maybe Integer case dropWhile isDigit s of (c:rest) -> do diff --git a/Utility/InodeCache.hs b/Utility/InodeCache.hs index 91359457a..328b77595 100644 --- a/Utility/InodeCache.hs +++ b/Utility/InodeCache.hs @@ -182,7 +182,7 @@ checkSentinalFile s = do SentinalStatus (not unchanged) tsdelta where #ifdef mingw32_HOST_OS - unchanged = oldinode == newinode && oldsize == newsize + unchanged = oldinode == newinode && oldsize == newsize tsdelta = TSDelta $ do -- Run when generating an InodeCache, -- to get the current delta. diff --git a/Utility/Matcher.hs b/Utility/Matcher.hs index 76f8903f5..3356bdd07 100644 --- a/Utility/Matcher.hs +++ b/Utility/Matcher.hs @@ -90,7 +90,7 @@ tokenGroups :: [Token op] -> [TokenGroup op] tokenGroups [] = [] tokenGroups (t:ts) = go t where - go Open = + go Open = let (gr, rest) = findClose ts in gr : tokenGroups rest go Close = tokenGroups ts -- not picky about missing Close @@ -101,7 +101,7 @@ findClose l = let (g, rest) = go [] l in (Group (reverse g), rest) where - go c [] = (c, []) -- not picky about extra Close + go c [] = (c, []) -- not picky about extra Close go c (t:ts) = dispatch t where dispatch Close = (c, ts) diff --git a/Utility/Path.hs b/Utility/Path.hs index 99c9438bf..9035cbc49 100644 --- a/Utility/Path.hs +++ b/Utility/Path.hs @@ -235,11 +235,11 @@ toCygPath p | null drive = recombine parts | otherwise = recombine $ "/cygdrive" : driveletter drive : parts where - (drive, p') = splitDrive p + (drive, p') = splitDrive p parts = splitDirectories p' - driveletter = map toLower . takeWhile (/= ':') + driveletter = map toLower . takeWhile (/= ':') recombine = fixtrailing . Posix.joinPath - fixtrailing s + fixtrailing s | hasTrailingPathSeparator p = Posix.addTrailingPathSeparator s | otherwise = s #endif @@ -272,7 +272,7 @@ fileNameLengthLimit dir = do sanitizeFilePath :: String -> FilePath sanitizeFilePath = map sanitize where - sanitize c + sanitize c | c == '.' = c | isSpace c || isPunctuation c || isSymbol c || isControl c || c == '/' = '_' | otherwise = c diff --git a/Utility/Quvi.hs b/Utility/Quvi.hs index 228ff7809..cf3a23cfd 100644 --- a/Utility/Quvi.hs +++ b/Utility/Quvi.hs @@ -113,7 +113,7 @@ supported Quvi04 url = boolSystem "quvi" supported Quvi09 url = (firstlevel <&&> secondlevel) `catchNonAsync` (\_ -> return False) where - firstlevel = case uriAuthority =<< parseURIRelaxed url of + firstlevel = case uriAuthority =<< parseURIRelaxed url of Nothing -> return False Just auth -> do let domain = map toLower $ uriRegName auth diff --git a/Utility/Rsync.hs b/Utility/Rsync.hs index d0a89b2b0..8dee6093c 100644 --- a/Utility/Rsync.hs +++ b/Utility/Rsync.hs @@ -57,7 +57,7 @@ rsync = boolSystem "rsync" . rsyncParamsFixup rsyncParamsFixup :: [CommandParam] -> [CommandParam] rsyncParamsFixup = map fixup where - fixup (File f) = File (toCygPath f) + fixup (File f) = File (toCygPath f) fixup p = p {- Runs rsync, but intercepts its progress output and updates a meter. diff --git a/Utility/SRV.hs b/Utility/SRV.hs index f1671758e..1b86aeb76 100644 --- a/Utility/SRV.hs +++ b/Utility/SRV.hs @@ -74,7 +74,7 @@ lookupSRV (SRV srv) = do maybe [] use r #endif where - use = orderHosts . map tohosts + use = orderHosts . map tohosts tohosts (priority, weight, port, hostname) = ( (priority, weight) , (B8.toString hostname, PortNumber $ fromIntegral port) diff --git a/Utility/Scheduled.hs b/Utility/Scheduled.hs index 305410c54..5a14b15f3 100644 --- a/Utility/Scheduled.hs +++ b/Utility/Scheduled.hs @@ -96,9 +96,9 @@ calcNextTime schedule@(Schedule recurrance scheduledtime) lasttime currenttime NextTimeExactly t -> window (localDay t) (localDay t) | otherwise = NextTimeExactly . startTime <$> findfromtoday False where - findfromtoday anytime = findfrom recurrance afterday today + findfromtoday anytime = findfrom recurrance afterday today where - today = localDay currenttime + today = localDay currenttime afterday = sameaslastrun || toolatetoday toolatetoday = not anytime && localTimeOfDay currenttime >= nexttime sameaslastrun = lastrun == Just today @@ -163,8 +163,8 @@ calcNextTime schedule@(Schedule recurrance scheduledtime) lasttime currenttime Divisible n r'@(Yearly _) -> handlediv n r' ynum Nothing Divisible _ r'@(Divisible _ _) -> findfrom r' afterday candidate where - skip n = findfrom r False (addDays n candidate) - handlediv n r' getval mmax + skip n = findfrom r False (addDays n candidate) + handlediv n r' getval mmax | n > 0 && maybe True (n <=) mmax = findfromwhere r' (divisible n . getval) afterday candidate | otherwise = Nothing @@ -267,7 +267,7 @@ toRecurrance s = case words s of constructor u | "s" `isSuffixOf` u = constructor $ reverse $ drop 1 $ reverse u | otherwise = Nothing - withday sd u = do + withday sd u = do c <- constructor u d <- readish sd Just $ c (Just d) @@ -285,7 +285,7 @@ fromScheduledTime AnyTime = "any time" fromScheduledTime (SpecificTime h m) = show h' ++ (if m > 0 then ":" ++ pad 2 (show m) else "") ++ " " ++ ampm where - pad n s = take (n - length s) (repeat '0') ++ s + pad n s = take (n - length s) (repeat '0') ++ s (h', ampm) | h == 0 = (12, "AM") | h < 12 = (h, "AM") @@ -304,10 +304,10 @@ toScheduledTime v = case words v of (s:[]) -> go s id _ -> Nothing where - h0 h + h0 h | h == 12 = 0 | otherwise = h - go :: String -> (Int -> Int) -> Maybe ScheduledTime + go :: String -> (Int -> Int) -> Maybe ScheduledTime go s adjust = let (h, m) = separate (== ':') s in SpecificTime @@ -363,7 +363,7 @@ instance Arbitrary Recurrance where ] ] where - arbday = oneof + arbday = oneof [ Just <$> nonNegative arbitrary , pure Nothing ] diff --git a/Utility/SshConfig.hs b/Utility/SshConfig.hs index 529e5c990..e45d09acd 100644 --- a/Utility/SshConfig.hs +++ b/Utility/SshConfig.hs @@ -56,7 +56,7 @@ parseSshConfig = go [] . lines | iscomment l = hoststanza host c ((Left $ mkcomment l):hc) ls | otherwise = case splitline l of (indent, k, v) - | isHost k -> hoststanza v + | isHost k -> hoststanza v (HostConfig host (reverse hc):c) [] ls | otherwise -> hoststanza host c ((Right $ SshSetting indent k v):hc) ls @@ -87,7 +87,7 @@ genSshConfig = unlines . concatMap gen findHostConfigKey :: SshConfig -> Key -> Maybe Value findHostConfigKey (HostConfig _ cs) wantk = go (rights cs) (map toLower wantk) where - go [] _ = Nothing + go [] _ = Nothing go ((SshSetting _ k v):rest) wantk' | map toLower k == wantk' = Just v | otherwise = go rest wantk' @@ -98,7 +98,7 @@ addToHostConfig :: SshConfig -> Key -> Value -> SshConfig addToHostConfig (HostConfig host cs) k v = HostConfig host $ Right (SshSetting indent k v) : cs where - {- The indent is taken from any existing SshSetting + {- The indent is taken from any existing SshSetting - in the HostConfig (largest indent wins). -} indent = fromMaybe "\t" $ headMaybe $ reverse $ sortBy (comparing length) $ map getindent cs diff --git a/Utility/TList.hs b/Utility/TList.hs index 4b91b767f..5532cdce5 100644 --- a/Utility/TList.hs +++ b/Utility/TList.hs @@ -57,7 +57,7 @@ modifyTList tlist a = do unless (emptyDList dl') $ putTMVar tlist dl' where - emptyDList = D.list True (\_ _ -> False) + emptyDList = D.list True (\_ _ -> False) consTList :: TList a -> a -> STM () consTList tlist v = modifyTList tlist $ \dl -> D.cons v dl diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 6bcfce919..6c42e103b 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -117,7 +117,7 @@ getSocket h = do when (isJust h) $ error "getSocket with HostName not supported on this OS" addr <- inet_addr "127.0.0.1" - sock <- socket AF_INET Stream defaultProtocol + sock <- socket AF_INET Stream defaultProtocol preparesocket sock bindSocket sock (SockAddrInet aNY_PORT addr) use sock diff --git a/doc/design/requests_routing/simroutes.hs b/doc/design/requests_routing/simroutes.hs index d91125935..391816040 100644 --- a/doc/design/requests_routing/simroutes.hs +++ b/doc/design/requests_routing/simroutes.hs @@ -182,7 +182,7 @@ merge (ImmobileNode ir) t@(TransferNode { transferrepo = tr }) = , satisfiedRequests = satisfiedRequests' `S.union` checkSatisfied wantFiles' haveFiles' } where - wantFiles' = foldr addRequest (wantFiles r1) (wantFiles r2) + wantFiles' = foldr addRequest (wantFiles r1) (wantFiles r2) haveFiles' = S.foldr (addFile wantFiles' satisfiedRequests') (haveFiles r1) (haveFiles r2) satisfiedRequests' = satisfiedRequests r1 `S.union` satisfiedRequests r2 @@ -229,7 +229,7 @@ emptyImmobile = ImmobileNode (NodeRepo [] S.empty S.empty) mkTransfer :: (RandomGen g) => [NodeName] -> Rand g TransferNode mkTransfer immobiles = do - -- Transfer nodes are given random routes. May be simplistic. + -- Transfer nodes are given random routes. May be simplistic. -- Also, some immobile nodes will not be serviced by any transfer nodes. numpossiblelocs <- getRandomR transferDestinationsRange possiblelocs <- sequence (replicate numpossiblelocs (randomfrom immobiles)) @@ -283,7 +283,7 @@ summarize _initial@(Network origis _) _final@(Network is _ts) = format --, ("Immobile nodes at end", show is) ] where - findoriginreqs = filter (\r -> requestTTL r == originTTL) + findoriginreqs = filter (\r -> requestTTL r == originTTL) findunsatisfied r = let wantedfs = S.fromList $ map requestedFile (findoriginreqs (wantFiles r)) in S.difference wantedfs (haveFiles r) -- cgit v1.2.3 From adb4603fbf69d8638d925627e0c85b473a3fef05 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 9 Oct 2014 15:09:26 -0400 Subject: indent with tabs not spaces Found these with: git grep "^ " $(find -type f -name \*.hs) |grep -v ': where' Unfortunately there is some inline hamlet that cannot use tabs for indentation. Also, Assistant/WebApp/Bootstrap3.hs is a copy of a module and so I'm leaving it as-is. --- Annex/TaggedPush.hs | 10 +++++----- Assistant/Threads/Watcher.hs | 2 +- Build/Standalone.hs | 2 +- Command/Fsck.hs | 2 +- Command/List.hs | 16 ++++++++-------- Git/DiffTree.hs | 2 +- Logs.hs | 6 +++--- Logs/MapLog.hs | 2 +- Logs/SingleValue.hs | 4 ++-- Remote/Helper/Encryptable.hs | 10 +++++----- Remote/Helper/Special.hs | 2 +- RemoteDaemon/Types.hs | 2 +- Test.hs | 12 ++++++------ Types/Crypto.hs | 8 ++++---- Types/ScheduledActivity.hs | 2 +- Utility/HumanTime.hs | 2 +- Utility/Scheduled.hs | 8 ++++---- 17 files changed, 46 insertions(+), 46 deletions(-) (limited to 'Remote/Helper/Special.hs') diff --git a/Annex/TaggedPush.hs b/Annex/TaggedPush.hs index 35fdf333c..a31758022 100644 --- a/Annex/TaggedPush.hs +++ b/Annex/TaggedPush.hs @@ -49,13 +49,13 @@ fromTaggedBranch b = case split "/" $ Git.fromRef b of taggedPush :: UUID -> Maybe String -> Git.Ref -> Remote -> Git.Repo -> IO Bool taggedPush u info branch remote = Git.Command.runBool - [ Param "push" - , Param $ Remote.name remote + [ Param "push" + , Param $ Remote.name remote {- Using forcePush here is safe because we "own" the tagged branch - we're pushing; it has no other writers. Ensures it is pushed - even if it has been rewritten by a transition. -} - , Param $ Git.Branch.forcePush $ refspec Annex.Branch.name - , Param $ refspec branch - ] + , Param $ Git.Branch.forcePush $ refspec Annex.Branch.name + , Param $ refspec branch + ] where refspec b = Git.fromRef b ++ ":" ++ Git.fromRef (toTaggedBranch u info b) diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 8482de895..2e69e1640 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -72,7 +72,7 @@ needLsof = error $ unlines {- A special exception that can be thrown to pause or resume the watcher. -} data WatcherControl = PauseWatcher | ResumeWatcher - deriving (Show, Eq, Typeable) + deriving (Show, Eq, Typeable) instance E.Exception WatcherControl diff --git a/Build/Standalone.hs b/Build/Standalone.hs index 110163acf..da030933d 100644 --- a/Build/Standalone.hs +++ b/Build/Standalone.hs @@ -40,7 +40,7 @@ main :: IO () main = getArgs >>= go where go [] = error "specify topdir" - go (topdir:_) = do + go (topdir:_) = do let dir = progDir topdir createDirectoryIfMissing True dir installed <- forM bundledPrograms $ installProg dir diff --git a/Command/Fsck.hs b/Command/Fsck.hs index f27f18e57..1a10a15b4 100644 --- a/Command/Fsck.hs +++ b/Command/Fsck.hs @@ -282,7 +282,7 @@ verifyDirectMode key file = do - the key's metadata, if available. - - Not checked in direct mode, because files can be changed directly. - -} + -} checkKeySize :: Key -> Annex Bool checkKeySize key = ifM isDirect ( return True diff --git a/Command/List.hs b/Command/List.hs index d038d6deb..e4d911d97 100644 --- a/Command/List.hs +++ b/Command/List.hs @@ -71,15 +71,15 @@ type Present = Bool header :: [(RemoteName, TrustLevel)] -> String header remotes = unlines (zipWith formatheader [0..] remotes) ++ pipes (length remotes) where - formatheader n (remotename, trustlevel) = pipes n ++ remotename ++ trust trustlevel - pipes = flip replicate '|' - trust UnTrusted = " (untrusted)" - trust _ = "" + formatheader n (remotename, trustlevel) = pipes n ++ remotename ++ trust trustlevel + pipes = flip replicate '|' + trust UnTrusted = " (untrusted)" + trust _ = "" format :: [(TrustLevel, Present)] -> FilePath -> String format remotes file = thereMap ++ " " ++ file where - thereMap = concatMap there remotes - there (UnTrusted, True) = "x" - there (_, True) = "X" - there (_, False) = "_" + thereMap = concatMap there remotes + there (UnTrusted, True) = "x" + there (_, True) = "X" + there (_, False) = "_" diff --git a/Git/DiffTree.hs b/Git/DiffTree.hs index 59de60871..489afa86c 100644 --- a/Git/DiffTree.hs +++ b/Git/DiffTree.hs @@ -53,7 +53,7 @@ diffIndex ref = diffIndex' ref [Param "--cached"] diffWorkTree :: Ref -> Repo -> IO ([DiffTreeItem], IO Bool) diffWorkTree ref repo = ifM (Git.Ref.headExists repo) - ( diffIndex' ref [] repo + ( diffIndex' ref [] repo , return ([], return True) ) diff --git a/Logs.hs b/Logs.hs index 1b7a61efe..a4522bd92 100644 --- a/Logs.hs +++ b/Logs.hs @@ -90,11 +90,11 @@ locationLogFile key = hashDirLower key ++ keyFile key ++ ".log" locationLogFileKey :: FilePath -> Maybe Key locationLogFileKey path | ["remote", "web"] `isPrefixOf` splitDirectories dir = Nothing - | ext == ".log" = fileKey base - | otherwise = Nothing + | ext == ".log" = fileKey base + | otherwise = Nothing where (dir, file) = splitFileName path - (base, ext) = splitAt (length file - 4) file + (base, ext) = splitAt (length file - 4) file {- The filename of the url log for a given key. -} urlLogFile :: Key -> FilePath diff --git a/Logs/MapLog.hs b/Logs/MapLog.hs index 1725ef953..dd3cc0696 100644 --- a/Logs/MapLog.hs +++ b/Logs/MapLog.hs @@ -15,7 +15,7 @@ import qualified Data.Map as M import Data.Time.Clock.POSIX import Data.Time import System.Locale - + import Common data TimeStamp = Unknown | Date POSIXTime diff --git a/Logs/SingleValue.hs b/Logs/SingleValue.hs index cbebdc8e5..bb774b6f4 100644 --- a/Logs/SingleValue.hs +++ b/Logs/SingleValue.hs @@ -60,6 +60,6 @@ getLog = newestValue <$$> readLog setLog :: (SingleValueSerializable v) => FilePath -> v -> Annex () setLog f v = do - now <- liftIO getPOSIXTime - let ent = LogEntry now v + now <- liftIO getPOSIXTime + let ent = LogEntry now v Annex.Branch.change f $ \_old -> showLog (S.singleton ent) diff --git a/Remote/Helper/Encryptable.hs b/Remote/Helper/Encryptable.hs index 05f3fc3f9..9a8e9ba5b 100644 --- a/Remote/Helper/Encryptable.hs +++ b/Remote/Helper/Encryptable.hs @@ -58,7 +58,7 @@ encryptionSetup c = maybe genCipher updateCipher $ extractCipher c Just "shared" -> use "encryption setup" . genSharedCipher =<< highRandomQuality -- hybrid encryption is the default when a keyid is - -- specified but no encryption + -- specified but no encryption _ | maybe (M.member "keyid" c) (== "hybrid") encryption -> use "encryption setup" . genEncryptedCipher key Hybrid =<< highRandomQuality @@ -88,10 +88,10 @@ encryptionSetup c = maybe genCipher updateCipher $ extractCipher c (&&) (maybe True ( /= "false") $ M.lookup "highRandomQuality" c) <$> fmap not (Annex.getState Annex.fast) c' = foldr M.delete c - -- git-annex used to remove 'encryption' as well, since - -- it was redundant; we now need to keep it for - -- public-key encryption, hence we leave it on newer - -- remotes (while being backward-compatible). + -- git-annex used to remove 'encryption' as well, since + -- it was redundant; we now need to keep it for + -- public-key encryption, hence we leave it on newer + -- remotes (while being backward-compatible). [ "keyid", "keyid+", "keyid-", "highRandomQuality" ] remoteCipher :: RemoteConfig -> Annex (Maybe Cipher) diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs index 5b9db9b08..4738180a8 100644 --- a/Remote/Helper/Special.hs +++ b/Remote/Helper/Special.hs @@ -87,7 +87,7 @@ checkPrepare checker helper k a = ifM (checker k) -- Use to acquire a resource when preparing a helper. resourcePrepare :: (Key -> (r -> Annex Bool) -> Annex Bool) -> (r -> helper) -> Preparer helper resourcePrepare withr helper k a = withr k $ \r -> - a (Just (helper r)) + a (Just (helper r)) -- A Storer that expects to be provided with a file containing -- the content of the key to store. diff --git a/RemoteDaemon/Types.hs b/RemoteDaemon/Types.hs index 0a7269534..7413f5851 100644 --- a/RemoteDaemon/Types.hs +++ b/RemoteDaemon/Types.hs @@ -20,7 +20,7 @@ import Control.Concurrent -- The URI of a remote is used to uniquely identify it (names change..) newtype RemoteURI = RemoteURI URI - deriving (Show) + deriving (Show) -- A Transport for a particular git remote consumes some messages -- from a Chan, and emits others to another Chan. diff --git a/Test.hs b/Test.hs index 50d2f1d55..1c9bf4e6a 100644 --- a/Test.hs +++ b/Test.hs @@ -943,12 +943,12 @@ test_remove_conflict_resolution testenv = do length v == 1 @? (what ++ " too many variant files in: " ++ show v) - {- Check merge confalict resolution when a file is annexed in one repo, - - and checked directly into git in the other repo. - - - - This test requires indirect mode to set it up, but tests both direct and - - indirect mode. - -} +{- Check merge confalict resolution when a file is annexed in one repo, + - and checked directly into git in the other repo. + - + - This test requires indirect mode to set it up, but tests both direct and + - indirect mode. + -} test_nonannexed_file_conflict_resolution :: TestEnv -> Assertion test_nonannexed_file_conflict_resolution testenv = do check True False diff --git a/Types/Crypto.hs b/Types/Crypto.hs index 1a9a7774a..48d03ce12 100644 --- a/Types/Crypto.hs +++ b/Types/Crypto.hs @@ -59,10 +59,10 @@ readMac "HMACSHA512" = Just HmacSha512 readMac _ = Nothing calcMac - :: Mac -- ^ MAC - -> L.ByteString -- ^ secret key - -> L.ByteString -- ^ message - -> String -- ^ MAC'ed message, in hexadecimals + :: Mac -- ^ MAC + -> L.ByteString -- ^ secret key + -> L.ByteString -- ^ message + -> String -- ^ MAC'ed message, in hexadecimal calcMac mac = case mac of HmacSha1 -> showDigest $* hmacSha1 HmacSha224 -> showDigest $* hmacSha224 diff --git a/Types/ScheduledActivity.hs b/Types/ScheduledActivity.hs index b683409ce..5cdbe29e8 100644 --- a/Types/ScheduledActivity.hs +++ b/Types/ScheduledActivity.hs @@ -17,7 +17,7 @@ import Data.Either data ScheduledActivity = ScheduledSelfFsck Schedule Duration | ScheduledRemoteFsck UUID Schedule Duration - deriving (Eq, Read, Show, Ord) + deriving (Eq, Read, Show, Ord) {- Activities that run on a remote, within a time window, so - should be run when the remote gets connected. -} diff --git a/Utility/HumanTime.hs b/Utility/HumanTime.hs index 4214ea680..3c23f31f7 100644 --- a/Utility/HumanTime.hs +++ b/Utility/HumanTime.hs @@ -27,7 +27,7 @@ import Control.Applicative import qualified Data.Map as M newtype Duration = Duration { durationSeconds :: Integer } - deriving (Eq, Ord, Read, Show) + deriving (Eq, Ord, Read, Show) durationSince :: UTCTime -> IO Duration durationSince pasttime = do diff --git a/Utility/Scheduled.hs b/Utility/Scheduled.hs index 5a14b15f3..4fa3a29f1 100644 --- a/Utility/Scheduled.hs +++ b/Utility/Scheduled.hs @@ -44,7 +44,7 @@ import Data.Char {- Some sort of scheduled event. -} data Schedule = Schedule Recurrance ScheduledTime - deriving (Eq, Read, Show, Ord) + deriving (Eq, Read, Show, Ord) data Recurrance = Daily @@ -54,7 +54,7 @@ data Recurrance | Divisible Int Recurrance -- ^ Days, Weeks, or Months of the year evenly divisible by a number. -- (Divisible Year is years evenly divisible by a number.) - deriving (Eq, Read, Show, Ord) + deriving (Eq, Read, Show, Ord) type WeekDay = Int type MonthDay = Int @@ -63,7 +63,7 @@ type YearDay = Int data ScheduledTime = AnyTime | SpecificTime Hour Minute - deriving (Eq, Read, Show, Ord) + deriving (Eq, Read, Show, Ord) type Hour = Int type Minute = Int @@ -73,7 +73,7 @@ type Minute = Int data NextTime = NextTimeExactly LocalTime | NextTimeWindow LocalTime LocalTime - deriving (Eq, Read, Show) + deriving (Eq, Read, Show) startTime :: NextTime -> LocalTime startTime (NextTimeExactly t) = t -- cgit v1.2.3 From 43201c32868c12461b46dd7e503c653608a40198 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 21 Oct 2014 14:36:09 -0400 Subject: add per-remote-type info MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Now `git annex info $remote` shows info specific to the type of the remote, for example, it shows the rsync url. Remote types that support encryption or chunking also include that in their info. This commit was sponsored by Ævar Arnfjörð Bjarmason. --- Command/Info.hs | 48 ++++++++++++++++++++++++++------------------ Remote/Bup.hs | 1 + Remote/Ddar.hs | 1 + Remote/Directory.hs | 3 ++- Remote/External.hs | 1 + Remote/GCrypt.hs | 1 + Remote/Git.hs | 1 + Remote/Glacier.hs | 3 ++- Remote/Helper/Chunked.hs | 9 +++++++++ Remote/Helper/Encryptable.hs | 8 ++++++++ Remote/Helper/Git.hs | 5 +++++ Remote/Helper/Special.hs | 6 ++++++ Remote/Hook.hs | 3 ++- Remote/Rsync.hs | 1 + Remote/S3.hs | 3 ++- Remote/Tahoe.hs | 3 ++- Remote/Web.hs | 3 ++- Remote/WebDAV.hs | 3 ++- Types/Remote.hs | 4 +++- doc/git-annex.mdwn | 4 ++-- 20 files changed, 82 insertions(+), 29 deletions(-) (limited to 'Remote/Helper/Special.hs') diff --git a/Command/Info.hs b/Command/Info.hs index 5cac2954a..96b7eb6d7 100644 --- a/Command/Info.hs +++ b/Command/Info.hs @@ -125,7 +125,8 @@ fileInfo file k = showCustom (unwords ["info", file]) $ do remoteInfo :: Remote -> Annex () remoteInfo r = showCustom (unwords ["info", Remote.name r]) $ do - evalStateT (mapM_ showStat (remote_stats r)) emptyStatInfo + info <- map (\(k, v) -> simpleStat k (pure v)) <$> Remote.getInfo r + evalStateT (mapM_ showStat (remote_stats r ++ info)) emptyStatInfo return True selStats :: [Stat] -> [Stat] -> Annex [Stat] @@ -179,16 +180,21 @@ file_stats f k = ] remote_stats :: Remote -> [Stat] -remote_stats r = - [ remote_name r - , remote_description r - , remote_uuid r - , remote_cost r +remote_stats r = map (\s -> s r) + [ remote_name + , remote_description + , remote_uuid + , remote_cost + , remote_type ] stat :: String -> (String -> StatState String) -> Stat stat desc a = return $ Just (desc, a desc) +-- The json simply contains the same string that is displayed. +simpleStat :: String -> StatState String -> Stat +simpleStat desc getval = stat desc $ json id getval + nostat :: Stat nostat = return Nothing @@ -209,7 +215,7 @@ showStat s = maybe noop calc =<< s lift . showRaw =<< a repository_mode :: Stat -repository_mode = stat "repository mode" $ json id $ lift $ +repository_mode = simpleStat "repository mode" $ lift $ ifM isDirect ( return "direct", return "indirect" ) @@ -223,32 +229,36 @@ remote_list level = stat n $ nojson $ lift $ do n = showTrustLevel level ++ " repositories" dir_name :: FilePath -> Stat -dir_name dir = stat "directory" $ json id $ pure dir +dir_name dir = simpleStat "directory" $ pure dir file_name :: FilePath -> Stat -file_name file = stat "file" $ json id $ pure file +file_name file = simpleStat "file" $ pure file remote_name :: Remote -> Stat -remote_name r = stat "remote" $ json id $ pure (Remote.name r) +remote_name r = simpleStat "remote" $ pure (Remote.name r) remote_description :: Remote -> Stat -remote_description r = stat "description" $ json id $ lift $ +remote_description r = simpleStat "description" $ lift $ Remote.prettyUUID (Remote.uuid r) remote_uuid :: Remote -> Stat -remote_uuid r = stat "uuid" $ json id $ pure $ +remote_uuid r = simpleStat "uuid" $ pure $ fromUUID $ Remote.uuid r remote_cost :: Remote -> Stat -remote_cost r = stat "cost" $ json id $ pure $ +remote_cost r = simpleStat "cost" $ pure $ show $ Remote.cost r +remote_type :: Remote -> Stat +remote_type r = simpleStat "type" $ pure $ + Remote.typename $ Remote.remotetype r + local_annex_keys :: Stat local_annex_keys = stat "local annex keys" $ json show $ countKeys <$> cachedPresentData local_annex_size :: Stat -local_annex_size = stat "local annex size" $ json id $ +local_annex_size = simpleStat "local annex size" $ showSizeKeys <$> cachedPresentData known_annex_files :: Stat @@ -256,7 +266,7 @@ known_annex_files = stat "annexed files in working tree" $ json show $ countKeys <$> cachedReferencedData known_annex_size :: Stat -known_annex_size = stat "size of annexed files in working tree" $ json id $ +known_annex_size = simpleStat "size of annexed files in working tree" $ showSizeKeys <$> cachedReferencedData tmp_size :: Stat @@ -266,13 +276,13 @@ bad_data_size :: Stat bad_data_size = staleSize "bad keys size" gitAnnexBadDir key_size :: Key -> Stat -key_size k = stat "size" $ json id $ pure $ showSizeKeys $ foldKeys [k] +key_size k = simpleStat "size" $ pure $ showSizeKeys $ foldKeys [k] key_name :: Key -> Stat -key_name k = stat "key" $ json id $ pure $ key2file k +key_name k = simpleStat "key" $ pure $ key2file k bloom_info :: Stat -bloom_info = stat "bloom filter size" $ json id $ do +bloom_info = simpleStat "bloom filter size" $ do localkeys <- countKeys <$> cachedPresentData capacity <- fromIntegral <$> lift Command.Unused.bloomCapacity let note = aside $ @@ -305,7 +315,7 @@ transfer_list = stat "transfers in progress" $ nojson $ lift $ do ] disk_size :: Stat -disk_size = stat "available local disk space" $ json id $ lift $ +disk_size = simpleStat "available local disk space" $ lift $ calcfree <$> (annexDiskReserve <$> Annex.getGitConfig) <*> inRepo (getDiskFree . gitAnnexDir) diff --git a/Remote/Bup.hs b/Remote/Bup.hs index cc64d6ff5..4f2ddf35a 100644 --- a/Remote/Bup.hs +++ b/Remote/Bup.hs @@ -73,6 +73,7 @@ gen r u c gc = do , availability = if bupLocal buprepo then LocallyAvailable else GloballyAvailable , readonly = False , mkUnavailable = return Nothing + , getInfo = return [("repo", buprepo)] } return $ Just $ specialRemote' specialcfg c (simplyPrepare $ store this buprepo) diff --git a/Remote/Ddar.hs b/Remote/Ddar.hs index 1db482b47..d73919bfd 100644 --- a/Remote/Ddar.hs +++ b/Remote/Ddar.hs @@ -70,6 +70,7 @@ gen r u c gc = do , availability = if ddarLocal ddarrepo then LocallyAvailable else GloballyAvailable , readonly = False , mkUnavailable = return Nothing + , getInfo = return [("repo", ddarrepo)] } ddarrepo = fromMaybe (error "missing ddarrepo") $ remoteAnnexDdarRepo gc specialcfg = (specialRemoteCfg c) diff --git a/Remote/Directory.hs b/Remote/Directory.hs index fa4d027ae..2e9e013ab 100644 --- a/Remote/Directory.hs +++ b/Remote/Directory.hs @@ -67,7 +67,8 @@ gen r u c gc = do availability = LocallyAvailable, remotetype = remote, mkUnavailable = gen r u c $ - gc { remoteAnnexDirectory = Just "/dev/null" } + gc { remoteAnnexDirectory = Just "/dev/null" }, + getInfo = return [("directory", dir)] } where dir = fromMaybe (error "missing directory") $ remoteAnnexDirectory gc diff --git a/Remote/External.hs b/Remote/External.hs index d40972412..e907ab0cf 100644 --- a/Remote/External.hs +++ b/Remote/External.hs @@ -68,6 +68,7 @@ gen r u c gc = do remotetype = remote, mkUnavailable = gen r u c $ gc { remoteAnnexExternalType = Just "!dne!" } + , getInfo = return [("externaltype", externaltype)] } where externaltype = fromMaybe (error "missing externaltype") (remoteAnnexExternalType gc) diff --git a/Remote/GCrypt.hs b/Remote/GCrypt.hs index fc7718a2a..995c3e838 100644 --- a/Remote/GCrypt.hs +++ b/Remote/GCrypt.hs @@ -121,6 +121,7 @@ gen' r u c gc = do , availability = availabilityCalc r , remotetype = remote , mkUnavailable = return Nothing + , getInfo = return $ gitRepoInfo r } return $ Just $ specialRemote' specialcfg c (simplyPrepare $ store this rsyncopts) diff --git a/Remote/Git.hs b/Remote/Git.hs index a249f43b2..50c34a2bb 100644 --- a/Remote/Git.hs +++ b/Remote/Git.hs @@ -159,6 +159,7 @@ gen r u c gc , availability = availabilityCalc r , remotetype = remote , mkUnavailable = unavailable r u c gc + , getInfo = return $ gitRepoInfo r } unavailable :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote) diff --git a/Remote/Glacier.hs b/Remote/Glacier.hs index 70bcec33f..0e2796da2 100644 --- a/Remote/Glacier.hs +++ b/Remote/Glacier.hs @@ -66,7 +66,8 @@ gen r u c gc = new <$> remoteCost gc veryExpensiveRemoteCost readonly = False, availability = GloballyAvailable, remotetype = remote, - mkUnavailable = return Nothing + mkUnavailable = return Nothing, + getInfo = return [("glacier vault", getVault c)] } specialcfg = (specialRemoteCfg c) -- Disabled until jobList gets support for chunks. diff --git a/Remote/Helper/Chunked.hs b/Remote/Helper/Chunked.hs index eb5dbc793..806fab542 100644 --- a/Remote/Helper/Chunked.hs +++ b/Remote/Helper/Chunked.hs @@ -8,6 +8,7 @@ module Remote.Helper.Chunked ( ChunkSize, ChunkConfig(..), + describeChunkConfig, getChunkConfig, storeChunks, removeChunks, @@ -34,6 +35,14 @@ data ChunkConfig | LegacyChunks ChunkSize deriving (Show) +describeChunkConfig :: ChunkConfig -> String +describeChunkConfig NoChunks = "none" +describeChunkConfig (UnpaddedChunks sz) = describeChunkSize sz ++ "chunks" +describeChunkConfig (LegacyChunks sz) = describeChunkSize sz ++ " chunks (old style)" + +describeChunkSize :: ChunkSize -> String +describeChunkSize sz = roughSize storageUnits False (fromIntegral sz) + noChunks :: ChunkConfig -> Bool noChunks NoChunks = True noChunks _ = False diff --git a/Remote/Helper/Encryptable.hs b/Remote/Helper/Encryptable.hs index 9a8e9ba5b..5e342803d 100644 --- a/Remote/Helper/Encryptable.hs +++ b/Remote/Helper/Encryptable.hs @@ -16,6 +16,7 @@ module Remote.Helper.Encryptable ( cipherKey, storeCipher, extractCipher, + describeEncryption, ) where import qualified Data.Map as M @@ -157,3 +158,10 @@ extractCipher c = case (M.lookup "cipher" c, _ -> Nothing where readkeys = KeyIds . split "," + +describeEncryption :: RemoteConfig -> String +describeEncryption c = case extractCipher c of + Nothing -> "not encrypted" + (Just (SharedCipher _)) -> "encrypted (encryption key stored in git repository)" + (Just (EncryptedCipher _ _ (KeyIds { keyIds = ks }))) -> + "encrypted (to gpg keys: " ++ unwords ks ++ ")" diff --git a/Remote/Helper/Git.hs b/Remote/Helper/Git.hs index b405fd358..156d7ac28 100644 --- a/Remote/Helper/Git.hs +++ b/Remote/Helper/Git.hs @@ -30,3 +30,8 @@ guardUsable :: Git.Repo -> Annex a -> Annex a -> Annex a guardUsable r fallback a | Git.repoIsLocalUnknown r = fallback | otherwise = a + +gitRepoInfo :: Git.Repo -> [(String, String)] +gitRepoInfo r = + [ ("repository location", Git.repoLocation r) + ] diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs index 4738180a8..181d7548f 100644 --- a/Remote/Helper/Special.hs +++ b/Remote/Helper/Special.hs @@ -168,6 +168,12 @@ specialRemote' cfg c preparestorer prepareretriever prepareremover preparecheckp (cost baser) (const $ cost baser + encryptedRemoteCostAdj) (extractCipher c) + , getInfo = do + l <- getInfo baser + return $ l ++ + [ ("encryption", describeEncryption c) + , ("chunking", describeChunkConfig (chunkConfig cfg)) + ] } cip = cipherKey c gpgopts = getGpgEncParams encr diff --git a/Remote/Hook.hs b/Remote/Hook.hs index 707e2cb75..f7c428e99 100644 --- a/Remote/Hook.hs +++ b/Remote/Hook.hs @@ -60,7 +60,8 @@ gen r u c gc = do availability = GloballyAvailable, remotetype = remote, mkUnavailable = gen r u c $ - gc { remoteAnnexHookType = Just "!dne!" } + gc { remoteAnnexHookType = Just "!dne!" }, + getInfo = return [("hooktype", hooktype)] } where hooktype = fromMaybe (error "missing hooktype") $ remoteAnnexHookType gc diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs index 7a965aa9d..a87d05a33 100644 --- a/Remote/Rsync.hs +++ b/Remote/Rsync.hs @@ -83,6 +83,7 @@ gen r u c gc = do , availability = if islocal then LocallyAvailable else GloballyAvailable , remotetype = remote , mkUnavailable = return Nothing + , getInfo = return [("url", url)] } where specialcfg = (specialRemoteCfg c) diff --git a/Remote/S3.hs b/Remote/S3.hs index 4fc13f390..154fb1ed4 100644 --- a/Remote/S3.hs +++ b/Remote/S3.hs @@ -71,7 +71,8 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost readonly = False, availability = GloballyAvailable, remotetype = remote, - mkUnavailable = gen r u (M.insert "host" "!dne!" c) gc + mkUnavailable = gen r u (M.insert "host" "!dne!" c) gc, + getInfo = return [("bucket", fromMaybe "unknown" (getBucket c))] } s3Setup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> Annex (RemoteConfig, UUID) diff --git a/Remote/Tahoe.hs b/Remote/Tahoe.hs index 5c1729448..7dd231c06 100644 --- a/Remote/Tahoe.hs +++ b/Remote/Tahoe.hs @@ -84,7 +84,8 @@ gen r u c gc = do readonly = False, availability = GloballyAvailable, remotetype = remote, - mkUnavailable = return Nothing + mkUnavailable = return Nothing, + getInfo = return [] } tahoeSetup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> Annex (RemoteConfig, UUID) diff --git a/Remote/Web.hs b/Remote/Web.hs index ef7d2b39a..4d4b43c41 100644 --- a/Remote/Web.hs +++ b/Remote/Web.hs @@ -62,7 +62,8 @@ gen r _ c gc = readonly = True, availability = GloballyAvailable, remotetype = remote, - mkUnavailable = return Nothing + mkUnavailable = return Nothing, + getInfo = return [] } downloadKey :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool diff --git a/Remote/WebDAV.hs b/Remote/WebDAV.hs index d90686608..0981c4373 100644 --- a/Remote/WebDAV.hs +++ b/Remote/WebDAV.hs @@ -71,7 +71,8 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost readonly = False, availability = GloballyAvailable, remotetype = remote, - mkUnavailable = gen r u (M.insert "url" "http://!dne!/" c) gc + mkUnavailable = gen r u (M.insert "url" "http://!dne!/" c) gc, + getInfo = return [("url", fromMaybe "unknown" (M.lookup "url" c))] } chunkconfig = getChunkConfig c diff --git a/Types/Remote.hs b/Types/Remote.hs index e166d7090..795121763 100644 --- a/Types/Remote.hs +++ b/Types/Remote.hs @@ -98,7 +98,9 @@ data RemoteA a = Remote { remotetype :: RemoteTypeA a, -- For testing, makes a version of this remote that is not -- available for use. All its actions should fail. - mkUnavailable :: a (Maybe (RemoteA a)) + mkUnavailable :: a (Maybe (RemoteA a)), + -- Information about the remote, for git annex info to display. + getInfo :: a [(String, String)] } instance Show (RemoteA a) where diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn index 7df4ecb3f..b22ff3881 100644 --- a/doc/git-annex.mdwn +++ b/doc/git-annex.mdwn @@ -679,8 +679,8 @@ subdirectories). * `info [directory|file|remote ...]` Displays statistics and other information for the specified item, - which can be a directory, or a file, or a remote (specified by name or - UUID). When no item is specified, displays statistics and information + which can be a directory, or a file, or a remote. + When no item is specified, displays statistics and information for the repository as a whole. When a directory is specified, the file matching options can be used -- cgit v1.2.3 From 2f2635528d8e428e0fafaf7877a4572a397cdf52 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 21 Jan 2015 12:50:09 -0400 Subject: update my email address and homepage url --- .mailmap | 6 +++--- Annex.hs | 2 +- Annex/AutoMerge.hs | 2 +- Annex/Branch.hs | 2 +- Annex/Branch/Transitions.hs | 2 +- Annex/BranchState.hs | 2 +- Annex/CatFile.hs | 2 +- Annex/CheckAttr.hs | 2 +- Annex/CheckIgnore.hs | 2 +- Annex/Content.hs | 2 +- Annex/Content/Direct.hs | 2 +- Annex/Direct.hs | 2 +- Annex/Direct/Fixup.hs | 2 +- Annex/Drop.hs | 2 +- Annex/Environment.hs | 2 +- Annex/FileMatcher.hs | 2 +- Annex/Hook.hs | 2 +- Annex/Index.hs | 2 +- Annex/Init.hs | 2 +- Annex/Journal.hs | 2 +- Annex/Link.hs | 2 +- Annex/LockFile.hs | 2 +- Annex/MakeRepo.hs | 2 +- Annex/MetaData.hs | 2 +- Annex/MetaData/StandardFields.hs | 2 +- Annex/Notification.hs | 2 +- Annex/Path.hs | 2 +- Annex/Perms.hs | 2 +- Annex/Queue.hs | 2 +- Annex/Quvi.hs | 2 +- Annex/ReplaceFile.hs | 2 +- Annex/Ssh.hs | 2 +- Annex/TaggedPush.hs | 2 +- Annex/Transfer.hs | 2 +- Annex/UUID.hs | 2 +- Annex/Url.hs | 2 +- Annex/VariantFile.hs | 2 +- Annex/Version.hs | 2 +- Annex/View.hs | 2 +- Annex/View/ViewedFile.hs | 2 +- Annex/Wanted.hs | 2 +- Assistant.hs | 2 +- Assistant/Alert.hs | 2 +- Assistant/Alert/Utility.hs | 2 +- Assistant/BranchChange.hs | 2 +- Assistant/Changes.hs | 2 +- Assistant/Commits.hs | 2 +- Assistant/Common.hs | 2 +- Assistant/CredPairCache.hs | 2 +- Assistant/DaemonStatus.hs | 2 +- Assistant/DeleteRemote.hs | 2 +- Assistant/Drop.hs | 2 +- Assistant/Install.hs | 2 +- Assistant/Install/AutoStart.hs | 2 +- Assistant/Install/Menu.hs | 2 +- Assistant/MakeRemote.hs | 2 +- Assistant/Monad.hs | 2 +- Assistant/NamedThread.hs | 2 +- Assistant/NetMessager.hs | 2 +- Assistant/Pairing.hs | 2 +- Assistant/Pairing/MakeRemote.hs | 2 +- Assistant/Pairing/Network.hs | 2 +- Assistant/Pushes.hs | 2 +- Assistant/RemoteControl.hs | 2 +- Assistant/RepoProblem.hs | 2 +- Assistant/ScanRemotes.hs | 2 +- Assistant/Ssh.hs | 2 +- Assistant/Sync.hs | 2 +- Assistant/Threads/Committer.hs | 2 +- Assistant/Threads/ConfigMonitor.hs | 2 +- Assistant/Threads/Cronner.hs | 2 +- Assistant/Threads/DaemonStatus.hs | 2 +- Assistant/Threads/Glacier.hs | 2 +- Assistant/Threads/Merger.hs | 2 +- Assistant/Threads/MountWatcher.hs | 2 +- Assistant/Threads/NetWatcher.hs | 2 +- Assistant/Threads/PairListener.hs | 2 +- Assistant/Threads/ProblemFixer.hs | 2 +- Assistant/Threads/Pusher.hs | 2 +- Assistant/Threads/RemoteControl.hs | 2 +- Assistant/Threads/SanityChecker.hs | 2 +- Assistant/Threads/TransferPoller.hs | 2 +- Assistant/Threads/TransferScanner.hs | 2 +- Assistant/Threads/TransferWatcher.hs | 2 +- Assistant/Threads/Transferrer.hs | 2 +- Assistant/Threads/UpgradeWatcher.hs | 2 +- Assistant/Threads/Upgrader.hs | 2 +- Assistant/Threads/Watcher.hs | 2 +- Assistant/Threads/WebApp.hs | 2 +- Assistant/Threads/XMPPClient.hs | 2 +- Assistant/Threads/XMPPPusher.hs | 2 +- Assistant/TransferQueue.hs | 2 +- Assistant/TransferSlots.hs | 2 +- Assistant/TransferrerPool.hs | 2 +- Assistant/Types/Alert.hs | 2 +- Assistant/Types/BranchChange.hs | 2 +- Assistant/Types/Buddies.hs | 2 +- Assistant/Types/Changes.hs | 2 +- Assistant/Types/Commits.hs | 2 +- Assistant/Types/CredPairCache.hs | 2 +- Assistant/Types/DaemonStatus.hs | 2 +- Assistant/Types/NamedThread.hs | 2 +- Assistant/Types/NetMessager.hs | 2 +- Assistant/Types/Pushes.hs | 2 +- Assistant/Types/RemoteControl.hs | 2 +- Assistant/Types/RepoProblem.hs | 2 +- Assistant/Types/ScanRemotes.hs | 2 +- Assistant/Types/ThreadName.hs | 2 +- Assistant/Types/ThreadedMonad.hs | 2 +- Assistant/Types/TransferQueue.hs | 2 +- Assistant/Types/TransferSlots.hs | 2 +- Assistant/Types/TransferrerPool.hs | 2 +- Assistant/Types/UrlRenderer.hs | 2 +- Assistant/Unused.hs | 2 +- Assistant/XMPP.hs | 2 +- Assistant/XMPP/Buddies.hs | 2 +- Assistant/XMPP/Client.hs | 2 +- Assistant/XMPP/Git.hs | 2 +- Backend.hs | 2 +- Backend/Hash.hs | 2 +- Backend/URL.hs | 2 +- Backend/Utilities.hs | 2 +- Backend/WORM.hs | 2 +- Build/BundledPrograms.hs | 2 +- Build/DesktopFile.hs | 2 +- Build/EvilLinker.hs | 2 +- Build/EvilSplicer.hs | 2 +- Build/InstallDesktopFile.hs | 2 +- Build/LinuxMkLibs.hs | 2 +- Build/NullSoftInstaller.hs | 2 +- Build/OSXMkLibs.hs | 2 +- Build/Standalone.hs | 2 +- BuildFlags.hs | 2 +- Checks.hs | 2 +- CmdLine.hs | 2 +- CmdLine/Action.hs | 2 +- CmdLine/GitAnnex.hs | 2 +- CmdLine/GitAnnex/Options.hs | 2 +- CmdLine/GitAnnexShell.hs | 2 +- CmdLine/GitAnnexShell/Fields.hs | 2 +- CmdLine/Option.hs | 2 +- CmdLine/Seek.hs | 2 +- CmdLine/Usage.hs | 2 +- Command.hs | 2 +- Command/Add.hs | 2 +- Command/AddUnused.hs | 2 +- Command/AddUrl.hs | 2 +- Command/Assistant.hs | 2 +- Command/Commit.hs | 2 +- Command/ConfigList.hs | 2 +- Command/Copy.hs | 2 +- Command/Dead.hs | 2 +- Command/Describe.hs | 2 +- Command/DiffDriver.hs | 2 +- Command/Direct.hs | 2 +- Command/Drop.hs | 2 +- Command/DropKey.hs | 2 +- Command/DropUnused.hs | 2 +- Command/EnableRemote.hs | 2 +- Command/ExamineKey.hs | 2 +- Command/Find.hs | 2 +- Command/FindRef.hs | 2 +- Command/Fix.hs | 2 +- Command/Forget.hs | 2 +- Command/FromKey.hs | 2 +- Command/Fsck.hs | 2 +- Command/FuzzTest.hs | 2 +- Command/GCryptSetup.hs | 2 +- Command/Get.hs | 2 +- Command/Group.hs | 2 +- Command/Help.hs | 2 +- Command/Import.hs | 2 +- Command/ImportFeed.hs | 2 +- Command/InAnnex.hs | 2 +- Command/Indirect.hs | 2 +- Command/Info.hs | 2 +- Command/Init.hs | 2 +- Command/InitRemote.hs | 2 +- Command/List.hs | 2 +- Command/Lock.hs | 2 +- Command/Log.hs | 2 +- Command/LookupKey.hs | 2 +- Command/Map.hs | 2 +- Command/Merge.hs | 2 +- Command/MetaData.hs | 2 +- Command/Migrate.hs | 2 +- Command/Mirror.hs | 2 +- Command/Move.hs | 2 +- Command/NotifyChanges.hs | 2 +- Command/NumCopies.hs | 2 +- Command/PreCommit.hs | 2 +- Command/Proxy.hs | 2 +- Command/ReKey.hs | 2 +- Command/RecvKey.hs | 2 +- Command/Reinit.hs | 2 +- Command/Reinject.hs | 2 +- Command/RemoteDaemon.hs | 2 +- Command/Repair.hs | 2 +- Command/ResolveMerge.hs | 2 +- Command/RmUrl.hs | 2 +- Command/Schedule.hs | 2 +- Command/Semitrust.hs | 2 +- Command/SendKey.hs | 2 +- Command/SetPresentKey.hs | 2 +- Command/Status.hs | 2 +- Command/Sync.hs | 2 +- Command/Test.hs | 2 +- Command/TestRemote.hs | 2 +- Command/TransferInfo.hs | 2 +- Command/TransferKey.hs | 2 +- Command/TransferKeys.hs | 2 +- Command/Trust.hs | 2 +- Command/Unannex.hs | 2 +- Command/Undo.hs | 2 +- Command/Ungroup.hs | 2 +- Command/Uninit.hs | 2 +- Command/Unlock.hs | 2 +- Command/Untrust.hs | 2 +- Command/Unused.hs | 2 +- Command/Upgrade.hs | 2 +- Command/VAdd.hs | 2 +- Command/VCycle.hs | 2 +- Command/VFilter.hs | 2 +- Command/VPop.hs | 2 +- Command/Version.hs | 2 +- Command/Vicfg.hs | 2 +- Command/View.hs | 2 +- Command/Wanted.hs | 2 +- Command/Watch.hs | 2 +- Command/WebApp.hs | 2 +- Command/Whereis.hs | 2 +- Command/XMPPGit.hs | 2 +- Config.hs | 2 +- Config/Cost.hs | 2 +- Config/Files.hs | 2 +- Config/NumCopies.hs | 2 +- Creds.hs | 2 +- Crypto.hs | 2 +- Git.hs | 2 +- Git/AutoCorrect.hs | 2 +- Git/Branch.hs | 2 +- Git/BuildVersion.hs | 2 +- Git/CatFile.hs | 2 +- Git/CheckAttr.hs | 2 +- Git/CheckIgnore.hs | 2 +- Git/Command.hs | 2 +- Git/Command/Batch.hs | 2 +- Git/Config.hs | 2 +- Git/Construct.hs | 2 +- Git/CurrentRepo.hs | 2 +- Git/DiffTree.hs | 2 +- Git/DiffTreeItem.hs | 2 +- Git/FileMode.hs | 2 +- Git/FilePath.hs | 2 +- Git/Filename.hs | 2 +- Git/Fsck.hs | 2 +- Git/GCrypt.hs | 2 +- Git/HashObject.hs | 2 +- Git/Hook.hs | 2 +- Git/Index.hs | 2 +- Git/LsFiles.hs | 2 +- Git/LsTree.hs | 2 +- Git/Merge.hs | 2 +- Git/Objects.hs | 2 +- Git/Queue.hs | 2 +- Git/Ref.hs | 2 +- Git/RefLog.hs | 2 +- Git/Remote.hs | 2 +- Git/Remote/Remove.hs | 2 +- Git/Repair.hs | 2 +- Git/Sha.hs | 2 +- Git/SharedRepository.hs | 2 +- Git/Types.hs | 2 +- Git/UnionMerge.hs | 2 +- Git/UpdateIndex.hs | 2 +- Git/Url.hs | 2 +- Git/Version.hs | 2 +- Limit.hs | 2 +- Limit/Wanted.hs | 2 +- Locations.hs | 2 +- Logs.hs | 2 +- Logs/Chunk.hs | 2 +- Logs/Chunk/Pure.hs | 2 +- Logs/FsckResults.hs | 2 +- Logs/Group.hs | 2 +- Logs/Location.hs | 2 +- Logs/MapLog.hs | 2 +- Logs/MetaData.hs | 2 +- Logs/NumCopies.hs | 2 +- Logs/PreferredContent.hs | 2 +- Logs/PreferredContent/Raw.hs | 2 +- Logs/Presence.hs | 2 +- Logs/Presence/Pure.hs | 2 +- Logs/Remote.hs | 2 +- Logs/RemoteState.hs | 2 +- Logs/Schedule.hs | 2 +- Logs/SingleValue.hs | 2 +- Logs/Transfer.hs | 2 +- Logs/Transitions.hs | 2 +- Logs/Trust.hs | 2 +- Logs/Trust/Basic.hs | 2 +- Logs/Trust/Pure.hs | 2 +- Logs/UUID.hs | 2 +- Logs/UUIDBased.hs | 2 +- Logs/Unused.hs | 2 +- Logs/View.hs | 2 +- Logs/Web.hs | 2 +- Messages.hs | 2 +- Messages/JSON.hs | 2 +- Remote.hs | 2 +- Remote/BitTorrent.hs | 2 +- Remote/Bup.hs | 2 +- Remote/Ddar.hs | 2 +- Remote/Directory.hs | 2 +- Remote/Directory/LegacyChunked.hs | 2 +- Remote/External.hs | 2 +- Remote/External/Types.hs | 2 +- Remote/GCrypt.hs | 2 +- Remote/Git.hs | 2 +- Remote/Glacier.hs | 2 +- Remote/Helper/AWS.hs | 2 +- Remote/Helper/Chunked.hs | 2 +- Remote/Helper/Chunked/Legacy.hs | 2 +- Remote/Helper/Encryptable.hs | 2 +- Remote/Helper/Git.hs | 2 +- Remote/Helper/Hooks.hs | 2 +- Remote/Helper/Http.hs | 2 +- Remote/Helper/Messages.hs | 2 +- Remote/Helper/ReadOnly.hs | 2 +- Remote/Helper/Special.hs | 2 +- Remote/Helper/Ssh.hs | 2 +- Remote/Hook.hs | 2 +- Remote/List.hs | 2 +- Remote/Rsync.hs | 2 +- Remote/Rsync/RsyncUrl.hs | 2 +- Remote/S3.hs | 2 +- Remote/Tahoe.hs | 2 +- Remote/Web.hs | 2 +- Remote/WebDAV.hs | 2 +- Remote/WebDAV/DavLocation.hs | 2 +- RemoteDaemon/Common.hs | 2 +- RemoteDaemon/Core.hs | 2 +- RemoteDaemon/Transport.hs | 2 +- RemoteDaemon/Transport/Ssh.hs | 2 +- RemoteDaemon/Transport/Ssh/Types.hs | 2 +- RemoteDaemon/Types.hs | 2 +- Test.hs | 2 +- Types.hs | 2 +- Types/Availability.hs | 2 +- Types/Backend.hs | 2 +- Types/BranchState.hs | 2 +- Types/CleanupActions.hs | 2 +- Types/Command.hs | 2 +- Types/Creds.hs | 2 +- Types/Crypto.hs | 2 +- Types/DesktopNotify.hs | 2 +- Types/Distribution.hs | 2 +- Types/FileMatcher.hs | 2 +- Types/GitConfig.hs | 2 +- Types/Group.hs | 2 +- Types/Key.hs | 2 +- Types/KeySource.hs | 2 +- Types/LockPool.hs | 2 +- Types/Messages.hs | 2 +- Types/MetaData.hs | 2 +- Types/NumCopies.hs | 2 +- Types/Option.hs | 2 +- Types/Remote.hs | 2 +- Types/ScheduledActivity.hs | 2 +- Types/StandardGroups.hs | 2 +- Types/StoreRetrieve.hs | 2 +- Types/TrustLevel.hs | 2 +- Types/UUID.hs | 2 +- Types/UrlContents.hs | 2 +- Types/View.hs | 2 +- Upgrade.hs | 2 +- Upgrade/V0.hs | 2 +- Upgrade/V1.hs | 2 +- Upgrade/V2.hs | 2 +- Upgrade/V3.hs | 2 +- Upgrade/V4.hs | 2 +- Utility/Applicative.hs | 2 +- Utility/Base64.hs | 2 +- Utility/Batch.hs | 2 +- Utility/Bloom.hs | 2 +- Utility/CoProcess.hs | 2 +- Utility/CopyFile.hs | 2 +- Utility/DBus.hs | 2 +- Utility/Daemon.hs | 2 +- Utility/Data.hs | 2 +- Utility/DataUnits.hs | 2 +- Utility/DirWatcher.hs | 2 +- Utility/DirWatcher/FSEvents.hs | 2 +- Utility/DirWatcher/INotify.hs | 2 +- Utility/DirWatcher/Kqueue.hs | 2 +- Utility/DirWatcher/Types.hs | 2 +- Utility/DirWatcher/Win32Notify.hs | 2 +- Utility/Directory.hs | 2 +- Utility/DiskFree.hs | 2 +- Utility/Dot.hs | 2 +- Utility/DottedVersion.hs | 2 +- Utility/Env.hs | 2 +- Utility/Exception.hs | 2 +- Utility/ExternalSHA.hs | 2 +- Utility/FileMode.hs | 2 +- Utility/FileSystemEncoding.hs | 2 +- Utility/Format.hs | 2 +- Utility/FreeDesktop.hs | 2 +- Utility/Glob.hs | 2 +- Utility/Gpg.hs | 2 +- Utility/HumanNumber.hs | 2 +- Utility/HumanTime.hs | 2 +- Utility/InodeCache.hs | 2 +- Utility/JSONStream.hs | 2 +- Utility/LinuxMkLibs.hs | 2 +- Utility/LockFile.hs | 2 +- Utility/LockFile/Posix.hs | 2 +- Utility/LockFile/Windows.hs | 2 +- Utility/LogFile.hs | 2 +- Utility/Lsof.hs | 2 +- Utility/Matcher.hs | 2 +- Utility/Metered.hs | 2 +- Utility/Misc.hs | 2 +- Utility/Monad.hs | 2 +- Utility/Mounts.hsc | 2 +- Utility/Network.hs | 2 +- Utility/NotificationBroadcaster.hs | 2 +- Utility/OSX.hs | 2 +- Utility/PID.hs | 2 +- Utility/Parallel.hs | 2 +- Utility/Path.hs | 2 +- Utility/Percentage.hs | 2 +- Utility/PosixFiles.hs | 2 +- Utility/QuickCheck.hs | 2 +- Utility/Quvi.hs | 2 +- Utility/Rsync.hs | 2 +- Utility/SRV.hs | 2 +- Utility/SafeCommand.hs | 2 +- Utility/Scheduled.hs | 2 +- Utility/Shell.hs | 2 +- Utility/SimpleProtocol.hs | 2 +- Utility/SshConfig.hs | 2 +- Utility/TList.hs | 2 +- Utility/Tense.hs | 2 +- Utility/ThreadLock.hs | 2 +- Utility/ThreadScheduler.hs | 2 +- Utility/Tmp.hs | 2 +- Utility/Touch.hsc | 2 +- Utility/URI.hs | 2 +- Utility/Url.hs | 2 +- Utility/UserInfo.hs | 2 +- Utility/Verifiable.hs | 2 +- Utility/WebApp.hs | 2 +- Utility/WinProcess.hs | 2 +- Utility/Yesod.hs | 2 +- Utility/libdiskfree.c | 2 +- Utility/libkqueue.c | 2 +- Utility/libmounts.c | 2 +- debian/copyright | 18 +++++++++--------- doc/contact.mdwn | 2 +- doc/encryption.mdwn | 2 +- .../example_of_massively_disconnected_operation.mdwn | 2 +- doc/git-annex-shell.mdwn | 2 +- doc/git-annex.mdwn | 2 +- doc/git-union-merge.mdwn | 2 +- doc/special_remotes/rsync.mdwn | 4 ++-- doc/special_remotes/webdav.mdwn | 2 +- doc/thanks.mdwn | 2 +- doc/tips/using_box.com_as_a_special_remote.mdwn | 2 +- doc/users/joey.mdwn | 4 ++-- git-annex.cabal | 2 +- git-annex.hs | 2 +- git-union-merge.hs | 2 +- 473 files changed, 485 insertions(+), 485 deletions(-) (limited to 'Remote/Helper/Special.hs') diff --git a/.mailmap b/.mailmap index 46423bd59..032707e4b 100644 --- a/.mailmap +++ b/.mailmap @@ -1,6 +1,6 @@ -Joey Hess http://joey.kitenet.net/ -Joey Hess http://joeyh.name/ -Joey Hess http://joeyh.name/ +Joey Hess http://joey.kitenet.net/ +Joey Hess http://joeyh.name/ +Joey Hess http://joeyh.name/ Yaroslav Halchenko Yaroslav Halchenko http://yarikoptic.myopenid.com/ Yaroslav Halchenko https://www.google.com/accounts/o8/id?id=AItOawnx8kHW66N3BqmkVpgtXDlYMvr8TJ5VvfY diff --git a/Annex.hs b/Annex.hs index 50c852526..f85c7e0f2 100644 --- a/Annex.hs +++ b/Annex.hs @@ -1,6 +1,6 @@ {- git-annex monad - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/AutoMerge.hs b/Annex/AutoMerge.hs index c19011e2d..92cccc004 100644 --- a/Annex/AutoMerge.hs +++ b/Annex/AutoMerge.hs @@ -1,6 +1,6 @@ {- git-annex automatic merge conflict resolution - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Branch.hs b/Annex/Branch.hs index f5c490212..2191ec263 100644 --- a/Annex/Branch.hs +++ b/Annex/Branch.hs @@ -1,6 +1,6 @@ {- management of the git-annex branch - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Branch/Transitions.hs b/Annex/Branch/Transitions.hs index 9d306fe80..a9c7daa20 100644 --- a/Annex/Branch/Transitions.hs +++ b/Annex/Branch/Transitions.hs @@ -1,6 +1,6 @@ {- git-annex branch transitions - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/BranchState.hs b/Annex/BranchState.hs index 9b2f9a04c..889a936b9 100644 --- a/Annex/BranchState.hs +++ b/Annex/BranchState.hs @@ -2,7 +2,7 @@ - - Runtime state about the git-annex branch. - - - Copyright 2011-2012 Joey Hess + - Copyright 2011-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/CatFile.hs b/Annex/CatFile.hs index 8a6f10def..179149844 100644 --- a/Annex/CatFile.hs +++ b/Annex/CatFile.hs @@ -1,6 +1,6 @@ {- git cat-file interface, with handle automatically stored in the Annex monad - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/CheckAttr.hs b/Annex/CheckAttr.hs index 8eed9e804..46c71fe72 100644 --- a/Annex/CheckAttr.hs +++ b/Annex/CheckAttr.hs @@ -1,6 +1,6 @@ {- git check-attr interface, with handle automatically stored in the Annex monad - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/CheckIgnore.hs b/Annex/CheckIgnore.hs index f2ed93543..8d7df1e2c 100644 --- a/Annex/CheckIgnore.hs +++ b/Annex/CheckIgnore.hs @@ -1,7 +1,7 @@ {- git check-ignore interface, with handle automatically stored in - the Annex monad - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Content.hs b/Annex/Content.hs index 60daaab90..73f27fd28 100644 --- a/Annex/Content.hs +++ b/Annex/Content.hs @@ -1,6 +1,6 @@ {- git-annex file content managing - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Content/Direct.hs b/Annex/Content/Direct.hs index 4392b5198..e6a9b5eda 100644 --- a/Annex/Content/Direct.hs +++ b/Annex/Content/Direct.hs @@ -1,6 +1,6 @@ {- git-annex file content managing for direct mode - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Direct.hs b/Annex/Direct.hs index 998849ad3..06d0342c1 100644 --- a/Annex/Direct.hs +++ b/Annex/Direct.hs @@ -1,6 +1,6 @@ {- git-annex direct mode - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Direct/Fixup.hs b/Annex/Direct/Fixup.hs index 13485242a..793f92eaf 100644 --- a/Annex/Direct/Fixup.hs +++ b/Annex/Direct/Fixup.hs @@ -1,6 +1,6 @@ {- git-annex direct mode guard fixup - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Drop.hs b/Annex/Drop.hs index c5a3fbe5f..6f3b95615 100644 --- a/Annex/Drop.hs +++ b/Annex/Drop.hs @@ -1,6 +1,6 @@ {- dropping of unwanted content - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Environment.hs b/Annex/Environment.hs index ffdd07157..13b52aa75 100644 --- a/Annex/Environment.hs +++ b/Annex/Environment.hs @@ -1,6 +1,6 @@ {- git-annex environment - - - Copyright 2012, 2013 Joey Hess + - Copyright 2012, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/FileMatcher.hs b/Annex/FileMatcher.hs index 856c68122..c6a729a9c 100644 --- a/Annex/FileMatcher.hs +++ b/Annex/FileMatcher.hs @@ -1,6 +1,6 @@ {- git-annex file matching - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Hook.hs b/Annex/Hook.hs index 44542c12d..253c77a60 100644 --- a/Annex/Hook.hs +++ b/Annex/Hook.hs @@ -4,7 +4,7 @@ - not change, otherwise removing old hooks using an old version of - the script would fail. - - - Copyright 2013-2014 Joey Hess + - Copyright 2013-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Index.hs b/Annex/Index.hs index 7757a412b..60340c50b 100644 --- a/Annex/Index.hs +++ b/Annex/Index.hs @@ -1,6 +1,6 @@ {- Using other git index files - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Init.hs b/Annex/Init.hs index b335d10d3..6947ea119 100644 --- a/Annex/Init.hs +++ b/Annex/Init.hs @@ -1,6 +1,6 @@ {- git-annex repository initialization - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Journal.hs b/Annex/Journal.hs index 798bcba29..148cefbbc 100644 --- a/Annex/Journal.hs +++ b/Annex/Journal.hs @@ -4,7 +4,7 @@ - git-annex branch. Among other things, it ensures that if git-annex is - interrupted, its recorded data is not lost. - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Link.hs b/Annex/Link.hs index e50b97447..98b200f0a 100644 --- a/Annex/Link.hs +++ b/Annex/Link.hs @@ -5,7 +5,7 @@ - On other filesystems, git instead stores the symlink target in a regular - file. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/LockFile.hs b/Annex/LockFile.hs index 75047e005..18e876c75 100644 --- a/Annex/LockFile.hs +++ b/Annex/LockFile.hs @@ -1,6 +1,6 @@ {- git-annex lock files. - - - Copyright 2012, 2014 Joey Hess + - Copyright 2012, 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/MakeRepo.hs b/Annex/MakeRepo.hs index a1f797a76..73443c43d 100644 --- a/Annex/MakeRepo.hs +++ b/Annex/MakeRepo.hs @@ -1,6 +1,6 @@ {- making local repositories (used by webapp mostly) - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/MetaData.hs b/Annex/MetaData.hs index 22e9e7e50..3b776a6d7 100644 --- a/Annex/MetaData.hs +++ b/Annex/MetaData.hs @@ -1,6 +1,6 @@ {- git-annex metadata - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/MetaData/StandardFields.hs b/Annex/MetaData/StandardFields.hs index d41fb1506..c91b53930 100644 --- a/Annex/MetaData/StandardFields.hs +++ b/Annex/MetaData/StandardFields.hs @@ -1,6 +1,6 @@ {- git-annex metadata, standard fields - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Notification.hs b/Annex/Notification.hs index 608bda7e2..25f1ee678 100644 --- a/Annex/Notification.hs +++ b/Annex/Notification.hs @@ -1,6 +1,6 @@ {- git-annex desktop notifications - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Path.hs b/Annex/Path.hs index a8c4907b2..6186a887b 100644 --- a/Annex/Path.hs +++ b/Annex/Path.hs @@ -1,6 +1,6 @@ {- git-annex program path - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Perms.hs b/Annex/Perms.hs index 3430554c7..3ae351d8c 100644 --- a/Annex/Perms.hs +++ b/Annex/Perms.hs @@ -1,6 +1,6 @@ {- git-annex file permissions - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Queue.hs b/Annex/Queue.hs index a5ef60037..47837e2d9 100644 --- a/Annex/Queue.hs +++ b/Annex/Queue.hs @@ -1,6 +1,6 @@ {- git-annex command queue - - - Copyright 2011, 2012 Joey Hess + - Copyright 2011, 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Quvi.hs b/Annex/Quvi.hs index 1a2edf6b8..8d4591b48 100644 --- a/Annex/Quvi.hs +++ b/Annex/Quvi.hs @@ -1,6 +1,6 @@ {- quvi options for git-annex - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/ReplaceFile.hs b/Annex/ReplaceFile.hs index 0355ddd51..1144ba083 100644 --- a/Annex/ReplaceFile.hs +++ b/Annex/ReplaceFile.hs @@ -1,6 +1,6 @@ {- git-annex file replacing - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Ssh.hs b/Annex/Ssh.hs index 15b169862..84637fd3d 100644 --- a/Annex/Ssh.hs +++ b/Annex/Ssh.hs @@ -1,6 +1,6 @@ {- git-annex ssh interface, with connection caching - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/TaggedPush.hs b/Annex/TaggedPush.hs index a31758022..642d4db0b 100644 --- a/Annex/TaggedPush.hs +++ b/Annex/TaggedPush.hs @@ -1,6 +1,6 @@ {- git-annex tagged pushes - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Transfer.hs b/Annex/Transfer.hs index 1603974ff..2723b2351 100644 --- a/Annex/Transfer.hs +++ b/Annex/Transfer.hs @@ -1,6 +1,6 @@ {- git-annex transfers - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/UUID.hs b/Annex/UUID.hs index ec642a0fe..7776b778a 100644 --- a/Annex/UUID.hs +++ b/Annex/UUID.hs @@ -6,7 +6,7 @@ - UUIDs of remotes are cached in git config, using keys named - remote..annex-uuid - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Url.hs b/Annex/Url.hs index 736905d33..b1a932e62 100644 --- a/Annex/Url.hs +++ b/Annex/Url.hs @@ -1,7 +1,7 @@ {- Url downloading, with git-annex user agent and configured http - headers and wget/curl options. - - - Copyright 2013-2014 Joey Hess + - Copyright 2013-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/VariantFile.hs b/Annex/VariantFile.hs index 7c849c59f..89cfbc16a 100644 --- a/Annex/VariantFile.hs +++ b/Annex/VariantFile.hs @@ -1,6 +1,6 @@ {- git-annex .variant files for automatic merge conflict resolution - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Version.hs b/Annex/Version.hs index 2a75a1c55..d08f994e9 100644 --- a/Annex/Version.hs +++ b/Annex/Version.hs @@ -1,6 +1,6 @@ {- git-annex repository versioning - - - Copyright 2010,2013 Joey Hess + - Copyright 2010,2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/View.hs b/Annex/View.hs index e148203c2..3a9168f6c 100644 --- a/Annex/View.hs +++ b/Annex/View.hs @@ -1,6 +1,6 @@ {- metadata based branch views - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/View/ViewedFile.hs b/Annex/View/ViewedFile.hs index 0b963fcd5..0acba235a 100644 --- a/Annex/View/ViewedFile.hs +++ b/Annex/View/ViewedFile.hs @@ -1,6 +1,6 @@ {- filenames (not paths) used in views - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Annex/Wanted.hs b/Annex/Wanted.hs index 42f813bbb..87b4377c2 100644 --- a/Annex/Wanted.hs +++ b/Annex/Wanted.hs @@ -1,6 +1,6 @@ {- git-annex checking whether content is wanted - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant.hs b/Assistant.hs index 2ba778d80..e49924928 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -1,6 +1,6 @@ {- git-annex assistant daemon - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index a41baa85f..1286e4590 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -1,6 +1,6 @@ {- git-annex assistant alerts - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Alert/Utility.hs b/Assistant/Alert/Utility.hs index ea1280dac..65484e0e6 100644 --- a/Assistant/Alert/Utility.hs +++ b/Assistant/Alert/Utility.hs @@ -1,6 +1,6 @@ {- git-annex assistant alert utilities - - - Copyright 2012, 2013 Joey Hess + - Copyright 2012, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/BranchChange.hs b/Assistant/BranchChange.hs index c9354544a..c588c910a 100644 --- a/Assistant/BranchChange.hs +++ b/Assistant/BranchChange.hs @@ -1,6 +1,6 @@ {- git-annex assistant git-annex branch change tracking - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Changes.hs b/Assistant/Changes.hs index 2ecd2036c..6eb9bc28e 100644 --- a/Assistant/Changes.hs +++ b/Assistant/Changes.hs @@ -1,6 +1,6 @@ {- git-annex assistant change tracking - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Commits.hs b/Assistant/Commits.hs index 7d1d3780f..c82f8f4c7 100644 --- a/Assistant/Commits.hs +++ b/Assistant/Commits.hs @@ -1,6 +1,6 @@ {- git-annex assistant commit tracking - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Common.hs b/Assistant/Common.hs index f9719422d..5fab84290 100644 --- a/Assistant/Common.hs +++ b/Assistant/Common.hs @@ -1,6 +1,6 @@ {- Common infrastructure for the git-annex assistant. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/CredPairCache.hs b/Assistant/CredPairCache.hs index 2b8f72e7c..ac355b55a 100644 --- a/Assistant/CredPairCache.hs +++ b/Assistant/CredPairCache.hs @@ -1,6 +1,6 @@ {- git-annex assistant CredPair cache. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 3edc2c174..1ed40595e 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -1,6 +1,6 @@ {- git-annex assistant daemon status - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/DeleteRemote.hs b/Assistant/DeleteRemote.hs index 9b1f974ff..5b044fd18 100644 --- a/Assistant/DeleteRemote.hs +++ b/Assistant/DeleteRemote.hs @@ -1,6 +1,6 @@ {- git-annex assistant remote deletion utilities - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Drop.hs b/Assistant/Drop.hs index efd74fdb3..57eef8f3a 100644 --- a/Assistant/Drop.hs +++ b/Assistant/Drop.hs @@ -1,6 +1,6 @@ {- git-annex assistant dropping of unwanted content - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Install.hs b/Assistant/Install.hs index e2d52692e..6da6d2389 100644 --- a/Assistant/Install.hs +++ b/Assistant/Install.hs @@ -1,6 +1,6 @@ {- Assistant installation - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Install/AutoStart.hs b/Assistant/Install/AutoStart.hs index b03d20224..b27b69775 100644 --- a/Assistant/Install/AutoStart.hs +++ b/Assistant/Install/AutoStart.hs @@ -1,6 +1,6 @@ {- Assistant autostart file installation - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Install/Menu.hs b/Assistant/Install/Menu.hs index d095cdd88..32393abaf 100644 --- a/Assistant/Install/Menu.hs +++ b/Assistant/Install/Menu.hs @@ -1,6 +1,6 @@ {- Assistant menu installation. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/MakeRemote.hs b/Assistant/MakeRemote.hs index d244a7729..a5eace724 100644 --- a/Assistant/MakeRemote.hs +++ b/Assistant/MakeRemote.hs @@ -1,6 +1,6 @@ {- git-annex assistant remote creation utilities - - - Copyright 2012, 2013 Joey Hess + - Copyright 2012, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Monad.hs b/Assistant/Monad.hs index 5b3f5abb4..a34264a01 100644 --- a/Assistant/Monad.hs +++ b/Assistant/Monad.hs @@ -1,6 +1,6 @@ {- git-annex assistant monad - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/NamedThread.hs b/Assistant/NamedThread.hs index e1b3983f7..f80953053 100644 --- a/Assistant/NamedThread.hs +++ b/Assistant/NamedThread.hs @@ -1,6 +1,6 @@ {- git-annex assistant named threads. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/NetMessager.hs b/Assistant/NetMessager.hs index f042b4e4e..dd1811141 100644 --- a/Assistant/NetMessager.hs +++ b/Assistant/NetMessager.hs @@ -1,6 +1,6 @@ {- git-annex assistant out of band network messager interface - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Pairing.hs b/Assistant/Pairing.hs index bb1384a15..492b98592 100644 --- a/Assistant/Pairing.hs +++ b/Assistant/Pairing.hs @@ -1,6 +1,6 @@ {- git-annex assistant repo pairing, core data types - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Pairing/MakeRemote.hs b/Assistant/Pairing/MakeRemote.hs index 3f3823664..8c0c4d524 100644 --- a/Assistant/Pairing/MakeRemote.hs +++ b/Assistant/Pairing/MakeRemote.hs @@ -1,6 +1,6 @@ {- git-annex assistant pairing remote creation - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Pairing/Network.hs b/Assistant/Pairing/Network.hs index 4bb6088b1..7a4ac3ffe 100644 --- a/Assistant/Pairing/Network.hs +++ b/Assistant/Pairing/Network.hs @@ -4,7 +4,7 @@ - each message is repeated until acknowledged. This is done using a - thread, that gets stopped before the next message is sent. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Pushes.hs b/Assistant/Pushes.hs index 54f31a84b..7b4de450f 100644 --- a/Assistant/Pushes.hs +++ b/Assistant/Pushes.hs @@ -1,6 +1,6 @@ {- git-annex assistant push tracking - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/RemoteControl.hs b/Assistant/RemoteControl.hs index 86d13cc56..1016f1169 100644 --- a/Assistant/RemoteControl.hs +++ b/Assistant/RemoteControl.hs @@ -1,6 +1,6 @@ {- git-annex assistant RemoteDaemon control - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/RepoProblem.hs b/Assistant/RepoProblem.hs index 6913fefc6..32595916e 100644 --- a/Assistant/RepoProblem.hs +++ b/Assistant/RepoProblem.hs @@ -1,6 +1,6 @@ {- git-annex assistant remote problem handling - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/ScanRemotes.hs b/Assistant/ScanRemotes.hs index 2743c0f36..0ce7a47cc 100644 --- a/Assistant/ScanRemotes.hs +++ b/Assistant/ScanRemotes.hs @@ -1,6 +1,6 @@ {- git-annex assistant remotes needing scanning - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Ssh.hs b/Assistant/Ssh.hs index 7b82f4624..c41340962 100644 --- a/Assistant/Ssh.hs +++ b/Assistant/Ssh.hs @@ -1,6 +1,6 @@ {- git-annex assistant ssh utilities - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Sync.hs b/Assistant/Sync.hs index 4bc63241c..d914d2246 100644 --- a/Assistant/Sync.hs +++ b/Assistant/Sync.hs @@ -1,6 +1,6 @@ {- git-annex assistant repo syncing - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index 47c2aa4aa..2c1addb24 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -1,6 +1,6 @@ {- git-annex assistant commit thread - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/ConfigMonitor.hs b/Assistant/Threads/ConfigMonitor.hs index d02e53db5..7ab55fb82 100644 --- a/Assistant/Threads/ConfigMonitor.hs +++ b/Assistant/Threads/ConfigMonitor.hs @@ -1,6 +1,6 @@ {- git-annex assistant config monitor thread - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/Cronner.hs b/Assistant/Threads/Cronner.hs index 6dc6f4c6b..451fa75c6 100644 --- a/Assistant/Threads/Cronner.hs +++ b/Assistant/Threads/Cronner.hs @@ -1,6 +1,6 @@ {- git-annex assistant sceduled jobs runner - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/DaemonStatus.hs b/Assistant/Threads/DaemonStatus.hs index 5bbb15acb..d5b2cc25d 100644 --- a/Assistant/Threads/DaemonStatus.hs +++ b/Assistant/Threads/DaemonStatus.hs @@ -1,6 +1,6 @@ {- git-annex assistant daemon status thread - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/Glacier.hs b/Assistant/Threads/Glacier.hs index 4c4012a67..900e0d423 100644 --- a/Assistant/Threads/Glacier.hs +++ b/Assistant/Threads/Glacier.hs @@ -1,6 +1,6 @@ {- git-annex assistant Amazon Glacier retrieval - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index 62dab59af..f1a64925d 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -1,6 +1,6 @@ {- git-annex assistant git merge thread - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index bd7aad69c..023af53cb 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -1,6 +1,6 @@ {- git-annex assistant mount watcher, using either dbus or mtab polling - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/NetWatcher.hs b/Assistant/Threads/NetWatcher.hs index 6a2515237..ad3a87a91 100644 --- a/Assistant/Threads/NetWatcher.hs +++ b/Assistant/Threads/NetWatcher.hs @@ -1,6 +1,6 @@ {- git-annex assistant network connection watcher, using dbus - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/PairListener.hs b/Assistant/Threads/PairListener.hs index cd95ab5a4..a02b8b91a 100644 --- a/Assistant/Threads/PairListener.hs +++ b/Assistant/Threads/PairListener.hs @@ -1,6 +1,6 @@ {- git-annex assistant thread to listen for incoming pairing traffic - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/ProblemFixer.hs b/Assistant/Threads/ProblemFixer.hs index 8095581a6..86ee027f7 100644 --- a/Assistant/Threads/ProblemFixer.hs +++ b/Assistant/Threads/ProblemFixer.hs @@ -1,6 +1,6 @@ {- git-annex assistant thread to handle fixing problems with repositories - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 3ec922fe4..35989ed48 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -1,6 +1,6 @@ {- git-annex assistant git pushing thread - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/RemoteControl.hs b/Assistant/Threads/RemoteControl.hs index 5af4fddcd..ae63aff5c 100644 --- a/Assistant/Threads/RemoteControl.hs +++ b/Assistant/Threads/RemoteControl.hs @@ -1,6 +1,6 @@ {- git-annex assistant communication with remotedaemon - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index df29df006..3073cfe41 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -1,6 +1,6 @@ {- git-annex assistant sanity checker - - - Copyright 2012, 2013 Joey Hess + - Copyright 2012, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/TransferPoller.hs b/Assistant/Threads/TransferPoller.hs index a5b30b4f0..73562dbf7 100644 --- a/Assistant/Threads/TransferPoller.hs +++ b/Assistant/Threads/TransferPoller.hs @@ -1,6 +1,6 @@ {- git-annex assistant transfer polling thread - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs index fc2394e62..3cbaadf19 100644 --- a/Assistant/Threads/TransferScanner.hs +++ b/Assistant/Threads/TransferScanner.hs @@ -1,6 +1,6 @@ {- git-annex assistant thread to scan remotes to find needed transfers - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index 6e8791732..c452d87c2 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -1,6 +1,6 @@ {- git-annex assistant transfer watching thread - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 53d8a578c..073dbef3c 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -1,6 +1,6 @@ {- git-annex assistant data transferrer thread - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/UpgradeWatcher.hs b/Assistant/Threads/UpgradeWatcher.hs index 431e6f339..e779c8e54 100644 --- a/Assistant/Threads/UpgradeWatcher.hs +++ b/Assistant/Threads/UpgradeWatcher.hs @@ -1,6 +1,6 @@ {- git-annex assistant thread to detect when git-annex is upgraded - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/Upgrader.hs b/Assistant/Threads/Upgrader.hs index 100c15414..602d09208 100644 --- a/Assistant/Threads/Upgrader.hs +++ b/Assistant/Threads/Upgrader.hs @@ -1,6 +1,6 @@ {- git-annex assistant thread to detect when upgrade is available - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index a921861b8..ca9de6836 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -1,6 +1,6 @@ {- git-annex assistant tree watcher - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index d01096c7a..fd78ba8d8 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -1,6 +1,6 @@ {- git-annex assistant webapp thread - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/XMPPClient.hs b/Assistant/Threads/XMPPClient.hs index 8ce99eac6..78d527920 100644 --- a/Assistant/Threads/XMPPClient.hs +++ b/Assistant/Threads/XMPPClient.hs @@ -1,6 +1,6 @@ {- git-annex XMPP client - - - Copyright 2012, 2013 Joey Hess + - Copyright 2012, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Threads/XMPPPusher.hs b/Assistant/Threads/XMPPPusher.hs index 35c76ebf1..ec11b9b94 100644 --- a/Assistant/Threads/XMPPPusher.hs +++ b/Assistant/Threads/XMPPPusher.hs @@ -9,7 +9,7 @@ - they would deadlock with only one thread. For larger numbers of - clients, the two threads are also sufficient. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index d138e16ef..ba13b3f04 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -1,6 +1,6 @@ {- git-annex assistant pending transfer queue - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/TransferSlots.hs b/Assistant/TransferSlots.hs index cafbb7bdf..bbc2ec7e5 100644 --- a/Assistant/TransferSlots.hs +++ b/Assistant/TransferSlots.hs @@ -1,6 +1,6 @@ {- git-annex assistant transfer slots - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/TransferrerPool.hs b/Assistant/TransferrerPool.hs index 3ac9f3452..152625f4f 100644 --- a/Assistant/TransferrerPool.hs +++ b/Assistant/TransferrerPool.hs @@ -1,6 +1,6 @@ {- A pool of "git-annex transferkeys" processes - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/Alert.hs b/Assistant/Types/Alert.hs index 9fd33c7a2..a2e5d5c82 100644 --- a/Assistant/Types/Alert.hs +++ b/Assistant/Types/Alert.hs @@ -1,6 +1,6 @@ {- git-annex assistant alert types - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/BranchChange.hs b/Assistant/Types/BranchChange.hs index 399abee54..f769657d0 100644 --- a/Assistant/Types/BranchChange.hs +++ b/Assistant/Types/BranchChange.hs @@ -1,6 +1,6 @@ {- git-annex assistant git-annex branch change tracking - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/Buddies.hs b/Assistant/Types/Buddies.hs index 36d8a4fed..2887aaef0 100644 --- a/Assistant/Types/Buddies.hs +++ b/Assistant/Types/Buddies.hs @@ -1,6 +1,6 @@ {- git-annex assistant buddies - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/Changes.hs b/Assistant/Types/Changes.hs index e8ecc6e48..1d8b51775 100644 --- a/Assistant/Types/Changes.hs +++ b/Assistant/Types/Changes.hs @@ -1,6 +1,6 @@ {- git-annex assistant change tracking - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/Commits.hs b/Assistant/Types/Commits.hs index 500faa901..bf83fc486 100644 --- a/Assistant/Types/Commits.hs +++ b/Assistant/Types/Commits.hs @@ -1,6 +1,6 @@ {- git-annex assistant commit tracking - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/CredPairCache.hs b/Assistant/Types/CredPairCache.hs index a1e11c257..9777e29ee 100644 --- a/Assistant/Types/CredPairCache.hs +++ b/Assistant/Types/CredPairCache.hs @@ -1,6 +1,6 @@ {- git-annex assistant CredPair cache. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/DaemonStatus.hs b/Assistant/Types/DaemonStatus.hs index 2adad2828..e1b6c997e 100644 --- a/Assistant/Types/DaemonStatus.hs +++ b/Assistant/Types/DaemonStatus.hs @@ -1,6 +1,6 @@ {- git-annex assistant daemon status - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/NamedThread.hs b/Assistant/Types/NamedThread.hs index 5dd1364ad..b07b322ad 100644 --- a/Assistant/Types/NamedThread.hs +++ b/Assistant/Types/NamedThread.hs @@ -1,6 +1,6 @@ {- named threads - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/NetMessager.hs b/Assistant/Types/NetMessager.hs index f5ad85b4a..475d810ae 100644 --- a/Assistant/Types/NetMessager.hs +++ b/Assistant/Types/NetMessager.hs @@ -1,6 +1,6 @@ {- git-annex assistant out of band network messager types - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/Pushes.hs b/Assistant/Types/Pushes.hs index 99e0ee162..0da8b44b5 100644 --- a/Assistant/Types/Pushes.hs +++ b/Assistant/Types/Pushes.hs @@ -1,6 +1,6 @@ {- git-annex assistant push tracking - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/RemoteControl.hs b/Assistant/Types/RemoteControl.hs index 523cd8b8d..42cb4a5aa 100644 --- a/Assistant/Types/RemoteControl.hs +++ b/Assistant/Types/RemoteControl.hs @@ -1,6 +1,6 @@ {- git-annex assistant RemoteDaemon control - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/RepoProblem.hs b/Assistant/Types/RepoProblem.hs index ece5a5286..3b9c72cf8 100644 --- a/Assistant/Types/RepoProblem.hs +++ b/Assistant/Types/RepoProblem.hs @@ -1,6 +1,6 @@ {- git-annex assistant repository problem tracking - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/ScanRemotes.hs b/Assistant/Types/ScanRemotes.hs index 8219f9baf..ac6d8fef9 100644 --- a/Assistant/Types/ScanRemotes.hs +++ b/Assistant/Types/ScanRemotes.hs @@ -1,6 +1,6 @@ {- git-annex assistant remotes needing scanning - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/ThreadName.hs b/Assistant/Types/ThreadName.hs index c8d264a38..57c704dad 100644 --- a/Assistant/Types/ThreadName.hs +++ b/Assistant/Types/ThreadName.hs @@ -1,6 +1,6 @@ {- name of a thread - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/ThreadedMonad.hs b/Assistant/Types/ThreadedMonad.hs index 1a2aa7eb7..eadf325ea 100644 --- a/Assistant/Types/ThreadedMonad.hs +++ b/Assistant/Types/ThreadedMonad.hs @@ -1,6 +1,6 @@ {- making the Annex monad available across threads - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/TransferQueue.hs b/Assistant/Types/TransferQueue.hs index e4bf2ae92..73a7521c5 100644 --- a/Assistant/Types/TransferQueue.hs +++ b/Assistant/Types/TransferQueue.hs @@ -1,6 +1,6 @@ {- git-annex assistant pending transfer queue - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/TransferSlots.hs b/Assistant/Types/TransferSlots.hs index 5140995a3..5fa1219a7 100644 --- a/Assistant/Types/TransferSlots.hs +++ b/Assistant/Types/TransferSlots.hs @@ -1,6 +1,6 @@ {- git-annex assistant transfer slots - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/TransferrerPool.hs b/Assistant/Types/TransferrerPool.hs index b66fdfa13..697bb8dd5 100644 --- a/Assistant/Types/TransferrerPool.hs +++ b/Assistant/Types/TransferrerPool.hs @@ -1,6 +1,6 @@ {- A pool of "git-annex transferkeys" processes available for use - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Types/UrlRenderer.hs b/Assistant/Types/UrlRenderer.hs index 521905bf3..68c238d6a 100644 --- a/Assistant/Types/UrlRenderer.hs +++ b/Assistant/Types/UrlRenderer.hs @@ -1,6 +1,6 @@ {- webapp url renderer access from the assistant - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/Unused.hs b/Assistant/Unused.hs index c2c10b048..194739367 100644 --- a/Assistant/Unused.hs +++ b/Assistant/Unused.hs @@ -1,6 +1,6 @@ {- git-annex assistant unused files - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/XMPP.hs b/Assistant/XMPP.hs index cc0343abf..b9ae50e27 100644 --- a/Assistant/XMPP.hs +++ b/Assistant/XMPP.hs @@ -1,6 +1,6 @@ {- core xmpp support - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/XMPP/Buddies.hs b/Assistant/XMPP/Buddies.hs index 0c466e51c..29e0e24cf 100644 --- a/Assistant/XMPP/Buddies.hs +++ b/Assistant/XMPP/Buddies.hs @@ -1,6 +1,6 @@ {- xmpp buddies - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/XMPP/Client.hs b/Assistant/XMPP/Client.hs index 314ace64a..6d09d32e6 100644 --- a/Assistant/XMPP/Client.hs +++ b/Assistant/XMPP/Client.hs @@ -1,6 +1,6 @@ {- xmpp client support - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Assistant/XMPP/Git.hs b/Assistant/XMPP/Git.hs index 120d4c53a..2186b5bce 100644 --- a/Assistant/XMPP/Git.hs +++ b/Assistant/XMPP/Git.hs @@ -1,6 +1,6 @@ {- git over XMPP - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Backend.hs b/Backend.hs index 0fcaaa7ed..922d0c2a7 100644 --- a/Backend.hs +++ b/Backend.hs @@ -1,6 +1,6 @@ {- git-annex key/value backends - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Backend/Hash.hs b/Backend/Hash.hs index 8ddccd229..82763a9be 100644 --- a/Backend/Hash.hs +++ b/Backend/Hash.hs @@ -1,6 +1,6 @@ {- git-tnnex hashing backends - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Backend/URL.hs b/Backend/URL.hs index ac517a5f3..8ec270e95 100644 --- a/Backend/URL.hs +++ b/Backend/URL.hs @@ -1,6 +1,6 @@ {- git-annex "URL" backend -- keys whose content is available from urls. - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Backend/Utilities.hs b/Backend/Utilities.hs index 6426353e7..4c1f70eda 100644 --- a/Backend/Utilities.hs +++ b/Backend/Utilities.hs @@ -1,6 +1,6 @@ {- git-annex backend utilities - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Backend/WORM.hs b/Backend/WORM.hs index 24dba5795..59f9a7354 100644 --- a/Backend/WORM.hs +++ b/Backend/WORM.hs @@ -1,6 +1,6 @@ {- git-annex "WORM" backend -- Write Once, Read Many - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Build/BundledPrograms.hs b/Build/BundledPrograms.hs index d5cf3ee7b..1e826cb10 100644 --- a/Build/BundledPrograms.hs +++ b/Build/BundledPrograms.hs @@ -1,6 +1,6 @@ {- Bundled programs - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Build/DesktopFile.hs b/Build/DesktopFile.hs index 6a5838f81..6e70b0d5f 100644 --- a/Build/DesktopFile.hs +++ b/Build/DesktopFile.hs @@ -1,7 +1,7 @@ {- Generating and installing a desktop menu entry file and icon, - and a desktop autostart file. (And OSX equivilants.) - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Build/EvilLinker.hs b/Build/EvilLinker.hs index e2921cc8c..d1b0cc746 100644 --- a/Build/EvilLinker.hs +++ b/Build/EvilLinker.hs @@ -3,7 +3,7 @@ - - See https://ghc.haskell.org/trac/ghc/ticket/8596 - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Build/EvilSplicer.hs b/Build/EvilSplicer.hs index fc41c624f..1fd64670b 100644 --- a/Build/EvilSplicer.hs +++ b/Build/EvilSplicer.hs @@ -23,7 +23,7 @@ - need modifications to compile. - - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Build/InstallDesktopFile.hs b/Build/InstallDesktopFile.hs index c8a3f07f5..d6a94adde 100644 --- a/Build/InstallDesktopFile.hs +++ b/Build/InstallDesktopFile.hs @@ -1,7 +1,7 @@ {- Generating and installing a desktop menu entry file and icon, - and a desktop autostart file. (And OSX equivilants.) - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Build/LinuxMkLibs.hs b/Build/LinuxMkLibs.hs index 1ca2fa651..3fb757a22 100644 --- a/Build/LinuxMkLibs.hs +++ b/Build/LinuxMkLibs.hs @@ -1,6 +1,6 @@ {- Linux library copier and binary shimmer - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Build/NullSoftInstaller.hs b/Build/NullSoftInstaller.hs index bc94e60cd..554681d9d 100644 --- a/Build/NullSoftInstaller.hs +++ b/Build/NullSoftInstaller.hs @@ -11,7 +11,7 @@ - exception of git. The user needs to install git separately, - and the installer checks for that. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Build/OSXMkLibs.hs b/Build/OSXMkLibs.hs index ef668bb4a..9622bcb14 100644 --- a/Build/OSXMkLibs.hs +++ b/Build/OSXMkLibs.hs @@ -1,6 +1,6 @@ {- OSX library copier - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Build/Standalone.hs b/Build/Standalone.hs index da030933d..2a6c04e6d 100644 --- a/Build/Standalone.hs +++ b/Build/Standalone.hs @@ -1,6 +1,6 @@ {- Makes standalone bundle. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/BuildFlags.hs b/BuildFlags.hs index b29c83c1f..168085749 100644 --- a/BuildFlags.hs +++ b/BuildFlags.hs @@ -1,6 +1,6 @@ {- git-annex build flags reporting - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Checks.hs b/Checks.hs index 831c0a009..e344cef2d 100644 --- a/Checks.hs +++ b/Checks.hs @@ -3,7 +3,7 @@ - Common sanity checks for commands, and an interface to selectively - remove them, or add others. - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/CmdLine.hs b/CmdLine.hs index 1d93855ce..cd7a1a986 100644 --- a/CmdLine.hs +++ b/CmdLine.hs @@ -1,6 +1,6 @@ {- git-annex command line parsing and dispatch - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/CmdLine/Action.hs b/CmdLine/Action.hs index 65cdbec14..57e1fa60b 100644 --- a/CmdLine/Action.hs +++ b/CmdLine/Action.hs @@ -1,6 +1,6 @@ {- git-annex command-line actions - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/CmdLine/GitAnnex.hs b/CmdLine/GitAnnex.hs index 6903ea1a8..cbae7d486 100644 --- a/CmdLine/GitAnnex.hs +++ b/CmdLine/GitAnnex.hs @@ -1,6 +1,6 @@ {- git-annex main program - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/CmdLine/GitAnnex/Options.hs b/CmdLine/GitAnnex/Options.hs index f9f5989ee..aaa77c92c 100644 --- a/CmdLine/GitAnnex/Options.hs +++ b/CmdLine/GitAnnex/Options.hs @@ -1,6 +1,6 @@ {- git-annex options - - - Copyright 2010, 2013 Joey Hess + - Copyright 2010, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/CmdLine/GitAnnexShell.hs b/CmdLine/GitAnnexShell.hs index 21284f400..b1b351e3b 100644 --- a/CmdLine/GitAnnexShell.hs +++ b/CmdLine/GitAnnexShell.hs @@ -1,6 +1,6 @@ {- git-annex-shell main program - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/CmdLine/GitAnnexShell/Fields.hs b/CmdLine/GitAnnexShell/Fields.hs index 4f208773b..93b048040 100644 --- a/CmdLine/GitAnnexShell/Fields.hs +++ b/CmdLine/GitAnnexShell/Fields.hs @@ -1,6 +1,6 @@ {- git-annex-shell fields - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/CmdLine/Option.hs b/CmdLine/Option.hs index ce44d2ace..1c1331aab 100644 --- a/CmdLine/Option.hs +++ b/CmdLine/Option.hs @@ -1,6 +1,6 @@ {- common command-line options - - - Copyright 2010-2011 Joey Hess + - Copyright 2010-2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/CmdLine/Seek.hs b/CmdLine/Seek.hs index 9a874807b..4a0bb299b 100644 --- a/CmdLine/Seek.hs +++ b/CmdLine/Seek.hs @@ -4,7 +4,7 @@ - the values a user passes to a command, and prepare actions operating - on them. - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/CmdLine/Usage.hs b/CmdLine/Usage.hs index 1998a5f54..82619a304 100644 --- a/CmdLine/Usage.hs +++ b/CmdLine/Usage.hs @@ -1,6 +1,6 @@ {- git-annex usage messages - - - Copyright 2010-2011 Joey Hess + - Copyright 2010-2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command.hs b/Command.hs index fc440f291..56e895cae 100644 --- a/Command.hs +++ b/Command.hs @@ -1,6 +1,6 @@ {- git-annex command infrastructure - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Add.hs b/Command/Add.hs index d745000f8..2671126ca 100644 --- a/Command/Add.hs +++ b/Command/Add.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010, 2013 Joey Hess + - Copyright 2010, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/AddUnused.hs b/Command/AddUnused.hs index 69dbefc17..4aab8d017 100644 --- a/Command/AddUnused.hs +++ b/Command/AddUnused.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/AddUrl.hs b/Command/AddUrl.hs index 97adc75ee..9e3aa31fb 100644 --- a/Command/AddUrl.hs +++ b/Command/AddUrl.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Assistant.hs b/Command/Assistant.hs index 8341a5694..5bdf51682 100644 --- a/Command/Assistant.hs +++ b/Command/Assistant.hs @@ -1,6 +1,6 @@ {- git-annex assistant - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Commit.hs b/Command/Commit.hs index 1f2478ee5..73f9e2d5e 100644 --- a/Command/Commit.hs +++ b/Command/Commit.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/ConfigList.hs b/Command/ConfigList.hs index 7d8f1ea70..33b348b07 100644 --- a/Command/ConfigList.hs +++ b/Command/ConfigList.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Copy.hs b/Command/Copy.hs index 23fa83a35..e5b093c61 100644 --- a/Command/Copy.hs +++ b/Command/Copy.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Dead.hs b/Command/Dead.hs index c19812b73..464db25f9 100644 --- a/Command/Dead.hs +++ b/Command/Dead.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Describe.hs b/Command/Describe.hs index 39a762c06..56a73334d 100644 --- a/Command/Describe.hs +++ b/Command/Describe.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/DiffDriver.hs b/Command/DiffDriver.hs index 41ccc26c2..fa4f49366 100644 --- a/Command/DiffDriver.hs +++ b/Command/DiffDriver.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Direct.hs b/Command/Direct.hs index 3493e103d..1a6b2cb05 100644 --- a/Command/Direct.hs +++ b/Command/Direct.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Drop.hs b/Command/Drop.hs index 3779b3459..6adc13ca5 100644 --- a/Command/Drop.hs +++ b/Command/Drop.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/DropKey.hs b/Command/DropKey.hs index ca20a1a64..890a79466 100644 --- a/Command/DropKey.hs +++ b/Command/DropKey.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/DropUnused.hs b/Command/DropUnused.hs index b9bc2bef6..36ff49720 100644 --- a/Command/DropUnused.hs +++ b/Command/DropUnused.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010,2012 Joey Hess + - Copyright 2010,2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/EnableRemote.hs b/Command/EnableRemote.hs index 909f1ea2f..db3ec2b37 100644 --- a/Command/EnableRemote.hs +++ b/Command/EnableRemote.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/ExamineKey.hs b/Command/ExamineKey.hs index 94f84c5b5..00d4d3a95 100644 --- a/Command/ExamineKey.hs +++ b/Command/ExamineKey.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Find.hs b/Command/Find.hs index 5ca2191db..a52d17384 100644 --- a/Command/Find.hs +++ b/Command/Find.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/FindRef.hs b/Command/FindRef.hs index a552e64e4..2e3d859fa 100644 --- a/Command/FindRef.hs +++ b/Command/FindRef.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Fix.hs b/Command/Fix.hs index 774ef8583..1ef15d0eb 100644 --- a/Command/Fix.hs +++ b/Command/Fix.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Forget.hs b/Command/Forget.hs index 3ea64d5c9..94a1fb421 100644 --- a/Command/Forget.hs +++ b/Command/Forget.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/FromKey.hs b/Command/FromKey.hs index 3b20749fe..14a3d8176 100644 --- a/Command/FromKey.hs +++ b/Command/FromKey.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Fsck.hs b/Command/Fsck.hs index 5dad10127..46fe983d8 100644 --- a/Command/Fsck.hs +++ b/Command/Fsck.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/FuzzTest.hs b/Command/FuzzTest.hs index 87bee963f..d6c9e1ac1 100644 --- a/Command/FuzzTest.hs +++ b/Command/FuzzTest.hs @@ -1,6 +1,6 @@ {- git-annex fuzz generator - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/GCryptSetup.hs b/Command/GCryptSetup.hs index 77aadb22d..7a7f8ae50 100644 --- a/Command/GCryptSetup.hs +++ b/Command/GCryptSetup.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Get.hs b/Command/Get.hs index 2213e32fb..b1929a79c 100644 --- a/Command/Get.hs +++ b/Command/Get.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010, 2013 Joey Hess + - Copyright 2010, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Group.hs b/Command/Group.hs index e1420be88..820f6ab17 100644 --- a/Command/Group.hs +++ b/Command/Group.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Help.hs b/Command/Help.hs index fc1206e03..72913d7c4 100644 --- a/Command/Help.hs +++ b/Command/Help.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Import.hs b/Command/Import.hs index b20e63853..29c139eb6 100644 --- a/Command/Import.hs +++ b/Command/Import.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/ImportFeed.hs b/Command/ImportFeed.hs index c45fad961..b9d78d713 100644 --- a/Command/ImportFeed.hs +++ b/Command/ImportFeed.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/InAnnex.hs b/Command/InAnnex.hs index db48a1422..8e792c4bb 100644 --- a/Command/InAnnex.hs +++ b/Command/InAnnex.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Indirect.hs b/Command/Indirect.hs index a363981be..34a2ef8c9 100644 --- a/Command/Indirect.hs +++ b/Command/Indirect.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Info.hs b/Command/Info.hs index 86b608928..0e66cbce2 100644 --- a/Command/Info.hs +++ b/Command/Info.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Init.hs b/Command/Init.hs index b921c0657..23203b035 100644 --- a/Command/Init.hs +++ b/Command/Init.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/InitRemote.hs b/Command/InitRemote.hs index 51ea15373..7831fe22a 100644 --- a/Command/InitRemote.hs +++ b/Command/InitRemote.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2011,2013 Joey Hess + - Copyright 2011,2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/List.hs b/Command/List.hs index 98cb82311..bc4e3edec 100644 --- a/Command/List.hs +++ b/Command/List.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - Copyright 2013 Antoine Beaupré - - Licensed under the GNU GPL version 3 or higher. diff --git a/Command/Lock.hs b/Command/Lock.hs index f227ab380..574e747c4 100644 --- a/Command/Lock.hs +++ b/Command/Lock.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Log.hs b/Command/Log.hs index 11fd51eb8..7eaa48f70 100644 --- a/Command/Log.hs +++ b/Command/Log.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/LookupKey.hs b/Command/LookupKey.hs index 202233233..0485232ae 100644 --- a/Command/LookupKey.hs +++ b/Command/LookupKey.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Map.hs b/Command/Map.hs index e15fd9c33..75af591d5 100644 --- a/Command/Map.hs +++ b/Command/Map.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Merge.hs b/Command/Merge.hs index eeb151c27..28e3bbb4d 100644 --- a/Command/Merge.hs +++ b/Command/Merge.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2011, 2013 Joey Hess + - Copyright 2011, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/MetaData.hs b/Command/MetaData.hs index 50b9b1f9a..095637959 100644 --- a/Command/MetaData.hs +++ b/Command/MetaData.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Migrate.hs b/Command/Migrate.hs index a7198c71f..9c7dec9ef 100644 --- a/Command/Migrate.hs +++ b/Command/Migrate.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Mirror.hs b/Command/Mirror.hs index ec9ef92c3..558f906c5 100644 --- a/Command/Mirror.hs +++ b/Command/Mirror.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Move.hs b/Command/Move.hs index edb7ede7b..4a3633e8f 100644 --- a/Command/Move.hs +++ b/Command/Move.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/NotifyChanges.hs b/Command/NotifyChanges.hs index 36997666d..7ec6072dd 100644 --- a/Command/NotifyChanges.hs +++ b/Command/NotifyChanges.hs @@ -1,6 +1,6 @@ {- git-annex-shell command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/NumCopies.hs b/Command/NumCopies.hs index 773e10b6a..6c69b2166 100644 --- a/Command/NumCopies.hs +++ b/Command/NumCopies.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/PreCommit.hs b/Command/PreCommit.hs index 91a972024..f4dcff269 100644 --- a/Command/PreCommit.hs +++ b/Command/PreCommit.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Proxy.hs b/Command/Proxy.hs index c34b86c8e..59a6bf959 100644 --- a/Command/Proxy.hs +++ b/Command/Proxy.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/ReKey.hs b/Command/ReKey.hs index 5dadf4e60..980b27f5a 100644 --- a/Command/ReKey.hs +++ b/Command/ReKey.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/RecvKey.hs b/Command/RecvKey.hs index 424ca923d..8572596d2 100644 --- a/Command/RecvKey.hs +++ b/Command/RecvKey.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Reinit.hs b/Command/Reinit.hs index 6de7b9932..b1264effa 100644 --- a/Command/Reinit.hs +++ b/Command/Reinit.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Reinject.hs b/Command/Reinject.hs index a968f6f56..2c785feb6 100644 --- a/Command/Reinject.hs +++ b/Command/Reinject.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/RemoteDaemon.hs b/Command/RemoteDaemon.hs index 9f4cc884d..2e3d62555 100644 --- a/Command/RemoteDaemon.hs +++ b/Command/RemoteDaemon.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Repair.hs b/Command/Repair.hs index 8eb937ce5..d41a074c0 100644 --- a/Command/Repair.hs +++ b/Command/Repair.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/ResolveMerge.hs b/Command/ResolveMerge.hs index 145db37df..ce199e504 100644 --- a/Command/ResolveMerge.hs +++ b/Command/ResolveMerge.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/RmUrl.hs b/Command/RmUrl.hs index 514dcc689..5287718c5 100644 --- a/Command/RmUrl.hs +++ b/Command/RmUrl.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Schedule.hs b/Command/Schedule.hs index ce8b67da0..91ef2c138 100644 --- a/Command/Schedule.hs +++ b/Command/Schedule.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Semitrust.hs b/Command/Semitrust.hs index 146ec2192..49004d7f9 100644 --- a/Command/Semitrust.hs +++ b/Command/Semitrust.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/SendKey.hs b/Command/SendKey.hs index 90eca20bb..62b4edcba 100644 --- a/Command/SendKey.hs +++ b/Command/SendKey.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010,2012 Joey Hess + - Copyright 2010,2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/SetPresentKey.hs b/Command/SetPresentKey.hs index 4e2cdc5a9..1c41dc2ae 100644 --- a/Command/SetPresentKey.hs +++ b/Command/SetPresentKey.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Status.hs b/Command/Status.hs index f49684258..26e96a925 100644 --- a/Command/Status.hs +++ b/Command/Status.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Sync.hs b/Command/Sync.hs index 5ecd0745a..65a025606 100644 --- a/Command/Sync.hs +++ b/Command/Sync.hs @@ -1,7 +1,7 @@ {- git-annex command - - Copyright 2011 Joachim Breitner - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Test.hs b/Command/Test.hs index 4d481369d..3c4251460 100644 --- a/Command/Test.hs +++ b/Command/Test.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/TestRemote.hs b/Command/TestRemote.hs index f0735e087..4a65aa4ec 100644 --- a/Command/TestRemote.hs +++ b/Command/TestRemote.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/TransferInfo.hs b/Command/TransferInfo.hs index ae7fbf033..f90e2ad73 100644 --- a/Command/TransferInfo.hs +++ b/Command/TransferInfo.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/TransferKey.hs b/Command/TransferKey.hs index 469e01322..55d6b95a1 100644 --- a/Command/TransferKey.hs +++ b/Command/TransferKey.hs @@ -1,6 +1,6 @@ {- git-annex plumbing command (for use by old assistant, and users) - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/TransferKeys.hs b/Command/TransferKeys.hs index 346e413e6..990582196 100644 --- a/Command/TransferKeys.hs +++ b/Command/TransferKeys.hs @@ -1,6 +1,6 @@ {- git-annex command, used internally by assistant - - - Copyright 2012, 2013 Joey Hess + - Copyright 2012, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Trust.hs b/Command/Trust.hs index f02fcf617..9d380990e 100644 --- a/Command/Trust.hs +++ b/Command/Trust.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010, 2014 Joey Hess + - Copyright 2010, 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Unannex.hs b/Command/Unannex.hs index e8cf70f51..a88b07c8b 100644 --- a/Command/Unannex.hs +++ b/Command/Unannex.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Undo.hs b/Command/Undo.hs index d47251ab8..8e6b1c44f 100644 --- a/Command/Undo.hs +++ b/Command/Undo.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Ungroup.hs b/Command/Ungroup.hs index a26bd34a9..dd6e8c952 100644 --- a/Command/Ungroup.hs +++ b/Command/Ungroup.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Uninit.hs b/Command/Uninit.hs index ea4a3a9f6..28c169919 100644 --- a/Command/Uninit.hs +++ b/Command/Uninit.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Unlock.hs b/Command/Unlock.hs index 56c4f1dc0..31bc1f2e2 100644 --- a/Command/Unlock.hs +++ b/Command/Unlock.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Untrust.hs b/Command/Untrust.hs index ecd0ae4cf..92e28b637 100644 --- a/Command/Untrust.hs +++ b/Command/Untrust.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Unused.hs b/Command/Unused.hs index 1859856af..4bbde4da4 100644 --- a/Command/Unused.hs +++ b/Command/Unused.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Upgrade.hs b/Command/Upgrade.hs index 7e03ec3ee..081d7ff35 100644 --- a/Command/Upgrade.hs +++ b/Command/Upgrade.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/VAdd.hs b/Command/VAdd.hs index 33614ae59..ea98e6639 100644 --- a/Command/VAdd.hs +++ b/Command/VAdd.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/VCycle.hs b/Command/VCycle.hs index eead9e022..f9a21892b 100644 --- a/Command/VCycle.hs +++ b/Command/VCycle.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/VFilter.hs b/Command/VFilter.hs index 320f28568..fd5ec9630 100644 --- a/Command/VFilter.hs +++ b/Command/VFilter.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/VPop.hs b/Command/VPop.hs index 5046b54b5..1fb1d7a56 100644 --- a/Command/VPop.hs +++ b/Command/VPop.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Version.hs b/Command/Version.hs index 255fd8188..c0c89af68 100644 --- a/Command/Version.hs +++ b/Command/Version.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Vicfg.hs b/Command/Vicfg.hs index 8fc10deb5..f1a64ba23 100644 --- a/Command/Vicfg.hs +++ b/Command/Vicfg.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/View.hs b/Command/View.hs index ae8fe824e..ae2878396 100644 --- a/Command/View.hs +++ b/Command/View.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Wanted.hs b/Command/Wanted.hs index 3f721e368..6b87e51d8 100644 --- a/Command/Wanted.hs +++ b/Command/Wanted.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Watch.hs b/Command/Watch.hs index 2d25b54c3..2f82a7b7f 100644 --- a/Command/Watch.hs +++ b/Command/Watch.hs @@ -1,6 +1,6 @@ {- git-annex watch command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 3a074218f..1c7bcfaa7 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -1,6 +1,6 @@ {- git-annex webapp launcher - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/Whereis.hs b/Command/Whereis.hs index 314c204be..d612ce4f0 100644 --- a/Command/Whereis.hs +++ b/Command/Whereis.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Command/XMPPGit.hs b/Command/XMPPGit.hs index ab238c85e..2bcb7405e 100644 --- a/Command/XMPPGit.hs +++ b/Command/XMPPGit.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Config.hs b/Config.hs index 32644263f..57ced7821 100644 --- a/Config.hs +++ b/Config.hs @@ -1,6 +1,6 @@ {- Git configuration - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Config/Cost.hs b/Config/Cost.hs index 44a26f064..026a90576 100644 --- a/Config/Cost.hs +++ b/Config/Cost.hs @@ -1,6 +1,6 @@ {- Remote costs. - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Config/Files.hs b/Config/Files.hs index 8d5c1fd12..b503a5443 100644 --- a/Config/Files.hs +++ b/Config/Files.hs @@ -1,6 +1,6 @@ {- git-annex extra config files - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Config/NumCopies.hs b/Config/NumCopies.hs index 26d81b8a4..b25e0818d 100644 --- a/Config/NumCopies.hs +++ b/Config/NumCopies.hs @@ -1,6 +1,6 @@ {- git-annex numcopies configuration - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Creds.hs b/Creds.hs index 1f5c83570..765be5a17 100644 --- a/Creds.hs +++ b/Creds.hs @@ -1,6 +1,6 @@ {- Credentials storage - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Crypto.hs b/Crypto.hs index 8d4d4f04f..c2076f461 100644 --- a/Crypto.hs +++ b/Crypto.hs @@ -3,7 +3,7 @@ - Currently using gpg; could later be modified to support different - crypto backends if neccessary. - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git.hs b/Git.hs index c9750a3af..6e270815e 100644 --- a/Git.hs +++ b/Git.hs @@ -3,7 +3,7 @@ - This is written to be completely independant of git-annex and should be - suitable for other uses. - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/AutoCorrect.hs b/Git/AutoCorrect.hs index ecc64e036..7a9d78851 100644 --- a/Git/AutoCorrect.hs +++ b/Git/AutoCorrect.hs @@ -1,6 +1,6 @@ {- git autocorrection using Damerau-Levenshtein edit distance - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Branch.hs b/Git/Branch.hs index 5c6135d57..fd04f1f46 100644 --- a/Git/Branch.hs +++ b/Git/Branch.hs @@ -1,6 +1,6 @@ {- git branch stuff - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/BuildVersion.hs b/Git/BuildVersion.hs index 832ee8ab7..50e4a3ae7 100644 --- a/Git/BuildVersion.hs +++ b/Git/BuildVersion.hs @@ -1,6 +1,6 @@ {- git build version - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/CatFile.hs b/Git/CatFile.hs index d0bcef4fb..a1a0a0d28 100644 --- a/Git/CatFile.hs +++ b/Git/CatFile.hs @@ -1,6 +1,6 @@ {- git cat-file interface - - - Copyright 2011, 2013 Joey Hess + - Copyright 2011, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/CheckAttr.hs b/Git/CheckAttr.hs index 430154116..21eeed493 100644 --- a/Git/CheckAttr.hs +++ b/Git/CheckAttr.hs @@ -1,6 +1,6 @@ {- git check-attr interface - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/CheckIgnore.hs b/Git/CheckIgnore.hs index 2ab7cb3dc..5fa3cb637 100644 --- a/Git/CheckIgnore.hs +++ b/Git/CheckIgnore.hs @@ -1,6 +1,6 @@ {- git check-ignore interface - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Command.hs b/Git/Command.hs index 53b1d68fd..02e3e5a34 100644 --- a/Git/Command.hs +++ b/Git/Command.hs @@ -1,6 +1,6 @@ {- running git commands - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Command/Batch.hs b/Git/Command/Batch.hs index 9cc176008..b2d6509b6 100644 --- a/Git/Command/Batch.hs +++ b/Git/Command/Batch.hs @@ -1,6 +1,6 @@ {- running batch git commands - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Config.hs b/Git/Config.hs index 32c0dd1cc..15109319a 100644 --- a/Git/Config.hs +++ b/Git/Config.hs @@ -1,6 +1,6 @@ {- git repository configuration handling - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Construct.hs b/Git/Construct.hs index 572c5eb37..a0632a223 100644 --- a/Git/Construct.hs +++ b/Git/Construct.hs @@ -1,6 +1,6 @@ {- Construction of Git Repo objects - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/CurrentRepo.hs b/Git/CurrentRepo.hs index f611f7a34..9de00034b 100644 --- a/Git/CurrentRepo.hs +++ b/Git/CurrentRepo.hs @@ -1,6 +1,6 @@ {- The current git repository. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/DiffTree.hs b/Git/DiffTree.hs index 3ea14a15f..5cdcc16bc 100644 --- a/Git/DiffTree.hs +++ b/Git/DiffTree.hs @@ -1,6 +1,6 @@ {- git diff-tree interface - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/DiffTreeItem.hs b/Git/DiffTreeItem.hs index 2389b698a..859f590c1 100644 --- a/Git/DiffTreeItem.hs +++ b/Git/DiffTreeItem.hs @@ -1,6 +1,6 @@ {- git diff-tree item - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/FileMode.hs b/Git/FileMode.hs index fc4d0264e..c3dfe570a 100644 --- a/Git/FileMode.hs +++ b/Git/FileMode.hs @@ -1,6 +1,6 @@ {- git file modes - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/FilePath.hs b/Git/FilePath.hs index 88f315b1c..edc3c0f90 100644 --- a/Git/FilePath.hs +++ b/Git/FilePath.hs @@ -5,7 +5,7 @@ - top of the repository even when run in a subdirectory. Adding some - types helps keep that straight. - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Filename.hs b/Git/Filename.hs index 5e076d3b5..382eb8d48 100644 --- a/Git/Filename.hs +++ b/Git/Filename.hs @@ -1,7 +1,7 @@ {- Some git commands output encoded filenames, in a rather annoyingly complex - C-style encoding. - - - Copyright 2010, 2011 Joey Hess + - Copyright 2010, 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Fsck.hs b/Git/Fsck.hs index c6002f681..f3e6db9f9 100644 --- a/Git/Fsck.hs +++ b/Git/Fsck.hs @@ -1,6 +1,6 @@ {- git fsck interface - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/GCrypt.hs b/Git/GCrypt.hs index db067e25c..46da37257 100644 --- a/Git/GCrypt.hs +++ b/Git/GCrypt.hs @@ -2,7 +2,7 @@ - - https://github.com/blake2-ppc/git-remote-gcrypt - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/HashObject.hs b/Git/HashObject.hs index 8cd35167d..07c72d080 100644 --- a/Git/HashObject.hs +++ b/Git/HashObject.hs @@ -1,6 +1,6 @@ {- git hash-object interface - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Hook.hs b/Git/Hook.hs index 0ea9fd1e7..aec2563f4 100644 --- a/Git/Hook.hs +++ b/Git/Hook.hs @@ -1,6 +1,6 @@ {- git hooks - - - Copyright 2013-2015 Joey Hess + - Copyright 2013-2015 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Index.hs b/Git/Index.hs index 7145bb943..551fd98d3 100644 --- a/Git/Index.hs +++ b/Git/Index.hs @@ -1,6 +1,6 @@ {- git index file stuff - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/LsFiles.hs b/Git/LsFiles.hs index 8d32ba7ef..c23c282d0 100644 --- a/Git/LsFiles.hs +++ b/Git/LsFiles.hs @@ -1,6 +1,6 @@ {- git ls-files interface - - - Copyright 2010,2012 Joey Hess + - Copyright 2010,2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/LsTree.hs b/Git/LsTree.hs index ca5e323e0..7ef951807 100644 --- a/Git/LsTree.hs +++ b/Git/LsTree.hs @@ -1,6 +1,6 @@ {- git ls-tree interface - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Merge.hs b/Git/Merge.hs index 12dfa7c1f..b3a048937 100644 --- a/Git/Merge.hs +++ b/Git/Merge.hs @@ -1,6 +1,6 @@ {- git merging - - - Copyright 2012, 2014 Joey Hess + - Copyright 2012, 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Objects.hs b/Git/Objects.hs index dadd4f543..bda220b5e 100644 --- a/Git/Objects.hs +++ b/Git/Objects.hs @@ -1,6 +1,6 @@ {- .git/objects - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Queue.hs b/Git/Queue.hs index 9b87a18ea..d5c19cd95 100644 --- a/Git/Queue.hs +++ b/Git/Queue.hs @@ -1,6 +1,6 @@ {- git repository command queue - - - Copyright 2010,2012 Joey Hess + - Copyright 2010,2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Ref.hs b/Git/Ref.hs index 3d0c68fb0..5ad7577ff 100644 --- a/Git/Ref.hs +++ b/Git/Ref.hs @@ -1,6 +1,6 @@ {- git ref stuff - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/RefLog.hs b/Git/RefLog.hs index 98c9d66ff..f3a9dad38 100644 --- a/Git/RefLog.hs +++ b/Git/RefLog.hs @@ -1,6 +1,6 @@ {- git reflog interface - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Remote.hs b/Git/Remote.hs index 156e30891..717b54045 100644 --- a/Git/Remote.hs +++ b/Git/Remote.hs @@ -1,6 +1,6 @@ {- git remote stuff - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Remote/Remove.hs b/Git/Remote/Remove.hs index ab1da9cde..2ffc9b358 100644 --- a/Git/Remote/Remove.hs +++ b/Git/Remote/Remove.hs @@ -1,6 +1,6 @@ {- git remote stuff - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Repair.hs b/Git/Repair.hs index bee9f2b50..2557e3b83 100644 --- a/Git/Repair.hs +++ b/Git/Repair.hs @@ -1,6 +1,6 @@ {- git repository recovery - - - Copyright 2013-2014 Joey Hess + - Copyright 2013-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Sha.hs b/Git/Sha.hs index cbb66ea2d..b802c8556 100644 --- a/Git/Sha.hs +++ b/Git/Sha.hs @@ -1,6 +1,6 @@ {- git SHA stuff - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/SharedRepository.hs b/Git/SharedRepository.hs index f3efa8fde..3aab1e39a 100644 --- a/Git/SharedRepository.hs +++ b/Git/SharedRepository.hs @@ -1,6 +1,6 @@ {- git core.sharedRepository handling - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Types.hs b/Git/Types.hs index 838c9e0e7..bb91a1703 100644 --- a/Git/Types.hs +++ b/Git/Types.hs @@ -1,6 +1,6 @@ {- git data types - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/UnionMerge.hs b/Git/UnionMerge.hs index 464200af4..d4dc35e4a 100644 --- a/Git/UnionMerge.hs +++ b/Git/UnionMerge.hs @@ -1,6 +1,6 @@ {- git-union-merge library - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/UpdateIndex.hs b/Git/UpdateIndex.hs index 613596d57..55c5b3bb2 100644 --- a/Git/UpdateIndex.hs +++ b/Git/UpdateIndex.hs @@ -1,6 +1,6 @@ {- git-update-index library - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Url.hs b/Git/Url.hs index d383a6aca..fa7d200dc 100644 --- a/Git/Url.hs +++ b/Git/Url.hs @@ -1,6 +1,6 @@ {- git repository urls - - - Copyright 2010, 2011 Joey Hess + - Copyright 2010, 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Git/Version.hs b/Git/Version.hs index 73ce2f81d..ecd12444c 100644 --- a/Git/Version.hs +++ b/Git/Version.hs @@ -1,6 +1,6 @@ {- git versions - - - Copyright 2011, 2013 Joey Hess + - Copyright 2011, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Limit.hs b/Limit.hs index 1053547ec..ec21b7287 100644 --- a/Limit.hs +++ b/Limit.hs @@ -1,6 +1,6 @@ {- user-specified limits on files to act on - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Limit/Wanted.hs b/Limit/Wanted.hs index 01b8da6b3..e3305398d 100644 --- a/Limit/Wanted.hs +++ b/Limit/Wanted.hs @@ -1,6 +1,6 @@ {- git-annex limits by wanted status - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Locations.hs b/Locations.hs index 614cbdde3..596bf4f85 100644 --- a/Locations.hs +++ b/Locations.hs @@ -1,6 +1,6 @@ {- git-annex file locations - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs.hs b/Logs.hs index d18339361..7452339cd 100644 --- a/Logs.hs +++ b/Logs.hs @@ -1,6 +1,6 @@ {- git-annex log file names - - - Copyright 2013-2014 Joey Hess + - Copyright 2013-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Chunk.hs b/Logs/Chunk.hs index a3e18efc1..8ca3ffed3 100644 --- a/Logs/Chunk.hs +++ b/Logs/Chunk.hs @@ -10,7 +10,7 @@ - - Format: "timestamp uuid:chunksize chunkcount" - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Chunk/Pure.hs b/Logs/Chunk/Pure.hs index 26fdd63c2..af209d7e1 100644 --- a/Logs/Chunk/Pure.hs +++ b/Logs/Chunk/Pure.hs @@ -1,6 +1,6 @@ {- Chunk logs, pure operations. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/FsckResults.hs b/Logs/FsckResults.hs index 23367a3d3..e6db9a076 100644 --- a/Logs/FsckResults.hs +++ b/Logs/FsckResults.hs @@ -1,6 +1,6 @@ {- git-annex fsck results log files - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Group.hs b/Logs/Group.hs index 3f88b627d..3725c046c 100644 --- a/Logs/Group.hs +++ b/Logs/Group.hs @@ -1,6 +1,6 @@ {- git-annex group log - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Location.hs b/Logs/Location.hs index cb1e415fd..d0109b848 100644 --- a/Logs/Location.hs +++ b/Logs/Location.hs @@ -8,7 +8,7 @@ - Repositories record their UUID and the date when they --get or --drop - a value. - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/MapLog.hs b/Logs/MapLog.hs index dd3cc0696..3c7eef26b 100644 --- a/Logs/MapLog.hs +++ b/Logs/MapLog.hs @@ -4,7 +4,7 @@ - - A line of the log will look like: "timestamp field value" - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/MetaData.hs b/Logs/MetaData.hs index d63a87470..3091935cf 100644 --- a/Logs/MetaData.hs +++ b/Logs/MetaData.hs @@ -18,7 +18,7 @@ - and so foo currently has no value. - - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/NumCopies.hs b/Logs/NumCopies.hs index 5cce61ce6..3fc29c2f2 100644 --- a/Logs/NumCopies.hs +++ b/Logs/NumCopies.hs @@ -1,6 +1,6 @@ {- git-annex numcopies log - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/PreferredContent.hs b/Logs/PreferredContent.hs index a485ec600..83269e6d7 100644 --- a/Logs/PreferredContent.hs +++ b/Logs/PreferredContent.hs @@ -1,6 +1,6 @@ {- git-annex preferred content matcher configuration - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/PreferredContent/Raw.hs b/Logs/PreferredContent/Raw.hs index bbf5a1edc..119261ab8 100644 --- a/Logs/PreferredContent/Raw.hs +++ b/Logs/PreferredContent/Raw.hs @@ -1,6 +1,6 @@ {- unparsed preferred content expressions - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Presence.hs b/Logs/Presence.hs index 7545f5afc..cb21adfb3 100644 --- a/Logs/Presence.hs +++ b/Logs/Presence.hs @@ -6,7 +6,7 @@ - A line of the log will look like: "date N INFO" - Where N=1 when the INFO is present, and 0 otherwise. - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Presence/Pure.hs b/Logs/Presence/Pure.hs index 6bf36d883..88f18435f 100644 --- a/Logs/Presence/Pure.hs +++ b/Logs/Presence/Pure.hs @@ -1,6 +1,6 @@ {- git-annex presence log, pure operations - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Remote.hs b/Logs/Remote.hs index 48ee9eb60..91afa242b 100644 --- a/Logs/Remote.hs +++ b/Logs/Remote.hs @@ -1,6 +1,6 @@ {- git-annex remote log - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/RemoteState.hs b/Logs/RemoteState.hs index 195d710c7..7b3859a35 100644 --- a/Logs/RemoteState.hs +++ b/Logs/RemoteState.hs @@ -1,6 +1,6 @@ {- Remote state logs. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Schedule.hs b/Logs/Schedule.hs index 540667059..d2dd0c343 100644 --- a/Logs/Schedule.hs +++ b/Logs/Schedule.hs @@ -1,6 +1,6 @@ {- git-annex scheduled activities log - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/SingleValue.hs b/Logs/SingleValue.hs index bb774b6f4..dbbe996f3 100644 --- a/Logs/SingleValue.hs +++ b/Logs/SingleValue.hs @@ -6,7 +6,7 @@ - - The line with the newest timestamp wins. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index 16c3ebb68..5b5b8f8cb 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -1,6 +1,6 @@ {- git-annex transfer information files and lock files - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Transitions.hs b/Logs/Transitions.hs index 15ea32401..d782455a6 100644 --- a/Logs/Transitions.hs +++ b/Logs/Transitions.hs @@ -7,7 +7,7 @@ - done that is listed in the remote branch by checking that the local - branch contains the same transition, with the same or newer start time. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Trust.hs b/Logs/Trust.hs index 41ce5a551..3d8d7bbae 100644 --- a/Logs/Trust.hs +++ b/Logs/Trust.hs @@ -1,6 +1,6 @@ {- git-annex trust log - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Trust/Basic.hs b/Logs/Trust/Basic.hs index c356be28f..30e8dfb58 100644 --- a/Logs/Trust/Basic.hs +++ b/Logs/Trust/Basic.hs @@ -1,6 +1,6 @@ {- git-annex trust log, basics - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Trust/Pure.hs b/Logs/Trust/Pure.hs index 11cfbe056..d493db63c 100644 --- a/Logs/Trust/Pure.hs +++ b/Logs/Trust/Pure.hs @@ -1,6 +1,6 @@ {- git-annex trust log, pure operations - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/UUID.hs b/Logs/UUID.hs index 154f86d51..8bdf41b9a 100644 --- a/Logs/UUID.hs +++ b/Logs/UUID.hs @@ -8,7 +8,7 @@ - - uuid.log stores a list of known uuids, and their descriptions. - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/UUIDBased.hs b/Logs/UUIDBased.hs index fe1c9e012..ac876e65f 100644 --- a/Logs/UUIDBased.hs +++ b/Logs/UUIDBased.hs @@ -9,7 +9,7 @@ - - New uuid based logs instead use the form: "timestamp UUID INFO" - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Unused.hs b/Logs/Unused.hs index cadf7ed9d..883ab8c5b 100644 --- a/Logs/Unused.hs +++ b/Logs/Unused.hs @@ -10,7 +10,7 @@ - The timestamp indicates when the key was first determined to be unused. - Older versions of the log omit the timestamp. - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/View.hs b/Logs/View.hs index b2a92c405..5ba4bf7c2 100644 --- a/Logs/View.hs +++ b/Logs/View.hs @@ -4,7 +4,7 @@ - - This file is stored locally in .git/annex/, not in the git-annex branch. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Logs/Web.hs b/Logs/Web.hs index 39f177c3b..4729cead4 100644 --- a/Logs/Web.hs +++ b/Logs/Web.hs @@ -1,6 +1,6 @@ {- Web url logs. - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Messages.hs b/Messages.hs index 976ba96d7..88a4a8c18 100644 --- a/Messages.hs +++ b/Messages.hs @@ -1,6 +1,6 @@ {- git-annex output messages - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Messages/JSON.hs b/Messages/JSON.hs index d57d69318..d0ed85a1f 100644 --- a/Messages/JSON.hs +++ b/Messages/JSON.hs @@ -1,6 +1,6 @@ {- git-annex JSON output - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote.hs b/Remote.hs index a48c5f75e..58c1a0f17 100644 --- a/Remote.hs +++ b/Remote.hs @@ -1,6 +1,6 @@ {- git-annex remotes - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/BitTorrent.hs b/Remote/BitTorrent.hs index d0a35fa30..0ecf3ef25 100644 --- a/Remote/BitTorrent.hs +++ b/Remote/BitTorrent.hs @@ -1,6 +1,6 @@ {- BitTorrent remote. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Bup.hs b/Remote/Bup.hs index 16f73a66f..01501dc9e 100644 --- a/Remote/Bup.hs +++ b/Remote/Bup.hs @@ -1,6 +1,6 @@ {- Using bup as a remote. - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Ddar.hs b/Remote/Ddar.hs index f77193051..d22a1f899 100644 --- a/Remote/Ddar.hs +++ b/Remote/Ddar.hs @@ -1,6 +1,6 @@ {- Using ddar as a remote. Based on bup and rsync remotes. - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - Copyright 2014 Robie Basak - - Licensed under the GNU GPL version 3 or higher. diff --git a/Remote/Directory.hs b/Remote/Directory.hs index 66a3de49f..2b887a82f 100644 --- a/Remote/Directory.hs +++ b/Remote/Directory.hs @@ -1,6 +1,6 @@ {- A "remote" that is just a filesystem directory. - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Directory/LegacyChunked.hs b/Remote/Directory/LegacyChunked.hs index b2248c5f6..72d52f95d 100644 --- a/Remote/Directory/LegacyChunked.hs +++ b/Remote/Directory/LegacyChunked.hs @@ -2,7 +2,7 @@ - - Can be removed eventually. - - - Copyright 2011-2012 Joey Hess + - Copyright 2011-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/External.hs b/Remote/External.hs index dd8e793c7..0ec284ff4 100644 --- a/Remote/External.hs +++ b/Remote/External.hs @@ -1,6 +1,6 @@ {- External special remote interface. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/External/Types.hs b/Remote/External/Types.hs index 73177d316..d0fb2ff7a 100644 --- a/Remote/External/Types.hs +++ b/Remote/External/Types.hs @@ -1,6 +1,6 @@ {- External special remote data types. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/GCrypt.hs b/Remote/GCrypt.hs index 6bf7f89f5..b977750c3 100644 --- a/Remote/GCrypt.hs +++ b/Remote/GCrypt.hs @@ -1,6 +1,6 @@ {- git remotes encrypted using git-remote-gcrypt - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Git.hs b/Remote/Git.hs index 583e9c728..b31a1d850 100644 --- a/Remote/Git.hs +++ b/Remote/Git.hs @@ -1,6 +1,6 @@ {- Standard git remotes. - - - Copyright 2011-2012 Joey Hess + - Copyright 2011-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Glacier.hs b/Remote/Glacier.hs index f24369d52..bffe33be8 100644 --- a/Remote/Glacier.hs +++ b/Remote/Glacier.hs @@ -1,6 +1,6 @@ {- Amazon Glacier remotes. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/AWS.hs b/Remote/Helper/AWS.hs index 17e1a2921..145c48714 100644 --- a/Remote/Helper/AWS.hs +++ b/Remote/Helper/AWS.hs @@ -1,6 +1,6 @@ {- Amazon Web Services common infrastructure. - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/Chunked.hs b/Remote/Helper/Chunked.hs index 8516268ce..2f21ba66c 100644 --- a/Remote/Helper/Chunked.hs +++ b/Remote/Helper/Chunked.hs @@ -1,6 +1,6 @@ {- git-annex chunked remotes - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/Chunked/Legacy.hs b/Remote/Helper/Chunked/Legacy.hs index 4f402705a..ae3a29f32 100644 --- a/Remote/Helper/Chunked/Legacy.hs +++ b/Remote/Helper/Chunked/Legacy.hs @@ -1,6 +1,6 @@ {- legacy git-annex chunked remotes - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/Encryptable.hs b/Remote/Helper/Encryptable.hs index 11e20d7b0..c1243a518 100644 --- a/Remote/Helper/Encryptable.hs +++ b/Remote/Helper/Encryptable.hs @@ -1,6 +1,6 @@ {- common functions for encryptable remotes - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/Git.hs b/Remote/Helper/Git.hs index 9ed27ac8b..3b438a0bb 100644 --- a/Remote/Helper/Git.hs +++ b/Remote/Helper/Git.hs @@ -1,6 +1,6 @@ {- Utilities for git remotes. - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/Hooks.hs b/Remote/Helper/Hooks.hs index 529c35d3f..3765281be 100644 --- a/Remote/Helper/Hooks.hs +++ b/Remote/Helper/Hooks.hs @@ -1,6 +1,6 @@ {- Adds hooks to remotes. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/Http.hs b/Remote/Helper/Http.hs index 3d08066ba..81c1654ef 100644 --- a/Remote/Helper/Http.hs +++ b/Remote/Helper/Http.hs @@ -1,6 +1,6 @@ {- helpers for remotes using http - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/Messages.hs b/Remote/Helper/Messages.hs index 774716ca1..30db70fbb 100644 --- a/Remote/Helper/Messages.hs +++ b/Remote/Helper/Messages.hs @@ -1,6 +1,6 @@ {- git-annex remote messages - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/ReadOnly.hs b/Remote/Helper/ReadOnly.hs index cd92a083c..2e327a040 100644 --- a/Remote/Helper/ReadOnly.hs +++ b/Remote/Helper/ReadOnly.hs @@ -1,6 +1,6 @@ {- Adds readonly support to remotes. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs index 181d7548f..bdf0ead22 100644 --- a/Remote/Helper/Special.hs +++ b/Remote/Helper/Special.hs @@ -1,6 +1,6 @@ {- helpers for special remotes - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Helper/Ssh.hs b/Remote/Helper/Ssh.hs index 9f0a77178..5d39f3bc8 100644 --- a/Remote/Helper/Ssh.hs +++ b/Remote/Helper/Ssh.hs @@ -1,6 +1,6 @@ {- git-annex remote access with ssh and git-annex-shell - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Hook.hs b/Remote/Hook.hs index 5955e51c2..ce7781cfb 100644 --- a/Remote/Hook.hs +++ b/Remote/Hook.hs @@ -1,6 +1,6 @@ {- A remote that provides hooks to run shell commands. - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/List.hs b/Remote/List.hs index a4d18c7c8..49b0a35f2 100644 --- a/Remote/List.hs +++ b/Remote/List.hs @@ -2,7 +2,7 @@ {- git-annex remote list - - - Copyright 2011,2012 Joey Hess + - Copyright 2011,2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs index ad5b77d38..ae6f5450e 100644 --- a/Remote/Rsync.hs +++ b/Remote/Rsync.hs @@ -1,6 +1,6 @@ {- A remote that is only accessible by rsync. - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Rsync/RsyncUrl.hs b/Remote/Rsync/RsyncUrl.hs index 61bbe2f3f..7ebd2f68d 100644 --- a/Remote/Rsync/RsyncUrl.hs +++ b/Remote/Rsync/RsyncUrl.hs @@ -1,6 +1,6 @@ {- Rsync urls. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/S3.hs b/Remote/S3.hs index 104fdddca..b0c1de114 100644 --- a/Remote/S3.hs +++ b/Remote/S3.hs @@ -1,6 +1,6 @@ {- S3 remotes - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Tahoe.hs b/Remote/Tahoe.hs index 27bb12884..56bf66427 100644 --- a/Remote/Tahoe.hs +++ b/Remote/Tahoe.hs @@ -13,7 +13,7 @@ - - Tahoe has its own encryption, so git-annex's encryption is not used. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/Web.hs b/Remote/Web.hs index 594f90b97..17e3830a8 100644 --- a/Remote/Web.hs +++ b/Remote/Web.hs @@ -1,6 +1,6 @@ {- Web remote. - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/WebDAV.hs b/Remote/WebDAV.hs index ae1e4b972..aaebecf41 100644 --- a/Remote/WebDAV.hs +++ b/Remote/WebDAV.hs @@ -1,6 +1,6 @@ {- WebDAV remotes. - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Remote/WebDAV/DavLocation.hs b/Remote/WebDAV/DavLocation.hs index 33c3aa079..b5d374943 100644 --- a/Remote/WebDAV/DavLocation.hs +++ b/Remote/WebDAV/DavLocation.hs @@ -1,6 +1,6 @@ {- WebDAV locations. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/RemoteDaemon/Common.hs b/RemoteDaemon/Common.hs index e844e2c88..50524b44c 100644 --- a/RemoteDaemon/Common.hs +++ b/RemoteDaemon/Common.hs @@ -1,6 +1,6 @@ {- git-remote-daemon utilities - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/RemoteDaemon/Core.hs b/RemoteDaemon/Core.hs index ed79c0195..bc5ad8a58 100644 --- a/RemoteDaemon/Core.hs +++ b/RemoteDaemon/Core.hs @@ -1,6 +1,6 @@ {- git-remote-daemon core - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/RemoteDaemon/Transport.hs b/RemoteDaemon/Transport.hs index 09118ca8b..8297bb3b0 100644 --- a/RemoteDaemon/Transport.hs +++ b/RemoteDaemon/Transport.hs @@ -1,6 +1,6 @@ {- git-remote-daemon transports - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/RemoteDaemon/Transport/Ssh.hs b/RemoteDaemon/Transport/Ssh.hs index 6315ede85..509b8f319 100644 --- a/RemoteDaemon/Transport/Ssh.hs +++ b/RemoteDaemon/Transport/Ssh.hs @@ -1,6 +1,6 @@ {- git-remote-daemon, git-annex-shell over ssh transport - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/RemoteDaemon/Transport/Ssh/Types.hs b/RemoteDaemon/Transport/Ssh/Types.hs index d3fd314b4..fa6a55d3d 100644 --- a/RemoteDaemon/Transport/Ssh/Types.hs +++ b/RemoteDaemon/Transport/Ssh/Types.hs @@ -1,6 +1,6 @@ {- git-remote-daemon, git-annex-shell notifychanges protocol types - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/RemoteDaemon/Types.hs b/RemoteDaemon/Types.hs index bdc94d949..9009533e1 100644 --- a/RemoteDaemon/Types.hs +++ b/RemoteDaemon/Types.hs @@ -1,6 +1,6 @@ {- git-remote-daemon data types. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Test.hs b/Test.hs index 803bc6220..8d432cb61 100644 --- a/Test.hs +++ b/Test.hs @@ -1,6 +1,6 @@ {- git-annex test suite - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types.hs b/Types.hs index 8768ed1fe..4d1cde61b 100644 --- a/Types.hs +++ b/Types.hs @@ -1,6 +1,6 @@ {- git-annex abstract data types - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Availability.hs b/Types/Availability.hs index f8c8ea3f3..6956537d2 100644 --- a/Types/Availability.hs +++ b/Types/Availability.hs @@ -1,6 +1,6 @@ {- git-annex remote availability - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Backend.hs b/Types/Backend.hs index 117ce8b24..8967f3153 100644 --- a/Types/Backend.hs +++ b/Types/Backend.hs @@ -2,7 +2,7 @@ - - Most things should not need this, using Types instead - - - Copyright 2010,2012 Joey Hess + - Copyright 2010,2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/BranchState.hs b/Types/BranchState.hs index 2f7948ebb..8c57a223a 100644 --- a/Types/BranchState.hs +++ b/Types/BranchState.hs @@ -1,6 +1,6 @@ {- git-annex BranchState data type - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/CleanupActions.hs b/Types/CleanupActions.hs index fafa2ee00..508579643 100644 --- a/Types/CleanupActions.hs +++ b/Types/CleanupActions.hs @@ -1,6 +1,6 @@ {- Enumeration of cleanup actions - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Command.hs b/Types/Command.hs index 1f8456194..de6e78038 100644 --- a/Types/Command.hs +++ b/Types/Command.hs @@ -1,6 +1,6 @@ {- git-annex command data types - - - Copyright 2010-2011 Joey Hess + - Copyright 2010-2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Creds.hs b/Types/Creds.hs index c16e530b1..ad1827bc9 100644 --- a/Types/Creds.hs +++ b/Types/Creds.hs @@ -1,6 +1,6 @@ {- credentials - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Crypto.hs b/Types/Crypto.hs index 48d03ce12..682629d6a 100644 --- a/Types/Crypto.hs +++ b/Types/Crypto.hs @@ -1,6 +1,6 @@ {- git-annex crypto types - - - Copyright 2011-2012 Joey Hess + - Copyright 2011-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/DesktopNotify.hs b/Types/DesktopNotify.hs index f8494487d..9ea51401f 100644 --- a/Types/DesktopNotify.hs +++ b/Types/DesktopNotify.hs @@ -1,6 +1,6 @@ {- git-annex DesktopNotify type - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Distribution.hs b/Types/Distribution.hs index 4201f49ad..2a44a1575 100644 --- a/Types/Distribution.hs +++ b/Types/Distribution.hs @@ -1,6 +1,6 @@ {- Data type for a distribution of git-annex - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/FileMatcher.hs b/Types/FileMatcher.hs index 03a86a38c..a79bbd258 100644 --- a/Types/FileMatcher.hs +++ b/Types/FileMatcher.hs @@ -1,6 +1,6 @@ {- git-annex file matcher types - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/GitConfig.hs b/Types/GitConfig.hs index 3d89b0433..ef8068cc4 100644 --- a/Types/GitConfig.hs +++ b/Types/GitConfig.hs @@ -1,6 +1,6 @@ {- git-annex configuration - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Group.hs b/Types/Group.hs index 88bc35207..2695670ab 100644 --- a/Types/Group.hs +++ b/Types/Group.hs @@ -1,6 +1,6 @@ {- git-annex repo groups - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Key.hs b/Types/Key.hs index da9ff494a..037437303 100644 --- a/Types/Key.hs +++ b/Types/Key.hs @@ -2,7 +2,7 @@ - - Most things should not need this, using Types instead - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/KeySource.hs b/Types/KeySource.hs index fd4af07a6..7c2fd13d5 100644 --- a/Types/KeySource.hs +++ b/Types/KeySource.hs @@ -1,6 +1,6 @@ {- KeySource data type - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/LockPool.hs b/Types/LockPool.hs index c7d411cdc..803822042 100644 --- a/Types/LockPool.hs +++ b/Types/LockPool.hs @@ -1,6 +1,6 @@ {- git-annex lock pool data types - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Messages.hs b/Types/Messages.hs index 2196028e3..224c2fe87 100644 --- a/Types/Messages.hs +++ b/Types/Messages.hs @@ -1,6 +1,6 @@ {- git-annex Messages data types - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/MetaData.hs b/Types/MetaData.hs index f19e0b439..2a6b3b864 100644 --- a/Types/MetaData.hs +++ b/Types/MetaData.hs @@ -1,6 +1,6 @@ {- git-annex general metadata - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/NumCopies.hs b/Types/NumCopies.hs index b93fcf968..d8ea31e69 100644 --- a/Types/NumCopies.hs +++ b/Types/NumCopies.hs @@ -1,6 +1,6 @@ {- git-annex numcopies type - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Option.hs b/Types/Option.hs index 036257838..f3b5ca9e1 100644 --- a/Types/Option.hs +++ b/Types/Option.hs @@ -1,6 +1,6 @@ {- git-annex command options - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/Remote.hs b/Types/Remote.hs index 4d17abf95..5df08c775 100644 --- a/Types/Remote.hs +++ b/Types/Remote.hs @@ -2,7 +2,7 @@ - - Most things should not need this, using Types instead - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/ScheduledActivity.hs b/Types/ScheduledActivity.hs index 5cdbe29e8..f4f80635b 100644 --- a/Types/ScheduledActivity.hs +++ b/Types/ScheduledActivity.hs @@ -1,6 +1,6 @@ {- git-annex scheduled activities - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/StandardGroups.hs b/Types/StandardGroups.hs index 66c1dd5ef..83e612917 100644 --- a/Types/StandardGroups.hs +++ b/Types/StandardGroups.hs @@ -1,6 +1,6 @@ {- git-annex standard repository groups - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/StoreRetrieve.hs b/Types/StoreRetrieve.hs index a21fa7866..13710fba2 100644 --- a/Types/StoreRetrieve.hs +++ b/Types/StoreRetrieve.hs @@ -1,6 +1,6 @@ {- Types for Storer and Retriever actions for remotes. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/TrustLevel.hs b/Types/TrustLevel.hs index 4af71294a..1cc4c662e 100644 --- a/Types/TrustLevel.hs +++ b/Types/TrustLevel.hs @@ -1,6 +1,6 @@ {- git-annex trust levels - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/UUID.hs b/Types/UUID.hs index df3884059..de7ddd65d 100644 --- a/Types/UUID.hs +++ b/Types/UUID.hs @@ -1,6 +1,6 @@ {- git-annex UUID type - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/UrlContents.hs b/Types/UrlContents.hs index 2085aebfa..411c3ae42 100644 --- a/Types/UrlContents.hs +++ b/Types/UrlContents.hs @@ -1,6 +1,6 @@ {- git-annex URL contents - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Types/View.hs b/Types/View.hs index 43afdb8c8..0426ba977 100644 --- a/Types/View.hs +++ b/Types/View.hs @@ -1,6 +1,6 @@ {- types for metadata based branch views - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Upgrade.hs b/Upgrade.hs index 8566f0d5d..8d205a874 100644 --- a/Upgrade.hs +++ b/Upgrade.hs @@ -1,6 +1,6 @@ {- git-annex upgrade support - - - Copyright 2010, 2013 Joey Hess + - Copyright 2010, 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Upgrade/V0.hs b/Upgrade/V0.hs index 00a08cb45..b3486f864 100644 --- a/Upgrade/V0.hs +++ b/Upgrade/V0.hs @@ -1,6 +1,6 @@ {- git-annex v0 -> v1 upgrade support - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Upgrade/V1.hs b/Upgrade/V1.hs index 347b102ac..1f0dae43e 100644 --- a/Upgrade/V1.hs +++ b/Upgrade/V1.hs @@ -1,6 +1,6 @@ {- git-annex v1 -> v2 upgrade support - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Upgrade/V2.hs b/Upgrade/V2.hs index 0672de8b6..2b0b277e8 100644 --- a/Upgrade/V2.hs +++ b/Upgrade/V2.hs @@ -1,6 +1,6 @@ {- git-annex v2 -> v3 upgrade support - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Upgrade/V3.hs b/Upgrade/V3.hs index 38f700cf8..8d873a6ce 100644 --- a/Upgrade/V3.hs +++ b/Upgrade/V3.hs @@ -2,7 +2,7 @@ - - There was no explicit v3 to v4 upgrade, so run v5 upgrade code. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Upgrade/V4.hs b/Upgrade/V4.hs index dad073d0b..cb1643ffd 100644 --- a/Upgrade/V4.hs +++ b/Upgrade/V4.hs @@ -1,6 +1,6 @@ {- git-annex v4 -> v5 uppgrade support - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Utility/Applicative.hs b/Utility/Applicative.hs index fd8944b28..fce3c0485 100644 --- a/Utility/Applicative.hs +++ b/Utility/Applicative.hs @@ -1,6 +1,6 @@ {- applicative stuff - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Base64.hs b/Utility/Base64.hs index 3f0c19965..56637a117 100644 --- a/Utility/Base64.hs +++ b/Utility/Base64.hs @@ -1,6 +1,6 @@ {- Simple Base64 access - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Batch.hs b/Utility/Batch.hs index ff81318fb..d96f9d3f3 100644 --- a/Utility/Batch.hs +++ b/Utility/Batch.hs @@ -1,6 +1,6 @@ {- Running a long or expensive batch operation niced. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Bloom.hs b/Utility/Bloom.hs index b0988a8c4..aee760a1d 100644 --- a/Utility/Bloom.hs +++ b/Utility/Bloom.hs @@ -1,6 +1,6 @@ {- bloomfilter compatability wrapper - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/CoProcess.hs b/Utility/CoProcess.hs index 97826ec1e..9854b47fc 100644 --- a/Utility/CoProcess.hs +++ b/Utility/CoProcess.hs @@ -1,7 +1,7 @@ {- Interface for running a shell command as a coprocess, - sending it queries and getting back results. - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/CopyFile.hs b/Utility/CopyFile.hs index 503ab842a..b123d006d 100644 --- a/Utility/CopyFile.hs +++ b/Utility/CopyFile.hs @@ -1,6 +1,6 @@ {- file copying - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/DBus.hs b/Utility/DBus.hs index 29dbc9479..5b0470301 100644 --- a/Utility/DBus.hs +++ b/Utility/DBus.hs @@ -1,6 +1,6 @@ {- DBus utilities - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Daemon.hs b/Utility/Daemon.hs index d1f539e98..d7f0407be 100644 --- a/Utility/Daemon.hs +++ b/Utility/Daemon.hs @@ -1,6 +1,6 @@ {- daemon support - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Data.hs b/Utility/Data.hs index 2df12b36d..5ecd218fb 100644 --- a/Utility/Data.hs +++ b/Utility/Data.hs @@ -1,6 +1,6 @@ {- utilities for simple data types - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/DataUnits.hs b/Utility/DataUnits.hs index e035b2f86..3ff553887 100644 --- a/Utility/DataUnits.hs +++ b/Utility/DataUnits.hs @@ -1,6 +1,6 @@ {- data size display and parsing - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - License: BSD-2-clause - diff --git a/Utility/DirWatcher.hs b/Utility/DirWatcher.hs index 7e582239d..3d3c14619 100644 --- a/Utility/DirWatcher.hs +++ b/Utility/DirWatcher.hs @@ -4,7 +4,7 @@ - (and subdirectories) for changes, and runs hooks for different - sorts of events as they occur. - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/DirWatcher/FSEvents.hs b/Utility/DirWatcher/FSEvents.hs index e16de7b94..a07139c44 100644 --- a/Utility/DirWatcher/FSEvents.hs +++ b/Utility/DirWatcher/FSEvents.hs @@ -1,6 +1,6 @@ {- FSEvents interface - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/DirWatcher/INotify.hs b/Utility/DirWatcher/INotify.hs index 9400c7940..4d11b95a8 100644 --- a/Utility/DirWatcher/INotify.hs +++ b/Utility/DirWatcher/INotify.hs @@ -1,6 +1,6 @@ {- higher-level inotify interface - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/DirWatcher/Kqueue.hs b/Utility/DirWatcher/Kqueue.hs index 453c8d3f1..b0a6ed84f 100644 --- a/Utility/DirWatcher/Kqueue.hs +++ b/Utility/DirWatcher/Kqueue.hs @@ -1,6 +1,6 @@ {- BSD kqueue file modification notification interface - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/DirWatcher/Types.hs b/Utility/DirWatcher/Types.hs index 2c92d6cd5..75ef69f83 100644 --- a/Utility/DirWatcher/Types.hs +++ b/Utility/DirWatcher/Types.hs @@ -1,6 +1,6 @@ {- generic directory watching types - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/DirWatcher/Win32Notify.hs b/Utility/DirWatcher/Win32Notify.hs index 54f34935a..3428f3db3 100644 --- a/Utility/DirWatcher/Win32Notify.hs +++ b/Utility/DirWatcher/Win32Notify.hs @@ -1,6 +1,6 @@ {- Win32-notify interface - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Directory.hs b/Utility/Directory.hs index e4e4b80a7..85ec8bf45 100644 --- a/Utility/Directory.hs +++ b/Utility/Directory.hs @@ -1,6 +1,6 @@ {- directory traversal and manipulation - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/DiskFree.hs b/Utility/DiskFree.hs index af4431e88..c4125d4f0 100644 --- a/Utility/DiskFree.hs +++ b/Utility/DiskFree.hs @@ -1,6 +1,6 @@ {- disk free space checking - - - Copyright 2012, 2014 Joey Hess + - Copyright 2012, 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Dot.hs b/Utility/Dot.hs index 3bea644f7..e21915d32 100644 --- a/Utility/Dot.hs +++ b/Utility/Dot.hs @@ -1,6 +1,6 @@ {- a simple graphviz / dot(1) digraph description generator library - - - Copyright 2010 Joey Hess + - Copyright 2010 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/DottedVersion.hs b/Utility/DottedVersion.hs index 14aa16da9..67e40ff3c 100644 --- a/Utility/DottedVersion.hs +++ b/Utility/DottedVersion.hs @@ -1,6 +1,6 @@ {- dotted versions, such as 1.0.1 - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Env.hs b/Utility/Env.hs index ff6644fbf..fdf06d807 100644 --- a/Utility/Env.hs +++ b/Utility/Env.hs @@ -1,6 +1,6 @@ {- portable environment variables - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Exception.hs b/Utility/Exception.hs index ef3ab1dac..ab47ae95f 100644 --- a/Utility/Exception.hs +++ b/Utility/Exception.hs @@ -1,6 +1,6 @@ {- Simple IO exception handling (and some more) - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/ExternalSHA.hs b/Utility/ExternalSHA.hs index 858d04e6a..6cef2830d 100644 --- a/Utility/ExternalSHA.hs +++ b/Utility/ExternalSHA.hs @@ -3,7 +3,7 @@ - This is typically a bit faster than using Haskell libraries, - by around 1% to 10%. Worth it for really big files. - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/FileMode.hs b/Utility/FileMode.hs index 832250bde..5c4001ed8 100644 --- a/Utility/FileMode.hs +++ b/Utility/FileMode.hs @@ -1,6 +1,6 @@ {- File mode utilities. - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/FileSystemEncoding.hs b/Utility/FileSystemEncoding.hs index fa4b39aa3..844e81e59 100644 --- a/Utility/FileSystemEncoding.hs +++ b/Utility/FileSystemEncoding.hs @@ -1,6 +1,6 @@ {- GHC File system encoding handling. - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Format.hs b/Utility/Format.hs index 78620f9b9..0a6f6ce7d 100644 --- a/Utility/Format.hs +++ b/Utility/Format.hs @@ -1,6 +1,6 @@ {- Formatted string handling. - - - Copyright 2010, 2011 Joey Hess + - Copyright 2010, 2011 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/FreeDesktop.hs b/Utility/FreeDesktop.hs index c1f042ce8..ee1c2f302 100644 --- a/Utility/FreeDesktop.hs +++ b/Utility/FreeDesktop.hs @@ -5,7 +5,7 @@ - http://standards.freedesktop.org/menu-spec/latest/ - http://standards.freedesktop.org/icon-theme-spec/latest/ - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Glob.hs b/Utility/Glob.hs index 373f3fdbf..d35a96849 100644 --- a/Utility/Glob.hs +++ b/Utility/Glob.hs @@ -3,7 +3,7 @@ - This uses TDFA when available, with a fallback to regex-compat. - TDFA is less buggy in its support for non-unicode characters. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Gpg.hs b/Utility/Gpg.hs index cda89028f..37508a495 100644 --- a/Utility/Gpg.hs +++ b/Utility/Gpg.hs @@ -1,6 +1,6 @@ {- gpg interface - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Utility/HumanNumber.hs b/Utility/HumanNumber.hs index 8783f8152..c3fede95f 100644 --- a/Utility/HumanNumber.hs +++ b/Utility/HumanNumber.hs @@ -1,6 +1,6 @@ {- numbers for humans - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/HumanTime.hs b/Utility/HumanTime.hs index 3c23f31f7..85a9e15b6 100644 --- a/Utility/HumanTime.hs +++ b/Utility/HumanTime.hs @@ -1,6 +1,6 @@ {- Time for humans. - - - Copyright 2012-2013 Joey Hess + - Copyright 2012-2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/InodeCache.hs b/Utility/InodeCache.hs index d068e3801..b5fe9034e 100644 --- a/Utility/InodeCache.hs +++ b/Utility/InodeCache.hs @@ -1,7 +1,7 @@ {- Caching a file's inode, size, and modification time - to see when it's changed. - - - Copyright 2013, 2014 Joey Hess + - Copyright 2013, 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/JSONStream.hs b/Utility/JSONStream.hs index b28646268..2746678cc 100644 --- a/Utility/JSONStream.hs +++ b/Utility/JSONStream.hs @@ -1,6 +1,6 @@ {- Streaming JSON output. - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/LinuxMkLibs.hs b/Utility/LinuxMkLibs.hs index aaafd8d0c..db64d1236 100644 --- a/Utility/LinuxMkLibs.hs +++ b/Utility/LinuxMkLibs.hs @@ -1,6 +1,6 @@ {- Linux library copier and binary shimmer - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/LockFile.hs b/Utility/LockFile.hs index 4f0d4ba3e..f9a0e6783 100644 --- a/Utility/LockFile.hs +++ b/Utility/LockFile.hs @@ -4,7 +4,7 @@ - This module does *not* attempt to be a portability shim, it just exposes - the native locking of the OS. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/LockFile/Posix.hs b/Utility/LockFile/Posix.hs index 6e4444fcf..a5775dba1 100644 --- a/Utility/LockFile/Posix.hs +++ b/Utility/LockFile/Posix.hs @@ -1,6 +1,6 @@ {- Posix lock files - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/LockFile/Windows.hs b/Utility/LockFile/Windows.hs index 73c248b03..eff129cee 100644 --- a/Utility/LockFile/Windows.hs +++ b/Utility/LockFile/Windows.hs @@ -1,6 +1,6 @@ {- Windows lock files - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/LogFile.hs b/Utility/LogFile.hs index e4f90d418..bc6d92ca9 100644 --- a/Utility/LogFile.hs +++ b/Utility/LogFile.hs @@ -1,6 +1,6 @@ {- log files - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Lsof.hs b/Utility/Lsof.hs index ae74b25fd..433b7c679 100644 --- a/Utility/Lsof.hs +++ b/Utility/Lsof.hs @@ -1,6 +1,6 @@ {- lsof interface - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Matcher.hs b/Utility/Matcher.hs index 3356bdd07..19a77201c 100644 --- a/Utility/Matcher.hs +++ b/Utility/Matcher.hs @@ -10,7 +10,7 @@ - Is forgiving about misplaced closing parens, so "foo and (bar or baz" - will be handled, as will "foo and ( bar or baz ) )" - - - Copyright 2011-2013 Joey Hess + - Copyright 2011-2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Metered.hs b/Utility/Metered.hs index e4f3b448a..84694b26b 100644 --- a/Utility/Metered.hs +++ b/Utility/Metered.hs @@ -1,6 +1,6 @@ {- Metered IO - - - Copyright 2012, 2013 Joey Hess + - Copyright 2012, 2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Misc.hs b/Utility/Misc.hs index 949f41e7b..e4eccac43 100644 --- a/Utility/Misc.hs +++ b/Utility/Misc.hs @@ -1,6 +1,6 @@ {- misc utility functions - - - Copyright 2010-2011 Joey Hess + - Copyright 2010-2011 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Monad.hs b/Utility/Monad.hs index eba3c4283..878e0da67 100644 --- a/Utility/Monad.hs +++ b/Utility/Monad.hs @@ -1,6 +1,6 @@ {- monadic stuff - - - Copyright 2010-2012 Joey Hess + - Copyright 2010-2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Mounts.hsc b/Utility/Mounts.hsc index b6defda43..1fb2362df 100644 --- a/Utility/Mounts.hsc +++ b/Utility/Mounts.hsc @@ -4,7 +4,7 @@ - Volker Wysk - - Modified to support BSD, Mac OS X, and Android by - - Joey Hess + - Joey Hess - - Licensed under the GNU LGPL version 2.1 or higher. -} diff --git a/Utility/Network.hs b/Utility/Network.hs index 9c6980261..7f228e155 100644 --- a/Utility/Network.hs +++ b/Utility/Network.hs @@ -1,6 +1,6 @@ {- network functions - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/NotificationBroadcaster.hs b/Utility/NotificationBroadcaster.hs index 8a6e09f92..6f7cabf10 100644 --- a/Utility/NotificationBroadcaster.hs +++ b/Utility/NotificationBroadcaster.hs @@ -6,7 +6,7 @@ - - Multiple clients are supported. Each has a unique id. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/OSX.hs b/Utility/OSX.hs index 4c930f2f8..22028e210 100644 --- a/Utility/OSX.hs +++ b/Utility/OSX.hs @@ -1,6 +1,6 @@ {- OSX stuff - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/PID.hs b/Utility/PID.hs index a70a4e2a4..ac63045a7 100644 --- a/Utility/PID.hs +++ b/Utility/PID.hs @@ -1,6 +1,6 @@ {- process ids - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Parallel.hs b/Utility/Parallel.hs index 7966811ab..2352ba706 100644 --- a/Utility/Parallel.hs +++ b/Utility/Parallel.hs @@ -1,6 +1,6 @@ {- parallel processing via threads - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Path.hs b/Utility/Path.hs index b9dbd92a9..4ff88f72e 100644 --- a/Utility/Path.hs +++ b/Utility/Path.hs @@ -1,6 +1,6 @@ {- path manipulation - - - Copyright 2010-2014 Joey Hess + - Copyright 2010-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Percentage.hs b/Utility/Percentage.hs index f2fb45762..a30c26037 100644 --- a/Utility/Percentage.hs +++ b/Utility/Percentage.hs @@ -1,6 +1,6 @@ {- percentages - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/PosixFiles.hs b/Utility/PosixFiles.hs index 5abbb5785..5a94ead01 100644 --- a/Utility/PosixFiles.hs +++ b/Utility/PosixFiles.hs @@ -2,7 +2,7 @@ - - This is like System.PosixCompat.Files, except with a fixed rename. - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/QuickCheck.hs b/Utility/QuickCheck.hs index a498ee619..54200d3f7 100644 --- a/Utility/QuickCheck.hs +++ b/Utility/QuickCheck.hs @@ -1,6 +1,6 @@ {- QuickCheck with additional instances - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Quvi.hs b/Utility/Quvi.hs index cf3a23cfd..7f73809c0 100644 --- a/Utility/Quvi.hs +++ b/Utility/Quvi.hs @@ -1,6 +1,6 @@ {- querying quvi (import qualified) - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Rsync.hs b/Utility/Rsync.hs index ed1eab6f3..241202813 100644 --- a/Utility/Rsync.hs +++ b/Utility/Rsync.hs @@ -1,6 +1,6 @@ {- various rsync stuff - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/SRV.hs b/Utility/SRV.hs index 1b86aeb76..203585a7e 100644 --- a/Utility/SRV.hs +++ b/Utility/SRV.hs @@ -3,7 +3,7 @@ - Uses either the ADNS Haskell library, or the standalone Haskell DNS - package, or the host command. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/SafeCommand.hs b/Utility/SafeCommand.hs index 86e60db0e..a5556200a 100644 --- a/Utility/SafeCommand.hs +++ b/Utility/SafeCommand.hs @@ -1,6 +1,6 @@ {- safely running shell commands - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Scheduled.hs b/Utility/Scheduled.hs index 4fa3a29f1..e077a1fea 100644 --- a/Utility/Scheduled.hs +++ b/Utility/Scheduled.hs @@ -1,6 +1,6 @@ {- scheduled activities - - - Copyright 2013-2014 Joey Hess + - Copyright 2013-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Shell.hs b/Utility/Shell.hs index 00f60d09f..e71ca53aa 100644 --- a/Utility/Shell.hs +++ b/Utility/Shell.hs @@ -1,6 +1,6 @@ {- /bin/sh handling - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/SimpleProtocol.hs b/Utility/SimpleProtocol.hs index 0ac0be4cc..4a2d8635e 100644 --- a/Utility/SimpleProtocol.hs +++ b/Utility/SimpleProtocol.hs @@ -1,6 +1,6 @@ {- Simple line-based protocols. - - - Copyright 2013-2014 Joey Hess + - Copyright 2013-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/SshConfig.hs b/Utility/SshConfig.hs index e45d09acd..ca336a4b8 100644 --- a/Utility/SshConfig.hs +++ b/Utility/SshConfig.hs @@ -1,6 +1,6 @@ {- ssh config file parsing and modification - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/TList.hs b/Utility/TList.hs index 5532cdce5..033c8ca02 100644 --- a/Utility/TList.hs +++ b/Utility/TList.hs @@ -6,7 +6,7 @@ - Unlike a TQueue, the entire contents of a TList can be efficiently - read without modifying it. - - - Copyright 2013 Joey Hess + - Copyright 2013 Joey Hess -} {-# LANGUAGE BangPatterns #-} diff --git a/Utility/Tense.hs b/Utility/Tense.hs index 0392ba500..ef2454bdc 100644 --- a/Utility/Tense.hs +++ b/Utility/Tense.hs @@ -1,6 +1,6 @@ {- Past and present tense text. - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/ThreadLock.hs b/Utility/ThreadLock.hs index 548d524e1..e212fc11f 100644 --- a/Utility/ThreadLock.hs +++ b/Utility/ThreadLock.hs @@ -1,6 +1,6 @@ {- locking between threads - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/ThreadScheduler.hs b/Utility/ThreadScheduler.hs index e6a81aebd..da05e9966 100644 --- a/Utility/ThreadScheduler.hs +++ b/Utility/ThreadScheduler.hs @@ -1,6 +1,6 @@ {- thread scheduling - - - Copyright 2012, 2013 Joey Hess + - Copyright 2012, 2013 Joey Hess - Copyright 2011 Bas van Dijk & Roel van Dijk - - License: BSD-2-clause diff --git a/Utility/Tmp.hs b/Utility/Tmp.hs index 7599cdd00..dc5598137 100644 --- a/Utility/Tmp.hs +++ b/Utility/Tmp.hs @@ -1,6 +1,6 @@ {- Temporary files and directories. - - - Copyright 2010-2013 Joey Hess + - Copyright 2010-2013 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Touch.hsc b/Utility/Touch.hsc index 87d551ad6..f87bb62d6 100644 --- a/Utility/Touch.hsc +++ b/Utility/Touch.hsc @@ -1,6 +1,6 @@ {- More control over touching a file. - - - Copyright 2011 Joey Hess + - Copyright 2011 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/URI.hs b/Utility/URI.hs index 30c6be3db..e68fda58d 100644 --- a/Utility/URI.hs +++ b/Utility/URI.hs @@ -1,6 +1,6 @@ {- Network.URI - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Url.hs b/Utility/Url.hs index a8828e048..9d131353a 100644 --- a/Utility/Url.hs +++ b/Utility/Url.hs @@ -1,6 +1,6 @@ {- Url downloading. - - - Copyright 2011-2014 Joey Hess + - Copyright 2011-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/UserInfo.hs b/Utility/UserInfo.hs index c82f04079..5bf8d5c09 100644 --- a/Utility/UserInfo.hs +++ b/Utility/UserInfo.hs @@ -1,6 +1,6 @@ {- user info - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Verifiable.hs b/Utility/Verifiable.hs index a62213074..a861416e2 100644 --- a/Utility/Verifiable.hs +++ b/Utility/Verifiable.hs @@ -1,6 +1,6 @@ {- values verified using a shared secret - - - Copyright 2012 Joey Hess + - Copyright 2012 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 6c42e103b..54f2d6f2b 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -1,6 +1,6 @@ {- Yesod webapp - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/WinProcess.hs b/Utility/WinProcess.hs index 4621b4fa6..36f079d04 100644 --- a/Utility/WinProcess.hs +++ b/Utility/WinProcess.hs @@ -1,6 +1,6 @@ {- Windows processes - - - Copyright 2014 Joey Hess + - Copyright 2014 Joey Hess - - License: BSD-2-clause -} diff --git a/Utility/Yesod.hs b/Utility/Yesod.hs index ecd4eaf94..231bb291e 100644 --- a/Utility/Yesod.hs +++ b/Utility/Yesod.hs @@ -3,7 +3,7 @@ - Also a bit of a compatability layer to make it easier to support yesod - 1.1-1.4 in the same code base. - - - Copyright 2012-2014 Joey Hess + - Copyright 2012-2014 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} diff --git a/Utility/libdiskfree.c b/Utility/libdiskfree.c index fd8f87766..c2f8368f0 100644 --- a/Utility/libdiskfree.c +++ b/Utility/libdiskfree.c @@ -1,6 +1,6 @@ /* disk free space checking, C mini-library * - * Copyright 2012, 2014 Joey Hess + * Copyright 2012, 2014 Joey Hess * * License: BSD-2-clause */ diff --git a/Utility/libkqueue.c b/Utility/libkqueue.c index 8e33d2885..3f40465e3 100644 --- a/Utility/libkqueue.c +++ b/Utility/libkqueue.c @@ -1,6 +1,6 @@ /* kqueue interface, C mini-library * - * Copyright 2012 Joey Hess + * Copyright 2012 Joey Hess * * License: BSD-2-clause */ diff --git a/Utility/libmounts.c b/Utility/libmounts.c index 9b3ae9578..c469d7710 100644 --- a/Utility/libmounts.c +++ b/Utility/libmounts.c @@ -5,7 +5,7 @@ * Copyright (c) 2001 * David Rufino * Copyright 2012 - * Joey Hess + * Joey Hess * * Redistribution and use in source and binary forms, with or without * modification, are permitted provided that the following conditions diff --git a/debian/copyright b/debian/copyright index 0053276b1..7b9807680 100644 --- a/debian/copyright +++ b/debian/copyright @@ -2,30 +2,30 @@ Format: http://www.debian.org/doc/packaging-manuals/copyright-format/1.0/ Source: native package Files: * -Copyright: © 2010-2015 Joey Hess +Copyright: © 2010-2015 Joey Hess License: GPL-3+ Files: Assistant/WebApp.hs Assistant/WebApp/* templates/* static/* -Copyright: © 2012-2014 Joey Hess +Copyright: © 2012-2014 Joey Hess © 2014 Sören Brunk License: AGPL-3+ Files: Remote/Ddar.hs -Copyright: © 2011 Joey Hess +Copyright: © 2011 Joey Hess © 2014 Robie Basak License: GPL-3+ Files: Utility/ThreadScheduler.hs Copyright: 2011 Bas van Dijk & Roel van Dijk - 2012, 2013 Joey Hess + 2012, 2013 Joey Hess License: BSD-2-clause Files: Utility/* -Copyright: 2012-2015 Joey Hess +Copyright: 2012-2015 Joey Hess License: BSD-2-clause Files: Utility/Gpg.hs Utility/DirWatcher* -Copyright: © 2010-2014 Joey Hess +Copyright: © 2010-2014 Joey Hess License: GPL-3+ Files: Assistant/WebApp/Bootstrap3.hs @@ -34,7 +34,7 @@ License: BSD-2-clause Files: doc/logo* */favicon.ico standalone/osx/git-annex.app/Contents/Resources/git-annex.icns standalone/android/icons/* Copyright: 2007 Henrik Nyh - 2010 Joey Hess + 2010 Joey Hess 2013 John Lawrence License: other Free to modify and redistribute with due credit, and obviously free to use. @@ -46,14 +46,14 @@ License: LGPL-2.1+ Files: Utility/libmounts.c Copyright: 1980, 1989, 1993, 1994 The Regents of the University of California 2001 David Rufino - 2012 Joey Hess + 2012 Joey Hess License: BSD-3-clause * Copyright (c) 1980, 1989, 1993, 1994 * The Regents of the University of California. All rights reserved. * Copyright (c) 2001 * David Rufino * Copyright 2012 - * Joey Hess + * Joey Hess * * Redistribution and use in source and binary forms, with or without * modification, are permitted provided that the following conditions diff --git a/doc/contact.mdwn b/doc/contact.mdwn index b2ccf8201..db9914d50 100644 --- a/doc/contact.mdwn +++ b/doc/contact.mdwn @@ -1,4 +1,4 @@ -Joey Hess is the author of git-annex. If you need to +Joey Hess is the author of git-annex. If you need to talk about something privately, email me. The [[forum]] is the best place to discuss git-annex. diff --git a/doc/encryption.mdwn b/doc/encryption.mdwn index 3cbc37ee3..29cb8a0bc 100644 --- a/doc/encryption.mdwn +++ b/doc/encryption.mdwn @@ -34,7 +34,7 @@ flexibility, it is the default and recommended encryption scheme. Here the KEYID(s) are passed to `gpg` to find encryption keys. Typically, you will say "keyid=2512E3C7" to use a specific gpg key. -Or, you might say "keyid=joey@kitenet.net" to search for matching keys. +Or, you might say "keyid=id@joeyh.name" to search for matching keys. To add a new key and allow it to access all the content that is stored in the encrypted special remote, just run `git annex diff --git a/doc/forum/example_of_massively_disconnected_operation.mdwn b/doc/forum/example_of_massively_disconnected_operation.mdwn index 00a5d8d6c..78ed6784b 100644 --- a/doc/forum/example_of_massively_disconnected_operation.mdwn +++ b/doc/forum/example_of_massively_disconnected_operation.mdwn @@ -4,7 +4,7 @@ So, I synced it back up! :) --[[Joey]]
 commit 4151f4595fe6205d4aed653617ab23eb3335130a
-Author: Joey Hess 
+Author: Joey Hess 
 Date:   Tue Oct 26 02:18:03 2010 -0400
 
 joey> git pull
diff --git a/doc/git-annex-shell.mdwn b/doc/git-annex-shell.mdwn
index 26ccb9a40..e43d51657 100644
--- a/doc/git-annex-shell.mdwn
+++ b/doc/git-annex-shell.mdwn
@@ -126,7 +126,7 @@ git-shell(1)
 
 # AUTHOR
 
-Joey Hess 
+Joey Hess 
 
 
 
diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn
index b8ad6a1d6..c92208e5c 100644
--- a/doc/git-annex.mdwn
+++ b/doc/git-annex.mdwn
@@ -1896,7 +1896,7 @@ should be included, in, for example, `/usr/share/doc/git-annex/`.
 
 # AUTHOR
 
-Joey Hess 
+Joey Hess 
 
 
 
diff --git a/doc/git-union-merge.mdwn b/doc/git-union-merge.mdwn
index 8e3c34f8f..d0ceb3a8f 100644
--- a/doc/git-union-merge.mdwn
+++ b/doc/git-union-merge.mdwn
@@ -31,7 +31,7 @@ File modes are not currently merged.
 
 # AUTHOR
 
-Joey Hess 
+Joey Hess 
 
 
 
diff --git a/doc/special_remotes/rsync.mdwn b/doc/special_remotes/rsync.mdwn
index 628d2e8cb..2271cbc2a 100644
--- a/doc/special_remotes/rsync.mdwn
+++ b/doc/special_remotes/rsync.mdwn
@@ -2,12 +2,12 @@ This special remote type rsyncs file contents to somewhere else.
 
 Setup example:
 
-	# git annex initremote myrsync type=rsync rsyncurl=rsync://rsync.example.com/myrsync keyid=joey@kitenet.net encryption=shared
+	# git annex initremote myrsync type=rsync rsyncurl=rsync://rsync.example.com/myrsync keyid=id@joeyh.name encryption=shared
 	# git annex describe myrsync "rsync server"
 
 Or for using rsync over SSH
 
-	# git annex initremote myrsync type=rsync rsyncurl=ssh.example.com:/myrsync keyid=joey@kitenet.net encryption=shared
+	# git annex initremote myrsync type=rsync rsyncurl=ssh.example.com:/myrsync keyid=id@joeyh.name encryption=shared
 	# git annex describe myrsync "rsync server"
 
 ## configuration
diff --git a/doc/special_remotes/webdav.mdwn b/doc/special_remotes/webdav.mdwn
index 6b5f5b122..100de8c20 100644
--- a/doc/special_remotes/webdav.mdwn
+++ b/doc/special_remotes/webdav.mdwn
@@ -37,4 +37,4 @@ the webdav remote.
 
 Setup example:
 
-	# WEBDAV_USERNAME=joey@kitenet.net WEBDAV_PASSWORD=xxxxxxx git annex initremote box.com type=webdav url=https://dav.box.com/dav/git-annex chunk=10mb keyid=joey@kitenet.net
+	# WEBDAV_USERNAME=id@joeyh.name WEBDAV_PASSWORD=xxxxxxx git annex initremote box.com type=webdav url=https://dav.box.com/dav/git-annex chunk=10mb keyid=id@joeyh.name
diff --git a/doc/thanks.mdwn b/doc/thanks.mdwn
index 90c994847..4b86a45d9 100644
--- a/doc/thanks.mdwn
+++ b/doc/thanks.mdwn
@@ -4,7 +4,7 @@ you individually, but until I meet all 1500 of you, this page will have to
 do. You have my most sincere thanks. --[[Joey]]
 
 (If I got your name wrong, or you don't want it publically posted here,
-email .)
+email .)
 
 ## 2014-2015
 
diff --git a/doc/tips/using_box.com_as_a_special_remote.mdwn b/doc/tips/using_box.com_as_a_special_remote.mdwn
index 149d1f824..2edd200b1 100644
--- a/doc/tips/using_box.com_as_a_special_remote.mdwn
+++ b/doc/tips/using_box.com_as_a_special_remote.mdwn
@@ -42,7 +42,7 @@ using the webdav special remote.
 * Create `~/.davfs2/secrets`. This file contains your Box.com login and password.
   Your login is probably the email address you signed up with.
 
-        echo "/media/box.com joey@kitenet.net mypassword" > ~/.davfs2/secrets
+        echo "/media/box.com id@joeyh.name mypassword" > ~/.davfs2/secrets
         chmod 600 ~/.davfs2/secrets
 
 * Now you should be able to mount Box, as a non-root user:
diff --git a/doc/users/joey.mdwn b/doc/users/joey.mdwn
index 306e1cc76..2180dd64f 100644
--- a/doc/users/joey.mdwn
+++ b/doc/users/joey.mdwn
@@ -1,2 +1,2 @@
-Joey Hess   
-
+Joey Hess   
+
diff --git a/git-annex.cabal b/git-annex.cabal
index 17d3131de..b4d3e03cd 100644
--- a/git-annex.cabal
+++ b/git-annex.cabal
@@ -2,7 +2,7 @@ Name: git-annex
 Version: 5.20150113
 Cabal-Version: >= 1.8
 License: GPL-3
-Maintainer: Joey Hess 
+Maintainer: Joey Hess 
 Author: Joey Hess
 Stability: Stable
 Copyright: 2010-2014 Joey Hess
diff --git a/git-annex.hs b/git-annex.hs
index f2005e13e..cdaa75434 100644
--- a/git-annex.hs
+++ b/git-annex.hs
@@ -1,6 +1,6 @@
 {- git-annex main program dispatch
  -
- - Copyright 2010-2014 Joey Hess 
+ - Copyright 2010-2014 Joey Hess 
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
diff --git a/git-union-merge.hs b/git-union-merge.hs
index 0e4cd644c..31c71ba72 100644
--- a/git-union-merge.hs
+++ b/git-union-merge.hs
@@ -1,6 +1,6 @@
 {- git-union-merge program
  -
- - Copyright 2011 Joey Hess 
+ - Copyright 2011 Joey Hess 
  -
  - Licensed under the GNU GPL version 3 or higher.
  -}
-- 
cgit v1.2.3


From 329267cb2b11da52956a86d9caec5225251a5ac1 Mon Sep 17 00:00:00 2001
From: Joey Hess 
Date: Thu, 12 Feb 2015 15:33:05 -0400
Subject: avoid unncessary IO

---
 Git/Config.hs            |  7 +++----
 Git/Construct.hs         | 15 +++++++--------
 Git/CurrentRepo.hs       |  4 ++--
 Remote/BitTorrent.hs     |  2 +-
 Remote/Helper/Special.hs |  2 +-
 Remote/Web.hs            |  2 +-
 6 files changed, 15 insertions(+), 17 deletions(-)

(limited to 'Remote/Helper/Special.hs')

diff --git a/Git/Config.hs b/Git/Config.hs
index 15109319a..44e0ad9a9 100644
--- a/Git/Config.hs
+++ b/Git/Config.hs
@@ -66,10 +66,9 @@ global = do
 	home <- myHomeDir
 	ifM (doesFileExist $ home  ".gitconfig")
 		( do
-			repo <- Git.Construct.fromUnknown
-			repo' <- withHandle StdoutHandle createProcessSuccess p $
-				hRead repo
-			return $ Just repo'
+			repo <- withHandle StdoutHandle createProcessSuccess p $
+				hRead (Git.Construct.fromUnknown)
+			return $ Just repo
 		, return Nothing
 		)
   where
diff --git a/Git/Construct.hs b/Git/Construct.hs
index a0632a223..5b206054b 100644
--- a/Git/Construct.hs
+++ b/Git/Construct.hs
@@ -19,8 +19,8 @@ module Git.Construct (
 	fromRemotes,
 	fromRemoteLocation,
 	repoAbsPath,
-	newFrom,
 	checkForRepo,
+	newFrom,
 ) where
 
 #ifndef mingw32_HOST_OS
@@ -48,7 +48,7 @@ fromCwd = getCurrentDirectory >>= seekUp
 			Nothing -> case upFrom dir of
 				Nothing -> return Nothing
 				Just d -> seekUp d
-			Just loc -> Just <$> newFrom loc
+			Just loc -> pure $ Just $ newFrom loc
 
 {- Local Repo constructor, accepts a relative or absolute path. -}
 fromPath :: FilePath -> IO Repo
@@ -62,7 +62,7 @@ fromAbsPath dir
 	| otherwise =
 		error $ "internal error, " ++ dir ++ " is not absolute"
   where
-	ret = newFrom . LocalUnknown
+	ret = pure . newFrom . LocalUnknown
 	{- Git always looks for "dir.git" in preference to
 	 - to "dir", even if dir ends in a "/". -}
 	canondir = dropTrailingPathSeparator dir
@@ -90,13 +90,13 @@ fromUrl url
 fromUrlStrict :: String -> IO Repo
 fromUrlStrict url
 	| startswith "file://" url = fromAbsPath $ unEscapeString $ uriPath u
-	| otherwise = newFrom $ Url u
+	| otherwise = pure $ newFrom $ Url u
   where
 	u = fromMaybe bad $ parseURI url
 	bad = error $ "bad url " ++ url
 
 {- Creates a repo that has an unknown location. -}
-fromUnknown :: IO Repo
+fromUnknown :: Repo
 fromUnknown = newFrom Unknown
 
 {- Converts a local Repo into a remote repo, using the reference repo
@@ -223,8 +223,8 @@ checkForRepo dir =
 		gitdirprefix = "gitdir: "
 	gitSignature file = doesFileExist $ dir  file
 
-newFrom :: RepoLocation -> IO Repo
-newFrom l = return Repo
+newFrom :: RepoLocation -> Repo
+newFrom l = Repo
 	{ location = l
 	, config = M.empty
 	, fullconfig = M.empty
@@ -234,4 +234,3 @@ newFrom l = return Repo
 	, gitGlobalOpts = []
 	}
 
-
diff --git a/Git/CurrentRepo.hs b/Git/CurrentRepo.hs
index 9de00034b..dab4ad21b 100644
--- a/Git/CurrentRepo.hs
+++ b/Git/CurrentRepo.hs
@@ -50,8 +50,8 @@ get = do
 	configure (Just d) _ = do
 		absd <- absPath d
 		curr <- getCurrentDirectory
-		r <- newFrom $ Local { gitdir = absd, worktree = Just curr }
-		Git.Config.read r
+		Git.Config.read $ newFrom $
+			Local { gitdir = absd, worktree = Just curr }
 	configure Nothing Nothing = error "Not in a git repository."
 
 	addworktree w r = changelocation r $
diff --git a/Remote/BitTorrent.hs b/Remote/BitTorrent.hs
index 0ecf3ef25..fe49d023a 100644
--- a/Remote/BitTorrent.hs
+++ b/Remote/BitTorrent.hs
@@ -44,7 +44,7 @@ remote = RemoteType {
 -- There is only one bittorrent remote, and it always exists.
 list :: Annex [Git.Repo]
 list = do
-	r <- liftIO $ Git.Construct.remoteNamed "bittorrent" Git.Construct.fromUnknown
+	r <- liftIO $ Git.Construct.remoteNamed "bittorrent" (pure Git.Construct.fromUnknown)
 	return [r]
 
 gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs
index bdf0ead22..9f219e8b1 100644
--- a/Remote/Helper/Special.hs
+++ b/Remote/Helper/Special.hs
@@ -59,7 +59,7 @@ findSpecialRemotes s = do
 	liftIO $ mapM construct $ remotepairs m
   where
 	remotepairs = M.toList . M.filterWithKey match
-	construct (k,_) = Git.Construct.remoteNamedFromKey k Git.Construct.fromUnknown
+	construct (k,_) = Git.Construct.remoteNamedFromKey k (pure Git.Construct.fromUnknown)
 	match k _ = startswith "remote." k && endswith (".annex-"++s) k
 
 {- Sets up configuration for a special remote in .git/config. -}
diff --git a/Remote/Web.hs b/Remote/Web.hs
index 17e3830a8..a4a484ca3 100644
--- a/Remote/Web.hs
+++ b/Remote/Web.hs
@@ -38,7 +38,7 @@ remote = RemoteType {
 -- a new release to the survivors by carrier pigeon.)
 list :: Annex [Git.Repo]
 list = do
-	r <- liftIO $ Git.Construct.remoteNamed "web" Git.Construct.fromUnknown
+	r <- liftIO $ Git.Construct.remoteNamed "web" (pure Git.Construct.fromUnknown)
 	return [r]
 
 gen :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
-- 
cgit v1.2.3