Commit b7c95d60 authored by James Laver's avatar James Laver

Refactor G.P.Texts to use Reactix

parent 6ecca031
module Gargantext.Pages.Lists where module Gargantext.Pages.Lists where
import Prelude ((<<<))
import Data.Array (head) import Data.Array (head)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect.Aff (Aff, throwError) import Effect.Aff (Aff, throwError)
import Effect.Exception (error) import Effect.Exception (error)
import Reactix as R import Reactix as R
import Thermite (Spec)
-------------------------------------------------------- --------------------------------------------------------
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..), HyperdataList) import Gargantext.Components.Node (NodePoly(..), HyperdataList)
import Gargantext.Components.Table as Table import Gargantext.Components.Table as Table
import Gargantext.Config (toUrl, endConfigStateful, Path(..), NodeType(..), End(..)) import Gargantext.Config
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Pages.Lists.Tabs.Types (CorpusData, CorpusInfo(..))
import Gargantext.Pages.Lists.Tabs.Specs (elt) as Tabs
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Pages.Lists.Tabs as Tabs
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
------------------------------------------------------------------------ ------------------------------------------------------------------------
layout :: Spec {} {nodeId :: Int} Void
layout = type Props = ( nodeId :: Int, ends :: Ends )
R2.elSpec $ R.hooksComponent "ListsLoader" \{nodeId} _ ->
useLoader nodeId getCorpus $ \{loaded: corpusData} -> listsLayout :: Record Props -> R.Element
let {corpusId listsLayout props = R.createElement listsLayoutCpt props []
,corpusNode:
NodePoly { name: title listsLayoutCpt :: R.Component Props
, date: date' listsLayoutCpt = R.hooksComponent "G.P.Lists.listsLayout" cpt
, hyperdata: CorpusInfo corpus where
} cpt {nodeId, ends} _ =
} = corpusData in useLoader nodeId (getCorpus ends) $
R2.toElement $ \corpusData@{corpusId, defaultListId, corpusNode: NodePoly poly} ->
Table.renderTableHeaderLayout let { name, date, hyperdata: Tabs.CorpusInfo corpus } = poly
{ title: "Corpus " <> title { desc, query, authors: user } = corpus in
, desc: corpus.desc R.fragment
, query: corpus.query [ Table.tableHeaderLayout
, date: date' { title: "Corpus " <> name, desc, query, user, date }
, user: corpus.authors , Tabs.tabs {ends, corpusId, corpusData}]
}
<> [Tabs.elt {corpusId, corpusData}]
------------------------------------------------------------------------ ------------------------------------------------------------------------
getCorpus :: Int -> Aff CorpusData getCorpus :: Ends -> Int -> Aff Tabs.CorpusData
getCorpus listId = do getCorpus ends listId = do
-- fetch corpus via lists parentId -- fetch corpus via lists parentId
(NodePoly {parentId: corpusId} :: NodePoly {}) <- get $ toUrl endConfigStateful Back Corpus $ Just listId (NodePoly {parentId: corpusId} :: NodePoly {}) <- get nodePolyUrl
corpusNode <- get $ toUrl endConfigStateful Back Corpus $ Just corpusId corpusNode <- get $ corpusNodeUrl corpusId
defaultListIds <- get $ toUrl endConfigStateful Back (Children NodeList 0 1 Nothing) $ Just corpusId defaultListIds <- get $ defaultListIdsUrl corpusId
case (head defaultListIds :: Maybe (NodePoly HyperdataList)) of case (head defaultListIds :: Maybe (NodePoly HyperdataList)) of
Just (NodePoly { id: defaultListId }) -> Just (NodePoly { id: defaultListId }) ->
pure {corpusId, corpusNode, defaultListId} pure {corpusId, corpusNode, defaultListId}
Nothing -> Nothing ->
throwError $ error "Missing default list" throwError $ error "Missing default list"
where
nodePolyUrl = url ends (NodeAPI Corpus (Just listId))
corpusNodeUrl = url ends <<< NodeAPI Corpus <<< Just
defaultListIdsUrl = url ends <<< Children NodeList 0 1 Nothing <<< Just
module Gargantext.Pages.Lists.Tabs module Gargantext.Pages.Lists.Tabs where
( module Gargantext.Pages.Lists.Tabs.Specs
) where import Data.Argonaut (class DecodeJson, decodeJson, (.?), (.??))
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.List (fromFoldable)
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Reactix as R
import Reactix.DOM.HTML as H
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
import Gargantext.Components.Charts.Options.ECharts (chart) as ECharts
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.Loader as Loader
import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Tab as Tab
import Gargantext.Config
import Gargantext.Pages.Corpus.Chart.Histo (histo)
import Gargantext.Pages.Corpus.Chart.Metrics (metrics)
import Gargantext.Pages.Corpus.Chart.Pie (pie, bar)
import Gargantext.Pages.Corpus.Chart.Tree (tree)
import Gargantext.Utils.Reactix as R2
data Mode = Authors | Sources | Institutes | Terms
derive instance genericMode :: Generic Mode _
instance showMode :: Show Mode where
show = genericShow
derive instance eqMode :: Eq Mode
modeTabType :: Mode -> CTabNgramType
modeTabType Authors = CTabAuthors
modeTabType Sources = CTabSources
modeTabType Institutes = CTabInstitutes
modeTabType Terms = CTabTerms
type Props =
( ends :: Ends
, corpusId :: Int
, corpusData :: CorpusData )
tabs :: Record Props -> R.Element
tabs props = R.createElement tabsCpt props []
tabsCpt :: R.Component Props
tabsCpt = R.hooksComponent "CorpusTabs" cpt
where
cpt {ends, corpusId, corpusData: corpusData@{defaultListId}} _ = do
(selected /\ setSelected) <- R.useState' 0
pure $ Tab.tabs { tabs, selected }
where
tabs = [ "Sources" /\ view Sources
, "Authors" /\ view Authors
, "Institutes" /\ view Institutes
, "Terms" /\ view Terms ]
view mode = ngramsView {mode, ends, corpusId, corpusData}
type NgramsViewProps = ( mode :: Mode | Props )
ngramsView :: Record NgramsViewProps -> R.Element
ngramsView props = R.createElement ngramsViewCpt props []
ngramsViewCpt :: R.Component NgramsViewProps
ngramsViewCpt = R.staticComponent "ListsNgramsView" cpt
where
cpt {mode, ends, corpusId, corpusData: {defaultListId}} _ =
NT.mainNgramsTable
{ends, defaultListId, nodeId: corpusId, tabType, tabNgramType}
where
tabNgramType = modeTabType mode
tabType = TabCorpus (TabNgramType tabNgramType)
listId = 0 -- TODO!
path = {corpusId, tabType}
path2 = {corpusId, listId, tabType, limit: (Just 1000)} -- todo
chart Authors = pie {ends, path}
chart Sources = bar {ends, path}
chart Institutes = tree {ends, path: path2}
chart Terms = metrics {ends, path: path2}
newtype CorpusInfo =
CorpusInfo
{ title :: String
, desc :: String
, query :: String
, authors :: String
, chart :: (Maybe (Array Number))
, totalRecords :: Int }
hyperdataDefault =
CorpusInfo
{ title : "Default title"
, desc : " Default desc"
, query : " Default Query"
, authors : " Author(s): default"
, chart : Nothing
, totalRecords : 0 }
corpusInfoDefault :: NodePoly CorpusInfo
corpusInfoDefault =
NodePoly
{ id : 0
, typename : 0
, userId : 0
, parentId : 0
, name : "Default name"
, date : " Default date"
, hyperdata : hyperdataDefault }
instance decodeCorpusInfo :: DecodeJson CorpusInfo where
decodeJson json = do
obj <- decodeJson json
title <- obj .? "title"
desc <- obj .? "desc"
query <- obj .? "query"
authors <- obj .? "authors"
chart <- obj .?? "chart"
let totalRecords = 47361 -- TODO
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
type CorpusData = { corpusId :: Int
, corpusNode :: NodePoly CorpusInfo
, defaultListId :: Int}
import Gargantext.Pages.Lists.Tabs.Specs
module Gargantext.Pages.Lists.Tabs.Specs where
import Prelude hiding (div)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.List (fromFoldable)
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))
import Gargantext.Config (CTabNgramType(..), TabSubType(..), TabType(..))
import Gargantext.Pages.Lists.Tabs.Types (Props, PropsRow)
import Gargantext.Pages.Corpus.Chart.Metrics (metricsSpec)
import Gargantext.Pages.Corpus.Chart.Pie (pieSpec, barSpec)
import Gargantext.Pages.Corpus.Chart.Tree (treeSpec)
import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.Tab as Tab
import React (ReactElement, ReactClass, createElement, Children)
import Thermite (Spec, hideState, noState, cmapProps, createClass)
data Mode = Authors | Sources | Institutes | Terms
derive instance genericMode :: Generic Mode _
instance showMode :: Show Mode where
show = genericShow
derive instance eqMode :: Eq Mode
modeTabType :: Mode -> CTabNgramType
modeTabType Authors = CTabAuthors
modeTabType Sources = CTabSources
modeTabType Institutes = CTabInstitutes
modeTabType Terms = CTabTerms
elt :: Props -> ReactElement
elt props = createElement tabsClass props []
tabsClass :: ReactClass { children :: Children | PropsRow }
tabsClass = createClass "CorpusTabs" pureTabs $ const {}
pureTabs :: Spec {} Props Void
pureTabs = hideState (const {activeTab: 0}) statefulTabs
statefulTabs :: Spec Tab.State Props Tab.Action
statefulTabs =
Tab.tabs identity identity $ fromFoldable
[ Tuple "Sources" $ ngramsViewSpec {mode: Sources }
, Tuple "Authors" $ ngramsViewSpec {mode: Authors }
, Tuple "Institutes" $ ngramsViewSpec {mode: Institutes}
, Tuple "Terms" $ ngramsViewSpec {mode: Terms }
]
ngramsViewSpec :: {mode :: Mode} -> Spec Tab.State Props Tab.Action
ngramsViewSpec {mode} =
noState $ chart mode <>
cmapProps (\{corpusData: {defaultListId}, corpusId: nodeId} ->
{defaultListId, nodeId, tabType})
(NT.mainNgramsTableSpec (modeTabType mode))
where
tabType = TabCorpus $ TabNgramType $ modeTabType mode
chart Authors = cmapProps (\{corpusId} -> {corpusId, tabType}) pieSpec
chart Sources = cmapProps (\{corpusId} -> {corpusId, tabType}) barSpec
chart Institutes = cmapProps (\{corpusData: {defaultListId}, corpusId} ->
{corpusId, listId: defaultListId, tabType, limit: (Just 1000)})
treeSpec
chart Terms = cmapProps (\{corpusData: {defaultListId}, corpusId} ->
{corpusId, listId: defaultListId, tabType, limit: (Just 1000)})
-- TODO limit should be select in the chart by default it is 1000
metricsSpec
module Gargantext.Pages.Lists.Tabs.Types where
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:!))
import Data.Maybe (Maybe(..))
--------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..))
newtype CorpusInfo = CorpusInfo { title :: String
, desc :: String
, query :: String
, authors :: String
, chart :: (Maybe (Array Number))
, totalRecords :: Int
}
corpusInfoDefault :: NodePoly CorpusInfo
corpusInfoDefault = NodePoly { id : 0
, typename : 0
, userId : 0
, parentId : 0
, name : "Default name"
, date : " Default date"
, hyperdata : CorpusInfo
{ title : "Default title"
, desc : " Default desc"
, query : " Default Query"
, authors : " Author(s): default"
, chart : Nothing
, totalRecords : 0
}
}
instance decodeCorpusInfo :: DecodeJson CorpusInfo where
decodeJson json = do
obj <- decodeJson json
title <- obj .: "title"
desc <- obj .: "desc"
query <- obj .: "query"
authors <- obj .: "authors"
chart <- obj .:! "chart"
let totalRecords = 47361 -- TODO
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
type CorpusData = { corpusId :: Int
, corpusNode :: NodePoly CorpusInfo
, defaultListId :: Int}
type PropsRow = ( corpusId :: Int, corpusData :: CorpusData )
type Props = Record PropsRow
-- TODO include Gargantext.Pages.Corpus.Tabs.States
-- TODO include Gargantext.Pages.Corpus.Tabs.Actions
module Gargantext.Pages.Texts where module Gargantext.Pages.Texts where
import Prelude ((<<<))
import Data.Array (head) import Data.Array (head)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect.Aff (Aff, throwError) import Effect.Aff (Aff, throwError)
import Effect.Exception (error) import Effect.Exception (error)
import Reactix as R import Reactix as R
import Thermite (Spec)
-------------------------------------------------------- --------------------------------------------------------
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..), HyperdataList) import Gargantext.Components.Node (NodePoly(..), HyperdataList)
import Gargantext.Components.Table as Table import Gargantext.Components.Table as Table
import Gargantext.Config (toUrl, endConfigStateful, Path(..), NodeType(..), End(..)) import Gargantext.Config
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Pages.Texts.Tabs.Types (CorpusData, CorpusInfo(..))
import Gargantext.Pages.Texts.Tabs.Specs (elt) as Tabs
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Pages.Texts.Tabs (CorpusData, CorpusInfo(..))
import Gargantext.Pages.Texts.Tabs as Tabs
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
type Props = ( ends :: Ends, nodeId :: Int )
textsLayout :: Record Props -> R.Element
textsLayout props = R.createElement textsLayoutCpt props []
------------------------------------------------------------------------ ------------------------------------------------------------------------
layout :: Spec {} {nodeId :: Int} Void textsLayoutCpt :: R.Component Props
layout = textsLayoutCpt = R.hooksComponent "TextsLoader" cpt
R2.elSpec $ R.hooksComponent "TextsLoader" \{nodeId} _ -> where
useLoader nodeId getCorpus $ \{loaded: corpusData} -> cpt {nodeId,ends} _ =
let {corpusId useLoader nodeId (getCorpus ends) $
,corpusNode: \corpusData@{corpusId, corpusNode, defaultListId} ->
NodePoly { name: title let
, date: date' NodePoly { name, date, hyperdata: CorpusInfo corpus } = corpusNode
, hyperdata: CorpusInfo corpus {desc, query, authors: user} = corpus
} tabs = Tabs.tabs {ends, corpusId, corpusData}
} = corpusData in title = "Corpus " <> name
R2.toElement $ headerProps = { title, desc, query, date, user } in
Table.renderTableHeaderLayout R.fragment [Table.tableHeaderLayout headerProps, tabs]
{ title: "Corpus " <> title
, desc: corpus.desc
, query: corpus.query
, date: date'
, user: corpus.authors
}
<> [Tabs.elt {corpusId, corpusData}]
------------------------------------------------------------------------ ------------------------------------------------------------------------
getCorpus :: Int -> Aff CorpusData getCorpus :: Ends -> Int -> Aff CorpusData
getCorpus textsId = do getCorpus ends textsId = do
-- fetch corpus via texts parentId -- fetch corpus via texts parentId
(NodePoly {parentId: corpusId} :: NodePoly {}) <- get $ toUrl endConfigStateful Back Corpus $ Just textsId (NodePoly {parentId: corpusId} :: NodePoly {}) <- get nodePolyUrl
corpusNode <- get $ toUrl endConfigStateful Back Corpus $ Just corpusId corpusNode <- get $ corpusNodeUrl corpusId
defaultListIds <- get $ toUrl endConfigStateful Back (Children NodeList 0 1 Nothing) $ Just corpusId defaultListIds <- get $ defaultListIdsUrl corpusId
case (head defaultListIds :: Maybe (NodePoly HyperdataList)) of case (head defaultListIds :: Maybe (NodePoly HyperdataList)) of
Just (NodePoly { id: defaultListId }) -> Just (NodePoly { id: defaultListId }) ->
pure {corpusId, corpusNode, defaultListId} pure {corpusId, corpusNode, defaultListId}
Nothing -> Nothing ->
throwError $ error "Missing default list" throwError $ error "Missing default list"
where
nodePolyUrl = url ends $ NodeAPI NodeList (Just textsId)
corpusNodeUrl = url ends <<< NodeAPI Corpus <<< Just
defaultListIdsUrl = url ends <<< Children NodeList 0 1 Nothing <<< Just
module Gargantext.Pages.Texts.Tabs module Gargantext.Pages.Texts.Tabs where
( module Gargantext.Pages.Texts.Tabs.Specs
) where import Data.Argonaut (class DecodeJson, decodeJson, (.?), (.??))
import Data.Maybe (Maybe(..))
--------------------------------------------------------
import Gargantext.Prelude
import Prelude hiding (div)
import Data.Array as Array
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.List (fromFoldable)
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Components.Charts.Options.ECharts (chart) as ECharts
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.Loader as Loader
import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Tab as Tab
import Gargantext.Config (CTabNgramType(..), TabSubType(..), TabType(..), Ends)
import Gargantext.Pages.Corpus.Chart.Histo (histo)
import Gargantext.Utils.Reactix as R2
data Mode = MoreLikeFav | MoreLikeTrash
derive instance genericMode :: Generic Mode _
instance showMode :: Show Mode where
show = genericShow
derive instance eqMode :: Eq Mode
modeTabType :: Mode -> CTabNgramType
modeTabType MoreLikeFav = CTabAuthors -- TODO
modeTabType MoreLikeTrash = CTabSources -- TODO
type Props = ( ends :: Ends, corpusId :: Int, corpusData :: CorpusData )
tabs :: Record Props -> R.Element
tabs props = R.createElement tabsCpt props []
tabsCpt :: R.Component Props
tabsCpt = R.hooksComponent "CorpusTabs" cpt
where
cpt {ends, corpusId, corpusData} _ = do
(selected /\ setSelected) <- R.useState' 0
pure $ Tab.tabs { tabs, selected }
where
tabs = [ "Documents" /\ docs, "Trash" /\ trash
, "More like fav" /\ moreLikeFav, "More like trash" /\ moreLikeTrash ]
docView' tabType = docView { ends, corpusId, corpusData, tabType }
docs = R.fragment [ docsHisto, docView' TabDocs ]
docsHisto = histo { path, ends }
where path = { corpusId, tabType: TabCorpus TabDocs }
moreLikeFav = docView' TabMoreLikeFav
moreLikeTrash = docView' TabMoreLikeTrash
trash = docView' TabTrash
type DocViewProps a = ( ends :: Ends, corpusId :: Int, corpusData :: CorpusData, tabType :: TabSubType a )
docView :: forall a. Record (DocViewProps a) -> R.Element
docView props = R.createElement docViewCpt props []
--docViewSpec :: forall a. TabSubType a -> Props -> R.Element
docViewCpt :: forall a. R.Component (DocViewProps a)
docViewCpt = R.hooksComponent "DocViewWithCorpus" cpt
where
cpt {ends, corpusId, corpusData: {defaultListId}, tabType} _children = do
pure $ DT.docView $ params tabType
where
params :: forall a. TabSubType a -> Record DT.Props
params TabDocs =
{ nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabDocs
, totalRecords: 4737
, listId: defaultListId
, corpusId: Just corpusId
, showSearch: true
, ends }
params TabMoreLikeFav =
{ nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabMoreLikeFav
, totalRecords: 4737
, listId: defaultListId
, corpusId: Just corpusId
, showSearch: false
, ends }
params TabMoreLikeTrash =
{ nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabMoreLikeTrash
, totalRecords: 4737
, listId: defaultListId
, corpusId: Just corpusId
, showSearch: false
, ends }
params TabTrash =
{ nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabTrash
, totalRecords: 4737
, listId: defaultListId
, corpusId: Nothing
, showSearch: true
, ends }
-- DUMMY
params _ =
{ nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabTrash
, totalRecords: 4737
, listId: defaultListId
, corpusId: Nothing
, showSearch: true
, ends }
newtype CorpusInfo = CorpusInfo { title :: String
, desc :: String
, query :: String
, authors :: String
, chart :: (Maybe (Array Number))
, totalRecords :: Int
}
corpusInfoDefault :: NodePoly CorpusInfo
corpusInfoDefault = NodePoly { id : 0
, typename : 0
, userId : 0
, parentId : 0
, name : "Default name"
, date : " Default date"
, hyperdata : CorpusInfo
{ title : "Default title"
, desc : " Default desc"
, query : " Default Query"
, authors : " Author(s): default"
, chart : Nothing
, totalRecords : 0
}
}
instance decodeCorpusInfo :: DecodeJson CorpusInfo where
decodeJson json = do
obj <- decodeJson json
title <- obj .? "title"
desc <- obj .? "desc"
query <- obj .? "query"
authors <- obj .? "authors"
chart <- obj .?? "chart"
let totalRecords = 47361 -- TODO
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
type CorpusData = { corpusId :: Int
, corpusNode :: NodePoly CorpusInfo
, defaultListId :: Int}
import Gargantext.Pages.Texts.Tabs.Specs
module Gargantext.Pages.Texts.Tabs.Specs where
import Prelude hiding (div)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.List (fromFoldable)
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))
import Gargantext.Config (CTabNgramType(..), TabSubType(..), TabType(..))
import Gargantext.Pages.Texts.Tabs.Types (Props, PropsRow)
import Gargantext.Pages.Corpus.Chart.Histo (histoSpec)
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.Tab as Tab
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import React (ReactElement, ReactClass, createElement, Children)
import Thermite (Spec, hideState, noState, cmapProps, createClass)
data Mode = MoreLikeFav | MoreLikeTrash
derive instance genericMode :: Generic Mode _
instance showMode :: Show Mode where
show = genericShow
derive instance eqMode :: Eq Mode
modeTabType :: Mode -> CTabNgramType
modeTabType MoreLikeFav = CTabAuthors -- TODO
modeTabType MoreLikeTrash = CTabSources -- TODO
elt :: Props -> ReactElement
elt props = createElement tabsClass props []
tabsClass :: ReactClass { children :: Children | PropsRow }
tabsClass = createClass "CorpusTabs" pureTabs $ const {}
pureTabs :: Spec {} Props Void
pureTabs = hideState (const {activeTab: 0}) statefulTabs
statefulTabs :: Spec Tab.State Props Tab.Action
statefulTabs =
Tab.tabs identity identity $ fromFoldable
[ Tuple "Documents" $ docs
, Tuple "Trash" $ trash
, Tuple "More like fav" $ moreLikeFav
, Tuple "More like trash" $ moreLikeTrash
]
where
-- TODO totalRecords
docs = noState ( cmapProps (\{corpusId} -> {corpusId, tabType: TabCorpus TabDocs}) histoSpec
<>
(cmapProps identity $ docViewSpec TabDocs)
)
moreLikeFav = noState $ cmapProps identity $ docViewSpec TabMoreLikeFav
moreLikeTrash = noState $ cmapProps identity $ docViewSpec TabMoreLikeTrash
trash = noState $ cmapProps identity $ docViewSpec TabTrash
--docViewSpec :: forall a. TabSubType a -> Props -> R.Element
docViewSpec :: forall a. TabSubType a -> Spec {} Props Void
docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
where
cpt {corpusId, corpusData: {defaultListId}} _children = do
pure $ DT.docViewSpec $ params tst
where
params :: forall b. TabSubType b -> DT.Props
params TabDocs = {
nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabDocs
, totalRecords: 4737
, listId: defaultListId
, corpusId: Just corpusId
, showSearch: true
}
params TabMoreLikeFav = {
nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabMoreLikeFav
, totalRecords: 4737
, listId: defaultListId
, corpusId: Just corpusId
, showSearch: false
}
params TabMoreLikeTrash = {
nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabMoreLikeTrash
, totalRecords: 4737
, listId: defaultListId
, corpusId: Just corpusId
, showSearch: false
}
params TabTrash = {
nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabTrash
, totalRecords: 4737
, listId: defaultListId
, corpusId: Nothing
, showSearch: true
}
-- DUMMY
params _ = {
nodeId: corpusId
-- ^ TODO merge nodeId and corpusId in DT
, chart : H.div {} []
, tabType: TabCorpus TabTrash
, totalRecords: 4737
, listId: defaultListId
, corpusId: Nothing
, showSearch: true
}
module Gargantext.Pages.Texts.Tabs.Types where
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:!))
import Data.Maybe (Maybe(..))
--------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..))
newtype CorpusInfo = CorpusInfo { title :: String
, desc :: String
, query :: String
, authors :: String
, chart :: (Maybe (Array Number))
, totalRecords :: Int
}
corpusInfoDefault :: NodePoly CorpusInfo
corpusInfoDefault = NodePoly { id : 0
, typename : 0
, userId : 0
, parentId : 0
, name : "Default name"
, date : " Default date"
, hyperdata : CorpusInfo
{ title : "Default title"
, desc : " Default desc"
, query : " Default Query"
, authors : " Author(s): default"
, chart : Nothing
, totalRecords : 0
}
}
instance decodeCorpusInfo :: DecodeJson CorpusInfo where
decodeJson json = do
obj <- decodeJson json
title <- obj .: "title"
desc <- obj .: "desc"
query <- obj .: "query"
authors <- obj .: "authors"
chart <- obj .:! "chart"
let totalRecords = 47361 -- TODO
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
type CorpusData = { corpusId :: Int
, corpusNode :: NodePoly CorpusInfo
, defaultListId :: Int}
type PropsRow = ( corpusId :: Int, corpusData :: CorpusData )
type Props = Record PropsRow
-- TODO include Gargantext.Pages.Corpus.Tabs.States
-- TODO include Gargantext.Pages.Corpus.Tabs.Actions
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