{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE CPP #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} module Yesod.Auth.OpenId ( authOpenId , forwardUrl , claimedKey , opLocalKey , credsIdentClaimed , IdentifierType (..) ) where import Yesod.Auth import qualified Web.Authenticate.OpenId as OpenId import Yesod.Form import Yesod.Core import Data.Text (Text, isPrefixOf) import qualified Yesod.Auth.Message as Msg import UnliftIO.Exception (tryAny) import Data.Maybe (fromMaybe) import qualified Data.Text as T forwardUrl :: AuthRoute forwardUrl = PluginR "openid" ["forward"] data IdentifierType = Claimed | OPLocal authOpenId :: YesodAuth master => IdentifierType -> [(Text, Text)] -- ^ extension fields -> AuthPlugin master authOpenId idType extensionFields = AuthPlugin "openid" dispatch login where complete = PluginR "openid" ["complete"] name :: Text name = "openid_identifier" login tm = do ident <- newIdent -- FIXME this is a hack to get GHC 7.6's type checker to allow the -- code, but it shouldn't be necessary let y :: a -> [(Text, Text)] -> Text y = undefined toWidget (\x -> [cassius|##{ident} background: #fff url(http://www.myopenid.com/static/openid-icon-small.gif) no-repeat scroll 0pt 50%; padding-left: 18px; |] $ x `asTypeOf` y) [whamlet| $newline never