Authentication system

This commit is contained in:
Michael Snoyman 2014-04-09 14:38:54 +03:00
parent 714ee2b272
commit 3c5637dc6d
18 changed files with 342 additions and 48 deletions

View File

@ -7,7 +7,6 @@ module Application
import Import import Import
import Settings import Settings
import Yesod.Auth
import Yesod.Default.Config import Yesod.Default.Config
import Yesod.Default.Main import Yesod.Default.Main
import Yesod.Default.Handlers import Yesod.Default.Handlers
@ -21,10 +20,16 @@ import Control.Concurrent (forkIO, threadDelay)
import System.Log.FastLogger (newStdoutLoggerSet, defaultBufSize) import System.Log.FastLogger (newStdoutLoggerSet, defaultBufSize)
import Network.Wai.Logger (clockDateCacher) import Network.Wai.Logger (clockDateCacher)
import Yesod.Core.Types (loggerSet, Logger (Logger)) import Yesod.Core.Types (loggerSet, Logger (Logger))
import qualified System.Random.MWC as MWC
import qualified Network.Wai as Wai
import Network.Wai.Middleware.MethodOverride (methodOverride)
-- Import all relevant handler modules here. -- Import all relevant handler modules here.
-- Don't forget to add new modules to your cabal file! -- Don't forget to add new modules to your cabal file!
import Handler.Home import Handler.Home
import Handler.Profile
import Handler.Email
import Handler.ResetToken
-- This line actually creates our YesodDispatch instance. It is the second half -- This line actually creates our YesodDispatch instance. It is the second half
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the -- of the call to mkYesodData which occurs in Foundation.hs. Please see the
@ -51,7 +56,11 @@ makeApplication conf = do
-- Create the WAI application and apply middlewares -- Create the WAI application and apply middlewares
app <- toWaiAppPlain foundation app <- toWaiAppPlain foundation
let logFunc = messageLoggerSource foundation (appLogger foundation) let logFunc = messageLoggerSource foundation (appLogger foundation)
return (logWare app, logFunc) middleware = logWare . defaultWAIMiddleware
return (middleware app, logFunc)
defaultWAIMiddleware :: Wai.Middleware -- FIXME move upstream
defaultWAIMiddleware = methodOverride
-- | Loads up any necessary settings, creates your foundation datatype, and -- | Loads up any necessary settings, creates your foundation datatype, and
-- performs some initialization. -- performs some initialization.
@ -77,8 +86,18 @@ makeFoundation conf = do
updateLoop updateLoop
_ <- forkIO updateLoop _ <- forkIO updateLoop
gen <- MWC.createSystemRandom
let logger = Yesod.Core.Types.Logger loggerSet' getter let logger = Yesod.Core.Types.Logger loggerSet' getter
foundation = App conf s p manager dbconf logger foundation = App
{ settings = conf
, getStatic = s
, connPool = p
, httpManager = manager
, persistConfig = dbconf
, appLogger = logger
, genIO = gen
}
-- Perform database migration using our application's logging settings. -- Perform database migration using our application's logging settings.
runLoggingT runLoggingT

88
Data/Slug.hs Normal file
View File

