{-# LANGUAGE OverloadedStrings #-}
module Server.Website.Views.Login
( displayLoginHome
) where
import Server.Core
import Server.Website.Views.Core
import Data.Maybe (isJust)
import Control.Monad (when)
import qualified Data.Text as T
import qualified Data.UUID as UUID
import qualified Text.Blaze as B
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as A
displayLoginHome :: ServerConfiguration -> Maybe UserIdentity -> Maybe T.Text -> UUID.UUID -> H.Html
displayLoginHome :: ServerConfiguration
-> Maybe UserIdentity -> Maybe Text -> UUID -> Html
displayLoginHome ServerConfiguration
serverConfiguration Maybe UserIdentity
userIdentityMaybe Maybe Text
refererMaybe UUID
uuid = do
Bool -> Html -> Html
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe UserIdentity -> Bool
forall a. Maybe a -> Bool
isJust Maybe UserIdentity
userIdentityMaybe) (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ [Char] -> Html
forall a. HasCallStack => [Char] -> a
error [Char]
"You are already signed in."
let shortDescription :: Text
shortDescription = (Text
"Register a new handle or sign in with an existing one. After doing so, you will be able to use decks and have your progress on individual cards tracked." :: T.Text)
Html
H.docType
Html -> Html
H.html (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.lang (Text -> AttributeValue
H.textValue Text
"en-us") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.head (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.title (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Register or sign in :: lojban.io" :: T.Text)
Html
H.meta Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.name (Text -> AttributeValue
H.textValue Text
"description") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.content (Text -> AttributeValue
H.textValue Text
shortDescription)
Html
includeUniversalStylesheets
Html
includeUniversalScripts
[Char] -> Html
includeInternalStylesheet [Char]
"login.css"
[Char] -> Html
includeInternalScript [Char]
"login.js"
Html -> Html
H.body (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
ServerConfiguration -> Maybe UserIdentity -> TopbarCategory -> Html
displayTopbar ServerConfiguration
serverConfiguration Maybe UserIdentity
userIdentityMaybe TopbarCategory
TopbarNone
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"main") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"header") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"header-bg") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"" :: T.Text)
Html -> Html
H.h1 (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Register or sign in" :: T.Text)
Html -> Html
H.p (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml Text
shortDescription
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"body") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Maybe Text -> UUID -> Html
displaySignIn Maybe Text
refererMaybe UUID
uuid
Html
displayFooter
displaySignIn :: Maybe T.Text -> UUID.UUID -> H.Html
displaySignIn :: Maybe Text -> UUID -> Html
displaySignIn Maybe Text
refererMaybe UUID
uuid = do
let handlePattern :: Text
handlePattern = Text
"[a-zA-Z0-9-_.]+" :: T.Text
let maxHandleLength :: Text
maxHandleLength = Text
"60" :: T.Text
let refererTag :: Html
refererTag = case Maybe Text
refererMaybe of
Maybe Text
Nothing -> Html
forall a. Monoid a => a
mempty
Just Text
referer ->
if (Text
"login" Text -> Text -> Bool
`T.isInfixOf` Text
referer) Bool -> Bool -> Bool
|| (Text
"authentication" Text -> Text -> Bool
`T.isInfixOf` Text
referer)
then Html
forall a. Monoid a => a
mempty
else Html
H.input Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.name (Text -> AttributeValue
H.textValue Text
"referer") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.type_ (Text -> AttributeValue
H.textValue Text
"hidden") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.value (Text -> AttributeValue
H.textValue Text
referer)
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"login-main") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html
H.input Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.type_ (Text -> AttributeValue
H.textValue Text
"radio") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.name (Text -> AttributeValue
H.textValue Text
"login-input") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.id (Text -> AttributeValue
H.textValue Text
"login-input-existing") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"login-input-existing") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.checked (Text -> AttributeValue
H.textValue Text
"checked")
Html
H.input Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.type_ (Text -> AttributeValue
H.textValue Text
"radio") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.name (Text -> AttributeValue
H.textValue Text
"login-input") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.id (Text -> AttributeValue
H.textValue Text
"login-input-register") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"login-input-register")
Html -> Html
H.label (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.for (Text -> AttributeValue
H.textValue Text
"login-input-existing") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.h2 (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.span (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"fas fa-user") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml Text
T.empty
Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Sign in with an existing handle" :: T.Text)
Html -> Html
H.label (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.for (Text -> AttributeValue
H.textValue Text
"login-input-register") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.h2 (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.span (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"fas fa-plus-square") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml Text
T.empty
Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Register a new handle" :: T.Text)
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"login-existing") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.h3 (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"If you have already registered a handle, you may sign in using it." :: T.Text)
Html -> Html
H.form (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.action (Text -> AttributeValue
H.textValue Text
"/authentication/handle/login") (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.method (Text -> AttributeValue
H.textValue Text
"POST") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html
refererTag
Html -> Html
H.label (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.for (Text -> AttributeValue
H.textValue Text
"existing-handle") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Handle" :: T.Text)
Html
H.input Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"handle") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.name (Text -> AttributeValue
H.textValue Text
"existing-handle") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.id (Text -> AttributeValue
H.textValue Text
"existing-handle") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.pattern (Text -> AttributeValue
H.textValue Text
handlePattern) Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.maxlength (Text -> AttributeValue
H.textValue Text
maxHandleLength)
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"buttons") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.button (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text -> Html) -> Text -> Html
forall a b. (a -> b) -> a -> b
$ (Text
"Sign in" :: T.Text)
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"login-register") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.h3 (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"You may register a new handle, if you do not have one already." :: T.Text)
Html
H.input Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.type_ (Text -> AttributeValue
H.textValue Text
"radio") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.name (Text -> AttributeValue
H.textValue Text
"login-register-input") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.id (Text -> AttributeValue
H.textValue Text
"login-register-input-random") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"login-register-input-random") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.checked (Text -> AttributeValue
H.textValue Text
"checked")
Html -> Html
H.label (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.for (Text -> AttributeValue
H.textValue Text
"login-register-input-random") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Use a randomly generated handle" :: T.Text)
Html
H.input Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.type_ (Text -> AttributeValue
H.textValue Text
"radio") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.name (Text -> AttributeValue
H.textValue Text
"login-register-input") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.id (Text -> AttributeValue
H.textValue Text
"login-register-input-custom") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"login-register-input-custom")
Html -> Html
H.label (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.for (Text -> AttributeValue
H.textValue Text
"login-register-input-custom") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Choose a custom handle" :: T.Text)
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (AttributeValue
"login-register-random") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.form (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.action (Text -> AttributeValue
H.textValue Text
"/authentication/handle/register") (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.method (Text -> AttributeValue
H.textValue Text
"POST") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html
refererTag
Html -> Html
H.label (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.for (Text -> AttributeValue
H.textValue Text
"new-handle-random") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Generated handle" :: T.Text)
Html
H.input Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"handle") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.name (Text -> AttributeValue
H.textValue Text
"new-handle") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.id (Text -> AttributeValue
H.textValue Text
"new-handle-random") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.value (Text -> AttributeValue
H.textValue (Text -> AttributeValue) -> Text -> AttributeValue
forall a b. (a -> b) -> a -> b
$ UUID -> Text
UUID.toText UUID
uuid) Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.readonly AttributeValue
forall a. Monoid a => a
mempty Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.pattern (Text -> AttributeValue
H.textValue Text
handlePattern) Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.maxlength (Text -> AttributeValue
H.textValue Text
maxHandleLength)
Html -> Html
H.p (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.b (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Remark: " :: T.Text)
Html -> Html
H.span (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Please safely store a copy of this randomly generated identifier." :: T.Text)
Html -> Html
H.span (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
" In the event that you lose it, you will be unable to restore your progress." :: T.Text)
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"buttons") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.button (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text -> Html) -> Text -> Html
forall a b. (a -> b) -> a -> b
$ (Text
"Register" :: T.Text)
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (AttributeValue
"login-register-custom") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.form (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.action (Text -> AttributeValue
H.textValue Text
"/authentication/handle/register") (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.method (Text -> AttributeValue
H.textValue Text
"POST") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html
refererTag
Html -> Html
H.label (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.for (Text -> AttributeValue
H.textValue Text
"new-handle-custom") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Custom handle" :: T.Text)
Html
H.input Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"handle") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.name (Text -> AttributeValue
H.textValue Text
"new-handle") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.id (Text -> AttributeValue
H.textValue Text
"new-handle-custom") Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.pattern (Text -> AttributeValue
H.textValue Text
handlePattern) Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.maxlength (Text -> AttributeValue
H.textValue Text
maxHandleLength)
Html -> Html
H.p (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.b (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"Warning: " :: T.Text)
Html -> Html
H.span (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"For your convenience, we accept the use of a custom identifier in lieu of a randomly generated one." :: T.Text)
Html -> Html
H.span (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
" If you choose this mechanism, please beware that anyone who shares your handle, or anyone who knows your handle, will be able to interfere with your progress." :: T.Text)
Html -> Html
H.p (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.span (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"For information on why we do not accept passwords, please refer to " :: T.Text)
Html -> Html
H.a Html
"Issue #8: Allow signing in or registering without a google account"
Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.href AttributeValue
"https://github.com/jqueiroz/lojban.io/issues/8#issuecomment-705981627"
Html -> Html
H.span (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text
"." :: T.Text)
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
B.! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
H.textValue Text
"buttons") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.button (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
H.toHtml (Text -> Html) -> Text -> Html
forall a b. (a -> b) -> a -> b
$ (Text
"Register" :: T.Text)