prune old filler alerts
This commit is contained in:
parent
40c9973675
commit
8d2667715b
3 changed files with 43 additions and 16 deletions
|
@ -12,6 +12,7 @@ module Assistant.Alert where
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
|
|
||||||
|
import qualified Data.Map as M
|
||||||
import Yesod
|
import Yesod
|
||||||
|
|
||||||
type Widget = forall sub master. GWidget sub master ()
|
type Widget = forall sub master. GWidget sub master ()
|
||||||
|
@ -20,6 +21,9 @@ type Widget = forall sub master. GWidget sub master ()
|
||||||
data AlertClass = Success | Message | Activity | Warning | Error
|
data AlertClass = Success | Message | Activity | Warning | Error
|
||||||
deriving (Eq, Ord)
|
deriving (Eq, Ord)
|
||||||
|
|
||||||
|
data AlertPriority = Filler | Low | Medium | High | Pinned
|
||||||
|
deriving (Eq, Ord)
|
||||||
|
|
||||||
{- An alert can be a simple message, or an arbitrary Yesod Widget. -}
|
{- An alert can be a simple message, or an arbitrary Yesod Widget. -}
|
||||||
data AlertMessage = StringAlert String | WidgetAlert (Alert -> Widget)
|
data AlertMessage = StringAlert String | WidgetAlert (Alert -> Widget)
|
||||||
|
|
||||||
|
@ -37,8 +41,19 @@ type AlertId = Integer
|
||||||
|
|
||||||
type AlertPair = (AlertId, Alert)
|
type AlertPair = (AlertId, Alert)
|
||||||
|
|
||||||
data AlertPriority = Filler | Low | Medium | High | Pinned
|
type AlertMap = M.Map AlertId Alert
|
||||||
deriving (Eq, Ord)
|
|
||||||
|
{- This is as many alerts as it makes sense to display at a time.
|
||||||
|
- A display might be smaller ,or larger, the point is to not overwhelm the
|
||||||
|
- user with a ton of alerts. -}
|
||||||
|
displayAlerts :: Int
|
||||||
|
displayAlerts = 10
|
||||||
|
|
||||||
|
{- This is not a hard maximum, but there's no point in keeping a great
|
||||||
|
- many filler alerts in an AlertMap, so when there's more than this many,
|
||||||
|
- they start being pruned, down toward displayAlerts. -}
|
||||||
|
maxAlerts :: Int
|
||||||
|
maxAlerts = displayAlerts * 2
|
||||||
|
|
||||||
{- The desired order is the reverse of:
|
{- The desired order is the reverse of:
|
||||||
-
|
-
|
||||||
|
@ -57,9 +72,12 @@ compareAlertPairs
|
||||||
`thenOrd` compare aid bid
|
`thenOrd` compare aid bid
|
||||||
`thenOrd` compare aclass bclass
|
`thenOrd` compare aclass bclass
|
||||||
|
|
||||||
|
sortAlertPairs :: [AlertPair] -> [AlertPair]
|
||||||
|
sortAlertPairs = sortBy compareAlertPairs
|
||||||
|
|
||||||
makeAlertFiller :: Bool -> Alert -> Alert
|
makeAlertFiller :: Bool -> Alert -> Alert
|
||||||
makeAlertFiller success alert
|
makeAlertFiller success alert
|
||||||
| alertPriority alert == Filler = alert
|
| isFiller alert = alert
|
||||||
| otherwise = alert
|
| otherwise = alert
|
||||||
{ alertClass = if c == Activity then c' else c
|
{ alertClass = if c == Activity then c' else c
|
||||||
, alertPriority = Filler
|
, alertPriority = Filler
|
||||||
|
@ -79,11 +97,26 @@ makeAlertFiller success alert
|
||||||
maybe (finished s) (const s) h
|
maybe (finished s) (const s) h
|
||||||
|
|
||||||
finished s
|
finished s
|
||||||
| success = s ++ ": Succeeded"
|
| success = s ++ ": Ok"
|
||||||
| otherwise = s ++ ": Failed"
|
| otherwise = s ++ ": Failed"
|
||||||
|
|
||||||
sortAlertPairs :: [AlertPair] -> [AlertPair]
|
isFiller :: Alert -> Bool
|
||||||
sortAlertPairs = reverse . sortBy compareAlertPairs
|
isFiller alert = alertPriority alert == Filler
|
||||||
|
|
||||||
|
{- Converts a given alert into filler, manipulating it in the AlertMap.
|
||||||
|
-
|
||||||
|
- Old filler alerts are pruned once maxAlerts is reached.
|
||||||
|
-}
|
||||||
|
convertToFiller :: AlertId -> Bool -> AlertMap -> AlertMap
|
||||||
|
convertToFiller i success m
|
||||||
|
| bloat > 0 = M.fromList $ prune $ M.toList m'
|
||||||
|
| otherwise = m'
|
||||||
|
where
|
||||||
|
bloat = M.size m - maxAlerts
|
||||||
|
m' = M.adjust (\al -> makeAlertFiller success al) i m
|
||||||
|
prune l =
|
||||||
|
let (f, rest) = partition (\(_, al) -> isFiller al) l
|
||||||
|
in drop bloat f ++ rest
|
||||||
|
|
||||||
baseActivityAlert :: Alert
|
baseActivityAlert :: Alert
|
||||||
baseActivityAlert = Alert
|
baseActivityAlert = Alert
|
||||||
|
|
|
@ -50,8 +50,6 @@ data DaemonStatus = DaemonStatus
|
||||||
|
|
||||||
type TransferMap = M.Map Transfer TransferInfo
|
type TransferMap = M.Map Transfer TransferInfo
|
||||||
|
|
||||||
type AlertMap = M.Map AlertId Alert
|
|
||||||
|
|
||||||
{- This TMVar is never left empty, so accessing it will never block. -}
|
{- This TMVar is never left empty, so accessing it will never block. -}
|
||||||
type DaemonStatusHandle = TMVar DaemonStatus
|
type DaemonStatusHandle = TMVar DaemonStatus
|
||||||
|
|
||||||
|
@ -242,10 +240,5 @@ alertWhile dstatus alert a = do
|
||||||
let alert' = alert { alertClass = Activity }
|
let alert' = alert { alertClass = Activity }
|
||||||
i <- addAlert dstatus alert'
|
i <- addAlert dstatus alert'
|
||||||
r <- bracket_ noop noop a
|
r <- bracket_ noop noop a
|
||||||
updateAlertMap dstatus $ makeold i (makeAlertFiller r)
|
updateAlertMap dstatus $ convertToFiller i r
|
||||||
return r
|
return r
|
||||||
where
|
|
||||||
-- TODO prune old filler
|
|
||||||
makeold i filler m
|
|
||||||
| M.size m < 20 = M.adjust filler i m
|
|
||||||
| otherwise = M.adjust filler i m
|
|
||||||
|
|
|
@ -204,11 +204,12 @@ sideBarDisplay noScript = do
|
||||||
{- Any yesod message appears as the first alert. -}
|
{- Any yesod message appears as the first alert. -}
|
||||||
maybe noop rendermessage =<< lift getMessage
|
maybe noop rendermessage =<< lift getMessage
|
||||||
|
|
||||||
{- Add newest 10 alerts to the sidebar. -}
|
{- Add newest alerts to the sidebar. -}
|
||||||
webapp <- lift getYesod
|
webapp <- lift getYesod
|
||||||
alertpairs <- M.toList . alertMap
|
alertpairs <- M.toList . alertMap
|
||||||
<$> liftIO (getDaemonStatus $ daemonStatus webapp)
|
<$> liftIO (getDaemonStatus $ daemonStatus webapp)
|
||||||
mapM_ renderalert $ take 10 $ sortAlertPairs alertpairs
|
mapM_ renderalert $
|
||||||
|
take displayAlerts $ reverse $ sortAlertPairs alertpairs
|
||||||
ident <- lift newIdent
|
ident <- lift newIdent
|
||||||
$(widgetFile "sidebar")
|
$(widgetFile "sidebar")
|
||||||
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue