WIP hide

parent 246ab19a
......@@ -8,17 +8,15 @@
],
"dependencies": {
"purescript-console": "^4.1.0",
"purescript-thermite": "https://github.com/np/purescript-thermite.git#migrate_0_12",
"purescript-thermite": "https://github.com/np/purescript-thermite.git#hide",
"purescript-affjax": "^7.0.0",
"purescript-routing": "^8.0.0",
"purescript-argonaut": "^4.0.1",
"purescript-random": "^4.0.0",
"purescript-react": "^6.1.0",
"purescript-css": "^4.0.0"
},
"devDependencies": {
"purescript-psci-support": "^4.0.0"
},
"resolutions": {
"purescript-react": "exports"
}
}
......@@ -2,17 +2,17 @@ module Gargantext.Pages.Corpus where
import Prelude hiding (div)
import Data.Array (fold)
import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard (globalPublis)
import Gargantext.Pages.Corpus.Doc.Facets as Tab
import React (class ReactPropFields)
import React.DOM (div, h3, hr, i, p, text)
import React.DOM.Props (className, style)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
type State = Tab.State
-- type State = {} -- Tab.State
type Action = Tab.Action
-- data Action = None -- type Action = Tab.Action
type Corpus = { title :: String
, desc :: String
......@@ -21,19 +21,20 @@ type Corpus = { title :: String
, authors :: String
}
initialState :: State
initialState = Tab.initialState
-- initialState :: State
-- initialState = {} -- Tab.initialState
spec' :: forall props. Spec Tab.State props Tab.Action
spec' = fold [ corpusSpec
, Tab.tab1
]
-- type PureSpec props = forall state action. Spec state props action
spec' :: forall action. Spec {} {} action
spec' = corpusSpec <> Tab.tab1
corpusSpec :: forall props. Spec Tab.State props Tab.Action
-- corpusSpec :: forall props. Spec Tab.State props Tab.Action
corpusSpec :: forall state props action. Spec (Record state) (Record props) action
corpusSpec = simpleSpec defaultPerformAction render
where
render :: Render Tab.State props Tab.Action
render dispatch _ state _ =
render :: Render (Record state) (Record props) action
render dispatch _ _ _ =
[ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text corpus.title] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
......
......@@ -2,12 +2,11 @@ module Gargantext.Pages.Corpus.Doc.Facets.Specs where
import Prelude hiding (div)
import Data.Lens (Lens', Prism', lens, prism)
import Data.List (fromFoldable)
import Data.Tuple (Tuple(..))
import Gargantext.Pages.Corpus.Doc.Facets.States (State(..), _doclens, _sourcelens, _authorlens, _termslens, _tablens)
import Gargantext.Pages.Corpus.Doc.Facets.Actions (Action(..), _docAction, _sourceAction, _authorAction, _termsAction, _tabAction)
import Gargantext.Pages.Corpus.Doc.Facets.States (State(), _doclens, _sourcelens, _authorlens, _termslens, _tablens, initialState)
import Gargantext.Pages.Corpus.Doc.Facets.Actions (Action(), _docAction, _sourceAction, _authorAction, _termsAction, _tabAction)
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Sources as SV
......@@ -15,12 +14,14 @@ import Gargantext.Pages.Corpus.Doc.Facets.Authors as AV
import Gargantext.Pages.Corpus.Doc.Facets.Terms as TV
import Gargantext.Components.Tab as Tab
import Thermite (Spec, focus)
import Thermite (Spec, focus, hide)
tab1 :: forall action. Spec {} {} action
tab1 = hide initialState tab1'
tab1 :: forall props. Spec State props Action
tab1 = Tab.tabs _tablens _tabAction $ fromFoldable [ Tuple "Doc View" docPageSpec
tab1' :: Spec State {} Action
tab1' = Tab.tabs _tablens _tabAction $ fromFoldable [ Tuple "Doc View" docPageSpec
, Tuple "Author View" authorPageSpec
, Tuple "Source View" sourcePageSpec
, Tuple "Terms View" termsPageSpec
......
......@@ -11,7 +11,7 @@ import Effect.Console (log)
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Corpus as CA
-- import Gargantext.Pages.Corpus as CA
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.Doc.Facets.Dashboard as Dsh
......@@ -43,7 +43,7 @@ data Action
| DashboardA Dsh.Action
| Search String
| Go
| CorpusAnalysisA CA.Action
-- | CorpusAnalysisA CA.Action
| ShowLogin
| ShowAddcorpus
| NgramsA NG.Action
......@@ -161,11 +161,13 @@ _tabviewAction = prism TabViewA \action ->
TabViewA caction -> Right caction
_-> Left action
{-
_corpusAction :: Prism' Action CA.Action
_corpusAction = prism CorpusAnalysisA \action ->
case action of
CorpusAnalysisA caction -> Right caction
_-> Left action
-}
_graphExplorerAction :: Prism' Action GE.Action
_graphExplorerAction = prism GraphExplorerA \action ->
......
......@@ -18,10 +18,10 @@ 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.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _LandingA, _NgramsA, _addCorpusAction, _corpusAction, _dashBoardAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _tabviewAction, _treeAction, _userPageAction, performAction)
import Gargantext.Pages.Layout.Actions (Action(..), _LandingA, _NgramsA, _addCorpusAction, {-_corpusAction,-} _dashBoardAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _tabviewAction, _treeAction, _userPageAction, performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _corpusState, _dashBoardSate, _docAnnotationViewState, _docViewState, _graphExplorerState, _landingState, _loginState, _ngramState, _searchState, _tabviewState, _treeState, _userPageState)
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, {-_corpusState,-} _dashBoardSate, _docAnnotationViewState, _docViewState, _graphExplorerState, _landingState, _loginState, _ngramState, _searchState, _tabviewState, _treeState, _userPageState)
import Gargantext.Router (Routes(..))
import React (ReactElement)
import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul)
......@@ -52,7 +52,7 @@ pagesComponent s =
Nothing -> selectSpec Home
where
selectSpec :: Routes -> Spec AppState props Action
selectSpec CorpusAnalysis = layout0 $ focus _corpusState _corpusAction CA.spec'
selectSpec CorpusAnalysis = unsafeCoerce {} -- TODO layout0 $ {-focus _corpusState _corpusAction-} CA.spec'
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = layout0 $ focus _landingState _LandingA (L.layoutLanding EN)
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus
......
......@@ -8,7 +8,7 @@ import Data.Maybe (Maybe(Just))
import Gargantext.Components.Login as LN
import Gargantext.Components.Tree as Tree
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Corpus as CA
-- import Gargantext.Pages.Corpus as CA
import Gargantext.Pages.Corpus.Doc.Annotation as D
import Gargantext.Pages.Corpus.Doc.Facets as TV
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
......@@ -33,7 +33,7 @@ type AppState =
, ntreeState :: Tree.State
, tabviewState :: TV.State
, search :: String
, corpusState :: CA.State
-- , corpusState :: CA.State
, showLogin :: Boolean
, showCorpus :: Boolean
, graphExplorerState :: GE.State
......@@ -55,7 +55,7 @@ initAppState =
, ntreeState : Tree.exampleTree
, tabviewState : TV.initialState
, search : ""
, corpusState : CA.initialState
-- , corpusState : CA.initialState
, showLogin : false
, showCorpus : false
, graphExplorerState : GE.initialState
......@@ -92,8 +92,8 @@ _treeState = lens (\s -> s.ntreeState) (\s ss -> s {ntreeState = ss})
_tabviewState :: Lens' AppState TV.State
_tabviewState = lens (\s -> s.tabviewState) (\s ss -> s {tabviewState = ss})
_corpusState :: Lens' AppState CA.State
_corpusState = lens (\s -> s.corpusState) (\s ss -> s {corpusState = ss})
-- _corpusState :: Lens' AppState CA.State
-- _corpusState = lens (\s -> s.corpusState) (\s ss -> s {corpusState = ss})
_dashBoardSate :: Lens' AppState Dsh.State
_dashBoardSate = lens (\s -> s.dashboardState) (\s ss -> s {dashboardState = 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