Commit 35e85826 authored by James Laver's avatar James Laver

Refactor G.P.Corpus to use Reactix

parent 4e2eb894
module Gargantext.Components.Search.Ajax where
import Prelude
import Effect.Class (liftEffect)
import Effect.Aff (Aff)
import Data.Argonaut (class DecodeJson)
import DOM.Simple.Console (log2)
import Gargantext.Types (toQuery)
import Gargantext.Components.Search.Types (SearchQuery)
import Gargantext.Config.REST (post)
import Gargantext.Config (urlPlease, End(Back))
import URI.Query as Q
searchUrl :: SearchQuery -> String
searchUrl q = urlPlease Back $ "new" <> Q.print (toQuery q)
search :: forall a. DecodeJson a => SearchQuery -> Aff a
search q = do
let url = searchUrl q
liftEffect $ log2 "url:" url
post (searchUrl q) q
module Gargantext.Components.Search.SearchField module Gargantext.Components.Search.SearchField
( Search, Props, searchField, searchFieldComponent )where ( Search, Props, searchField, searchFieldComponent )where
import Prelude hiding (div) import Prelude (bind, const, identity, pure, show, ($), (/=), (<$>), (||))
import Data.Maybe ( Maybe(..), maybe ) import Data.Maybe ( Maybe(..), maybe )
import Data.Tuple ( fst ) import Data.Tuple ( fst )
import Data.Tuple.Nested ( (/\) ) import Data.Tuple.Nested ( (/\) )
import Effect ( Effect )
import Effect.Uncurried (mkEffectFn1) import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..)) import FFI.Simple ((..))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML (text, button, div, input, option, form, span, ul, li, a) import Reactix.DOM.HTML as HTML
import Reactix.DOM.HTML (text, button, div, input, span, ul, li, a)
import Gargantext.Components.Search.Types (Database) import Gargantext.Components.Search.Types (Database)
select
:: forall props
. R.IsComponent String props (Array R.Element)
=> Record props -> Array R.Element -> R.Element
select = R.createElement "select" select = R.createElement "select"
type Search = { database :: Maybe Database, term :: String } type Search = { database :: Maybe Database, term :: String }
......
module Gargantext.Components.Search.Types where module Gargantext.Components.Search.Types where
import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>), encodeJson) import Data.Argonaut (class EncodeJson, class DecodeJson, jsonEmptyObject, (:=), (~>), encodeJson)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq) import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
...@@ -9,14 +9,13 @@ import Data.Newtype (class Newtype) ...@@ -9,14 +9,13 @@ import Data.Newtype (class Newtype)
import Data.Tuple (Tuple) import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Types (class ToQuery) import Gargantext.Types (class ToQuery, toQuery)
import Gargantext.Config (endConfigStateful, End(..), NodeType(..), Path(..), toUrl) import Gargantext.Config (Ends, NodeType(..), class Path, PathType(..), BackendRoute(..), url)
import Gargantext.Config.REST (post, put) import Gargantext.Config.REST (post, put)
import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Utils (id) import Gargantext.Utils (id)
import URI.Extra.QueryPairs as QP import URI.Extra.QueryPairs as QP
import URI.Query as Q
allDatabases :: Array Database allDatabases :: Array Database
allDatabases = [All, PubMed allDatabases = [All, PubMed
...@@ -109,6 +108,10 @@ defaultSearchQuery = SearchQuery ...@@ -109,6 +108,10 @@ defaultSearchQuery = SearchQuery
, limit: Nothing , limit: Nothing
, order: Nothing } , order: Nothing }
instance pathSearchQuery :: Path SearchQuery where
pathType _ = BackendPath
path q = "new" <> Q.print (toQuery q)
instance searchQueryToQuery :: ToQuery SearchQuery where instance searchQueryToQuery :: ToQuery SearchQuery where
toQuery (SearchQuery {offset, limit, order}) = toQuery (SearchQuery {offset, limit, order}) =
QP.print id id $ QP.QueryPairs $ QP.print id id $ QP.QueryPairs $
...@@ -168,7 +171,11 @@ instance encodeJsonCategoryQuery :: EncodeJson CategoryQuery where ...@@ -168,7 +171,11 @@ instance encodeJsonCategoryQuery :: EncodeJson CategoryQuery where
~> jsonEmptyObject ~> jsonEmptyObject
categoryUrl :: Ends -> Int -> String categoryUrl :: Ends -> Int -> String
categoryUrl ends nodeId = url ends (NodeAPI Node (Just nodeId)) <> "/category" categoryUrl ends nodeId = url ends (NodeAPI Node $ Just nodeId) <> "/category"
putCategories :: Ends -> Int -> CategoryQuery -> Aff (Array Int) putCategories :: Ends -> Int -> CategoryQuery -> Aff (Array Int)
putCategories = put <<< categoryUrl putCategories ends nodeId = put $ categoryUrl ends nodeId
performSearch :: forall a. DecodeJson a => Ends -> SearchQuery -> Aff a
performSearch ends q = post (url ends q) q
...@@ -2,20 +2,16 @@ module Gargantext.Pages.Corpus where ...@@ -2,20 +2,16 @@ module Gargantext.Pages.Corpus where
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Thermite (Spec) import Gargantext.Config (Ends)
--------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..), HyperdataList)
import Gargantext.Components.Loader2 (useLoader)
import Gargantext.Components.Table as Table
import Gargantext.Config.REST (get)
import Gargantext.Pages.Texts.Tabs.Types (CorpusData, CorpusInfo(..))
import Gargantext.Pages.Texts.Tabs.Specs (elt) as Tabs
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
------------------------------------------------------------------------ type Props = ( nodeId :: Int, ends :: Ends )
layout :: Spec {} {nodeId :: Int} Void
layout = R2.elSpec $ R.hooksComponent "CorpusLoader" cpt corpusLayout :: Record Props -> R.Element
corpusLayout props = R.createElement corpusLayoutCpt props []
corpusLayoutCpt :: R.Component Props
corpusLayoutCpt = R.staticComponent "G.P.Corpus.corpusLayout" cpt
where where
cpt {nodeId} _children = do cpt {nodeId} _children = do
pure $ H.div {} [ H.h1 {} [H.text "Corpus Description"] pure $ H.div {} [ H.h1 {} [H.text "Corpus Description"]
......
...@@ -8,51 +8,52 @@ import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', ...@@ -8,51 +8,52 @@ import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis',
import Gargantext.Components.Charts.Options.Data import Gargantext.Components.Charts.Options.Data
import Gargantext.Components.Charts.Options.Series import Gargantext.Components.Charts.Options.Series
import Data.Int (toNumber) import Data.Int (toNumber)
import React.DOM (div, h1, text)
import React.DOM.Props (className) import React.DOM.Props (className)
import Reactix as R
import Reactix.DOM.HTML as H
import Thermite (Render, Spec, simpleSpec, defaultPerformAction) import Thermite (Render, Spec, simpleSpec, defaultPerformAction)
render :: Render {} {} Void dashboardLayout :: {} -> R.Element
render dispatch _ state _ = [ dashboardLayout props = R.createElement dashboardLayoutCpt props []
h1 [] [text "IMT DashBoard"]
, div [className "row"] [ div [className "col-md-9 content"] [chart globalPublis] dashboardLayoutCpt :: R.Component ()
, div [className "col-md-3 content"] [chart naturePublis] dashboardLayoutCpt = R.staticComponent "G.P.Corpus.Dashboard.dashboardLayout" cpt
] where
, chart distriBySchool cpt _ _ =
, div [className "row"] (map (\school -> div [className "col-md-4 content"] [chart $ focus school]) R.fragment
[ "Télécom Bretagne", "Mines Nantes", "Eurecom"] [ H.h1 {} [ H.text "IMT DashBoard" ]
) , H.div {className: "row"}
, chart scatterEx [ H.div {className: "col-md-9 content"} [ chart globalPublis ]
, chart sankeyEx , H.div {className: "col-md-3 content"} [ chart naturePublis ] ]
, chart treeMapEx , chart distriBySchool
, chart treeEx , H.div {className: "row"} (aSchool <$> schools)
] , chart scatterEx
where , chart sankeyEx
myData = [seriesBarD1 {name: "Bar Data"} , chart treeMapEx
[ dataSerie {name: "val1", value: 50.0} , chart treeEx ]
, dataSerie {name: "val2", value: 70.0} aSchool school = H.div {className: "col-md-4 content"} [ chart $ focus school ]
, dataSerie {name: "val3", value: 80.0} schools = [ "Télécom Bretagne", "Mines Nantes", "Eurecom" ]
] myData =
] [seriesBarD1 {name: "Bar Data"}
[ dataSerie {name: "val1", value: 50.0}
focus :: String -> Options , dataSerie {name: "val2", value: 70.0}
focus school = Options , dataSerie {name: "val3", value: 80.0} ] ]
{ mainTitle : "Focus " <> school focus :: String -> Options
, subTitle : "Total scientific publications" focus school =
, xAxis : xAxis' ["2015", "2016", "2017"] Options
, yAxis : yAxis' { position: "left" { mainTitle : "Focus " <> school
, show: false , subTitle : "Total scientific publications"
, min : 0 , xAxis : xAxis' ["2015", "2016", "2017"]
} , yAxis : yAxis' { position: "left", show: false, min : 0 }
, series : myData , series : myData
, addZoom : false , addZoom : false
, tooltip : tooltipTriggerAxis -- Necessary? , tooltip : tooltipTriggerAxis } -- Necessary?
}
----------------------------------------------------------------------------------------------------------- -----------------------------------------------------------------------------------------------------------
naturePublis_x :: Array String naturePublis_x :: Array String
naturePublis_x = ["Com","Articles","Thèses","Reports"] naturePublis_x = ["Com","Articles","Thèses","Reports"]
naturePublis_y' :: Array Int naturePublis_y' :: Array Int
naturePublis_y' = [23901,17417,1188,1176] naturePublis_y' = [23901,17417,1188,1176]
...@@ -130,7 +131,7 @@ sankeyEx = Options ...@@ -130,7 +131,7 @@ sankeyEx = Options
[ seriesSankey [ seriesSankey
{ "data": { "data":
[ {name : "a"}, {name : "b"} [ {name : "a"}, {name : "b"}
, {name:"c"}, {name:"d"} ] , {name:"c"}, {name:"d"} ]
, links: , links:
[ {source : "a", target : "b", value :2.0} [ {source : "a", target : "b", value :2.0}
, {source : "a", target : "c", value :1.0} , {source : "a", target : "c", value :1.0}
...@@ -145,49 +146,46 @@ sankeyEx = Options ...@@ -145,49 +146,46 @@ sankeyEx = Options
} }
treeData :: Array TreeNode treeData :: Array TreeNode
treeData = [ treeNode "nodeA" 10 [ treeNode "nodeAa" 4 [] treeData =
, treeNode "nodeAb" 5 [] [ treeNode "nodeA" 10
, treeNode "nodeAc" 1 [ treeNode "nodeAca" 5 [] [ treeNode "nodeAa" 4 []
, treeNode "nodeAcb" 5 [] , treeNode "nodeAb" 5 []
] , treeNode "nodeAc" 1
] [ treeNode "nodeAca" 5 []
, treeNode "nodeB" 20 [ treeNode "nodeBa" 20 [ treeNode "nodeBa1" 20 [] ]] , treeNode "nodeAcb" 5 [] ] ]
, treeNode "nodeC" 20 [ treeNode "nodeCa" 20 [ treeNode "nodeCa1" 10 [] , treeNode "nodeB" 20
, treeNode "nodeCa2" 10 [] [ treeNode "nodeBa" 20
] [ treeNode "nodeBa1" 20 [] ]]
] , treeNode "nodeC" 20
, treeNode "nodeD" 20 [ treeNode "nodeDa" 20 [ treeNode "nodeDa1" 2 [] [ treeNode "nodeCa" 20
, treeNode "nodeDa2" 2 [] [ treeNode "nodeCa1" 10 []
, treeNode "nodeDa3" 2 [] , treeNode "nodeCa2" 10 [] ]
, treeNode "nodeDa4" 2 [] , treeNode "nodeD" 20
, treeNode "nodeDa5" 2 [] [ treeNode "nodeDa" 20
, treeNode "nodeDa6" 2 [] [ treeNode "nodeDa1" 2 []
, treeNode "nodeDa7" 2 [] , treeNode "nodeDa2" 2 []
, treeNode "nodeDa8" 2 [] , treeNode "nodeDa3" 2 []
, treeNode "nodeDa9" 2 [] , treeNode "nodeDa4" 2 []
, treeNode "nodeDa10" 2 [] , treeNode "nodeDa5" 2 []
] , treeNode "nodeDa6" 2 []
] , treeNode "nodeDa7" 2 []
] , treeNode "nodeDa8" 2 []
, treeNode "nodeDa9" 2 []
, treeNode "nodeDa10" 2 [] ]]]]
treeData' :: Array TreeNode treeData' :: Array TreeNode
treeData' = [ treeNode "nodeA" 10 [ treeLeaf "nodeAa" 4 treeData' =
, treeLeaf "nodeAb" 5 [ treeNode "nodeA" 10
, treeNode "nodeAc" 1 [ treeLeaf "nodeAca" 5 [ treeLeaf "nodeAa" 4
, treeLeaf "nodeAcb" 5 , treeLeaf "nodeAb" 5
] , treeNode "nodeAc" 1 [ treeLeaf "nodeAca" 5, treeLeaf "nodeAcb" 5 ]]
, treeNode "nodeB" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]] , treeNode "nodeB" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]]
, treeNode "nodeC" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]] , treeNode "nodeC" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]]
, treeNode "nodeD" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]] , treeNode "nodeD" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]]
, treeNode "nodeE" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]] , treeNode "nodeE" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]]
, treeNode "nodeF" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]] , treeNode "nodeF" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]]
, treeNode "nodeG" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]] , treeNode "nodeG" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]]
, treeNode "nodeH" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]] , treeNode "nodeH" 20 [ treeNode "nodeBa" 20 [ treeLeaf "nodeBa1" 20]]]
]
]
treeMapEx :: Options treeMapEx :: Options
treeMapEx = Options treeMapEx = Options
...@@ -211,5 +209,3 @@ treeEx = Options ...@@ -211,5 +209,3 @@ treeEx = Options
, tooltip : tooltipTriggerAxis -- Necessary? , tooltip : tooltipTriggerAxis -- Necessary?
} }
layoutDashboard :: Spec {} {} Void
layoutDashboard = simpleSpec defaultPerformAction render
...@@ -9,10 +9,11 @@ import React (ReactClass, Children) ...@@ -9,10 +9,11 @@ import React (ReactClass, Children)
import React.DOM (div, h4, li, p, span, text, ul) import React.DOM (div, h4, li, p, span, text, ul)
import React.DOM.Props (className) import React.DOM.Props (className)
import Reactix as R import Reactix as R
import Thermite (PerformAction, Render, Spec, simpleSpec, cmapProps, createClass) import Thermite (PerformAction, Render, Spec, simpleSpec, createClass)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Config (toUrl, endConfigStateful, NodeType(..), End(..), TabSubType(..), TabType(..), CTabNgramType(..), CTabNgramType(..)) import Gargantext.Config
( NodeType(..), Ends, TabSubType(..), TabType(..), CTabNgramType(..), BackendRoute(..), url )
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Components.AutoUpdate (autoUpdateElt) import Gargantext.Components.AutoUpdate (autoUpdateElt)
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
...@@ -28,19 +29,23 @@ type NodeDocument = NodePoly Document ...@@ -28,19 +29,23 @@ type NodeDocument = NodePoly Document
type LoadedData = type LoadedData =
{ document :: NodeDocument { document :: NodeDocument
, ngramsTable :: VersionedNgramsTable } , ngramsTable :: VersionedNgramsTable
}
type Props = type Props =
{ loaded :: LoadedData { loaded :: LoadedData
, path :: DocPath , path :: DocPath
, ends :: Ends
} }
-- This is a subpart of NgramsTable.State. -- This is a subpart of NgramsTable.State.
type State = CoreState () type State = CoreState ()
initialState :: forall props others initialState
. { loaded :: { ngramsTable :: VersionedNgramsTable | others } | props } :: forall props others
-> State . { loaded :: { ngramsTable :: VersionedNgramsTable | others }
| props }
-> State
initialState {loaded: {ngramsTable: Versioned {version}}} = initialState {loaded: {ngramsTable: Versioned {version}}} =
{ ngramsTablePatch: mempty { ngramsTablePatch: mempty
, ngramsVersion: version , ngramsVersion: version
...@@ -278,15 +283,15 @@ docViewSpec :: Spec State Props Action ...@@ -278,15 +283,15 @@ docViewSpec :: Spec State Props Action
docViewSpec = simpleSpec performAction render docViewSpec = simpleSpec performAction render
where where
performAction :: PerformAction State Props Action performAction :: PerformAction State Props Action
performAction Refresh {path: {nodeId, listIds, tabType}} {ngramsVersion} = do performAction Refresh {path: {nodeId, listIds, tabType}, ends} {ngramsVersion} = do
commitPatch {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: mempty}) commitPatch ends {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: mempty})
performAction (SetTermListItem n pl) {path: {nodeId, listIds, tabType}} {ngramsVersion} = performAction (SetTermListItem n pl) {path: {nodeId, listIds, tabType}, ends} {ngramsVersion} =
commitPatch {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: pt}) commitPatch ends {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: pt})
where where
pe = NgramsPatch { patch_list: pl, patch_children: mempty } pe = NgramsPatch { patch_list: pl, patch_children: mempty }
pt = singletonNgramsTablePatch CTabTerms n pe pt = singletonNgramsTablePatch CTabTerms n pe
performAction (AddNewNgram ngram termList) {path: {nodeId, listIds, tabType}} {ngramsVersion} = performAction (AddNewNgram ngram termList) {path: {nodeId, listIds, tabType},ends} {ngramsVersion} =
commitPatch {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: pt}) commitPatch ends {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: pt})
where where
pt = addNewNgram CTabTerms ngram termList pt = addNewNgram CTabTerms ngram termList
...@@ -334,32 +339,40 @@ docViewSpec = simpleSpec performAction render ...@@ -334,32 +339,40 @@ docViewSpec = simpleSpec performAction render
badge s = span [className "badge badge-default badge-pill"] [text s] badge s = span [className "badge badge-default badge-pill"] [text s]
NodePoly {hyperdata : Document doc} = document NodePoly {hyperdata : Document doc} = document
docViewClass :: ReactClass docViewClass
{ children :: Children :: ReactClass
, loaded :: LoadedData { ends :: Ends
, path :: DocPath , children :: Children
} , loaded :: LoadedData
, path :: DocPath }
docViewClass = createClass "DocumentView" docViewSpec initialState docViewClass = createClass "DocumentView" docViewSpec initialState
layout :: Spec {} {nodeId :: Int, listId :: Int, corpusId :: Maybe Int} Void type LayoutProps = ( ends :: Ends, nodeId :: Int, listId :: Int, corpusId :: Maybe Int )
layout =
cmapProps (\{nodeId, listId, corpusId} -> {nodeId, listIds: [listId], corpusId, tabType}) $ documentLayout :: Record LayoutProps -> R.Element
R2.elSpec $ R.hooksComponent "DocumentLoader" \path _ -> documentLayout props = R.createElement documentLayoutCpt props []
useLoader path loadData $ \props ->
R2.createElement' docViewClass props [] documentLayoutCpt :: R.Component LayoutProps
documentLayoutCpt = R.hooksComponent "G.P.Corpus.Document.documentLayout" cpt
where where
tabType = TabDocument (TabNgramType CTabTerms) cpt {ends, nodeId, listId, corpusId} _ = do
useLoader path (loadData ends) $ \loaded ->
R2.createElement' docViewClass {ends, path, loaded} []
where
tabType = TabDocument (TabNgramType CTabTerms)
path = {nodeId, listIds: [listId], corpusId, tabType}
------------------------------------------------------------------------ ------------------------------------------------------------------------
loadDocument :: Int -> Aff NodeDocument loadDocument :: Ends -> Int -> Aff NodeDocument
loadDocument = get <<< toUrl endConfigStateful Back Node <<< Just loadDocument ends = get <<< url ends <<< NodeAPI Node <<< Just
loadData :: DocPath -> Aff LoadedData loadData :: Ends -> DocPath -> Aff LoadedData
loadData {nodeId, listIds, tabType} = do loadData ends {nodeId, listIds, tabType} = do
document <- loadDocument nodeId document <- loadDocument ends nodeId
ngramsTable <- loadNgramsTable ngramsTable <- loadNgramsTable ends
{ nodeId { ends
, nodeId
, listIds: listIds , listIds: listIds
, params: { offset : 0, limit : 100, orderBy: Nothing} , params: { offset : 0, limit : 100, orderBy: Nothing}
, tabType , tabType
......
This diff is collapsed.
module Gargantext.Pages.Corpus.Graph.Tabs where module Gargantext.Pages.Corpus.Graph.Tabs where
import Prelude hiding (div) import Prelude hiding (div)
import Data.Lens (view) import Data.Array (fromFoldable)
import Data.List (fromFoldable) import Data.Tuple (Tuple(..), fst)
import Data.Tuple (Tuple(..)) import Gargantext.Config (Ends)
import Gargantext.Components.GraphExplorer.Types (GraphSideCorpus(..)) import Gargantext.Components.GraphExplorer.Types (GraphSideCorpus(..))
import Gargantext.Components.FacetsTable (TextQuery, docViewSpec) import Gargantext.Components.FacetsTable (TextQuery, docView)
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import React (ReactElement, ReactClass, Children, createElement) import Reactix as R
import Thermite ( Spec, PerformAction, Render, _performAction, _render import Reactix.DOM.HTML as H
, hideState, noState, cmapProps, simpleSpec, createClass
)
type Props = { query :: TextQuery, sides :: Array GraphSideCorpus } type Props = ( ends :: Ends, query :: TextQuery, sides :: Array GraphSideCorpus )
tabsElt :: Props -> ReactElement tabs :: Record Props -> R.Element
tabsElt props = createElement tabsClass props [] tabs props = R.createElement tabsCpt props []
-- TODO no need for Children here -- TODO no need for Children here
tabsClass :: ReactClass { query :: TextQuery, sides :: Array GraphSideCorpus, children :: Children } tabsCpt :: R.Component Props
tabsClass = createClass "GraphTabs" pureTabs (const {}) tabsCpt = R.hooksComponent "G.P.Corpus.Graph.Tabs.tabs" cpt
where
pureTabs :: Spec {} Props Void cpt {ends, query, sides} _ = do
pureTabs = hideState (const {activeTab: 0}) statefulTabs active <- R.useState' 0
pure $ Tab.tabs {tabs: tabs', selected: fst active}
tab :: forall props state. TextQuery -> GraphSideCorpus -> Tuple String (Spec state props Tab.Action) where
tab query (GraphSideCorpus {corpusId: nodeId, corpusLabel, listId}) = tabs' = fromFoldable $ tab ends query <$> sides
Tuple corpusLabel $
cmapProps (const {nodeId, listId, query, chart, totalRecords: 4736, container}) $ tab :: Ends -> TextQuery -> GraphSideCorpus -> Tuple String R.Element
noState docViewSpec tab ends query (GraphSideCorpus {corpusId: nodeId, corpusLabel, listId}) =
Tuple corpusLabel (docView dvProps)
where where
dvProps = {ends, nodeId, listId, query, chart, totalRecords: 4736, container}
-- TODO totalRecords: probably need to insert a corpusLoader. -- TODO totalRecords: probably need to insert a corpusLoader.
chart = mempty chart = mempty
container = T.graphContainer {title: corpusLabel} container = T.graphContainer {title: corpusLabel}
statefulTabs :: Spec Tab.State Props Tab.Action
statefulTabs =
withProps (\{query, sides} ->
Tab.tabs identity identity $ fromFoldable $ tab query <$> sides)
-- TODO move to Thermite
-- | This function captures the props of the `Spec` as a function argument.
withProps
:: forall state props action
. (props -> Spec state props action)
-> Spec state props action
withProps f = simpleSpec performAction render
where
performAction :: PerformAction state props action
performAction a p st = view _performAction (f p) a p st
render :: Render state props action
render k p st = view _render (f p) k p st
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