{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-}
module Yesod.Auth.BrowserId
{-# DEPRECATED "Mozilla Persona will be shut down by the end of 2016" #-}
( authBrowserId
, createOnClick, createOnClickOverride
, def
, BrowserIdSettings
, bisAudience
, bisLazyLoad
, forwardUrl
) where
import Yesod.Auth
import Web.Authenticate.BrowserId
import Data.Text (Text)
import Yesod.Core
import qualified Data.Text as T
import Data.Maybe (fromMaybe)
import Control.Monad (when, unless)
import Text.Julius (rawJS)
import Network.URI (uriPath, parseURI)
import Data.FileEmbed (embedFile)
import Data.ByteString (ByteString)
import Data.Default
pid :: Text
pid = "browserid"
forwardUrl :: AuthRoute
forwardUrl = PluginR pid []
complete :: AuthRoute
complete = forwardUrl
data BrowserIdSettings = BrowserIdSettings
{ bisAudience :: Maybe Text
, bisLazyLoad :: Bool
}
instance Default BrowserIdSettings where
def = BrowserIdSettings
{ bisAudience = Nothing
, bisLazyLoad = True
}
authBrowserId :: YesodAuth m => BrowserIdSettings -> AuthPlugin m
authBrowserId bis@BrowserIdSettings {..} = AuthPlugin
{ apName = pid
, apDispatch = \m ps ->
case (m, ps) of
("GET", [assertion]) -> do
audience <-
case bisAudience of
Just a -> return a
Nothing -> do
r <- getUrlRender
tm <- getRouteToParent
return $ T.takeWhile (/= '/') $ stripScheme $ r $ tm LoginR
manager <- authHttpManager
memail <- checkAssertion audience assertion manager
case memail of
Nothing -> do
$logErrorS "yesod-auth" "BrowserID assertion failure"
tm <- getRouteToParent
loginErrorMessage (tm LoginR) "BrowserID login error."
Just email -> setCredsRedirect Creds
{ credsPlugin = pid
, credsIdent = email
, credsExtra = []
}
("GET", ["static", "sign-in.png"]) -> sendResponse
( "image/png" :: ByteString
, toContent $(embedFile "persona_sign_in_blue.png")
)
(_, []) -> badMethod
_ -> notFound
, apLogin = \toMaster -> do
onclick <- createOnClick bis toMaster
autologin <- fmap (== Just "true") $ lookupGetParam "autologin"
when autologin $ toWidget [julius|#{rawJS onclick}();|]
toWidget [hamlet|
$newline never
<p>
<a href="javascript:#{onclick}()">
<img src=@{toMaster loginIcon}>
|]
}
where
loginIcon = PluginR pid ["static", "sign-in.png"]
stripScheme t = fromMaybe t $ T.stripPrefix "//" $ snd $ T.breakOn "//" t
createOnClickOverride :: BrowserIdSettings
-> (Route Auth -> Route master)
-> Maybe (Route master)
-> WidgetFor master Text
createOnClickOverride BrowserIdSettings {..} toMaster mOnRegistration = do
unless bisLazyLoad $ addScriptRemote browserIdJs
onclick <- newIdent
render <- getUrlRender
let login = toJSON $ getPath $ render loginRoute
loginRoute = maybe (toMaster LoginR) id mOnRegistration
toWidget [julius|
function #{rawJS onclick}() {
if (navigator.id) {
navigator.id.watch({
onlogin: function (assertion) {
if (assertion) {
document.location = "@{toMaster complete}/" + assertion;
}
},
onlogout: function () {}
});
navigator.id.request({
returnTo: #{login} + "?autologin=true"
});
}
else {
alert("Loading, please try again");
}
}
|]
when bisLazyLoad $ toWidget [julius|
(function(){
var bid = document.createElement("script");
bid.async = true;
bid.src = #{toJSON browserIdJs};
var s = document.getElementsByTagName('script')[0];
s.parentNode.insertBefore(bid, s);
})();
|]
autologin <- fmap (== Just "true") $ lookupGetParam "autologin"
when autologin $ toWidget [julius|#{rawJS onclick}();|]
return onclick
where
getPath t = fromMaybe t $ do
uri <- parseURI $ T.unpack t
return $ T.pack $ uriPath uri
createOnClick :: BrowserIdSettings
-> (Route Auth -> Route master)
-> WidgetFor master Text
createOnClick bidSettings toMaster = createOnClickOverride bidSettings toMaster Nothing