Skip to content
Projects
Groups
Snippets
Help
Loading...
Help
Submit feedback
Contribute to GitLab
Sign in
Toggle navigation
P
purescript-gargantext
Project
Project
Details
Activity
Releases
Cycle Analytics
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Charts
Issues
154
Issues
154
List
Board
Labels
Milestones
Merge Requests
3
Merge Requests
3
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Charts
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Charts
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
gargantext
purescript-gargantext
Commits
5b68c602
Commit
5b68c602
authored
Jun 30, 2021
by
arturo
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
>>> continue
parent
cac55543
Pipeline
#1564
canceled with stage
Changes
6
Pipelines
1
Hide whitespace changes
Inline
Side-by-side
Showing
6 changed files
with
88 additions
and
56 deletions
+88
-56
DocsTable.purs
src/Gargantext/Components/DocsTable.purs
+35
-17
Types.purs
src/Gargantext/Components/DocsTable/Types.purs
+1
-0
Tabs.purs
src/Gargantext/Components/Nodes/Annuaire/Tabs.purs
+9
-8
Tabs.purs
...gantext/Components/Nodes/Annuaire/User/Contacts/Tabs.purs
+1
-0
Types.purs
src/Gargantext/Components/Nodes/Corpus/Types.purs
+0
-14
Texts.purs
src/Gargantext/Components/Nodes/Texts.purs
+42
-17
No files found.
src/Gargantext/Components/DocsTable.purs
View file @
5b68c602
-- TODO: this module should be replaced by FacetsTable
-- TODO: this module should be replaced by FacetsTable
module Gargantext.Components.DocsTable where
module Gargantext.Components.DocsTable where
import Gargantext.Prelude
import Prelude
( class Ord, Unit, bind, const, discard, identity, mempty
, otherwise, pure, show, unit, ($), (/=), (<$>), (<<<), (<>), (==) )
import DOM.Simple.Console (log2)
import DOM.Simple.Event as DE
import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>))
import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>))
import Data.Array as A
import Data.Array as A
import Data.Lens ((^.))
import Data.Lens ((^.))
...
@@ -16,34 +17,31 @@ import Data.Set as Set
...
@@ -16,34 +17,31 @@ import Data.Set as Set
import Data.String as Str
import Data.String as Str
import Data.Symbol (SProxy(..))
import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..))
import Data.Tuple (Tuple(..))
import DOM.Simple.Console (log2)
import DOM.Simple.Event as DE
import Effect (Effect)
import Effect (Effect)
import Effect.Aff (Aff, launchAff_)
import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect)
import Effect.Class (liftEffect)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.Category (rating)
import Gargantext.Components.Category (rating)
import Gargantext.Components.Category.Types (Star(..))
import Gargantext.Components.Category.Types (Star(..))
import Gargantext.Components.DocsTable.Types
import Gargantext.Components.DocsTable.Types (DocumentsView(..), Hyperdata(..), LocalUserScore, Query, Response(..), Year, sampleData)
( DocumentsView(..), Hyperdata(..), LocalUserScore, Query, Response(..), sampleData )
import Gargantext.Components.Table.Types as TT
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Table as TT
import Gargantext.Components.Table as TT
import Gargantext.Components.Table.Types as TT
import Gargantext.Ends (Frontends, url)
import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.Loader (useLoader, useLoaderWithCacheAPI, HashedResponse(..))
import Gargantext.Hooks.Loader (useLoader, useLoaderWithCacheAPI, HashedResponse(..))
import Gargantext.
Routes as Routes
import Gargantext.
Prelude (class Ord, Unit, bind, const, discard, identity, mempty, otherwise, pure, show, unit, ($), (/=), (<$>), (<<<), (<>), (==))
import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId, get, delete)
import Gargantext.Sessions (Session, sessionId, get, delete)
import Gargantext.Types (ListId, NodeID, NodeType(..), OrderBy(..), SidePanelState(..), TableResult, TabSubType, TabType, showTabType')
import Gargantext.Types (ListId, NodeID, NodeType(..), OrderBy(..), SidePanelState(..), TableResult, TabSubType, TabType, showTabType')
import Gargantext.Utils (sortWith)
import Gargantext.Utils (sortWith)
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.QueryString (joinQueryStrings, mQueryParamS, queryParam, queryParamS)
import Gargantext.Utils.QueryString (joinQueryStrings, mQueryParam
, mQueryParam
S, queryParam, queryParamS)
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Gargantext.Utils.Toestand as T2
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
here :: R2.Here
here :: R2.Here
here = R2.here "Gargantext.Components.DocsTable"
here = R2.here "Gargantext.Components.DocsTable"
...
@@ -70,7 +68,8 @@ type CommonProps =
...
@@ -70,7 +68,8 @@ type CommonProps =
, tabType :: TabType
, tabType :: TabType
-- ^ tabType is not ideal here since it is too much entangled with tabs and
-- ^ tabType is not ideal here since it is too much entangled with tabs and
-- ngramtable. Let's see how this evolves. )
-- ngramtable. Let's see how this evolves. )
, totalRecords :: Int
, totalRecords :: Int
, yearFilter :: Maybe Year
)
)
type LayoutProps =
type LayoutProps =
...
@@ -126,6 +125,7 @@ docViewCpt = here.component "docView" cpt where
...
@@ -126,6 +125,7 @@ docViewCpt = here.component "docView" cpt where
, sidePanelState
, sidePanelState
, tabType
, tabType
, totalRecords
, totalRecords
, yearFilter
}
}
, params
, params
, query
, query
...
@@ -151,6 +151,7 @@ docViewCpt = here.component "docView" cpt where
...
@@ -151,6 +151,7 @@ docViewCpt = here.component "docView" cpt where
, sidePanelState
, sidePanelState
, tabType
, tabType
, totalRecords
, totalRecords
, yearFilter
} [] ] ] ]
} [] ] ] ]
type SearchBarProps =
type SearchBarProps =
...
@@ -247,6 +248,12 @@ filterDocs query docs = A.filter filterFunc docs
...
@@ -247,6 +248,12 @@ filterDocs query docs = A.filter filterFunc docs
filterFunc (Response { hyperdata: Hyperdata { title } }) =
filterFunc (Response { hyperdata: Hyperdata { title } }) =
isJust $ Str.indexOf (Str.Pattern $ Str.toLower query) $ Str.toLower title
isJust $ Str.indexOf (Str.Pattern $ Str.toLower query) $ Str.toLower title
filterDocsByYear :: Year -> Array Response -> Array Response
filterDocsByYear year docs = A.filter filterFunc docs
where
filterFunc :: Response -> Boolean
filterFunc (Response { hyperdata: Hyperdata { pub_year } }) = eq year $ show pub_year
pageLayout :: R2.Component PageLayoutProps
pageLayout :: R2.Component PageLayoutProps
pageLayout = R.createElement pageLayoutCpt
pageLayout = R.createElement pageLayoutCpt
...
@@ -261,19 +268,29 @@ pageLayoutCpt = here.component "pageLayout" cpt where
...
@@ -261,19 +268,29 @@ pageLayoutCpt = here.component "pageLayout" cpt where
, query
, query
, session
, session
, sidePanel
, sidePanel
, tabType } _ = do
, tabType
, yearFilter
} _ = do
cacheState' <- T.useLive T.unequal cacheState
cacheState' <- T.useLive T.unequal cacheState
let path = { listId, mCorpusId, nodeId, params, query, tabType }
let path = { listId, mCorpusId, nodeId, params, query, tabType }
handleResponse :: HashedResponse (TableResult Response) -> Tuple Int (Array DocumentsView)
handleResponse :: HashedResponse (TableResult Response) -> Tuple Int (Array DocumentsView)
handleResponse (HashedResponse { hash, value: res }) = ret
handleResponse (HashedResponse { hash, value: res }) = ret
where
where
docs = res2corpus <$> filterDocs query res.docs
filters = filterDocs query
>>> \res' -> case yearFilter of
Nothing -> res'
Just year -> filterDocsByYear year res'
docs = res2corpus <$> filters res.docs
ret = if mock then
ret = if mock then
--Tuple 0 (take limit $ drop offset sampleData)
--Tuple 0 (take limit $ drop offset sampleData)
Tuple 0 sampleData
Tuple 0 sampleData
else
else
Tuple res.count docs
Tuple res.count docs
case cacheState' of
case cacheState' of
NT.CacheOn -> do
NT.CacheOn -> do
let paint (Tuple count docs) = page { documents: docs
let paint (Tuple count docs) = page { documents: docs
...
@@ -540,6 +557,7 @@ tableRouteWithPage { listId, nodeId, params: { limit, offset, orderBy, searchTyp
...
@@ -540,6 +557,7 @@ tableRouteWithPage { listId, nodeId, params: { limit, offset, orderBy, searchTyp
st = queryParam "searchType" searchType
st = queryParam "searchType" searchType
tt = queryParamS "tabType" (showTabType' tabType)
tt = queryParamS "tabType" (showTabType' tabType)
q = queryParamS "query" query
q = queryParamS "query" query
-- y = mQueryParam "year" year
deleteAllDocuments :: Session -> Int -> Aff (Array Int)
deleteAllDocuments :: Session -> Int -> Aff (Array Int)
deleteAllDocuments session = delete session <<< documentsRoute
deleteAllDocuments session = delete session <<< documentsRoute
...
...
src/Gargantext/Components/DocsTable/Types.purs
View file @
5b68c602
...
@@ -105,6 +105,7 @@ instance decodeResponse :: DecodeJson Response where
...
@@ -105,6 +105,7 @@ instance decodeResponse :: DecodeJson Response where
type LocalCategories = Map Int Category
type LocalCategories = Map Int Category
type LocalUserScore = Map Int Star
type LocalUserScore = Map Int Star
type Query = String
type Query = String
type Year = String
---------------------------------------------------------
---------------------------------------------------------
sampleData' :: DocumentsView
sampleData' :: DocumentsView
...
...
src/Gargantext/Components/Nodes/Annuaire/Tabs.purs
View file @
5b68c602
...
@@ -2,31 +2,31 @@
...
@@ -2,31 +2,31 @@
module Gargantext.Components.Nodes.Annuaire.Tabs where
module Gargantext.Components.Nodes.Annuaire.Tabs where
import Prelude hiding (div)
import Prelude hiding (div)
import Effect.Aff (Aff)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..))
import Data.Maybe (Maybe(..))
import Data.Tuple (fst)
import Data.Tuple (fst)
import Data.Tuple.Nested ((/\))
import Data.Tuple.Nested ((/\))
import Reactix as R
import Effect.Aff (Aff)
import Record as Record
import Record.Extra as RX
import Toestand as T
import Gargantext.AsyncTasks as GAT
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Tab as Tab
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData)
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData)
import Gargantext.Components.Nodes.Lists.Types as LTypes
import Gargantext.Components.Nodes.Lists.Types as LTypes
import Gargantext.Components.Nodes.Texts.Types as TTypes
import Gargantext.Components.Nodes.Texts.Types as TTypes
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Tab as Tab
import Gargantext.Ends (Frontends)
import Gargantext.Ends (Frontends)
import Gargantext.Sessions (Session)
import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType(..), PTabNgramType(..), SidePanelState, TabType(..), TabSubType(..))
import Gargantext.Types (CTabNgramType(..), PTabNgramType(..), SidePanelState, TabType(..), TabSubType(..))
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Gargantext.Utils.Toestand as T2
import Reactix as R
import Record as Record
import Record.Extra as RX
import Toestand as T
here :: R2.Here
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs"
here = R2.here "Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs"
...
@@ -92,6 +92,7 @@ tabsCpt = here.component "tabs" cpt where
...
@@ -92,6 +92,7 @@ tabsCpt = here.component "tabs" cpt where
, showSearch: true
, showSearch: true
, tabType: TabPairing TabDocs
, tabType: TabPairing TabDocs
, totalRecords
, totalRecords
, yearFilter: Nothing
}
}
type DTCommon =
type DTCommon =
...
...
src/Gargantext/Components/Nodes/Annuaire/User/Contacts/Tabs.purs
View file @
5b68c602
...
@@ -127,6 +127,7 @@ tabsCpt = here.component "tabs" cpt
...
@@ -127,6 +127,7 @@ tabsCpt = here.component "tabs" cpt
, sidePanelState
, sidePanelState
, tabType: TabPairing TabDocs
, tabType: TabPairing TabDocs
, totalRecords
, totalRecords
, yearFilter: Nothing
}
}
...
...
src/Gargantext/Components/Nodes/Corpus/Types.purs
View file @
5b68c602
...
@@ -63,17 +63,3 @@ getCorpusInfo as = case List.head (List.filter isJSON as) of
...
@@ -63,17 +63,3 @@ getCorpusInfo as = case List.head (List.filter isJSON as) of
, authors:""
, authors:""
, totalRecords: 0
, totalRecords: 0
}
}
----
type CorpusFilters =
( year :: T.Box (Maybe String) -- "YYYY"
)
defaultCorpusFilters :: R.Hooks (Record CorpusFilters)
defaultCorpusFilters = do
year <- T.useBox Nothing
pure
{ year
}
src/Gargantext/Components/Nodes/Texts.purs
View file @
5b68c602
...
@@ -2,19 +2,22 @@ module Gargantext.Components.Nodes.Texts where
...
@@ -2,19 +2,22 @@ module Gargantext.Components.Nodes.Texts where
import Gargantext.Prelude
import Gargantext.Prelude
import DOM.Simple.Console (log
, log
2)
import DOM.Simple.Console (log2)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..))
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (launchAff_)
import Effect.Aff (launchAff_)
import Gargantext.Components.Charts.Options.Type (MouseEvent)
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.DocsTable.Types (Year)
import Gargantext.Components.NgramsTable.Loader (clearCache)
import Gargantext.Components.NgramsTable.Loader (clearCache)
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo)
import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo)
import Gargantext.Components.Nodes.Corpus.Document as D
import Gargantext.Components.Nodes.Corpus.Document as D
import Gargantext.Components.Nodes.Corpus.Types (CorpusData, CorpusInfo(..), Hyperdata(..),
CorpusFilters, defaultCorpusFilters,
getCorpusInfo)
import Gargantext.Components.Nodes.Corpus.Types (CorpusData, CorpusInfo(..), Hyperdata(..), getCorpusInfo)
import Gargantext.Components.Nodes.Lists.Types as LT
import Gargantext.Components.Nodes.Lists.Types as LT
import Gargantext.Components.Nodes.Texts.Types as TT
import Gargantext.Components.Nodes.Texts.Types as TT
import Gargantext.Components.Tab as Tab
import Gargantext.Components.Tab as Tab
...
@@ -82,10 +85,13 @@ textsLayoutWithKeyCpt = here.component "textsLayoutWithKey" cpt
...
@@ -82,10 +85,13 @@ textsLayoutWithKeyCpt = here.component "textsLayoutWithKey" cpt
cacheState <- T.useBox $ getCacheState LT.CacheOff session nodeId
cacheState <- T.useBox $ getCacheState LT.CacheOff session nodeId
cacheState' <- T.useLive T.unequal cacheState
cacheState' <- T.useLive T.unequal cacheState
corpusFilters <- defaultCorpusFilters
yearFilterBox <- T.useBox (Nothing :: Maybe Year)
yearFilter <- T.useLive T.unequal yearFilterBox
R.useEffectOnce' do
R.useEffect1' yearFilter $ log2 "filter" yearFilter
T.listen (\{ new } -> log2 "filter" new) corpusFilters.year
let onClick = Just \{ name } -> T.write_ (Just name) yearFilterBox
R.useEffectOnce' $ do
R.useEffectOnce' $ do
T.listen (\{ new } -> afterCacheStateChange new) cacheState
T.listen (\{ new } -> afterCacheStateChange new) cacheState
...
@@ -111,7 +117,8 @@ textsLayoutWithKeyCpt = here.component "textsLayoutWithKey" cpt
...
@@ -111,7 +117,8 @@ textsLayoutWithKeyCpt = here.component "textsLayoutWithKey" cpt
, session
, session
, sidePanel
, sidePanel
, sidePanelState
, sidePanelState
, corpusFilters
, onClick
, yearFilter
}
}
]
]
where
where
...
@@ -138,11 +145,12 @@ type TabsProps =
...
@@ -138,11 +145,12 @@ type TabsProps =
( cacheState :: T.Box LT.CacheState
( cacheState :: T.Box LT.CacheState
, corpusData :: CorpusData
, corpusData :: CorpusData
, corpusId :: NodeID
, corpusId :: NodeID
, corpusFilters :: Record CorpusFilters
, frontends :: Frontends
, frontends :: Frontends
, session :: Session
, session :: Session
, sidePanel :: T.Box (Maybe (Record TT.SidePanel))
, sidePanel :: T.Box (Maybe (Record TT.SidePanel))
, sidePanelState :: T.Box SidePanelState
, sidePanelState :: T.Box SidePanelState
, onClick :: Maybe (MouseEvent -> Effect Unit)
, yearFilter :: Maybe Year
)
)
tabs :: Record TabsProps -> R.Element
tabs :: Record TabsProps -> R.Element
...
@@ -151,9 +159,9 @@ tabs props = R.createElement tabsCpt props []
...
@@ -151,9 +159,9 @@ tabs props = R.createElement tabsCpt props []
tabsCpt :: R.Component TabsProps
tabsCpt :: R.Component TabsProps
tabsCpt = here.component "tabs" cpt
tabsCpt = here.component "tabs" cpt
where
where
cpt { cacheState, corpusId, corpusData, frontends, session, sidePanel, sidePanelState, corpusFilters } _ = do
cpt { cacheState, corpusId, corpusData, frontends, session, sidePanel, sidePanelState, onClick, yearFilter } _ = do
let path = initialPath
let path = initialPath
let onClick = Just \{ name } -> T.write_ (Just name) (corpusFilters.year)
activeTab <- T.useBox 0
activeTab <- T.useBox 0
...
@@ -162,9 +170,9 @@ tabsCpt = here.component "tabs" cpt
...
@@ -162,9 +170,9 @@ tabsCpt = here.component "tabs" cpt
, tabs: [
, tabs: [
"Documents" /\ R.fragment [
"Documents" /\ R.fragment [
histo { path, session, onClick }
histo { path, session, onClick }
, docView' path TabDocs
, docView' path
yearFilter
TabDocs
]
]
, "Trash" /\ docView' path TabTrash
, "Trash" /\ docView' path
yearFilter
TabTrash
-- , "More like fav" /\ docView' path TabMoreLikeFav
-- , "More like fav" /\ docView' path TabMoreLikeFav
-- , "More like trash" /\ docView' path TabMoreLikeTrash
-- , "More like trash" /\ docView' path TabMoreLikeTrash
]
]
...
@@ -175,7 +183,7 @@ tabsCpt = here.component "tabs" cpt
...
@@ -175,7 +183,7 @@ tabsCpt = here.component "tabs" cpt
, listId: corpusData.defaultListId
, listId: corpusData.defaultListId
, limit: Nothing
, limit: Nothing
, tabType: TabCorpus TabDocs }
, tabType: TabCorpus TabDocs }
docView' path tabType = docView { cacheState
docView' path
yearFilter
tabType = docView { cacheState
, corpusData
, corpusData
, corpusId
, corpusId
, frontends
, frontends
...
@@ -185,6 +193,7 @@ tabsCpt = here.component "tabs" cpt
...
@@ -185,6 +193,7 @@ tabsCpt = here.component "tabs" cpt
, tabType
, tabType
, sidePanel
, sidePanel
, sidePanelState
, sidePanelState
, yearFilter
} []
} []
type DocViewProps a = (
type DocViewProps a = (
...
@@ -198,6 +207,7 @@ type DocViewProps a = (
...
@@ -198,6 +207,7 @@ type DocViewProps a = (
, tabType :: TabSubType a
, tabType :: TabSubType a
, sidePanel :: T.Box (Maybe (Record TT.SidePanel))
, sidePanel :: T.Box (Maybe (Record TT.SidePanel))
, sidePanelState :: T.Box SidePanelState
, sidePanelState :: T.Box SidePanelState
, yearFilter :: Maybe Year
)
)
docView :: forall a. R2.Component (DocViewProps a)
docView :: forall a. R2.Component (DocViewProps a)
...
@@ -217,7 +227,9 @@ docViewLayoutRec { cacheState
...
@@ -217,7 +227,9 @@ docViewLayoutRec { cacheState
, session
, session
, tabType: TabDocs
, tabType: TabDocs
, sidePanel
, sidePanel
, sidePanelState } =
, sidePanelState
, yearFilter
} =
{ cacheState
{ cacheState
, chart : H.div {} []
, chart : H.div {} []
, frontends
, frontends
...
@@ -231,6 +243,7 @@ docViewLayoutRec { cacheState
...
@@ -231,6 +243,7 @@ docViewLayoutRec { cacheState
, sidePanelState
, sidePanelState
, tabType: TabCorpus TabDocs
, tabType: TabCorpus TabDocs
, totalRecords: 4737
, totalRecords: 4737
, yearFilter
}
}
docViewLayoutRec { cacheState
docViewLayoutRec { cacheState
, corpusId
, corpusId
...
@@ -239,7 +252,9 @@ docViewLayoutRec { cacheState
...
@@ -239,7 +252,9 @@ docViewLayoutRec { cacheState
, session
, session
, tabType: TabMoreLikeFav
, tabType: TabMoreLikeFav
, sidePanel
, sidePanel
, sidePanelState } =
, sidePanelState
, yearFilter
} =
{ cacheState
{ cacheState
, chart : H.div {} []
, chart : H.div {} []
, frontends
, frontends
...
@@ -253,6 +268,7 @@ docViewLayoutRec { cacheState
...
@@ -253,6 +268,7 @@ docViewLayoutRec { cacheState
, sidePanelState
, sidePanelState
, tabType: TabCorpus TabMoreLikeFav
, tabType: TabCorpus TabMoreLikeFav
, totalRecords: 4737
, totalRecords: 4737
, yearFilter
}
}
docViewLayoutRec { cacheState
docViewLayoutRec { cacheState
, corpusId
, corpusId
...
@@ -261,7 +277,9 @@ docViewLayoutRec { cacheState
...
@@ -261,7 +277,9 @@ docViewLayoutRec { cacheState
, session
, session
, tabType: TabMoreLikeTrash
, tabType: TabMoreLikeTrash
, sidePanel
, sidePanel
, sidePanelState } =
, sidePanelState
, yearFilter
} =
{ cacheState
{ cacheState
, chart : H.div {} []
, chart : H.div {} []
, frontends
, frontends
...
@@ -275,6 +293,7 @@ docViewLayoutRec { cacheState
...
@@ -275,6 +293,7 @@ docViewLayoutRec { cacheState
, sidePanelState
, sidePanelState
, tabType: TabCorpus TabMoreLikeTrash
, tabType: TabCorpus TabMoreLikeTrash
, totalRecords: 4737
, totalRecords: 4737
, yearFilter
}
}
docViewLayoutRec { cacheState
docViewLayoutRec { cacheState
, corpusId
, corpusId
...
@@ -283,7 +302,9 @@ docViewLayoutRec { cacheState
...
@@ -283,7 +302,9 @@ docViewLayoutRec { cacheState
, session
, session
, tabType: TabTrash
, tabType: TabTrash
, sidePanel
, sidePanel
, sidePanelState } =
, sidePanelState
, yearFilter
} =
{ cacheState
{ cacheState
, chart : H.div {} []
, chart : H.div {} []
, frontends
, frontends
...
@@ -297,6 +318,7 @@ docViewLayoutRec { cacheState
...
@@ -297,6 +318,7 @@ docViewLayoutRec { cacheState
, sidePanelState
, sidePanelState
, tabType: TabCorpus TabTrash
, tabType: TabCorpus TabTrash
, totalRecords: 4737
, totalRecords: 4737
, yearFilter
}
}
-- DUMMY
-- DUMMY
docViewLayoutRec { cacheState
docViewLayoutRec { cacheState
...
@@ -306,7 +328,9 @@ docViewLayoutRec { cacheState
...
@@ -306,7 +328,9 @@ docViewLayoutRec { cacheState
, session
, session
, tabType
, tabType
, sidePanel
, sidePanel
, sidePanelState } =
, sidePanelState
, yearFilter
} =
{ cacheState
{ cacheState
, chart : H.div {} []
, chart : H.div {} []
, frontends
, frontends
...
@@ -320,6 +344,7 @@ docViewLayoutRec { cacheState
...
@@ -320,6 +344,7 @@ docViewLayoutRec { cacheState
, sidePanelState
, sidePanelState
, tabType: TabCorpus TabTrash
, tabType: TabCorpus TabTrash
, totalRecords: 4737
, totalRecords: 4737
, yearFilter
}
}
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment