Hide ngramState of the NgramsTable component

parent c1332153
...@@ -3,15 +3,19 @@ module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable where ...@@ -3,15 +3,19 @@ module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable where
import Data.Array (filter, fold, toUnfoldable) import Data.Array (filter, fold, toUnfoldable)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Newtype (class Newtype, unwrap)
import Data.Lens (Lens', Prism', lens, over, prism) import Data.Lens (Lens', Prism', lens, over, prism)
import Data.Lens.Iso (re)
import Data.Lens.Iso.Newtype (_Newtype)
import Data.List (List) import Data.List (List)
import Data.Tuple (Tuple(..), uncurry) import Data.Tuple (Tuple(..), uncurry)
import Data.Void (Void)
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem as NI import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem as NI
import Prelude (class Eq, class Ord, class Show, map, show, void, ($), (*), (+), (-), (/), (<), (<>), (==), (>), (>=)) import Prelude (class Eq, class Ord, class Show, map, show, void, ($), (*), (+), (-), (/), (<), (<>), (==), (>), (>=))
import React (ReactElement) import React (ReactElement)
import React.DOM hiding (style, map) import React.DOM hiding (style, map)
import React.DOM.Props (_id, _type, className, href, name, onChange, onClick, onInput, placeholder, scope, selected, style, value) import React.DOM.Props (_id, _type, className, href, name, onChange, onClick, onInput, placeholder, scope, selected, style, value)
import Thermite (PerformAction, Spec, _render, cotransform, focus, foreach, modifyState, withState) import Thermite (PerformAction, Spec, _render, cotransform, focus, foreach, modifyState, withState, focusState, hide)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
newtype State = State newtype State = State
...@@ -24,6 +28,8 @@ newtype State = State ...@@ -24,6 +28,8 @@ newtype State = State
, totalRecords :: Int , totalRecords :: Int
} }
derive instance newtypeState :: Newtype State _
initialState :: State initialState :: State
initialState = State { items : toUnfoldable [NI.initialState] initialState = State { items : toUnfoldable [NI.initialState]
, search : "" , search : ""
...@@ -146,9 +152,11 @@ tableSpec = over _render \render dispatch p (State s) c -> ...@@ -146,9 +152,11 @@ tableSpec = over _render \render dispatch p (State s) c ->
] ]
] ]
ngramsTableSpec :: Spec State {} Action ngramsTableSpec :: Spec {} {} Void
ngramsTableSpec = container $ fold ngramsTableSpec = hide (unwrap initialState) $
[ tableSpec $ withState \st -> focusState (re _Newtype) $
container $ fold
[ tableSpec $ withState \st ->
focus _itemsList _ItemAction $ focus _itemsList _ItemAction $
foreach \_ -> NI.ngramsItemSpec foreach \_ -> NI.ngramsItemSpec
] ]
......
...@@ -13,7 +13,6 @@ import Gargantext.Components.Tree as Tree ...@@ -13,7 +13,6 @@ import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus.Doc.Annotation as D import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.User.Users as U import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Pages.Layout.Specs.Search as S
...@@ -37,7 +36,6 @@ data Action ...@@ -37,7 +36,6 @@ data Action
| Go | Go
| ShowLogin | ShowLogin
| ShowAddcorpus | ShowAddcorpus
| NgramsA NG.Action
performAction :: PerformAction AppState {} Action performAction :: PerformAction AppState {} Action
...@@ -97,7 +95,6 @@ performAction (UserPageA _) _ _ = pure unit ...@@ -97,7 +95,6 @@ performAction (UserPageA _) _ _ = pure unit
performAction (DocAnnotationViewA _) _ _ = pure unit performAction (DocAnnotationViewA _) _ _ = pure unit
performAction (TreeViewA _) _ _ = pure unit performAction (TreeViewA _) _ _ = pure unit
performAction (GraphExplorerA _) _ _ = pure unit performAction (GraphExplorerA _) _ _ = pure unit
performAction (NgramsA _) _ _ = pure unit
---------------------------------------------------------- ----------------------------------------------------------
...@@ -148,9 +145,3 @@ _graphExplorerAction = prism GraphExplorerA \action -> ...@@ -148,9 +145,3 @@ _graphExplorerAction = prism GraphExplorerA \action ->
case action of case action of
GraphExplorerA caction -> Right caction GraphExplorerA caction -> Right caction
_-> Left action _-> Left action
_NgramsA :: Prism' Action NG.Action
_NgramsA = prism NgramsA \action ->
case action of
NgramsA caction -> Right caction
_-> Left action
...@@ -18,10 +18,10 @@ import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE ...@@ -18,10 +18,10 @@ import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.User.Users as U import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Home as L import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _NgramsA, _addCorpusAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction) import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _docAnnotationViewState, _docViewState, _graphExplorerState, _loginState, _ngramState, _searchState, _treeState, _userPageState) import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _docAnnotationViewState, _docViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState)
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
import React (ReactElement) import React (ReactElement)
import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul) import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul)
...@@ -62,7 +62,7 @@ pagesComponent s = ...@@ -62,7 +62,7 @@ pagesComponent s =
selectSpec Tabview = layout0 $ noState TV.pureTab1 selectSpec Tabview = layout0 $ noState TV.pureTab1
-- To be removed -- To be removed
selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec
selectSpec NGramsTable = layout0 $ focus _ngramState _NgramsA NG.ngramsTableSpec selectSpec NGramsTable = layout0 $ noState NG.ngramsTableSpec
selectSpec PGraphExplorer = focus _graphExplorerState _graphExplorerAction GE.specOld selectSpec PGraphExplorer = focus _graphExplorerState _graphExplorerAction GE.specOld
selectSpec Dashboard = layout0 $ noState Dsh.layoutDashboard selectSpec Dashboard = layout0 $ noState Dsh.layoutDashboard
......
...@@ -9,7 +9,6 @@ import Gargantext.Components.Tree as Tree ...@@ -9,7 +9,6 @@ import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus.Doc.Annotation as D import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.User.Users as U import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Layout.Specs.AddCorpus as AC import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S import Gargantext.Pages.Layout.Specs.Search as S
...@@ -29,7 +28,6 @@ type AppState = ...@@ -29,7 +28,6 @@ type AppState =
, showCorpus :: Boolean , showCorpus :: Boolean
, graphExplorerState :: GE.State , graphExplorerState :: GE.State
, initialized :: Boolean , initialized :: Boolean
, ngramState :: NG.State
} }
initAppState :: AppState initAppState :: AppState
...@@ -47,7 +45,6 @@ initAppState = ...@@ -47,7 +45,6 @@ initAppState =
, showCorpus : false , showCorpus : false
, graphExplorerState : GE.initialState , graphExplorerState : GE.initialState
, initialized : false , initialized : false
, ngramState : NG.initialState
} }
--------------------------------------------------------- ---------------------------------------------------------
...@@ -74,6 +71,3 @@ _treeState = lens (\s -> s.ntreeState) (\s ss -> s {ntreeState = ss}) ...@@ -74,6 +71,3 @@ _treeState = lens (\s -> s.ntreeState) (\s ss -> s {ntreeState = ss})
_graphExplorerState :: Lens' AppState GE.State _graphExplorerState :: Lens' AppState GE.State
_graphExplorerState = lens (\s -> s.graphExplorerState) (\s ss -> s{graphExplorerState = ss}) _graphExplorerState = lens (\s -> s.graphExplorerState) (\s ss -> s{graphExplorerState = ss})
_ngramState :: Lens' AppState NG.State
_ngramState = lens (\s -> s.ngramState) (\s ss -> s{ngramState = ss})
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