finished where indentation changes
This commit is contained in:
parent
b77290cecc
commit
f87a781aa6
68 changed files with 1619 additions and 1628 deletions
|
@ -175,8 +175,7 @@ get' staleok file = fromjournal =<< getJournalFile file
|
|||
| otherwise = do
|
||||
update
|
||||
frombranch
|
||||
frombranch = withIndex $
|
||||
L.unpack <$> catFile fullname file
|
||||
frombranch = withIndex $ L.unpack <$> catFile fullname file
|
||||
|
||||
{- Applies a function to modifiy the content of a file.
|
||||
-
|
||||
|
|
|
@ -101,10 +101,12 @@ localToUrl reference r
|
|||
| repoIsUrl r = r
|
||||
| otherwise = r { location = Url $ fromJust $ parseURI absurl }
|
||||
where
|
||||
absurl =
|
||||
Url.scheme reference ++ "//" ++
|
||||
Url.authority reference ++
|
||||
repoPath r
|
||||
absurl = concat
|
||||
[ Url.scheme reference
|
||||
, "//"
|
||||
, Url.authority reference
|
||||
, repoPath r
|
||||
]
|
||||
|
||||
{- Calculates a list of a repo's configured remotes, by parsing its config. -}
|
||||
fromRemotes :: Repo -> IO [Repo]
|
||||
|
@ -127,8 +129,7 @@ remoteNamed n constructor = do
|
|||
remoteNamedFromKey :: String -> IO Repo -> IO Repo
|
||||
remoteNamedFromKey k = remoteNamed basename
|
||||
where
|
||||
basename = join "." $ reverse $ drop 1 $
|
||||
reverse $ drop 1 $ split "." k
|
||||
basename = join "." $ reverse $ drop 1 $ reverse $ drop 1 $ split "." k
|
||||
|
||||
{- Constructs a new Repo for one of a Repo's remotes using a given
|
||||
- location (ie, an url). -}
|
||||
|
@ -153,8 +154,7 @@ fromRemoteLocation s repo = gen $ calcloc s
|
|||
endswith suffix k &&
|
||||
startswith v l
|
||||
filterconfig f = filter f $
|
||||
concatMap splitconfigs $
|
||||
M.toList $ fullconfig repo
|
||||
concatMap splitconfigs $ M.toList $ fullconfig repo
|
||||
splitconfigs (k, vs) = map (\v -> (k, v)) vs
|
||||
(prefix, suffix) = ("url." , ".insteadof")
|
||||
urlstyle v = isURI v || ":" `isInfixOf` v && "//" `isInfixOf` v
|
||||
|
|
|
@ -52,8 +52,8 @@ matching :: Ref -> Repo -> IO [(Ref, Branch)]
|
|||
matching ref repo = map gen . lines <$>
|
||||
pipeReadStrict [Param "show-ref", Param $ show ref] repo
|
||||
where
|
||||
gen l = let (r, b) = separate (== ' ') l in
|
||||
(Ref r, Ref b)
|
||||
gen l = let (r, b) = separate (== ' ') l
|
||||
in (Ref r, Ref b)
|
||||
|
||||
{- List of (refs, branches) matching a given ref spec.
|
||||
- Duplicate refs are filtered out. -}
|
||||
|
|
|
@ -73,12 +73,12 @@ moveFile src dest = tryIO (rename src dest) >>= onrename
|
|||
where
|
||||
rethrow = throw e
|
||||
mv tmp _ = do
|
||||
ok <- boolSystem "mv" [Param "-f",
|
||||
Param src, Param tmp]
|
||||
ok <- boolSystem "mv" [Param "-f", Param src, Param tmp]
|
||||
unless ok $ do
|
||||
-- delete any partial
|
||||
_ <- tryIO $ removeFile tmp
|
||||
rethrow
|
||||
|
||||
isdir f = do
|
||||
r <- tryIO $ getFileStatus f
|
||||
case r of
|
||||
|
|
|
@ -118,9 +118,7 @@ decode_c s = unescape ("", s)
|
|||
handle (x:n1:n2:n3:rest)
|
||||
| isescape x && alloctal = (fromoctal, rest)
|
||||
where
|
||||
alloctal = isOctDigit n1 &&
|
||||
isOctDigit n2 &&
|
||||
isOctDigit n3
|
||||
alloctal = isOctDigit n1 && isOctDigit n2 && isOctDigit n3
|
||||
fromoctal = [chr $ readoctal [n1, n2, n3]]
|
||||
readoctal o = Prelude.read $ "0o" ++ o :: Int
|
||||
-- \C is used for a few special characters
|
||||
|
|
|
@ -117,8 +117,7 @@ userDesktopDir :: IO FilePath
|
|||
userDesktopDir = maybe fallback return =<< (parse <$> xdg_user_dir)
|
||||
where
|
||||
parse = maybe Nothing (headMaybe . lines)
|
||||
xdg_user_dir = catchMaybeIO $
|
||||
readProcess "xdg-user-dir" ["DESKTOP"]
|
||||
xdg_user_dir = catchMaybeIO $ readProcess "xdg-user-dir" ["DESKTOP"]
|
||||
fallback = xdgEnvHome "DESKTOP_DIR" "Desktop"
|
||||
|
||||
xdgEnvHome :: String -> String -> IO String
|
||||
|
|
|
@ -249,11 +249,9 @@ runHooks kq hooks = do
|
|||
withstatus change $ dispatchadd dirmap
|
||||
|
||||
dispatchadd dirmap change s
|
||||
| Files.isSymbolicLink s =
|
||||
callhook addSymlinkHook (Just s) change
|
||||
| Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change
|
||||
| Files.isDirectory s = recursiveadd dirmap change
|
||||
| Files.isRegularFile s =
|
||||
callhook addHook (Just s) change
|
||||
| Files.isRegularFile s = callhook addHook (Just s) change
|
||||
| otherwise = noop
|
||||
|
||||
recursiveadd dirmap change = do
|
||||
|
|
|
@ -62,8 +62,7 @@ parse s = bundle $ go [] $ lines s
|
|||
| otherwise = parsefail
|
||||
go _ _ = parsefail
|
||||
|
||||
parseprocess l =
|
||||
case splitnull l of
|
||||
parseprocess l = case splitnull l of
|
||||
[pid, 'c':cmdline, ""] ->
|
||||
case readish pid of
|
||||
(Just n) -> ProcessInfo n cmdline
|
||||
|
@ -71,8 +70,7 @@ parse s = bundle $ go [] $ lines s
|
|||
_ -> parsefail
|
||||
|
||||
parsefiles c [] = (c, [])
|
||||
parsefiles c (l:ls) =
|
||||
case splitnull l of
|
||||
parsefiles c (l:ls) = case splitnull l of
|
||||
['a':mode, 'n':file, ""] ->
|
||||
parsefiles ((file, parsemode mode):c) ls
|
||||
(('p':_):_) -> (c, l:ls)
|
||||
|
|
|
@ -18,5 +18,4 @@ import Control.Applicative
|
|||
getHostname :: IO (Maybe String)
|
||||
getHostname = catchMaybeIO uname_node
|
||||
where
|
||||
uname_node = takeWhile (/= '\n') <$>
|
||||
readProcess "uname" ["-n"]
|
||||
uname_node = takeWhile (/= '\n') <$> readProcess "uname" ["-n"]
|
||||
|
|
|
@ -71,9 +71,9 @@ touchBoth file atime mtime follow =
|
|||
r <- c_utimensat at_fdcwd f ptr flags
|
||||
when (r /= 0) $ throwErrno "touchBoth"
|
||||
where
|
||||
flags = if follow
|
||||
then 0
|
||||
else at_symlink_nofollow
|
||||
flags
|
||||
| follow = 0
|
||||
| otherwise = at_symlink_nofollow
|
||||
|
||||
#else
|
||||
#if 0
|
||||
|
@ -109,9 +109,9 @@ touchBoth file atime mtime follow =
|
|||
when (r /= 0) $
|
||||
throwErrno "touchBoth"
|
||||
where
|
||||
syscall = if follow
|
||||
then c_lutimes
|
||||
else c_utimes
|
||||
syscall
|
||||
| follow = c_lutimes
|
||||
| otherwise = c_utimes
|
||||
|
||||
#else
|
||||
#warning "utimensat and lutimes not available; building without symlink timestamp preservation support"
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue