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.
This commit is contained in:
Joey Hess 2014-10-09 14:53:13 -04:00
parent 8f69d55f03
commit 7b50b3c057
131 changed files with 242 additions and 242 deletions

View file

@ -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.

View file

@ -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

View file

@ -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. -}

View file

@ -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

View file

@ -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

View file

@ -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

View file

@ -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))

View file

@ -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

View file

@ -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

View file

@ -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

View file

@ -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"

View file

@ -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

View file

@ -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

View file

@ -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"

View file

@ -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

View file

@ -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)

View file

@ -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

View file

@ -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

View file

@ -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]

View file

@ -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