Commit 4c51907c authored by James Laver's avatar James Laver

Refactor layout

parent 4f479973
This diff is collapsed.
module Gargantext.Pages.Layout.Specs.SearchBar module Gargantext.Components.Search.SearchBar
( Props, defaultProps, searchBar, searchBarComponent ( Props, defaultProps, searchBar, searchBarCpt
) where ) where
import Prelude import Prelude (Unit, bind, const, discard, not, pure, show, ($), (<>))
import Control.Monad.Cont.Trans (lift)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Newtype (over) import Data.Newtype (over)
import Data.Traversable (traverse_) import Data.Traversable (traverse_)
import Data.Tuple (fst)
import Data.Tuple.Nested ( (/\) ) import Data.Tuple.Nested ( (/\) )
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Uncurried (EffectFn1, mkEffectFn1) import Effect.Uncurried (EffectFn1, mkEffectFn1)
import Reactix as R import Reactix as R
import DOM.Simple.Console import DOM.Simple.Console (log2)
import Effect.Aff (launchAff) import Effect.Aff (Aff, launchAff)
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Components.Search.Types import Gargantext.Config (Ends)
import Gargantext.Components.Search.Ajax as Ajax import Gargantext.Components.Search.Types (Database, SearchQuery(..), allDatabases, defaultSearchQuery, performSearch)
import Gargantext.Components.Modals.Modal (modalShow) import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Search.SearchField (Search, searchField) import Gargantext.Components.Search.SearchField (Search, searchField)
import Gargantext.Utils (id)
type Props = ( open :: Boolean, databases :: Array Database ) type Props = ( ends :: Ends, open :: Boolean, databases :: Array Database )
defaultProps :: Record Props defaultProps :: Ends -> Record Props
defaultProps = { open: false, databases: allDatabases } defaultProps ends = { open: false, databases: allDatabases, ends }
searchBar :: Record Props -> R.Element searchBar :: Record Props -> R.Element
searchBar p = R.createElement searchBarComponent p [] searchBar p = R.createElement searchBarCpt p []
searchBarComponent :: R.Component Props searchBarCpt :: R.Component Props
searchBarComponent = R.hooksComponent "SearchBar" cpt searchBarCpt = R.hooksComponent "SearchBar" cpt
where where
cpt props _ = do cpt {ends, databases, open} _ = do
open <- R.useState $ const props.open open' <- R.useState $ const open
search <- R.useState $ const Nothing search <- R.useState $ const Nothing
onSearchChange search onSearchChange ends search
pure $ H.div { className: "search-bar-container" } pure $ H.div { className: "search-bar-container" }
[ toggleButton open [ toggleButton open'
, searchFieldContainer open props.databases search ] , searchFieldContainer open' databases search ]
searchFieldContainer :: R.State Boolean -> Array Database -> R.State (Maybe Search) -> R.Element searchFieldContainer :: R.State Boolean -> Array Database -> R.State (Maybe Search) -> R.Element
searchFieldContainer (open /\ _) databases search = searchFieldContainer (open /\ _) databases search =
...@@ -46,15 +43,15 @@ searchFieldContainer (open /\ _) databases search = ...@@ -46,15 +43,15 @@ searchFieldContainer (open /\ _) databases search =
where where
openClass = if open then "open" else "closed" openClass = if open then "open" else "closed"
onSearchChange :: R.State (Maybe Search) -> R.Hooks Unit onSearchChange :: Ends -> R.State (Maybe Search) -> R.Hooks Unit
onSearchChange (search /\ setSearch) = onSearchChange ends (search /\ setSearch) =
R.useLayoutEffect1' search $ traverse_ triggerSearch search R.useLayoutEffect1' search $ traverse_ triggerSearch search
where where
triggerSearch q = do triggerSearch q = do
launchAff $ do launchAff $ do
liftEffect $ log2 "Searching db: " $ show q.database liftEffect $ log2 "Searching db: " $ show q.database
liftEffect $ log2 "Searching term: " q.term liftEffect $ log2 "Searching term: " q.term
(r :: Unit) <- Ajax.search (searchQuery q) r <- (performSearch ends $ searchQuery q) :: Aff Unit
liftEffect $ log2 "Return:" r liftEffect $ log2 "Return:" r
liftEffect $ modalShow "addCorpus" liftEffect $ modalShow "addCorpus"
searchQuery {database: Nothing, term} = over SearchQuery (_ {query=term}) defaultSearchQuery searchQuery {database: Nothing, term} = over SearchQuery (_ {query=term}) defaultSearchQuery
...@@ -63,9 +60,8 @@ onSearchChange (search /\ setSearch) = ...@@ -63,9 +60,8 @@ onSearchChange (search /\ setSearch) =
toggleButton :: R.State Boolean -> R.Element toggleButton :: R.State Boolean -> R.Element
toggleButton open = toggleButton open =
H.button { onClick: onToggleExpanded open, className: "search-bar-toggle" } H.button { onClick: onToggleExpanded open, className: "search-bar-toggle" }
[ H.i { className: "material-icons md-24" [ H.i { className: "material-icons md-24", style } [ H.text "control_point" ] ]
, style: { marginTop: "-2px", color: "#000" } } where style = { marginTop: "-2px", color: "#000" }
[ H.text "control_point" ] ]
onToggleExpanded :: forall e. R.State Boolean -> EffectFn1 e Unit onToggleExpanded :: forall e. R.State Boolean -> EffectFn1 e Unit
onToggleExpanded (_open /\ setOpen) = mkEffectFn1 $ \_ -> setOpen not onToggleExpanded (_open /\ setOpen) = mkEffectFn1 $ \_ -> setOpen not
module Gargantext.Pages.Layout where
import Prelude hiding (div)
import Gargantext.Pages.Layout.Actions (Action(..))
import Gargantext.Router (Routes(..))
dispatchAction :: forall ignored m.
Monad m =>
(Action -> m Unit) -> ignored -> Routes -> m Unit
dispatchAction dispatcher _ Home = do
dispatcher $ SetRoute Home
-- dispatcher $ LandingA TODO
dispatchAction dispatcher _ Login = do
dispatcher $ SetRoute Login
-- dispatcher $ LoginA TODO
dispatchAction dispatcher _ (Corpus n) = do
dispatcher $ SetRoute $ Corpus n
dispatchAction dispatcher _ (UserPage id) = do
dispatcher $ SetRoute $ UserPage id
dispatchAction dispatcher _ (ContactPage id) = do
dispatcher $ SetRoute $ ContactPage id
dispatchAction dispatcher _ (Annuaire id) = do
dispatcher $ SetRoute $ Annuaire id
dispatchAction dispatcher _ (Folder id) = do
dispatcher $ SetRoute $ Folder id
dispatchAction dispatcher _ (CorpusDocument c i n) = do
dispatcher $ SetRoute $ CorpusDocument c i n
dispatchAction dispatcher _ (Document i n) = do
dispatcher $ SetRoute $ Document i n
dispatchAction dispatcher _ (PGraphExplorer nid) = do
dispatcher $ SetRoute $ PGraphExplorer nid
-- dispatcher $ GraphExplorerA $ GE.LoadGraph nid
--dispatcher $ GraphExplorerA $ GE.LoadGraph "imtNew.json"
dispatchAction dispatcher _ (Texts nid) = do
dispatcher $ SetRoute $ Texts nid
dispatchAction dispatcher _ (Lists nid) = do
dispatcher $ SetRoute $ Lists nid
dispatchAction dispatcher _ Dashboard = do
dispatcher $ SetRoute Dashboard
-- | Module Description
module Gargantext.Pages.Layout.Actions where
import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
import Data.Lens (Prism', prism)
import Effect.Class (liftEffect)
import Thermite (PerformAction, modifyState, modifyState_)
import Routing.Hash (setHash)
import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Components.Login as LN
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Config as C
import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Layout.States (AppState)
import Gargantext.Prelude
import Gargantext.Router (Routes)
------------------------------------------------------------------------
data Action
= LoginA LN.Action
| SetRoute Routes
| GraphExplorerA GET.Action
| AnnuaireAction Annuaire.Action
| ShowLogin
| Logout
| ShowAddCorpus
| ToggleTree
| ConfigStateA C.StateAction
performAction :: PerformAction AppState {} Action
performAction (SetRoute route) _ _ = void do
modifyState $ _ {currentRoute = pure route}
performAction (ToggleTree) _ (state) = void do -- TODO
modifyState $ _ {showTree = not (state.showTree)}
performAction ShowLogin _ _ = void do
liftEffect $ modalShow "loginModal"
modifyState $ _ {showLogin = true}
performAction Logout _ _ = do
loginState <- liftEffect do
LN.setAuthData Nothing
setHash "/"
LN.initialState
modifyState_ $ _ {currentRoute = Nothing, loginState = loginState}
---------------------------------------------------------
-- TODO chose one of them
performAction ShowAddCorpus _ _ = void do
liftEffect $ modalShow "addCorpus"
modifyState $ _ {showCorpus = true}
---------------------------------------------------------
performAction (LoginA _) _ _ = pure unit
performAction (GraphExplorerA _) _ _ = pure unit
performAction (AnnuaireAction _) _ _ = pure unit
-- liftEffect $ modalShow "addCorpus"
-- modifyState $ _ {showCorpus = true}
performAction (ConfigStateA _) _ _ = pure unit
----------------------------------------------------------
_loginAction :: Prism' Action LN.Action
_loginAction = prism LoginA \action ->
case action of
LoginA caction -> Right caction
_-> Left action
_configStateAction :: Prism' Action C.StateAction
_configStateAction = prism ConfigStateA \action ->
case action of
ConfigStateA caction -> Right caction
_-> Left action
_annuaireAction :: Prism' Action Annuaire.Action
_annuaireAction = prism AnnuaireAction \action ->
case action of
AnnuaireAction a -> Right a
_ -> Left action
_graphExplorerAction :: Prism' Action GET.Action
_graphExplorerAction = prism GraphExplorerA \action ->
case action of
GraphExplorerA caction -> Right caction
_-> Left action
This diff is collapsed.
module Gargantext.Pages.Layout.States where
import Prelude hiding (div)
import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Gargantext.Config as C
import Gargantext.Components.Login as LN
import Gargantext.Components.Login as LN
--import Gargantext.Components.Login.Types as LNT
--import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Router (Routes(..))
type AppState =
{ currentRoute :: Maybe Routes
, loginState :: LN.State
, showLogin :: Boolean
, showCorpus :: Boolean
--, graphExplorerState :: Record GET.StateGlue
, showTree :: Boolean
, configState :: C.State
}
initAppState :: Effect AppState
initAppState = do
loginState <- LN.initialState
pure
{ currentRoute : Just Home
, loginState
, showLogin : false
, showCorpus : false
--, graphExplorerState : GET.initialStateGlue
, showTree : false
, configState : C.initialState
}
---------------------------------------------------------
_loginState :: Lens' AppState LN.State
_loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
_configState :: Lens' AppState C.State
_configState = lens (\s -> s.configState) (\s ss -> s{configState = ss})
_graphExplorerState :: Lens' AppState GE.State
_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