2012-07-31 05:11:32 +00:00
|
|
|
{- git-annex assistant webapp dashboard
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
|
|
|
|
|
|
|
|
module Assistant.WebApp.DashBoard where
|
|
|
|
|
|
|
|
import Assistant.Common
|
|
|
|
import Assistant.WebApp
|
|
|
|
import Assistant.WebApp.SideBar
|
|
|
|
import Assistant.WebApp.Notifications
|
|
|
|
import Assistant.WebApp.Configurators
|
|
|
|
import Assistant.DaemonStatus
|
|
|
|
import Assistant.TransferQueue
|
|
|
|
import Utility.NotificationBroadcaster
|
|
|
|
import Utility.Yesod
|
|
|
|
import Logs.Transfer
|
|
|
|
import Utility.Percentage
|
|
|
|
import Utility.DataUnits
|
|
|
|
import Types.Key
|
|
|
|
import qualified Remote
|
|
|
|
|
|
|
|
import Yesod
|
|
|
|
import Text.Hamlet
|
|
|
|
import qualified Data.Map as M
|
|
|
|
|
|
|
|
{- A display of currently running and queued transfers.
|
|
|
|
-
|
|
|
|
- Or, if there have never been any this run, an intro display. -}
|
|
|
|
transfersDisplay :: Bool -> Widget
|
|
|
|
transfersDisplay warnNoScript = do
|
|
|
|
webapp <- lift getYesod
|
2012-07-31 15:19:40 +00:00
|
|
|
current <- lift $ runAnnex [] $
|
2012-07-31 05:11:32 +00:00
|
|
|
M.toList . currentTransfers
|
|
|
|
<$> liftIO (getDaemonStatus $ daemonStatus webapp)
|
|
|
|
queued <- liftIO $ getTransferQueue $ transferQueue webapp
|
|
|
|
let ident = "transfers"
|
|
|
|
autoUpdate ident NotifierTransfersR (10 :: Int) (10 :: Int)
|
|
|
|
let transfers = current ++ queued
|
|
|
|
if null transfers
|
|
|
|
then ifM (lift $ showIntro <$> getWebAppState)
|
|
|
|
( introDisplay ident
|
2012-07-31 05:24:49 +00:00
|
|
|
, $(widgetFile "dashboard/transfers")
|
2012-07-31 05:11:32 +00:00
|
|
|
)
|
2012-07-31 05:24:49 +00:00
|
|
|
else $(widgetFile "dashboard/transfers")
|
2012-07-31 05:11:32 +00:00
|
|
|
|
|
|
|
{- Called by client to get a display of currently in process transfers.
|
|
|
|
-
|
|
|
|
- Returns a div, which will be inserted into the calling page.
|
|
|
|
-
|
|
|
|
- Note that the head of the widget is not included, only its
|
|
|
|
- body is. To get the widget head content, the widget is also
|
|
|
|
- inserted onto the getHomeR page.
|
|
|
|
-}
|
|
|
|
getTransfersR :: NotificationId -> Handler RepHtml
|
|
|
|
getTransfersR nid = do
|
|
|
|
waitNotifier transferNotifier nid
|
|
|
|
|
|
|
|
page <- widgetToPageContent $ transfersDisplay False
|
|
|
|
hamletToRepHtml $ [hamlet|^{pageBody page}|]
|
|
|
|
|
|
|
|
{- The main dashboard. -}
|
|
|
|
dashboard :: Bool -> Widget
|
|
|
|
dashboard warnNoScript = do
|
|
|
|
sideBarDisplay
|
|
|
|
let content = transfersDisplay warnNoScript
|
2012-07-31 05:24:49 +00:00
|
|
|
$(widgetFile "dashboard/main")
|
2012-07-31 05:11:32 +00:00
|
|
|
|
|
|
|
getHomeR :: Handler RepHtml
|
2012-07-31 06:30:26 +00:00
|
|
|
getHomeR = bootstrap (Just DashBoard) $ dashboard True
|
|
|
|
|
|
|
|
{- Same as HomeR, except no autorefresh at all (and no noscript warning). -}
|
|
|
|
getNoScriptR :: Handler RepHtml
|
|
|
|
getNoScriptR = bootstrap (Just DashBoard) $ dashboard False
|
2012-07-31 05:11:32 +00:00
|
|
|
|
|
|
|
{- Same as HomeR, except with autorefreshing via meta refresh. -}
|
|
|
|
getNoScriptAutoR :: Handler RepHtml
|
2012-07-31 06:30:26 +00:00
|
|
|
getNoScriptAutoR = bootstrap (Just DashBoard) $ do
|
2012-07-31 05:11:32 +00:00
|
|
|
let ident = NoScriptR
|
|
|
|
let delayseconds = 3 :: Int
|
|
|
|
let this = NoScriptAutoR
|
2012-07-31 05:24:49 +00:00
|
|
|
toWidgetHead $(hamletFile $ hamletTemplate "dashboard/metarefresh")
|
2012-07-31 05:11:32 +00:00
|
|
|
dashboard False
|