@ -0,0 +1,88 @@
module Data.Slug
( Slug
, mkSlug
, safeMakeSlug
, unSlug
, InvalidSlugException (..)
, HasGenIO (..)
, randomSlug
, slugField
) where
import ClassyPrelude.Yesod
import Database.Persist.Sql (PersistFieldSql)
import qualified System.Random.MWC as MWC
import Control.Monad.Reader (MonadReader, ask)
import GHC.Prim (RealWorld)
import Text.Blaze (ToMarkup)
newtype Slug = Slug { unSlug :: Text }
deriving (Show, Read, Eq, Typeable, PersistField, PersistFieldSql, ToMarkup)
mkSlug :: MonadThrow m => Text -> m Slug
mkSlug t
| length t < minLen = throwM $ InvalidSlugException t "Too short"
| length t > maxLen = throwM $ InvalidSlugException t "Too long"
| any (not . validChar) t = throwM $ InvalidSlugException t "Contains invalid characters"
| "-" `isPrefixOf` t = throwM $ InvalidSlugException t "Must not start with a hyphen"
| otherwise = return $ Slug t
where
minLen, maxLen :: Int
minLen = 3
maxLen = 30
validChar :: Char -> Bool
validChar c =
('A' <= c && c <= 'Z') ||
('a' <= c && c <= 'z') ||
('0' <= c && c <= '9') ||
c == '-' ||
c == '_'
data InvalidSlugException = InvalidSlugException !Text !Text
deriving (Show, Typeable)
instance Exception InvalidSlugException
instance PathPiece Slug where
toPathPiece = unSlug
fromPathPiece = mkSlug
class HasGenIO a where
getGenIO :: a -> MWC.GenIO
instance s ~ RealWorld => HasGenIO (MWC.Gen s) where
getGenIO = id
safeMakeSlug :: (MonadIO m, MonadReader env m, HasGenIO env)
=> Text
-> Bool -- ^ force some randomness?
-> m Slug
safeMakeSlug orig forceRandom
| needsRandom || forceRandom = do
gen <- liftM getGenIO ask
cs <- liftIO $ replicateM 3 $ MWC.uniformR (0, 61) gen
return $ Slug $ cleaned ++ pack ('_':map toChar cs)
| otherwise = return $ Slug cleaned
where
cleaned = take (maxLen - minLen - 1) $ dropWhile (== '-') $ filter validChar orig
needsRandom = length cleaned < minLen
toChar :: Int -> Char
toChar i
| i < 26 = toEnum $ fromEnum 'A' + i
| i < 52 = toEnum $ fromEnum 'a' + i - 26
| otherwise = toEnum $ fromEnum '0' + i - 52
randomSlug :: (MonadIO m, MonadReader env m, HasGenIO env)
=> Int -- ^ length
-> m Slug
randomSlug (min maxLen . max minLen -> len) = do
gen <- liftM getGenIO ask
cs <- liftIO $ replicateM len $ MWC.uniformR (0, 61) gen
return $ Slug $ pack $ map toChar cs
slugField :: (Monad m, RenderMessage (HandlerSite m) FormMessage) => Field m Slug
slugField =
checkMMap go unSlug textField
where
go = return . either (Left . tshow) Right . mkSlug

View File

