git-annex/Assistant/Alert.hs

462 lines
14 KiB
Haskell
Raw Normal View History

2012-07-29 13:35:01 +00:00
{- git-annex assistant alerts
-
- Copyright 2012-2014 Joey Hess <id@joeyh.name>
2012-07-29 13:35:01 +00:00
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE OverloadedStrings, CPP, BangPatterns #-}
2012-07-29 13:35:01 +00:00
module Assistant.Alert where
import Common.Annex
2013-04-04 05:48:26 +00:00
import Assistant.Types.Alert
import Assistant.Alert.Utility
import qualified Remote
import Utility.Tense
2012-08-06 21:09:23 +00:00
import Logs.Transfer
import Types.Distribution
import Git.Types (RemoteName)
import Data.String
2013-04-04 05:48:26 +00:00
import qualified Data.Text as T
import qualified Control.Exception as E
2012-07-29 13:35:01 +00:00
2013-04-04 05:48:26 +00:00
#ifdef WITH_WEBAPP
import Assistant.DaemonStatus
import Assistant.WebApp.Types
2013-10-28 15:24:25 +00:00
import Assistant.WebApp (renderUrl)
2013-04-04 05:50:36 +00:00
import Yesod
2013-04-04 05:48:26 +00:00
#endif
2013-10-28 15:24:25 +00:00
import Assistant.Monad
import Assistant.Types.UrlRenderer
2013-04-04 05:48:26 +00:00
{- Makes a button for an alert that opens a Route.
-
- If autoclose is set, the button will close the alert it's
- attached to when clicked. -}
2013-04-04 05:48:26 +00:00
#ifdef WITH_WEBAPP
mkAlertButton :: Bool -> T.Text -> UrlRenderer -> Route WebApp -> Assistant AlertButton
mkAlertButton autoclose label urlrenderer route = do
2013-04-04 05:48:26 +00:00
close <- asIO1 removeAlert
url <- liftIO $ renderUrl urlrenderer route []
return $ AlertButton
{ buttonLabel = label
, buttonUrl = url
, buttonAction = if autoclose then Just close else Nothing
, buttonPrimary = True
}
2013-04-04 05:48:26 +00:00
#endif
2012-07-29 23:05:51 +00:00
2013-07-10 19:37:40 +00:00
renderData :: Alert -> TenseText
renderData = tenseWords . alertData
baseActivityAlert :: Alert
baseActivityAlert = Alert
{ alertClass = Activity
, alertHeader = Nothing
2013-07-10 19:37:40 +00:00
, alertMessageRender = renderData
2012-08-06 19:41:42 +00:00
, alertData = []
2013-07-10 19:37:40 +00:00
, alertCounter = 0
, alertBlockDisplay = False
, alertClosable = False
2012-07-29 23:05:51 +00:00
, alertPriority = Medium
, alertIcon = Just ActivityIcon
, alertCombiner = Nothing
, alertName = Nothing
, alertButtons = []
2012-07-29 13:35:01 +00:00
}
warningAlert :: String -> String -> Alert
warningAlert name msg = Alert
{ alertClass = Warning
, alertHeader = Just $ tenseWords ["warning"]
2013-07-10 19:37:40 +00:00
, alertMessageRender = renderData
, alertData = [UnTensed $ T.pack msg]
2013-07-10 19:37:40 +00:00
, alertCounter = 0
, alertBlockDisplay = True
, alertClosable = True
, alertPriority = High
, alertIcon = Just ErrorIcon
, alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertName = Just $ WarningAlert name
, alertButtons = []
}
2013-11-24 18:04:03 +00:00
errorAlert :: String -> [AlertButton] -> Alert
errorAlert msg buttons = Alert
{ alertClass = Error
2013-10-22 20:30:23 +00:00
, alertHeader = Nothing
, alertMessageRender = renderData
, alertData = [UnTensed $ T.pack msg]
, alertCounter = 0
, alertBlockDisplay = True
, alertClosable = True
, alertPriority = Pinned
, alertIcon = Just ErrorIcon
, alertCombiner = Nothing
, alertName = Nothing
2013-11-24 18:04:03 +00:00
, alertButtons = buttons
}
2012-08-06 19:41:42 +00:00
activityAlert :: Maybe TenseText -> [TenseChunk] -> Alert
activityAlert header dat = baseActivityAlert
{ alertHeader = header
2012-08-06 19:41:42 +00:00
, alertData = dat
}
startupScanAlert :: Alert
2012-09-13 04:57:52 +00:00
startupScanAlert = activityAlert Nothing
2012-08-06 19:41:42 +00:00
[Tensed "Performing" "Performed", "startup scan"]
{- Displayed when a shutdown is occurring, so will be seen after shutdown
- has happened. -}
shutdownAlert :: Alert
shutdownAlert = warningAlert "shutdown" "git-annex has been shut down"
2012-08-02 18:02:35 +00:00
commitAlert :: Alert
2012-09-13 04:57:52 +00:00
commitAlert = activityAlert Nothing
[Tensed "Committing" "Committed", "changes to git"]
showRemotes :: [RemoteName] -> TenseChunk
showRemotes = UnTensed . T.intercalate ", " . map T.pack
2012-08-02 18:02:35 +00:00
2012-08-06 21:09:23 +00:00
syncAlert :: [Remote] -> Alert
syncAlert = syncAlert' . map Remote.name
syncAlert' :: [RemoteName] -> Alert
syncAlert' rs = baseActivityAlert
{ alertName = Just SyncAlert
, alertHeader = Just $ tenseWords
2012-08-06 21:09:23 +00:00
[Tensed "Syncing" "Synced", "with", showRemotes rs]
2012-07-29 23:05:51 +00:00
, alertPriority = Low
, alertIcon = Just SyncIcon
2012-12-13 04:45:27 +00:00
}
syncResultAlert :: [Remote] -> [Remote] -> Alert
syncResultAlert succeeded failed = syncResultAlert'
(map Remote.name succeeded)
(map Remote.name failed)
syncResultAlert' :: [RemoteName] -> [RemoteName] -> Alert
syncResultAlert' succeeded failed = makeAlertFiller (not $ null succeeded) $
baseActivityAlert
{ alertName = Just SyncAlert
, alertHeader = Just $ tenseWords msg
}
where
msg
| null succeeded = ["Failed to sync with", showRemotes failed]
| null failed = ["Synced with", showRemotes succeeded]
| otherwise =
[ "Synced with", showRemotes succeeded
, "but not with", showRemotes failed
]
sanityCheckAlert :: Alert
sanityCheckAlert = activityAlert
(Just $ tenseWords [Tensed "Running" "Ran", "daily sanity check"])
2012-08-06 19:41:42 +00:00
["to make sure everything is ok."]
sanityCheckFixAlert :: String -> Alert
sanityCheckFixAlert msg = Alert
{ alertClass = Warning
, alertHeader = Just $ tenseWords ["Fixed a problem"]
2012-08-06 19:41:42 +00:00
, alertMessageRender = render
, alertData = [UnTensed $ T.pack msg]
2013-07-10 19:37:40 +00:00
, alertCounter = 0
, alertBlockDisplay = True
2012-07-29 23:05:51 +00:00
, alertPriority = High
, alertClosable = True
, alertIcon = Just ErrorIcon
, alertName = Just SanityCheckFixAlert
2012-08-06 19:41:42 +00:00
, alertCombiner = Just $ dataCombiner (++)
, alertButtons = []
}
2012-10-31 06:34:03 +00:00
where
2013-07-10 19:37:40 +00:00
render alert = tenseWords $ alerthead : alertData alert ++ [alertfoot]
2012-10-31 06:34:03 +00:00
alerthead = "The daily sanity check found and fixed a problem:"
alertfoot = "If these problems persist, consider filing a bug report."
fsckingAlert :: AlertButton -> Maybe Remote -> Alert
fsckingAlert button mr = baseActivityAlert
{ alertData = case mr of
Nothing -> [ UnTensed $ T.pack $ "Consistency check in progress" ]
Just r -> [ UnTensed $ T.pack $ "Consistency check of " ++ Remote.name r ++ " in progress"]
, alertButtons = [button]
}
showFscking :: UrlRenderer -> Maybe Remote -> IO (Either E.SomeException a) -> Assistant a
showFscking urlrenderer mr a = do
#ifdef WITH_WEBAPP
button <- mkAlertButton False (T.pack "Configure") urlrenderer ConfigFsckR
r <- alertDuring (fsckingAlert button mr) $
liftIO a
#else
2013-10-28 15:24:25 +00:00
r <- liftIO a
#endif
2013-10-28 15:24:25 +00:00
either (liftIO . E.throwIO) return r
notFsckedNudge :: UrlRenderer -> Maybe Remote -> Assistant ()
#ifdef WITH_WEBAPP
notFsckedNudge urlrenderer mr = do
button <- mkAlertButton True (T.pack "Configure") urlrenderer ConfigFsckR
void $ addAlert (notFsckedAlert mr button)
#else
2013-11-02 17:38:44 +00:00
notFsckedNudge _ _ = noop
#endif
notFsckedAlert :: Maybe Remote -> AlertButton -> Alert
notFsckedAlert mr button = Alert
{ alertHeader = Just $ fromString $ concat
[ "You should enable consistency checking to protect your data"
, maybe "" (\r -> " in " ++ Remote.name r) mr
, "."
]
, alertIcon = Just InfoIcon
, alertPriority = High
, alertButtons = [button]
, alertClosable = True
, alertClass = Message
, alertMessageRender = renderData
, alertCounter = 0
, alertBlockDisplay = True
, alertName = Just NotFsckedAlert
, alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertData = []
}
baseUpgradeAlert :: [AlertButton] -> TenseText -> Alert
baseUpgradeAlert buttons message = Alert
{ alertHeader = Just message
, alertIcon = Just UpgradeIcon
, alertPriority = High
, alertButtons = buttons
, alertClosable = True
, alertClass = Message
, alertMessageRender = renderData
, alertCounter = 0
, alertBlockDisplay = True
, alertName = Just UpgradeAlert
, alertCombiner = Just $ fullCombiner $ \new _old -> new
, alertData = []
}
2013-11-24 17:28:34 +00:00
canUpgradeAlert :: AlertPriority -> GitAnnexVersion -> AlertButton -> Alert
canUpgradeAlert priority version button =
(baseUpgradeAlert [button] $ fromString msg)
2013-11-24 17:28:34 +00:00
{ alertPriority = priority
, alertData = [fromString $ " (version " ++ version ++ ")"]
}
where
msg = if priority >= High
then "An important upgrade of git-annex is available!"
else "An upgrade of git-annex is available."
upgradeReadyAlert :: AlertButton -> Alert
upgradeReadyAlert button = baseUpgradeAlert [button] $
fromString "A new version of git-annex has been installed."
2013-11-23 03:12:06 +00:00
upgradingAlert :: Alert
upgradingAlert = activityAlert Nothing [ fromString "Upgrading git-annex" ]
upgradeFinishedAlert :: Maybe AlertButton -> GitAnnexVersion -> Alert
upgradeFinishedAlert button version =
2014-02-01 21:14:38 +00:00
baseUpgradeAlert (maybeToList button) $ fromString $
"Finished upgrading git-annex to version " ++ version
2013-11-23 03:12:06 +00:00
2013-11-24 18:04:03 +00:00
upgradeFailedAlert :: String -> Alert
upgradeFailedAlert msg = (errorAlert msg [])
{ alertHeader = Just $ fromString "Upgrade failed." }
unusedFilesAlert :: [AlertButton] -> String -> Alert
unusedFilesAlert buttons message = Alert
{ alertHeader = Just $ fromString $ unwords
[ "Old and deleted files are piling up --"
, message
]
, alertIcon = Just InfoIcon
, alertPriority = High
, alertButtons = buttons
, alertClosable = True
, alertClass = Message
, alertMessageRender = renderData
, alertCounter = 0
, alertBlockDisplay = True
, alertName = Just UnusedFilesAlert
, alertCombiner = Just $ fullCombiner $ \new _old -> new
, alertData = []
}
2013-11-24 18:04:03 +00:00
brokenRepositoryAlert :: [AlertButton] -> Alert
2013-10-22 20:30:23 +00:00
brokenRepositoryAlert = errorAlert "Serious problems have been detected with your repository. This needs your immediate attention!"
repairingAlert :: String -> Alert
repairingAlert repodesc = activityAlert Nothing
[ Tensed "Attempting to repair" "Repaired"
, UnTensed $ T.pack repodesc
]
pairingAlert :: AlertButton -> Alert
pairingAlert button = baseActivityAlert
{ alertData = [ UnTensed "Pairing in progress" ]
, alertPriority = High
, alertButtons = [button]
}
pairRequestReceivedAlert :: String -> AlertButton -> Alert
pairRequestReceivedAlert who button = Alert
2012-09-11 20:11:28 +00:00
{ alertClass = Message
, alertHeader = Nothing
2013-07-10 19:37:40 +00:00
, alertMessageRender = renderData
, alertData = [UnTensed $ T.pack $ who ++ " is sending a pair request."]
2013-07-10 19:37:40 +00:00
, alertCounter = 0
2012-09-11 20:11:28 +00:00
, alertBlockDisplay = False
2012-09-08 19:07:44 +00:00
, alertPriority = High
, alertClosable = True
, alertIcon = Just InfoIcon
, alertName = Just $ PairAlert who
, alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertButtons = [button]
}
2012-09-13 04:57:52 +00:00
pairRequestAcknowledgedAlert :: String -> Maybe AlertButton -> Alert
pairRequestAcknowledgedAlert who button = baseActivityAlert
{ alertData = ["Pairing with", UnTensed (T.pack who), Tensed "in progress" "complete"]
, alertPriority = High
, alertName = Just $ PairAlert who
, alertCombiner = Just $ dataCombiner $ \_old new -> new
2014-02-01 21:14:38 +00:00
, alertButtons = maybeToList button
2012-09-08 19:07:44 +00:00
}
connectionNeededAlert :: AlertButton -> Alert
connectionNeededAlert button = Alert
2012-11-11 00:52:46 +00:00
{ alertHeader = Just "Share with friends, and keep your devices in sync across the cloud."
, alertIcon = Just ConnectionIcon
, alertPriority = High
, alertButtons = [button]
, alertClosable = True
, alertClass = Message
2013-07-10 19:37:40 +00:00
, alertMessageRender = renderData
, alertCounter = 0
, alertBlockDisplay = True
, alertName = Just ConnectionNeededAlert
, alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertData = []
}
cloudRepoNeededAlert :: Maybe String -> AlertButton -> Alert
cloudRepoNeededAlert friendname button = Alert
{ alertHeader = Just $ fromString $ unwords
[ "Unable to download files from"
, (fromMaybe "your other devices" friendname) ++ "."
]
, alertIcon = Just ErrorIcon
, alertPriority = High
, alertButtons = [button]
, alertClosable = True
, alertClass = Message
2013-07-10 19:37:40 +00:00
, alertMessageRender = renderData
, alertCounter = 0
, alertBlockDisplay = True
, alertName = Just $ CloudRepoNeededAlert
, alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertData = []
}
remoteRemovalAlert :: String -> AlertButton -> Alert
remoteRemovalAlert desc button = Alert
{ alertHeader = Just $ fromString $
"The repository \"" ++ desc ++
"\" has been emptied, and can now be removed."
, alertIcon = Just InfoIcon
, alertPriority = High
, alertButtons = [button]
, alertClosable = True
, alertClass = Message
2013-07-10 19:37:40 +00:00
, alertMessageRender = renderData
, alertCounter = 0
, alertBlockDisplay = True
, alertName = Just $ RemoteRemovalAlert desc
, alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertData = []
}
2013-07-10 19:37:40 +00:00
{- Show a message that relates to a list of files.
-
- The most recent several files are shown, and a count of any others. -}
fileAlert :: TenseChunk -> [FilePath] -> Alert
fileAlert msg files = (activityAlert Nothing shortfiles)
2012-08-06 21:09:23 +00:00
{ alertName = Just $ FileAlert msg
2013-07-10 19:37:40 +00:00
, alertMessageRender = renderer
, alertCounter = counter
, alertCombiner = Just $ fullCombiner combiner
}
2012-10-31 06:34:03 +00:00
where
2013-07-10 19:37:40 +00:00
maxfilesshown = 10
(!somefiles, !counter) = splitcounter (dedupadjacent files)
!shortfiles = map (fromString . shortFile . takeFileName) somefiles
2013-07-10 19:37:40 +00:00
renderer alert = tenseWords $ msg : alertData alert ++ showcounter
where
showcounter = case alertCounter alert of
0 -> []
_ -> [fromString $ "and " ++ show (alertCounter alert) ++ " other files"]
2012-08-06 19:41:42 +00:00
2013-07-10 19:37:40 +00:00
dedupadjacent (x:y:rest)
| x == y = dedupadjacent (y:rest)
| otherwise = x : dedupadjacent (y:rest)
dedupadjacent (x:[]) = [x]
dedupadjacent [] = []
{- Note that this ensures the counter is never 1; no need to say
- "1 file" when the filename could be shown. -}
splitcounter l
| length l <= maxfilesshown = (l, 0)
| otherwise =
let (keep, rest) = splitAt (maxfilesshown - 1) l
in (keep, length rest)
combiner new old =
let (!fs, n) = splitcounter $
2013-07-10 19:37:40 +00:00
dedupadjacent $ alertData new ++ alertData old
!cnt = n + alertCounter new + alertCounter old
2013-07-10 19:37:40 +00:00
in old
{ alertData = fs
, alertCounter = cnt
}
addFileAlert :: [FilePath] -> Alert
2012-08-06 21:09:23 +00:00
addFileAlert = fileAlert (Tensed "Adding" "Added")
{- This is only used as a success alert after a transfer, not during it. -}
transferFileAlert :: Direction -> Bool -> FilePath -> Alert
2013-07-10 19:37:40 +00:00
transferFileAlert direction True file
| direction == Upload = fileAlert "Uploaded" [file]
| otherwise = fileAlert "Downloaded" [file]
transferFileAlert direction False file
| direction == Upload = fileAlert "Upload failed" [file]
| otherwise = fileAlert "Download failed" [file]
2012-08-06 21:09:23 +00:00
2012-08-06 19:41:42 +00:00
dataCombiner :: ([TenseChunk] -> [TenseChunk] -> [TenseChunk]) -> AlertCombiner
2013-07-10 19:37:40 +00:00
dataCombiner combiner = fullCombiner $
\new old -> old { alertData = alertData new `combiner` alertData old }
fullCombiner :: (Alert -> Alert -> Alert) -> AlertCombiner
fullCombiner combiner new old
2012-08-06 19:41:42 +00:00
| alertClass new /= alertClass old = Nothing
| alertName new == alertName old =
2013-07-10 19:37:40 +00:00
Just $! new `combiner` old
2012-08-06 19:41:42 +00:00
| otherwise = Nothing
2012-08-02 17:47:26 +00:00
shortFile :: FilePath -> String
shortFile f
| len < maxlen = f
| otherwise = take half f ++ ".." ++ drop (len - half) f
2012-10-31 06:34:03 +00:00
where
len = length f
maxlen = 20
half = (maxlen - 2) `div` 2
2012-08-02 17:47:26 +00:00