summaryrefslogtreecommitdiff
path: root/Command
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2014-10-09 14:53:13 -0400
committerGravatar Joey Hess <joey@kitenet.net>2014-10-09 15:09:11 -0400
commita26b7127d4cc8b2a5e15ef662ab2793dbf9e7919 (patch)
tree95fb3ff9231bffe68f99b02d872ee308b40d0bc8 /Command
parentbe9989b76db21772118f8893ea00d22b6365d301 (diff)
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.
Diffstat (limited to 'Command')
-rw-r--r--Command/Add.hs6
-rw-r--r--Command/AddUrl.hs8
-rw-r--r--Command/ConfigList.hs2
-rw-r--r--Command/Copy.hs2
-rw-r--r--Command/EnableRemote.hs2
-rw-r--r--Command/Fsck.hs2
-rw-r--r--Command/FuzzTest.hs6
-rw-r--r--Command/Get.hs2
-rw-r--r--Command/Import.hs4
-rw-r--r--Command/ImportFeed.hs4
-rw-r--r--Command/Indirect.hs2
-rw-r--r--Command/Info.hs2
-rw-r--r--Command/Migrate.hs2
-rw-r--r--Command/RecvKey.hs4
-rw-r--r--Command/Schedule.hs2
-rw-r--r--Command/Sync.hs2
-rw-r--r--Command/TransferKeys.hs2
-rw-r--r--Command/Uninit.hs2
-rw-r--r--Command/Vicfg.hs4
-rw-r--r--Command/Wanted.hs2
20 files changed, 31 insertions, 31 deletions
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