@ -1,24 +1,22 @@
module Foundation where module Foundation where
import Prelude import ClassyPrelude.Yesod
import Yesod
import Yesod.Static
import Yesod.Auth import Yesod.Auth
import Yesod.Auth.BrowserId import Yesod.Auth.BrowserId
import Yesod.Auth.GoogleEmail import Yesod.Auth.GoogleEmail
import Yesod.Default.Config import Yesod.Default.Config
import Yesod.Default.Util (addStaticContentExternal) import Yesod.Default.Util (addStaticContentExternal)
import Network.HTTP.Client.Conduit (Manager, HasHttpManager (getHttpManager))
import qualified Settings import qualified Settings
import Settings.Development (development) import Settings.Development (development)
import qualified Database.Persist import qualified Database.Persist
import Database.Persist.Sql (SqlPersistT)
import Settings.StaticFiles import Settings.StaticFiles
import Settings (widgetFile, Extra (..)) import Settings (widgetFile, Extra (..))
import Model import Model
import Text.Jasmine (minifym) import Text.Jasmine (minifym)
import Text.Hamlet (hamletFile) import Text.Hamlet (hamletFile)
import Yesod.Core.Types (Logger) import Yesod.Core.Types (Logger)
import Data.Slug (safeMakeSlug, HasGenIO (getGenIO), randomSlug, Slug)
import qualified System.Random.MWC as MWC
-- | The site argument for your application. This can be a good place to -- | The site argument for your application. This can be a good place to
-- keep settings and values requiring initialization before your application -- keep settings and values requiring initialization before your application
@ -31,8 +29,12 @@ data App = App
, httpManager :: Manager , httpManager :: Manager
, persistConfig :: Settings.PersistConf , persistConfig :: Settings.PersistConf
, appLogger :: Logger , appLogger :: Logger
, genIO :: !MWC.GenIO
} }
instance HasGenIO App where
getGenIO = genIO
instance HasHttpManager App where instance HasHttpManager App where
getHttpManager = httpManager getHttpManager = httpManager
@ -61,6 +63,7 @@ instance Yesod App where
defaultLayout widget = do defaultLayout widget = do
master <- getYesod master <- getYesod
mmsg <- getMessage mmsg <- getMessage
muser <- maybeAuth
-- We break up the default layout into two components: -- We break up the default layout into two components:
-- default-layout is the contents of the body tag, and -- default-layout is the contents of the body tag, and
@ -74,6 +77,10 @@ instance Yesod App where
, css_bootstrap_css , css_bootstrap_css
]) ])
$(widgetFile "default-layout") $(widgetFile "default-layout")
mcurr <- getCurrentRoute
let notHome = mcurr /= Just HomeR
giveUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet") giveUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
-- This is done to provide an optimization for serving static files from -- This is done to provide an optimization for serving static files from
@ -122,21 +129,73 @@ instance YesodAuth App where
-- Where to send a user after logout -- Where to send a user after logout
logoutDest _ = HomeR logoutDest _ = HomeR
getAuthId creds = runDB $ do getAuthId creds = do
x <- getBy $ UniqueUser $ credsIdent creds muid <- maybeAuthId
case x of join $ runDB $ case muid of
Just (Entity uid _) -> return $ Just uid
Nothing -> do Nothing -> do
fmap Just $ insert User x <- getBy $ UniqueEmail $ credsIdent creds
{ userIdent = credsIdent creds case x of
, userPassword = Nothing Just (Entity _ email) -> return $ return $ Just $ emailUser email
} Nothing -> do
handle' <- getHandle (0 :: Int)
token <- getToken
userid <- insert User
{ userHandle = handle'
, userDisplay = credsIdent creds
, userToken = token
}
void $ insert Email
{ emailEmail = credsIdent creds
, emailUser = userid
}
return $ return $ Just userid
Just uid -> do
memail <- getBy $ UniqueEmail $ credsIdent creds
case memail of
Nothing -> do
void $ insert Email
{ emailEmail = credsIdent creds
, emailUser = uid
}
return $ do
setMessage $ toHtml $ concat
[ "Email address "
, credsIdent creds
, " added to your account."
]
redirect ProfileR
Just _ -> invalidArgs $ return $ concat
[ "The email address "
, credsIdent creds
, " is already associated with a different account."
]
where
handleBase = takeWhile (/= '@') (credsIdent creds)
getHandle cnt | cnt > 50 = error "Could not get a unique slug"
getHandle cnt = do
slug <- lift $ safeMakeSlug handleBase (cnt > 0)
muser <- getBy $ UniqueHandle slug
case muser of
Nothing -> return slug
Just _ -> getHandle (cnt + 1)
-- You can add other plugins like BrowserID, email or OAuth here -- You can add other plugins like BrowserID, email or OAuth here
authPlugins _ = [authBrowserId def, authGoogleEmail] authPlugins _ = [authBrowserId def, authGoogleEmail]
authHttpManager = httpManager authHttpManager = httpManager
getToken :: YesodDB App Slug
getToken =
go (0 :: Int)
where
go cnt | cnt > 50 = error "Could not get a unique token"
go cnt = do
slug <- lift $ randomSlug 25
muser <- getBy $ UniqueToken slug
case muser of
Nothing -> return slug
Just _ -> go (cnt + 1)
-- This instance is required to use forms. You can modify renderMessage to -- This instance is required to use forms. You can modify renderMessage to
-- achieve customized and internationalized form validation messages. -- achieve customized and internationalized form validation messages.
instance RenderMessage App FormMessage where instance RenderMessage App FormMessage where

14
Handler/Email.hs Normal file
View File

@ -0,0 +1,14 @@
module Handler.Email where
import Import
import Database.Persist.Sql (deleteWhereCount)
deleteEmailR :: EmailId -> Handler ()
deleteEmailR eid = do
Entity uid _ <- requireAuth
cnt <- runDB $ deleteWhereCount [EmailUser ==. uid, EmailId ==. eid]
setMessage $
if cnt > 0
then "Email address deleted"
else "No matching email address found"
redirect ProfileR

View File

@ -12,28 +12,6 @@ import Import
-- inclined, or create a single monolithic file. -- inclined, or create a single monolithic file.
getHomeR :: Handler Html getHomeR :: Handler Html
getHomeR = do getHomeR = do
(formWidget, formEnctype) <- generateFormPost sampleForm
let submission = Nothing :: Maybe (FileInfo, Text)
handlerName = "getHomeR" :: Text
defaultLayout $ do defaultLayout $ do
aDomId <- newIdent setTitle "Stackage Server"
setTitle "Welcome To Yesod!"
$(widgetFile "homepage") $(widgetFile "homepage")
postHomeR :: Handler Html
postHomeR = do
((result, formWidget), formEnctype) <- runFormPost sampleForm
let handlerName = "postHomeR" :: Text
submission = case result of
FormSuccess res -> Just res
_ -> Nothing
defaultLayout $ do
aDomId <- newIdent
setTitle "Welcome To Yesod!"
$(widgetFile "homepage")
sampleForm :: Form (FileInfo, Text)
sampleForm = renderDivs $ (,)
<$> fileAFormReq "Choose a file"
<*> areq textField "What's on the file?" Nothing

