| Portability | Portable |
|---|---|
| Stability | Stable |
| Maintainer | pbrisbin@gmail.com |
Yesod.Auth.HashDB
Contents
Description
A yesod-auth AuthPlugin designed to look users up in Persist where their user id's and a salted SHA1 hash of their password is stored.
Example usage:
-- import the function
import Auth.HashDB
-- make sure you have an auth route
mkYesodData "MyApp" [$parseRoutes|
/ RootR GET
/auth AuthR Auth getAuth
|]
-- make your app an instance of YesodAuth using this plugin
instance YesodAuth MyApp where
type AuthId MyApp = UserId
loginDest _ = RootR
logoutDest _ = RootR
getAuthId = getAuthIdHashDB AuthR (Just . UniqueUser)
authPlugins = [authHashDB (Just . UniqueUser)]
-- include the migration function in site startup
withServer :: (Application -> IO a) -> IO a
withServer f = withConnectionPool $ \p -> do
runSqlPool (runMigration migrateUsers) p
let h = DevSite p
Note that function which converts username to unique identifier must be same.
Your app must be an instance of YesodPersist. and the username, salt and hashed-passwords should be added to the database.
echo -n 'MySaltMyPassword' | sha1sum
can be used to get the hash from the commandline.
- class HashDBUser user where
- userPasswordHash :: user -> Maybe Text
- userPasswordSalt :: user -> Maybe Text
- setUserHashAndSalt :: Text -> Text -> user -> user
- setSaltAndPasswordHash :: Text -> Text -> user -> user
- setPassword :: (MonadIO m, HashDBUser user) => Text -> user -> m user
- validateUser :: (YesodPersist yesod, b ~ YesodPersistBackend yesod, PersistBackend b (GGHandler sub yesod IO), PersistEntity user, HashDBUser user) => Unique user b -> Text -> GHandler sub yesod Bool
- authHashDB :: (YesodAuth m, YesodPersist m, HashDBUser user, PersistEntity user, b ~ YesodPersistBackend m, PersistBackend b (GGHandler Auth m IO)) => (Text -> Maybe (Unique user b)) -> AuthPlugin m
- getAuthIdHashDB :: (YesodAuth master, YesodPersist master, HashDBUser user, PersistEntity user, Key b user ~ AuthId master, b ~ YesodPersistBackend master, PersistBackend b (GGHandler sub master IO)) => (AuthRoute -> Route master) -> (Text -> Maybe (Unique user b)) -> Creds master -> GHandler sub master (Maybe (AuthId master))
- type User = UserGeneric SqlPersist
- data UserGeneric backend = User {
- userUsername :: Text
- userPassword :: Text
- userSalt :: Text
- type UserId = Key SqlPersist User
- migrateUsers :: forall m. MonadControlIO m => Migration (SqlPersist m)
Documentation
class HashDBUser user whereSource
Interface for data type which holds user info. It's just a collection of getters and setters
Methods
userPasswordHash :: user -> Maybe TextSource
Retrieve password hash from user data
userPasswordSalt :: user -> Maybe TextSource
Retrieve salt for password
Deprecated for the better named setSaltAndPasswordHash
a callback for setPassword
Instances
| HashDBUser (UserGeneric backend) |
setPassword :: (MonadIO m, HashDBUser user) => Text -> user -> m userSource
Set password for user. This function should be used for setting passwords. It generates random salt and calculates proper hashes.
Authentification
Arguments
| :: (YesodPersist yesod, b ~ YesodPersistBackend yesod, PersistBackend b (GGHandler sub yesod IO), PersistEntity user, HashDBUser user) | |
| => Unique user b | User unique identifier |
| -> Text | Password in plaint-text |
| -> GHandler sub yesod Bool |
Given a user ID and password in plaintext, validate them against the database values.
authHashDB :: (YesodAuth m, YesodPersist m, HashDBUser user, PersistEntity user, b ~ YesodPersistBackend m, PersistBackend b (GGHandler Auth m IO)) => (Text -> Maybe (Unique user b)) -> AuthPlugin mSource
Prompt for username and password, validate that against a database which holds the username and a hash of the password
Arguments
| :: (YesodAuth master, YesodPersist master, HashDBUser user, PersistEntity user, Key b user ~ AuthId master, b ~ YesodPersistBackend master, PersistBackend b (GGHandler sub master IO)) | |
| => (AuthRoute -> Route master) | your site's Auth Route |
| -> (Text -> Maybe (Unique user b)) | gets user ID |
| -> Creds master | the creds argument |
| -> GHandler sub master (Maybe (AuthId master)) |
A drop in for the getAuthId method of your YesodAuth instance which can be used if authHashDB is the only plugin in use.
Predefined data type
type User = UserGeneric SqlPersistSource
data UserGeneric backend Source
Generate data base instances for a valid user
Constructors
| User | |
Fields
| |
Instances
| Eq (UserGeneric backend) | |
| Read (UserGeneric backend) | |
| Show (UserGeneric backend) | |
| PersistEntity (UserGeneric backend) | |
| HashDBUser (UserGeneric backend) | |
| Eq (Unique (UserGeneric backend) backend2) | |
| Read (Unique (UserGeneric backend) backend2) | |
| Show (Unique (UserGeneric backend) backend2) |
type UserId = Key SqlPersist UserSource
migrateUsers :: forall m. MonadControlIO m => Migration (SqlPersist m)Source