diff --git a/src/Gargantext/Pages/Corpus.purs b/src/Gargantext/Pages/Corpus.purs
index 40c265a57109059f5f7b7b7130fc14ccc288876a..7e598805b737a8b02f6a4c991026b17958e4fdc9 100644
--- a/src/Gargantext/Pages/Corpus.purs
+++ b/src/Gargantext/Pages/Corpus.purs
@@ -2,7 +2,6 @@ module Gargantext.Pages.Corpus where
 
 import Prelude hiding (div)
 
-import Data.Array (fold)
 import Gargantext.Components.Charts.Options.ECharts (chart)
 import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis)
 import Gargantext.Pages.Corpus.Doc.Facets as Tab
@@ -10,10 +9,6 @@ import React.DOM (div, h3, hr, i, p, text)
 import React.DOM.Props (className, style)
 import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
 
-type State = Tab.State
-
-type Action = Tab.Action
-
 type Corpus = { title :: String
               , desc  :: String
               , query :: String
@@ -21,19 +16,14 @@ type Corpus = { title :: String
               , authors :: String
               }
 
-initialState :: State
-initialState = Tab.initialState
-
-spec' :: Spec Tab.State {} Tab.Action
-spec' = fold [ corpusSpec
-             , Tab.tab1
-             ]
+spec' :: Spec {} {} Void
+spec' = corpusSpec <> Tab.pureTab1
 
-corpusSpec :: Spec Tab.State {} Tab.Action
+corpusSpec :: Spec {} {} Void
 corpusSpec = simpleSpec defaultPerformAction render
   where
