Commit e3947a48 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev' into 289-dev-graph-view-refresh

parents a60c6c57 c9fdc900
......@@ -8,7 +8,7 @@ module Gargantext.Components.Forest
import Gargantext.Prelude
import Data.Array as A
import Data.Maybe (Maybe)
import Data.Maybe (Maybe(..))
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest.Tree (treeLoader)
import Gargantext.Ends (Frontends, Backend)
......@@ -80,7 +80,7 @@ forestCpt = here.component "forest" cpt where
-- TODO If `reloadForest` is set, `reload` state should be updated
-- TODO fix tasks ref
pure $ H.div { className: "forest " <> if showTree' then "" else "d-none" }
(A.cons (plus { handed, showLogin }) (trees handed' sessions'))
(A.cons (plus { backend, handed, showLogin }) (trees handed' sessions'))
where
common = RX.pick props :: Record Common
trees handed' sessions' = (tree handed') <$> unSessions sessions'
......@@ -97,14 +97,15 @@ forestCpt = here.component "forest" cpt where
, tasks } []
type Plus =
( handed :: T.Box Handed
( backend :: T.Box (Maybe Backend)
, handed :: T.Box Handed
, showLogin :: T.Box Boolean )
plus :: R2.Leaf Plus
plus p = R.createElement plusCpt p []
plusCpt :: R.Component Plus
plusCpt = here.component "plus" cpt where
cpt { handed, showLogin } _ = do
cpt { backend, handed, showLogin } _ = do
handed' <- T.useLive T.unequal handed
pure $ H.div { className: "row" }
......@@ -120,7 +121,9 @@ plusCpt = here.component "plus" cpt where
-- [ H.i { className: "material-icons md-36"} [] ]
where
click _ = do
-- _ <- T.write Nothing backend
-- NOTE Reset backend in case G.C.N.Home.homeLayout set that to (Just b)
-- from current url
_ <- T.write Nothing backend
T.write_ true showLogin
title = "Add or remove connections to the server(s)."
divClass = "fa fa-universal-access"
......
......@@ -239,7 +239,7 @@ folderIconCpt :: R.Component FolderIconProps
folderIconCpt = here.component "folderIcon" cpt
where
cpt { folderOpen, nodeType } _ = do
open <- T.read folderOpen
open <- T.useLive T.unequal folderOpen
pure $ H.a { className: "folder-icon", on: { click: \_ -> T.modify_ not folderOpen } }
[ H.i { className: GT.fldr nodeType open } [] ]
......
......@@ -52,7 +52,6 @@ type Props s v =
form :: forall s v. T.ReadWrite s Sessions => T.ReadWrite v Boolean
=> Record (Props s v) -> R.Element
form props = R.createElement formCpt props []
formCpt :: forall s v. T.ReadWrite s Sessions => T.ReadWrite v Boolean
=> R.Component (Props s v)
formCpt = here.component "form" cpt where
......
......@@ -3,7 +3,7 @@ module Gargantext.Components.Nodes.Home where
import Gargantext.Prelude
import Data.Array as Array
import Data.Maybe (fromJust)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Effect (Effect)
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
......@@ -12,12 +12,13 @@ import Gargantext.Components.Lang (LandingLang(..))
import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Nodes.Home.Public (renderPublic)
import Gargantext.Config as Config
import Gargantext.Ends (Backend(..))
import Gargantext.License (license)
import Gargantext.Sessions (Sessions)
import Gargantext.Sessions as Sessions
import Gargantext.Sessions.Types (Session(..))
import Gargantext.Utils.Reactix as R2
import Partial.Unsafe (unsafePartial)
import Reactix as R
import Reactix.DOM.HTML as H
import Routing.Hash (setHash)
......@@ -52,7 +53,8 @@ langLandingData LL_EN = En.landingData
------------------------------------------------------------------------
type HomeProps s l =
( lang :: LandingLang
( backend :: T.Box (Maybe Backend)
, lang :: LandingLang
, sessions :: s
, showLogin :: l
)
......@@ -60,12 +62,12 @@ type HomeProps s l =
homeLayout :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean
=> R2.Leaf (HomeProps s l)
homeLayout props = R.createElement homeLayoutCpt props []
homeLayoutCpt :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean
=> R.Component (HomeProps s l)
homeLayoutCpt = here.component "homeLayout" cpt
where
cpt { lang, sessions, showLogin } _ = do
cpt { backend, lang, sessions, showLogin } _ = do
backend' <- T.useLive T.unequal backend
sessions' <- T.useLive T.unequal sessions
let landingData = langLandingData lang
pure $
......@@ -73,7 +75,7 @@ homeLayoutCpt = here.component "homeLayout" cpt
[ H.div { className: "home-title container1" }
[ jumboTitle landingData ]
, H.div { className: "home-research-form container1" } [] -- TODO
, joinButtonOrTutorial sessions' click
, joinButtonOrTutorial sessions' (click backend')
, H.div { className: "home-public container1" }
[ renderPublic { }
, H.div { className:"col-12 d-flex justify-content-center" }
......@@ -83,19 +85,27 @@ homeLayoutCpt = here.component "homeLayout" cpt
, license
]
] where
click _
= T.write true showLogin
*> here.log "[homeLayout] Clicked: Join"
click mBackend _ =
case mBackend of
Nothing -> do
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 sessions click =
if Sessions.null sessions
then joinButton click
-- sessions is not empty
else tutorial {session: unsafePartial $ fromJust $ Array.head $ Sessions.unSessions sessions}
else tutorial {sessions: Sessions.unSessions sessions}
joinButton :: forall e. (e -> Effect Unit) -> R.Element
joinButton click =
-- TODO Add G.C.L.F.form -- which backend to use?
-- form { backend, sessions, visible }
H.div { className: divClass
, style: { paddingTop: "100px", paddingBottom: "100px" } }
[ H.button { className: buttonClass, title, on: { click } } [ H.text "Join" ] ] where
......@@ -136,17 +146,16 @@ summary =
, H.ol {} (map toSummary tutos) ] ]
toSummary (Tuto x) = H.li {} [ H.a {href: "#" <> x.id} [ H.text x.title ]]
tutorial :: R2.Leaf (session :: Session)
tutorial :: R2.Leaf (sessions :: Array Session)
tutorial props = R.createElement tutorialCpt props []
tutorialCpt :: R.Component (session :: Session)
tutorialCpt :: R.Component (sessions :: Array Session)
tutorialCpt = here.component "tutorial" cpt where
cpt {session: session@(Session {treeId})} _ = do
let nodeId = treeId
cpt {sessions} _ = do
let folders = makeFolders sessions
pure $ H.div { className: "mx-auto container" }
[ H.div {className: "d-flex justify-content-center"}
[FV.folderView {session, nodeId, backFolder: false}]
[ H.div {className: "d-flex justify-content-center"} [ H.table {} folders ]
, H.h1 {} [H.text "Welcome!"]
, H.h2 {} [H.text "For easy start, just watch the tutorials"]
, summary
......@@ -162,6 +171,13 @@ tutorialCpt = here.component "tutorial" cpt where
H.div { className : "alert " <> class', id: x.id}
[ video x.id, H.h4 {} [ H.text x.title ], H.p {} [ H.text x.text ] ]
makeFolders :: Array Session -> Array R.Element
makeFolders s = sessionToFolder <$> s where
sessionToFolder session@(Session {treeId, username, backend: (Backend {name})}) =
H.tr {} [
H.div { className: "d-flex justify-content-center" } [ H.text (username <> "@" <> name) ]
, H.div {} [ FV.folderView {session, nodeId: treeId, backFolder: false} ] ]
startTutos :: Array Tuto
startTutos =
[ Tuto { title: "The tree is your friend"
......
......@@ -352,8 +352,8 @@ home :: R2.Component Props
home = R.createElement homeCpt
homeCpt :: R.Component Props
homeCpt = here.component "home" cpt where
cpt props@{ boxes: boxes@{ sessions, showLogin } } _ = do
pure $ homeLayout { lang: LL_EN, sessions, showLogin }
cpt props@{ boxes: boxes@{ backend, sessions, showLogin } } _ = do
pure $ homeLayout { backend, lang: LL_EN, sessions, showLogin }
lists :: R2.Component SessionNodeProps
lists = R.createElement listsCpt
......
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.Utils as S
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Data.NonEmpty (NonEmpty, (:|), head)
import Gargantext.Prelude (bind, pure, ($))
import Gargantext.Ends
import Gargantext.Types (ApiVersion(..))
import Gargantext.Utils (location)
import Gargantext.Prelude (bind, pure, ($))
import Gargantext.Utils (href)
defaultBackends :: NonEmpty Array Backend
defaultBackends =
backend_local :| [ backend_prod, backend_partner, backend_demo, backend_dev ]
prodUrl :: String
prodUrl = "https://v4.gargantext.org"
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 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 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 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 V10 "/api/" "http://localhost:8008" "local.cnrs"
backend_local = backend V10 "/api/" localUrl "local.cnrs"
matchCurrentLocation :: Effect (Maybe Backend)
matchCurrentLocation = do
href <- href
let starts = AN.filter (\(Backend { baseUrl }) -> S.startsWith baseUrl href) $ AN.fromNonEmpty defaultBackends
pure $ A.head starts
-- | public Backend
......@@ -36,9 +60,9 @@ publicBackend = backend_local
publicBackend' :: Effect Backend
publicBackend' = do
url <- location
href <- href
pure $ Backend { name : "Public Backend"
, baseUrl : url
, baseUrl : href
, prePath : "api/"
, version : V10
}
......
......@@ -11,9 +11,10 @@ import Data.String as S
import Data.Unfoldable (class Unfoldable)
import DOM.Simple.Window (window)
import Effect (Effect)
import FFI.Simple ((..))
import FFI.Simple.Functions (delay)
import Prelude
import Web.HTML (window)
import Web.HTML.Window (location)
import Web.HTML.Location as WHL
-- | TODO (hard coded)
csrfMiddlewareToken :: String
......@@ -82,10 +83,6 @@ 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"
data On a b = On a b
instance eqOn :: Eq a => Eq (On a b) where
......@@ -102,3 +99,10 @@ sortWith :: forall a b f. Functor f =>
Ord b =>
(a -> b) -> f a -> f a
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