No state for projectSpec

parent 84bbe044
...@@ -24,7 +24,7 @@ brevetSpec :: Spec State {} Action ...@@ -24,7 +24,7 @@ brevetSpec :: Spec State {} Action
brevetSpec = noState B.brevetsSpec brevetSpec = noState B.brevetsSpec
projectSpec :: Spec State {} Action projectSpec :: Spec State {} Action
projectSpec = focus _projectslens _projectsAction PS.projets projectSpec = noState PS.projets
facets :: Spec State {} Action facets :: Spec State {} Action
facets = tabs _tablens _tabAction $ fromFoldable facets = tabs _tablens _tabAction $ fromFoldable
......
...@@ -6,7 +6,6 @@ import Data.Lens (Lens', Prism', lens, prism) ...@@ -6,7 +6,6 @@ import Data.Lens (Lens', Prism', lens, prism)
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Gargantext.Pages.Corpus.User.Users.Types.States (Action(..), State) import Gargantext.Pages.Corpus.User.Users.Types.States (Action(..), State)
import Gargantext.Pages.Corpus.User.Users.Types.Types (User) import Gargantext.Pages.Corpus.User.Users.Types.Types (User)
import Gargantext.Pages.Folder as PS
import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Thermite (Spec, noState) import Thermite (Spec, noState)
...@@ -25,12 +24,3 @@ _tabAction = prism TabA \ action -> ...@@ -25,12 +24,3 @@ _tabAction = prism TabA \ action ->
publicationSpec :: Spec State {} Action publicationSpec :: Spec State {} Action
publicationSpec = noState P.publicationSpec publicationSpec = noState P.publicationSpec
_projectslens :: Lens' State PS.State
_projectslens = lens (\s -> s.projects) (\s ss -> s {projects = ss})
_projectsAction :: Prism' Action PS.Action
_projectsAction = prism ProjectsA \ action ->
case action of
ProjectsA laction -> Right laction
_-> Left action
...@@ -2,25 +2,21 @@ module Gargantext.Pages.Corpus.User.Users.Types.States where ...@@ -2,25 +2,21 @@ module Gargantext.Pages.Corpus.User.Users.Types.States where
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.Pages.Corpus.User.Users.Types.Types (User) import Gargantext.Pages.Corpus.User.Users.Types.Types (User)
import Gargantext.Pages.Folder as PS
import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P import Gargantext.Pages.Corpus.User.Users.Specs.Documents as P
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
data Action data Action
= NoOp = NoOp
| ProjectsA PS.Action
| TabA Tab.Action | TabA Tab.Action
| FetchUser Int | FetchUser Int
type State = type State =
{ activeTab :: Int { activeTab :: Int
, projects :: PS.State
, user :: Maybe User , user :: Maybe User
} }
initialState :: State initialState :: State
initialState = initialState =
{ activeTab : 0 { activeTab : 0
, projects : PS.initialState
, user: Nothing , user: Nothing
} }
...@@ -2,22 +2,12 @@ module Gargantext.Pages.Folder where ...@@ -2,22 +2,12 @@ module Gargantext.Pages.Folder where
import Prelude import Prelude
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
type State = String projets :: Spec {} {} Void
projets = simpleSpec defaultPerformAction render
initialState :: State
initialState = ""
data Action = NoOp
performAction :: PerformAction State {} Action
performAction NoOp _ _ = pure unit
projets :: Spec State {} Action
projets = simpleSpec performAction render
where where
render :: Render State {} Action render :: Render {} {} Void
render dispatch _ state _ = render dispatch _ state _ =
[] []
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