halogen-websocket-ipc-playzone/src/App/Setup.purs

172 lines
5.2 KiB
Plaintext

-- | `App.SetupInterface` allows users to change their password or their email address.
-- | Users can also erase their account.
module App.SetupInterface where
import Prelude (Unit, bind, discard, pure, ($), (<<<), (<>), (==))
import Data.ArrayBuffer.Types (ArrayBuffer)
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))
import Effect.Aff.Class (class MonadAff)
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.HTML.Properties as HP
import Web.Event.Event as Event
import Web.Event.Event (Event)
import Bulma as Bulma
import App.Email as Email
import App.LogMessage
import App.Messages.AuthenticationDaemon as AuthD
data Output
= Log LogMessage
| ChangePassword String
| DeleteUserAccount
-- | The component's parent provides received messages.
-- |
-- | Also, the component is informed when the connection went up or down.
data Query a
= MessageReceived AuthD.AnswerMessage a
| ConnectionIsDown a
| ConnectionIsUp a
type Slot = H.Slot Query Output
type Input = String
data AuthenticationInput
= AUTH_INP_login String
| AUTH_INP_pass String
data NewPasswordInput
= NEWPASS_INP_password String
| NEWPASS_INP_confirmation String
data Action
= HandleNewPassword NewPasswordInput
| ChangePasswordAttempt Event
| CancelModal
| DeleteAccountPopup
| DeleteAccount
type StateNewPasswordForm = { password :: String, confirmation :: String }
data Modal
= NoModal
| DeleteAccountModal
type State =
{ newPasswordForm :: StateNewPasswordForm
, token :: String
, wsUp :: Boolean
, 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 token =
{ newPasswordForm: { password: "", confirmation: "" }
, token
, modal: NoModal
, wsUp: true
}
render :: forall m. State -> H.ComponentHTML Action () m
render { modal, wsUp, newPasswordForm } =
case modal of
DeleteAccountModal -> render_delete_account_modal
NoModal -> Bulma.columns_ [ b [ Bulma.h3 "Change password", render_new_password_form ]
, b [ Bulma.h3 "Delete account", render_delete_account ]
]
where
b e = Bulma.column_ [ Bulma.box e ]
should_be_disabled = (if wsUp then (HP.enabled true) else (HP.disabled true))
render_delete_account = Bulma.alert_btn "Delete my account" DeleteAccountPopup
render_new_password_form = HH.form
[ HE.onSubmit ChangePasswordAttempt ]
[ Bulma.box_input "passwordNEWPASS" "Password" "password"
(HandleNewPassword <<< NEWPASS_INP_password)
newPasswordForm.password
should_be_disabled
, Bulma.box_input "confirmationNEWPASS" "Confirmation" "confirmation"
(HandleNewPassword <<< NEWPASS_INP_confirmation)
newPasswordForm.confirmation
should_be_disabled
, HH.button
[ HP.style "padding: 0.5rem 1.25rem;"
, HP.type_ HP.ButtonSubmit
, (if wsUp then (HP.enabled true) else (HP.disabled true))
]
[ HH.text "Send Message to Server" ]
]
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 "Write your password!"
_ , "" -> H.raise $ Log $ UnableToSend "Confirm your password!"
pass, confirmation -> do
if pass == confirmation
then do H.raise $ Log $ SystemLog "Changing the password"
H.raise $ ChangePassword pass
else H.raise $ Log $ UnableToSend "Confirmation differs from password"
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
ConnectionIsDown a -> do
H.modify_ _ { wsUp = false }
pure (Just a)
ConnectionIsUp a -> do
H.modify_ _ { wsUp = true }
pure (Just a)