Commit a0cef540 authored by Karen Konou's avatar Karen Konou

forgot password route

parent af97f328
Pipeline #3006 failed with stage
in 0 seconds
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 )
...@@ -5,7 +5,8 @@ import Gargantext.Prelude ...@@ -5,7 +5,8 @@ import Gargantext.Prelude
import Data.Array (filter, length) import Data.Array (filter, length)
import Data.Array as A import Data.Array as A
import Data.Foldable (intercalate) 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 (UUID)
import Data.UUID as UUID import Data.UUID as UUID
import Effect (Effect) import Effect (Effect)
...@@ -13,6 +14,7 @@ import Gargantext.Components.App.Store (Boxes) ...@@ -13,6 +14,7 @@ import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.ErrorsView (errorsView) import Gargantext.Components.ErrorsView (errorsView)
import Gargantext.Components.Forest (forestLayout) import Gargantext.Components.Forest (forestLayout)
import Gargantext.Components.Login (login) import Gargantext.Components.Login (login)
import Gargantext.Components.ForgotPassword (forgotPasswordLayout)
import Gargantext.Components.Nodes.Annuaire (annuaireLayout) import Gargantext.Components.Nodes.Annuaire (annuaireLayout)
import Gargantext.Components.Nodes.Annuaire.User (userLayout) import Gargantext.Components.Nodes.Annuaire.User (userLayout)
import Gargantext.Components.Nodes.Annuaire.User.Contact (contactLayout) import Gargantext.Components.Nodes.Annuaire.User.Contact (contactLayout)
...@@ -316,6 +318,7 @@ renderRouteCpt = R.memo' $ here.component "renderRoute" cpt where ...@@ -316,6 +318,7 @@ renderRouteCpt = R.memo' $ here.component "renderRoute" cpt where
GR.Team s n -> team (sessionNodeProps s n) [] GR.Team s n -> team (sessionNodeProps s n) []
GR.NodeTexts s n -> texts (sessionNodeProps s n) [] GR.NodeTexts s n -> texts (sessionNodeProps s n) []
GR.UserPage s n -> user (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 ...@@ -690,3 +693,18 @@ contactCpt = here.component "contact" cpt where
} `Record.merge` sessionProps } `Record.merge` sessionProps
pure $ authed authedProps [] 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) ...@@ -6,11 +6,12 @@ import Data.Foldable (oneOf)
import Data.Int (floor) import Data.Int (floor)
import Gargantext.Routes (AppRoute(..)) import Gargantext.Routes (AppRoute(..))
import Gargantext.Types (SessionId(..)) import Gargantext.Types (SessionId(..))
import Routing.Match (Match, lit, num, str) import Routing.Match (Match, lit, num, params, str)
router :: Match AppRoute router :: Match AppRoute
router = oneOf router = oneOf
[ Login <$ route "login" [ Login <$ route "login"
, ForgotPassword <$> (route "forgotPassword" *> params)
, Folder <$> (route "folder" *> sid) <*> int , Folder <$> (route "folder" *> sid) <*> int
, FolderPrivate <$> (route "folderPrivate" *> sid) <*> int , FolderPrivate <$> (route "folderPrivate" *> sid) <*> int
, FolderPublic <$> (route "folderPublic" *> sid) <*> int , FolderPublic <$> (route "folderPublic" *> sid) <*> int
......
...@@ -4,6 +4,7 @@ import Prelude ...@@ -4,6 +4,7 @@ import Prelude
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.UUID (UUID) 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 (ChartOpts, ChartType, CorpusMetricOpts, CTabNgramType, Id, Limit, ListId, DocId, NgramsGetOpts, NgramsGetTableAllOpts, NodeType, Offset, OrderBy, SearchOpts, SessionId, TabSubType, TabType, TermList)
import Gargantext.Types as GT import Gargantext.Types as GT
...@@ -32,6 +33,7 @@ data AppRoute ...@@ -32,6 +33,7 @@ data AppRoute
| Team SessionId Int | Team SessionId Int
| NodeTexts SessionId Int | NodeTexts SessionId Int
| UserPage SessionId Int | UserPage SessionId Int
| ForgotPassword (M.Map String String)
derive instance Eq AppRoute derive instance Eq AppRoute
...@@ -63,6 +65,7 @@ data SessionRoute ...@@ -63,6 +65,7 @@ data SessionRoute
instance Show AppRoute where instance Show AppRoute where
show Home = "Home" show Home = "Home"
show Login = "Login" show Login = "Login"
show (ForgotPassword u) = "ForgotPassword" <> show u
show (Folder s i) = "Folder" <> show i <> " (" <> show s <> ")" show (Folder s i) = "Folder" <> show i <> " (" <> show s <> ")"
show (FolderPrivate s i) = "FolderPrivate" <> show i <> " (" <> show s <> ")" show (FolderPrivate s i) = "FolderPrivate" <> show i <> " (" <> show s <> ")"
show (FolderPublic s i) = "FolderPublic" <> show i <> " (" <> show s <> ")" show (FolderPublic s i) = "FolderPublic" <> show i <> " (" <> show s <> ")"
...@@ -90,11 +93,12 @@ instance Show AppRoute where ...@@ -90,11 +93,12 @@ instance Show AppRoute where
appPath :: AppRoute -> String appPath :: AppRoute -> String
appPath Home = "" appPath Home = ""
appPath Login = "login" appPath Login = "login"
appPath (Folder s i) = "folder/" <> show s <> "/" <> show i appPath (ForgotPassword u) = "forgotPassword/" <> show u
appPath (FolderPrivate s i) = "folderPrivate/" <> show s <> "/" <> show i appPath (Folder s i) = "folder/" <> show s <> "/" <> show i
appPath (FolderPublic s i) = "folderPublic/" <> show s <> "/" <> show i appPath (FolderPrivate s i) = "folderPrivate/" <> show s <> "/" <> show i
appPath (FolderShared s i) = "folderShared/" <> show s <> "/" <> show i appPath (FolderPublic s i) = "folderPublic/" <> show s <> "/" <> show i
appPath (Team s i) = "team/" <> 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 (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 (Corpus s i) = "corpus/" <> show s <> "/" <> show i
appPath (CorpusCode s i) = "corpusCode/" <> 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