Skip to content

Commit

Permalink
Removed formless dependancy
Browse files Browse the repository at this point in the history
  • Loading branch information
tusharad committed Sep 4, 2024
1 parent 3734708 commit a0c0bd0
Show file tree
Hide file tree
Showing 7 changed files with 241 additions and 366 deletions.
1 change: 0 additions & 1 deletion haskread-platform-ui/spago.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ package:
- console
- effect
- halogen
- halogen-formless
- halogen-store
- http-methods
- media-types
Expand Down
4 changes: 2 additions & 2 deletions haskread-platform-ui/src/Component/Router.purs
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,7 @@ component = connect (selectEq _.currentUser) $ H.mkComponent {
handleQuery :: forall a. Query a -> H.HalogenM State Action ChildSlots Void m (Maybe a)
handleQuery = case _ of
Navigate dest a -> do
{ route,currentUser } <- H.get
{ currentUser } <- H.get
unless (isNothing currentUser && dest `elem` authRoute)
(H.modify_ _ { route = Just dest })
pure (Just a)
Expand All @@ -99,7 +99,7 @@ component = connect (selectEq _.currentUser) $ H.mkComponent {
Login -> HH.slot_ (Proxy :: _ "login") unit Login.component { redirect: true }
Register ->
HH.slot_ (Proxy :: _ "register") unit Register.component { redirect: true }
OTP uID -> HH.slot_ (Proxy :: _ "otp") unit OTP.component { uId : uID }
OTP uID -> HH.slot_ (Proxy :: _ "otp") unit OTP.component { userID : uID }
CreateThread ->
HH.slot_
(Proxy :: _ "createThread")
Expand Down
82 changes: 0 additions & 82 deletions haskread-platform-ui/src/Form/Field.purs

This file was deleted.

41 changes: 0 additions & 41 deletions haskread-platform-ui/src/Form/Validation.purs

This file was deleted.

114 changes: 58 additions & 56 deletions haskread-platform-ui/src/Page/Login.purs
Original file line number Diff line number Diff line change
@@ -1,83 +1,80 @@
module Page.Login
where
module Page.Login where

import Prelude
import Halogen as H
import Halogen.HTML as HH
import Formless as F
import Form.Validation (FormError)
import Form.Validation as V
import Effect.Aff.Class (class MonadAff)
import Data.Maybe (Maybe(..))
import Capability.Resource (class ManageUser, loginUser,class Navigate, navigate)
import Common.Types (MyRoute(..))
import Common.Utils (safeHref,whenElem)
import Halogen.HTML.Events as HE
import Form.Field as Field
import Halogen.HTML.Properties as HP
import Web.Event.Event as Event
import Web.Event.Event (Event)
import Data.Either (Either(..),isLeft)
import Effect.Class.Console (log)

type Input = { redirect :: Boolean }

type Form :: (Type -> Type -> Type -> Type) -> Row Type
type Form f =
( emailForLogin :: f String FormError String
, passwordForLogin :: f String FormError String
)

type FormContext = F.FormContext (Form F.FieldState) (Form (F.FieldAction Action)) Input Action
type FormlessAction = F.FormlessAction (Form F.FieldState)

data Action
= Receive FormContext
| Eval FormlessAction
= SetEmail String | SetPassword String | HandleSubmit Event

type State =
{ form :: FormContext
, loginError :: Boolean
type State = {
email :: String
, password :: String
, loginError :: Either String Unit
}

validateInput :: State -> Either String Unit
validateInput { email, password } = do
if (email == mempty) then Left "email required"
else if (password == mempty) then Left "password required"
else (Right unit)

component ::
forall query output m.
MonadAff m =>
Navigate m =>
ManageUser m =>
H.Component query Input output m
component = F.formless { liftAction : Eval } mempty $ H.mkComponent {
initialState : \context -> { form: context, loginError : false } ,
component = H.mkComponent {
initialState,
render,
eval : H.mkEval H.defaultEval {
receive = Just <<< Receive
, handleAction = handleAction
, handleQuery = handleQuery
handleAction = handleAction
}
}
where
handleAction :: Action -> H.HalogenM _ _ _ _ _ Unit
handleAction = case _ of
Receive context -> H.modify_ _ { form = context }
Eval action -> F.eval action

handleQuery :: forall a. F.FormQuery _ _ _ _ a -> H.HalogenM _ _ _ _ _ (Maybe a)
handleQuery = do
let
onSubmit = loginUser >=> case _ of
Nothing ->
H.modify_ _ { loginError = true }
Just _ -> do
H.modify_ _ { loginError = false }
{ redirect } <- H.gets _.form.input
when redirect (navigate Home)
initialState _ = {
email : "",
password : "",
loginError : Right unit
}

validation =
{
emailForLogin : V.required >=> V.minLength 3 >=> V.emailFormat
, passwordForLogin : V.required >=> V.minLength 2 >=> V.maxLength 20
}

F.handleSubmitValidate onSubmit F.validate validation
handleAction :: forall slots. Action -> H.HalogenM State Action slots output m Unit
handleAction = case _ of
SetEmail email -> H.modify_ _ { email = email }
SetPassword password -> H.modify_ _ { password = password }
HandleSubmit event -> do
H.liftEffect $ Event.preventDefault event
st <- H.get
mRes <- case validateInput st of
Left err -> do
H.modify_ _ { loginError = Left err }
log err *> pure Nothing
Right _ -> do
let loginFields = {
emailForLogin : st.email
, passwordForLogin : st.password
}
loginUser loginFields
case mRes of
Nothing -> pure unit
Just _ -> navigate Home

render :: State -> H.ComponentHTML Action () m
render { loginError, form: { formActions, fields, actions } } =
render st =
HH.div_
[ HH.h1
[ ]
Expand All @@ -89,23 +86,28 @@ component = F.formless { liftAction : Eval } mempty $ H.mkComponent {
[ HH.text "Need an account?" ]
]
, HH.form
[ HE.onSubmit formActions.handleSubmit ]
[ whenElem loginError \_ ->
[ HE.onSubmit HandleSubmit ]
[ whenElem (isLeft st.loginError) \_ ->
HH.div
[ ]
[ HH.text "Email or password is invalid" ]
, HH.fieldset_
[ Field.textInput
{ state: fields.emailForLogin, action: actions.emailForLogin }
[ HP.placeholder "Email"
[ HH.input
[
HP.placeholder "Email"
, HP.type_ HP.InputEmail
, HE.onValueInput SetEmail
, HP.value st.email
]
, Field.textInput
{ state: fields.passwordForLogin, action: actions.passwordForLogin }
, HH.input
[ HP.placeholder "Password"
, HP.type_ HP.InputPassword
, HE.onValueInput SetPassword
, HP.value st.password
]
, Field.submitButton "Log in"
, HH.button
[HP.type_ HP.ButtonSubmit]
[HH.text "Login"]
]
]
]
Loading

0 comments on commit a0c0bd0

Please sign in to comment.