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

259 lines
9.4 KiB
Plaintext
Raw Normal View History

2023-05-22 02:11:40 +02:00
module App.AuthenticationForm where
import Prelude (Unit, Void, bind, discard, map, show, void, when, ($), (&&), (<$>), (<<<), (<>), (>>=), pure, unit)
2023-05-22 02:11:40 +02:00
2023-06-08 21:51:12 +02:00
import Bulma as Bulma
2023-05-22 02:11:40 +02:00
import Control.Monad.State (class MonadState)
import Data.Tuple (Tuple(..))
2023-05-22 02:11:40 +02:00
import Data.Const (Const)
import Data.Either (Either(..))
import Data.Maybe (Maybe(..), isJust, isNothing, maybe)
import Data.String as String
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 (Event)
import Web.Event.Event as Event
import Effect.Class (class MonadEffect)
import App.IPC as IPC
import App.Email as Email
2023-05-22 02:11:40 +02:00
import App.Messages.AuthenticationDaemon as AuthD
import Data.ArrayBuffer.Types (ArrayBuffer)
data Output
= AuthToken (Tuple Int String)
| MessageToSend ArrayBuffer
data Query a = MessageReceived ArrayBuffer a
2023-05-22 02:11:40 +02:00
type Slot = H.Slot Query Output
type Input = Unit
2023-05-22 02:11:40 +02:00
2023-06-04 01:24:05 +02:00
data AuthenticationInput
= AUTH_INP_login String
| AUTH_INP_pass String
data RegisterInput
= REG_INP_login String
| REG_INP_email String
| REG_INP_pass String
2023-05-22 02:11:40 +02:00
data Action
= Initialize
-- | WebSocketParseError String
-- | ConnectWebSocket
2023-06-03 00:54:18 +02:00
2023-06-04 01:24:05 +02:00
| HandleAuthenticationInput AuthenticationInput
| HandleRegisterInput RegisterInput
2023-05-22 02:11:40 +02:00
| AuthenticationAttempt Event
2023-06-03 00:54:18 +02:00
| RegisterAttempt Event
| Finalize
--| HandleWebSocket (WebSocketEvent WebSocketMessageType)
2023-05-22 02:11:40 +02:00
2023-06-04 01:24:05 +02:00
type StateAuthenticationForm = { login :: String, pass :: String }
type StateRegistrationForm = { login :: String, email :: String, pass :: String }
2023-05-22 02:11:40 +02:00
type State =
{ authenticationForm :: StateAuthenticationForm
, registrationForm :: StateRegistrationForm
, wsUp :: Boolean
2023-05-22 02:11:40 +02:00
}
component :: forall m. MonadAff m => H.Component Query Input Output m
component =
2023-05-22 02:11:40 +02:00
H.mkComponent
{ initialState
, render
, eval: H.mkEval $ H.defaultEval
{ initialize = Just Initialize
, handleAction = handleAction
, handleQuery = handleQuery
, finalize = Just Finalize
2023-05-22 02:11:40 +02:00
}
}
initialState :: Input -> State
initialState _ =
{ authenticationForm: { login: "", pass: "" }
2023-06-04 01:24:05 +02:00
, registrationForm: { login: "", email: "", pass: "" }
2023-06-03 00:54:18 +02:00
, wsUp: true
2023-05-22 02:11:40 +02:00
}
render :: forall m. State -> H.ComponentHTML Action () m
render { wsUp,
2023-06-04 01:24:05 +02:00
authenticationForm,
registrationForm }
2023-06-08 21:51:12 +02:00
= HH.div_
[ Bulma.columns_ [ Bulma.column_ auth_form, Bulma.column_ register_form ]
2023-06-03 00:54:18 +02:00
]
where
2023-06-08 21:51:12 +02:00
auth_form
= [ Bulma.h3 "Authentication"
, render_auth_form
]
register_form
= [ Bulma.h3 "Register!"
, render_register_form
]
2023-06-03 00:54:18 +02:00
render_auth_form = HH.form
[ HE.onSubmit AuthenticationAttempt ]
[ Bulma.box_input "Login" "login" -- title, placeholder
(HandleAuthenticationInput <<< AUTH_INP_login) -- action
authenticationForm.login -- value
true -- validity (TODO)
(if wsUp then (HP.enabled true) else (HP.disabled true)) -- condition
, Bulma.box_password "Password" "password" -- title, placeholder
(HandleAuthenticationInput <<< AUTH_INP_pass) -- action
authenticationForm.pass -- value
true -- validity (TODO)
(if wsUp then (HP.enabled true) else (HP.disabled true)) -- condition
, 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" ]
2023-05-22 02:11:40 +02:00
]
2023-06-03 00:54:18 +02:00
render_register_form = HH.form
[ HE.onSubmit RegisterAttempt ]
[ Bulma.box_input "Login" "login" -- title, placeholder
(HandleRegisterInput <<< REG_INP_login) -- action
registrationForm.login -- value
true -- validity (TODO)
(if wsUp then (HP.enabled true) else (HP.disabled true)) -- condition
, Bulma.box_input "Email" "email@example.com" -- title, placeholder
(HandleRegisterInput <<< REG_INP_email) -- action
registrationForm.email -- value
true -- validity (TODO)
(if wsUp then (HP.enabled true) else (HP.disabled true)) -- condition
, Bulma.box_password "Password" "password" -- title, placeholder
(HandleRegisterInput <<< REG_INP_pass) -- action
registrationForm.pass -- value
true -- validity (TODO)
(if wsUp then (HP.enabled true) else (HP.disabled true)) -- condition
, HH.div_
[ HH.button
[ HP.style "padding: 0.5rem 1.25rem;"
, HP.type_ HP.ButtonSubmit
, (if wsUp then (HP.enabled true) else (HP.disabled true))
2023-06-03 00:54:18 +02:00
]
[ HH.text "Send Message to Server" ]
2023-06-03 00:54:18 +02:00
]
2023-05-22 02:11:40 +02:00
]
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
handleAction = case _ of
Initialize -> pure unit
-- systemMessage "Component initialized!"
Finalize -> pure unit
-- systemMessage "Finalize"
2023-05-22 02:11:40 +02:00
2023-06-04 01:24:05 +02:00
HandleAuthenticationInput authinp -> do
case authinp of
AUTH_INP_login v -> H.modify_ _ { authenticationForm { login = v } }
AUTH_INP_pass v -> H.modify_ _ { authenticationForm { pass = v } }
HandleRegisterInput reginp -> do
case reginp of
REG_INP_login v -> H.modify_ _ { registrationForm { login = v } }
REG_INP_email v -> H.modify_ _ { registrationForm { email = v } }
REG_INP_pass v -> H.modify_ _ { registrationForm { pass = v } }
2023-06-03 00:54:18 +02:00
RegisterAttempt ev -> do
H.liftEffect $ Event.preventDefault ev
{ registrationForm } <- H.get
2023-06-04 01:24:05 +02:00
let login = registrationForm.login
email = registrationForm.email
pass = registrationForm.pass
case login, email, pass of
"", _, _ -> pure unit
-- unableToSend "Write your login!"
_, "", _ -> pure unit
-- unableToSend "Write your email!"
_, _, "" -> pure unit
-- unableToSend "Write your password!"
_, _, _ -> do
message <- H.liftEffect $ AuthD.serialize $
AuthD.MkRegister { login: login
, email: Just (Email.Email email)
, password: pass }
H.raise $ MessageToSend message
-- appendMessage "[😇] Trying to register"
2023-06-03 00:54:18 +02:00
2023-05-22 02:11:40 +02:00
AuthenticationAttempt ev -> do
H.liftEffect $ Event.preventDefault ev
{ authenticationForm } <- H.get
case authenticationForm.login, authenticationForm.pass of
"" , _ -> pure unit
-- unableToSend "Write your login!"
_ , "" -> pure unit
-- unableToSend "Write your password!"
login, pass -> do
message <- H.liftEffect $ AuthD.serialize $ AuthD.MkLogin { login: login, password: pass }
H.raise $ MessageToSend message
-- appendMessage $ "[😇] Trying to connect with login: " <> login
handleQuery :: forall a m. MonadAff m => Query a -> H.HalogenM State Action () Output m (Maybe a)
handleQuery = case _ of
MessageReceived message a -> do
receivedMessage <- H.liftEffect $ AuthD.deserialize message
case receivedMessage of
-- Cases where we didn't understand the message.
Left _ -> pure Nothing
--case err of
-- (AuthD.JSONERROR jerr) -> do
-- print_json_string messageEvent.message
-- handleAction $ WebSocketParseError ("JSON parsing error: " <> jerr <> " JSON is: " <> jerr)
-- (AuthD.UnknownError unerr) -> handleAction $ WebSocketParseError ("Parsing error: AuthD.UnknownError" <> (show unerr))
-- (AuthD.UnknownNumber ) -> handleAction $ WebSocketParseError ("Parsing error: AuthD.UnknownNumber")
-- Cases where we understood the message.
Right response -> do
case response of
-- The authentication failed.
(AuthD.GotError errmsg) -> pure (Just a)
-- appendMessage $ "[😈] Failed: " <> maybe "server didn't tell why" (\v -> v) errmsg.reason
-- The authentication was a success!
(AuthD.GotToken msg) -> do
-- appendMessage $ "[😈] Success! user " <> (show msg.uid) <> " has token: " <> msg.token
H.raise $ AuthToken (Tuple msg.uid msg.token)
pure (Just a)
-- WTH?!
_ -> pure Nothing
-- appendMessage $ "[😈] Failed! Authentication server didn't send a valid message."
2023-05-22 02:11:40 +02:00
print_json_string :: forall m. MonadEffect m => MonadState State m => ArrayBuffer -> m Unit
print_json_string arraybuffer = do
-- fromTypedIPC :: ArrayBuffer -> Effect (Either ParseError (Tuple UInt String))
value <- H.liftEffect $ IPC.fromTypedIPC arraybuffer
pure unit
--appendMessage $ case (value) of
-- Left _ -> "Cannot even fromTypedIPC the message."
-- Right (Tuple messageTypeNumber string) -> "Number is: " <> show messageTypeNumber <> ", received string: " <> string