Commit 7588c9a6 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[MENU] WYSIWYG

parent fd0cc749
module Gargantext.Data.Array where
import Control.Monad.Aff.Console (log)
import Data.Array
--
---- | The 'intersperse' function takes an element and a list and
---- \`intersperses\' that element between the elements of the list.
---- For example,
----
---- >>> intersperse ',' "abcde"
---- "a,b,c,d,e"
--intersperse :: a -> [a] -> [a]
--intersperse _ [] = []
--intersperse sep (x:xs) = x : prependToAll sep xs
--
--
---- We want to make every element in the 'intersperse'd list available
---- as soon as possible to avoid space leaks. Experiments suggested that
---- a separate top-level helper is more efficient than a local worker.
--prependToAll :: a -> [a] -> [a]
--prependToAll _ [] = []
--prependToAll sep (x:xs) = sep : x : prependToAll sep xs
--
---- | 'intercalate' @xs xss@ is equivalent to @('concat' ('intersperse' xs xss))@.
---- It inserts the list @xs@ in between the lists in @xss@ and concatenates the
---- result.
----
---- >>> intercalate ", " ["Lorem", "ipsum", "dolor"]
---- "Lorem, ipsum, dolor"
--intercalate :: [a] -> [[a]] -> [a]
--intercalate xs xss = concat (intersperse xs xss)
--
...@@ -4,8 +4,10 @@ import DOM ...@@ -4,8 +4,10 @@ import DOM
import AddCorpusview as AC import AddCorpusview as AC
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import Data.Array (concat)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Foldable (fold) import Data.Foldable (fold, intercalate)
import Data.Lens (Lens', Prism', lens, over, prism) import Data.Lens (Lens', Prism', lens, over, prism)
import Data.Maybe (Maybe(Nothing, Just)) import Data.Maybe (Maybe(Nothing, Just))
import DocView as DV import DocView as DV
...@@ -161,7 +163,8 @@ routingSpec = simpleSpec performAction defaultRender ...@@ -161,7 +163,8 @@ routingSpec = simpleSpec performAction defaultRender
layout0 :: forall eff props. Spec (E eff) AppState props Action -> Spec (E eff) AppState props Action layout0 :: forall eff props. Spec (E eff) AppState props Action
-> Spec (E eff) AppState props Action
layout0 layout = layout0 layout =
fold fold
[ layoutSidebar [ layoutSidebar
...@@ -171,7 +174,8 @@ layout0 layout = ...@@ -171,7 +174,8 @@ layout0 layout =
, layoutFooter , layoutFooter
] ]
where where
innerLayout :: Spec (E eff) AppState props Action -> Spec (E eff) AppState props Action innerLayout :: Spec (E eff) AppState props Action
-> Spec (E eff) AppState props Action
innerLayout = over _render \render d p s c -> innerLayout = over _render \render d p s c ->
[ div [_id "page-wrapper"] [ div [_id "page-wrapper"]
[ [
...@@ -235,52 +239,48 @@ divDropdownLeft = ul [className "nav navbar-nav"] ...@@ -235,52 +239,48 @@ divDropdownLeft = ul [className "nav navbar-nav"]
] ]
] ]
-- TODO
-- import Gargantext.Data.Array -- WYSIWYG = Pure React
-- menu [[ LiNav, LiNav]
-- ,[ LiNav, LiNav]
-- ,[ LiNav ]
-- ]
-- where
-- menu = map linNav . foldl (\a b -> a <> b) . intercalate [divider]
-- where
-- divider = [li [className "divider"] []]
--
divLeftdropdownElements :: Array ReactElement divLeftdropdownElements :: Array ReactElement
divLeftdropdownElements = ( (map liNav [ LiNav { title : "Quick start, tutorials and methodology" divLeftdropdownElements = menu
, href : "https://iscpif.fr/gargantext/your-first-map/" [ -- ===========================================================
, icon : "fas fa-book" [ LiNav { title : "Quick start, tutorials and methodology"
, text : "Documentation" , href : "https://iscpif.fr/gargantext/your-first-map/"
} , icon : "fas fa-book"
, LiNav { title : "Report bug here" , text : "Documentation"
, href : "https://www.iscpif.fr/gargantext/feedback-and-bug-reports/" }
, icon : "glyphicon glyphicon-bullhorn" , LiNav { title : "Report bug here"
, text : "Feedback" , href : "https://www.iscpif.fr/gargantext/feedback-and-bug-reports/"
} , icon : "glyphicon glyphicon-bullhorn"
] , text : "Feedback"
) }
<> [li [className "divider"] []] <> ]
(map liNav [ LiNav { title : "Interactive chat" , -----------------------------------------------------------
, href : "https://chat.iscpif.fr/channel/gargantext" [ LiNav { title : "Interactive chat"
, icon : "fab fa-rocketchat" , href : "https://chat.iscpif.fr/channel/gargantext"
, text : "Chat" , icon : "fab fa-rocketchat"
} , text : "Chat"
, LiNav { title : "Asynchronous discussions" }
, href : "https://discourse.iscpif.fr/c/gargantext" , LiNav { title : "Asynchronous discussions"
, icon : "fab fa-discourse" , href : "https://discourse.iscpif.fr/c/gargantext"
, text : "Forum" , icon : "fab fa-discourse"
} , text : "Forum"
] }
) ]
<> [li [className "divider"] []] <> ,------------------------------------------------------------
[ liNav (LiNav { title : "More about us (you)" [ LiNav { title : "More about us (you)"
, href : "http://iscpif.fr" , href : "http://iscpif.fr"
, icon : "fas fa-question-circle" , icon : "fas fa-question-circle"
, text : "About" , text : "About"
} }
) ]
] ] -- ===========================================================
)
menu :: Array (Array LiNav) -> Array ReactElement
menu ns = intercalate divider $ map (map liNav) ns
where
divider :: Array ReactElement
divider = [li [className "divider"] []]
data LiNav = LiNav { title :: String data LiNav = LiNav { title :: String
......
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