2012-07-31 05:11:32 +00:00
|
|
|
{- git-annex assistant webapp dashboard
|
|
|
|
-
|
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
|
|
|
-}
|
|
|
|
|
2012-08-03 13:44:43 +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
|
2013-03-15 04:34:42 +00:00
|
|
|
import Assistant.WebApp.RepoList
|
2012-07-31 05:11:32 +00:00
|
|
|
import Assistant.WebApp.Notifications
|
|
|
|
import Assistant.TransferQueue
|
2013-10-26 20:54:49 +00:00
|
|
|
import Assistant.TransferSlots
|
2013-03-19 16:51:22 +00:00
|
|
|
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
|
2012-08-03 13:44:43 +00:00
|
|
|
import qualified Git
|
2012-07-31 05:11:32 +00:00
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
import qualified Text.Hamlet as Hamlet
|
2012-07-31 05:11:32 +00:00
|
|
|
import qualified Data.Map as M
|
2012-08-03 14:18:57 +00:00
|
|
|
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. -}
|
2013-12-19 02:39:15 +00:00
|
|
|
transfersDisplay :: Widget
|
|
|
|
transfersDisplay = do
|
2013-10-26 20:54:49 +00:00
|
|
|
current <- liftAssistant $ M.toList <$> getCurrentTransfers
|
2013-03-16 04:12:28 +00:00
|
|
|
queued <- take 10 <$> liftAssistant getTransferQueue
|
2012-07-31 05:11:32 +00:00
|
|
|
autoUpdate ident NotifierTransfersR (10 :: Int) (10 :: Int)
|
2012-08-29 17:41:47 +00:00
|
|
|
let transfers = simplifyTransfers $ current ++ queued
|
2013-03-19 16:51:22 +00:00
|
|
|
let transfersrunning = not $ null transfers
|
|
|
|
scanrunning <- if transfersrunning
|
|
|
|
then return False
|
|
|
|
else liftAssistant $ transferScanRunning <$> getDaemonStatus
|
2013-03-15 04:34:42 +00:00
|
|
|
$(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
|
|
|
|
2012-08-29 19:24:09 +00:00
|
|
|
{- Simplifies a list of transfers, avoiding display of redundant
|
|
|
|
- equivilant transfers. -}
|
2012-08-29 17:41:47 +00:00
|
|
|
simplifyTransfers :: [(Transfer, TransferInfo)] -> [(Transfer, TransferInfo)]
|
|
|
|
simplifyTransfers [] = []
|
|
|
|
simplifyTransfers (x:[]) = [x]
|
|
|
|
simplifyTransfers (v@(t1, _):r@((t2, _):l))
|
2012-08-29 19:24:09 +00:00
|
|
|
| equivilantTransfer t1 t2 = simplifyTransfers (v:l)
|
2013-10-02 05:06:59 +00:00
|
|
|
| otherwise = v : simplifyTransfers r
|
2012-08-29 17:41:47 +00:00
|
|
|
|
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
|
|
|
-}
|
2013-06-27 05:15:28 +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
|
|
|
|
2013-12-19 02:39:15 +00:00
|
|
|
p <- widgetToPageContent transfersDisplay
|
2014-10-24 00:26:46 +00:00
|
|
|
withUrlRenderer $ [hamlet|^{pageBody p}|]
|
2012-07-31 05:11:32 +00:00
|
|
|
|
|
|
|
{- The main dashboard. -}
|
|
|
|
dashboard :: Bool -> Widget
|
|
|
|
dashboard warnNoScript = do
|
2013-03-15 04:34:42 +00:00
|
|
|
let repolist = repoListDisplay $
|
|
|
|
mainRepoSelector { nudgeAddMore = True }
|
2013-12-19 02:39:15 +00:00
|
|
|
let transferlist = transfersDisplay
|
2012-07-31 05:24:49 +00:00
|
|
|
$(widgetFile "dashboard/main")
|
2012-07-31 05:11:32 +00:00
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
getDashboardR :: Handler Html
|
2013-10-02 05:06:59 +00:00
|
|
|
getDashboardR = ifM inFirstRun
|
2012-12-30 03:10:18 +00:00
|
|
|
( redirect ConfigurationR
|
2012-11-25 04:26:46 +00:00
|
|
|
, page "" (Just DashBoard) $ dashboard True
|
2012-07-31 18:23:17 +00:00
|
|
|
)
|
2012-07-31 06:30:26 +00:00
|
|
|
|
2012-09-18 21:50:07 +00:00
|
|
|
{- Used to test if the webapp is running. -}
|
2013-12-09 21:26:25 +00:00
|
|
|
headDashboardR :: Handler ()
|
|
|
|
headDashboardR = noop
|
2012-09-18 21:50:07 +00:00
|
|
|
|
2013-03-13 02:18:36 +00:00
|
|
|
{- Same as DashboardR, except no autorefresh at all (and no noscript warning). -}
|
2013-06-27 05:15:28 +00:00
|
|
|
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. -}
|
2013-06-27 05:15:28 +00:00
|
|
|
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 delayseconds = 3 :: Int
|
|
|
|
let this = NoScriptAutoR
|
2013-06-27 05:15:28 +00:00
|
|
|
toWidgetHead $(Hamlet.hamletFile $ hamletTemplate "dashboard/metarefresh")
|
2012-07-31 05:11:32 +00:00
|
|
|
dashboard False
|
2012-08-03 13:44:43 +00:00
|
|
|
|
|
|
|
{- 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
|
2012-08-08 20:06:01 +00:00
|
|
|
|
2012-08-03 13:44:43 +00:00
|
|
|
{- 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
|
2012-08-03 14:18:57 +00:00
|
|
|
- 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. -}
|
2012-08-03 13:44:43 +00:00
|
|
|
openFileBrowser :: Handler Bool
|
|
|
|
openFileBrowser = do
|
2013-03-04 20:36:38 +00:00
|
|
|
path <- liftAnnex $ fromRepo Git.repoPath
|
2013-12-09 20:39:10 +00:00
|
|
|
#ifdef darwin_HOST_OS
|
|
|
|
let cmd = "open"
|
2014-06-17 18:18:15 +00:00
|
|
|
let p = proc cmd [path]
|
2013-12-09 20:39:10 +00:00
|
|
|
#else
|
|
|
|
#ifdef mingw32_HOST_OS
|
2014-06-17 18:18:15 +00:00
|
|
|
{- Changing to the directory and then opening . works around
|
|
|
|
- spaces in directory name, etc. -}
|
2013-12-09 20:39:10 +00:00
|
|
|
let cmd = "cmd"
|
2014-06-17 18:18:15 +00:00
|
|
|
let p = (proc cmd ["/c start ."]) { cwd = Just path }
|
2013-12-09 20:39:10 +00:00
|
|
|
#else
|
|
|
|
let cmd = "xdg-open"
|
2014-06-17 18:18:15 +00:00
|
|
|
let p = proc cmd [path]
|
2013-12-09 20:39:10 +00:00
|
|
|
#endif
|
|
|
|
#endif
|
|
|
|
ifM (liftIO $ inPath cmd)
|
2012-08-03 14:18:57 +00:00
|
|
|
( do
|
2014-02-13 17:08:08 +00:00
|
|
|
let run = void $ liftIO $ forkIO $ void $
|
2014-06-17 18:18:15 +00:00
|
|
|
createProcess p
|
2014-02-13 17:08:08 +00:00
|
|
|
run
|
|
|
|
#ifdef mingw32_HOST_OS
|
|
|
|
{- On windows, if the file browser is not
|
|
|
|
- already open, it comes up below the
|
|
|
|
- web browser when started.
|
|
|
|
-
|
|
|
|
- Running it a second time brings it
|
|
|
|
- to the foreground.
|
|
|
|
-
|
|
|
|
- Seems to need a delay long enough for the file
|
|
|
|
- browser to be open in order to work. Here 1
|
|
|
|
- second. -}
|
|
|
|
liftIO $ threadDelay 1000000
|
|
|
|
run
|
|
|
|
#endif
|
2012-08-03 14:18:57 +00:00
|
|
|
return True
|
2012-08-03 13:44:43 +00:00
|
|
|
, do
|
2013-01-03 22:50:30 +00:00
|
|
|
void $ redirect $ "file://" ++ path
|
2012-08-03 13:44:43 +00:00
|
|
|
return False
|
|
|
|
)
|
2012-08-08 20:06:01 +00:00
|
|
|
|
|
|
|
{- 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
|
2012-08-08 20:06:01 +00:00
|
|
|
postPauseTransferR :: Transfer -> Handler ()
|
2013-10-26 20:54:49 +00:00
|
|
|
postPauseTransferR = liftAssistant . pauseTransfer
|
2012-08-08 20:06:01 +00:00
|
|
|
getStartTransferR :: Transfer -> Handler ()
|
2013-10-02 05:06:59 +00:00
|
|
|
getStartTransferR = noscript postStartTransferR
|
2012-08-08 20:06:01 +00:00
|
|
|
postStartTransferR :: Transfer -> Handler ()
|
2013-10-26 20:54:49 +00:00
|
|
|
postStartTransferR = liftAssistant . startTransfer
|
2012-08-08 20:06:01 +00:00
|
|
|
getCancelTransferR :: Transfer -> Handler ()
|
2013-10-02 05:06:59 +00:00
|
|
|
getCancelTransferR = noscript postCancelTransferR
|
2012-08-08 20:06:01 +00:00
|
|
|
postCancelTransferR :: Transfer -> Handler ()
|
2013-10-26 20:54:49 +00:00
|
|
|
postCancelTransferR = liftAssistant . cancelTransfer False
|
2013-10-02 05:06:59 +00:00
|
|
|
|
|
|
|
noscript :: (Transfer -> Handler ()) -> Transfer -> Handler ()
|
|
|
|
noscript a t = a t >> redirectBack
|