diff --git a/src/Gargantext/Components/NgramsTable.purs b/src/Gargantext/Components/NgramsTable.purs
index c64e64460e7b8885109dc63d20cf01851fae6a39..78c7e36cdc54928d227a69b0acfc76d347f5663c 100644
--- a/src/Gargantext/Components/NgramsTable.purs
+++ b/src/Gargantext/Components/NgramsTable.purs
@@ -41,8 +41,6 @@ import Gargantext.Prelude
 import Gargantext.Components.Loader as Loader
 import Gargantext.Components.NgramsTable.Core
 
-type Props' = Loader.InnerProps PageParams VersionedNgramsTable ()
-
 type State =
   CoreState
   ( ngramsParent     :: Maybe NgramsTerm -- Nothing means we are not currently grouping terms
@@ -198,13 +196,13 @@ toggleMap :: forall a. a -> Maybe a -> Maybe a
 toggleMap _ (Just _) = Nothing
 toggleMap b Nothing  = Just b
 
-ngramsTableSpec :: Spec State Props' Action
+ngramsTableSpec :: Spec State LoadedNgramsTableProps Action
 ngramsTableSpec = simpleSpec performAction render
   where
     setParentResetChildren :: Maybe NgramsTerm -> State -> State
     setParentResetChildren p = _ { ngramsParent = p, ngramsChildren = mempty }
 
-    performAction :: PerformAction State Props' Action
+    performAction :: PerformAction State LoadedNgramsTableProps Action
     performAction (SetParentResetChildren p) _ _ =
       modifyState_ $ setParentResetChildren p
     performAction (ToggleChild b c) _ _ =
@@ -237,7 +235,7 @@ ngramsTableSpec = simpleSpec performAction render
     performAction (AddNewNgram ngram) {path: params} _ =
       lift $ addNewNgram ngram params
 
-    render :: Render State Props' Action
+    render :: Render State LoadedNgramsTableProps Action
     render dispatch { path: pageParams
                     , loaded: Versioned { data: initTable }
                     , dispatch: loaderDispatch }
diff --git a/src/Gargantext/Components/NgramsTable/Core.purs b/src/Gargantext/Components/NgramsTable/Core.purs
index 4db7a574965e41048a663c2684f4c87beb41d0e2..1f031d84cb16ce07e7a0557d93d9421422d3e98b 100644
--- a/src/Gargantext/Components/NgramsTable/Core.purs
+++ b/src/Gargantext/Components/NgramsTable/Core.purs
@@ -1,5 +1,6 @@
 module Gargantext.Components.NgramsTable.Core
   ( PageParams
+  , CoreParams
   , PatchMap
   , NgramsElement(..)
   , _NgramsElement
@@ -12,6 +13,7 @@ module Gargantext.Components.NgramsTable.Core
   , Versioned(..)
   , VersionedNgramsTable
   , CoreState
+  , LoadedNgramsTableProps
   , highlightNgrams
   , initialPageParams
   , loadNgramsTable
@@ -83,17 +85,21 @@ import Gargantext.Components.Table as T
 import Gargantext.Prelude
 import Gargantext.Components.Loader as Loader
 
-
-type PageParams =
-  { nodeId :: Int
+type CoreParams s =
+  { nodeId  :: Int
   , listIds :: Array Int
-  , params :: T.Params
   , tabType :: TabType
-  , searchQuery :: String
-  , termListFilter :: Maybe TermList -- Nothing means all
-  , termSizeFilter :: Maybe TermSize -- Nothing means all
+  | s
   }
 
+type PageParams =
+  CoreParams
+    ( params :: T.Params
+    , searchQuery :: String
+    , termListFilter :: Maybe TermList -- Nothing means all
+    , termSizeFilter :: Maybe TermSize -- Nothing means all
+    )
+
 initialPageParams :: Int -> Array Int -> TabType -> PageParams
 initialPageParams nodeId listIds tabType =
   { nodeId
@@ -518,7 +524,7 @@ convOrderBy (T.DESC (T.ColumnName "Score (Occurrences)")) = ScoreDesc
 convOrderBy (T.ASC  _) = TermAsc
 convOrderBy (T.DESC _) = TermDesc
 
-addNewNgram :: NgramsTerm -> PageParams -> Aff Unit
+addNewNgram :: forall s. NgramsTerm -> CoreParams s -> Aff Unit
 addNewNgram ngram {nodeId, listIds, tabType} =
   post (toUrl Back (PutNgrams tabType (head listIds)) $ Just nodeId) [ngram]
 
@@ -527,3 +533,5 @@ ngramsLoaderClass = Loader.createLoaderClass "NgramsTableLoader" loadNgramsTable
 
 ngramsLoader :: Loader.Props' PageParams VersionedNgramsTable -> ReactElement
 ngramsLoader props = React.createElement ngramsLoaderClass props []
+
+type LoadedNgramsTableProps = Loader.InnerProps PageParams VersionedNgramsTable ()
diff --git a/src/Gargantext/Pages/Corpus/Document.purs b/src/Gargantext/Pages/Corpus/Document.purs
index 271c7882c5927db089565f98ff9c2d1367e63abe..a307d58f6adcd3d756309acf758d5b3099030b00 100644
--- a/src/Gargantext/Pages/Corpus/Document.purs
+++ b/src/Gargantext/Pages/Corpus/Document.purs
@@ -2,42 +2,54 @@ module Gargantext.Pages.Corpus.Document where
 
 import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?))
 import Data.Generic.Rep (class Generic)
-import Data.Lens (Lens', lens, (?~))
 import Data.Generic.Rep.Show (genericShow)
 import Data.Map as Map
-import Data.Set as Set
-import Data.Tuple (Tuple(..))
 import Data.Maybe (Maybe(..), maybe)
 import Effect.Aff (Aff)
-import React (ReactElement)
-import React.DOM (div, h4, li, option, p, span, text, ul)
-import React.DOM.Props (className, value)
-import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
-import Unsafe.Coerce (unsafeCoerce)
+import React (ReactElement, ReactClass)
+import React as React
+import React.DOM (div, h4, li, p, span, text, ul)
+import React.DOM.Props (className)
+import Thermite (PerformAction, Render, Spec, simpleSpec, cmapProps, defaultPerformAction, createClass)
 import Control.Monad.Trans.Class (lift)
 
 import Gargantext.Prelude
 import Gargantext.Config          (toUrl, NodeType(..), End(..), TabSubType(..), TabType(..), CTabNgramType(..))
 import Gargantext.Config.REST     (get)
+import Gargantext.Components.AutoUpdate (autoUpdateElt)
+import Gargantext.Components.Loader as Loader
 import Gargantext.Components.Node (NodePoly(..))
-import Gargantext.Components.NgramsTable.Core (NgramsTable(..), NgramsElement(..), loadNgramsTable, Versioned(..))
+import Gargantext.Components.NgramsTable.Core
 import Gargantext.Components.Annotation.AnnotatedField as AnnotatedField
-import Gargantext.Types (TermList(..))
+import Gargantext.Types (TermList)
 import Gargantext.Utils.Reactix ( scuff )
 
-type State =
-  { document    :: Maybe (NodePoly Document)
-  , ngramsTable :: Maybe NgramsTable
-  }
+type DocPath = { nodeId :: Int, listIds :: Array Int, tabType :: TabType }
+
+type NodeDocument = NodePoly Document
+
+type LoadedData =
+  { document    :: NodeDocument
+  , ngramsTable :: VersionedNgramsTable }
 
-initialState :: {} -> State
-initialState {} =
-  { document: Nothing
-  , ngramsTable: Nothing
+type LoadedDataProps = Loader.InnerProps DocPath LoadedData ()
+
+-- This is a subpart of NgramsTable.State.
+type State = CoreState ()
+
+initialState :: forall props others
+              . { loaded :: { ngramsTable :: VersionedNgramsTable | others } | props }
+             -> State
+initialState {loaded: {ngramsTable: Versioned {version}}} =
+  { ngramsTablePatch: mempty
+  , ngramsVersion:    version
   }
 
+-- This is a subset of NgramsTable.Action.
 data Action
-  = Load Int Int
+  = SetTermListItem NgramsTerm (Replace TermList)
+  | AddNewNgram NgramsTerm
+  | Refresh
 
 newtype Status = Status { failed    :: Int
                         , succeeded :: Int
@@ -119,7 +131,7 @@ data Document
     --, text               :: Maybe String
     }
 
-defaultNodeDocument :: NodePoly Document
+defaultNodeDocument :: NodeDocument
 defaultNodeDocument =
   NodePoly { id : 0
            , typename : 0
@@ -261,70 +273,97 @@ instance decodeDocument :: DecodeJson Document
                       --, text
                       }
 
-------------------------------------------------------------------------
-performAction :: PerformAction State {} Action
-performAction (Load lId nId) _ _ = do
-  node <- lift $ getNode (Just nId)
-  (Versioned {version:_version, data:table}) <- lift $ loadNgramsTable {nodeId : nId
-                                  , listIds : [lId]
-                                  , params : { offset : 0, limit : 100, orderBy: Nothing}
-                                  , tabType : (TabDocument (TabNgramType CTabTerms))
-                                  , searchQuery : ""
-                                  , termListFilter : Nothing
-                                  , termSizeFilter : Nothing
-                                   }
-  void $ modifyState $ _document    ?~ node
-  void $ modifyState $ _ngramsTable ?~ table
-  logs $ "Node Document " <> show nId <> " fetched."
-
-getNode :: Maybe Int -> Aff (NodePoly Document)
-getNode = get <<< toUrl Back Node
-
-_document :: Lens' State (Maybe (NodePoly Document))
-_document = lens (\s -> s.document) (\s ss -> s{document = ss})
-
-_ngramsTable :: Lens' State (Maybe NgramsTable)
-_ngramsTable = lens (\s -> s.ngramsTable) (\s ss -> s{ngramsTable = ss})
-
-------------------------------------------------------------------------
-
-docview :: Spec State {} Action
-docview = simpleSpec performAction render
+docViewSpec :: Spec State LoadedDataProps Action
+docViewSpec = simpleSpec performAction render
   where
-    render :: Render State {} Action
-    render dispatch _ state _ =
-      [
-          div [className "container1"]
+    performAction :: PerformAction State LoadedDataProps Action
+    performAction Refresh {path: {nodeId, listIds, tabType}} {ngramsVersion} = do
+        commitPatch {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: mempty})
+    performAction (SetTermListItem n pl) {path: {nodeId, listIds, tabType}} {ngramsVersion} =
+        commitPatch {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: pt})
+      where
+        pe = NgramsPatch { patch_list: pl, patch_children: mempty }
+        pt = PatchMap $ Map.singleton n pe
+    performAction (AddNewNgram ngram) {path: params} _ =
+      lift $ addNewNgram ngram params
+
+    render :: Render State LoadedDataProps Action
+    render dispatch { path: pageParams
+                    , loaded: { ngramsTable: Versioned { data: initTable }, document }
+                    , dispatch: loaderDispatch }
+                    { ngramsTablePatch }
+                    _reactChildren =
+      [ autoUpdateElt { duration: 3000
+                      , effect:   dispatch Refresh
+                      }
+      , div [className "container1"]
+        [
+          div [className "row"]
           [
-            div [className "row"]
-            [
-              div [className "col-md-8"]
-              [ h4 [] [annotate document.title]
-              , ul [className "list-group"]
-                [ li' [ span [] [text' document.source]
-                      , badge "source"
-                      ]
-                -- TODO add href to /author/ if author present in
-                , li' [ span [] [text' document.authors]
-                      , badge "authors"
-                      ]
-                , li' [ span [] [text' document.publication_date]
-                      , badge "date"
-                      ]
-                ]
-              , badge "abstract"
-              , annotate document.abstract
-              , div [className "jumbotron"]
-                [ p [] [text "Empty Full Text"]
-                ]
+            div [className "col-md-8"]
+            [ h4 [] [annotate doc.title]
+            , ul [className "list-group"]
+              [ li' [ span [] [text' doc.source]
+                    , badge "source"
+                    ]
+              -- TODO add href to /author/ if author present in
+              , li' [ span [] [text' doc.authors]
+                    , badge "authors"
+                    ]
+              , li' [ span [] [text' doc.publication_date]
+                    , badge "date"
+                    ]
+              ]
+            , badge "abstract"
+            , annotate doc.abstract
+            , div [className "jumbotron"]
+              [ p [] [text "Empty Full Text"]
               ]
             ]
           ]