30
Handler/Profile.hs Normal file
View File

@ -0,0 +1,30 @@
module Handler.Profile where
import Import
import Data.Slug (slugField)
userForm :: User -> Form User
userForm user = renderBootstrap $ User
<$> areq slugField "User handle"
{ fsTooltip = Just "Used for URLs"
} (Just $ userHandle user)
<*> areq textField "Display name" (Just $ userDisplay user)
<*> pure (userToken user)
getProfileR :: Handler Html
getProfileR = do
Entity uid user <- requireAuth
((result, userWidget), enctype) <- runFormPost $ userForm user
case result of
FormSuccess user' -> do
runDB $ replace uid user'
setMessage "Profile updated"
redirect ProfileR
_ -> return ()
emails <- runDB $ selectList [EmailUser ==. uid] [Asc EmailEmail]
defaultLayout $ do
setTitle "Your Profile"
$(widgetFile "profile")
putProfileR :: Handler Html
putProfileR = getProfileR

12
Handler/ResetToken.hs Normal file
View File

@ -0,0 +1,12 @@
module Handler.ResetToken where
import Import
postResetTokenR :: Handler ()
postResetTokenR = do
Entity uid _ <- requireAuth
runDB $ do
token <- getToken
update uid [UserToken =. token]
setMessage "Token updated"
redirect ProfileR

View File

@ -8,3 +8,4 @@ import Model as Import
import Settings as Import import Settings as Import
import Settings.Development as Import import Settings.Development as Import
import Settings.StaticFiles as Import import Settings.StaticFiles as Import
import Yesod.Auth as Import

View File

@ -5,6 +5,7 @@ import Yesod
import Data.Text (Text) import Data.Text (Text)
import Database.Persist.Quasi import Database.Persist.Quasi
import Data.Typeable (Typeable) import Data.Typeable (Typeable)
import Data.Slug (Slug)
-- You can define all of your database entities in the entities file. -- You can define all of your database entities in the entities file.
-- You can find more information on persistent and how to declare entities -- You can find more information on persistent and how to declare entities

View File

@ -1,12 +1,15 @@
User User
ident Text handle Slug
password Text Maybe display Text
UniqueUser ident token Slug
UniqueHandle handle
UniqueToken token
deriving Typeable deriving Typeable
Email Email
email Text email Text
user UserId Maybe user UserId
verkey Text Maybe
UniqueEmail email UniqueEmail email
-- By default this file is used in Model.hs (which is imported by Foundation.hs) Verkey
email Text
verkey Text

View File

@ -4,4 +4,7 @@
/favicon.ico FaviconR GET /favicon.ico FaviconR GET
/robots.txt RobotsR GET /robots.txt RobotsR GET
/ HomeR GET POST / HomeR GET
/profile ProfileR GET PUT
/email/#EmailId EmailR DELETE
/reset-token ResetTokenR POST

View File

@ -19,7 +19,11 @@ library
Settings Settings
Settings.StaticFiles Settings.StaticFiles
Settings.Development Settings.Development
Data.Slug
Handler.Home Handler.Home
Handler.Profile
Handler.Email
Handler.ResetToken
if flag(dev) || flag(library-only) if flag(dev) || flag(library-only)
cpp-options: -DDEVELOPMENT cpp-options: -DDEVELOPMENT
@ -40,6 +44,9 @@ library
EmptyDataDecls EmptyDataDecls
NoMonomorphismRestriction NoMonomorphismRestriction
DeriveDataTypeable DeriveDataTypeable
ViewPatterns
TypeSynonymInstances
FlexibleInstances
build-depends: base >= 4 && < 5 build-depends: base >= 4 && < 5
, yesod >= 1.2.5 && < 1.3 , yesod >= 1.2.5 && < 1.3
@ -66,8 +73,14 @@ library
, conduit >= 1.0 && < 2.0 , conduit >= 1.0 && < 2.0
, monad-logger >= 0.3 && < 0.4 , monad-logger >= 0.3 && < 0.4
, fast-logger >= 2.1.4 && < 2.2 , fast-logger >= 2.1.4 && < 2.2
, wai >= 2.1 && < 2.2
, wai-logger >= 2.1 && < 2.2 , wai-logger >= 2.1 && < 2.2
, classy-prelude-yesod >= 0.9 && < 0.9.1 , classy-prelude-yesod >= 0.9 && < 0.9.1
, mwc-random >= 0.13 && < 0.14
, mtl >= 2.1 && < 2.2
, blaze-markup >= 0.6 && < 0.7
, ghc-prim
, ghc-prim
executable stackage-server executable stackage-server
if flag(library-only) if flag(library-only)
@ -98,3 +111,6 @@ test-suite test
, monad-logger , monad-logger
, transformers , transformers
, hspec , hspec
, classy-prelude-yesod
, mtl
, mwc-random

