git-annex/Assistant/WebApp/DashBoard.hs

160 lines
5.2 KiB
Haskell
Raw Normal View History

2012-07-31 05:11:32 +00:00
{- git-annex assistant webapp dashboard
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU AGPL version 3 or higher.
2012-07-31 05:11:32 +00:00
-}
{-# LANGUAGE CPP, TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
2012-07-31 05:11:32 +00:00
module Assistant.WebApp.DashBoard where
2012-11-25 04:26:46 +00:00
import Assistant.WebApp.Common
import Assistant.WebApp.RepoList
2012-07-31 05:11:32 +00:00
import Assistant.WebApp.Notifications
import Assistant.TransferQueue
import Assistant.TransferSlots
import Assistant.DaemonStatus
2012-07-31 05:11:32 +00:00
import Utility.NotificationBroadcaster
import Logs.Transfer
import Utility.Percentage
import Utility.DataUnits
import Types.Key
import qualified Remote
import qualified Git
2012-07-31 05:11:32 +00:00
import qualified Text.Hamlet as Hamlet
2012-07-31 05:11:32 +00:00
import qualified Data.Map as M
import Control.Concurrent
2012-07-31 05:11:32 +00:00
2013-03-28 19:03:51 +00:00
{- A display of currently running and queued transfers. -}
2012-07-31 05:11:32 +00:00
transfersDisplay :: Bool -> Widget
transfersDisplay warnNoScript = do
webapp <- liftH getYesod
current <- liftAssistant $ M.toList <$> getCurrentTransfers
queued <- take 10 <$> liftAssistant getTransferQueue
2012-07-31 05:11:32 +00:00
autoUpdate ident NotifierTransfersR (10 :: Int) (10 :: Int)
let transfers = simplifyTransfers $ current ++ queued
let transfersrunning = not $ null transfers
scanrunning <- if transfersrunning
then return False
else liftAssistant $ transferScanRunning <$> getDaemonStatus
$(widgetFile "dashboard/transfers")
2012-10-31 06:34:03 +00:00
where
ident = "transfers"
isrunning info = not $
transferPaused info || isNothing (startedTime info)
2012-07-31 05:11:32 +00:00
{- Simplifies a list of transfers, avoiding display of redundant
- equivilant transfers. -}
simplifyTransfers :: [(Transfer, TransferInfo)] -> [(Transfer, TransferInfo)]
simplifyTransfers [] = []
simplifyTransfers (x:[]) = [x]
simplifyTransfers (v@(t1, _):r@((t2, _):l))
| equivilantTransfer t1 t2 = simplifyTransfers (v:l)
2013-10-02 05:06:59 +00:00
| otherwise = v : simplifyTransfers r
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
2013-03-13 02:18:36 +00:00
- inserted onto the getDashboardR page.
2012-07-31 05:11:32 +00:00
-}
getTransfersR :: NotificationId -> Handler Html
2012-07-31 05:11:32 +00:00
getTransfersR nid = do
2012-11-03 01:13:06 +00:00
waitNotifier getTransferBroadcaster nid
2012-07-31 05:11:32 +00:00
2012-11-25 04:26:46 +00:00
p <- widgetToPageContent $ transfersDisplay False
giveUrlRenderer $ [hamlet|^{pageBody p}|]
2012-07-31 05:11:32 +00:00
{- The main dashboard. -}
dashboard :: Bool -> Widget
dashboard warnNoScript = do
let repolist = repoListDisplay $
mainRepoSelector { nudgeAddMore = True }
let transferlist = transfersDisplay warnNoScript
2012-07-31 05:24:49 +00:00
$(widgetFile "dashboard/main")
2012-07-31 05:11:32 +00:00
getDashboardR :: Handler Html
2013-10-02 05:06:59 +00:00
getDashboardR = ifM inFirstRun
( redirect ConfigurationR
2012-11-25 04:26:46 +00:00
, page "" (Just DashBoard) $ dashboard True
2012-07-31 18:23:17 +00:00
)
{- Used to test if the webapp is running. -}
headDashboardR :: Handler ()
headDashboardR = noop
2013-03-13 02:18:36 +00:00
{- Same as DashboardR, except no autorefresh at all (and no noscript warning). -}
getNoScriptR :: Handler Html
2012-11-25 04:26:46 +00:00
getNoScriptR = page "" (Just DashBoard) $ dashboard False
2012-07-31 05:11:32 +00:00
2013-03-13 02:18:36 +00:00
{- Same as DashboardR, except with autorefreshing via meta refresh. -}
getNoScriptAutoR :: Handler Html
2012-11-25 04:26:46 +00:00
getNoScriptAutoR = page "" (Just DashBoard) $ do
2012-07-31 05:11:32 +00:00
let ident = NoScriptR
let delayseconds = 3 :: Int
let this = NoScriptAutoR
toWidgetHead $(Hamlet.hamletFile $ hamletTemplate "dashboard/metarefresh")
2012-07-31 05:11:32 +00:00
dashboard False
{- The javascript code does a post. -}
postFileBrowserR :: Handler ()
postFileBrowserR = void openFileBrowser
{- Used by non-javascript browsers, where clicking on the link actually
- opens this page, so we redirect back to the referrer. -}
getFileBrowserR :: Handler ()
2013-10-02 05:06:59 +00:00
getFileBrowserR = whenM openFileBrowser redirectBack
{- Opens the system file browser on the repo, or, as a fallback,
- goes to a file:// url. Returns True if it's ok to redirect away
- from the page (ie, the system file browser was opened).
-
- Note that the command is opened using a different thread, to avoid
- blocking the response to the browser on it. -}
openFileBrowser :: Handler Bool
openFileBrowser = do
path <- liftAnnex $ fromRepo Git.repoPath
#ifdef darwin_HOST_OS
let cmd = "open"
let params = [Param path]
#else
#ifdef mingw32_HOST_OS
let cmd = "cmd"
let params = [Param $ "/c start " ++ path]
#else
let cmd = "xdg-open"
let params = [Param path]
#endif
#endif
ifM (liftIO $ inPath cmd)
( do
void $ liftIO $ forkIO $ void $
boolSystem cmd params
return True
, do
void $ redirect $ "file://" ++ path
return False
)
{- Transfer controls. The GET is done in noscript mode and redirects back
- to the referring page. The POST is called by javascript. -}
getPauseTransferR :: Transfer -> Handler ()
2013-10-02 05:06:59 +00:00
getPauseTransferR = noscript postPauseTransferR
postPauseTransferR :: Transfer -> Handler ()
postPauseTransferR = liftAssistant . pauseTransfer
getStartTransferR :: Transfer -> Handler ()
2013-10-02 05:06:59 +00:00
getStartTransferR = noscript postStartTransferR
postStartTransferR :: Transfer -> Handler ()
postStartTransferR = liftAssistant . startTransfer
getCancelTransferR :: Transfer -> Handler ()
2013-10-02 05:06:59 +00:00
getCancelTransferR = noscript postCancelTransferR
postCancelTransferR :: Transfer -> Handler ()
postCancelTransferR = liftAssistant . cancelTransfer False
2013-10-02 05:06:59 +00:00
noscript :: (Transfer -> Handler ()) -> Transfer -> Handler ()
noscript a t = a t >> redirectBack