+        ]
       ]
         where
-          annotate t = scuff $ AnnotatedField.annotatedField { ngrams: maybe (NgramsTable Map.empty) identity state.ngramsTable, text: t }
+          ngramsTable = applyNgramsTablePatch ngramsTablePatch initTable
+          annotate text = scuff $ AnnotatedField.annotatedField { ngrams: ngramsTable, text }
           li' = li [className "list-group-item justify-content-between"]
           text' x = text $ maybe "Nothing" identity x
           badge s = span [className "badge badge-default badge-pill"] [text s]
-          NodePoly {hyperdata : Document document} =
-            maybe defaultNodeDocument identity state.document
+          NodePoly {hyperdata : Document doc} = document
+
+layout :: Spec {} {nodeId :: Int, listId :: Int} Void
+layout = cmapProps (\{nodeId, listId} -> {nodeId, listIds: [listId], tabType})
+       $ simpleSpec defaultPerformAction render
+  where
+    tabType = TabDocument (TabNgramType CTabTerms)
+    render :: Render {} DocPath Void
+    render _ path _ _ =
+      [ documentLoader
+        { path
+        , component: createClass "DocumentView" docViewSpec initialState
+        } ]
+
+------------------------------------------------------------------------
+
+loadDocument :: Int -> Aff NodeDocument
+loadDocument = get <<< toUrl Back Node <<< Just
+
+loadData :: DocPath -> Aff LoadedData
+loadData {nodeId, listIds, tabType} = do
+  document <- loadDocument nodeId
+  ngramsTable <- loadNgramsTable
+    { nodeId
+    , listIds: listIds
+    , params: { offset : 0, limit : 100, orderBy: Nothing}
+    , tabType
+    , searchQuery : ""
+    , termListFilter : Nothing
+    , termSizeFilter : Nothing
+    }
+  pure {document, ngramsTable}
+
+documentLoaderClass :: ReactClass (Loader.Props DocPath LoadedData)
+documentLoaderClass = Loader.createLoaderClass "DocumentLoader" loadData
+
+documentLoader :: Loader.Props' DocPath LoadedData -> ReactElement
+documentLoader props = React.createElement documentLoaderClass props []
diff --git a/src/Gargantext/Pages/Layout.purs b/src/Gargantext/Pages/Layout.purs
index 7d49e390c3fd04bc7d9d31567b689b1f1ac39b49..b0d5602a92a64a7635fa965fcdca62effd2e212a 100644
--- a/src/Gargantext/Pages/Layout.purs
+++ b/src/Gargantext/Pages/Layout.purs
@@ -6,7 +6,6 @@ import Gargantext.Pages.Layout.Actions (Action(..))
 import Gargantext.Pages.Layout.Specs.AddCorpus as AC
 -- import Gargantext.Pages.Corpus.Tabs as TV
 
