Skip to content

Commit

Permalink
UI: Added OTP page
Browse files Browse the repository at this point in the history
  • Loading branch information
tusharad committed Aug 30, 2024
1 parent f919e4b commit f276ef6
Show file tree
Hide file tree
Showing 9 changed files with 99 additions and 66 deletions.
3 changes: 2 additions & 1 deletion haskread-platform-ui/src/AppM.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import Capability.Navigate (class Navigate)
import Capability.Resource (class ManageThreads,class ManageUser)
import Common.Types (Endpoint(..), RequestMethod(..), threadsCodec)
import Common.Types as Route
import Common.Utils (mkRequest, decode, authenticate,login,register)
import Common.Utils (mkRequest, decode, authenticate,login,register,verifyOtp)
import Effect.Aff (Aff)
import Effect.Aff.Class (class MonadAff)
import Effect.Class (class MonadEffect, liftEffect)
Expand Down Expand Up @@ -50,3 +50,4 @@ instance threadHalogenM :: ManageThreads AppM where
instance manageUserAppM :: ManageUser AppM where
loginUser = authenticate login
registerUser = register
verifyOtp = verifyOtp
6 changes: 4 additions & 2 deletions haskread-platform-ui/src/Capability/Resource.purs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Capability.Resource where

import Halogen (HalogenM, lift)
import Common.Types (PaginatedArray,Thread,LoginFields,Profile,RegisterFields)
import Common.Types (PaginatedArray,Thread,LoginFields,Profile,RegisterFields,OtpFields)
import Data.Maybe (Maybe)
import Data.Either (Either)

Expand All @@ -15,9 +15,11 @@ instance manageThreadHalogenM :: ManageThreads m => ManageThreads (HalogenM st a

class Monad m <= ManageUser m where
loginUser :: LoginFields -> m (Maybe Profile)
registerUser :: RegisterFields -> m (Either String Unit)
registerUser :: RegisterFields -> m (Either String Int)
verifyOtp :: OtpFields -> m (Either String Unit)

-- | This instance lets us avoid having to use `lift` when we use these functions in a component.
instance manageUserHalogenM :: ManageUser m => ManageUser (HalogenM st act slots msg m) where
loginUser = lift <<< loginUser
registerUser = lift <<< registerUser
verifyOtp = lift <<< verifyOtp
16 changes: 11 additions & 5 deletions haskread-platform-ui/src/Common/Types.purs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ module Common.Types
, RegisterFields
, loginCodec
, registerCodec
, OtpFields
)
where

Expand All @@ -31,22 +32,23 @@ import Data.Codec.Argonaut.Migration as CAM
import Data.Codec.Argonaut.Record as CAR
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe)
import Routing.Duplex (RouteDuplex', path, root)
import Routing.Duplex (RouteDuplex', path, root,int,segment)
import Routing.Duplex.Generic (noArgs, sum)
import Routing.Duplex.Generic as G
import Routing.Duplex.Generic.Syntax ((/))

newtype BaseURL = BaseURL String

data Endpoint = Threads | UserByToken | Login0 | Register0
data Endpoint = Threads | UserByToken | Login0 | Register0 | VerifyOtp0 Int Int
derive instance genericEndpoint :: Generic Endpoint _

endpointCodec :: RouteDuplex' Endpoint
endpointCodec = root $ sum {
"Threads" : "api" / "v1" / "thread" / "all" / noArgs ,
"UserByToken" : "api" / "v1" / "user" / "profile" / noArgs,
"Login0" : "api" / "v1" / "user" / "auth" / "login" / noArgs,
"Register0" : "api" / "v1" / "user" / "auth" / "register" / noArgs
"Register0" : "api" / "v1" / "user" / "auth" / "register" / noArgs,
"VerifyOtp0" : "api" / "v1" / "user" / "auth" / "verify" / (int segment) / (int segment)
}

data RequestMethod =
Expand All @@ -61,7 +63,7 @@ data MyRoute =
Home
| Login
| Register
| OTP
| OTP Int

derive instance genericRoute :: Generic MyRoute _
derive instance eqRoute :: Eq MyRoute
Expand All @@ -77,7 +79,7 @@ myRoute = root $ G.sum {
"Home" : G.noArgs
, "Login" : path "login" G.noArgs
, "Register" : path "register" G.noArgs
, "OTP" : path "otp" G.noArgs
, "OTP" : "otp" / (int segment)
}

type PaginatedArray a =
Expand Down Expand Up @@ -126,6 +128,10 @@ profileCodec =
userName: CA.string
})

type OtpFields = {
otp :: Int,
userID :: Int
}