-    render :: Render Tab.State {} Tab.Action
-    render dispatch _ state _ =
+    render :: Render {} {} Void
+    render _ _ _ _ =
       [ div [className "row"]
         [ div [className "col-md-3"] [ h3 [] [text corpus.title] ]
         , div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
diff --git a/src/Gargantext/Pages/Corpus/Doc/Facets/Specs.purs b/src/Gargantext/Pages/Corpus/Doc/Facets/Specs.purs
index 9eeaa8185c47f4bb1b2d934fb5d1f514e70d28c5..24912a2473be3cea9e0b71625f6b997a1e10c423 100644
--- a/src/Gargantext/Pages/Corpus/Doc/Facets/Specs.purs
+++ b/src/Gargantext/Pages/Corpus/Doc/Facets/Specs.purs
@@ -2,12 +2,11 @@ module Gargantext.Pages.Corpus.Doc.Facets.Specs where
 
 import Prelude hiding (div)
 
-import Data.Lens (Lens', Prism', lens, prism)
 import Data.List (fromFoldable)
 import Data.Tuple (Tuple(..))
 
-import Gargantext.Pages.Corpus.Doc.Facets.States (State(..), _doclens, _sourcelens, _authorlens, _termslens, _tablens)
-import Gargantext.Pages.Corpus.Doc.Facets.Actions (Action(..), _docAction, _sourceAction, _authorAction, _termsAction, _tabAction)
+import Gargantext.Pages.Corpus.Doc.Facets.States (State(), _doclens, _sourcelens, _authorlens, _termslens, _tablens, initialState)
+import Gargantext.Pages.Corpus.Doc.Facets.Actions (Action(), _docAction, _sourceAction, _authorAction, _termsAction, _tabAction)
 
 import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
 import Gargantext.Pages.Corpus.Doc.Facets.Sources as SV
@@ -15,16 +14,19 @@ import Gargantext.Pages.Corpus.Doc.Facets.Authors as AV
 import Gargantext.Pages.Corpus.Doc.Facets.Terms as TV
 import Gargantext.Components.Tab as Tab
 
-import Thermite (Spec, focus)
+import Thermite (Spec, focus, hide)
 
 
+pureTab1 :: Spec {} {} Void
+pureTab1 = hide initialState statefulTab1
 
-tab1 :: Spec State {} Action
-tab1 = Tab.tabs _tablens _tabAction $ fromFoldable [ Tuple "Doc View"    docPageSpec
-                                                   , Tuple "Author View" authorPageSpec
-                                                   , Tuple "Source View" sourcePageSpec
-                                                   , Tuple "Terms View"  termsPageSpec
-                                                   ]
+statefulTab1 :: Spec State {} Action
+statefulTab1 =
+  Tab.tabs _tablens _tabAction $ fromFoldable [ Tuple "Doc View"    docPageSpec
+                                              , Tuple "Author View" authorPageSpec
+                                              , Tuple "Source View" sourcePageSpec
+                                              , Tuple "Terms View"  termsPageSpec
+                                              ]
 
 docPageSpec :: Spec State {} Action
 docPageSpec = focus _doclens _docAction DV.layoutDocview
diff --git a/src/Gargantext/Pages/Layout/Actions.purs b/src/Gargantext/Pages/Layout/Actions.purs
index ae5aff6e336745c4d64577408d88a38ba1ed4f3e..0c3c5b77b18ffb114a41afdc7168ccdc707201b5 100644
--- a/src/Gargantext/Pages/Layout/Actions.purs
+++ b/src/Gargantext/Pages/Layout/Actions.purs
@@ -10,9 +10,7 @@ import Effect.Console (log)
 import Gargantext.Components.Login as LN
 import Gargantext.Components.Modals.Modal (modalShow)
 import Gargantext.Components.Tree as Tree
-import Gargantext.Pages.Corpus as CA
 import Gargantext.Pages.Corpus.Doc.Annotation as D
-import Gargantext.Pages.Corpus.Doc.Facets as TV
 import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
 import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
 import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
@@ -37,12 +35,10 @@ data Action
   | UserPageA  U.Action
   | DocAnnotationViewA  D.Action
   | TreeViewA  Tree.Action
-  | TabViewA   TV.Action
   | GraphExplorerA GE.Action
   | DashboardA Dsh.Action
   | Search     String
   | Go
-  | CorpusAnalysisA CA.Action
   | ShowLogin
   | ShowAddcorpus
   | NgramsA    NG.Action
@@ -105,11 +101,9 @@ performAction (SearchA _) _ _ = pure unit
 performAction (UserPageA _) _ _ = pure unit
 performAction (DocAnnotationViewA _) _ _ = pure unit
 performAction (TreeViewA _) _ _ = pure unit
-performAction (TabViewA _) _ _ = pure unit
 performAction (GraphExplorerA _) _ _ = pure unit
 performAction (DashboardA _) _ _ = pure unit
 performAction (NgramsA _) _ _ = pure unit
-performAction (CorpusAnalysisA _) _ _ = pure unit
 
 ----------------------------------------------------------
 
@@ -167,18 +161,6 @@ _treeAction = prism TreeViewA \action ->
     TreeViewA caction -> Right caction
     _-> Left action
 
-_tabviewAction :: Prism' Action TV.Action
-_tabviewAction = prism TabViewA \action ->
-  case action of
-    TabViewA caction -> Right caction
-    _-> Left action
-
-_corpusAction :: Prism' Action CA.Action
-_corpusAction = prism CorpusAnalysisA \action ->
-  case action of
-    CorpusAnalysisA caction -> Right caction
-    _-> Left action
-
 _graphExplorerAction :: Prism' Action GE.Action
 _graphExplorerAction = prism GraphExplorerA \action ->
   case action of
diff --git a/src/Gargantext/Pages/Layout/Specs.purs b/src/Gargantext/Pages/Layout/Specs.purs
index 4fe59cc1feb018148d90c185f6ae62b2a0aed931..d02a0f6d0e7839e7ada4f576bd281474ba526eb7 100644
--- a/src/Gargantext/Pages/Layout/Specs.purs
+++ b/src/Gargantext/Pages/Layout/Specs.purs
@@ -18,15 +18,15 @@ 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.Home as L
-import Gargantext.Pages.Layout.Actions (Action(..), _LandingA, _NgramsA, _addCorpusAction, _corpusAction, _dashBoardAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _tabviewAction, _treeAction, _userPageAction, performAction)
+import Gargantext.Pages.Layout.Actions (Action(..), _LandingA, _NgramsA, _addCorpusAction, _dashBoardAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction)
 import Gargantext.Pages.Layout.Specs.AddCorpus as AC
 import Gargantext.Pages.Layout.Specs.Search as S
-import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _corpusState, _dashBoardSate, _docAnnotationViewState, _docViewState, _graphExplorerState, _landingState, _loginState, _ngramState, _searchState, _tabviewState, _treeState, _userPageState)
+import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _dashBoardSate, _docAnnotationViewState, _docViewState, _graphExplorerState, _landingState, _loginState, _ngramState, _searchState, _treeState, _userPageState)
 import Gargantext.Router (Routes(..))
 import React (ReactElement)
 import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul)
 import React.DOM.Props (_data, _id, _type, aria, className, href, onChange, onClick, placeholder, role, src, style, tabIndex, target, title)