-import Gargantext.Pages.Corpus.Document       as Document
 import Gargantext.Pages.Corpus.Graph          as GE
 -- import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG
 
@@ -51,7 +50,6 @@ dispatchAction dispatcher _ (Folder id) = do
 
 dispatchAction dispatcher _ (Document i n) = do
   dispatcher $ SetRoute $ Document i n
-  dispatcher $ DocumentViewA $ Document.Load i n
 
 dispatchAction dispatcher _ (PGraphExplorer nid) = do
   dispatcher $ SetRoute $ PGraphExplorer nid
diff --git a/src/Gargantext/Pages/Layout/Actions.purs b/src/Gargantext/Pages/Layout/Actions.purs
index eae18697c1f9be77d699bd318ca84ab3cbec0a18..aba737b63357ef2dddc9da22a94f6c320887887d 100644
--- a/src/Gargantext/Pages/Layout/Actions.purs
+++ b/src/Gargantext/Pages/Layout/Actions.purs
@@ -12,7 +12,6 @@ import Routing.Hash                                    (setHash)
 import Gargantext.Components.Login                  as LN
 import Gargantext.Components.Modals.Modal              (modalShow)
 import Gargantext.Pages.Annuaire             as Annuaire
-import Gargantext.Pages.Corpus.Document       as D
 import Gargantext.Pages.Corpus.Graph     as GE
 import Gargantext.Pages.Layout.Specs.AddCorpus      as AC
 import Gargantext.Pages.Layout.Specs.Search         as S
