where indentation
This commit is contained in:
parent
f0dd6d00d1
commit
ebd576ebcb
30 changed files with 804 additions and 812 deletions
|
@ -48,8 +48,7 @@ passthruOptions = map odate ["since", "after", "until", "before"] ++
|
|||
"limit number of logs displayed"
|
||||
]
|
||||
where
|
||||
odate n = Option.field [] n paramDate $
|
||||
"show log " ++ n ++ " date"
|
||||
odate n = Option.field [] n paramDate $ "show log " ++ n ++ " date"
|
||||
|
||||
gourceOption :: Option
|
||||
gourceOption = Option.flag [] "gource" "format output for gource"
|
||||
|
|
|
@ -69,8 +69,7 @@ drawMap rs umap ts = Dot.graph $ repos ++ trusted ++ others
|
|||
others = map (unreachable . uuidnode) $
|
||||
filter (`notElem` ruuids) (M.keys umap)
|
||||
trusted = map (trustworthy . uuidnode) ts
|
||||
uuidnode u = Dot.graphNode (fromUUID u) $
|
||||
M.findWithDefault "" u umap
|
||||
uuidnode u = Dot.graphNode (fromUUID u) $ M.findWithDefault "" u umap
|
||||
|
||||
hostname :: Git.Repo -> String
|
||||
hostname r
|
||||
|
@ -165,7 +164,6 @@ same a b
|
|||
| both Git.repoIsUrl && neither Git.repoIsSsh = matching show
|
||||
| neither Git.repoIsSsh = matching Git.repoPath
|
||||
| otherwise = False
|
||||
|
||||
where
|
||||
matching t = t a == t b
|
||||
both t = t a && t b
|
||||
|
@ -204,8 +202,7 @@ tryScan r
|
|||
where
|
||||
p = proc cmd $ toCommand params
|
||||
|
||||
configlist =
|
||||
onRemote r (pipedconfig, Nothing) "configlist" [] []
|
||||
configlist = onRemote r (pipedconfig, Nothing) "configlist" [] []
|
||||
manualconfiglist = do
|
||||
sshparams <- sshToRepo r [Param sshcmd]
|
||||
liftIO $ pipedconfig "ssh" sshparams
|
||||
|
|
|
@ -122,6 +122,7 @@ fromStart src move file key
|
|||
go = stopUnless (fromOk src key) $ do
|
||||
showMoveAction move file
|
||||
next $ fromPerform src move key file
|
||||
|
||||
fromOk :: Remote -> Key -> Annex Bool
|
||||
fromOk src key
|
||||
| Remote.hasKeyCheap src =
|
||||
|
@ -132,6 +133,7 @@ fromOk src key
|
|||
u <- getUUID
|
||||
remotes <- Remote.keyPossibilities key
|
||||
return $ u /= Remote.uuid src && elem src remotes
|
||||
|
||||
fromPerform :: Remote -> Bool -> Key -> FilePath -> CommandPerform
|
||||
fromPerform src move key file = moveLock move key $
|
||||
ifM (inAnnex key)
|
||||
|
|
|
@ -202,8 +202,8 @@ disk_size = stat "available local disk space" $ json id $ lift $
|
|||
, "(+" ++ roughSize storageUnits False reserve
|
||||
, "reserved)"
|
||||
]
|
||||
|
||||
calcfree _ _ = "unknown"
|
||||
|
||||
nonneg x
|
||||
| x >= 0 = x
|
||||
| otherwise = 0
|
||||
|
@ -280,8 +280,7 @@ staleSize label dirspec = go =<< lift (Command.Unused.staleKeys dirspec)
|
|||
keysizes keys = map (fromIntegral . fileSize) <$> stats keys
|
||||
stats keys = do
|
||||
dir <- lift $ fromRepo dirspec
|
||||
liftIO $ forM keys $ \k ->
|
||||
getFileStatus (dir </> keyFile k)
|
||||
liftIO $ forM keys $ \k -> getFileStatus (dir </> keyFile k)
|
||||
|
||||
aside :: String -> String
|
||||
aside s = " (" ++ s ++ ")"
|
||||
|
|
|
@ -83,8 +83,7 @@ checkRemoteUnused name = go =<< fromJust <$> Remote.byName (Just name)
|
|||
showAction "checking for unused data"
|
||||
_ <- check "" (remoteUnusedMsg r) (remoteunused r) 0
|
||||
next $ return True
|
||||
remoteunused r =
|
||||
excludeReferenced <=< loggedKeysFor $ Remote.uuid r
|
||||
remoteunused r = excludeReferenced <=< loggedKeysFor $ Remote.uuid r
|
||||
|
||||
check :: FilePath -> ([(Int, Key)] -> String) -> Annex [Key] -> Int -> Annex Int
|
||||
check file msg a c = do
|
||||
|
@ -249,7 +248,6 @@ withKeysReferenced' initial a = do
|
|||
!v' <- a k v
|
||||
go v' fs
|
||||
|
||||
|
||||
withKeysReferencedInGit :: (Key -> Annex ()) -> Annex ()
|
||||
withKeysReferencedInGit a = do
|
||||
rs <- relevantrefs <$> showref
|
||||
|
|
|
@ -118,10 +118,8 @@ genCfg cfg descs = unlines $ concat [intro, trust, groups, preferredcontent]
|
|||
|
||||
settings field desc showvals showdefaults = concat
|
||||
[ desc
|
||||
, concatMap showvals $
|
||||
sort $ map swap $ M.toList $ field cfg
|
||||
, concatMap (\u -> lcom $ showdefaults u) $
|
||||
missing field
|
||||
, concatMap showvals $ sort $ map swap $ M.toList $ field cfg
|
||||
, concatMap (\u -> lcom $ showdefaults u) $ missing field
|
||||
]
|
||||
|
||||
line setting u value =
|
||||
|
@ -153,8 +151,7 @@ parseCfg curcfg = go [] curcfg . lines
|
|||
(setting, rest) = separate isSpace l
|
||||
(r, value) = separate (== '=') rest
|
||||
value' = trimspace value
|
||||
u = reverse $ trimspace $
|
||||
reverse $ trimspace r
|
||||
u = reverse $ trimspace $ reverse $ trimspace r
|
||||
trimspace = dropWhile isSpace
|
||||
|
||||
handle cfg u setting value
|
||||
|
|
|
@ -126,9 +126,9 @@ firstRun = do
|
|||
dummydaemonize
|
||||
startAssistant True id $ Just $ sendurlback v
|
||||
sendurlback v url _htmlshim = putMVar v url
|
||||
|
||||
{- Set up the pid file in the new repo. -}
|
||||
dummydaemonize =
|
||||
liftIO . lockPidFile =<< fromRepo gitAnnexPidFile
|
||||
dummydaemonize = liftIO . lockPidFile =<< fromRepo gitAnnexPidFile
|
||||
|
||||
openBrowser :: Maybe FilePath -> FilePath -> IO ()
|
||||
openBrowser cmd htmlshim = go $ maybe runBrowser runCustomBrowser cmd
|
||||
|
|
Loading…
Reference in a new issue