Safe Haskell | None |
---|---|
Language | Haskell98 |
- data AuthenticateConfig = AuthenticateConfig {
- _isAuthAdmin :: UserId -> IO Bool
- _usernameAcceptable :: Username -> Maybe CoreError
- _requireEmail :: Bool
- isAuthAdmin :: Lens' AuthenticateConfig (UserId -> IO Bool)
- usernameAcceptable :: Lens' AuthenticateConfig (Username -> Maybe CoreError)
- requireEmail :: Lens' AuthenticateConfig Bool
- data HappstackAuthenticateI18N = HappstackAuthenticateI18N
- newtype UserId :: * = UserId {}
- unUserId :: Functor f => (Integer -> f Integer) -> UserId -> f UserId
- rUserId :: Boomerang e tok ((:-) Integer r) ((:-) UserId r)
- succUserId :: UserId -> UserId
- jsonOptions :: Options
- toJSONResponse :: (RenderMessage HappstackAuthenticateI18N e, ToJSON a) => Either e a -> Response
- toJSONSuccess :: ToJSON a => a -> Response
- toJSONError :: forall e. RenderMessage HappstackAuthenticateI18N e => e -> Response
- newtype Username = Username {
- _unUsername :: Text
- unUsername :: Iso' Username Text
- rUsername :: forall tok e r. Boomerang e tok ((:-) Text r) ((:-) Username r)
- usernamePolicy :: Username -> Maybe CoreError
- newtype Email = Email {}
- unEmail :: Iso' Email Text
- data User = User {}
- userId :: Lens' User UserId
- username :: Lens' User Username
- email :: Lens' User (Maybe Email)
- type UserIxs = '[UserId, Username, Email]
- type IxUser = IxSet UserIxs User
- newtype SharedSecret = SharedSecret {}
- unSharedSecret :: Iso' SharedSecret Text
- genSharedSecret :: MonadIO m => m SharedSecret
- genSharedSecretDevURandom :: IO SharedSecret
- genSharedSecretSysRandom :: IO SharedSecret
- type SharedSecrets = Map UserId SharedSecret
- initialSharedSecrets :: SharedSecrets
- data CoreError
- data NewAccountMode
- data AuthenticateState = AuthenticateState {}
- sharedSecrets :: Lens' AuthenticateState SharedSecrets
- users :: Lens' AuthenticateState IxUser
- nextUserId :: Lens' AuthenticateState UserId
- defaultSessionTimeout :: Lens' AuthenticateState Int
- newAccountMode :: Lens' AuthenticateState NewAccountMode
- initialAuthenticateState :: AuthenticateState
- data SetSharedSecret = SetSharedSecret UserId SharedSecret
- newtype GetSharedSecret = GetSharedSecret UserId
- newtype SetDefaultSessionTimeout = SetDefaultSessionTimeout Int
- data GetDefaultSessionTimeout = GetDefaultSessionTimeout
- newtype SetNewAccountMode = SetNewAccountMode NewAccountMode
- data GetNewAccountMode = GetNewAccountMode
- newtype CreateUser = CreateUser User
- data CreateAnonymousUser = CreateAnonymousUser
- newtype UpdateUser = UpdateUser User
- newtype DeleteUser = DeleteUser UserId
- newtype GetUserByUsername = GetUserByUsername Username
- newtype GetUserByUserId = GetUserByUserId UserId
- newtype GetUserByEmail = GetUserByEmail Email
- data GetAuthenticateState = GetAuthenticateState
- getOrGenSharedSecret :: MonadIO m => AcidState AuthenticateState -> UserId -> m SharedSecret
- data Token = Token {}
- tokenUser :: Lens' Token User
- tokenIsAuthAdmin :: Lens' Token Bool
- type TokenText = Text
- issueToken :: MonadIO m => AcidState AuthenticateState -> AuthenticateConfig -> User -> m TokenText
- decodeAndVerifyToken :: MonadIO m => AcidState AuthenticateState -> UTCTime -> TokenText -> m (Maybe (Token, JWT VerifiedJWT))
- authCookieName :: String
- addTokenCookie :: Happstack m => AcidState AuthenticateState -> AuthenticateConfig -> User -> m TokenText
- deleteTokenCookie :: Happstack m => m ()
- getTokenCookie :: Happstack m => AcidState AuthenticateState -> m (Maybe (Token, JWT VerifiedJWT))
- getTokenHeader :: Happstack m => AcidState AuthenticateState -> m (Maybe (Token, JWT VerifiedJWT))
- getToken :: Happstack m => AcidState AuthenticateState -> m (Maybe (Token, JWT VerifiedJWT))
- getUserId :: Happstack m => AcidState AuthenticateState -> m (Maybe UserId)
- newtype AuthenticationMethod = AuthenticationMethod {}
- unAuthenticationMethod :: Iso' AuthenticationMethod Text
- rAuthenticationMethod :: forall tok e r. Boomerang e tok ((:-) Text r) ((:-) AuthenticationMethod r)
- type AuthenticationHandler = [Text] -> RouteT AuthenticateURL (ServerPartT IO) Response
- type AuthenticationHandlers = Map AuthenticationMethod AuthenticationHandler
- data AuthenticateURL
- rAuthenticationMethods :: forall tok e r. Boomerang e tok ((:-) (Maybe (AuthenticationMethod, [Text])) r) ((:-) AuthenticateURL r)
- rControllers :: forall tok e r. Boomerang e tok r ((:-) AuthenticateURL r)
- authenticateURL :: Router () (AuthenticateURL :- ())
- nestAuthenticationMethod :: PathInfo methodURL => AuthenticationMethod -> RouteT methodURL m a -> RouteT AuthenticateURL m a
Documentation
data AuthenticateConfig Source #
Various configuration options that apply to all authentication methods
AuthenticateConfig | |
|
isAuthAdmin :: Lens' AuthenticateConfig (UserId -> IO Bool) Source #
a UserId
uniquely identifies a user.
succUserId :: UserId -> UserId #
get the next UserId
jsonOptions :: Options Source #
when creating JSON field names, drop the first character. Since we are using lens, the leading character should always be _.
toJSONResponse :: (RenderMessage HappstackAuthenticateI18N e, ToJSON a) => Either e a -> Response Source #
convert a value to a JSON encoded Response
toJSONError :: forall e. RenderMessage HappstackAuthenticateI18N e => e -> Response Source #
convert an error to a JSON encoded Response
FIXME: I18N
an arbitrary, but unique string that the user uses to identify themselves
an Email
address. No validation in performed.
A unique User
newtype SharedSecret Source #
The shared secret is used to encrypt a users data on a per-user basis. We can invalidate a JWT value by changing the shared secret.
genSharedSecret :: MonadIO m => m SharedSecret Source #
Generate a Salt
from 128 bits of data from /dev/urandom
, with the
system RNG as a fallback. This is the function used to generate salts by
makePassword
.
genSharedSecretDevURandom :: IO SharedSecret Source #
Generate a SharedSecret
from /dev/urandom
.
see: genSharedSecret
genSharedSecretSysRandom :: IO SharedSecret Source #
Generate a SharedSecret
from Random
.
see: genSharedSecret
type SharedSecrets = Map UserId SharedSecret Source #
A map which stores the SharedSecret
for each UserId
initialSharedSecrets :: SharedSecrets Source #
An empty SharedSecrets
the CoreError
type is used to represent errors in a language
agnostic manner. The errors are translated into human readable form
via the I18N translations.
HandlerNotFound | |
URLDecodeFailed | |
UsernameAlreadyExists | |
AuthorizationRequired | |
Forbidden | |
JSONDecodeFailed | |
InvalidUserId | |
UsernameNotAcceptable | |
InvalidEmail | |
TextError Text |
data NewAccountMode Source #
This value is used to configure the type of new user registrations permitted for this system.
OpenRegistration | new users can create their own accounts |
ModeratedRegistration | new users can apply to create their own accounts, but a moderator must approve them before they are active |
ClosedRegistration | only the admin can create a new account |
data AuthenticateState Source #
this acid-state value contains the state common to all authentication methods
AuthenticateState | |
|
initialAuthenticateState :: AuthenticateState Source #
a reasonable initial AuthenticateState
newtype SetDefaultSessionTimeout Source #
newtype SetNewAccountMode Source #
data GetNewAccountMode Source #
newtype CreateUser Source #
data CreateAnonymousUser Source #
newtype UpdateUser Source #
newtype DeleteUser Source #
newtype GetUserByUsername Source #
newtype GetUserByUserId Source #
newtype GetUserByEmail Source #
data GetAuthenticateState Source #
getOrGenSharedSecret :: MonadIO m => AcidState AuthenticateState -> UserId -> m SharedSecret Source #
get the SharedSecret
for UserId
. Generate one if they don't have one yet.
The Token
type represents the encrypted data used to identify a
user.
Token | |
|
:: MonadIO m | |
=> AcidState AuthenticateState | |
-> AuthenticateConfig | |
-> User | the user |
-> m TokenText |
decodeAndVerifyToken :: MonadIO m => AcidState AuthenticateState -> UTCTime -> TokenText -> m (Maybe (Token, JWT VerifiedJWT)) Source #
addTokenCookie :: Happstack m => AcidState AuthenticateState -> AuthenticateConfig -> User -> m TokenText Source #
create a Token
for User
and add a Cookie
to the Response
see also: issueToken
getTokenCookie :: Happstack m => AcidState AuthenticateState -> m (Maybe (Token, JWT VerifiedJWT)) Source #
getTokenHeader :: Happstack m => AcidState AuthenticateState -> m (Maybe (Token, JWT VerifiedJWT)) Source #
get, decode, and verify the Token
from the Authorization
HTTP header
getToken :: Happstack m => AcidState AuthenticateState -> m (Maybe (Token, JWT VerifiedJWT)) Source #
get, decode, and verify the Token
looking first in the
Authorization
header and then in Cookie
.
see also: getTokenHeader
, getTokenCookie
newtype AuthenticationMethod Source #
AuthenticationMethod
is used by the routing system to select which
authentication backend should handle this request.
rAuthenticationMethod :: forall tok e r. Boomerang e tok ((:-) Text r) ((:-) AuthenticationMethod r) Source #
type AuthenticationHandler = [Text] -> RouteT AuthenticateURL (ServerPartT IO) Response Source #
data AuthenticateURL Source #
Eq AuthenticateURL Source # | |
Data AuthenticateURL Source # | |
Ord AuthenticateURL Source # | |
Read AuthenticateURL Source # | |
Show AuthenticateURL Source # | |
Generic AuthenticateURL Source # | |
PathInfo AuthenticateURL Source # | |
(Functor m, Monad m) => EmbedAsChild (Partial' m) PartialMsgs # | |
(Functor m, Monad m) => EmbedAsChild (Partial' m) PartialMsgs # | |
(Functor m, Monad m) => EmbedAsAttr (Partial' m) (Attr Text PartialMsgs) # | |
(Functor m, Monad m) => EmbedAsAttr (Partial' m) (Attr Text PartialMsgs) # | |
type Rep AuthenticateURL Source # | |
rAuthenticationMethods :: forall tok e r. Boomerang e tok ((:-) (Maybe (AuthenticationMethod, [Text])) r) ((:-) AuthenticateURL r) Source #
rControllers :: forall tok e r. Boomerang e tok r ((:-) AuthenticateURL r) Source #
authenticateURL :: Router () (AuthenticateURL :- ()) Source #
a Router
for AuthenicateURL
nestAuthenticationMethod :: PathInfo methodURL => AuthenticationMethod -> RouteT methodURL m a -> RouteT AuthenticateURL m a Source #
helper function which converts a URL for an authentication
backend into an AuthenticateURL
.