@@ -28,7 +27,6 @@ data Action
   | SearchA    S.Action
   | AddCorpusA AC.Action
   | GraphExplorerA     GE.Action
-  | DocumentViewA D.Action
   | AnnuaireAction     Annuaire.Action
   | ShowLogin
   | Logout
@@ -65,7 +63,6 @@ performAction ShowAddCorpus  _ _ = void do
 performAction (LoginA          _) _ _ = pure unit
 performAction (AddCorpusA      _) _ _ = pure unit
 performAction (SearchA         _) _ _ = pure unit
-performAction (DocumentViewA   _) _ _ = pure unit
 performAction (GraphExplorerA  _) _ _ = pure unit
 performAction (AnnuaireAction  _) _ _ = pure unit
   -- liftEffect $ modalShow "addCorpus"
@@ -97,12 +94,6 @@ _annuaireAction = prism AnnuaireAction \action ->
        AnnuaireAction a -> Right a
        _                -> Left  action
 
-_documentViewAction :: Prism' Action D.Action
-_documentViewAction = prism DocumentViewA \action ->
-  case action of
-    DocumentViewA 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 2185ec8b259779a9c1aca060ceb64e958f11af34..48f963a1acc03c8cb9fa5b449855e8085ab22294 100644
--- a/src/Gargantext/Pages/Layout/Specs.purs
+++ b/src/Gargantext/Pages/Layout/Specs.purs
@@ -23,11 +23,11 @@ import Gargantext.Pages.Corpus.Document as Annotation
 import Gargantext.Pages.Corpus.Dashboard as Dsh
 import Gargantext.Pages.Corpus.Graph as GE
 import Gargantext.Pages.Home as L
