dnsmanager-webclient/src/App/Page/Setup.purs

198 lines
6.6 KiB
Text

-- | `App.SetupInterface` enables users to change their password or their email address.
-- | Users can also erase their account.
module App.Page.Setup where
import Prelude (Unit, bind, discard, pure, ($), (<<<), (==), (<>), show, map)
import Data.Array as A
import Data.Tuple (Tuple(..))
import Data.Maybe (Maybe(..), maybe)
import Data.Either (Either(..))
import Effect.Aff.Class (class MonadAff)
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Web.Event.Event as Event
import Web.Event.Event (Event)
import Bulma as Bulma
import CSSClasses as C
import App.Type.Email as Email
import App.Validation.Password as P
import App.Type.LogMessage
import App.Message.AuthenticationDaemon as AuthD
data Output
= Log LogMessage
| ChangePassword String
| ChangeEmailAddress
| DeleteUserAccount
-- | The component's parent provides received messages.
data Query a
= MessageReceived AuthD.AnswerMessage a
type Slot = H.Slot Query Output
type Input = Tuple (Maybe Email.Email) (Maybe Email.Email)
data AuthenticationInput
= AUTH_INP_login String
| AUTH_INP_pass String
data NewPasswordInput
= NEWPASS_INP_password String
| NEWPASS_INP_confirmation String
data Action
= HandleNewPassword NewPasswordInput -- user input
| ChangePasswordAttempt Event -- validation
| SendChangePasswordMessage -- sends the message
| RouteChangeEmailAddressPage
| CancelModal
| DeleteAccountPopup
| DeleteAccount
type StateNewPasswordForm = { password :: String, confirmation :: String }
data Modal
= NoModal
| DeleteAccountModal
type State =
{ newPasswordForm :: StateNewPasswordForm
, emails :: Tuple (Maybe Email.Email) (Maybe Email.Email)
, modal :: Modal
}
component :: forall m. MonadAff m => H.Component Query Input Output m
component =
H.mkComponent
{ initialState
, render
, eval: H.mkEval $ H.defaultEval
{ handleAction = handleAction
, handleQuery = handleQuery
}
}
initialState :: Input -> State
initialState emails =
{ newPasswordForm: { password: "", confirmation: "" }
, emails
, modal: NoModal
}
render :: forall m. State -> H.ComponentHTML Action () m
render { modal, newPasswordForm, emails } =
Bulma.section_small
[ render_emails emails
, Bulma.hr
, case modal of
DeleteAccountModal -> render_delete_account_modal
NoModal -> Bulma.columns_
[ b [ Bulma.btn_ [C.is_large, C.is_info] "Change email address" RouteChangeEmailAddressPage ]
, b [ Bulma.h3 "Change password", render_new_password_form ]
, b [ Bulma.h3 "Delete account", render_delete_account ]
]
]
where
b e = Bulma.column_ e
render_emails (Tuple current pending) = HH.div [] $ render_current current <> render_pending pending
where
render_current (Just (Email.Email e)) = [ Bulma.p $ "Current email address: " ] <>
[ Bulma.btn_ro [C.is_small, C.is_warning] e]
render_current Nothing = [ Bulma.p "You do not currently have a validated email address." ]
render_pending (Just (Email.Email e)) = [ Bulma.p $ "Pending email address: " ] <>
[ Bulma.btn_ro [C.is_small, C.is_warning] e]
render_pending Nothing = []
render_delete_account = Bulma.alert_btn "Delete my account" DeleteAccountPopup
render_new_password_form = HH.form
[ HE.onSubmit ChangePasswordAttempt ]
[ Bulma.box_password "passwordNEWPASS" "New Password" "password"
(HandleNewPassword <<< NEWPASS_INP_password)
newPasswordForm.password
, Bulma.box_password "confirmationNEWPASS" "Confirmation" "confirmation"
(HandleNewPassword <<< NEWPASS_INP_confirmation)
newPasswordForm.confirmation
, Bulma.btn_validation
]
render_delete_account_modal = Bulma.modal "Delete your account"
[ Bulma.p "Your account and domains will be removed."
, Bulma.strong "⚠ You won't be able to recover your data."
]
[ Bulma.alert_btn "GO AHEAD LOL" DeleteAccount
, Bulma.cancel_button CancelModal
]
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
handleAction = case _ of
HandleNewPassword authinp -> do
case authinp of
NEWPASS_INP_password v -> H.modify_ _ { newPasswordForm { password = v } }
NEWPASS_INP_confirmation v -> H.modify_ _ { newPasswordForm { confirmation = v } }
CancelModal -> do
H.modify_ _ { modal = NoModal }
DeleteAccountPopup -> do
H.modify_ _ { modal = DeleteAccountModal }
DeleteAccount -> do
H.raise $ DeleteUserAccount
handleAction $ CancelModal
ChangePasswordAttempt ev -> do
H.liftEffect $ Event.preventDefault ev
{ newPasswordForm } <- H.get
case newPasswordForm.password, newPasswordForm.confirmation of
"" , _ -> H.raise $ Log $ UnableToSend "Please, write your password."
_ , "" -> H.raise $ Log $ UnableToSend "Please, confirm your password."
pass, confirmation -> do
if pass == confirmation
then case P.password pass of
Left errors -> H.raise $ Log $ UnableToSend $ A.fold $ map show_error_password errors
Right _ -> handleAction SendChangePasswordMessage
else H.raise $ Log $ UnableToSend "Confirmation differs from password"
RouteChangeEmailAddressPage -> H.raise $ ChangeEmailAddress
SendChangePasswordMessage -> do
state <- H.get
H.raise $ Log $ SystemLog "Changing the password"
H.raise $ ChangePassword state.newPasswordForm.password
where
show_error_password :: P.Error -> String
show_error_password = case _ of
-- P.ParsingError {error, position} ->
-- "position " <> show position <> " " <> maybe "" string_error_password error
P.ParsingError {error} -> maybe "" string_error_password error
string_error_password :: P.PasswordParsingError -> String
string_error_password = case _ of
P.CannotParse -> "Cannot parse the password"
P.CannotEntirelyParse -> "Cannot entirely parse the password"
P.Size min max n -> "Password size should be between "
<> show min <> " and " <> show max
<> " (currently: " <> show n <> ")"
handleQuery :: forall a m. MonadAff m => Query a -> H.HalogenM State Action () Output m (Maybe a)
handleQuery = case _ of
-- For now, no message actually needs to be handled here.
-- Error messages are simply logged (see the code in the Container component).
MessageReceived message _ -> do
case message of
_ -> do
H.raise $ Log $ ErrorLog $ "Message not handled in SetupInterface."
pure Nothing