git-annex/Assistant/WebApp.hs

74 lines
2.4 KiB
Haskell
Raw Normal View History

{- git-annex assistant webapp core
2012-07-31 05:11:32 +00:00
-
- Copyright 2012, 2013 Joey Hess <joey@kitenet.net>
2012-07-31 05:11:32 +00:00
-
- Licensed under the GNU AGPL version 3 or higher.
2012-07-31 05:11:32 +00:00
-}
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell, OverloadedStrings, RankNTypes #-}
2012-07-31 05:11:32 +00:00
module Assistant.WebApp where
import Assistant.WebApp.Types
import Assistant.Common
2012-07-31 05:11:32 +00:00
import Utility.NotificationBroadcaster
import Utility.Yesod
import Data.Text (Text)
import Control.Concurrent
import qualified Network.Wai as W
import qualified Data.ByteString.Char8 as S8
import qualified Data.Text as T
2012-07-31 05:11:32 +00:00
2013-06-02 19:57:22 +00:00
waitNotifier :: Assistant NotificationBroadcaster -> NotificationId -> Handler ()
2012-11-03 01:13:06 +00:00
waitNotifier getbroadcaster nid = liftAssistant $ do
b <- getbroadcaster
liftIO $ waitNotification $ notificationHandleFromId b nid
2012-07-31 05:11:32 +00:00
2013-06-02 19:57:22 +00:00
newNotifier :: Assistant NotificationBroadcaster -> Handler NotificationId
2012-11-03 01:13:06 +00:00
newNotifier getbroadcaster = liftAssistant $ do
b <- getbroadcaster
liftIO $ notificationHandleToId <$> newNotificationHandle True b
2012-07-31 05:11:32 +00:00
{- Adds the auth parameter as a hidden field on a form. Must be put into
- every form. -}
webAppFormAuthToken :: Widget
webAppFormAuthToken = do
webapp <- liftH getYesod
[whamlet|<input type="hidden" name="auth" value="#{secretToken webapp}">|]
2012-08-08 21:07:38 +00:00
2012-09-27 16:55:00 +00:00
{- A button with an icon, and maybe label or tooltip, that can be
- clicked to perform some action.
2012-08-08 21:07:38 +00:00
- With javascript, clicking it POSTs the Route, and remains on the same
- page.
- With noscript, clicking it GETs the Route. -}
2012-09-27 16:55:00 +00:00
actionButton :: Route WebApp -> (Maybe String) -> (Maybe String) -> String -> String -> Widget
actionButton route label tooltip buttonclass iconclass = $(widgetFile "actionbutton")
type UrlRenderFunc = Route WebApp -> [(Text, Text)] -> Text
type UrlRenderer = MVar (UrlRenderFunc)
newUrlRenderer :: IO UrlRenderer
newUrlRenderer = newEmptyMVar
setUrlRenderer :: UrlRenderer -> (UrlRenderFunc) -> IO ()
setUrlRenderer = putMVar
inFirstRun :: Handler Bool
inFirstRun = isNothing . relDir <$> getYesod
{- Blocks until the webapp is running and has called setUrlRenderer. -}
renderUrl :: UrlRenderer -> Route WebApp -> [(Text, Text)] -> IO Text
renderUrl urlrenderer route params = do
r <- readMVar urlrenderer
return $ r route params
2013-03-13 02:18:36 +00:00
{- Redirects back to the referring page, or if there's none, DashboardR -}
redirectBack :: Handler ()
redirectBack = do
mr <- lookup "referer" . W.requestHeaders <$> waiRequest
case mr of
Nothing -> redirect DashboardR
Just r -> redirect $ T.pack $ S8.unpack r