Commit 46038d62 authored by Mael NICOLAS's avatar Mael NICOLAS

look like the action is never called dunno why

parent 30998d6f
...@@ -12,7 +12,7 @@ import Data.Lens (set) ...@@ -12,7 +12,7 @@ import Data.Lens (set)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.REST (get) import Gargantext.REST (get)
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Prelude (id, show, void, ($), (<>), bind) import Prelude (bind, id, pure, show, void, ($), (<<<), (<>))
import Thermite (PerformAction, modifyState) import Thermite (PerformAction, modifyState)
getUser :: forall eff. Int -> Aff getUser :: forall eff. Int -> Aff
...@@ -26,11 +26,12 @@ performAction :: forall eff props. PerformAction ( console :: CONSOLE ...@@ -26,11 +26,12 @@ performAction :: forall eff props. PerformAction ( console :: CONSOLE
| eff ) State props Action | eff ) State props Action
performAction NoOp _ _ = void do performAction NoOp _ _ = void do
modifyState id modifyState id
performAction FetchUser _ _ = void do performAction (FetchUser id) _ _ = void do
value <- lift $ getUser 452145 value <- lift $ getUser id
let user = case value of let user = case value of
(Right user) -> Just user (Right user) -> Just user
_ -> Nothing _ -> Nothing
modifyState \state -> set _user user state _ <- pure <<< log $ "Fetching user..."
pure $ modifyState \state -> set _user user state
performAction _ _ _ = void do performAction _ _ _ = void do
modifyState id modifyState id
module Gargantext.Users.Specs.Renders module Gargantext.Users.Specs.Renders
where where
import Gargantext.Users.Types
import Control.Monad.Aff (attempt) import Control.Monad.Aff (attempt)
import Control.Monad.Aff.Class (liftAff) import Control.Monad.Aff.Class (liftAff)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Generic (gShow) import Data.Generic (gShow)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Gargantext.Users.API (getUser) import Prelude (($), (<<<))
import Gargantext.Users.Types
import Prelude (show, ($), (<<<))
import React (ReactElement) import React (ReactElement)
import React.DOM (div, h4, li, span, text, ul) import React.DOM (button, div, h4, li, span, text, ul)
import React.DOM.Props (_id, className) import React.DOM.Props (_id, className)
import React.DOM.Props as RP
import Thermite (Render) import Thermite (Render)
...@@ -71,6 +72,7 @@ render dispatch _ state _ = ...@@ -71,6 +72,7 @@ render dispatch _ state _ =
[ [
div [className "row"] div [className "row"]
[ [
button [RP.onClick \_ -> dispatch $ FetchUser 452145] [ text "Fetch User"],
div [className "col-md-8"] div [className "col-md-8"]
$ card (case state.user of (Just _) -> "Ok" $ card (case state.user of (Just _) -> "Ok"
Nothing -> "Pas Ok") Nothing -> "Pas Ok")
......
...@@ -14,7 +14,7 @@ data Action ...@@ -14,7 +14,7 @@ data Action
| BrevetsA B.Action | BrevetsA B.Action
| ProjectsA PS.Action | ProjectsA PS.Action
| TabA Tab.Action | TabA Tab.Action
| FetchUser | FetchUser Int
type State = type State =
{ activeTab :: Int { activeTab :: Int
......
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