-import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, performAction)
+import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _graphExplorerAction, _loginAction, _searchAction, performAction)
 import Gargantext.Pages.Layout.Specs.AddCorpus as AC
 import Gargantext.Pages.Layout.Specs.Search    as S
 import Gargantext.Pages.Layout.Specs.SearchBar as SB
-import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState)
+import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _graphExplorerState, _loginState, _searchState)
 import Gargantext.Router (Routes(..))
 import Gargantext.Utils.Reactix as R'
 
@@ -60,7 +60,7 @@ pagesComponent s = case s.currentRoute of
     selectSpec (Corpus   i)      = layout0 $ cmapProps (const {nodeId: i}) $ noState Corpus.layout
     selectSpec AddCorpus         = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
     selectSpec SearchView        = layout0 $ focus _searchState _searchAction  S.searchSpec
-    selectSpec (Document l i)      = layout0 $ focus _documentViewState _documentViewAction  Annotation.docview
+    selectSpec (Document l i)    = layout0 $ cmapProps (const {nodeId: i, listId: l}) $ noState Annotation.layout
     selectSpec (PGraphExplorer i)= layout1  $ focus _graphExplorerState _graphExplorerAction  GE.specOld
     selectSpec Dashboard         = layout0 $ noState Dsh.layoutDashboard
     selectSpec (Annuaire i)      = layout0 $ cmapProps (const {annuaireId: i}) $ noState A.layout
diff --git a/src/Gargantext/Pages/Layout/States.purs b/src/Gargantext/Pages/Layout/States.purs
index 57517e7efd2e6b2a12d07c6d7465b536b9322a12..fa4cf9d8b3dffabd0453d1f7c1d6ddfc6687c2be 100644
--- a/src/Gargantext/Pages/Layout/States.purs
+++ b/src/Gargantext/Pages/Layout/States.purs
@@ -7,7 +7,6 @@ import Data.Maybe                                      (Maybe(Just))
 import Effect (Effect)
 import Gargantext.Components.Login                  as LN
 
-import Gargantext.Pages.Corpus.Document       as D
 import Gargantext.Pages.Corpus.Graph     as GE
 import Gargantext.Pages.Layout.Specs.AddCorpus      as AC
 import Gargantext.Pages.Layout.Specs.Search         as S
@@ -18,7 +17,6 @@ type AppState =
   , loginState         :: LN.State
   , addCorpusState     :: AC.State
   , searchState        :: S.State
-  , documentState      :: D.State
   , showLogin          :: Boolean
   , showCorpus         :: Boolean
   , graphExplorerState :: GE.State
@@ -33,7 +31,6 @@ initAppState = do
     , loginState
     , addCorpusState : AC.initialState
     , searchState    : S.initialState
-    , documentState  : D.initialState {}
     , showLogin      : false
     , showCorpus     : false
     , graphExplorerState : GE.initialState
@@ -52,9 +49,6 @@ _addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss}
 _searchState :: Lens' AppState S.State
 _searchState = lens (\s -> s.searchState) (\s ss -> s{searchState = ss})
 
-_documentViewState :: Lens' AppState D.State
-_documentViewState = lens (\s -> s.documentState) (\s ss -> s{documentState = ss})
-
 _graphExplorerState :: Lens' AppState GE.State
 _graphExplorerState = lens (\s -> s.graphExplorerState) (\s ss -> s{graphExplorerState = ss})