finished where indentation changes

This commit is contained in:
Joey Hess 2012-12-13 00:24:19 -04:00
parent b77290cecc
commit f87a781aa6
68 changed files with 1619 additions and 1628 deletions

View file

@ -175,8 +175,7 @@ get' staleok file = fromjournal =<< getJournalFile file
| otherwise = do | otherwise = do
update update
frombranch frombranch
frombranch = withIndex $ frombranch = withIndex $ L.unpack <$> catFile fullname file
L.unpack <$> catFile fullname file
{- Applies a function to modifiy the content of a file. {- Applies a function to modifiy the content of a file.
- -

View file

@ -101,10 +101,12 @@ localToUrl reference r
| repoIsUrl r = r | repoIsUrl r = r
| otherwise = r { location = Url $ fromJust $ parseURI absurl } | otherwise = r { location = Url $ fromJust $ parseURI absurl }
where where
absurl = absurl = concat
Url.scheme reference ++ "//" ++ [ Url.scheme reference
Url.authority reference ++ , "//"
repoPath r , Url.authority reference
, repoPath r
]
{- Calculates a list of a repo's configured remotes, by parsing its config. -} {- Calculates a list of a repo's configured remotes, by parsing its config. -}
fromRemotes :: Repo -> IO [Repo] fromRemotes :: Repo -> IO [Repo]
@ -127,8 +129,7 @@ remoteNamed n constructor = do
remoteNamedFromKey :: String -> IO Repo -> IO Repo remoteNamedFromKey :: String -> IO Repo -> IO Repo
remoteNamedFromKey k = remoteNamed basename remoteNamedFromKey k = remoteNamed basename
where where
basename = join "." $ reverse $ drop 1 $ basename = join "." $ reverse $ drop 1 $ reverse $ drop 1 $ split "." k
reverse $ drop 1 $ split "." k
{- Constructs a new Repo for one of a Repo's remotes using a given {- Constructs a new Repo for one of a Repo's remotes using a given
- location (ie, an url). -} - location (ie, an url). -}
@ -153,8 +154,7 @@ fromRemoteLocation s repo = gen $ calcloc s
endswith suffix k && endswith suffix k &&
startswith v l startswith v l
filterconfig f = filter f $ filterconfig f = filter f $
concatMap splitconfigs $ concatMap splitconfigs $ M.toList $ fullconfig repo
M.toList $ fullconfig repo
splitconfigs (k, vs) = map (\v -> (k, v)) vs splitconfigs (k, vs) = map (\v -> (k, v)) vs
(prefix, suffix) = ("url." , ".insteadof") (prefix, suffix) = ("url." , ".insteadof")
urlstyle v = isURI v || ":" `isInfixOf` v && "//" `isInfixOf` v urlstyle v = isURI v || ":" `isInfixOf` v && "//" `isInfixOf` v

View file

@ -52,8 +52,8 @@ matching :: Ref -> Repo -> IO [(Ref, Branch)]
matching ref repo = map gen . lines <$> matching ref repo = map gen . lines <$>
pipeReadStrict [Param "show-ref", Param $ show ref] repo pipeReadStrict [Param "show-ref", Param $ show ref] repo
where where
gen l = let (r, b) = separate (== ' ') l in gen l = let (r, b) = separate (== ' ') l
(Ref r, Ref b) in (Ref r, Ref b)
{- List of (refs, branches) matching a given ref spec. {- List of (refs, branches) matching a given ref spec.
- Duplicate refs are filtered out. -} - Duplicate refs are filtered out. -}

View file

@ -73,12 +73,12 @@ moveFile src dest = tryIO (rename src dest) >>= onrename
where where
rethrow = throw e rethrow = throw e
mv tmp _ = do mv tmp _ = do
ok <- boolSystem "mv" [Param "-f", ok <- boolSystem "mv" [Param "-f", Param src, Param tmp]
Param src, Param tmp]
unless ok $ do unless ok $ do
-- delete any partial -- delete any partial
_ <- tryIO $ removeFile tmp _ <- tryIO $ removeFile tmp
rethrow rethrow
isdir f = do isdir f = do
r <- tryIO $ getFileStatus f r <- tryIO $ getFileStatus f
case r of case r of

View file

@ -118,9 +118,7 @@ decode_c s = unescape ("", s)
handle (x:n1:n2:n3:rest) handle (x:n1:n2:n3:rest)
| isescape x && alloctal = (fromoctal, rest) | isescape x && alloctal = (fromoctal, rest)
where where
alloctal = isOctDigit n1 && alloctal = isOctDigit n1 && isOctDigit n2 && isOctDigit n3
isOctDigit n2 &&
isOctDigit n3
fromoctal = [chr $ readoctal [n1, n2, n3]] fromoctal = [chr $ readoctal [n1, n2, n3]]
readoctal o = Prelude.read $ "0o" ++ o :: Int readoctal o = Prelude.read $ "0o" ++ o :: Int
-- \C is used for a few special characters -- \C is used for a few special characters

View file

@ -117,8 +117,7 @@ userDesktopDir :: IO FilePath
userDesktopDir = maybe fallback return =<< (parse <$> xdg_user_dir) userDesktopDir = maybe fallback return =<< (parse <$> xdg_user_dir)
where where
parse = maybe Nothing (headMaybe . lines) parse = maybe Nothing (headMaybe . lines)
xdg_user_dir = catchMaybeIO $ xdg_user_dir = catchMaybeIO $ readProcess "xdg-user-dir" ["DESKTOP"]
readProcess "xdg-user-dir" ["DESKTOP"]
fallback = xdgEnvHome "DESKTOP_DIR" "Desktop" fallback = xdgEnvHome "DESKTOP_DIR" "Desktop"
xdgEnvHome :: String -> String -> IO String xdgEnvHome :: String -> String -> IO String

View file

@ -249,11 +249,9 @@ runHooks kq hooks = do
withstatus change $ dispatchadd dirmap withstatus change $ dispatchadd dirmap
dispatchadd dirmap change s dispatchadd dirmap change s
| Files.isSymbolicLink s = | Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change
callhook addSymlinkHook (Just s) change
| Files.isDirectory s = recursiveadd dirmap change | Files.isDirectory s = recursiveadd dirmap change
| Files.isRegularFile s = | Files.isRegularFile s = callhook addHook (Just s) change
callhook addHook (Just s) change
| otherwise = noop | otherwise = noop
recursiveadd dirmap change = do recursiveadd dirmap change = do

View file

@ -62,8 +62,7 @@ parse s = bundle $ go [] $ lines s
| otherwise = parsefail | otherwise = parsefail
go _ _ = parsefail go _ _ = parsefail
parseprocess l = parseprocess l = case splitnull l of
case splitnull l of
[pid, 'c':cmdline, ""] -> [pid, 'c':cmdline, ""] ->
case readish pid of case readish pid of
(Just n) -> ProcessInfo n cmdline (Just n) -> ProcessInfo n cmdline
@ -71,8 +70,7 @@ parse s = bundle $ go [] $ lines s
_ -> parsefail _ -> parsefail
parsefiles c [] = (c, []) parsefiles c [] = (c, [])
parsefiles c (l:ls) = parsefiles c (l:ls) = case splitnull l of
case splitnull l of
['a':mode, 'n':file, ""] -> ['a':mode, 'n':file, ""] ->
parsefiles ((file, parsemode mode):c) ls parsefiles ((file, parsemode mode):c) ls
(('p':_):_) -> (c, l:ls) (('p':_):_) -> (c, l:ls)

View file

@ -18,5 +18,4 @@ import Control.Applicative
getHostname :: IO (Maybe String) getHostname :: IO (Maybe String)
getHostname = catchMaybeIO uname_node getHostname = catchMaybeIO uname_node
where where
uname_node = takeWhile (/= '\n') <$> uname_node = takeWhile (/= '\n') <$> readProcess "uname" ["-n"]
readProcess "uname" ["-n"]

View file

@ -71,9 +71,9 @@ touchBoth file atime mtime follow =
r <- c_utimensat at_fdcwd f ptr flags r <- c_utimensat at_fdcwd f ptr flags
when (r /= 0) $ throwErrno "touchBoth" when (r /= 0) $ throwErrno "touchBoth"
where where
flags = if follow flags
then 0 | follow = 0
else at_symlink_nofollow | otherwise = at_symlink_nofollow
#else #else
#if 0 #if 0
@ -109,9 +109,9 @@ touchBoth file atime mtime follow =
when (r /= 0) $ when (r /= 0) $
throwErrno "touchBoth" throwErrno "touchBoth"
where where
syscall = if follow syscall
then c_lutimes | follow = c_lutimes
else c_utimes | otherwise = c_utimes
#else #else
#warning "utimensat and lutimes not available; building without symlink timestamp preservation support" #warning "utimensat and lutimes not available; building without symlink timestamp preservation support"