summaryrefslogtreecommitdiff
path: root/Assistant
diff options
context:
space:
mode:
Diffstat (limited to 'Assistant')
-rw-r--r--Assistant/Alert.hs2
-rw-r--r--Assistant/Alert/Utility.hs2
-rw-r--r--Assistant/DaemonStatus.hs2
-rw-r--r--Assistant/DeleteRemote.hs2
-rw-r--r--Assistant/MakeRemote.hs2
-rw-r--r--Assistant/NetMessager.hs4
-rw-r--r--Assistant/Ssh.hs6
-rw-r--r--Assistant/Threads/Committer.hs6
-rw-r--r--Assistant/Threads/Cronner.hs8
-rw-r--r--Assistant/Threads/SanityChecker.hs2
-rw-r--r--Assistant/Threads/UpgradeWatcher.hs4
-rw-r--r--Assistant/Threads/Upgrader.hs2
-rw-r--r--Assistant/Threads/Watcher.hs6
-rw-r--r--Assistant/Threads/WebApp.hs2
-rw-r--r--Assistant/Threads/XMPPClient.hs2
-rw-r--r--Assistant/Threads/XMPPPusher.hs4
-rw-r--r--Assistant/TransferQueue.hs2
-rw-r--r--Assistant/Types/NetMessager.hs2
-rw-r--r--Assistant/XMPP.hs2
-rw-r--r--Assistant/XMPP/Git.hs10
20 files changed, 36 insertions, 36 deletions
diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs
index 745694f59..a41baa85f 100644
--- a/Assistant/Alert.hs
+++ b/Assistant/Alert.hs
@@ -145,7 +145,7 @@ syncResultAlert' succeeded failed = makeAlertFiller (not $ null succeeded) $
, alertHeader = Just $ tenseWords msg
}
where
- msg
+ msg
| null succeeded = ["Failed to sync with", showRemotes failed]
| null failed = ["Synced with", showRemotes succeeded]
| otherwise =
diff --git a/Assistant/Alert/Utility.hs b/Assistant/Alert/Utility.hs
index be631e999..ea1280dac 100644
--- a/Assistant/Alert/Utility.hs
+++ b/Assistant/Alert/Utility.hs
@@ -119,7 +119,7 @@ mergeAlert i al m = maybe updatePrune updateCombine (alertCombiner al)
where
bloat = M.size m' - maxAlerts
pruneold l =
- let (f, rest) = partition (\(_, a) -> isFiller a) l
+ let (f, rest) = partition (\(_, a) -> isFiller a) l
in drop bloat f ++ rest
updatePrune = pruneBloat $ M.filterWithKey pruneSame $
M.insertWith' const i al m
diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs
index 35f8fc856..3edc2c174 100644
--- a/Assistant/DaemonStatus.hs
+++ b/Assistant/DaemonStatus.hs
@@ -65,7 +65,7 @@ calcSyncRemotes = do
, syncingToCloudRemote = any iscloud syncdata
}
where
- iscloud r = not (Remote.readonly r) && Remote.availability r == Remote.GloballyAvailable
+ iscloud r = not (Remote.readonly r) && Remote.availability r == Remote.GloballyAvailable
{- Updates the syncRemotes list from the list of all remotes in Annex state. -}
updateSyncRemotes :: Assistant ()
diff --git a/Assistant/DeleteRemote.hs b/Assistant/DeleteRemote.hs
index cc05786e4..a900753a7 100644
--- a/Assistant/DeleteRemote.hs
+++ b/Assistant/DeleteRemote.hs
@@ -62,7 +62,7 @@ removableRemote urlrenderer uuid = do
<$> liftAnnex (Remote.remoteFromUUID uuid)
mapM_ (queueremaining r) keys
where
- queueremaining r k =
+ queueremaining r k =
queueTransferWhenSmall "remaining object in unwanted remote"
Nothing (Transfer Download uuid k) r
{- Scanning for keys can take a long time; do not tie up
diff --git a/Assistant/MakeRemote.hs b/Assistant/MakeRemote.hs
index 967a4d41d..d244a7729 100644
--- a/Assistant/MakeRemote.hs
+++ b/Assistant/MakeRemote.hs
@@ -48,7 +48,7 @@ makeRsyncRemote :: RemoteName -> String -> Annex String
makeRsyncRemote name location = makeRemote name location $ const $ void $
go =<< Command.InitRemote.findExisting name
where
- go Nothing = setupSpecialRemote name Rsync.remote config Nothing
+ go Nothing = setupSpecialRemote name Rsync.remote config Nothing
(Nothing, Command.InitRemote.newConfig name)
go (Just (u, c)) = setupSpecialRemote name Rsync.remote config Nothing
(Just u, c)
diff --git a/Assistant/NetMessager.hs b/Assistant/NetMessager.hs
index acb18b648..f042b4e4e 100644
--- a/Assistant/NetMessager.hs
+++ b/Assistant/NetMessager.hs
@@ -80,7 +80,7 @@ checkImportantNetMessages (storedclient, sentclient) = go <<~ netMessager
queuePushInitiation :: NetMessage -> Assistant ()
queuePushInitiation msg@(Pushing clientid stage) = do
tv <- getPushInitiationQueue side
- liftIO $ atomically $ do
+ liftIO $ atomically $ do
r <- tryTakeTMVar tv
case r of
Nothing -> putTMVar tv [msg]
@@ -88,7 +88,7 @@ queuePushInitiation msg@(Pushing clientid stage) = do
let !l' = msg : filter differentclient l
putTMVar tv l'
where
- side = pushDestinationSide stage
+ side = pushDestinationSide stage
differentclient (Pushing cid _) = cid /= clientid
differentclient _ = True
queuePushInitiation _ = noop
diff --git a/Assistant/Ssh.hs b/Assistant/Ssh.hs
index e1a78cd00..7b82f4624 100644
--- a/Assistant/Ssh.hs
+++ b/Assistant/Ssh.hs
@@ -92,7 +92,7 @@ parseSshUrl u
, sshCapabilities = []
}
where
- (user, host) = if '@' `elem` userhost
+ (user, host) = if '@' `elem` userhost
then separate (== '@') userhost
else ("", userhost)
fromrsync s
@@ -260,7 +260,7 @@ setupSshKeyPair sshkeypair sshdata = do
fixSshKeyPairIdentitiesOnly :: IO ()
fixSshKeyPairIdentitiesOnly = changeUserSshConfig $ unlines . go [] . lines
where
- go c [] = reverse c
+ go c [] = reverse c
go c (l:[])
| all (`isInfixOf` l) indicators = go (fixedline l:l:c) []
| otherwise = go (l:c) []
@@ -268,7 +268,7 @@ fixSshKeyPairIdentitiesOnly = changeUserSshConfig $ unlines . go [] . lines
| all (`isInfixOf` l) indicators && not ("IdentitiesOnly" `isInfixOf` next) =
go (fixedline l:l:c) (next:rest)
| otherwise = go (l:c) (next:rest)
- indicators = ["IdentityFile", "key.git-annex"]
+ indicators = ["IdentityFile", "key.git-annex"]
fixedline tmpl = takeWhile isSpace tmpl ++ "IdentitiesOnly yes"
{- Add StrictHostKeyChecking to any ssh config stanzas that were written
diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs
index 4a47a9e2c..47c2aa4aa 100644
--- a/Assistant/Threads/Committer.hs
+++ b/Assistant/Threads/Committer.hs
@@ -164,8 +164,8 @@ waitChangeTime a = waitchanges 0
-}
aftermaxcommit oldchanges = loop (30 :: Int)
where
- loop 0 = continue oldchanges
- loop n = do
+ loop 0 = continue oldchanges
+ loop n = do
liftAnnex noop -- ensure Annex state is free
liftIO $ threadDelaySeconds (Seconds 1)
changes <- getAnyChanges
@@ -301,7 +301,7 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
add change@(InProcessAddChange { keySource = ks }) =
catchDefaultIO Nothing <~> doadd
where
- doadd = sanitycheck ks $ do
+ doadd = sanitycheck ks $ do
(mkey, mcache) <- liftAnnex $ do
showStart "add" $ keyFilename ks
Command.Add.ingest $ Just ks
diff --git a/Assistant/Threads/Cronner.hs b/Assistant/Threads/Cronner.hs
index 0fe7f58f4..6dc6f4c6b 100644
--- a/Assistant/Threads/Cronner.hs
+++ b/Assistant/Threads/Cronner.hs
@@ -87,7 +87,7 @@ cronnerThread urlrenderer = namedThreadUnchecked "Cronner" $ do
liftIO $ waitNotification h
debug ["reloading changed activities"]
go h amap' nmap'
- startactivities as lastruntimes = forM as $ \activity ->
+ startactivities as lastruntimes = forM as $ \activity ->
case connectActivityUUID activity of
Nothing -> do
runner <- asIO2 (sleepingActivityThread urlrenderer)
@@ -108,8 +108,8 @@ cronnerThread urlrenderer = namedThreadUnchecked "Cronner" $ do
sleepingActivityThread :: UrlRenderer -> ScheduledActivity -> Maybe LocalTime -> Assistant ()
sleepingActivityThread urlrenderer activity lasttime = go lasttime =<< getnexttime lasttime
where
- getnexttime = liftIO . nextTime schedule
- go _ Nothing = debug ["no scheduled events left for", desc]
+ getnexttime = liftIO . nextTime schedule
+ go _ Nothing = debug ["no scheduled events left for", desc]
go l (Just (NextTimeExactly t)) = waitrun l t Nothing
go l (Just (NextTimeWindow windowstart windowend)) =
waitrun l windowstart (Just windowend)
@@ -129,7 +129,7 @@ sleepingActivityThread urlrenderer activity lasttime = go lasttime =<< getnextti
go l =<< getnexttime l
else run nowt
where
- tolate nowt tz = case mmaxt of
+ tolate nowt tz = case mmaxt of
Just maxt -> nowt > maxt
-- allow the job to start 10 minutes late
Nothing ->diffUTCTime
diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs
index 3371f212f..9fd963a69 100644
--- a/Assistant/Threads/SanityChecker.hs
+++ b/Assistant/Threads/SanityChecker.hs
@@ -258,7 +258,7 @@ checkOldUnused :: UrlRenderer -> Assistant ()
checkOldUnused urlrenderer = go =<< annexExpireUnused <$> liftAnnex Annex.getGitConfig
where
go (Just Nothing) = noop
- go (Just (Just expireunused)) = expireUnused (Just expireunused)
+ go (Just (Just expireunused)) = expireUnused (Just expireunused)
go Nothing = maybe noop prompt =<< describeUnusedWhenBig
prompt msg =
diff --git a/Assistant/Threads/UpgradeWatcher.hs b/Assistant/Threads/UpgradeWatcher.hs
index ffad09d3d..431e6f339 100644
--- a/Assistant/Threads/UpgradeWatcher.hs
+++ b/Assistant/Threads/UpgradeWatcher.hs
@@ -51,9 +51,9 @@ upgradeWatcherThread urlrenderer = namedThread "UpgradeWatcher" $ do
let depth = length (splitPath dir) + 1
let nosubdirs f = length (splitPath f) == depth
void $ liftIO $ watchDir dir nosubdirs False hooks (startup mvar)
- -- Ignore bogus events generated during the startup scan.
+ -- Ignore bogus events generated during the startup scan.
-- We ask the watcher to not generate them, but just to be safe..
- startup mvar scanner = do
+ startup mvar scanner = do
r <- scanner
void $ swapMVar mvar Started
return r
diff --git a/Assistant/Threads/Upgrader.hs b/Assistant/Threads/Upgrader.hs
index 637c82a7d..100c15414 100644
--- a/Assistant/Threads/Upgrader.hs
+++ b/Assistant/Threads/Upgrader.hs
@@ -39,7 +39,7 @@ upgraderThread urlrenderer = namedThread "Upgrader" $
h <- liftIO . newNotificationHandle False . networkConnectedNotifier =<< getDaemonStatus
go h =<< liftIO getCurrentTime
where
- {- Wait for a network connection event. Then see if it's been
+ {- Wait for a network connection event. Then see if it's been
- half a day since the last upgrade check. If so, proceed with
- check. -}
go h lastchecked = do
diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs
index fe9a95471..8482de895 100644
--- a/Assistant/Threads/Watcher.hs
+++ b/Assistant/Threads/Watcher.hs
@@ -192,7 +192,7 @@ runHandler handler file filestatus = void $ do
liftAnnex Annex.Queue.flushWhenFull
recordChange change
where
- normalize f
+ normalize f
| "./" `isPrefixOf` file = drop 2 f
| otherwise = f
@@ -246,7 +246,7 @@ onAddDirect symlinkssupported matcher file fs = do
debug ["add direct", file]
add matcher file
where
- {- On a filesystem without symlinks, we'll get changes for regular
+ {- On a filesystem without symlinks, we'll get changes for regular
- files that git uses to stand-in for symlinks. Detect when
- this happens, and stage the symlink, rather than annexing the
- file. -}
@@ -276,7 +276,7 @@ onAddSymlink isdirect file filestatus = unlessIgnored file $ do
onAddSymlink' :: Maybe String -> Maybe Key -> Bool -> Handler
onAddSymlink' linktarget mk isdirect file filestatus = go mk
where
- go (Just key) = do
+ go (Just key) = do
when isdirect $
liftAnnex $ void $ addAssociatedFile key file
link <- liftAnnex $ inRepo $ gitAnnexLink file key
diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs
index 416c07874..b22b54a8d 100644
--- a/Assistant/Threads/WebApp.hs
+++ b/Assistant/Threads/WebApp.hs
@@ -97,7 +97,7 @@ webAppThread assistantdata urlrenderer noannex cannotrun postfirstrun listenhost
urlfile <- getAnnex' $ fromRepo gitAnnexUrlFile
go tlssettings addr webapp htmlshim (Just urlfile)
where
- -- The webapp thread does not wait for the startupSanityCheckThread
+ -- The webapp thread does not wait for the startupSanityCheckThread
-- to finish, so that the user interface remains responsive while
-- that's going on.
thread = namedThreadUnchecked "WebApp"
diff --git a/Assistant/Threads/XMPPClient.hs b/Assistant/Threads/XMPPClient.hs
index 2f70b508f..8ce99eac6 100644
--- a/Assistant/Threads/XMPPClient.hs
+++ b/Assistant/Threads/XMPPClient.hs
@@ -131,7 +131,7 @@ xmppClient urlrenderer d creds xmppuuid =
{- XEP-0199 says that the server will respond with either
- a ping response or an error message. Either will
- cause traffic, so good enough. -}
- pingstanza = xmppPing selfjid
+ pingstanza = xmppPing selfjid
handlemsg selfjid (PresenceMessage p) = do
void $ inAssistant $
diff --git a/Assistant/Threads/XMPPPusher.hs b/Assistant/Threads/XMPPPusher.hs
index 30c91c7f0..35c76ebf1 100644
--- a/Assistant/Threads/XMPPPusher.hs
+++ b/Assistant/Threads/XMPPPusher.hs
@@ -34,7 +34,7 @@ xmppReceivePackThread = pusherThread "XMPPReceivePack" ReceivePack
pusherThread :: String -> PushSide -> UrlRenderer -> NamedThread
pusherThread threadname side urlrenderer = namedThread threadname $ go Nothing
where
- go lastpushedto = do
+ go lastpushedto = do
msg <- waitPushInitiation side $ selectNextPush lastpushedto
debug ["started running push", logNetMessage msg]
@@ -78,4 +78,4 @@ selectNextPush lastpushedto l = go [] l
(Pushing clientid _)
| Just clientid /= lastpushedto -> (m, rejected ++ ms)
_ -> go (m:rejected) ms
- go [] [] = undefined
+ go [] [] = undefined
diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs
index 93c982224..d138e16ef 100644
--- a/Assistant/TransferQueue.hs
+++ b/Assistant/TransferQueue.hs
@@ -92,7 +92,7 @@ queueTransfersMatching matching reason schedule k f direction
filterM (wantSend True (Just k) f . Remote.uuid) $
filter (\r -> not (inset s r || Remote.readonly r)) rs
where
- locs = S.fromList <$> Remote.keyLocations k
+ locs = S.fromList <$> Remote.keyLocations k
inset s r = S.member (Remote.uuid r) s
gentransfer r = Transfer
{ transferDirection = direction
diff --git a/Assistant/Types/NetMessager.hs b/Assistant/Types/NetMessager.hs
index 5ae987a61..f5ad85b4a 100644
--- a/Assistant/Types/NetMessager.hs
+++ b/Assistant/Types/NetMessager.hs
@@ -85,7 +85,7 @@ logNetMessage (Pushing c stage) = show $ Pushing (logClientID c) $
SendPackOutput n _ -> SendPackOutput n elided
s -> s
where
- elided = T.encodeUtf8 $ T.pack "<elided>"
+ elided = T.encodeUtf8 $ T.pack "<elided>"
logNetMessage (PairingNotification stage c uuid) =
show $ PairingNotification stage (logClientID c) uuid
logNetMessage m = show m
diff --git a/Assistant/XMPP.hs b/Assistant/XMPP.hs
index e74705021..cc0343abf 100644
--- a/Assistant/XMPP.hs
+++ b/Assistant/XMPP.hs
@@ -195,7 +195,7 @@ decodeMessage m = decode =<< gitAnnexTagInfo m
<*> a i
gen c i = c . toUUID <$> headMaybe (words (T.unpack (tagValue i)))
seqgen c i = do
- packet <- decodeTagContent $ tagElement i
+ packet <- decodeTagContent $ tagElement i
let seqnum = fromMaybe 0 $ readish $ T.unpack $ tagValue i
return $ c seqnum packet
shasgen c i = do
diff --git a/Assistant/XMPP/Git.hs b/Assistant/XMPP/Git.hs
index 19050c7d0..868fe6609 100644
--- a/Assistant/XMPP/Git.hs
+++ b/Assistant/XMPP/Git.hs
@@ -152,7 +152,7 @@ xmppPush cid gitpush = do
fromxmpp outh controlh = withPushMessagesInSequence cid SendPack handlemsg
where
- handlemsg (Just (Pushing _ (ReceivePackOutput _ b))) =
+ handlemsg (Just (Pushing _ (ReceivePackOutput _ b))) =
liftIO $ writeChunk outh b
handlemsg (Just (Pushing _ (ReceivePackDone exitcode))) =
liftIO $ do
@@ -266,7 +266,7 @@ xmppReceivePack cid = do
relaytoxmpp seqnum' outh
relayfromxmpp inh = withPushMessagesInSequence cid ReceivePack handlemsg
where
- handlemsg (Just (Pushing _ (SendPackOutput _ b))) =
+ handlemsg (Just (Pushing _ (SendPackOutput _ b))) =
liftIO $ writeChunk inh b
handlemsg (Just _) = noop
handlemsg Nothing = do
@@ -337,7 +337,7 @@ handlePushNotice (Pushing cid (CanPush theiruuid shas)) =
, go
)
where
- go = do
+ go = do
u <- liftAnnex getUUID
sendNetMessage $ Pushing cid (PushRequest u)
haveall l = liftAnnex $ not <$> anyM donthave l
@@ -359,9 +359,9 @@ writeChunk h b = do
withPushMessagesInSequence :: ClientID -> PushSide -> (Maybe NetMessage -> Assistant ()) -> Assistant ()
withPushMessagesInSequence cid side a = loop 0
where
- loop seqnum = do
+ loop seqnum = do
m <- timeout xmppTimeout <~> waitInbox cid side
- let go s = a m >> loop s
+ let go s = a m >> loop s
let next = seqnum + 1
case extractSequence =<< m of
Just seqnum'