-import Thermite (Render, Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState)
+import Thermite (Render, Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState, noState)
 import Unsafe.Coerce (unsafeCoerce)
 
 layoutSpec :: Spec AppState {} Action
@@ -53,14 +53,14 @@ pagesComponent s =
     Nothing    -> selectSpec Home
   where
     selectSpec :: Routes -> Spec AppState {} Action
-    selectSpec CorpusAnalysis    = layout0 $ focus _corpusState  _corpusAction CA.spec'
+    selectSpec CorpusAnalysis    = layout0 $ noState CA.spec'
     selectSpec Login             = focus _loginState _loginAction LN.renderSpec
     selectSpec Home              = layout0 $ focus _landingState   _LandingA   (L.layoutLanding EN)
     selectSpec AddCorpus         = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
     selectSpec DocView           = layout0 $ focus _docViewState   _docViewAction   DV.layoutDocview
     selectSpec (UserPage i)      = layout0 $ focus _userPageState  _userPageAction  U.layoutUser
     selectSpec (DocAnnotation i) = layout0 $ focus _docAnnotationViewState  _docAnnotationViewAction  D.docview
-    selectSpec Tabview           = layout0 $ focus _tabviewState  _tabviewAction  TV.tab1
+    selectSpec Tabview           = layout0 $ noState TV.pureTab1
     -- To be removed
     selectSpec SearchView        = layout0 $ focus _searchState _searchAction  S.searchSpec
     selectSpec NGramsTable       = layout0 $ focus _ngramState _NgramsA  NG.ngramsTableSpec
diff --git a/src/Gargantext/Pages/Layout/States.purs b/src/Gargantext/Pages/Layout/States.purs
index baafbdf1729dbfdb044cbe92e240b906d220ef8d..d67a6472c277c69193962c315edd6ad054392eb7 100644
--- a/src/Gargantext/Pages/Layout/States.purs
+++ b/src/Gargantext/Pages/Layout/States.purs
@@ -6,9 +6,7 @@ import Data.Lens (Lens', lens)
 import Data.Maybe (Maybe(Just))
 import Gargantext.Components.Login as LN
 import Gargantext.Components.Tree as Tree
-import Gargantext.Pages.Corpus as CA
 import Gargantext.Pages.Corpus.Doc.Annotation as D
-import Gargantext.Pages.Corpus.Doc.Facets as TV
 import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
 import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
 import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
@@ -29,9 +27,7 @@ type AppState =
   , userPageState  :: U.State
   , docAnnotationState :: D.State
   , ntreeState     :: Tree.State
-  , tabviewState   :: TV.State
   , search         :: String
-  , corpusState    :: CA.State
   , showLogin      :: Boolean
   , showCorpus     :: Boolean
   , graphExplorerState  :: GE.State
@@ -51,9 +47,7 @@ initAppState =
   , userPageState  : U.initialState
   , docAnnotationState : D.initialState
   , ntreeState   : Tree.exampleTree
-  , tabviewState : TV.initialState
   , search  : ""
-  , corpusState  : CA.initialState
   , showLogin    : false
   , showCorpus   : false
   , graphExplorerState  : GE.initialState
@@ -87,12 +81,6 @@ _docAnnotationViewState = lens (\s -> s.docAnnotationState) (\s ss -> s{docAnnot
 _treeState :: Lens' AppState Tree.State
 _treeState = lens (\s -> s.ntreeState) (\s ss -> s {ntreeState = ss})
 
-_tabviewState :: Lens' AppState TV.State
-_tabviewState = lens (\s -> s.tabviewState) (\s ss -> s {tabviewState = ss})
-
-_corpusState :: Lens' AppState CA.State
-_corpusState = lens (\s -> s.corpusState) (\s ss -> s {corpusState = ss})
-
 _dashBoardSate :: Lens' AppState Dsh.State
 _dashBoardSate = lens (\s -> s.dashboardState) (\s ss -> s {dashboardState = ss})