2012-07-29 09:35:01 -04:00
|
|
|
{- git-annex assistant alerts
|
|
|
|
-
|
2013-04-04 01:48:26 -04:00
|
|
|
- Copyright 2012, 2013 Joey Hess <joey@kitenet.net>
|
2012-07-29 09:35:01 -04:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-04-04 01:48:26 -04:00
|
|
|
{-# LANGUAGE OverloadedStrings, CPP #-}
|
2012-07-29 09:35:01 -04:00
|
|
|
|
|
|
|
module Assistant.Alert where
|
|
|
|
|
2012-07-29 18:07:45 -04:00
|
|
|
import Common.Annex
|
2013-04-04 01:48:26 -04:00
|
|
|
import Assistant.Types.Alert
|
|
|
|
import Assistant.Alert.Utility
|
2012-07-29 18:07:45 -04:00
|
|
|
import qualified Remote
|
2012-08-06 15:00:46 -04:00
|
|
|
import Utility.Tense
|
2012-08-06 17:09:23 -04:00
|
|
|
import Logs.Transfer
|
2012-07-29 18:07:45 -04:00
|
|
|
|
2012-08-06 15:00:46 -04:00
|
|
|
import Data.String
|
2013-04-04 01:48:26 -04:00
|
|
|
import qualified Data.Text as T
|
2012-07-29 09:35:01 -04:00
|
|
|
|
2013-04-04 01:48:26 -04:00
|
|
|
#ifdef WITH_WEBAPP
|
|
|
|
import Assistant.Monad
|
|
|
|
import Assistant.DaemonStatus
|
|
|
|
import Assistant.WebApp.Types
|
|
|
|
import Assistant.WebApp
|
2013-04-04 01:50:36 -04:00
|
|
|
import Yesod
|
2013-04-04 01:48:26 -04:00
|
|
|
#endif
|
|
|
|
|
|
|
|
{- Makes a button for an alert that opens a Route. The button will
|
|
|
|
- close the alert it's attached to when clicked. -}
|
|
|
|
#ifdef WITH_WEBAPP
|
|
|
|
mkAlertButton :: T.Text -> UrlRenderer -> Route WebApp -> Assistant AlertButton
|
|
|
|
mkAlertButton label urlrenderer route = do
|
|
|
|
close <- asIO1 removeAlert
|
|
|
|
url <- liftIO $ renderUrl urlrenderer route []
|
|
|
|
return $ AlertButton
|
|
|
|
{ buttonLabel = label
|
|
|
|
, buttonUrl = url
|
|
|
|
, buttonAction = Just close
|
2012-07-30 02:07:02 -04:00
|
|
|
}
|
2013-04-04 01:48:26 -04:00
|
|
|
#endif
|
2012-07-29 19:05:51 -04:00
|
|
|
|
2012-07-29 19:41:17 -04:00
|
|
|
baseActivityAlert :: Alert
|
|
|
|
baseActivityAlert = Alert
|
2012-07-29 11:31:06 -04:00
|
|
|
{ alertClass = Activity
|
2012-07-29 19:41:17 -04:00
|
|
|
, alertHeader = Nothing
|
2012-08-06 15:41:42 -04:00
|
|
|
, alertMessageRender = tenseWords
|
|
|
|
, alertData = []
|
2012-07-29 11:31:06 -04:00
|
|
|
, alertBlockDisplay = False
|
2012-07-29 19:41:17 -04:00
|
|
|
, alertClosable = False
|
2012-07-29 19:05:51 -04:00
|
|
|
, alertPriority = Medium
|
2012-09-09 15:09:22 -04:00
|
|
|
, alertIcon = Just ActivityIcon
|
2012-08-02 09:03:04 -04:00
|
|
|
, alertCombiner = Nothing
|
|
|
|
, alertName = Nothing
|
2012-09-08 19:57:15 -04:00
|
|
|
, alertButton = Nothing
|
2012-07-29 09:35:01 -04:00
|
|
|
}
|
2012-07-29 18:07:45 -04:00
|
|
|
|
2012-09-06 13:56:23 -04:00
|
|
|
warningAlert :: String -> String -> Alert
|
|
|
|
warningAlert name msg = Alert
|
|
|
|
{ alertClass = Warning
|
|
|
|
, alertHeader = Just $ tenseWords ["warning"]
|
|
|
|
, alertMessageRender = tenseWords
|
|
|
|
, alertData = [UnTensed $ T.pack msg]
|
|
|
|
, alertBlockDisplay = True
|
|
|
|
, alertClosable = True
|
|
|
|
, alertPriority = High
|
2012-09-09 15:09:22 -04:00
|
|
|
, alertIcon = Just ErrorIcon
|
2013-04-24 11:27:30 -04:00
|
|
|
, alertCombiner = Just $ dataCombiner $ \_old new -> new
|
2012-09-06 13:56:23 -04:00
|
|
|
, alertName = Just $ WarningAlert name
|
2012-09-08 19:57:15 -04:00
|
|
|
, alertButton = Nothing
|
2012-09-06 13:56:23 -04:00
|
|
|
}
|
|
|
|
|
2012-08-06 15:41:42 -04:00
|
|
|
activityAlert :: Maybe TenseText -> [TenseChunk] -> Alert
|
|
|
|
activityAlert header dat = baseActivityAlert
|
2012-07-29 19:41:17 -04:00
|
|
|
{ alertHeader = header
|
2012-08-06 15:41:42 -04:00
|
|
|
, alertData = dat
|
2012-07-29 19:41:17 -04:00
|
|
|
}
|
|
|
|
|
2012-07-29 18:07:45 -04:00
|
|
|
startupScanAlert :: Alert
|
2012-09-13 00:57:52 -04:00
|
|
|
startupScanAlert = activityAlert Nothing
|
2012-08-06 15:41:42 -04:00
|
|
|
[Tensed "Performing" "Performed", "startup scan"]
|
2012-07-29 18:07:45 -04:00
|
|
|
|
2013-04-10 17:52:04 -04:00
|
|
|
{- 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 14:02:35 -04:00
|
|
|
commitAlert :: Alert
|
2012-09-13 00:57:52 -04:00
|
|
|
commitAlert = activityAlert Nothing
|
2012-08-06 15:00:46 -04:00
|
|
|
[Tensed "Committing" "Committed", "changes to git"]
|
|
|
|
|
|
|
|
showRemotes :: [Remote] -> TenseChunk
|
2013-03-18 19:11:46 -04:00
|
|
|
showRemotes = UnTensed . T.intercalate ", " . map (T.pack . Remote.name)
|
2012-08-02 14:02:35 -04:00
|
|
|
|
2012-08-06 17:09:23 -04:00
|
|
|
syncAlert :: [Remote] -> Alert
|
|
|
|
syncAlert rs = baseActivityAlert
|
2013-03-18 16:19:42 -04:00
|
|
|
{ alertName = Just SyncAlert
|
|
|
|
, alertHeader = Just $ tenseWords
|
2012-08-06 17:09:23 -04:00
|
|
|
[Tensed "Syncing" "Synced", "with", showRemotes rs]
|
2012-07-29 19:05:51 -04:00
|
|
|
, alertPriority = Low
|
2013-04-08 22:54:02 -04:00
|
|
|
, alertIcon = Just SyncIcon
|
2012-12-13 00:45:27 -04:00
|
|
|
}
|
2012-07-29 18:07:45 -04:00
|
|
|
|
2013-03-18 16:19:42 -04:00
|
|
|
syncResultAlert :: [Remote] -> [Remote] -> 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
|
|
|
|
]
|
2012-07-29 18:07:45 -04:00
|
|
|
|
|
|
|
sanityCheckAlert :: Alert
|
2012-08-06 15:00:46 -04:00
|
|
|
sanityCheckAlert = activityAlert
|
|
|
|
(Just $ tenseWords [Tensed "Running" "Ran", "daily sanity check"])
|
2012-08-06 15:41:42 -04:00
|
|
|
["to make sure everything is ok."]
|
2012-07-29 18:07:45 -04:00
|
|
|
|
|
|
|
sanityCheckFixAlert :: String -> Alert
|
|
|
|
sanityCheckFixAlert msg = Alert
|
|
|
|
{ alertClass = Warning
|
2012-08-06 15:00:46 -04:00
|
|
|
, alertHeader = Just $ tenseWords ["Fixed a problem"]
|
2012-08-06 15:41:42 -04:00
|
|
|
, alertMessageRender = render
|
|
|
|
, alertData = [UnTensed $ T.pack msg]
|
2012-07-29 18:07:45 -04:00
|
|
|
, alertBlockDisplay = True
|
2012-07-29 19:05:51 -04:00
|
|
|
, alertPriority = High
|
2012-07-29 19:41:17 -04:00
|
|
|
, alertClosable = True
|
2012-09-09 15:09:22 -04:00
|
|
|
, alertIcon = Just ErrorIcon
|
2012-08-02 09:03:04 -04:00
|
|
|
, alertName = Just SanityCheckFixAlert
|
2012-08-06 15:41:42 -04:00
|
|
|
, alertCombiner = Just $ dataCombiner (++)
|
2012-09-08 19:57:15 -04:00
|
|
|
, alertButton = Nothing
|
2012-08-02 09:03:04 -04:00
|
|
|
}
|
2012-10-31 02:34:03 -04:00
|
|
|
where
|
|
|
|
render dta = tenseWords $ alerthead : dta ++ [alertfoot]
|
|
|
|
alerthead = "The daily sanity check found and fixed a problem:"
|
|
|
|
alertfoot = "If these problems persist, consider filing a bug report."
|
2012-08-02 09:03:04 -04:00
|
|
|
|
2012-09-10 17:53:51 -04:00
|
|
|
pairingAlert :: AlertButton -> Alert
|
|
|
|
pairingAlert button = baseActivityAlert
|
|
|
|
{ alertData = [ UnTensed "Pairing in progress" ]
|
2012-09-09 16:24:34 -04:00
|
|
|
, alertPriority = High
|
|
|
|
, alertButton = Just button
|
|
|
|
}
|
|
|
|
|
2012-09-11 15:06:29 -04:00
|
|
|
pairRequestReceivedAlert :: String -> AlertButton -> Alert
|
2012-11-03 17:34:19 -04:00
|
|
|
pairRequestReceivedAlert who button = Alert
|
2012-09-11 16:11:28 -04:00
|
|
|
{ alertClass = Message
|
|
|
|
, alertHeader = Nothing
|
|
|
|
, alertMessageRender = tenseWords
|
2012-11-03 17:34:19 -04:00
|
|
|
, alertData = [UnTensed $ T.pack $ who ++ " is sending a pair request."]
|
2012-09-11 16:11:28 -04:00
|
|
|
, alertBlockDisplay = False
|
2012-09-08 15:07:44 -04:00
|
|
|
, alertPriority = High
|
|
|
|
, alertClosable = True
|
2012-09-09 15:09:22 -04:00
|
|
|
, alertIcon = Just InfoIcon
|
2012-11-03 17:34:19 -04:00
|
|
|
, alertName = Just $ PairAlert who
|
2012-09-11 15:06:29 -04:00
|
|
|
, alertCombiner = Just $ dataCombiner $ \_old new -> new
|
|
|
|
, alertButton = Just button
|
|
|
|
}
|
|
|
|
|
2012-09-13 00:57:52 -04:00
|
|
|
pairRequestAcknowledgedAlert :: String -> Maybe AlertButton -> Alert
|
2012-11-03 17:34:19 -04:00
|
|
|
pairRequestAcknowledgedAlert who button = baseActivityAlert
|
2012-11-05 17:43:17 -04:00
|
|
|
{ alertData = ["Pairing with", UnTensed (T.pack who), Tensed "in progress" "complete"]
|
2012-09-11 15:06:29 -04:00
|
|
|
, alertPriority = High
|
2013-03-05 16:23:56 -04:00
|
|
|
, alertName = Just $ PairAlert who
|
2012-09-11 15:06:29 -04:00
|
|
|
, alertCombiner = Just $ dataCombiner $ \_old new -> new
|
2012-09-11 15:43:33 -04:00
|
|
|
, alertButton = button
|
2012-09-08 15:07:44 -04:00
|
|
|
}
|
|
|
|
|
2012-10-27 12:25:29 -04:00
|
|
|
xmppNeededAlert :: AlertButton -> Alert
|
|
|
|
xmppNeededAlert button = Alert
|
2012-11-10 20:52:46 -04:00
|
|
|
{ alertHeader = Just "Share with friends, and keep your devices in sync across the cloud."
|
2012-10-27 12:25:29 -04:00
|
|
|
, alertIcon = Just TheCloud
|
|
|
|
, alertPriority = High
|
|
|
|
, alertButton = Just button
|
|
|
|
, alertClosable = True
|
|
|
|
, alertClass = Message
|
|
|
|
, alertMessageRender = tenseWords
|
|
|
|
, alertBlockDisplay = True
|
|
|
|
, alertName = Just $ XMPPNeededAlert
|
|
|
|
, alertCombiner = Just $ dataCombiner $ \_old new -> new
|
|
|
|
, alertData = []
|
|
|
|
}
|
|
|
|
|
2013-03-15 17:52:41 -04:00
|
|
|
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
|
|
|
|
, alertButton = Just button
|
|
|
|
, alertClosable = True
|
|
|
|
, alertClass = Message
|
|
|
|
, alertMessageRender = tenseWords
|
|
|
|
, alertBlockDisplay = True
|
|
|
|
, alertName = Just $ CloudRepoNeededAlert
|
|
|
|
, alertCombiner = Just $ dataCombiner $ \_old new -> new
|
|
|
|
, alertData = []
|
|
|
|
}
|
|
|
|
|
2013-04-03 17:01:40 -04:00
|
|
|
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
|
|
|
|
, alertButton = Just button
|
|
|
|
, alertClosable = True
|
|
|
|
, alertClass = Message
|
|
|
|
, alertMessageRender = tenseWords
|
|
|
|
, alertBlockDisplay = True
|
|
|
|
, alertName = Just $ RemoteRemovalAlert desc
|
|
|
|
, alertCombiner = Just $ dataCombiner $ \_old new -> new
|
|
|
|
, alertData = []
|
|
|
|
}
|
|
|
|
|
2012-08-06 17:09:23 -04:00
|
|
|
fileAlert :: TenseChunk -> FilePath -> Alert
|
|
|
|
fileAlert msg file = (activityAlert Nothing [f])
|
|
|
|
{ alertName = Just $ FileAlert msg
|
2012-08-06 15:41:42 -04:00
|
|
|
, alertMessageRender = render
|
|
|
|
, alertCombiner = Just $ dataCombiner combiner
|
2012-07-29 18:07:45 -04:00
|
|
|
}
|
2012-10-31 02:34:03 -04:00
|
|
|
where
|
|
|
|
f = fromString $ shortFile $ takeFileName file
|
|
|
|
render fs = tenseWords $ msg : fs
|
|
|
|
combiner new old = take 10 $ new ++ old
|
2012-08-06 15:41:42 -04:00
|
|
|
|
2013-04-24 13:04:46 -04:00
|
|
|
addFileAlert :: String -> Alert
|
2012-08-06 17:09:23 -04:00
|
|
|
addFileAlert = fileAlert (Tensed "Adding" "Added")
|
|
|
|
|
|
|
|
{- This is only used as a success alert after a transfer, not during it. -}
|
2012-08-27 13:52:48 -04:00
|
|
|
transferFileAlert :: Direction -> Bool -> FilePath -> Alert
|
|
|
|
transferFileAlert direction True
|
2012-08-06 17:09:23 -04:00
|
|
|
| direction == Upload = fileAlert "Uploaded"
|
|
|
|
| otherwise = fileAlert "Downloaded"
|
2012-08-27 13:52:48 -04:00
|
|
|
transferFileAlert direction False
|
|
|
|
| direction == Upload = fileAlert "Upload failed"
|
|
|
|
| otherwise = fileAlert "Download failed"
|
2012-08-06 17:09:23 -04:00
|
|
|
|
2012-08-06 15:41:42 -04:00
|
|
|
dataCombiner :: ([TenseChunk] -> [TenseChunk] -> [TenseChunk]) -> AlertCombiner
|
|
|
|
dataCombiner combiner new old
|
|
|
|
| alertClass new /= alertClass old = Nothing
|
|
|
|
| alertName new == alertName old =
|
|
|
|
Just $! old { alertData = alertData new `combiner` alertData old }
|
|
|
|
| otherwise = Nothing
|
2012-08-02 13:47:26 -04:00
|
|
|
|
|
|
|
shortFile :: FilePath -> String
|
|
|
|
shortFile f
|
|
|
|
| len < maxlen = f
|
|
|
|
| otherwise = take half f ++ ".." ++ drop (len - half) f
|
2012-10-31 02:34:03 -04:00
|
|
|
where
|
|
|
|
len = length f
|
|
|
|
maxlen = 20
|
|
|
|
half = (maxlen - 2) `div` 2
|
2012-08-02 13:47:26 -04:00
|
|
|
|