Commit 5f364a76 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[login] guess the backend upon login click

parent 9c0da593
...@@ -6,23 +6,23 @@ import Data.Array as Array ...@@ -6,23 +6,23 @@ import Data.Array as Array
import Data.Maybe (Maybe(..)) 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(..))
import Gargantext.Components.Lang.Landing.EnUS as En import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Nodes.Home.Public (renderPublic) import Gargantext.Components.Nodes.Home.Public (renderPublic)
import Gargantext.Config as Config
import Gargantext.Ends (Backend(..)) import Gargantext.Ends (Backend(..))
import Gargantext.License (license) import Gargantext.License (license)
import Gargantext.Sessions (Sessions) 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"
...@@ -87,8 +87,14 @@ homeLayoutCpt = here.component "homeLayout" cpt ...@@ -87,8 +87,14 @@ homeLayoutCpt = here.component "homeLayout" cpt
] where ] where
click mBackend _ = click mBackend _ =
case mBackend of case mBackend of
Nothing -> T.write_ true showLogin Nothing -> do
Just b -> pure unit mLoc <- Config.matchCurrentLocation
case mLoc of
Nothing -> pure unit
Just b -> do
T.write_ (Just b) backend
T.write_ true showLogin
Just b -> T.write_ true showLogin
joinButtonOrTutorial :: forall e. Sessions -> (e -> Effect Unit) -> R.Element joinButtonOrTutorial :: forall e. Sessions -> (e -> Effect Unit) -> R.Element
joinButtonOrTutorial sessions click = joinButtonOrTutorial sessions click =
......
...@@ -13,7 +13,7 @@ import Gargantext.Prelude (bind, pure, ($)) ...@@ -13,7 +13,7 @@ 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 (href)
defaultBackends :: NonEmpty Array Backend defaultBackends :: NonEmpty Array Backend
defaultBackends = defaultBackends =
...@@ -47,8 +47,8 @@ backend_local = backend V10 "/api/" localUrl "local.cnrs" ...@@ -47,8 +47,8 @@ backend_local = backend V10 "/api/" localUrl "local.cnrs"
matchCurrentLocation :: Effect (Maybe Backend) matchCurrentLocation :: Effect (Maybe Backend)
matchCurrentLocation = do matchCurrentLocation = do
url <- location href <- href
let starts = AN.filter (\(Backend { baseUrl }) -> S.startsWith baseUrl url) $ AN.fromNonEmpty defaultBackends let starts = AN.filter (\(Backend { baseUrl }) -> S.startsWith baseUrl href) $ AN.fromNonEmpty defaultBackends
pure $ A.head starts pure $ A.head starts
...@@ -60,9 +60,9 @@ publicBackend = backend_local ...@@ -60,9 +60,9 @@ publicBackend = backend_local
publicBackend' :: Effect Backend publicBackend' :: Effect Backend
publicBackend' = do publicBackend' = do
url <- location href <- href
pure $ Backend { name : "Public Backend" pure $ Backend { name : "Public Backend"
, baseUrl : url , baseUrl : href
, prePath : "api/" , prePath : "api/"
, version : V10 , version : V10
} }
......
module Gargantext.Utils where module Gargantext.Utils where
import DOM.Simple.Window (window)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Foldable (class Foldable, foldr) import Data.Foldable (class Foldable, foldr)
import Data.Lens (Lens', lens) import Data.Lens (Lens', lens)
...@@ -11,9 +10,10 @@ import Data.Sequence.Ordered as OSeq ...@@ -11,9 +10,10 @@ import Data.Sequence.Ordered as OSeq
import Data.String as S import Data.String as S
import Data.Unfoldable (class Unfoldable) import Data.Unfoldable (class Unfoldable)
import Effect (Effect) import Effect (Effect)
import FFI.Simple ((..))
import FFI.Simple.Functions (delay)
import Prelude import Prelude
import Web.HTML (window)
import Web.HTML.Window (location)
import Web.HTML.Location as WHL
-- | TODO (hard coded) -- | TODO (hard coded)
csrfMiddlewareToken :: String csrfMiddlewareToken :: String
...@@ -82,10 +82,6 @@ mapLeft :: forall l m r. (l -> m) -> Either l r -> Either m r ...@@ -82,10 +82,6 @@ mapLeft :: forall l m r. (l -> m) -> Either l r -> Either m r
mapLeft f (Left l) = Left (f l) mapLeft f (Left l) = Left (f l)
mapLeft _ (Right r) = Right r mapLeft _ (Right r) = Right r
-- | Get current Window Location
location :: Effect String
location = delay unit $ \_ -> pure $ window .. "location"
data On a b = On a b data On a b = On a b
instance eqOn :: Eq a => Eq (On a b) where instance eqOn :: Eq a => Eq (On a b) where
...@@ -102,3 +98,10 @@ sortWith :: forall a b f. Functor f => ...@@ -102,3 +98,10 @@ sortWith :: forall a b f. Functor f =>
Ord b => Ord b =>
(a -> b) -> f a -> f a (a -> b) -> f a -> f a
sortWith f = map (\(On _ y) -> y) <<< OSeq.toUnfoldable <<< foldr (\x -> OSeq.insert (On (f x) x)) OSeq.empty sortWith f = map (\(On _ y) -> y) <<< OSeq.toUnfoldable <<< foldr (\x -> OSeq.insert (On (f x) x)) OSeq.empty
href :: Effect String
href = do
w <- window
loc <- location w
WHL.href loc
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