type LoginFields =
{ emailForLogin :: String
Expand Down
35 changes: 31 additions & 4 deletions haskread-platform-ui/src/Common/Utils.purs
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ import Data.Codec as Codec
import Data.Codec.Argonaut.Record as CAR
import Halogen.HTML as HH
import Halogen.HTML.Properties as HP
import Undefined (undefined)

mkRequest
:: forall m
Expand Down Expand Up @@ -106,6 +107,16 @@ decode codec (Just json) = case CA.decode codec json of
Left err -> (log $ "failed decodig: " <> (CA.printJsonDecodeError err)) *> pure Nothing
Right response -> pure (Just response)

verifyOtp :: forall m.
MonadStore Action Store m =>
MonadAff m => OtpFields -> m (Either String Unit)
verifyOtp fields = do
let method = Put Nothing
mjson <- mkRequest { endpoint: VerifyOtp0 fields.userID fields.otp, method }
case mjson of
Nothing -> pure $ Left "got nothing"
Just _ -> pure $ Right unit

authenticate
:: forall m a
. MonadAff m
Expand All @@ -130,15 +141,31 @@ login baseUrl fields =

register :: forall m.
MonadStore Action Store m =>
MonadAff m => RegisterFields -> m (Either String Unit)
MonadAff m => RegisterFields -> m (Either String Int)
register fields = do
let method = Post $ Just $ Codec.encode registerCodec fields
mjson <- mkRequest { endpoint: Register0, method }
case mjson of
Nothing -> pure $ Left "got nothing"
Just _ -> pure $ Right unit

requestUser :: forall m. MonadAff m => BaseURL -> RequestOptions -> m (Either String (Tuple Token Profile))
Just registerResp -> do
let eRes = decodeRegisterResp registerResp
case eRes of
Left _ -> pure $ Left "Decoding response failed"
Right res -> pure $ Right res

decodeRegisterResp :: Json -> Either JsonDecodeError Int
decodeRegisterResp registerResp = do
{ userIDForRUR } <- Codec.decode decodeResp_ registerResp
pure userIDForRUR
where
decodeResp_ =
CAR.object "Register Response" { userIDForRUR : CA.int }

requestUser ::
forall m. MonadAff m =>
BaseURL ->
RequestOptions ->
m (Either String (Tuple Token Profile))
requestUser baseUrl opts = do
eRes <- liftAff $ request $ defaultRequest baseUrl Nothing opts
case eRes of
Expand Down
5 changes: 3 additions & 2 deletions haskread-platform-ui/src/Component/Router.purs
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,7 @@ component = connect (selectEq _.currentUser) $ H.mkComponent {
Just r -> case r of
Home -> HH.slot_ (Proxy :: _ "home") unit Home.component unit
Login -> HH.slot_ (Proxy :: _ "login") unit Login.component { redirect: true }
Register -> HH.slot_ (Proxy :: _ "register") unit Register.component { redirect: true }
OTP -> HH.slot_ (Proxy :: _ "otp") unit OTP.component unit
Register ->
HH.slot_ (Proxy :: _ "register") unit Register.component { redirect: true }
OTP uID -> HH.slot_ (Proxy :: _ "otp") unit OTP.component { uId : uID }
Nothing -> HH.div_ [ HH.text "page not found!" ]
3 changes: 1 addition & 2 deletions haskread-platform-ui/src/Form/Field.purs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,6 @@ type TextInput action output =
, action :: F.FieldAction action String FormError output
}


textInput
:: forall output action slots m
. TextInput action output
Expand Down Expand Up @@ -74,4 +73,4 @@ textarea { state, action } props =
]
props
)
]
]
4 changes: 2 additions & 2 deletions haskread-platform-ui/src/Page/Home.purs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import Effect.Aff.Class (class MonadAff)
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.Store.Connect (Connected, connect)
import Halogen.Store.Connect (connect)
import Halogen.Store.Monad (class MonadStore)
import Halogen.Store.Select (selectEq)
import Network.RemoteData (RemoteData(..), fromMaybe)
Expand Down Expand Up @@ -44,7 +44,7 @@ component = connect (selectEq _.currentUser) $ H.mkComponent {

render :: forall slots. State -> H.ComponentHTML Action slots m
render state = HH.div_ [
HH.text "home Pages :)",
HH.text "Home Pages :)",
HH.br_,
HH.text $ "user: " <> show state.currentUser,
HH.br_,
Expand Down
91 changes: 44 additions & 47 deletions haskread-platform-ui/src/Page/OTP.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,25 +10,27 @@ import Form.Validation as V
import Capability.Navigate (class Navigate, navigate)
import Effect.Aff.Class (class MonadAff)
import Data.Maybe (Maybe(..))
import Capability.Resource (class ManageUser, registerUser)
import Capability.Resource (class ManageUser, verifyOtp)
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 Effect.Class.Console (log)
import Data.Either (Either(..))
import Data.Int (fromString)
import Store as Store
import Halogen.Store.Monad (class MonadStore)

type Input = {uId :: Int }

type Form :: (Type -> Type -> Type -> Type) -> Row Type
type Form f =
(
userNameForRegister :: f String FormError String,
emailForRegister :: f String FormError String,
passwordForRegister :: f String FormError String,
confirmPasswordForRegister :: f String FormError String
otpField :: f String FormError String
)

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

data Action
Expand All @@ -37,17 +39,25 @@ data Action

type State =
{ form :: FormContext
, registerError :: Boolean
, otpError :: Boolean
, userID :: Int
}

toInt :: String -> Int
toInt str =
case fromString str of
Nothing -> 23
Just num -> num

component ::
forall query output m.
MonadAff m =>
MonadStore Store.Action Store.Store m =>
Navigate m =>
ManageUser m =>
H.Component query Unit output m
H.Component query Input output m
component = F.formless { liftAction : Eval } mempty $ H.mkComponent {
initialState : \context -> { form: context, registerError : false } ,
initialState,
render,
eval : H.mkEval H.defaultEval {
receive = Just <<< Receive
Expand All @@ -56,74 +66,61 @@ component = F.formless { liftAction : Eval } mempty $ H.mkComponent {
}
}
where
initialState ctx = { form: ctx, otpError : false, userID : ctx.input.uId}

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
handleQuery r = do
let
onSubmit = registerUser >=> case _ of
Left _ ->
H.modify_ _ { registerError = true }
Right _ -> do
H.modify_ _ { registerError = false }
-- initiating OTP process
navigate OTP
onSubmit = do
verifyOtp >=> case _ of
Left _ -> do
H.modify_ _ { otpError = true }
Right _ -> do
H.modify_ _ { otpError = false }
-- initiating OTP process
navigate Home

validation =
{
passwordForRegister : V.required ,
confirmPasswordForRegister : V.required ,
emailForRegister : V.required,
userNameForRegister : V.required
otpField : V.required
}

F.handleSubmitValidate onSubmit F.validate validation
{userID} <- H.get
let onSubmit_ { otpField} =
onSubmit { otp : toInt otpField,userID : userID}
F.handleSubmitValidate onSubmit_ F.validate validation r

render :: State -> H.ComponentHTML Action () m
render { registerError, form: { formActions, fields, actions } } =
render { otpError, form: { formActions, fields, actions} } =
HH.div_
[ HH.h1
[ ]
[ HH.text "Sign up" ]
[ HH.text "OTP Veify" ]
, HH.p
[ ]
[ HH.a
[ safeHref Login ] --
[ HH.text "Already have an account?" ]
[ safeHref Register] --
[ HH.text "wanna Resend?" ]
]
, HH.form
[ HE.onSubmit formActions.handleSubmit ]
[ whenElem registerError \_ ->
[ whenElem otpError \_ ->
HH.div
[ ]
[ HH.text "Something went wrong" ]
, HH.fieldset_
[
Field.textInput
{ state: fields.userNameForRegister, action: actions.userNameForRegister }
[ HP.placeholder "Username"
, HP.type_ HP.InputText
]
, Field.textInput
{ state: fields.emailForRegister, action: actions.emailForRegister }
[ HP.placeholder "Email"
, HP.type_ HP.InputEmail
]
, Field.textInput
{ state: fields.passwordForRegister, action: actions.passwordForRegister }
[ HP.placeholder "Password"
, HP.type_ HP.InputPassword
]
,
Field.textInput
{ state: fields.confirmPasswordForRegister, action: actions.confirmPasswordForRegister }
[ HP.placeholder "Confirm password"
, HP.type_ HP.InputPassword
{ state: fields.otpField , action: actions.otpField}
[ HP.placeholder "Enter OTP"
, HP.type_ HP.InputNumber
]
, Field.submitButton "Get OTP"
, Field.submitButton "Verify"
]
]
]
2 changes: 1 addition & 1 deletion haskread-platform-ui/src/Page/Register.purs
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ component = F.formless { liftAction : Eval } mempty $ H.mkComponent {
{ redirect } <- H.gets _.form.input
-- initiating OTP process
log "dasdasdasdasdsa"
when redirect (navigate OTP)
when redirect (navigate $ OTP 1)

validation =
{
Expand Down

0 comments on commit f276ef6

Please sign in to comment.