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
0
Issues
0
List
Board
Labels
Milestones
Merge Requests
0
Merge Requests
0
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
Grégoire Locqueville
purescript-gargantext
Commits
04c93526
Unverified
Commit
04c93526
authored
Oct 18, 2018
by
Nicolas Pouillard
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Add CorpusLoader React component
parent
1278c352
Changes
8
Show whitespace changes
Inline
Side-by-side
Showing
8 changed files
with
151 additions
and
124 deletions
+151
-124
Loader.purs
src/Gargantext/Components/Loader.purs
+51
-0
Corpus.purs
src/Gargantext/Pages/Corpus.purs
+41
-87
Documents.purs
src/Gargantext/Pages/Corpus/Tabs/Documents.purs
+11
-11
Types.purs
src/Gargantext/Pages/Corpus/Tabs/Types.purs
+44
-1
Layout.purs
src/Gargantext/Pages/Layout.purs
+1
-5
Actions.purs
src/Gargantext/Pages/Layout/Actions.purs
+0
-9
Specs.purs
src/Gargantext/Pages/Layout/Specs.purs
+3
-5
States.purs
src/Gargantext/Pages/Layout/States.purs
+0
-6
No files found.
src/Gargantext/Components/Loader.purs
0 → 100644
View file @
04c93526
module Gargantext.Components.Loader where
import Data.Maybe (Maybe(..))
import Data.Either (Either(..))
import Data.Traversable (traverse_)
import React as React
import React (ReactClass)
import Gargantext.Prelude
import Effect.Aff (Aff, launchAff, launchAff_, makeAff, nonCanceler, killFiber)
import Effect.Exception (error)
type InnerProps a b =
{ path :: a
, loaded :: Maybe b
, children :: React.Children
}
type Props a b = { path :: a
, component :: ReactClass (InnerProps a b)
}
createLoaderClass :: forall a b
. String
-> (a -> Aff b)
-> ReactClass (Props a b)
createLoaderClass name loader = React.component name mk
where
mk this =
pure
{ state: { loaded: Nothing, fiber: Nothing }
, componentDidMount: do
logs "componentDidMount"
{path} <- React.getProps this
fiber <- launchAff $ do
newState <- loader path
makeAff $ \cb -> do
void $ React.modifyStateWithCallback
this
(_ {loaded = Just newState})
(cb (Right unit))
pure nonCanceler
React.modifyState this (_ { fiber = Just fiber })
, componentWillUnmount: do
{fiber} <- React.getState this
traverse_ (launchAff_ <<< killFiber (error "Loader: killFiber"))
fiber
, render: do
{path, component} <- React.getProps this
{loaded} <- React.getState this
pure $ React.createElement component {path, loaded} []
}
src/Gargantext/Pages/Corpus.purs
View file @
04c93526
module Gargantext.Pages.Corpus where
module Gargantext.Pages.Corpus where
import Control.Monad.Trans.Class (lift)
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Either (Either(..))
import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism, (?~))
import Data.Lens (Lens', Prism', lens, prism)
import Data.List (fromFoldable)
import Data.Maybe (maybe)
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..))
import Effect.Aff (Aff)
import Effect.Aff (Aff)
import React as React
import React (ReactClass, ReactElement)
import React.DOM (div, h3, hr, i, p, text)
import React.DOM (div, h3, hr, i, p, text)
import React.DOM.Props (className, style)
import React.DOM.Props (className, style)
import Thermite ( Render, Spec,
PerformAction, focus, cmapProp
s
import Thermite ( Render, Spec,
createClass, defaultPerformAction, focu
s
, simpleSpec,
modifyState, noState
)
, simpleSpec,
noState
)
--------------------------------------------------------
--------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Loader as Loader
import Gargantext.Components.Loader (createLoaderClass)
import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config (toUrl, NodeType(..), End(..))
import Gargantext.Config.REST (get)
import Gargantext.Config.REST (get)
import Gargantext.Pages.Corpus.Tabs.Types as Tabs
import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo(..), corpusInfoDefault)
import Gargantext.Pages.Corpus.Tabs.States as Tabs
import Gargantext.Pages.Corpus.Tabs.Types (Props) as Tabs
import Gargantext.Pages.Corpus.Tabs.Actions as Tabs
import Gargantext.Pages.Corpus.Tabs.States (State, initialState) as Tabs
import Gargantext.Pages.Corpus.Tabs.Specs as Tabs
import Gargantext.Pages.Corpus.Tabs.Actions (Action) as Tabs
import Gargantext.Pages.Corpus.Tabs.Specs (statefulTabs) as Tabs
-------------------------------------------------------------------
-------------------------------------------------------------------
type Props = Tabs.Props
type Props = Tabs.Props
type HeaderState = { info :: Maybe (NodePoly CorpusInfo) }
type State = { tabsView :: Tabs.State
type State = { headerView :: HeaderState
, tabsView :: Tabs.State
}
}
initialState :: State
initialState :: State
initialState = { headerView : { info : Nothing }
initialState = { tabsView : Tabs.initialState
, tabsView : Tabs.initialState
}
}
------------------------------------------------------------------------
------------------------------------------------------------------------
_info :: forall a b. Lens' { info :: a | b } a
_info = lens (\s -> s.info) (\s ss -> s{info = ss})
_headerView :: forall a b. Lens' { headerView :: a | b } a
_headerView = lens (\s -> s.headerView) (\s ss -> s{headerView = ss})
_tabsView :: forall a b. Lens' { tabsView :: a | b } a
_tabsView :: forall a b. Lens' { tabsView :: a | b } a
_tabsView = lens (\s -> s.tabsView) (\s ss -> s{tabsView = ss})
_tabsView = lens (\s -> s.tabsView) (\s ss -> s{tabsView = ss})
------------------------------------------------------------------------
------------------------------------------------------------------------
data HeaderAction = Load Int
data Action
data Action
= HeaderA HeaderAction
= TabsA Tabs.Action
| TabsA Tabs.Action
_headerAction :: Prism' Action HeaderAction
_headerAction = prism HeaderA \ action ->
case action of
HeaderA haction -> Right haction
_-> Left action
_tabsAction :: Prism' Action Tabs.Action
_tabsAction :: Prism' Action Tabs.Action
_tabsAction = prism TabsA \ action ->
_tabsAction = prism TabsA \ action ->
case action of
case action of
TabsA taction -> Right taction
TabsA taction -> Right taction
_-> Left action
_loadAction :: Prism' HeaderAction Int
_loadAction = prism Load \ action ->
case action of
Load x -> Right x
-- _-> Left action
-- _-> Left action
------------------------------------------------------------------------
------------------------------------------------------------------------
newtype CorpusInfo = CorpusInfo { title :: String
layout :: Spec {} {nodeId :: Int} Void
, desc :: String
layout = simpleSpec defaultPerformAction render
, query :: String
where
, authors :: String
render :: Render {} {nodeId :: Int} Void
, chart :: (Maybe (Array Number))
render _ {nodeId} _ _ =
}
[ nodeLoader { path: nodeId
, component: createClass "Layout" layout' initialState
corpusInfoDefault :: NodePoly CorpusInfo
} ]
corpusInfoDefault = NodePoly { id : 0
, typename : 0
layout' :: Spec State Props Action
, userId : 0
layout' = noState corpusHeaderSpec
, 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
}
}
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"
pure $ CorpusInfo {title, desc, query, authors, chart}
------------------------------------------------------------------------
layout :: Spec State Props Action
layout = cmapProps (const {}) (focus _headerView _headerAction corpusHeaderSpec)
<> focus _tabsView _tabsAction Tabs.statefulTabs
<> focus _tabsView _tabsAction Tabs.statefulTabs
corpusHeaderSpec :: Spec
HeaderState {} HeaderAction
corpusHeaderSpec :: Spec
{} Props Void
corpusHeaderSpec = simpleSpec
p
erformAction render
corpusHeaderSpec = simpleSpec
defaultP
erformAction render
where
where
render :: Render
HeaderState {} HeaderAction
render :: Render
{} Props Void
render dispatch
_ state
_ =
render dispatch
{loaded} _
_ =
[ div [className "row"]
[ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text "Corpus " <> text title] ]
[ div [className "col-md-3"] [ h3 [] [text "Corpus " <> text title] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
...
@@ -143,14 +95,16 @@ corpusHeaderSpec = simpleSpec performAction render
...
@@ -143,14 +95,16 @@ corpusHeaderSpec = simpleSpec performAction render
, date: date'
, date: date'
, hyperdata : CorpusInfo corpus
, hyperdata : CorpusInfo corpus
}
}
= maybe corpusInfoDefault identity
state.info
= maybe corpusInfoDefault identity
loaded
------------------------------------------------------------------------
------------------------------------------------------------------------
performAction :: PerformAction HeaderState {} HeaderAction
performAction (Load nId) _ _ = do
node <- lift $ getNode nId
void $ modifyState $ _info ?~ node
logs $ "Node Corpus fetched."
getNode :: Int -> Aff (NodePoly CorpusInfo)
getNode :: Int -> Aff (NodePoly CorpusInfo)
getNode = get <<< toUrl Back Node
getNode = get <<< toUrl Back Node
-- MOCK getNode = const $ pure corpusInfoDefault
nodeLoaderClass :: ReactClass (Loader.Props Int (NodePoly CorpusInfo))
nodeLoaderClass = createLoaderClass "NodeLoader" getNode
nodeLoader :: Loader.Props Int (NodePoly CorpusInfo) -> ReactElement
nodeLoader = React.createLeafElement nodeLoaderClass
src/Gargantext/Pages/Corpus/Tabs/Documents.purs
View file @
04c93526
...
@@ -5,6 +5,7 @@ import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyO
...
@@ -5,6 +5,7 @@ import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyO
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.Tuple (Tuple(..))
import Data.Tuple (Tuple(..))
import Effect.Aff (Aff)
import Effect.Aff (Aff)
import React.DOM (a, br', div, input, p, text)
import React.DOM (a, br', div, input, p, text)
...
@@ -17,6 +18,8 @@ import Gargantext.Config.REST (get, post)
...
@@ -17,6 +18,8 @@ import Gargantext.Config.REST (get, post)
import Gargantext.Utils.DecodeMaybe ((.|))
import Gargantext.Utils.DecodeMaybe ((.|))
import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Components.Table as T
import Gargantext.Components.Table as T
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Pages.Corpus.Tabs.Types
import Gargantext.Pages.Corpus.Dashboard (globalPublis)
import Gargantext.Pages.Corpus.Dashboard (globalPublis)
------------------------------------------------------------------------
------------------------------------------------------------------------
-- TODO: Pagination Details are not available from the BackEnd
-- TODO: Pagination Details are not available from the BackEnd
...
@@ -26,14 +29,6 @@ import Gargantext.Pages.Corpus.Dashboard (globalPublis)
...
@@ -26,14 +29,6 @@ import Gargantext.Pages.Corpus.Dashboard (globalPublis)
-- TODO: Filter is Pending
-- TODO: Filter is Pending
-- TODO: When a pagination link is clicked, reload data.
-- TODO: When a pagination link is clicked, reload data.
type Props =
{ totalRecords :: Int
, nodeId :: Int -- /!\ When changing the pages of the Table, NodeId
-- is needed to reload Data (other solution is using
-- NodeId as a parameter
-- NP,TODO this should not be in state
}
type State = {}
type State = {}
type Action = Void
type Action = Void
...
@@ -120,7 +115,7 @@ layoutDocview :: Spec State Props Action
...
@@ -120,7 +115,7 @@ layoutDocview :: Spec State Props Action
layoutDocview = simpleSpec absurd render
layoutDocview = simpleSpec absurd render
where
where
render :: Render State Props Action
render :: Render State Props Action
render dispatch {
nodeId, totalRecords
} _ _ =
render dispatch {
path, loaded
} _ _ =
[ div [className "container1"]
[ div [className "container1"]
[ div [className "row"]
[ div [className "row"]
[ chart globalPublis
[ chart globalPublis
...
@@ -138,7 +133,12 @@ layoutDocview = simpleSpec absurd render
...
@@ -138,7 +133,12 @@ layoutDocview = simpleSpec absurd render
, "Source"
, "Source"
, "Delete"
, "Delete"
]
]
, totalRecords
, totalRecords: maybe 47361 -- TODO
identity
((\(NodePoly n) -> n.hyperdata)
>>>
(\(CorpusInfo c) -> c.totalRecords)
<$> loaded)
}
}
]
]
]
]
...
@@ -147,7 +147,7 @@ layoutDocview = simpleSpec absurd render
...
@@ -147,7 +147,7 @@ layoutDocview = simpleSpec absurd render
where
where
loadRows {offset, limit} = do
loadRows {offset, limit} = do
_ <- logs "loading documents page"
_ <- logs "loading documents page"
res <- loadPage {nodeId,offset,limit}
res <- loadPage {nodeId
: path
,offset,limit}
_ <- logs "OK: loading page documents."
_ <- logs "OK: loading page documents."
pure $
pure $
(\(DocumentsView r) ->
(\(DocumentsView r) ->
...
...
src/Gargantext/Pages/Corpus/Tabs/Types.purs
View file @
04c93526
module Gargantext.Pages.Corpus.Tabs.Types where
module Gargantext.Pages.Corpus.Tabs.Types where
type Props = {nodeId :: Int, totalRecords :: Int}
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}
-- TODO type Props = {nodeId :: Int, info :: Maybe (NodePoly CorpusInfo) }
type Props = {path :: Int, loaded :: Maybe (NodePoly CorpusInfo) }
-- TODO include Gargantext.Pages.Corpus.Tabs.States
-- TODO include Gargantext.Pages.Corpus.Tabs.States
-- TODO include Gargantext.Pages.Corpus.Tabs.Actions
-- TODO include Gargantext.Pages.Corpus.Tabs.Actions
src/Gargantext/Pages/Layout.purs
View file @
04c93526
...
@@ -6,10 +6,7 @@ import Gargantext.Pages.Layout.Actions (Action(..))
...
@@ -6,10 +6,7 @@ import Gargantext.Pages.Layout.Actions (Action(..))
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
-- import Gargantext.Pages.Corpus.Tabs as TV
-- import Gargantext.Pages.Corpus.Tabs as TV
import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Document as Document
import Gargantext.Pages.Corpus.Document as Document
import Gargantext.Pages.Corpus.Tabs.Documents as D
import Gargantext.Pages.Corpus.Tabs.Actions as TabsA
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Corpus.Graph as GE
-- import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG
-- import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG
...
@@ -39,7 +36,6 @@ dispatchAction dispatcher _ AddCorpus = do
...
@@ -39,7 +36,6 @@ dispatchAction dispatcher _ AddCorpus = do
dispatchAction dispatcher _ (Corpus n) = do
dispatchAction dispatcher _ (Corpus n) = do
dispatcher $ SetRoute $ Corpus n
dispatcher $ SetRoute $ Corpus n
dispatcher $ CorpusAction $ Corpus.HeaderA $ Corpus.Load n
dispatchAction dispatcher _ SearchView = do
dispatchAction dispatcher _ SearchView = do
dispatcher $ SetRoute SearchView
dispatcher $ SetRoute SearchView
...
...
src/Gargantext/Pages/Layout/Actions.purs
View file @
04c93526
...
@@ -13,7 +13,6 @@ import Gargantext.Components.Modals.Modal (modalShow)
...
@@ -13,7 +13,6 @@ import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Document as D
import Gargantext.Pages.Corpus.Document as D
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
...
@@ -29,7 +28,6 @@ data Action
...
@@ -29,7 +28,6 @@ data Action
| LoginA LN.Action
| LoginA LN.Action
| SetRoute Routes
| SetRoute Routes
| TreeViewA Tree.Action
| TreeViewA Tree.Action
| CorpusAction Corpus.Action
| SearchA S.Action
| SearchA S.Action
| Search String
| Search String
| AddCorpusA AC.Action
| AddCorpusA AC.Action
...
@@ -76,7 +74,6 @@ performAction Initialize _ state = void do
...
@@ -76,7 +74,6 @@ performAction Initialize _ state = void do
performAction (LoginA _) _ _ = pure unit
performAction (LoginA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (CorpusAction _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit
performAction (UserPageA _) _ _ = pure unit
performAction (UserPageA _) _ _ = pure unit
performAction (DocumentViewA _) _ _ = pure unit
performAction (DocumentViewA _) _ _ = pure unit
...
@@ -98,12 +95,6 @@ _addCorpusAction = prism AddCorpusA \action ->
...
@@ -98,12 +95,6 @@ _addCorpusAction = prism AddCorpusA \action ->
AddCorpusA caction -> Right caction
AddCorpusA caction -> Right caction
_-> Left action
_-> Left action
_corpusAction :: Prism' Action Corpus.Action
_corpusAction = prism CorpusAction \action ->
case action of
CorpusAction caction -> Right caction
_-> Left action
_searchAction :: Prism' Action S.Action
_searchAction :: Prism' Action S.Action
_searchAction = prism SearchA \action ->
_searchAction = prism SearchA \action ->
case action of
case action of
...
...
src/Gargantext/Pages/Layout/Specs.purs
View file @
04c93526
...
@@ -23,10 +23,10 @@ import Gargantext.Pages.Corpus.Dashboard as Dsh
...
@@ -23,10 +23,10 @@ import Gargantext.Pages.Corpus.Dashboard as Dsh
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG
import Gargantext.Pages.Home as L
import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _
corpusAction, _
addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction)
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState, _
corpusState, _
addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState)
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState)
import Gargantext.Router (Routes(..))
import Gargantext.Router (Routes(..))
layoutSpec :: Spec AppState {} Action
layoutSpec :: Spec AppState {} Action
...
@@ -55,9 +55,7 @@ pagesComponent s = case s.currentRoute of
...
@@ -55,9 +55,7 @@ pagesComponent s = case s.currentRoute of
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec (Folder i) = layout0 $ noState F.layoutFolder
selectSpec (Folder i) = layout0 $ noState F.layoutFolder
selectSpec (Corpus i) = layout0 $
selectSpec (Corpus i) = layout0 $ cmapProps (const {nodeId: i}) $ noState Corpus.layout
cmapProps (const {nodeId: i, totalRecords: 47361}) -- TODO
(focus _corpusState _corpusAction Corpus.layout)
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec
selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec
selectSpec (Document i) = layout0 $ focus _documentViewState _documentViewAction Annotation.docview
selectSpec (Document i) = layout0 $ focus _documentViewState _documentViewAction Annotation.docview
...
...
src/Gargantext/Pages/Layout/States.purs
View file @
04c93526
...
@@ -7,7 +7,6 @@ import Data.Maybe (Maybe(Just))
...
@@ -7,7 +7,6 @@ import Data.Maybe (Maybe(Just))
import Gargantext.Components.Login as LN
import Gargantext.Components.Login as LN
import Gargantext.Components.Tree as Tree
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Document as D
import Gargantext.Pages.Corpus.Document as D
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Tabs.Documents as DV
import Gargantext.Pages.Corpus.Tabs.Documents as DV
...
@@ -20,7 +19,6 @@ import Gargantext.Router (Routes(..))
...
@@ -20,7 +19,6 @@ import Gargantext.Router (Routes(..))
type AppState =
type AppState =
{ currentRoute :: Maybe Routes
{ currentRoute :: Maybe Routes
, loginState :: LN.State
, loginState :: LN.State
, corpus :: Corpus.State
, addCorpusState :: AC.State
, addCorpusState :: AC.State
, docViewState :: DV.State
, docViewState :: DV.State
, searchState :: S.State
, searchState :: S.State
...
@@ -38,7 +36,6 @@ type AppState =
...
@@ -38,7 +36,6 @@ type AppState =
initAppState :: AppState
initAppState :: AppState
initAppState =
initAppState =
{ currentRoute : Just Home
{ currentRoute : Just Home
, corpus : Corpus.initialState
, loginState : LN.initialState
, loginState : LN.initialState
, addCorpusState : AC.initialState
, addCorpusState : AC.initialState
, docViewState : DV.initialState
, docViewState : DV.initialState
...
@@ -61,9 +58,6 @@ _loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
...
@@ -61,9 +58,6 @@ _loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
_addCorpusState :: Lens' AppState AC.State
_addCorpusState :: Lens' AppState AC.State
_addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss})
_addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss})
_corpusState :: Lens' AppState Corpus.State
_corpusState = lens (\s -> s.corpus) (\s ss -> s{corpus = ss})
_docViewState :: Lens' AppState DV.State
_docViewState :: Lens' AppState DV.State
_docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss})
_docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss})
...
...
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