WIP: hide AddCorpus state

parent fe72f3d0
...@@ -3,7 +3,7 @@ module Gargantext.Pages.Layout where ...@@ -3,7 +3,7 @@ module Gargantext.Pages.Layout where
import Prelude hiding (div) import Prelude hiding (div)
-- import Gargantext.Components.Login as LN -- import Gargantext.Components.Login as LN
import Gargantext.Pages.Layout.Actions (Action(..)) 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.Doc.Facets as TV -- import Gargantext.Pages.Corpus.Doc.Facets as TV
-- import Gargantext.Pages.Corpus.Doc.Annotation as D -- import Gargantext.Pages.Corpus.Doc.Annotation as D
...@@ -33,7 +33,10 @@ dispatchAction dispatcher _ Login = do ...@@ -33,7 +33,10 @@ dispatchAction dispatcher _ Login = do
dispatchAction dispatcher _ AddCorpus = do dispatchAction dispatcher _ AddCorpus = do
dispatcher $ SetRoute AddCorpus dispatcher $ SetRoute AddCorpus
dispatcher $ AddCorpusA AC.LoadDatabaseDetails -- NP: I think that init code should be part of the Spec.
-- TODO: Add a Thermite combinator which takes an initialisation
-- command.
-- dispatcher $ AddCorpusA AC.LoadDatabaseDetails
dispatchAction dispatcher _ (DocView n) = do dispatchAction dispatcher _ (DocView n) = do
dispatcher $ SetRoute (DocView n) dispatcher $ SetRoute (DocView n)
......
...@@ -17,7 +17,6 @@ import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV ...@@ -17,7 +17,6 @@ import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Annuaire.User.Users as U import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Annuaire as Annuaire import Gargantext.Pages.Annuaire as Annuaire
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) import Gargantext.Pages.Layout.States (AppState)
import Gargantext.Router (Routes) import Gargantext.Router (Routes)
...@@ -29,7 +28,6 @@ data Action ...@@ -29,7 +28,6 @@ data Action
= Initialize = Initialize
| LoginA LN.Action | LoginA LN.Action
| SetRoute Routes | SetRoute Routes
| AddCorpusA AC.Action
| DocViewA DV.Action | DocViewA DV.Action
| SearchA S.Action | SearchA S.Action
| UserPageA U.Action | UserPageA U.Action
...@@ -95,7 +93,6 @@ performAction Initialize _ state = void do ...@@ -95,7 +93,6 @@ performAction Initialize _ state = void do
pure unit pure unit
performAction (LoginA _) _ _ = pure unit performAction (LoginA _) _ _ = pure unit
performAction (AddCorpusA _) _ _ = pure unit
performAction (DocViewA _) _ _ = pure unit performAction (DocViewA _) _ _ = pure unit
performAction (SearchA _) _ _ = pure unit performAction (SearchA _) _ _ = pure unit
performAction (UserPageA _) _ _ = pure unit performAction (UserPageA _) _ _ = pure unit
...@@ -112,12 +109,6 @@ _loginAction = prism LoginA \action -> ...@@ -112,12 +109,6 @@ _loginAction = prism LoginA \action ->
LoginA caction -> Right caction LoginA caction -> Right caction
_-> Left action _-> Left action
_addCorpusAction :: Prism' Action AC.Action
_addCorpusAction = prism AddCorpusA \action ->
case action of
AddCorpusA caction -> Right caction
_-> Left action
_docViewAction :: Prism' Action DV.Action _docViewAction :: Prism' Action DV.Action
_docViewAction = prism DocViewA \action -> _docViewAction = prism DocViewA \action ->
case action of case action of
......
...@@ -20,10 +20,10 @@ import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE ...@@ -20,10 +20,10 @@ import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable as NG
import Gargantext.Pages.Annuaire.User.Users as U import Gargantext.Pages.Annuaire.User.Users as U
import Gargantext.Pages.Home as L import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _docAnnotationViewAction, _docViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction, _annuaireAction) import Gargantext.Pages.Layout.Actions (Action(..), _docAnnotationViewAction, _docViewAction, _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, _addCorpusState, _docAnnotationViewState, _docViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState) import Gargantext.Pages.Layout.States (AppState, _docAnnotationViewState, _docViewState, _graphExplorerState, _loginState, _searchState, _treeState, _userPageState, _annuaireState)
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
import React (ReactElement) import React (ReactElement)
import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul) import React.DOM (a, button, div, footer, hr', img, input, li, p, span, text, ul)
...@@ -38,7 +38,7 @@ layoutSpec = ...@@ -38,7 +38,7 @@ layoutSpec =
, container $ withState pagesComponent , container $ withState pagesComponent
, withState \st -> , withState \st ->
fold [ focus _loginState _loginAction (LN.modalSpec st.showLogin "Login" LN.renderSpec) fold [ focus _loginState _loginAction (LN.modalSpec st.showLogin "Login" LN.renderSpec)
, focus _addCorpusState _addCorpusAction (AC.modalSpec st.showCorpus "Search Results" AC.layoutAddcorpus) , noState (AC.modalSpec st.showCorpus "Search Results" AC.layoutAddcorpus)
] ]
] ]
where where
...@@ -57,7 +57,7 @@ pagesComponent s = ...@@ -57,7 +57,7 @@ pagesComponent s =
selectSpec (Corpus i) = layout0 $ focus _docViewState _docViewAction DV.layoutDocview selectSpec (Corpus i) = layout0 $ focus _docViewState _docViewAction DV.layoutDocview
selectSpec Login = focus _loginState _loginAction LN.renderSpec selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = layout0 $ noState (L.layoutLanding EN) selectSpec Home = layout0 $ noState (L.layoutLanding EN)
selectSpec AddCorpus = layout0 $ focus _addCorpusState _addCorpusAction AC.layoutAddcorpus selectSpec AddCorpus = layout0 $ noState AC.layoutAddcorpus
selectSpec (DocView i) = layout0 $ focus _docViewState _docViewAction DV.layoutDocview selectSpec (DocView i) = layout0 $ focus _docViewState _docViewAction DV.layoutDocview
selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction U.layoutUser selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction U.layoutUser
selectSpec (DocAnnotation i) = layout0 $ focus _docAnnotationViewState selectSpec (DocAnnotation i) = layout0 $ focus _docAnnotationViewState
......
module Gargantext.Pages.Layout.Specs.AddCorpus.Specs where module Gargantext.Pages.Layout.Specs.AddCorpus.Specs where
import Gargantext.Pages.Layout.Specs.AddCorpus.Actions import Gargantext.Pages.Layout.Specs.AddCorpus.Actions (Action(..), performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus.States import Gargantext.Pages.Layout.Specs.AddCorpus.States (Query, Response(..), State, initialState)
import Prelude hiding (div) import Prelude hiding (div)
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.RequestBody (RequestBody(..)) import Affjax.RequestBody (RequestBody(..))
import Affjax.ResponseFormat as ResponseFormat import Affjax.ResponseFormat as ResponseFormat
import Control.Monad.Cont.Trans (lift) import Data.Argonaut (decodeJson, encodeJson)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.Lens (over) import Data.Lens (over)
import Data.Maybe (Maybe(Just)) import Data.Maybe (Maybe(Just))
import Data.MediaType.Common (applicationJSON)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Console (log) import Effect.Console (log)
import Gargantext.Components.Modals.Modal (modalHide)
import React (ReactElement) import React (ReactElement)
import React.DOM (button, div, h3, h5, li, span, text, ul) import React.DOM (button, div, h3, h5, li, span, text, ul)
import React.DOM.Props (_data, _id, _type, aria, className, onClick, role) import React.DOM.Props (_data, _id, _type, aria, className, onClick, role)
import Thermite (PerformAction, Render, Spec, _render, simpleSpec) import Thermite (Render, Spec, _render, hide, simpleSpec)
modalSpec :: Boolean -> String -> Spec State {} Action -> Spec State {} Action modalSpec :: forall state props action
. Boolean -> String -> Spec state props action -> Spec state props action
modalSpec sm t = over _render \render d p s c -> modalSpec sm t = over _render \render d p s c ->
[ div [ _id "addCorpus", className $ "modal myModal" <> if sm then "" else " fade" [ div [ _id "addCorpus", className $ "modal myModal" <> if sm then "" else " fade"
, role "dialog" , role "dialog"
...@@ -46,7 +44,7 @@ modalSpec sm t = over _render \render d p s c -> ...@@ -46,7 +44,7 @@ modalSpec sm t = over _render \render d p s c ->
] ]
spec' :: Spec State {} Action spec' :: Spec {} {} Void
spec' = modalSpec true "Search Results" layoutAddcorpus spec' = modalSpec true "Search Results" layoutAddcorpus
...@@ -96,8 +94,8 @@ layoutModal state = ...@@ -96,8 +94,8 @@ layoutModal state =
] ]
layoutAddcorpus :: Spec State {} Action layoutAddcorpus :: Spec {} {} Void
layoutAddcorpus = simpleSpec performAction render layoutAddcorpus = hide initialState $ simpleSpec performAction render
where where
render :: Render State {} Action render :: Render State {} Action
render dispatch _ state _ = render dispatch _ state _ =
......
...@@ -11,14 +11,12 @@ import Gargantext.Pages.Annuaire as Annuaire ...@@ -11,14 +11,12 @@ import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV import Gargantext.Pages.Corpus.Doc.Facets.Documents as DV
import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE import Gargantext.Pages.Corpus.Doc.Facets.Graph as GE
import Gargantext.Pages.Annuaire.User.Users as U import Gargantext.Pages.Annuaire.User.Users as U
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.Router (Routes(..)) import Gargantext.Router (Routes(..))
type AppState = type AppState =
{ currentRoute :: Maybe Routes { currentRoute :: Maybe Routes
, loginState :: LN.State , loginState :: LN.State
, addCorpusState :: AC.State
, docViewState :: DV.State , docViewState :: DV.State
, searchState :: S.State , searchState :: S.State
, userPageState :: U.State , userPageState :: U.State
...@@ -36,7 +34,6 @@ initAppState :: AppState ...@@ -36,7 +34,6 @@ initAppState :: AppState
initAppState = initAppState =
{ currentRoute : Just Home { currentRoute : Just Home
, loginState : LN.initialState , loginState : LN.initialState
, addCorpusState : AC.initialState
, docViewState : DV.tdata , docViewState : DV.tdata
, searchState : S.initialState , searchState : S.initialState
, userPageState : U.initialState , userPageState : U.initialState
...@@ -54,9 +51,6 @@ initAppState = ...@@ -54,9 +51,6 @@ initAppState =
_loginState :: Lens' AppState LN.State _loginState :: Lens' AppState LN.State
_loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss}) _loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
_addCorpusState :: Lens' AppState AC.State
_addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = 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})
......
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