Commit 9c0da593 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[login page] some url refactoring

parent d711e6ce
...@@ -52,7 +52,6 @@ type Props s v = ...@@ -52,7 +52,6 @@ type Props s v =
form :: forall s v. T.ReadWrite s Sessions => T.ReadWrite v Boolean form :: forall s v. T.ReadWrite s Sessions => T.ReadWrite v Boolean
=> Record (Props s v) -> R.Element => Record (Props s v) -> R.Element
form props = R.createElement formCpt props [] form props = R.createElement formCpt props []
formCpt :: forall s v. T.ReadWrite s Sessions => T.ReadWrite v Boolean formCpt :: forall s v. T.ReadWrite s Sessions => T.ReadWrite v Boolean
=> R.Component (Props s v) => R.Component (Props s v)
formCpt = here.component "form" cpt where formCpt = here.component "form" cpt where
......
...@@ -3,8 +3,14 @@ module Gargantext.Components.Nodes.Home where ...@@ -3,8 +3,14 @@ module Gargantext.Components.Nodes.Home where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Array as Array import Data.Array as Array
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Effect (Effect) import Effect (Effect)
import Reactix as R
import Reactix.DOM.HTML as H
import Routing.Hash (setHash)
import Toestand as T
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..)) import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
import Gargantext.Components.FolderView as FV import Gargantext.Components.FolderView as FV
import Gargantext.Components.Lang (LandingLang(..)) import Gargantext.Components.Lang (LandingLang(..))
...@@ -17,10 +23,6 @@ import Gargantext.Sessions (Sessions) ...@@ -17,10 +23,6 @@ import Gargantext.Sessions (Sessions)
import Gargantext.Sessions as Sessions import Gargantext.Sessions as Sessions
import Gargantext.Sessions.Types (Session(..)) import Gargantext.Sessions.Types (Session(..))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Routing.Hash (setHash)
import Toestand as T
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Home" here = R2.here "Gargantext.Components.Nodes.Home"
...@@ -51,7 +53,8 @@ langLandingData LL_EN = En.landingData ...@@ -51,7 +53,8 @@ langLandingData LL_EN = En.landingData
------------------------------------------------------------------------ ------------------------------------------------------------------------
type HomeProps s l = type HomeProps s l =
( lang :: LandingLang ( backend :: T.Box (Maybe Backend)
, lang :: LandingLang
, sessions :: s , sessions :: s
, showLogin :: l , showLogin :: l
) )
...@@ -59,12 +62,12 @@ type HomeProps s l = ...@@ -59,12 +62,12 @@ type HomeProps s l =
homeLayout :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean homeLayout :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean
=> R2.Leaf (HomeProps s l) => R2.Leaf (HomeProps s l)
homeLayout props = R.createElement homeLayoutCpt props [] homeLayout props = R.createElement homeLayoutCpt props []
homeLayoutCpt :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean homeLayoutCpt :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean
=> R.Component (HomeProps s l) => R.Component (HomeProps s l)
homeLayoutCpt = here.component "homeLayout" cpt homeLayoutCpt = here.component "homeLayout" cpt
where where
cpt { lang, sessions, showLogin } _ = do cpt { backend, lang, sessions, showLogin } _ = do
backend' <- T.useLive T.unequal backend
sessions' <- T.useLive T.unequal sessions sessions' <- T.useLive T.unequal sessions
let landingData = langLandingData lang let landingData = langLandingData lang
pure $ pure $
...@@ -72,7 +75,7 @@ homeLayoutCpt = here.component "homeLayout" cpt ...@@ -72,7 +75,7 @@ homeLayoutCpt = here.component "homeLayout" cpt
[ H.div { className: "home-title container1" } [ H.div { className: "home-title container1" }
[ jumboTitle landingData ] [ jumboTitle landingData ]
, H.div { className: "home-research-form container1" } [] -- TODO , H.div { className: "home-research-form container1" } [] -- TODO
, joinButtonOrTutorial sessions' click , joinButtonOrTutorial sessions' (click backend')
, H.div { className: "home-public container1" } , H.div { className: "home-public container1" }
[ renderPublic { } [ renderPublic { }
, H.div { className:"col-12 d-flex justify-content-center" } , H.div { className:"col-12 d-flex justify-content-center" }
...@@ -82,9 +85,10 @@ homeLayoutCpt = here.component "homeLayout" cpt ...@@ -82,9 +85,10 @@ homeLayoutCpt = here.component "homeLayout" cpt
, license , license
] ]
] where ] where
click _ click mBackend _ =
= T.write true showLogin case mBackend of
*> here.log "[homeLayout] Clicked: Join" Nothing -> T.write_ true showLogin
Just b -> pure unit
joinButtonOrTutorial :: forall e. Sessions -> (e -> Effect Unit) -> R.Element joinButtonOrTutorial :: forall e. Sessions -> (e -> Effect Unit) -> R.Element
joinButtonOrTutorial sessions click = joinButtonOrTutorial sessions click =
...@@ -94,6 +98,8 @@ joinButtonOrTutorial sessions click = ...@@ -94,6 +98,8 @@ joinButtonOrTutorial sessions click =
joinButton :: forall e. (e -> Effect Unit) -> R.Element joinButton :: forall e. (e -> Effect Unit) -> R.Element
joinButton click = joinButton click =
-- TODO Add G.C.L.F.form -- which backend to use?
-- form { backend, sessions, visible }
H.div { className: divClass H.div { className: divClass
, style: { paddingTop: "100px", paddingBottom: "100px" } } , style: { paddingTop: "100px", paddingBottom: "100px" } }
[ H.button { className: buttonClass, title, on: { click } } [ H.text "Join" ] ] where [ H.button { className: buttonClass, title, on: { click } } [ H.text "Join" ] ] where
......
...@@ -361,8 +361,8 @@ home = R.createElement homeCpt ...@@ -361,8 +361,8 @@ home = R.createElement homeCpt
homeCpt :: R.Component Props homeCpt :: R.Component Props
homeCpt = here.component "home" cpt where homeCpt = here.component "home" cpt where
cpt props@{ boxes: boxes@{ sessions, showLogin } } _ = do cpt props@{ boxes: boxes@{ backend, sessions, showLogin } } _ = do
pure $ homeLayout { lang: LL_EN, sessions, showLogin } pure $ homeLayout { backend, lang: LL_EN, sessions, showLogin }
lists :: R2.Component SessionNodeProps lists :: R2.Component SessionNodeProps
lists = R.createElement listsCpt lists = R.createElement listsCpt
......
module Gargantext.Config where module Gargantext.Config where
import Data.Array as A
import Data.Maybe (Maybe)
import Data.Array.NonEmpty as AN
import Data.NonEmpty (NonEmpty, (:|), head)
import Data.String as S import Data.String as S
import Data.String.Utils as S
import Data.Tuple.Nested ((/\))
import Effect (Effect) import Effect (Effect)
import Data.NonEmpty (NonEmpty, (:|), head)
import Gargantext.Prelude (bind, pure, ($))
import Gargantext.Ends import Gargantext.Ends
import Gargantext.Types (ApiVersion(..)) import Gargantext.Types (ApiVersion(..))
import Gargantext.Utils (location) import Gargantext.Utils (location)
import Gargantext.Prelude (bind, pure, ($))
defaultBackends :: NonEmpty Array Backend defaultBackends :: NonEmpty Array Backend
defaultBackends = defaultBackends =
backend_local :| [ backend_prod, backend_partner, backend_demo, backend_dev ] backend_local :| [ backend_prod, backend_partner, backend_demo, backend_dev ]
prodUrl :: String
prodUrl = "https://v4.gargantext.org"
backend_prod :: Backend backend_prod :: Backend
backend_prod = backend V10 "/api/" "https://v4.gargantext.org" "iscpif.cnrs" backend_prod = backend V10 "/api/" prodUrl "iscpif.cnrs"
partnerUrl :: String
partnerUrl = "https://imtv4.gargantext.org"
backend_partner :: Backend backend_partner :: Backend
backend_partner = backend V10 "/api/" "https://imtv4.gargantext.org" "institut-mines-telecom.imt" backend_partner = backend V10 "/api/" partnerUrl "institut-mines-telecom.imt"
demoUrl :: String
demoUrl = "https://demo.gargantext.org"
backend_demo :: Backend backend_demo :: Backend
backend_demo = backend V10 "/api/" "https://demo.gargantext.org" "demo.inshs.cnrs" backend_demo = backend V10 "/api/" demoUrl "demo.inshs.cnrs"
devUrl :: String
devUrl = "https://dev.gargantext.org"
backend_dev :: Backend backend_dev :: Backend
backend_dev = backend V10 "/api/" "https://dev.gargantext.org" "devel.inshs.cnrs" backend_dev = backend V10 "/api/" devUrl "devel.inshs.cnrs"
localUrl :: String
localUrl = "http://localhost:8008"
backend_local :: Backend backend_local :: Backend
backend_local = backend V10 "/api/" "http://localhost:8008" "local.cnrs" backend_local = backend V10 "/api/" localUrl "local.cnrs"
matchCurrentLocation :: Effect (Maybe Backend)
matchCurrentLocation = do
url <- location
let starts = AN.filter (\(Backend { baseUrl }) -> S.startsWith baseUrl url) $ AN.fromNonEmpty defaultBackends
pure $ A.head starts
-- | public Backend -- | public Backend
......
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