{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE CPP #-} module Yesod.Auth.OpenId ( authOpenId , authOpenIdExtended , forwardUrl , claimedKey , credsIdentClaimed ) where import Yesod.Auth import qualified Web.Authenticate.OpenId as OpenId import Yesod.Form import Yesod.Handler import Yesod.Widget (toWidget, whamlet) import Yesod.Request import Text.Cassius (cassius) #if MIN_VERSION_blaze_html(0, 5, 0) import Text.Blaze.Html (toHtml) #else import Text.Blaze (toHtml) #endif import Data.Text (Text, isPrefixOf) import qualified Yesod.Auth.Message as Msg import Control.Exception.Lifted (SomeException, try) import Data.Maybe (fromMaybe) forwardUrl :: AuthRoute forwardUrl = PluginR "openid" ["forward"] authOpenId :: YesodAuth m => AuthPlugin m authOpenId = authOpenIdExtended [] authOpenIdExtended :: YesodAuth m => [(Text, Text)] -> AuthPlugin m authOpenIdExtended extensionFields = AuthPlugin "openid" dispatch login where complete = PluginR "openid" ["complete"] name = "openid_identifier" login tm = do ident <- lift newIdent toWidget [cassius|##{ident} background: #fff url(http://www.myopenid.com/static/openid-icon-small.gif) no-repeat scroll 0pt 50%; padding-left: 18px; |] [whamlet|