2012-07-31 05:11:32 +00:00
|
|
|
{- git-annex assistant webapp notifications
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012 Joey Hess <id@joeyh.name>
|
2012-07-31 05:11:32 +00:00
|
|
|
-
|
2012-09-24 18:48:47 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2012-07-31 05:11:32 +00:00
|
|
|
-}
|
|
|
|
|
2015-04-22 20:19:05 +00:00
|
|
|
{-# LANGUAGE QuasiQuotes, TemplateHaskell, OverloadedStrings #-}
|
2013-02-27 06:39:22 +00:00
|
|
|
|
2012-07-31 05:11:32 +00:00
|
|
|
module Assistant.WebApp.Notifications where
|
|
|
|
|
|
|
|
import Assistant.Common
|
|
|
|
import Assistant.WebApp
|
2012-09-02 04:27:48 +00:00
|
|
|
import Assistant.WebApp.Types
|
2012-11-03 01:13:06 +00:00
|
|
|
import Assistant.DaemonStatus
|
2012-07-31 05:11:32 +00:00
|
|
|
import Utility.NotificationBroadcaster
|
|
|
|
import Utility.Yesod
|
2016-11-22 18:18:34 +00:00
|
|
|
import Utility.AuthToken
|
2012-07-31 05:11:32 +00:00
|
|
|
|
|
|
|
import Data.Text (Text)
|
|
|
|
import qualified Data.Text as T
|
2012-11-18 17:00:35 +00:00
|
|
|
import qualified Data.Aeson.Types as Aeson
|
2012-07-31 05:11:32 +00:00
|
|
|
|
|
|
|
{- Add to any widget to make it auto-update using long polling.
|
|
|
|
-
|
|
|
|
- The widget should have a html element with an id=ident, which will be
|
|
|
|
- replaced when it's updated.
|
|
|
|
-
|
|
|
|
- The geturl route should return the notifier url to use for polling.
|
|
|
|
-
|
|
|
|
- ms_delay is how long to delay between AJAX updates
|
|
|
|
- ms_startdelay is how long to delay before updating with AJAX at the start
|
|
|
|
-}
|
|
|
|
autoUpdate :: Text -> Route WebApp -> Int -> Int -> Widget
|
2012-11-18 17:00:35 +00:00
|
|
|
autoUpdate tident geturl ms_delay ms_startdelay = do
|
|
|
|
let delay = Aeson.String (T.pack (show ms_delay))
|
|
|
|
let startdelay = Aeson.String (T.pack (show ms_startdelay))
|
|
|
|
let ident = Aeson.String tident
|
2012-07-31 05:24:49 +00:00
|
|
|
$(widgetFile "notifications/longpolling")
|
2012-07-31 05:11:32 +00:00
|
|
|
|
|
|
|
{- Notifier urls are requested by the javascript, to avoid allocation
|
|
|
|
- of NotificationIds when noscript pages are loaded. This constructs a
|
|
|
|
- notifier url for a given Route and NotificationBroadcaster.
|
|
|
|
-}
|
2012-11-03 01:13:06 +00:00
|
|
|
notifierUrl :: (NotificationId -> Route WebApp) -> Assistant NotificationBroadcaster -> Handler RepPlain
|
|
|
|
notifierUrl route broadcaster = do
|
|
|
|
(urlbits, _params) <- renderRoute . route <$> newNotifier broadcaster
|
2012-07-31 05:11:32 +00:00
|
|
|
webapp <- getYesod
|
|
|
|
return $ RepPlain $ toContent $ T.concat
|
|
|
|
[ "/"
|
|
|
|
, T.intercalate "/" urlbits
|
|
|
|
, "?auth="
|
2014-03-13 01:21:10 +00:00
|
|
|
, fromAuthToken (authToken webapp)
|
2012-07-31 05:11:32 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
getNotifierTransfersR :: Handler RepPlain
|
2012-11-03 01:13:06 +00:00
|
|
|
getNotifierTransfersR = notifierUrl TransfersR getTransferBroadcaster
|
2012-07-31 05:11:32 +00:00
|
|
|
|
|
|
|
getNotifierSideBarR :: Handler RepPlain
|
2012-11-03 01:13:06 +00:00
|
|
|
getNotifierSideBarR = notifierUrl SideBarR getAlertBroadcaster
|
|
|
|
|
2012-11-13 21:50:54 +00:00
|
|
|
getNotifierRepoListR :: RepoSelector -> Handler RepPlain
|
|
|
|
getNotifierRepoListR reposelector = notifierUrl route getRepoListBroadcaster
|
|
|
|
where
|
2013-09-27 04:35:37 +00:00
|
|
|
route nid = RepoListR nid reposelector
|
2012-11-13 21:50:54 +00:00
|
|
|
|
global webapp redirects, to finish upgrades
When an automatic upgrade completes, or when the user clicks on the upgrade
button in one webapp, but also has it open in another browser window/tab,
we have a problem: The current web server is going to stop running in
minutes, but there is no way to send a redirect to the web browser to the
new url.
To solve this, used long polling, so the webapp is always listening for
urls it should redirect to. This allows globally redirecting every open
webapp. Works great! Tested with 2 web browsers with 2 tabs each.
May be useful for other purposes later too, dunno.
The overhead is 2 http requests per page load in the webapp. Due to yesod's
speed, this does not seem to noticibly delay it. Only 1 of the requests
could possibly block the page load, the other is async.
2013-11-23 18:47:38 +00:00
|
|
|
getNotifierGlobalRedirR :: Handler RepPlain
|
|
|
|
getNotifierGlobalRedirR = notifierUrl GlobalRedirR getGlobalRedirBroadcaster
|
|
|
|
|
2012-11-03 01:13:06 +00:00
|
|
|
getTransferBroadcaster :: Assistant NotificationBroadcaster
|
|
|
|
getTransferBroadcaster = transferNotifier <$> getDaemonStatus
|
|
|
|
|
|
|
|
getAlertBroadcaster :: Assistant NotificationBroadcaster
|
|
|
|
getAlertBroadcaster = alertNotifier <$> getDaemonStatus
|
|
|
|
|
2012-11-13 21:50:54 +00:00
|
|
|
getRepoListBroadcaster :: Assistant NotificationBroadcaster
|
|
|
|
getRepoListBroadcaster = syncRemotesNotifier <$> getDaemonStatus
|
global webapp redirects, to finish upgrades
When an automatic upgrade completes, or when the user clicks on the upgrade
button in one webapp, but also has it open in another browser window/tab,
we have a problem: The current web server is going to stop running in
minutes, but there is no way to send a redirect to the web browser to the
new url.
To solve this, used long polling, so the webapp is always listening for
urls it should redirect to. This allows globally redirecting every open
webapp. Works great! Tested with 2 web browsers with 2 tabs each.
May be useful for other purposes later too, dunno.
The overhead is 2 http requests per page load in the webapp. Due to yesod's
speed, this does not seem to noticibly delay it. Only 1 of the requests
could possibly block the page load, the other is async.
2013-11-23 18:47:38 +00:00
|
|
|
|
|
|
|
getGlobalRedirBroadcaster :: Assistant NotificationBroadcaster
|
|
|
|
getGlobalRedirBroadcaster = globalRedirNotifier <$> getDaemonStatus
|
|
|
|
|
2013-11-25 19:14:34 +00:00
|
|
|
getGlobalRedirR :: NotificationId -> Handler RepPlain
|
global webapp redirects, to finish upgrades
When an automatic upgrade completes, or when the user clicks on the upgrade
button in one webapp, but also has it open in another browser window/tab,
we have a problem: The current web server is going to stop running in
minutes, but there is no way to send a redirect to the web browser to the
new url.
To solve this, used long polling, so the webapp is always listening for
urls it should redirect to. This allows globally redirecting every open
webapp. Works great! Tested with 2 web browsers with 2 tabs each.
May be useful for other purposes later too, dunno.
The overhead is 2 http requests per page load in the webapp. Due to yesod's
speed, this does not seem to noticibly delay it. Only 1 of the requests
could possibly block the page load, the other is async.
2013-11-23 18:47:38 +00:00
|
|
|
getGlobalRedirR nid = do
|
|
|
|
waitNotifier getGlobalRedirBroadcaster nid
|
2013-11-25 19:14:34 +00:00
|
|
|
maybe (getGlobalRedirR nid) (return . RepPlain . toContent . T.pack)
|
global webapp redirects, to finish upgrades
When an automatic upgrade completes, or when the user clicks on the upgrade
button in one webapp, but also has it open in another browser window/tab,
we have a problem: The current web server is going to stop running in
minutes, but there is no way to send a redirect to the web browser to the
new url.
To solve this, used long polling, so the webapp is always listening for
urls it should redirect to. This allows globally redirecting every open
webapp. Works great! Tested with 2 web browsers with 2 tabs each.
May be useful for other purposes later too, dunno.
The overhead is 2 http requests per page load in the webapp. Due to yesod's
speed, this does not seem to noticibly delay it. Only 1 of the requests
could possibly block the page load, the other is async.
2013-11-23 18:47:38 +00:00
|
|
|
=<< globalRedirUrl <$> liftAssistant getDaemonStatus
|