Commit 5a8e5abd authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge remote-tracking branch 'origin/405-dev-lost-password-design' into dev

parents eb1bb88e a0cef540
module Gargantext.Components.ForgotPassword where
import Gargantext.Prelude
import Data.Maybe (Maybe(..))
import Gargantext.Config.REST (AffRESTError, logRESTError, get)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
here :: R2.Here
here = R2.here "Gargantext.Components.ForgotPassword"
type ForgotPasswordProps = ( server :: String, uuid :: String )
forgotPasswordLayout :: R2.Component ForgotPasswordProps
forgotPasswordLayout = R.createElement forgotPasswordLayoutCpt
forgotPasswordLayoutCpt :: R.Component ForgotPasswordProps
forgotPasswordLayoutCpt = here.component "forgotPasswordLayout" cpt where
cpt { server, uuid } _ = do
useLoader { errorHandler
, loader: loadPassword
, path: { server, uuid }
, render: \{ password } ->
H.p {} [ H.text ("Your new password is: " <> password) ] }
where
errorHandler = logRESTError here "[forgotPasswordLayout]"
------------------------------------
type PasswordData = ( password :: String )
loadPassword :: Record ForgotPasswordProps -> AffRESTError (Record PasswordData)
loadPassword { server, uuid } = get Nothing (server <> "/api/v1.0/forgot-password?uuid=" <> uuid )
module Gargantext.Components.Login.ForgotPassword where
import Gargantext.Prelude
import DOM.Simple.Event as DE
import Data.Either (Either(..))
import Effect (Effect)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Formula as F
import Gargantext.Components.Forms (formGroup)
import Gargantext.Ends (Backend)
import Gargantext.Prelude
import Gargantext.Sessions (Sessions, postForgotPasswordRequest)
import Gargantext.Utils.Reactix as R2
import Formula as F
import Reactix as R
import Reactix.DOM.HTML as H
import Reactix.SyntheticEvent as E
......@@ -30,13 +32,15 @@ forgotPasswordCpt :: R.Component Props
forgotPasswordCpt = here.component "forgotPassword" cpt where
cpt { backend, sessions } _ = do
email <- T.useBox ""
message <- T.useBox ""
pure $ H.div { className: "row" }
[ H.form { className: "text-center col-md-12" }
[ H.h4 {} [ H.text "Forgot password" ]
, messageDisplay { message }
, formGroup
[ emailInput email ]
, submitButton { backend, email, sessions }
, submitButton { backend, email, sessions, message }
]
]
......@@ -50,14 +54,15 @@ emailInput value = F.bindInput { value
, maxLength: "254" }
type SubmitButtonProps =
( email :: T.Box Email
( email :: T.Box Email
, message :: T.Box String
| Props )
submitButton :: R2.Leaf SubmitButtonProps
submitButton = R2.leafComponent submitButtonCpt
submitButtonCpt :: R.Component SubmitButtonProps
submitButtonCpt = here.component "submitButton" cpt where
cpt { backend, email, sessions } _ = do
cpt { backend, email, sessions, message} _ = do
email' <- T.useLive T.unequal email
pure $ H.div {className: "form-group text-center"}
......@@ -75,3 +80,16 @@ submitButtonCpt = here.component "submitButton" cpt where
launchAff_ $ do
res <- postForgotPasswordRequest backend email'
liftEffect $ here.log2 "res" res
liftEffect $ case res of
Left s -> T.write_ s message
Right _ -> T.write_ "Request sent!" message
messageDisplay :: R2.Leaf (message :: T.Box String)
messageDisplay = R2.leafComponent messageDisplayCpt
messageDisplayCpt :: R.Component (message :: T.Box String)
messageDisplayCpt = here.component "messageDisplay" cpt where
cpt {message} _ = do
message' <- T.useLive T.unequal message
pure $ H.p {} [H.text message']
\ No newline at end of file
......@@ -5,7 +5,8 @@ import Gargantext.Prelude
import Data.Array (filter, length)
import Data.Array as A
import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..))
import Data.Map as M
import Data.Maybe (Maybe(..), fromMaybe)
import Data.UUID (UUID)
import Data.UUID as UUID
import Effect (Effect)
......@@ -13,6 +14,7 @@ import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.ErrorsView (errorsView)
import Gargantext.Components.Forest (forestLayout)
import Gargantext.Components.Login (login)
import Gargantext.Components.ForgotPassword (forgotPasswordLayout)
import Gargantext.Components.Nodes.Annuaire (annuaireLayout)
import Gargantext.Components.Nodes.Annuaire.User (userLayout)
import Gargantext.Components.Nodes.Annuaire.User.Contact (contactLayout)
......@@ -316,6 +318,7 @@ renderRouteCpt = R.memo' $ here.component "renderRoute" cpt where
GR.Team s n -> team (sessionNodeProps s n) []
GR.NodeTexts s n -> texts (sessionNodeProps s n) []
GR.UserPage s n -> user (sessionNodeProps s n) []
GR.ForgotPassword p -> forgotPassword {boxes, params: p} []
]
--------------------------------------------------------------
......@@ -690,3 +693,18 @@ contactCpt = here.component "contact" cpt where
} `Record.merge` sessionProps
pure $ authed authedProps []
--------------------------------------------------------------
type ForgotPasswordProps = ( params :: (M.Map String String) | Props)
forgotPassword :: R2.Component ForgotPasswordProps
forgotPassword = R.createElement forgotPasswordCpt
forgotPasswordCpt :: R.Component ForgotPasswordProps
forgotPasswordCpt = here.component "forgotPassword" cpt where
cpt { params } _ = do
let server = fromMaybe "" $ M.lookup "server" params
let uuid = fromMaybe "" $ M.lookup "uuid" params
pure $ forgotPasswordLayout { server, uuid } []
......@@ -6,11 +6,12 @@ import Data.Foldable (oneOf)
import Data.Int (floor)
import Gargantext.Routes (AppRoute(..))
import Gargantext.Types (SessionId(..))
import Routing.Match (Match, lit, num, str)
import Routing.Match (Match, lit, num, params, str)
router :: Match AppRoute
router = oneOf
[ Login <$ route "login"
, ForgotPassword <$> (route "forgotPassword" *> params)
, Folder <$> (route "folder" *> sid) <*> int
, FolderPrivate <$> (route "folderPrivate" *> sid) <*> int
, FolderPublic <$> (route "folderPublic" *> sid) <*> int
......
......@@ -4,6 +4,7 @@ import Prelude
import Data.Maybe (Maybe(..))
import Data.UUID (UUID)
import Data.Map as M
import Gargantext.Types (ChartOpts, ChartType, CorpusMetricOpts, CTabNgramType, Id, Limit, ListId, DocId, NgramsGetOpts, NgramsGetTableAllOpts, NodeType, Offset, OrderBy, SearchOpts, SessionId, TabSubType, TabType, TermList)
import Gargantext.Types as GT
......@@ -32,6 +33,7 @@ data AppRoute
| Team SessionId Int
| NodeTexts SessionId Int
| UserPage SessionId Int
| ForgotPassword (M.Map String String)
derive instance Eq AppRoute
......@@ -63,6 +65,7 @@ data SessionRoute
instance Show AppRoute where
show Home = "Home"
show Login = "Login"
show (ForgotPassword u) = "ForgotPassword" <> show u
show (Folder s i) = "Folder" <> show i <> " (" <> show s <> ")"
show (FolderPrivate s i) = "FolderPrivate" <> show i <> " (" <> show s <> ")"
show (FolderPublic s i) = "FolderPublic" <> show i <> " (" <> show s <> ")"
......@@ -90,11 +93,12 @@ instance Show AppRoute where
appPath :: AppRoute -> String
appPath Home = ""
appPath Login = "login"
appPath (Folder s i) = "folder/" <> show s <> "/" <> show i
appPath (FolderPrivate s i) = "folderPrivate/" <> show s <> "/" <> show i
appPath (FolderPublic s i) = "folderPublic/" <> show s <> "/" <> show i
appPath (FolderShared s i) = "folderShared/" <> show s <> "/" <> show i
appPath (Team s i) = "team/" <> show s <> "/" <> show i
appPath (ForgotPassword u) = "forgotPassword/" <> show u
appPath (Folder s i) = "folder/" <> show s <> "/" <> show i
appPath (FolderPrivate s i) = "folderPrivate/" <> show s <> "/" <> show i
appPath (FolderPublic s i) = "folderPublic/" <> show s <> "/" <> show i
appPath (FolderShared s i) = "folderShared/" <> show s <> "/" <> show i
appPath (Team s i) = "team/" <> show s <> "/" <> show i
appPath (CorpusDocument s c l i) = "corpus/" <> show s <> "/" <> show c <> "/list/" <> show l <> "/document/" <> show i
appPath (Corpus s i) = "corpus/" <> show s <> "/" <> show i
appPath (CorpusCode s i) = "corpusCode/" <> show s <> "/" <> show i
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment