Commit 72455d0a authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[Config] allow to switch the current backend

NOTE This doesn't work yet, especially the dropdown is problematic...
parent fafd5a21
"use strict";
exports.createDropdown = function(iid) {
var el = document.getElementById(iid);
if (!window.Dropdown) return;
new window.Dropdown(el, {});
};
module Gargantext.BootstrapNative where
import Effect (Effect)
import Gargantext.Prelude
foreign import createDropdown :: String -> Effect Unit
...@@ -388,7 +388,7 @@ renderPage loaderDispatch { totalRecords, dispatch, container ...@@ -388,7 +388,7 @@ renderPage loaderDispatch { totalRecords, dispatch, container
] ]
-- TODO show date: Year-Month-Day only -- TODO show date: Year-Month-Day only
, div strikeIfDeleted [text date] , div strikeIfDeleted [text date]
, a (strikeIfDeleted <> [ href $ toLink $ endConfigStateful Router.Document listId id , a (strikeIfDeleted <> [ href $ toLink endConfigStateful $ Router.Document listId id
, target "blank"]) , target "blank"])
[ text title ] [ text title ]
, div strikeIfDeleted [text source] , div strikeIfDeleted [text source]
......
...@@ -17,7 +17,7 @@ import Thermite (PerformAction, modifyState) ...@@ -17,7 +17,7 @@ import Thermite (PerformAction, modifyState)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Types (class ToQuery) import Gargantext.Types (class ToQuery)
import Gargantext.Config (End(..), NodeType(..), Path(..), toUrl) import Gargantext.Config (endConfigStateful, End(..), NodeType(..), Path(..), toUrl)
import Gargantext.Config.REST (post, put) import Gargantext.Config.REST (post, put)
import Gargantext.Components.Modals.Modal (modalHide) import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Utils (id) import Gargantext.Utils (id)
...@@ -143,7 +143,7 @@ instance encodeJsonCategoryQuery :: EncodeJson CategoryQuery where ...@@ -143,7 +143,7 @@ instance encodeJsonCategoryQuery :: EncodeJson CategoryQuery where
~> jsonEmptyObject ~> jsonEmptyObject
categoryUrl :: Int -> String categoryUrl :: Int -> String
categoryUrl nodeId = toUrl Back Node (Just nodeId) <> "/category" categoryUrl nodeId = toUrl endConfigStateful Back Node (Just nodeId) <> "/category"
putCategories :: Int -> CategoryQuery -> Aff (Array Int) putCategories :: Int -> CategoryQuery -> Aff (Array Int)
putCategories nodeId = put $ categoryUrl nodeId putCategories nodeId = put $ categoryUrl nodeId
This diff is collapsed.
...@@ -11,12 +11,15 @@ module Gargantext.Config where ...@@ -11,12 +11,15 @@ module Gargantext.Config where
import Prelude import Prelude
import Data.Argonaut (class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), jsonEmptyObject) import Data.Argonaut (class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), jsonEmptyObject)
import Data.Array (filter, head)
import Data.Foldable (foldMap) import Data.Foldable (foldMap)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe, fromJust)
import Gargantext.Router as R import Partial.Unsafe (unsafePartial)
import Thermite (PerformAction, modifyState_)
import Gargantext.Router as R
import Gargantext.Types (TermList, TermSize(..)) import Gargantext.Types (TermList, TermSize(..))
urlPlease :: End -> String -> String urlPlease :: End -> String -> String
...@@ -28,15 +31,63 @@ endConfigStateful :: EndConfig ...@@ -28,15 +31,63 @@ endConfigStateful :: EndConfig
endConfigStateful = endConfig endConfigStateful = endConfig
endConfig :: EndConfig endConfig :: EndConfig
endConfig = endConfig' V10 endConfig = devEndConfig
endConfig' :: ApiVersion -> EndConfig devEndConfig :: EndConfig
endConfig' v = { front : frontRelative devEndConfig = devEndConfig' V10
, back : backLocal v
--, back: backDev v devEndConfig' :: ApiVersion -> EndConfig
, static : staticRelative devEndConfig' v = { front : frontRelative
} , back: backDev v
-- , back : backDemo v } , static : staticRelative
}
localEndConfig :: EndConfig
localEndConfig = localEndConfig' V10
localEndConfig' :: ApiVersion -> EndConfig
localEndConfig' v = { front : frontRelative
, back : backLocal v
, static : staticRelative
}
type EndConfigOption = {
endConfig :: EndConfig
, displayName :: String
}
endConfigOptions :: Array EndConfigOption
endConfigOptions = [
{
endConfig: devEndConfig
, displayName: "dev"
}
, {
endConfig: localEndConfig
, displayName: "local"
}
]
endConfigDisplayName :: EndConfig -> String
endConfigDisplayName endConfig = (unsafePartial $ fromJust h).displayName
where
h = head $ filter (\ec -> ec.endConfig == endConfig) endConfigOptions
type State = {
endConfig :: EndConfig
}
initialState :: State
initialState = {
endConfig: endConfig
}
data StateAction = UpdateState State
statePerformAction :: forall props. PerformAction State props StateAction
statePerformAction (UpdateState state) _ _ =
void $ modifyState_ $ const state
------------------------------------------------------------------------ ------------------------------------------------------------------------
frontRelative :: Config frontRelative :: Config
......
...@@ -11,6 +11,7 @@ import Routing.Hash (setHash) ...@@ -11,6 +11,7 @@ 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.Config as C
import Gargantext.Pages.Annuaire as Annuaire import Gargantext.Pages.Annuaire as Annuaire
import Gargantext.Pages.Corpus.Graph as GE import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Layout.States (AppState) import Gargantext.Pages.Layout.States (AppState)
...@@ -28,6 +29,7 @@ data Action ...@@ -28,6 +29,7 @@ data Action
| Logout | Logout
| ShowAddCorpus | ShowAddCorpus
| ToggleTree | ToggleTree
| ConfigStateA C.StateAction
performAction :: PerformAction AppState {} Action performAction :: PerformAction AppState {} Action
...@@ -62,6 +64,8 @@ performAction (AnnuaireAction _) _ _ = pure unit ...@@ -62,6 +64,8 @@ performAction (AnnuaireAction _) _ _ = pure unit
-- liftEffect $ modalShow "addCorpus" -- liftEffect $ modalShow "addCorpus"
-- modifyState $ _ {showCorpus = true} -- modifyState $ _ {showCorpus = true}
performAction (ConfigStateA _) _ _ = pure unit
---------------------------------------------------------- ----------------------------------------------------------
_loginAction :: Prism' Action LN.Action _loginAction :: Prism' Action LN.Action
...@@ -70,6 +74,12 @@ _loginAction = prism LoginA \action -> ...@@ -70,6 +74,12 @@ _loginAction = prism LoginA \action ->
LoginA caction -> Right caction LoginA caction -> Right caction
_-> Left action _-> 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' Action Annuaire.Action
_annuaireAction = prism AnnuaireAction \action -> _annuaireAction = prism AnnuaireAction \action ->
case action of case action of
......
...@@ -3,6 +3,7 @@ module Gargantext.Pages.Layout.Specs where ...@@ -3,6 +3,7 @@ module Gargantext.Pages.Layout.Specs where
import Data.Foldable (fold, intercalate) import Data.Foldable (fold, intercalate)
import Data.Lens (over) import Data.Lens (over)
import Data.Maybe (Maybe(Nothing, Just)) import Data.Maybe (Maybe(Nothing, Just))
import Data.Tuple.Nested((/\))
import Effect (Effect) import Effect (Effect)
import React.DOM (button, div, text) import React.DOM (button, div, text)
import React.DOM.Props (_id, className, onClick, role, style) import React.DOM.Props (_id, className, onClick, role, style)
...@@ -11,11 +12,13 @@ import Reactix.DOM.HTML as H ...@@ -11,11 +12,13 @@ import Reactix.DOM.HTML as H
import Thermite (Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState, noState, cmapProps) import Thermite (Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState, noState, cmapProps)
-- import Unsafe.Coerce (unsafeCoerce) -- import Unsafe.Coerce (unsafeCoerce)
import Gargantext.BootstrapNative (createDropdown)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Data.Lang (Lang(..)) import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Components.Login.Types (AuthData(..)) import Gargantext.Components.Login.Types (AuthData(..))
import Gargantext.Components.Login as LN import Gargantext.Components.Login as LN
import Gargantext.Components.Tree as Tree import Gargantext.Components.Tree as Tree
import Gargantext.Config as C
import Gargantext.Folder as F import Gargantext.Folder as F
import Gargantext.Pages.Annuaire as A import Gargantext.Pages.Annuaire as A
import Gargantext.Pages.Annuaire.User.Contacts as C import Gargantext.Pages.Annuaire.User.Contacts as C
...@@ -26,9 +29,9 @@ import Gargantext.Pages.Corpus.Graph as GE ...@@ -26,9 +29,9 @@ import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Lists as Lists import Gargantext.Pages.Lists as Lists
import Gargantext.Pages.Texts as Texts import Gargantext.Pages.Texts as Texts
import Gargantext.Pages.Home as L import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _graphExplorerAction, _loginAction, performAction) import Gargantext.Pages.Layout.Actions (Action(..), _graphExplorerAction, _loginAction, performAction, _configStateAction)
import Gargantext.Pages.Layout.Specs.SearchBar as SB import Gargantext.Pages.Layout.Specs.SearchBar as SB
import Gargantext.Pages.Layout.States (AppState, _graphExplorerState, _loginState) import Gargantext.Pages.Layout.States (AppState, _graphExplorerState, _loginState, _configState)
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
...@@ -94,7 +97,7 @@ layout0 layout = ...@@ -94,7 +97,7 @@ layout0 layout =
withState \st -> withState \st ->
case st.loginState.authData of case st.loginState.authData of
Just (AuthData {tree_id}) -> Just (AuthData {tree_id}) ->
ls $ cmapProps (const {root: tree_id, mCurrentRoute: st.currentRoute}) $ Tree.treeview ls $ cmapProps (const {root: tree_id, mCurrentRoute: st.currentRoute, endConfig: st.configState.endConfig}) $ noState $ Tree.treeview
Nothing -> Nothing ->
outerLayout1 outerLayout1
, rs bs , rs bs
...@@ -140,7 +143,7 @@ layout1 layout = ...@@ -140,7 +143,7 @@ layout1 layout =
[ withState \st -> [ withState \st ->
case st.loginState.authData of case st.loginState.authData of
Just (AuthData {tree_id}) -> Just (AuthData {tree_id}) ->
ls $ cmapProps (const {root: tree_id, mCurrentRoute: st.currentRoute}) $ Tree.treeview ls $ cmapProps (const {root: tree_id, mCurrentRoute: st.currentRoute, endConfig: st.configState.endConfig}) $ noState $ Tree.treeview
Nothing -> Nothing ->
outerLayout1 outerLayout1
, rs bs , rs bs
...@@ -333,12 +336,51 @@ logLinks d s = case s.loginState.authData of ...@@ -333,12 +336,51 @@ logLinks d s = case s.loginState.authData of
[H.text " Logout"] [H.text " Logout"]
endConfigChooser :: R.State C.State -> R.Element
endConfigChooser (configState /\ setConfigState) = R.createElement el {} []
where
el = R.hooksComponent "EndConfigChooser" cpt
cpt {} _ = do
-- NOTE Need to rebind the component after rerender
R.useEffect $
pure $ createDropdown "end-config-chooser"
pure $ H.li {className: "dropdown"}
[ H.a { className: "navbar-text dropdown-toggle"
, href: "#"
, role: "button"
, data: {toggle: "dropdown"}
, id: "end-config-chooser"
}
[ H.text $ C.endConfigDisplayName configState.endConfig ]
, H.ul { className: "dropdown-menu"
} (liItem <$> C.endConfigOptions)
]
liItem :: C.EndConfigOption -> R.Element
liItem {endConfig, displayName} =
--H.li {on: {click: \_ -> setConfigState $ \st -> st {endConfig = endConfig}}}
H.li {}
[ H.a {href: "#"} [H.text displayName] ]
divDropdownRight :: (Action -> Effect Unit) -> AppState -> R.Element divDropdownRight :: (Action -> Effect Unit) -> AppState -> R.Element
divDropdownRight d s = divDropdownRight d s = R.createElement el {} []
H.ul {className: "nav navbar-nav pull-right"} where
[ H.li {className: "dropdown"} el = R.hooksComponent "DivDropdownRight" cpt
[ logLinks d s ] cpt {} _children = do
] (configState /\ setConfigState) <- R.useState' s.configState
R.useEffect $
if (configState /= s.configState) then do
pure $ d $ ConfigStateA $ C.UpdateState configState
else
pure $ pure $ unit
pure $ H.ul {className: "nav navbar-nav pull-right"}
[ endConfigChooser (configState /\ setConfigState)
, logLinks d s
]
layoutFooter :: Spec {} {} Void layoutFooter :: Spec {} {} Void
layoutFooter = R2.elSpec $ R.hooksComponent "LayoutFooter" cpt layoutFooter = R2.elSpec $ R.hooksComponent "LayoutFooter" cpt
......
...@@ -5,8 +5,8 @@ import Prelude hiding (div) ...@@ -5,8 +5,8 @@ import Prelude hiding (div)
import Data.Lens (Lens', lens) import Data.Lens (Lens', lens)
import Data.Maybe (Maybe(Just)) import Data.Maybe (Maybe(Just))
import Effect (Effect) import Effect (Effect)
import Gargantext.Config as C
import Gargantext.Components.Login as LN import Gargantext.Components.Login as LN
import Gargantext.Config (EndConfig, endConfigStateful)
import Gargantext.Pages.Corpus.Graph as GE import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Router (Routes(..)) import Gargantext.Router (Routes(..))
...@@ -18,7 +18,7 @@ type AppState = ...@@ -18,7 +18,7 @@ type AppState =
, showCorpus :: Boolean , showCorpus :: Boolean
, graphExplorerState :: GE.State , graphExplorerState :: GE.State
, showTree :: Boolean , showTree :: Boolean
, endConfig :: EndConfig , configState :: C.State
} }
initAppState :: Effect AppState initAppState :: Effect AppState
...@@ -31,7 +31,7 @@ initAppState = do ...@@ -31,7 +31,7 @@ initAppState = do
, showCorpus : false , showCorpus : false
, graphExplorerState : GE.initialState , graphExplorerState : GE.initialState
, showTree : false , showTree : false
, endConfig : endConfigStateful , configState : C.initialState
} }
...@@ -40,6 +40,9 @@ initAppState = do ...@@ -40,6 +40,9 @@ initAppState = do
_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})
_configState :: Lens' AppState C.State
_configState = lens (\s -> s.configState) (\s ss -> s{configState = 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