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