diff --git a/src/Gargantext/Components/Nodes/Home/Public.purs b/src/Gargantext/Components/Nodes/Home/Public.purs index cb0628a0d660072b2946ce7722c0d796d4c349b1..b3c7d7d75d5a4b99ca841c06450c2c6dae7a5f6d 100644 --- a/src/Gargantext/Components/Nodes/Home/Public.purs +++ b/src/Gargantext/Components/Nodes/Home/Public.purs @@ -1,10 +1,6 @@ module Gargantext.Components.Nodes.Home.Public where import DOM.Simple.Console (log) -import Effect (Effect) -import Effect.Class (liftEffect) -import DOM.Simple.Window (window) -import FFI.Simple.Functions ((...), delay) import Data.Tuple (fst) import Data.Argonaut as Argonaut import Data.Generic.Rep (class Generic) @@ -13,9 +9,10 @@ import Data.Maybe (Maybe(..)) import Data.NonEmpty (head) import Data.String (take) import Effect.Aff (Aff) -import Gargantext.Config (defaultBackends) +import Effect.Class (liftEffect) +import Gargantext.Config (publicBackend) import Gargantext.Config.REST (get) -import Gargantext.Ends (backendUrl) +import Gargantext.Ends (toUrl) import Gargantext.Prelude import Gargantext.Hooks.Loader (useLoader) import Gargantext.Utils.Argonaut (genericSumDecodeJson, genericSumEncodeJson) @@ -56,16 +53,10 @@ type LoadData = () type LoadProps = (reload :: Int) loadPublicData :: Record LoadProps -> Aff (Array PublicData) ---loadPublicData _l = get Nothing (backendUrl backend "public") loadPublicData _l = do - -- let backend = head defaultBackends - let windowLocation = "localhost:8008/" - windowLocation' <- liftEffect (location {}) - _ <- liftEffect $ log windowLocation' - get Nothing (windowLocation <> "public") - -location :: forall a. a -> Effect String -location _ = window ... "location" $ [] + backend <- liftEffect publicBackend + _ <- liftEffect (log backend) + get Nothing (toUrl backend "public") renderPublic :: R.Element renderPublic = R.createElement renderPublicCpt {} [] diff --git a/src/Gargantext/Config.purs b/src/Gargantext/Config.purs index 9902cc3228ab12cb12779c3454d815836706dd48..ef46a85d75e771ff293655542b7248d48b7e0434 100644 --- a/src/Gargantext/Config.purs +++ b/src/Gargantext/Config.purs @@ -1,8 +1,13 @@ module Gargantext.Config where +import Data.String as S +import Web.HTML.Location (Location(..)) +import Effect (Effect) import Data.NonEmpty (NonEmpty, (:|), head) import Gargantext.Ends import Gargantext.Types (ApiVersion(..)) +import Gargantext.Utils (location) +import Gargantext.Prelude (bind, pure, ($)) defaultBackends :: NonEmpty Array Backend defaultBackends = local :| [prod, partner, demo, dev] @@ -38,3 +43,18 @@ defaultStatic = head defaultStatics defaultFrontends :: Frontends defaultFrontends = Frontends { app: defaultApp, static: defaultStatic } +-- | public Backend +-- When user is not logged, use the location of the window +publicBackend :: Effect Backend +publicBackend = do + url <- location + pure $ Backend { name : "Public Backend" + , baseUrl : url + , prePath : "api/" + , version : V10 + } + +changePort :: String -> String +changePort = S.replace (S.Pattern "http://localhost:8000/") (S.Replacement "http://localhost:8008/") + + diff --git a/src/Gargantext/Utils.purs b/src/Gargantext/Utils.purs index 58e70491f6448a0d7170513a15861bb90945fa69..f8902c8e672b8909cfa0f41a4d3dbe7efe906be5 100644 --- a/src/Gargantext/Utils.purs +++ b/src/Gargantext/Utils.purs @@ -1,12 +1,17 @@ module Gargantext.Utils where -import Prelude +import DOM.Simple.Window (window) import Data.Either (Either(..)) import Data.Lens (Lens', lens) import Data.Newtype (class Newtype, unwrap, wrap) -import Data.Set as Set import Data.Set (Set) +import Data.Set as Set import Data.String as S +import Effect (Effect) +import Effect.Class (liftEffect) +import FFI.Simple ((..)) +import FFI.Simple.Functions (delay) +import Prelude -- | TODO (hard coded) csrfMiddlewareToken :: String @@ -74,3 +79,10 @@ queryMatchesLabel q l = S.contains (S.Pattern $ normalize q) (normalize l) mapLeft :: forall l m r. (l -> m) -> Either l r -> Either m r mapLeft f (Left l) = Left (f l) mapLeft _ (Right r) = Right r + +-- | Get current Window Location +location :: Effect String +location = delay unit $ \_ -> pure $ window .. "location" + + +