Auth.hs 20 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578
  1. {-# LANGUAGE CPP #-}
  2. {-# LANGUAGE ViewPatterns #-}
  3. {-# LANGUAGE ConstraintKinds #-}
  4. {-# LANGUAGE DefaultSignatures #-}
  5. {-# LANGUAGE QuasiQuotes, TypeFamilies, TemplateHaskell #-}
  6. {-# LANGUAGE FlexibleContexts #-}
  7. {-# LANGUAGE FlexibleInstances #-}
  8. {-# LANGUAGE MultiParamTypeClasses #-}
  9. {-# LANGUAGE RankNTypes #-}
  10. {-# LANGUAGE OverloadedStrings #-}
  11. {-# LANGUAGE DeriveDataTypeable #-}
  12. {-# LANGUAGE UndecidableInstances #-}
  13. {-# OPTIONS_GHC -fno-warn-orphans #-}
  14. module Yesod.Auth
  15. ( -- * Subsite
  16. Auth
  17. , AuthRoute
  18. , Route (..)
  19. , AuthPlugin (..)
  20. , getAuth
  21. , YesodAuth (..)
  22. , YesodAuthPersist (..)
  23. -- * Plugin interface
  24. , Creds (..)
  25. , setCreds
  26. , setCredsRedirect
  27. , clearCreds
  28. , loginErrorMessage
  29. , loginErrorMessageI
  30. -- * User functions
  31. , AuthenticationResult (..)
  32. , defaultMaybeAuthId
  33. , defaultLoginHandler
  34. , maybeAuthPair
  35. , maybeAuth
  36. , requireAuthId
  37. , requireAuthPair
  38. , requireAuth
  39. -- * Exception
  40. , AuthException (..)
  41. -- * Helper
  42. , AuthHandler
  43. -- * Internal
  44. , credsKey
  45. , provideJsonMessage
  46. , messageJson401
  47. , asHtml
  48. ) where
  49. import Control.Applicative ((<$>))
  50. import Control.Monad (when)
  51. import Control.Monad.Trans.Maybe
  52. import Yesod.Auth.Routes
  53. import Data.Aeson hiding (json)
  54. import Data.Text.Encoding (decodeUtf8With)
  55. import Data.Text.Encoding.Error (lenientDecode)
  56. import Data.Text (Text)
  57. import qualified Data.Text as T
  58. import qualified Data.HashMap.Lazy as Map
  59. import Data.Monoid (Endo)
  60. import Network.HTTP.Client (Manager, Request, withResponse, Response, BodyReader)
  61. import qualified Network.Wai as W
  62. import Yesod.Core
  63. import Yesod.Core.Types (HandlerT(..), unHandlerT)
  64. import Yesod.Persist
  65. import Yesod.Auth.Message (AuthMessage, defaultMessage)
  66. import qualified Yesod.Auth.Message as Msg
  67. import Yesod.Form (FormMessage)
  68. import Data.Typeable (Typeable)
  69. import Control.Exception (Exception)
  70. import Network.HTTP.Types (Status, internalServerError500, unauthorized401)
  71. import Control.Monad.Trans.Resource (MonadResourceBase)
  72. import qualified Control.Monad.Trans.Writer as Writer
  73. import Control.Monad (void)
  74. type AuthRoute = Route Auth
  75. type AuthHandler master a = YesodAuth master => HandlerT Auth (HandlerT master IO) a
  76. type Method = Text
  77. type Piece = Text
  78. -- | The result of an authentication based on credentials
  79. --
  80. -- Since 1.4.4
  81. data AuthenticationResult master
  82. = Authenticated (AuthId master) -- ^ Authenticated successfully
  83. | UserError AuthMessage -- ^ Invalid credentials provided by user
  84. | ServerError Text -- ^ Some other error
  85. data AuthPlugin master = AuthPlugin
  86. { apName :: Text
  87. , apDispatch :: Method -> [Piece] -> AuthHandler master TypedContent
  88. , apLogin :: (Route Auth -> Route master) -> WidgetT master IO ()
  89. }
  90. getAuth :: a -> Auth
  91. getAuth = const Auth
  92. -- | User credentials
  93. data Creds master = Creds
  94. { credsPlugin :: Text -- ^ How the user was authenticated
  95. , credsIdent :: Text -- ^ Identifier. Exact meaning depends on plugin.
  96. , credsExtra :: [(Text, Text)]
  97. }
  98. class (Yesod master, PathPiece (AuthId master), RenderMessage master FormMessage) => YesodAuth master where
  99. type AuthId master
  100. -- | specify the layout. Uses defaultLayout by default
  101. authLayout :: WidgetT master IO () -> HandlerT master IO Html
  102. authLayout = defaultLayout
  103. -- | Default destination on successful login, if no other
  104. -- destination exists.
  105. loginDest :: master -> Route master
  106. -- | Default destination on successful logout, if no other
  107. -- destination exists.
  108. logoutDest :: master -> Route master
  109. -- | Perform authentication based on the given credentials.
  110. --
  111. -- Default implementation is in terms of @'getAuthId'@
  112. --
  113. -- Since: 1.4.4
  114. authenticate :: Creds master -> HandlerT master IO (AuthenticationResult master)
  115. authenticate creds = do
  116. muid <- getAuthId creds
  117. return $ maybe (UserError Msg.InvalidLogin) Authenticated muid
  118. -- | Determine the ID associated with the set of credentials.
  119. --
  120. -- Default implementation is in terms of @'authenticate'@
  121. --
  122. getAuthId :: Creds master -> HandlerT master IO (Maybe (AuthId master))
  123. getAuthId creds = do
  124. auth <- authenticate creds
  125. return $ case auth of
  126. Authenticated auid -> Just auid
  127. _ -> Nothing
  128. -- | Which authentication backends to use.
  129. authPlugins :: master -> [AuthPlugin master]
  130. -- | What to show on the login page.
  131. --
  132. -- By default this calls 'defaultLoginHandler', which concatenates
  133. -- plugin widgets and wraps the result in 'authLayout'. Override if
  134. -- you need fancy widget containers, additional functionality, or an
  135. -- entirely custom page. For example, in some applications you may
  136. -- want to prevent the login page being displayed for a user who is
  137. -- already logged in, even if the URL is visited explicitly; this can
  138. -- be done by overriding 'loginHandler' in your instance declaration
  139. -- with something like:
  140. --
  141. -- > instance YesodAuth App where
  142. -- > ...
  143. -- > loginHandler = do
  144. -- > ma <- lift maybeAuthId
  145. -- > when (isJust ma) $
  146. -- > lift $ redirect HomeR -- or any other Handler code you want
  147. -- > defaultLoginHandler
  148. --
  149. loginHandler :: AuthHandler master Html
  150. loginHandler = defaultLoginHandler
  151. -- | Used for i18n of messages provided by this package.
  152. renderAuthMessage :: master
  153. -> [Text] -- ^ languages
  154. -> AuthMessage
  155. -> Text
  156. renderAuthMessage _ _ = defaultMessage
  157. -- | After login and logout, redirect to the referring page, instead of
  158. -- 'loginDest' and 'logoutDest'. Default is 'False'.
  159. redirectToReferer :: master -> Bool
  160. redirectToReferer _ = False
  161. -- | Return an HTTP connection manager that is stored in the foundation
  162. -- type. This allows backends to reuse persistent connections. If none of
  163. -- the backends you're using use HTTP connections, you can safely return
  164. -- @error \"authHttpManager\"@ here.
  165. authHttpManager :: master -> Manager
  166. -- | Called on a successful login. By default, calls
  167. -- @addMessageI "success" NowLoggedIn@.
  168. onLogin :: HandlerT master IO ()
  169. onLogin = addMessageI "success" Msg.NowLoggedIn
  170. -- | Called on logout. By default, does nothing
  171. onLogout :: HandlerT master IO ()
  172. onLogout = return ()
  173. -- | Retrieves user credentials, if user is authenticated.
  174. --
  175. -- By default, this calls 'defaultMaybeAuthId' to get the user ID from the
  176. -- session. This can be overridden to allow authentication via other means,
  177. -- such as checking for a special token in a request header. This is
  178. -- especially useful for creating an API to be accessed via some means
  179. -- other than a browser.
  180. --
  181. -- Since 1.2.0
  182. maybeAuthId :: HandlerT master IO (Maybe (AuthId master))
  183. default maybeAuthId
  184. :: (YesodAuthPersist master, Typeable (AuthEntity master))
  185. => HandlerT master IO (Maybe (AuthId master))
  186. maybeAuthId = defaultMaybeAuthId
  187. -- | Called on login error for HTTP requests. By default, calls
  188. -- @addMessage@ with "error" as status and redirects to @dest@.
  189. onErrorHtml :: (MonadResourceBase m) => Route master -> Text -> HandlerT master m Html
  190. onErrorHtml dest msg = do
  191. addMessage "error" $ toHtml msg
  192. fmap asHtml $ redirect dest
  193. -- | runHttpRequest gives you a chance to handle an HttpException and retry
  194. -- The default behavior is to simply execute the request which will throw an exception on failure
  195. --
  196. -- The HTTP 'Request' is given in case it is useful to change behavior based on inspecting the request.
  197. -- This is an experimental API that is not broadly used throughout the yesod-auth code base
  198. runHttpRequest :: Request -> (Response BodyReader -> HandlerT master IO a) -> HandlerT master IO a
  199. runHttpRequest req inner = do
  200. man <- authHttpManager <$> getYesod
  201. HandlerT $ \t -> withResponse req man $ \res -> unHandlerT (inner res) t
  202. {-# MINIMAL loginDest, logoutDest, (authenticate | getAuthId), authPlugins, authHttpManager #-}
  203. {-# DEPRECATED getAuthId "Define 'authenticate' instead; 'getAuthId' will be removed in the next major version" #-}
  204. -- | Internal session key used to hold the authentication information.
  205. --
  206. -- Since 1.2.3
  207. credsKey :: Text
  208. credsKey = "_ID"
  209. -- | Retrieves user credentials from the session, if user is authenticated.
  210. --
  211. -- This function does /not/ confirm that the credentials are valid, see
  212. -- 'maybeAuthIdRaw' for more information.
  213. --
  214. -- Since 1.1.2
  215. defaultMaybeAuthId
  216. :: (YesodAuthPersist master, Typeable (AuthEntity master))
  217. => HandlerT master IO (Maybe (AuthId master))
  218. defaultMaybeAuthId = runMaybeT $ do
  219. s <- MaybeT $ lookupSession credsKey
  220. aid <- MaybeT $ return $ fromPathPiece s
  221. _ <- MaybeT $ cachedAuth aid
  222. return aid
  223. cachedAuth
  224. :: (YesodAuthPersist master, Typeable (AuthEntity master))
  225. => AuthId master -> HandlerT master IO (Maybe (AuthEntity master))
  226. cachedAuth
  227. = fmap unCachedMaybeAuth
  228. . cached
  229. . fmap CachedMaybeAuth
  230. . getAuthEntity
  231. -- | Default handler to show the login page.
  232. --
  233. -- This is the default 'loginHandler'. It concatenates plugin widgets and
  234. -- wraps the result in 'authLayout'. See 'loginHandler' for more details.
  235. --
  236. -- Since 1.4.9
  237. defaultLoginHandler :: AuthHandler master Html
  238. defaultLoginHandler = do
  239. tp <- getRouteToParent
  240. lift $ authLayout $ do
  241. setTitleI Msg.LoginTitle
  242. master <- getYesod
  243. mapM_ (flip apLogin tp) (authPlugins master)
  244. loginErrorMessageI :: (MonadResourceBase m, YesodAuth master)
  245. => Route child
  246. -> AuthMessage
  247. -> HandlerT child (HandlerT master m) TypedContent
  248. loginErrorMessageI dest msg = do
  249. toParent <- getRouteToParent
  250. lift $ loginErrorMessageMasterI (toParent dest) msg
  251. loginErrorMessageMasterI :: (YesodAuth master, MonadResourceBase m, RenderMessage master AuthMessage)
  252. => Route master
  253. -> AuthMessage
  254. -> HandlerT master m TypedContent
  255. loginErrorMessageMasterI dest msg = do
  256. mr <- getMessageRender
  257. loginErrorMessage dest (mr msg)
  258. -- | For HTML, set the message and redirect to the route.
  259. -- For JSON, send the message and a 401 status
  260. loginErrorMessage :: (YesodAuth master, MonadResourceBase m)
  261. => Route master
  262. -> Text
  263. -> HandlerT master m TypedContent
  264. loginErrorMessage dest msg = messageJson401 msg (onErrorHtml dest msg)
  265. messageJson401 :: MonadResourceBase m => Text -> HandlerT master m Html -> HandlerT master m TypedContent
  266. messageJson401 = messageJsonStatus unauthorized401
  267. messageJson500 :: MonadResourceBase m => Text -> HandlerT master m Html -> HandlerT master m TypedContent
  268. messageJson500 = messageJsonStatus internalServerError500
  269. messageJsonStatus :: MonadResourceBase m
  270. => Status
  271. -> Text
  272. -> HandlerT master m Html
  273. -> HandlerT master m TypedContent
  274. messageJsonStatus status msg html = selectRep $ do
  275. provideRep html
  276. provideRep $ do
  277. let obj = object ["message" .= msg]
  278. void $ sendResponseStatus status obj
  279. return obj
  280. provideJsonMessage :: Monad m => Text -> Writer.Writer (Endo [ProvidedRep m]) ()
  281. provideJsonMessage msg = provideRep $ return $ object ["message" .= msg]
  282. setCredsRedirect :: YesodAuth master
  283. => Creds master -- ^ new credentials
  284. -> HandlerT master IO TypedContent
  285. setCredsRedirect creds = do
  286. y <- getYesod
  287. auth <- authenticate creds
  288. case auth of
  289. Authenticated aid -> do
  290. setSession credsKey $ toPathPiece aid
  291. onLogin
  292. res <- selectRep $ do
  293. provideRepType typeHtml $
  294. fmap asHtml $ redirectUltDest $ loginDest y
  295. provideJsonMessage "Login Successful"
  296. sendResponse res
  297. UserError msg ->
  298. case authRoute y of
  299. Nothing -> do
  300. msg' <- renderMessage' msg
  301. messageJson401 msg' $ authLayout $ -- TODO
  302. toWidget [whamlet|<h1>_{msg}|]
  303. Just ar -> loginErrorMessageMasterI ar msg
  304. ServerError msg -> do
  305. $(logError) msg
  306. case authRoute y of
  307. Nothing -> do
  308. msg' <- renderMessage' Msg.AuthError
  309. messageJson500 msg' $ authLayout $
  310. toWidget [whamlet|<h1>_{Msg.AuthError}|]
  311. Just ar -> loginErrorMessageMasterI ar Msg.AuthError
  312. where
  313. renderMessage' msg = do
  314. langs <- languages
  315. master <- getYesod
  316. return $ renderAuthMessage master langs msg
  317. -- | Sets user credentials for the session after checking them with authentication backends.
  318. setCreds :: YesodAuth master
  319. => Bool -- ^ if HTTP redirects should be done
  320. -> Creds master -- ^ new credentials
  321. -> HandlerT master IO ()
  322. setCreds doRedirects creds =
  323. if doRedirects
  324. then void $ setCredsRedirect creds
  325. else do auth <- authenticate creds
  326. case auth of
  327. Authenticated aid -> setSession credsKey $ toPathPiece aid
  328. _ -> return ()
  329. -- | same as defaultLayoutJson, but uses authLayout
  330. authLayoutJson :: (YesodAuth site, ToJSON j)
  331. => WidgetT site IO () -- ^ HTML
  332. -> HandlerT site IO j -- ^ JSON
  333. -> HandlerT site IO TypedContent
  334. authLayoutJson w json = selectRep $ do
  335. provideRep $ authLayout w
  336. provideRep $ fmap toJSON json
  337. -- | Clears current user credentials for the session.
  338. --
  339. -- Since 1.1.7
  340. clearCreds :: YesodAuth master
  341. => Bool -- ^ if HTTP redirect to 'logoutDest' should be done
  342. -> HandlerT master IO ()
  343. clearCreds doRedirects = do
  344. y <- getYesod
  345. onLogout
  346. deleteSession credsKey
  347. when doRedirects $ do
  348. redirectUltDest $ logoutDest y
  349. getCheckR :: AuthHandler master TypedContent
  350. getCheckR = lift $ do
  351. creds <- maybeAuthId
  352. authLayoutJson (do
  353. setTitle "Authentication Status"
  354. toWidget $ html' creds) (return $ jsonCreds creds)
  355. where
  356. html' creds =
  357. [shamlet|
  358. $newline never
  359. <h1>Authentication Status
  360. $maybe _ <- creds
  361. <p>Logged in.
  362. $nothing
  363. <p>Not logged in.
  364. |]
  365. jsonCreds creds =
  366. Object $ Map.fromList
  367. [ (T.pack "logged_in", Bool $ maybe False (const True) creds)
  368. ]
  369. setUltDestReferer' :: AuthHandler master ()
  370. setUltDestReferer' = lift $ do
  371. master <- getYesod
  372. when (redirectToReferer master) setUltDestReferer
  373. getLoginR :: AuthHandler master Html
  374. getLoginR = setUltDestReferer' >> loginHandler
  375. getLogoutR :: AuthHandler master ()
  376. getLogoutR = setUltDestReferer' >> redirectToPost LogoutR
  377. postLogoutR :: AuthHandler master ()
  378. postLogoutR = lift $ clearCreds True
  379. handlePluginR :: Text -> [Text] -> AuthHandler master TypedContent
  380. handlePluginR plugin pieces = do
  381. master <- lift getYesod
  382. env <- waiRequest
  383. let method = decodeUtf8With lenientDecode $ W.requestMethod env
  384. case filter (\x -> apName x == plugin) (authPlugins master) of
  385. [] -> notFound
  386. ap:_ -> apDispatch ap method pieces
  387. -- | Similar to 'maybeAuthId', but additionally look up the value associated
  388. -- with the user\'s database identifier to get the value in the database. This
  389. -- assumes that you are using a Persistent database.
  390. --
  391. -- Since 1.1.0
  392. maybeAuth :: ( YesodAuthPersist master
  393. , val ~ AuthEntity master
  394. , Key val ~ AuthId master
  395. , PersistEntity val
  396. , Typeable val
  397. ) => HandlerT master IO (Maybe (Entity val))
  398. maybeAuth = runMaybeT $ do
  399. (aid, ae) <- MaybeT maybeAuthPair
  400. return $ Entity aid ae
  401. -- | Similar to 'maybeAuth', but doesn’t assume that you are using a
  402. -- Persistent database.
  403. --
  404. -- Since 1.4.0
  405. maybeAuthPair :: (YesodAuthPersist master, Typeable (AuthEntity master))
  406. => HandlerT master IO (Maybe (AuthId master, AuthEntity master))
  407. maybeAuthPair = runMaybeT $ do
  408. aid <- MaybeT maybeAuthId
  409. ae <- MaybeT $ cachedAuth aid
  410. return (aid, ae)
  411. newtype CachedMaybeAuth val = CachedMaybeAuth { unCachedMaybeAuth :: Maybe val }
  412. deriving Typeable
  413. -- | Class which states that the given site is an instance of @YesodAuth@
  414. -- and that its @AuthId@ is a lookup key for the full user information in
  415. -- a @YesodPersist@ database.
  416. --
  417. -- The default implementation of @getAuthEntity@ assumes that the @AuthId@
  418. -- for the @YesodAuth@ superclass is in fact a persistent @Key@ for the
  419. -- given value. This is the common case in Yesod, and means that you can
  420. -- easily look up the full information on a given user.
  421. --
  422. -- Since 1.4.0
  423. class (YesodAuth master, YesodPersist master) => YesodAuthPersist master where
  424. -- | If the @AuthId@ for a given site is a persistent ID, this will give the
  425. -- value for that entity. E.g.:
  426. --
  427. -- > type AuthId MySite = UserId
  428. -- > AuthEntity MySite ~ User
  429. --
  430. -- Since 1.2.0
  431. type AuthEntity master :: *
  432. type AuthEntity master = KeyEntity (AuthId master)
  433. getAuthEntity :: AuthId master -> HandlerT master IO (Maybe (AuthEntity master))
  434. #if MIN_VERSION_persistent(2,5,0)
  435. default getAuthEntity
  436. :: ( YesodPersistBackend master ~ backend
  437. , PersistRecordBackend (AuthEntity master) backend
  438. , Key (AuthEntity master) ~ AuthId master
  439. , PersistStore backend
  440. )
  441. => AuthId master -> HandlerT master IO (Maybe (AuthEntity master))
  442. #else
  443. default getAuthEntity
  444. :: ( YesodPersistBackend master
  445. ~ PersistEntityBackend (AuthEntity master)
  446. , Key (AuthEntity master) ~ AuthId master
  447. , PersistStore (YesodPersistBackend master)
  448. , PersistEntity (AuthEntity master)
  449. )
  450. => AuthId master -> HandlerT master IO (Maybe (AuthEntity master))
  451. #endif
  452. getAuthEntity = runDB . get
  453. type family KeyEntity key
  454. type instance KeyEntity (Key x) = x
  455. -- | Similar to 'maybeAuthId', but redirects to a login page if user is not
  456. -- authenticated or responds with error 401 if this is an API client (expecting JSON).
  457. --
  458. -- Since 1.1.0
  459. requireAuthId :: YesodAuth master => HandlerT master IO (AuthId master)
  460. requireAuthId = maybeAuthId >>= maybe handleAuthLack return
  461. -- | Similar to 'maybeAuth', but redirects to a login page if user is not
  462. -- authenticated or responds with error 401 if this is an API client (expecting JSON).
  463. --
  464. -- Since 1.1.0
  465. requireAuth :: ( YesodAuthPersist master
  466. , val ~ AuthEntity master
  467. , Key val ~ AuthId master
  468. , PersistEntity val
  469. , Typeable val
  470. ) => HandlerT master IO (Entity val)
  471. requireAuth = maybeAuth >>= maybe handleAuthLack return
  472. -- | Similar to 'requireAuth', but not tied to Persistent's 'Entity' type.
  473. -- Instead, the 'AuthId' and 'AuthEntity' are returned in a tuple.
  474. --
  475. -- Since 1.4.0
  476. requireAuthPair :: (YesodAuthPersist master, Typeable (AuthEntity master))
  477. => HandlerT master IO (AuthId master, AuthEntity master)
  478. requireAuthPair = maybeAuthPair >>= maybe handleAuthLack return
  479. handleAuthLack :: Yesod master => HandlerT master IO a
  480. handleAuthLack = do
  481. aj <- acceptsJson
  482. if aj then notAuthenticated else redirectLogin
  483. redirectLogin :: Yesod master => HandlerT master IO a
  484. redirectLogin = do
  485. y <- getYesod
  486. setUltDestCurrent
  487. case authRoute y of
  488. Just z -> redirect z
  489. Nothing -> permissionDenied "Please configure authRoute"
  490. instance YesodAuth master => RenderMessage master AuthMessage where
  491. renderMessage = renderAuthMessage
  492. data AuthException = InvalidFacebookResponse
  493. deriving (Show, Typeable)
  494. instance Exception AuthException
  495. instance YesodAuth master => YesodSubDispatch Auth (HandlerT master IO) where
  496. yesodSubDispatch = $(mkYesodSubDispatch resourcesAuth)
  497. asHtml :: Html -> Html
  498. asHtml = id