2012-07-26 01:26:13 +00:00
|
|
|
{- git-annex assistant webapp
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2012-07-29 12:52:57 +00:00
|
|
|
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
|
2012-07-29 01:21:22 +00:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
2012-07-26 01:26:13 +00:00
|
|
|
|
|
|
|
module Assistant.Threads.WebApp where
|
|
|
|
|
|
|
|
import Assistant.Common
|
2012-07-26 03:13:01 +00:00
|
|
|
import Assistant.ThreadedMonad
|
2012-07-26 01:26:13 +00:00
|
|
|
import Assistant.DaemonStatus
|
2012-07-27 15:47:34 +00:00
|
|
|
import Assistant.TransferQueue
|
2012-07-29 15:31:06 +00:00
|
|
|
import Assistant.Alert hiding (Widget)
|
2012-07-29 01:21:22 +00:00
|
|
|
import Utility.NotificationBroadcaster
|
2012-07-26 01:26:13 +00:00
|
|
|
import Utility.WebApp
|
2012-07-26 06:45:01 +00:00
|
|
|
import Utility.Yesod
|
2012-07-26 07:38:20 +00:00
|
|
|
import Utility.FileMode
|
|
|
|
import Utility.TempFile
|
2012-07-26 06:45:01 +00:00
|
|
|
import Git
|
2012-07-27 15:47:34 +00:00
|
|
|
import Logs.Transfer
|
|
|
|
import Utility.Percentage
|
|
|
|
import Utility.DataUnits
|
|
|
|
import Types.Key
|
|
|
|
import qualified Remote
|
2012-07-30 01:54:23 +00:00
|
|
|
import Logs.Web (webUUID)
|
2012-07-30 04:31:33 +00:00
|
|
|
import Logs.Trust
|
2012-07-30 02:11:01 +00:00
|
|
|
import Annex.UUID (getUUID)
|
2012-07-26 01:26:13 +00:00
|
|
|
|
|
|
|
import Yesod
|
2012-07-26 06:45:01 +00:00
|
|
|
import Yesod.Static
|
2012-07-26 03:50:29 +00:00
|
|
|
import Text.Hamlet
|
2012-07-26 03:13:01 +00:00
|
|
|
import Network.Socket (PortNumber)
|
2012-07-26 07:38:20 +00:00
|
|
|
import Text.Blaze.Renderer.String
|
2012-07-27 15:47:34 +00:00
|
|
|
import Data.Text (Text, pack, unpack)
|
|
|
|
import qualified Data.Map as M
|
2012-07-30 01:54:23 +00:00
|
|
|
import Control.Concurrent.STM
|
2012-07-26 08:50:09 +00:00
|
|
|
|
|
|
|
thisThread :: String
|
|
|
|
thisThread = "WebApp"
|
2012-07-26 01:26:13 +00:00
|
|
|
|
2012-07-26 06:45:01 +00:00
|
|
|
data WebApp = WebApp
|
2012-07-27 01:51:56 +00:00
|
|
|
{ threadState :: ThreadState
|
|
|
|
, daemonStatus :: DaemonStatusHandle
|
2012-07-27 15:47:34 +00:00
|
|
|
, transferQueue :: TransferQueue
|
2012-07-26 08:50:09 +00:00
|
|
|
, secretToken :: Text
|
2012-07-30 01:54:23 +00:00
|
|
|
, relDir :: FilePath
|
2012-07-26 06:45:01 +00:00
|
|
|
, getStatic :: Static
|
2012-07-30 01:54:23 +00:00
|
|
|
, webAppState :: TMVar WebAppState
|
2012-07-26 06:45:01 +00:00
|
|
|
}
|
|
|
|
|
2012-07-30 01:54:23 +00:00
|
|
|
data WebAppState = WebAppState
|
|
|
|
{ showIntro :: Bool
|
|
|
|
}
|
|
|
|
|
|
|
|
newWebAppState :: IO (TMVar WebAppState)
|
|
|
|
newWebAppState = liftIO $ atomically $
|
|
|
|
newTMVar $ WebAppState { showIntro = True }
|
|
|
|
|
|
|
|
getWebAppState :: forall sub. GHandler sub WebApp WebAppState
|
|
|
|
getWebAppState = liftIO . atomically . readTMVar =<< webAppState <$> getYesod
|
|
|
|
|
|
|
|
modifyWebAppState :: forall sub. (WebAppState -> WebAppState) -> GHandler sub WebApp ()
|
|
|
|
modifyWebAppState a = go =<< webAppState <$> getYesod
|
|
|
|
where
|
|
|
|
go s = liftIO $ atomically $ do
|
|
|
|
v <- takeTMVar s
|
|
|
|
putTMVar s $ a v
|
|
|
|
|
2012-07-29 12:52:57 +00:00
|
|
|
waitNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> NotificationId -> GHandler sub WebApp ()
|
|
|
|
waitNotifier selector nid = do
|
|
|
|
notifier <- getNotifier selector
|
|
|
|
liftIO $ waitNotification $ notificationHandleFromId notifier nid
|
|
|
|
|
|
|
|
newNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationId
|
|
|
|
newNotifier selector = do
|
|
|
|
notifier <- getNotifier selector
|
|
|
|
liftIO $ notificationHandleToId <$> newNotificationHandle notifier
|
|
|
|
|
|
|
|
getNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationBroadcaster
|
|
|
|
getNotifier selector = do
|
|
|
|
webapp <- getYesod
|
|
|
|
liftIO $ selector <$> getDaemonStatus (daemonStatus webapp)
|
2012-07-29 07:23:17 +00:00
|
|
|
|
2012-07-26 06:45:01 +00:00
|
|
|
staticFiles "static"
|
2012-07-26 01:26:13 +00:00
|
|
|
|
|
|
|
mkYesod "WebApp" [parseRoutes|
|
|
|
|
/ HomeR GET
|
2012-07-29 04:08:14 +00:00
|
|
|
/noscript NoScriptR GET
|
2012-07-29 04:55:22 +00:00
|
|
|
/noscriptauto NoScriptAutoR GET
|
2012-07-29 03:55:41 +00:00
|
|
|
/transfers/#NotificationId TransfersR GET
|
2012-07-29 07:23:17 +00:00
|
|
|
/sidebar/#NotificationId SideBarR GET
|
2012-07-30 18:08:22 +00:00
|
|
|
/closealert/#AlertId CloseAlert GET
|
2012-07-26 01:26:13 +00:00
|
|
|
/config ConfigR GET
|
2012-07-30 01:54:23 +00:00
|
|
|
/addrepository AddRepositoryR GET
|
2012-07-26 09:20:52 +00:00
|
|
|
/static StaticR Static getStatic
|
2012-07-26 01:26:13 +00:00
|
|
|
|]
|
|
|
|
|
2012-07-29 01:21:22 +00:00
|
|
|
instance PathPiece NotificationId where
|
|
|
|
toPathPiece = pack . show
|
|
|
|
fromPathPiece = readish . unpack
|
|
|
|
|
2012-07-30 18:08:22 +00:00
|
|
|
instance PathPiece AlertId where
|
|
|
|
toPathPiece = pack . show
|
|
|
|
fromPathPiece = readish . unpack
|
|
|
|
|
2012-07-26 06:45:01 +00:00
|
|
|
instance Yesod WebApp where
|
2012-07-29 07:23:17 +00:00
|
|
|
defaultLayout content = do
|
2012-07-26 06:45:01 +00:00
|
|
|
webapp <- getYesod
|
2012-07-27 08:48:50 +00:00
|
|
|
page <- widgetToPageContent $ do
|
|
|
|
addStylesheet $ StaticR css_bootstrap_css
|
|
|
|
addStylesheet $ StaticR css_bootstrap_responsive_css
|
|
|
|
addScript $ StaticR jquery_full_js
|
|
|
|
addScript $ StaticR js_bootstrap_dropdown_js
|
2012-07-30 18:50:32 +00:00
|
|
|
addScript $ StaticR js_bootstrap_modal_js
|
2012-07-28 00:47:48 +00:00
|
|
|
$(widgetFile "page")
|
2012-07-27 08:48:50 +00:00
|
|
|
hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap")
|
2012-07-26 01:26:13 +00:00
|
|
|
|
2012-07-26 08:50:09 +00:00
|
|
|
{- Require an auth token be set when accessing any (non-static route) -}
|
|
|
|
isAuthorized _ _ = checkAuthToken secretToken
|
|
|
|
|
|
|
|
{- Add the auth token to every url generated, except static subsite
|
|
|
|
- urls (which can show up in Permission Denied pages). -}
|
|
|
|
joinPath = insertAuthToken secretToken excludeStatic
|
|
|
|
where
|
|
|
|
excludeStatic [] = True
|
|
|
|
excludeStatic (p:_) = p /= "static"
|
|
|
|
|
2012-07-26 16:41:20 +00:00
|
|
|
makeSessionBackend = webAppSessionBackend
|
2012-07-26 21:56:24 +00:00
|
|
|
jsLoader _ = BottomOfHeadBlocking
|
2012-07-26 16:10:53 +00:00
|
|
|
|
2012-07-29 04:55:22 +00:00
|
|
|
{- Add to any widget to make it auto-update using long polling.
|
2012-07-27 01:03:46 +00:00
|
|
|
-
|
2012-07-29 03:55:41 +00:00
|
|
|
- The widget should have a html element with an id=ident, which will be
|
2012-07-27 01:03:46 +00:00
|
|
|
- replaced when it's updated.
|
|
|
|
-
|
|
|
|
- Updating is done by getting html from the gethtml route.
|
|
|
|
-
|
2012-07-29 01:25:56 +00:00
|
|
|
- ms_delay is how long to delay between AJAX updates
|
|
|
|
- ms_startdelay is how long to delay before updating with AJAX at the start
|
2012-07-27 01:03:46 +00:00
|
|
|
-}
|
2012-07-29 07:23:17 +00:00
|
|
|
autoUpdate :: Text -> Route WebApp -> Int -> Int -> Widget
|
|
|
|
autoUpdate ident gethtml ms_delay ms_startdelay = do
|
2012-07-27 01:03:46 +00:00
|
|
|
let delay = show ms_delay
|
|
|
|
let startdelay = show ms_startdelay
|
2012-07-27 02:54:31 +00:00
|
|
|
$(widgetFile "longpolling")
|
2012-07-27 01:03:46 +00:00
|
|
|
|
2012-07-30 01:54:23 +00:00
|
|
|
{- A display of currently running and queued transfers.
|
|
|
|
-
|
|
|
|
- Or, if there have never been any this run, an intro display. -}
|
2012-07-29 04:55:22 +00:00
|
|
|
transfersDisplay :: Bool -> Widget
|
|
|
|
transfersDisplay warnNoScript = do
|
2012-07-27 01:03:46 +00:00
|
|
|
webapp <- lift getYesod
|
2012-07-27 15:47:34 +00:00
|
|
|
current <- liftIO $ runThreadState (threadState webapp) $
|
|
|
|
M.toList . currentTransfers
|
2012-07-28 22:02:11 +00:00
|
|
|
<$> liftIO (getDaemonStatus $ daemonStatus webapp)
|
2012-07-27 15:47:34 +00:00
|
|
|
queued <- liftIO $ getTransferQueue $ transferQueue webapp
|
2012-07-29 03:55:41 +00:00
|
|
|
let ident = transfersDisplayIdent
|
2012-07-30 01:54:23 +00:00
|
|
|
let transfers = current ++ queued
|
|
|
|
if null transfers
|
|
|
|
then ifM (lift $ showIntro <$> getWebAppState)
|
|
|
|
( introDisplay ident
|
|
|
|
, noop
|
|
|
|
)
|
|
|
|
else do
|
|
|
|
lift $ modifyWebAppState $ \s -> s { showIntro = False }
|
|
|
|
$(widgetFile "transfers")
|
2012-07-27 15:47:34 +00:00
|
|
|
|
2012-07-29 03:55:41 +00:00
|
|
|
transfersDisplayIdent :: Text
|
|
|
|
transfersDisplayIdent = "transfers"
|
2012-07-29 01:21:22 +00:00
|
|
|
|
2012-07-30 01:54:23 +00:00
|
|
|
introDisplay :: Text -> Widget
|
|
|
|
introDisplay ident = do
|
|
|
|
webapp <- lift getYesod
|
|
|
|
let reldir = relDir webapp
|
2012-07-30 17:31:19 +00:00
|
|
|
l <- liftIO $ runThreadState (threadState webapp) $ do
|
2012-07-30 02:11:01 +00:00
|
|
|
u <- getUUID
|
|
|
|
rs <- map Remote.uuid <$> Remote.remoteList
|
2012-07-30 04:31:33 +00:00
|
|
|
rs' <- snd <$> trustPartition DeadTrusted rs
|
|
|
|
Remote.prettyListUUIDs $ filter (/= webUUID) $ nub $ u:rs'
|
2012-07-30 17:31:19 +00:00
|
|
|
let remotelist = zip counter l
|
|
|
|
let n = length l
|
2012-07-30 01:54:23 +00:00
|
|
|
let numrepos = show n
|
|
|
|
let notenough = n < 2
|
|
|
|
let barelyenough = n == 2
|
|
|
|
let morethanenough = n > 2
|
|
|
|
$(widgetFile "intro")
|
2012-07-30 17:31:19 +00:00
|
|
|
where
|
|
|
|
counter = map show ([1..] :: [Int])
|
2012-07-30 01:54:23 +00:00
|
|
|
|
2012-07-29 07:23:17 +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
|
2012-07-29 12:52:57 +00:00
|
|
|
waitNotifier transferNotifier nid
|
2012-07-27 01:03:46 +00:00
|
|
|
|
2012-07-29 07:23:17 +00:00
|
|
|
page <- widgetToPageContent $ transfersDisplay False
|
|
|
|
hamletToRepHtml $ [hamlet|^{pageBody page}|]
|
|
|
|
|
|
|
|
sideBarDisplay :: Bool -> Widget
|
|
|
|
sideBarDisplay noScript = do
|
2012-07-29 15:31:06 +00:00
|
|
|
let content = do
|
|
|
|
{- Any yesod message appears as the first alert. -}
|
|
|
|
maybe noop rendermessage =<< lift getMessage
|
|
|
|
|
2012-07-30 16:21:53 +00:00
|
|
|
{- Add newest alerts to the sidebar. -}
|
2012-07-29 15:31:06 +00:00
|
|
|
webapp <- lift getYesod
|
2012-07-29 23:05:51 +00:00
|
|
|
alertpairs <- M.toList . alertMap
|
2012-07-29 15:31:06 +00:00
|
|
|
<$> liftIO (getDaemonStatus $ daemonStatus webapp)
|
2012-07-30 16:21:53 +00:00
|
|
|
mapM_ renderalert $
|
|
|
|
take displayAlerts $ reverse $ sortAlertPairs alertpairs
|
2012-07-29 07:23:17 +00:00
|
|
|
ident <- lift newIdent
|
|
|
|
$(widgetFile "sidebar")
|
2012-07-29 15:31:06 +00:00
|
|
|
|
2012-07-29 07:23:17 +00:00
|
|
|
unless noScript $ do
|
2012-07-29 15:31:06 +00:00
|
|
|
{- Set up automatic updates of the sidebar
|
|
|
|
- when alerts come in. -}
|
|
|
|
nid <- lift $ newNotifier alertNotifier
|
2012-07-29 07:23:17 +00:00
|
|
|
autoUpdate ident (SideBarR nid) (10 :: Int) (10 :: Int)
|
2012-07-29 15:31:06 +00:00
|
|
|
where
|
|
|
|
bootstrapclass Activity = "alert-info"
|
|
|
|
bootstrapclass Warning = "alert"
|
|
|
|
bootstrapclass Error = "alert-error"
|
|
|
|
bootstrapclass Success = "alert-success"
|
|
|
|
bootstrapclass Message = "alert-info"
|
|
|
|
|
|
|
|
renderalert (alertid, alert) = addalert
|
2012-07-30 18:08:22 +00:00
|
|
|
alertid
|
2012-07-29 23:41:17 +00:00
|
|
|
(alertClosable alert)
|
2012-07-29 15:31:06 +00:00
|
|
|
(alertBlockDisplay alert)
|
|
|
|
(bootstrapclass $ alertClass alert)
|
|
|
|
(alertHeader alert)
|
|
|
|
$ case alertMessage alert of
|
|
|
|
StringAlert s -> [whamlet|#{s}|]
|
2012-07-30 06:07:02 +00:00
|
|
|
WidgetAlert w -> w alert
|
2012-07-29 15:31:06 +00:00
|
|
|
|
2012-07-30 18:08:22 +00:00
|
|
|
rendermessage msg = addalert firstAlertId True False
|
2012-07-29 15:31:06 +00:00
|
|
|
"alert-info" Nothing [whamlet|#{msg}|]
|
|
|
|
|
2012-07-30 18:08:22 +00:00
|
|
|
addalert :: AlertId -> Bool -> Bool -> Text -> Maybe String -> Widget -> Widget
|
|
|
|
addalert i closable block divclass heading widget = do
|
|
|
|
let alertid = show i
|
|
|
|
let closealert = CloseAlert i
|
|
|
|
$(widgetFile "alert")
|
2012-07-29 07:23:17 +00:00
|
|
|
|
|
|
|
{- Called by client to get a sidebar display.
|
|
|
|
-
|
|
|
|
- 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 all pages.
|
|
|
|
-}
|
|
|
|
getSideBarR :: NotificationId -> Handler RepHtml
|
|
|
|
getSideBarR nid = do
|
2012-07-29 16:37:45 +00:00
|
|
|
waitNotifier alertNotifier nid
|
2012-07-29 07:23:17 +00:00
|
|
|
|
|
|
|
page <- widgetToPageContent $ sideBarDisplay True
|
|
|
|
hamletToRepHtml $ [hamlet|^{pageBody page}|]
|
|
|
|
|
2012-07-30 18:08:22 +00:00
|
|
|
{- Called by the client to close an alert. -}
|
|
|
|
getCloseAlert :: AlertId -> Handler ()
|
|
|
|
getCloseAlert i = do
|
|
|
|
webapp <- getYesod
|
|
|
|
void $ liftIO $ removeAlert (daemonStatus webapp) i
|
|
|
|
|
2012-07-29 07:23:17 +00:00
|
|
|
dashboard :: Bool -> Bool -> Widget
|
|
|
|
dashboard noScript warnNoScript = do
|
|
|
|
sideBarDisplay noScript
|
|
|
|
transfersDisplay warnNoScript
|
2012-07-29 04:08:14 +00:00
|
|
|
|
2012-07-26 01:26:13 +00:00
|
|
|
getHomeR :: Handler RepHtml
|
2012-07-29 03:55:41 +00:00
|
|
|
getHomeR = defaultLayout $ do
|
|
|
|
{- Set up automatic updates for the transfers display. -}
|
2012-07-29 12:52:57 +00:00
|
|
|
nid <- lift $ newNotifier transferNotifier
|
2012-07-29 07:23:17 +00:00
|
|
|
autoUpdate transfersDisplayIdent (TransfersR nid) (10 :: Int) (10 :: Int)
|
2012-07-29 04:08:14 +00:00
|
|
|
|
2012-07-29 07:23:17 +00:00
|
|
|
dashboard False True
|
2012-07-29 04:08:14 +00:00
|
|
|
|
|
|
|
{- Same as HomeR, except with no javascript, so it doesn't allocate
|
2012-07-29 04:55:22 +00:00
|
|
|
- new resources each time the page is refreshed, and with autorefreshing
|
|
|
|
- via meta refresh. -}
|
|
|
|
getNoScriptAutoR :: Handler RepHtml
|
|
|
|
getNoScriptAutoR = defaultLayout $ do
|
2012-07-29 04:08:14 +00:00
|
|
|
let ident = NoScriptR
|
|
|
|
let delayseconds = 3 :: Int
|
2012-07-29 04:55:22 +00:00
|
|
|
let this = NoScriptAutoR
|
2012-07-29 04:08:14 +00:00
|
|
|
toWidgetHead $(hamletFile $ hamletTemplate "metarefresh")
|
2012-07-29 07:23:17 +00:00
|
|
|
dashboard True False
|
2012-07-29 04:55:22 +00:00
|
|
|
|
|
|
|
getNoScriptR :: Handler RepHtml
|
|
|
|
getNoScriptR = defaultLayout $
|
2012-07-29 07:23:17 +00:00
|
|
|
dashboard True True
|
2012-07-26 01:26:13 +00:00
|
|
|
|
|
|
|
getConfigR :: Handler RepHtml
|
2012-07-26 06:45:01 +00:00
|
|
|
getConfigR = defaultLayout $ do
|
2012-07-29 07:23:17 +00:00
|
|
|
sideBarDisplay False
|
2012-07-30 01:54:23 +00:00
|
|
|
setTitle "Configuration"
|
|
|
|
[whamlet|<a href="@{HomeR}">main|]
|
|
|
|
|
|
|
|
getAddRepositoryR :: Handler RepHtml
|
|
|
|
getAddRepositoryR = defaultLayout $ do
|
|
|
|
sideBarDisplay False
|
|
|
|
setTitle "Add repository"
|
2012-07-26 09:20:52 +00:00
|
|
|
[whamlet|<a href="@{HomeR}">main|]
|
2012-07-26 01:26:13 +00:00
|
|
|
|
2012-07-27 19:33:24 +00:00
|
|
|
webAppThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Maybe (IO ()) -> IO ()
|
|
|
|
webAppThread st dstatus transferqueue onstartup = do
|
2012-07-27 15:47:34 +00:00
|
|
|
webapp <- mkWebApp
|
2012-07-27 03:55:51 +00:00
|
|
|
app <- toWaiAppPlain webapp
|
2012-07-26 01:26:13 +00:00
|
|
|
app' <- ifM debugEnabled
|
|
|
|
( return $ httpDebugLogger app
|
|
|
|
, return app
|
|
|
|
)
|
2012-07-27 19:33:24 +00:00
|
|
|
runWebApp app' $ \port -> do
|
|
|
|
runThreadState st $ writeHtmlShim webapp port
|
|
|
|
maybe noop id onstartup
|
2012-07-27 15:47:34 +00:00
|
|
|
where
|
|
|
|
mkWebApp = do
|
|
|
|
dir <- absPath =<< runThreadState st (fromRepo repoPath)
|
|
|
|
home <- myHomeDir
|
|
|
|
let reldir = if dirContains home dir
|
|
|
|
then relPathDirToFile home dir
|
|
|
|
else dir
|
|
|
|
token <- genRandomToken
|
2012-07-30 01:54:23 +00:00
|
|
|
s <- newWebAppState
|
2012-07-27 15:47:34 +00:00
|
|
|
return $ WebApp
|
|
|
|
{ threadState = st
|
|
|
|
, daemonStatus = dstatus
|
|
|
|
, transferQueue = transferqueue
|
|
|
|
, secretToken = pack token
|
2012-07-30 01:54:23 +00:00
|
|
|
, relDir = reldir
|
2012-07-27 15:47:34 +00:00
|
|
|
, getStatic = $(embed "static")
|
2012-07-30 01:54:23 +00:00
|
|
|
, webAppState = s
|
2012-07-27 15:47:34 +00:00
|
|
|
}
|
2012-07-26 03:13:01 +00:00
|
|
|
|
2012-07-26 08:50:09 +00:00
|
|
|
{- Creates a html shim file that's used to redirect into the webapp,
|
|
|
|
- to avoid exposing the secretToken when launching the web browser. -}
|
2012-07-26 07:38:20 +00:00
|
|
|
writeHtmlShim :: WebApp -> PortNumber -> Annex ()
|
|
|
|
writeHtmlShim webapp port = do
|
2012-07-26 08:50:09 +00:00
|
|
|
liftIO $ debug thisThread ["running on port", show port]
|
2012-07-26 03:13:01 +00:00
|
|
|
htmlshim <- fromRepo gitAnnexHtmlShim
|
2012-07-26 07:38:20 +00:00
|
|
|
liftIO $ viaTmp go htmlshim $ genHtmlShim webapp port
|
|
|
|
where
|
|
|
|
go file content = do
|
|
|
|
h <- openFile file WriteMode
|
|
|
|
modifyFileMode file $ removeModes [groupReadMode, otherReadMode]
|
|
|
|
hPutStr h content
|
|
|
|
hClose h
|
2012-07-26 03:13:01 +00:00
|
|
|
|
|
|
|
{- TODO: generate this static file using Yesod. -}
|
2012-07-26 07:38:20 +00:00
|
|
|
genHtmlShim :: WebApp -> PortNumber -> String
|
|
|
|
genHtmlShim webapp port = renderHtml $(shamletFile $ hamletTemplate "htmlshim")
|
2012-07-26 01:26:13 +00:00
|
|
|
where
|
2012-07-26 08:50:09 +00:00
|
|
|
url = "http://localhost:" ++ show port ++
|
|
|
|
"/?auth=" ++ unpack (secretToken webapp)
|