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

[Array] some functions needed (same as in Data.List from Haskell) searching for it.

parent 871b5c71
...@@ -71,12 +71,11 @@ performAction NoOp _ _ = void do ...@@ -71,12 +71,11 @@ performAction NoOp _ _ = void do
performAction (SelectDatabase selected) _ _ = void do performAction (SelectDatabase selected) _ _ = void do
modifyState \( state) -> state { select_database = selected } modifyState \( state) -> state { select_database = selected }
performAction (UnselectDatabase unselected) _ _ = void do performAction (UnselectDatabase unselected) _ _ = void do
modifyState \( state) -> state { unselect_database = unselected } modifyState \( state) -> state { unselect_database = unselected }
performAction (LoadDatabaseDetails) _ _ = void do performAction (LoadDatabaseDetails) _ _ = void do
res <- lift $ getDatabaseDetails $ QueryString{query_query: "string",query_name: ["Pubmed"]} res <- lift $ getDatabaseDetails $ QueryString { query_query: "string",query_name: ["Pubmed"]}
case res of case res of
Left err -> cotransform $ \(state) -> state Left err -> cotransform $ \(state) -> state
Right resData -> do Right resData -> do
...@@ -173,7 +172,7 @@ layoutAddcorpus = simpleSpec performAction render ...@@ -173,7 +172,7 @@ layoutAddcorpus = simpleSpec performAction render
newtype QueryString = QueryString newtype QueryString = QueryString
{ {
query_query :: String query_query :: String
, query_name :: Array String , query_name :: Array String
} }
queryString :: QueryString queryString :: QueryString
......
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)
--
...@@ -217,7 +217,6 @@ divLogo = a [ className "navbar-brand logoSmall" ...@@ -217,7 +217,6 @@ divLogo = a [ className "navbar-brand logoSmall"
] [] ] []
] ]
divDropdownLeft :: ReactElement divDropdownLeft :: ReactElement
divDropdownLeft = ul [className "nav navbar-nav"] divDropdownLeft = ul [className "nav navbar-nav"]
[ ul [className "nav navbar-nav pull-left"] [ ul [className "nav navbar-nav pull-left"]
...@@ -231,8 +230,24 @@ divDropdownLeft = ul [className "nav navbar-nav"] ...@@ -231,8 +230,24 @@ divDropdownLeft = ul [className "nav navbar-nav"]
] [] ] []
, text " Info" , text " Info"
] ]
, ul [className "dropdown-menu"] , ul [className "dropdown-menu"] divLeftdropdownElements
(( map liNav [ LiNav { title : "Quick start, tutorials and methodology" ]
]
]
-- TODO
-- import Gargantext.Data.Array
-- 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 = (( map liNav [ LiNav { title : "Quick start, tutorials and methodology"
, href : "https://iscpif.fr/gargantext/your-first-map/" , href : "https://iscpif.fr/gargantext/your-first-map/"
, icon : "fas fa-book" , icon : "fas fa-book"
, text : "Documentation" , text : "Documentation"
...@@ -266,9 +281,6 @@ divDropdownLeft = ul [className "nav navbar-nav"] ...@@ -266,9 +281,6 @@ divDropdownLeft = ul [className "nav navbar-nav"]
) )
] ]
) )
]
]
]
data LiNav = LiNav { title :: String data LiNav = LiNav { title :: String
...@@ -296,42 +308,44 @@ liNav (LiNav { title:tit ...@@ -296,42 +308,44 @@ liNav (LiNav { title:tit
-- TODO put the search form in the center of the navBar -- TODO put the search form in the center of the navBar
divSearchBar :: ReactElement divSearchBar :: ReactElement
divSearchBar = ul [ className "nav navbar-nav", style { "margin-left" : "146px"}] divSearchBar = ul [ className "nav navbar-nav"
[ div [className "navbar-form"] , style { "margin-left" : "146px"}
[ input [ className "search-query" ] [ div [className "navbar-form"]
, placeholder "Query, URL or FILE (works with Firefox or Chromium browsers)" [ input [ className "search-query"
, _type "text" , placeholder "Query, URL or FILE (works with Firefox or Chromium browsers)"
, style { height: "35px" , _type "text"
, width : "450px" , style { height: "35px"
-- , color: "white" , width : "450px"
-- , background : "#A1C2D8" -- , color: "white"
} -- , background : "#A1C2D8"
] [] }
-- TODO add button in navbar (and "enter" execution) ] []
-- , div [] [button [][]] -- TODO add button in navbar (and "enter" execution)
] -- , div [] [button [][]]
]
] ]
--divDropdownRight :: Render AppState props Action --divDropdownRight :: Render AppState props Action
divDropdownRight :: ReactElement divDropdownRight :: ReactElement
divDropdownRight = ul [className "nav navbar-nav pull-right"] divDropdownRight =
[ ul [className "nav navbar-nav pull-right"]
-- TODO if logged in : enable dropdown to logout [
li [className "dropdown"] -- TODO if logged in : enable dropdown to logout
[ li [className "dropdown"]
a [ aria {hidden : true} [
, className "glyphicon glyphicon-log-in" a [ aria {hidden : true}
, href "#/login" , className "glyphicon glyphicon-log-in"
, style {color:"white"} , href "#/login"
, title "Log in and save your time" , style {color:"white"}
-- TODO hover: bold , title "Log in and save your time"
] -- TODO hover: bold
-- TODO if logged in ]
--, text " username" -- TODO if logged in
-- else --, text " username"
[text " Login / Signup"] -- else
] [text " Login / Signup"]
] ]
]
...@@ -367,8 +381,7 @@ layoutSpec :: forall eff props. Spec (E eff) AppState props Action ...@@ -367,8 +381,7 @@ layoutSpec :: forall eff props. Spec (E eff) AppState props Action
layoutSpec = layoutSpec =
fold fold
[ routingSpec [ routingSpec
, container $ , container $ withState pagesComponent
withState pagesComponent
] ]
where where
container :: Spec (E eff) AppState props Action -> Spec (E eff) AppState props Action container :: Spec (E eff) AppState props Action -> Spec (E eff) AppState props Action
......
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