Commit 014f5921 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FACTO] State and Action file, removing Types.purs.

parent 4f00e702
module Gargantext.Layout.Action where
module Gargantext.Pages.Layout.Action where
import Prelude hiding (div)
......@@ -8,13 +8,53 @@ import Control.Monad.Eff.Console (CONSOLE, log)
import DOM (DOM)
import Data.Array (length)
import Data.Either (Either(..))
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree
import Gargantext.Layout.Types (Action(..), AppState)
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Body as CA
import Gargantext.Pages.Corpus.Doc.Document as DV
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
import Gargantext.Pages.Corpus as AC
import Gargantext.Router (Routes(..))
import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Home as L
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Search as S
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Layout.State (AppState)
import Gargantext.Pages.Corpus.Doc.Document as DV
import Network.HTTP.Affjax (AJAX)
import Thermite (PerformAction, modifyState)
data Action
= Initialize
| LandingA L.Action
| LoginA LN.Action
| SetRoute Routes
| AddCorpusA AC.Action
| DocViewA DV.Action
| SearchA S.Action
| UserPageA U.Action
| DocAnnotationViewA D.Action
| TreeViewA Tree.Action
| TabViewA TV.Action
| GraphExplorerA GE.Action
| DashboardA Dsh.Action
| Search String
| Go
| CorpusAnalysisA CA.Action
| ShowLogin
| ShowAddcorpus
| NgramsA NG.Action
performAction :: forall eff props. PerformAction ( dom :: DOM
, ajax :: AJAX
, console :: CONSOLE
......
......@@ -2,7 +2,7 @@ module Gargantext.Layout.Dispatcher where
import Prelude hiding (div)
import Gargantext.Components.Login as LN
import Gargantext.Layout.Types (Action(..))
import Gargantext.Pages.Layout.Action (Action(..))
import Gargantext.Pages.Corpus as AC
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Document as DV
......
......@@ -10,9 +10,9 @@ import Data.Maybe (Maybe(Nothing, Just))
import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Components.Login as LN
import Gargantext.Components.Tree as Tree
import Gargantext.Layout.Action (performAction)
import Gargantext.Pages.Layout.Action (Action(..), performAction)
import Gargantext.Layout.Lens (_addCorpusAction, _addCorpusState, _corpusAction, _corpusState, _dashBoardAction, _dashBoardSate, _docAnnotationViewAction, _docAnnotationViewState, _docViewAction, _docViewState, _graphExplorerAction, _graphExplorerState, _landingAction, _landingState, _loginAction, _loginState, _ngAction, _ngState, _searchAction, _searchState, _tabviewAction, _tabviewState, _treeAction, _treeState, _userPageAction, _userPageState)
import Gargantext.Layout.Types (Action(..), AppState, E)
import Gargantext.Pages.Layout.State (AppState, E)
import Gargantext.Pages.Corpus as AC
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Body as CA
......@@ -79,12 +79,9 @@ layout0 layout =
if ((\(LN.State s) -> s.loginC) st.loginState == true) then ls as
else outerLayout1
, rs bs ]
ls = over _render \render d p s c ->
[div [className "col-md-2"] (render d p s c)]
rs = over _render \render d p s c ->
[ div [className "col-md-10"] (render d p s c) ]
cont = over _render \render d p s c ->
[ div [ className "row" ] (render d p s c) ]
ls = over _render \render d p s c -> [ div [className "col-md-2" ] (render d p s c) ]
rs = over _render \render d p s c -> [ div [className "col-md-10"] (render d p s c) ]
cont = over _render \render d p s c -> [ div [ className "row" ] (render d p s c) ]
as = focus _treeState _treeAction Tree.treeview
......
module Gargantext.Layout.Lens where
---- Lens and Prism
import Gargantext.Layout.Types
import Gargantext.Pages.Layout.State
import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism)
import Gargantext.Pages.Home as L
import Gargantext.Components.Login as LN
import Gargantext.Pages.Corpus as AC
import Gargantext.Components.Tree as Tree
import Gargantext.Components.Login as LN
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus as AC
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Body as CA
import Gargantext.Pages.Corpus.Doc.Body as CA
import Gargantext.Pages.Corpus.Doc.Document as DV
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Search as S
import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Action (Action(..))
import Gargantext.Pages.Search as S
---- Lens and Prism
_landingState :: Lens' AppState L.State
......
module Gargantext.Layout.Types where
module Gargantext.Pages.Layout.State where
import Prelude hiding (div)
import Control.Monad.Cont.Trans (lift)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Gargantext.Pages.Corpus.Doc.Body as CA
import DOM (DOM)
import Data.Array (length)
import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, prism)
import Data.Maybe (Maybe(Just))
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Document as DV
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus as AC
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Body as CA
import Gargantext.Pages.Corpus.Doc.Document as DV
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
import Gargantext.Pages.Corpus as AC
import Gargantext.Router (Routes(..))
import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Home as L
import Network.HTTP.Affjax (AJAX)
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Search as S
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.User.Users as U
import Gargantext.Pages.Home as L
import Gargantext.Pages.Search as S
import Gargantext.Router (Routes(..))
import Network.HTTP.Affjax (AJAX)
import Thermite (PerformAction, modifyState)
type E e = (dom :: DOM, ajax :: AJAX, console :: CONSOLE | e)
......@@ -38,17 +40,17 @@ type AppState =
, docViewState :: DV.State
, searchState :: S.State
, userPage :: U.State
, docAnnotationView :: D.State
, ntreeView :: Tree.State
, tabview :: TV.State
, search :: String
, docAnnotationView :: D.State
, ntreeView :: Tree.State
, tabview :: TV.State
, search :: String
, corpusAnalysis :: CA.State
, showLogin :: Boolean
, showCorpus :: Boolean
, graphExplorer :: GE.State
, initialized :: Boolean
, ngState :: NG.State
, dashboard :: Dsh.State
, showLogin :: Boolean
, showCorpus :: Boolean
, graphExplorer :: GE.State
, initialized :: Boolean
, ngState :: NG.State
, dashboard :: Dsh.State
}
initAppState :: AppState
......@@ -60,36 +62,17 @@ initAppState =
, docViewState : DV.tdata
, searchState : S.initialState
, userPage : U.initialState
, docAnnotationView : D.initialState
, ntreeView : Tree.exampleTree
, tabview : TV.initialState
, search : ""
, docAnnotationView : D.initialState
, ntreeView : Tree.exampleTree
, tabview : TV.initialState
, search : ""
, corpusAnalysis : CA.initialState
, showLogin : false
, showCorpus : false
, graphExplorer : GE.initialState
, initialized : false
, ngState : NG.initialState
, dashboard : Dsh.initialState
, showLogin : false
, showCorpus : false
, graphExplorer : GE.initialState
, initialized : false
, ngState : NG.initialState
, dashboard : Dsh.initialState
}
data Action
= Initialize
| LandingA L.Action
| LoginA LN.Action
| SetRoute Routes
| AddCorpusA AC.Action
| DocViewA DV.Action
| SearchA S.Action
| UserPageA U.Action
| DocAnnotationViewA D.Action
| TreeViewA Tree.Action
| TabViewA TV.Action
| GraphExplorerA GE.Action
| DashboardA Dsh.Action
| Search String
| Go
| CorpusAnalysisA CA.Action
| ShowLogin
| ShowAddcorpus
| NgramsA NG.Action
......@@ -11,9 +11,11 @@ import DOM.HTML.Window (document) as DOM
import DOM.Node.ParentNode (QuerySelector(..))
import DOM.Node.ParentNode (querySelector) as DOM
import Data.Maybe (fromJust)
import Gargantext.Layout (layoutSpec)
import Gargantext.Layout.Dispatcher (dispatchAction)
import Gargantext.Layout.Types (initAppState)
import Gargantext.Pages.Layout.State (initAppState)
import Gargantext.Router (routeHandler, routing)
import Network.HTTP.Affjax (AJAX)
import Partial.Unsafe (unsafePartial)
......
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