Commit b0788423 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FOREST] CSS

parent effda708
...@@ -33,10 +33,9 @@ forestCpt = R.staticComponent "G.C.Forest.forest" cpt where ...@@ -33,10 +33,9 @@ forestCpt = R.staticComponent "G.C.Forest.forest" cpt where
plus :: R2.Setter Boolean -> R.Element plus :: R2.Setter Boolean -> R.Element
plus showLogin = plus showLogin =
H.button {on: {click}} H.button {on: {click}, className: "btn btn-primary"}
[ H.div { "type": "" [ H.div { "type": ""
, className: "fa fa-plus-circle fa-lg" , className: "fa fa-plus-circle fa-lg"
--, className: "glyphicon glyphicon-plus"
} [H.text "Login"] ] } [H.text "Login"] ]
-- TODO same as the one in the Login Modal (same CSS) -- TODO same as the one in the Login Modal (same CSS)
-- [ H.i { className: "material-icons md-36"} [] ] -- [ H.i { className: "material-icons md-36"} [] ]
......
...@@ -3,7 +3,7 @@ ...@@ -3,7 +3,7 @@
-- Select a backend and log into it -- Select a backend and log into it
module Gargantext.Components.Login where module Gargantext.Components.Login where
import Prelude (Unit, bind, const, discard, pure, flip, show, ($), (<>), (*>), (<$>), (>)) import Prelude (Unit, bind, const, discard, pure, flip, show, ($), (<>), (*>), (<$>), (>), map)
import Data.Array (head) import Data.Array (head)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Maybe (Maybe(..), fromMaybe) import Data.Maybe (Maybe(..), fromMaybe)
...@@ -103,15 +103,21 @@ chooserCpt = R.staticComponent "G.C.Login.chooser" cpt where ...@@ -103,15 +103,21 @@ chooserCpt = R.staticComponent "G.C.Login.chooser" cpt where
] else [] where ] else [] where
Sessions {sessions:ss} = fst sessions Sessions {sessions:ss} = fst sessions
new = [ H.h3 {} [H.text "New connection(s)"] new = [ H.h3 {} [H.text "New connection(s)"]
, H.ul {} [renderBackends backends backend ] , H.table {className : "table"}
[ H.thead {className: "thead-dark"} [ H.tr {} [ H.th {} [H.text "Label of instance"]
, H.th {} [H.text "Url garg protocole"]
, H.th {} [ H.text ""]
]
]
, H.tbody {} (map (renderBackend backend) backends)
]
] ]
renderSessions :: R2.Reductor Sessions Sessions.Action -> R.Element renderSessions :: R2.Reductor Sessions Sessions.Action -> R.Element
renderSessions sessions = R.fragment (renderSession sessions <$> unSessions (fst sessions)) renderSessions sessions = R.fragment (renderSession sessions <$> unSessions (fst sessions))
where
renderSession :: R2.Reductor Sessions Sessions.Action -> Session -> R.Element
renderSession :: R2.Reductor Sessions Sessions.Action -> Session -> R.Element renderSession sessions session = H.li {} $ [ H.text $ "Active session: " <> show session ]
renderSession sessions session = H.li {} $ [ H.text $ "Active session: " <> show session ]
<> [ H.a { on : {click} <> [ H.a { on : {click}
, className: "glyphitem glyphicon glyphicon-log-out" , className: "glyphitem glyphicon glyphicon-log-out"
, id : "log-out" , id : "log-out"
...@@ -120,23 +126,16 @@ renderSession sessions session = H.li {} $ [ H.text $ "Active session: " <> show ...@@ -120,23 +126,16 @@ renderSession sessions session = H.li {} $ [ H.text $ "Active session: " <> show
where where
click _ = (snd sessions) (Sessions.Logout session) click _ = (snd sessions) (Sessions.Logout session)
renderBackends :: Array Backend -> R.State (Maybe Backend) -> R.Element
renderBackends backends state = R.fragment $ (flip renderBackend $ state) <$> backends
{-
renderBackend :: Backend -> R.State (Maybe Backend) -> R.Element
renderBackend backend@(Backend {name}) state =
H.li {} [ H.a {on: {click}, className: glyphicon "log-in"} [ H.text $ "Connect to " <> name ] ] where
click _ = (snd state) (const $ Just backend)
-}
renderBackend :: Backend -> R.State (Maybe Backend) -> R.Element renderBackend :: R.State (Maybe Backend) -> Backend -> R.Element
renderBackend backend@(Backend {name}) state = renderBackend state backend@(Backend {name}) =
H.li {} $ [ H.div {className: "flex-space-between"} [ H.a { on : {click}} [H.text label], H.div {}[H.text url]] ] H.tr {} [ H.td {} [H.a { on : {click}} [H.text label]]
<> [ H.a { on : {click} , H.td {} [ H.text url ]
, H.td {} [H.a { on : {click}
, className : "glyphitem glyphicon glyphicon-log-in" , className : "glyphitem glyphicon glyphicon-log-in"
, title: "Log In"} [] , title: "Log In"} []
] ]
]
where where
click _ = (snd state) (const $ Just backend) click _ = (snd state) (const $ Just backend)
label = DST.toUpper $ fromMaybe "" $ head $ DST.split (DST.Pattern ".") name label = DST.toUpper $ fromMaybe "" $ head $ DST.split (DST.Pattern ".") name
......
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