first pass at alert buttons
They work fine. But I had to go to a lot of trouble to get Yesod to render routes in a pure function. It may instead make more sense to have each alert have an assocated IO action, and a single route that runs the IO action of a given alert id. I just wish I'd realized that before the past several hours of struggling with something Yesod really doesn't want to allow.
This commit is contained in:
parent
e6e0877378
commit
e59b0a1c88
9 changed files with 100 additions and 41 deletions
10
Assistant.hs
10
Assistant.hs
|
@ -97,6 +97,10 @@
|
||||||
- ScanRemotes (STM TMVar)
|
- ScanRemotes (STM TMVar)
|
||||||
- Remotes that have been disconnected, and should be scanned
|
- Remotes that have been disconnected, and should be scanned
|
||||||
- are indicated by writing to this TMVar.
|
- are indicated by writing to this TMVar.
|
||||||
|
- UrlRenderer (MVar)
|
||||||
|
- A Yesod route rendering function is stored here. This allows
|
||||||
|
- things that need to render Yesod routes to block until the webapp
|
||||||
|
- has started up and such rendering is possible.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
@ -125,6 +129,7 @@ import Assistant.Threads.NetWatcher
|
||||||
import Assistant.Threads.TransferScanner
|
import Assistant.Threads.TransferScanner
|
||||||
import Assistant.Threads.TransferPoller
|
import Assistant.Threads.TransferPoller
|
||||||
#ifdef WITH_WEBAPP
|
#ifdef WITH_WEBAPP
|
||||||
|
import Assistant.WebApp
|
||||||
import Assistant.Threads.WebApp
|
import Assistant.Threads.WebApp
|
||||||
#ifdef WITH_PAIRING
|
#ifdef WITH_PAIRING
|
||||||
import Assistant.Threads.PairListener
|
import Assistant.Threads.PairListener
|
||||||
|
@ -170,12 +175,13 @@ startAssistant assistant daemonize webappwaiter = do
|
||||||
transferqueue <- newTransferQueue
|
transferqueue <- newTransferQueue
|
||||||
transferslots <- newTransferSlots
|
transferslots <- newTransferSlots
|
||||||
scanremotes <- newScanRemoteMap
|
scanremotes <- newScanRemoteMap
|
||||||
|
urlrenderer <- newUrlRenderer
|
||||||
mapM_ (startthread dstatus)
|
mapM_ (startthread dstatus)
|
||||||
[ watch $ commitThread st changechan commitchan transferqueue dstatus
|
[ watch $ commitThread st changechan commitchan transferqueue dstatus
|
||||||
#ifdef WITH_WEBAPP
|
#ifdef WITH_WEBAPP
|
||||||
, assist $ webAppThread (Just st) dstatus scanremotes transferqueue transferslots Nothing webappwaiter
|
, assist $ webAppThread (Just st) dstatus scanremotes transferqueue transferslots urlrenderer Nothing webappwaiter
|
||||||
#ifdef WITH_PAIRING
|
#ifdef WITH_PAIRING
|
||||||
, assist $ pairListenerThread st dstatus
|
, assist $ pairListenerThread st dstatus urlrenderer
|
||||||
#endif
|
#endif
|
||||||
#endif
|
#endif
|
||||||
, assist $ pushThread st dstatus commitchan pushmap
|
, assist $ pushThread st dstatus commitchan pushmap
|
||||||
|
|
|
@ -15,6 +15,7 @@ import Utility.Tense
|
||||||
import Logs.Transfer
|
import Logs.Transfer
|
||||||
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
import Data.Text (Text)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Data.String
|
import Data.String
|
||||||
|
|
||||||
|
@ -49,6 +50,12 @@ data Alert = Alert
|
||||||
, alertIcon :: Maybe String
|
, alertIcon :: Maybe String
|
||||||
, alertCombiner :: Maybe AlertCombiner
|
, alertCombiner :: Maybe AlertCombiner
|
||||||
, alertName :: Maybe AlertName
|
, alertName :: Maybe AlertName
|
||||||
|
, alertButton :: Maybe AlertButton
|
||||||
|
}
|
||||||
|
|
||||||
|
data AlertButton = AlertButton
|
||||||
|
{ buttonUrl :: Text
|
||||||
|
, buttonLabel :: Text
|
||||||
}
|
}
|
||||||
|
|
||||||
type AlertPair = (AlertId, Alert)
|
type AlertPair = (AlertId, Alert)
|
||||||
|
@ -98,11 +105,11 @@ sortAlertPairs :: [AlertPair] -> [AlertPair]
|
||||||
sortAlertPairs = sortBy compareAlertPairs
|
sortAlertPairs = sortBy compareAlertPairs
|
||||||
|
|
||||||
{- Renders an alert's header for display, if it has one. -}
|
{- Renders an alert's header for display, if it has one. -}
|
||||||
renderAlertHeader :: Alert -> Maybe T.Text
|
renderAlertHeader :: Alert -> Maybe Text
|
||||||
renderAlertHeader alert = renderTense (alertTense alert) <$> alertHeader alert
|
renderAlertHeader alert = renderTense (alertTense alert) <$> alertHeader alert
|
||||||
|
|
||||||
{- Renders an alert's message for display. -}
|
{- Renders an alert's message for display. -}
|
||||||
renderAlertMessage :: Alert -> T.Text
|
renderAlertMessage :: Alert -> Text
|
||||||
renderAlertMessage alert = renderTense (alertTense alert) $
|
renderAlertMessage alert = renderTense (alertTense alert) $
|
||||||
(alertMessageRender alert) (alertData alert)
|
(alertMessageRender alert) (alertData alert)
|
||||||
|
|
||||||
|
@ -182,6 +189,7 @@ baseActivityAlert = Alert
|
||||||
, alertIcon = Just "refresh"
|
, alertIcon = Just "refresh"
|
||||||
, alertCombiner = Nothing
|
, alertCombiner = Nothing
|
||||||
, alertName = Nothing
|
, alertName = Nothing
|
||||||
|
, alertButton = Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
warningAlert :: String -> String -> Alert
|
warningAlert :: String -> String -> Alert
|
||||||
|
@ -196,6 +204,7 @@ warningAlert name msg = Alert
|
||||||
, alertIcon = Just "exclamation-sign"
|
, alertIcon = Just "exclamation-sign"
|
||||||
, alertCombiner = Just $ dataCombiner (++)
|
, alertCombiner = Just $ dataCombiner (++)
|
||||||
, alertName = Just $ WarningAlert name
|
, alertName = Just $ WarningAlert name
|
||||||
|
, alertButton = Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
activityAlert :: Maybe TenseText -> [TenseChunk] -> Alert
|
activityAlert :: Maybe TenseText -> [TenseChunk] -> Alert
|
||||||
|
@ -257,14 +266,15 @@ sanityCheckFixAlert msg = Alert
|
||||||
, alertIcon = Just "exclamation-sign"
|
, alertIcon = Just "exclamation-sign"
|
||||||
, alertName = Just SanityCheckFixAlert
|
, alertName = Just SanityCheckFixAlert
|
||||||
, alertCombiner = Just $ dataCombiner (++)
|
, alertCombiner = Just $ dataCombiner (++)
|
||||||
|
, alertButton = Nothing
|
||||||
}
|
}
|
||||||
where
|
where
|
||||||
render dta = tenseWords $ alerthead : dta ++ [alertfoot]
|
render dta = tenseWords $ alerthead : dta ++ [alertfoot]
|
||||||
alerthead = "The daily sanity check found and fixed a problem:"
|
alerthead = "The daily sanity check found and fixed a problem:"
|
||||||
alertfoot = "If these problems persist, consider filing a bug report."
|
alertfoot = "If these problems persist, consider filing a bug report."
|
||||||
|
|
||||||
pairRequestAlert :: String -> String -> Alert
|
pairRequestAlert :: String -> String -> AlertButton -> Alert
|
||||||
pairRequestAlert repo msg = Alert
|
pairRequestAlert repo msg button = Alert
|
||||||
{ alertClass = Message
|
{ alertClass = Message
|
||||||
, alertHeader = Just $ tenseWords ["Pair request"]
|
, alertHeader = Just $ tenseWords ["Pair request"]
|
||||||
, alertMessageRender = tenseWords
|
, alertMessageRender = tenseWords
|
||||||
|
@ -275,6 +285,7 @@ pairRequestAlert repo msg = Alert
|
||||||
, alertIcon = Just "info-sign"
|
, alertIcon = Just "info-sign"
|
||||||
, alertName = Just $ PairRequestAlert repo
|
, alertName = Just $ PairRequestAlert repo
|
||||||
, alertCombiner = Just $ dataCombiner $ const id
|
, alertCombiner = Just $ dataCombiner $ const id
|
||||||
|
, alertButton = Just button
|
||||||
}
|
}
|
||||||
|
|
||||||
fileAlert :: TenseChunk -> FilePath -> Alert
|
fileAlert :: TenseChunk -> FilePath -> Alert
|
||||||
|
|
|
@ -5,6 +5,8 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE CPP, RankNTypes, ImpredicativeTypes #-}
|
||||||
|
|
||||||
module Assistant.DaemonStatus where
|
module Assistant.DaemonStatus where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
|
|
|
@ -12,17 +12,20 @@ import Assistant.Pairing
|
||||||
import Assistant.Pairing.Network
|
import Assistant.Pairing.Network
|
||||||
import Assistant.ThreadedMonad
|
import Assistant.ThreadedMonad
|
||||||
import Assistant.DaemonStatus
|
import Assistant.DaemonStatus
|
||||||
|
import Assistant.WebApp
|
||||||
|
import Assistant.WebApp.Types
|
||||||
import Assistant.Alert
|
import Assistant.Alert
|
||||||
import Utility.Verifiable
|
import Utility.Verifiable
|
||||||
|
|
||||||
import Network.Multicast
|
import Network.Multicast
|
||||||
import Network.Socket
|
import Network.Socket
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
thisThread :: ThreadName
|
thisThread :: ThreadName
|
||||||
thisThread = "PairListener"
|
thisThread = "PairListener"
|
||||||
|
|
||||||
pairListenerThread :: ThreadState -> DaemonStatusHandle -> NamedThread
|
pairListenerThread :: ThreadState -> DaemonStatusHandle -> UrlRenderer -> NamedThread
|
||||||
pairListenerThread st dstatus = thread $ withSocketsDo $ do
|
pairListenerThread st dstatus urlrenderer = thread $ withSocketsDo $ do
|
||||||
sock <- multicastReceiver (multicastAddress $ IPv4Addr undefined) pairingPort
|
sock <- multicastReceiver (multicastAddress $ IPv4Addr undefined) pairingPort
|
||||||
forever $ do
|
forever $ do
|
||||||
msg <- getmsg sock []
|
msg <- getmsg sock []
|
||||||
|
@ -39,19 +42,34 @@ pairListenerThread st dstatus = thread $ withSocketsDo $ do
|
||||||
chunksz = 1024
|
chunksz = 1024
|
||||||
|
|
||||||
dispatch Nothing = noop
|
dispatch Nothing = noop
|
||||||
dispatch (Just (PairReqM (PairReq v))) = unlessM (mypair v) $ do
|
dispatch (Just (PairReqM r@(PairReq v))) =
|
||||||
|
unlessM (mypair v) $
|
||||||
|
pairReqAlert dstatus urlrenderer r
|
||||||
|
dispatch (Just (PairAckM r@(PairAck v))) =
|
||||||
|
unlessM (mypair v) $
|
||||||
|
pairAckAlert dstatus r
|
||||||
|
|
||||||
|
{- Filter out our own pair requests, by checking if we
|
||||||
|
- can verify using the secrets of any of them. -}
|
||||||
|
mypair v = any (verified v . inProgressSecret) . pairingInProgress
|
||||||
|
<$> getDaemonStatus dstatus
|
||||||
|
|
||||||
|
{- Pair request alerts from the same host combine,
|
||||||
|
- so repeated requests do not add additional alerts. -}
|
||||||
|
pairReqAlert :: DaemonStatusHandle -> UrlRenderer -> PairReq -> IO ()
|
||||||
|
pairReqAlert dstatus urlrenderer r@(PairReq v) = do
|
||||||
let pairdata = verifiableVal v
|
let pairdata = verifiableVal v
|
||||||
let repo = remoteUserName pairdata ++ "@" ++
|
let repo = remoteUserName pairdata ++ "@" ++
|
||||||
fromMaybe (showAddr $ remoteAddress pairdata)
|
fromMaybe (showAddr $ remoteAddress pairdata)
|
||||||
(remoteHostName pairdata) ++
|
(remoteHostName pairdata) ++
|
||||||
(remoteDirectory pairdata)
|
(remoteDirectory pairdata)
|
||||||
let msg = repo ++ " is sending a pair request."
|
let msg = repo ++ " is sending a pair request."
|
||||||
{- Pair request alerts from the same host combine,
|
url <- renderUrl urlrenderer (FinishPairR r) []
|
||||||
- so repeated requests do not add additional alerts. -}
|
void $ addAlert dstatus $ pairRequestAlert repo msg $
|
||||||
void $ addAlert dstatus $ pairRequestAlert repo msg
|
AlertButton
|
||||||
dispatch (Just (PairAckM _)) = noop -- TODO
|
{ buttonUrl = url
|
||||||
|
, buttonLabel = T.pack "Respond"
|
||||||
|
}
|
||||||
|
|
||||||
{- Filter out our own pair requests, by checking if we
|
pairAckAlert :: DaemonStatusHandle -> PairAck -> IO ()
|
||||||
- can verify using the secrets of any of them. -}
|
pairAckAlert dstatus r@(PairAck v) = error "TODO"
|
||||||
mypair v = any (verified v . inProgressSecret) . pairingInProgress
|
|
||||||
<$> getDaemonStatus dstatus
|
|
||||||
|
|
|
@ -49,10 +49,11 @@ webAppThread
|
||||||
-> ScanRemoteMap
|
-> ScanRemoteMap
|
||||||
-> TransferQueue
|
-> TransferQueue
|
||||||
-> TransferSlots
|
-> TransferSlots
|
||||||
|
-> UrlRenderer
|
||||||
-> Maybe (IO String)
|
-> Maybe (IO String)
|
||||||
-> Maybe (Url -> FilePath -> IO ())
|
-> Maybe (Url -> FilePath -> IO ())
|
||||||
-> NamedThread
|
-> NamedThread
|
||||||
webAppThread mst dstatus scanremotes transferqueue transferslots postfirstrun onstartup = thread $ do
|
webAppThread mst dstatus scanremotes transferqueue transferslots urlrenderer postfirstrun onstartup = thread $ do
|
||||||
webapp <- WebApp
|
webapp <- WebApp
|
||||||
<$> pure mst
|
<$> pure mst
|
||||||
<*> pure dstatus
|
<*> pure dstatus
|
||||||
|
@ -64,12 +65,14 @@ webAppThread mst dstatus scanremotes transferqueue transferslots postfirstrun on
|
||||||
<*> pure $(embed "static")
|
<*> pure $(embed "static")
|
||||||
<*> newWebAppState
|
<*> newWebAppState
|
||||||
<*> pure postfirstrun
|
<*> pure postfirstrun
|
||||||
|
setUrlRenderer urlrenderer $ yesodRender webapp (pack "")
|
||||||
app <- toWaiAppPlain webapp
|
app <- toWaiAppPlain webapp
|
||||||
app' <- ifM debugEnabled
|
app' <- ifM debugEnabled
|
||||||
( return $ httpDebugLogger app
|
( return $ httpDebugLogger app
|
||||||
, return app
|
, return app
|
||||||
)
|
)
|
||||||
runWebApp app' $ \port -> case mst of
|
runWebApp app' $ \port -> do
|
||||||
|
case mst of
|
||||||
Nothing -> withTempFile "webapp.html" $ \tmpfile _ -> go port webapp tmpfile
|
Nothing -> withTempFile "webapp.html" $ \tmpfile _ -> go port webapp tmpfile
|
||||||
Just st -> go port webapp =<< runThreadState st (fromRepo gitAnnexHtmlShim)
|
Just st -> go port webapp =<< runThreadState st (fromRepo gitAnnexHtmlShim)
|
||||||
where
|
where
|
||||||
|
|
|
@ -20,6 +20,7 @@ import Yesod
|
||||||
import Text.Hamlet
|
import Text.Hamlet
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
|
import Control.Concurrent
|
||||||
|
|
||||||
data NavBarItem = DashBoard | Config | About
|
data NavBarItem = DashBoard | Config | About
|
||||||
deriving (Eq)
|
deriving (Eq)
|
||||||
|
@ -116,3 +117,18 @@ webAppFormAuthToken = do
|
||||||
- With noscript, clicking it GETs the Route. -}
|
- With noscript, clicking it GETs the Route. -}
|
||||||
actionButton :: Route WebApp -> (Maybe String) -> String -> String -> Widget
|
actionButton :: Route WebApp -> (Maybe String) -> String -> String -> Widget
|
||||||
actionButton route label buttonclass iconclass = $(widgetFile "actionbutton")
|
actionButton route label buttonclass iconclass = $(widgetFile "actionbutton")
|
||||||
|
|
||||||
|
type UrlRenderFunc = Route WebApp -> [(Text, Text)] -> Text
|
||||||
|
type UrlRenderer = MVar (UrlRenderFunc)
|
||||||
|
|
||||||
|
newUrlRenderer :: IO UrlRenderer
|
||||||
|
newUrlRenderer = newEmptyMVar
|
||||||
|
|
||||||
|
setUrlRenderer :: UrlRenderer -> (UrlRenderFunc) -> IO ()
|
||||||
|
setUrlRenderer = putMVar
|
||||||
|
|
||||||
|
{- Blocks until the webapp is running and has called setUrlRenderer. -}
|
||||||
|
renderUrl :: UrlRenderer -> Route WebApp -> [(Text, Text)] -> IO Text
|
||||||
|
renderUrl urlrenderer route params = do
|
||||||
|
r <- readMVar urlrenderer
|
||||||
|
return $ r route params
|
||||||
|
|
|
@ -36,24 +36,18 @@ sideBarDisplay = do
|
||||||
$(widgetFile "sidebar/main")
|
$(widgetFile "sidebar/main")
|
||||||
autoUpdate ident NotifierSideBarR (10 :: Int) (10 :: Int)
|
autoUpdate ident NotifierSideBarR (10 :: Int) (10 :: Int)
|
||||||
where
|
where
|
||||||
|
bootstrapclass :: AlertClass -> Text
|
||||||
bootstrapclass Activity = "alert-info"
|
bootstrapclass Activity = "alert-info"
|
||||||
bootstrapclass Warning = "alert"
|
bootstrapclass Warning = "alert"
|
||||||
bootstrapclass Error = "alert-error"
|
bootstrapclass Error = "alert-error"
|
||||||
bootstrapclass Success = "alert-success"
|
bootstrapclass Success = "alert-success"
|
||||||
bootstrapclass Message = "alert-info"
|
bootstrapclass Message = "alert-info"
|
||||||
|
|
||||||
renderalert (alertid, alert) = addalert
|
renderalert (aid, alert) = do
|
||||||
alertid
|
let alertid = show aid
|
||||||
(alertClosable alert)
|
let closable = alertClosable alert
|
||||||
(alertBlockDisplay alert)
|
let block = alertBlockDisplay alert
|
||||||
(bootstrapclass $ alertClass alert)
|
let divclass = bootstrapclass $ alertClass alert
|
||||||
(renderAlertHeader alert)
|
|
||||||
(renderAlertMessage alert)
|
|
||||||
(alertIcon alert)
|
|
||||||
|
|
||||||
addalert :: AlertId -> Bool -> Bool -> Text -> Maybe Text -> Text -> Maybe String -> Widget
|
|
||||||
addalert i closable block divclass heading message icon = do
|
|
||||||
let alertid = show i
|
|
||||||
$(widgetFile "sidebar/alert")
|
$(widgetFile "sidebar/alert")
|
||||||
|
|
||||||
{- Called by client to get a sidebar display.
|
{- Called by client to get a sidebar display.
|
||||||
|
|
|
@ -16,6 +16,7 @@ import Assistant.ScanRemotes
|
||||||
import Assistant.TransferQueue
|
import Assistant.TransferQueue
|
||||||
import Assistant.TransferSlots
|
import Assistant.TransferSlots
|
||||||
import Assistant.Threads.WebApp
|
import Assistant.Threads.WebApp
|
||||||
|
import Assistant.WebApp
|
||||||
import Utility.WebApp
|
import Utility.WebApp
|
||||||
import Utility.Daemon (checkDaemon, lockPidFile)
|
import Utility.Daemon (checkDaemon, lockPidFile)
|
||||||
import Init
|
import Init
|
||||||
|
@ -92,10 +93,12 @@ firstRun = do
|
||||||
scanremotes <- newScanRemoteMap
|
scanremotes <- newScanRemoteMap
|
||||||
transferqueue <- newTransferQueue
|
transferqueue <- newTransferQueue
|
||||||
transferslots <- newTransferSlots
|
transferslots <- newTransferSlots
|
||||||
|
urlrenderer <- newUrlRenderer
|
||||||
v <- newEmptyMVar
|
v <- newEmptyMVar
|
||||||
let callback a = Just $ a v
|
let callback a = Just $ a v
|
||||||
void $ runNamedThread dstatus $
|
void $ runNamedThread dstatus $
|
||||||
webAppThread Nothing dstatus scanremotes transferqueue transferslots
|
webAppThread Nothing dstatus scanremotes
|
||||||
|
transferqueue transferslots urlrenderer
|
||||||
(callback signaler) (callback mainthread)
|
(callback signaler) (callback mainthread)
|
||||||
where
|
where
|
||||||
signaler v = do
|
signaler v = do
|
||||||
|
|
|
@ -1,18 +1,24 @@
|
||||||
<div .alert .fade .in .#{divclass} :block:.alert-block ##{alertid} :closable:onclick="(function( $ ) { $.get('@{CloseAlert i}') })( jQuery );">
|
<div .alert .fade .in .#{divclass} :block:.alert-block ##{alertid} :closable:onclick="(function( $ ) { $.get('@{CloseAlert aid}') })( jQuery );">
|
||||||
$if closable
|
$if closable
|
||||||
<a .close>×</a>
|
<a .close>×</a>
|
||||||
$maybe h <- heading
|
$maybe h <- renderAlertHeader alert
|
||||||
$if block
|
$if block
|
||||||
<h4 .alert-heading>
|
<h4 .alert-heading>
|
||||||
$case icon
|
$case alertIcon alert
|
||||||
$of Nothing
|
$of Nothing
|
||||||
$of Just name
|
$of Just name
|
||||||
<i .icon-#{name}></i> #
|
<i .icon-#{name}></i> #
|
||||||
#{h}
|
#{h}
|
||||||
$else
|
$else
|
||||||
$case icon
|
$case alertIcon alert
|
||||||
$of Nothing
|
$of Nothing
|
||||||
$of Just name
|
$of Just name
|
||||||
<i .icon-#{name}></i> #
|
<i .icon-#{name}></i> #
|
||||||
<strong>#{h}</strong> #
|
<strong>#{h}</strong> #
|
||||||
#{message}
|
#{renderAlertMessage alert}
|
||||||
|
$case alertButton alert
|
||||||
|
$of Nothing
|
||||||
|
$of Just button
|
||||||
|
<br>
|
||||||
|
<a .btn .btn-primary href="#{buttonUrl button}">
|
||||||
|
#{buttonLabel button}
|
||||||
|
|
Loading…
Reference in a new issue