View File

@ -8,7 +8,10 @@ $newline never
<head> <head>
<meta charset="UTF-8"> <meta charset="UTF-8">
<title>#{pageTitle pc} <title>
#{pageTitle pc}
$if notHome
:: Stackage Server
<meta name="description" content=""> <meta name="description" content="">
<meta name="author" content=""> <meta name="author" content="">

View File

@ -1,3 +1,14 @@
<nav .navbar .navbar-default role=navigation>
<p>
<a href=@{HomeR}>Home
$maybe Entity _ user <- muser
You are logged in as #{userDisplay user} (#{userHandle user}).
View public page
<a href=@{ProfileR}>Edit profile
<a href=@{AuthR LogoutR}>Logout
$nothing
<a href=@{AuthR LoginR}>Login
$maybe msg <- mmsg $maybe msg <- mmsg
<div #message>#{msg} <div .alert .alter-info>#{msg}
^{widget} ^{widget}

28
templates/profile.hamlet Normal file
View File

@ -0,0 +1,28 @@
<h2>Email addresses
$if length emails <= 1
$forall Entity _ email <- emails
<p>#{emailEmail email}
$else
<ul>
$forall Entity eid email <- emails
<li .email>
#{emailEmail email}
<form method=post action=@{EmailR eid}?_method=DELETE>
<button .btn>Remove
<p>
<a href=@{AuthR LoginR}>Add another email address.
<h2>Profile
<form method=post action=@{ProfileR}?_method=PUT enctype=#{enctype} role=form>
<div .form-group>
^{userWidget}
<button .btn>Update
<h2>Security token
<p>
Your security token is #{userToken user}.
<form method=post action=@{ResetTokenR}>
<button>Reset token

3
templates/profile.lucius Normal file
View File

@ -0,0 +1,3 @@
.email > form {
display: inline-block;
}

22
test/Data/SlugSpec.hs Normal file
View File

@ -0,0 +1,22 @@
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Data.SlugSpec where
import Test.Hspec
import Test.Hspec.QuickCheck
import Data.Slug
import ClassyPrelude.Yesod
import qualified System.Random.MWC as MWC
import Control.Monad.Reader (runReaderT)
spec :: Spec
spec = describe "Data.Slug" $ do
prop "safeMakeSlug generates valid slugs" $ \(pack -> orig) -> do
gen <- MWC.createSystemRandom
slug <- runReaderT (safeMakeSlug orig False) gen
mkSlug (unSlug slug) `shouldBe` Just slug
prop "randomization works" $ \(pack -> orig) -> do
gen <- MWC.createSystemRandom
slug1 <- runReaderT (safeMakeSlug orig True) gen
slug2 <- runReaderT (safeMakeSlug orig True) gen
when (slug1 == slug2) $ error $ show (slug1, slug2)

View File

@ -10,6 +10,8 @@ import Yesod.Test
import Test.Hspec (hspec) import Test.Hspec (hspec)
import Application (makeFoundation) import Application (makeFoundation)
import qualified Data.SlugSpec
main :: IO () main :: IO ()
main = do main = do
conf <- Yesod.Default.Config.loadConfig $ (configSettings Testing) conf <- Yesod.Default.Config.loadConfig $ (configSettings Testing)
@ -17,5 +19,6 @@ main = do
} }
foundation <- makeFoundation conf foundation <- makeFoundation conf
hspec $ do hspec $ do
Data.SlugSpec.spec
yesodSpec foundation $ do yesodSpec foundation $ do
return () return ()