Document: refactore to use loader and enable patching

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